definition of take

2005-02-16 Thread Jorge Adriano Aires
Hi, 
I don't know much about the internals of GHC, but I like look around once in a 
while to learn a few things. I was wondering about the definition of take, 
which is, for Ints:

-
takeUInt :: Int# - [b] - [b]
takeUInt n xs
  | n =# 0#  =  take_unsafe_UInt n xs
  | otherwise =  []

take_unsafe_UInt :: Int# - [b] - [b]
take_unsafe_UInt 0#  _  = []
take_unsafe_UInt m   ls =
  case ls of
[] - []
(x:xs) - x : take_unsafe_UInt (m -# 1#) xs
-

Wouldn't pattern matching against 1# instead of 0#, like in the following 
definition, be better in terms of garbage collecting the list or what it 
depends on? 

---
takeUInt :: Int# - [b] - [b]
takeUInt 0# _ =  []
takeUInt n xs
  | n # 0#   =  take_unsafe_UInt n xs
  | otherwise =  []

take_unsafe_UInt :: Int# - [b] - [b]
take_unsafe_UInt 1#  (x:xs)  = [x]
take_unsafe_UInt m   ls  =
  case ls of
[] - []
(x:xs) - x : take_unsafe_UInt (m -# 1#) xs
--

My guess would be that, if we're consuming a (take n xs) lazily, with the 
first definition garbage collecting would happen when the last element had 
been consumed  and with the second, when the last element had been produced - 
(which is when we find out there are no more elements to consume in each 
case).

Thanks, and sorry if the question is to naive,
J.A.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] mathematical notation and functional programming

2005-01-28 Thread Jorge Adriano Aires

 Things I'm unhappy about are for instance

 f(x) \in L(\R)
where f \in L(\R) is meant

 F(x) = \int f(x) \dif x
where x shouldn't be visible outside the integral

 O(n)
which should be O(\n - n) (a remark by Simon Thompson in
The Craft of Functional Programming)
 f(.)
which means \x - f x or just f

All of these are the same notation abuse,
sometimes f x is meant to be interpreted as \x-f x

In some cases it would be really tedious to add the extra lambdas, so the 
expression used in its definition is used to denote the function itself. 

 a  b  c
which is a short-cut of a  b \land b  c

Both, ambiguity and complex notation, can lead to (human) parsing problems, 
which is what we are trying to minimise here.

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Jorge Adriano Aires

  How can I convert an Int into a Double?
 
  You don't convert to, you convert from :-)
  The function 'fromIntegral' is probably what you want.

 And what function can I use to convert from Double to Int (the inverse of
 fromIntegral) ?

Use the functions in the RealFrac class.
http://www.haskell.org/onlinereport/standard-prelude.html#$tRealFrac

class  (Real a, Fractional a) = RealFrac a  where
 properFraction   :: (Integral b) = a - (b,a)
 truncate, round  :: (Integral b) = a - b
 ceiling, floor   :: (Integral b) = a - b

J.A.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Jorge Adriano Aires
On Tuesday 25 January 2005 02:25, Jan-Willem Maessen wrote:
 On Jan 24, 2005, at 8:53 PM, Jorge Adriano Aires wrote:
  And it would say nothing about things like:
  return 4  return 5  ==?== return 5
  I can live with it.

 I feel obliged to point out (because the repeated references to the
 question are driving me up the wall) that this simple equality holds in
 every monad:


 return 4  return 5
 ...
 return 5

Opss, of course...

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using Map rather than FiniteMap

2005-01-25 Thread Jorge Adriano Aires

 Just did a search after my last post and learned
 that FiniteMap is bad.  Discoverd that Data.Map is
 the intended replacement.  Downloaded it and
 modified it to work with 6.2.  Blazingly fast!

 Yay.

Hi, just curious, 
How much trouble was getting it to work with ghc 6.2 and adapting your program 
to use the API of Data.Map instead of Data.FiniteMap?

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 Right, but we are dealing with the type system here. Remember Haskell
 monoids are functors on types, not on values ... (ie the base objects the
 'category theory' is applied to are the types not the values)...

 Therefore we only consider the types when considering Monads.

How so? Functors map morphisms and objects from one category into another.

class Functor f where 
  fmap :: (a-b) - f b - f a 

We have the two maps there. 
- The type constructor, maps the objects  (types).
- The fmap higher order function, maps the morphisms (function between types).

Monads are, in particular, functors. So again, the type constructor maps the 
objects (types) and the mapping on morphisms (functions from one type to the 
other) is given by liftM (that is, fmap = liftM).

Like Ashley Yakeley said, we can have many different functions (morphism) 
between two types, namely IO a types.

 As such if you wished to consider the examples you gave distinct, the
 type system would need to distinguish side effects... 

Why? I don't see how side effects make any difference here... How do you 
distinguish morphisms f and g:

f,g :: Int - Int
f n = 2*n
g n = 2+n

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 We face a severe problem here, not only that IO a is not an instance of Eq,
 which takes this whole discussion outside the realm of Haskell, on top of

 that we find the horrible fact that x /= x may be true in the IO Monad,
 consider

 x = getLine = putStrLn

 or anything similar  -- actually we already have getChar /= getChar

This isn't obvious to me. So x is an action, and it does not always produces 
the same side effects when executed. But why should that make x/=x? It is the 
same action, it gets one line from the input, and then prints it...

In fact, I do not agree. See Rant 2 below.


 The sad truth is that IO actions in general aren't well defined entities
 (unless we index them with the space-time-coordinates of their invocation).
 So I suggest ending the discussion by agreeing that the question whether or
 not
 x  mzero == mzero 
 holds in the IO-Monad is meaningless (at least, it's fruitless).
 If you cannot agree, I have another question: is

 return 4  return 5 == return 5

 true in the IO-Monad?

Yeap, I thought about it too, have no idea, and cannot afford to spend much 
time thinking about it now either, since I got work to do... :-/ 

--- Rant 1
My gut feeling would be no. I think my intuitive reasoning is too just 
consider that, every IO action is equal to itself, then take the closure with 
respect to function application, and assume all others cannot be proved. That 
is,

x === x,  for all   x :: IO a 
f x === g x, for all   x :: a  and  f,g :: a - IO b,  such that f === g

Where equality between functions is defined the usual way.


--- Rant 2

Nope, we have to have getChar === getChar.

I think you'll agree if I say that we have:
1. return === return 
2- return 5 === return 5 
return 5   return 5 ===  return 5  return 5

Because this has nothing to do with IO.  
1. We have that, return :: a-IO a  is a function, not an action, so it must 
be equal to itself. 

2. We have that, return :: a-IO a  is a function, not an action, so it must 
return the same value when applied to the same element.  

3.  () :: (Monad m) = m a - m b - m b   
It is also a function, so  () x ===  () x. 
And by the same reasoning () x y ===  () x y. 
So from 2 we have 3.

A constant c :: a  is just morphism(function) c : 0 - a, where 0 is the 
initial object (empty set).  So we must have c === c. 
Which means getChar === getChar.

In other words, by questioning wether you can have  x ==/= x for x :: IO a, 
you are questioning wether we really have f === f for all functions f::a-b.
---

  return hello = putStrLn
 
  this does not only have the same type as putStrLn hello, and return
  the same value (), but it also carries out exactly the same actions.

 But does it really? hugs thinks otherwise:
 Prelude putStrLn hello
 hello
 ()
 (28 reductions, 55 cells)
 Prelude return hello = putStrLn
 hello
 ()
 (31 reductions, 56 cells)
 Prelude putStrLn hello
 hello
 ()
 (26 reductions, 50 cells)

 even the same input does not necessarily lead to exactly the same actions,
 depending on whether hello is already known or not.

This I don't agree with, I think you are using the word actions for two 
different things, the elements of type IO a, and their execution. What you 
just showed is that those IO () elements (actions) when executed, always 
created different side effects in the real world. Not that the actions 
themselves are different. 

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 A constant c :: a  is just morphism(function) c : 0 - a, where 0 is the
 initial object (empty set). 

--- Rant2 correction
Opss I messed up here. Should be terminal should 1- a  (terminal object/unit 
set). At least that's how I usually think of constants  in haskell  1 is 
()... so I think I don't know what is a constant in Haskell... Anyway, 
stopping now.

J.A.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires

 This isn't obvious to me. So x is an action, and it does not always
  produces the same side effects when executed. But why should that make
  x/=x? It is the same action, it gets one line from the input, and then
  prints it...

 OK, but then the different side-effects could not be used to distinguish
 putStrLn hello  mzero
 and mzero. So I still believe, if you say these two are different, because
 they produce different output, you cannot easily insist on x === x.

Agree. But I don't say that. 

  This I don't agree with, I think you are using the word actions for two
  different things, the elements of type IO a, and their execution. What
  you

 You're right, but one of my problems is to identify elements of type IO a.
 If the returned value isn't the thing, the execution must matter, but which
 parts of the execution are to be taken into account?

How can we tell if  functions f === g? They must have the same domain, 
codomain and return the same result for every element of the domain. This is 
just the mathematical definition. For any two arbitrary functions f,g, can 
you tell if they are the same or not?

As a definition, I'd be happy to have, x,y :: IO a are the same if, given the 
same, real world, they produce the same effects and return the same result. 

Now I'm not saying we can derive that x === x, for x ::IO, from that, but it 
is certainly consistent with that point of view, so we can take it as an 
axiom. Which I think we already do. We also have that if f === g than  f x 
=== g x. That includes functions of type  f,g :: a - IO b. All seems 
consistent. 

Any other equality relation should include that one. 

Is it enough? It's enough to be able to tell that:
putStrLn hello  return 3 === putStrLn (he++llo) =\ _ return (1+2)

And it would say nothing about things like: 
return 4  return 5  ==?== return 5 
I can live with it.


To prove that two functions are in deed the same, we may use, say, number 
theory knowledge, which falls outside the scope of haskell. I find it 
sensible to do the same with actions. Maybe (not sure) it is sensible to 
specify return::(a - IO a), as an action with no side effects such that  
return x === return x  iff  x === x. If we add that to our knowledge of IO, 
along with an appropriate specification for (=), then we would have:
return 4  return 5  === return 5 

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Jorge Adriano Aires
(Sorry about the recurrent self answers)

 Maybe (not sure) it is sensible to
 sapecify return::(a - IO a), as an action with no side effects such that

 return x === return x  iff  x === x. 
return x === return y iff x === y-- this is what I meant to write.

But even that is not enough, should be:
return x is an action with no side effects and that always returns x 

The previous specification is be a consequence of this one, and it failed to 
specify that the returned value was always x.

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires
 What would happen if this was the definition?
 
 instance MonadPlus [] where
mzero = []
mplus a b
 
| a == [] = b
| otherwise = a

 Isn't the above a monoid as well?

Yes.

 Is there only on correct definition of a monad/monoid on lists - or does
 anything that satisfies the monad laws count? I got the impression you
 could define anthing you liked for mzero and mplus - providing the laws
 are upheld?

I'm not arguing that definition would be wrong. It is a monoid. This is the 
instance for ():

instance MonadPlus() where
  mzero = ()
  mplus a b = ()


And this would be correct too:

instance MonadPlus Maybe where
  mzero = Nothing
  mplus a b = Nothing

instance MonadPlus [] where
  mzero = []
  mplus a b = []

Which are not really useful. I'm claiming that the fact that Maybe is a 
trivial Monoid doesn't mean we should dumb down other instances, like the 
one on lists. The usual definition of Monoid on lists is [] as identity and 
++ as the monoid operation. That is how it's defined  in class monoid, and I 
expect this relation to hold:

instance MonadPlus m = Monoid (m a) where
   mempty = mzero
   mappend = mplus


 Then, I'd say you're not thinking of monadic sums, but of catching errors,
  and the appropriate place for that is the class MonadError.

 I am thinking about how some monads are summed - like Maybe and
 the Parser monad.

But, this is not how monadic parsers are summed. Just look into the instace of 
MonadError for Text.ParserCombinators.ReadP.P. Again it would be the case for 
parsers that would return just one possible parsing, but not for parsers that 
return [(a,String)].

J.A.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires

  One common example is using MonadPlus for some backtracking algorithm,
  then instantiatiating it to Maybe or List instance depending on wether
  you just want one solution or all of them.

 Backtracking only works with the first kind, even if you're only
 interested in the first solution. This must hold:

   (mplus a b) = c = mplus (a = c) (b = c)

Not really. If the recursive call is something like msum 
[all_possible_paths], then you are backtracking. The difference is that by 
using Maybe you'll stop as soon as you succeed, and with list you will find 
all possible paths. 

I don't have a small, self-contained, example at hand so I'll use one by 
Carsten Schultz that I once saw posted in comp.lang.functional. Hope he 
doesn't mind. 

http://groups-beta.google.com/group/comp.lang.functional/msg/d7ac1fe1684ef840
-- ---
-- knapsack problem 

module Subset2 where
import Control.Monad

sss :: MonadPlus m = Int - [Int] - m [Int]
sss n [] | n0 = mzero
sss n (x:xs) = 
case compare n x 
of LT - mzero
   EQ - return [x]
   GT - liftM (x:) (sss (n-x) xs) `mplus` sss n xs
-- ---
sss 40 [3, 8, 9, 13, 14, 15, 17, 19] :: [[Int]]
[[3,8,14,15],[3,9,13,15],[8,13,19],[8,15,17],[9,14,17]]

sss 40 [3, 8, 9, 13, 14, 15, 17, 19] :: Maybe [Int]
Just [3,8,14,15]


  [*] For instance, I've missed Maybe being an instance of MonadError.
 You could define your own instance, of course.

Yes of course, and I did ;)  But I think it should be provided nontheless, and 
I even find the fact that it isn't is playing a big part in all this 
confusion. Since there is no MonadError instance for Maybe, we end up using 
its MonadPlus instance, which just happens to be the same. But it cannot be 
generalized, for other types.

Lets forget about lists, think (Either e). It's usual to move from (Maybe a) 
to (Either e a) to consider more than one kind of error. But, there is no 
natural instance of MonadPlus for (Either e a). What would mzero be? 

Yet, the Maybe like, mplus operation makes perfect sense in (Either e) or 
any other MonadError, though. You don't need Monoids at all, what you need is 
the concept of error. Just define it as:

skipError x y = catchError x (\_-y)

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires

 I think it would be helpful if all these classes came with their laws
 prominently attached in their Haddock documentation or wherever. 
Agree.

 The  trouble with MonadPlus is that the precise set of associated laws is
 either unspecified or not the most useful (I assume there's a paper on
 the class somewhere). I think everyone can agree on these:

   mplus mzero a = a
   mplus a mzero = a
   mplus (mplus a b) c = mplus a (mplus b c)
snip
   (mplus a b) = c = mplus (a = c) (b = c)

I just checked the paper,
A monadic Interpretation of Tatics, by Andrew Martin and Jeremy Gibbons
http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/tactics.pdf

And in deed, these are the listed laws for MonadPlus. On the other hand, Maybe 
is said to be an instance of MonadPlus.

So now I'm lost. 

Cheers,
J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-23 Thread Jorge Adriano Aires

 Am Sonntag, 23. Januar 2005 15:58 schrieb Jorge Adriano Aires:
  I'm not arguing that definition would be wrong. It is a monoid. This is
  the instance for ():
 
  instance MonadPlus() where
mzero = ()
mplus a b = ()

 Maybe I'm stupid, but:

 class Monad m = MonadPlus m where
 mzero :: m a
 mplus :: m a - m a - m a

 How does () fit into this, () isn't of kind * - *, as far as I know
 () Int is meaningless -- just checked, gives Kind Error.


Nope, I am. Sorry! I was alternating between monoids and monadplus, and came 
up with that nonsense. I was obviously thinking about Monoid () and not 
MonadPlus (). 


  And this would be correct too:
 
  instance MonadPlus Maybe where
mzero = Nothing
mplus a b = Nothing
 
  instance MonadPlus [] where
 
mzero = []
mplus a b = []

 Both aren't correct, since mzero `mplus` x == x
 doesn't hold (they're syntactically correct, though).

Yeap. You are right again. Sorry for this terrible example, please ignore it.

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-22 Thread Jorge Adriano Aires
 But only some instances (such as []) satisfy this:

   (mplus a b) = c = mplus (a = c) (b = c)

 Other instances (IO, Maybe) satisfy this:

   mplus (return a) b = return a

 I think mplus should be separated into two functions. 

How would we implement the first kind in the Maybe instance of MonadPlus?

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-22 Thread Jorge Adriano Aires
snip
 Only the monoid Maybe a is not very nice (nor is the monoid IO a),since the 
 second argument of the composition is in  general ignored. 

snip

 So I think, rather than separating mplus, one should think about whether it
 is sensible to make Maybe and IO instances of MonadPlus in the first place.
 I don't know nearly enough of the innards of Haskell to form a valuable
 opinion of that, but perhaps somebody could enlighten me?

My humble opinion follows. 

It's still a Monoid, being boring should be no reason not to include it [*]. 
By taking advantage of typeclasses, we can easily alternate between more 
elaborate approaches and dull ones (if we have the dull ones available too). 

One common example is using MonadPlus for some backtracking algorithm, then 
instantiatiating it to Maybe or List instance depending on wether you just 
want one solution or all of them. 

[*] For instance, I've missed Maybe being an instance of MonadError. 

Greetings,
J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Implicit parameters:

2005-01-19 Thread Jorge Adriano Aires
Isn't it just the monomorphism restriction at work?
This works fine:

 f () = do
    a - get_unique
    putStr (showInt a \n)
    b - get_unique
    putStr (showInt b \n)
    c - get_unique
    putStr (showInt c \n)                                                    
              
                                                            

 get_unique :: (?global_counter :: IORef Int) = IO Int
 get_unique = readIORef ?global_counter


J.A.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Top Level etc.

2005-01-19 Thread Jorge Adriano Aires
 Perhaps one could have top-level implicit parameters (or top-level
 contexts in general):

 module (?myvar :: IORef Int) = Random where

Hi!
I suggested something very similar to this some months ago, syntax and all. 
Nice to see I'm not the only one thinking along this lines.
http://www.mail-archive.com/haskell%40haskell.org/msg14884.html


 module Main where
   import MyMain

   -- mymain :: (?myvar :: IORef Int) = IO () -- outside

   main = do
  var - newIORef 1   -- initialisers in the order you want
  let ?myvar = var in mymain

By then I also suggest that maybe we could also bind the implicit on import,  
something like:

 module (?par :: Parameter) = A where 
 ...

 module B where
 import A -- simple, ?par unbound
 import qualified A as Ak where ?par = k -- ?par bound to k
 import qualified A as Am where ?par = m -- ?par bound to m

Seemed fine as long as the parameters didn't depend on the imported modules. 
But on hindsight, making an import depend on valued defined in the body of 
the module is probably quite clumsy, unfortunately (right?). Still, 

 import qualified A as Ak where ?par = 1
or 
 import qualified A as Ak where ?par = newIORef
or even 
 import C(k)
 import qualified A as Ak where ?par = k 

Doesn't sound that bad though. 

J.A.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires
On Friday 07 January 2005 12:03, Ketil Malde wrote:
 Naive use of foldl.  I tend to think the default foldl should be
 strict (ie. replaced by foldl') -- are there important cases where it
 needs to be lazy?

Hi, 
One simple example would be,
 reverse = foldl (flip (:)) []

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires

 On Friday 07 January 2005 12:03, Ketil Malde wrote:
  Naive use of foldl.  I tend to think the default foldl should be
  strict (ie. replaced by foldl') -- are there important cases where it
  needs to be lazy?

 Hi,
 One simple example would be,
  reverse = foldl (flip (:)) []

A better example would be building some other lazy structure that is strict 
on it's elements...
J.A.

---
module Test where
import Data.List 

data L = E | !Int :+: L deriving Show

-- my head
h (x:+:xs) = x 
h E= error ops

-- 
rev1 = foldl  (flip (:+:)) E
rev2 = foldl' (flip (:+:)) E

l= [error , error , 1::Int]
--

*Test h (rev1 l)
1
(0.00 secs, 264560 bytes)
*Test h (rev2 l)
*** Exception:
(0.01 secs, 264524 bytes)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires

 No, it would work with strict foldl too. In fact in the absence
 of optimization it would work better (uses less time and space).
 The optimization required is inlining and strictness analysis.

Is this also true if your just going to use the first few elements after 
reversing it?

 A function which requires lazy foldl for correctness would have
 to be sometimes lazy in its first argument, and at the same time
 some partial results would have to be undefined. By function
 I mean the first argument of foldl, treated as a binary function.

 Here this doesn't apply because flip (:) x y is always defined. And
 another common case for foldl, sum, doesn't apply because (+) is
 usually strict on both arguments (although in principle it does not
 have to be true because of overloading, which implies that a compiler
 can only optimize particular specializations of sum, not generic sum).

 I don't know of any real-life example.

Yes you are right, my bad. I was thinking as if lists were not lazy on their 
elements, therefore my second example... But yes, now it is not a common 
example anymore. 

 Perhaps there are cases where evaluating partial results is correct
 but inefficient. I don't know such case either.

Just replace the errors on my second example by some big computations...

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires
On Sunday 09 January 2005 21:30, Marcin 'Qrczak' Kowalczyk wrote:
 Jorge Adriano Aires [EMAIL PROTECTED] writes:
  No, it would work with strict foldl too. In fact in the absence
  of optimization it would work better (uses less time and space).
  The optimization required is inlining and strictness analysis.
 
  Is this also true if your just going to use the first few elements after
  reversing it?

 Yes. A strict fold would evaluate cons cells of the result while they
 are constructed, not list elements. They are all defined (flip (:) x y
 is always defined), so a strict foldl is correct.

Yes, now I was refering to the efficiency issue only. 

 Making a cons cell should be not more expensive than making a thunk
 which will make a cons cell when evaluated. 

Ok, I wasn't sure about this...

 Well, unless the 
 implementation doesn't inline flip and thus making these thunks
 is actually faster than running them. In this case a lazy foldl is
 more efficient than a strict foldl, as long as a sufficiently small
 part of the result is used; it's always less efficient if the whole
 result is examined.

Right.

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-09 Thread Jorge Adriano Aires
 (+) is
 usually strict on both arguments (although in principle it does not
 have to be true because of overloading, which implies that a compiler
 can only optimize particular specializations of sum, not generic sum).

Since you mention it, there was some talk about this in the #haskell channel, 
and I wondered why aren't sum and product members of Num with default 
instances, just like mconcat is also a member of Data.Monoid.Monoid. 
From the docs: 

mconcat :: [a] - a
Fold a list using the monoid. For most types, the default definition for 
mconcat will be used, but the function is included in the class definition so 
that an optimized version can be provided for specific types

J.A.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Class Synonyms - example 2

2004-12-11 Thread Jorge Adriano Aires

 Jorge,

  Besides the case where 'a' is the same as 'b', there is also another
  interesting case. That is when you have both, Foo A B and Foo B A.
  This is a
  known property (named DoubleFoo) [...]

 Again, with -fallow-undecidable-instances:

 \begin{code}
 class (Foo a b, Foo b a) = DoubleFoo a b
 instance (Foo a b, Foo b a) = DoubleFoo a b
 \end{code}

Ah! Got it.
Thanks  Stefan,

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Class Synonyms

2004-12-10 Thread Jorge Adriano Aires
Hello! 

I got a multi-parameter type class:

 class Foo a b | a - b where
foo_method1 :: ...
foo_method2 :: ...
...

And some particular cases are important on their own, like the one where 'a' 
and 'b' are the same, I call elements with this property, Bar. So I defined:

class Foo a a = Bar a where

This is nice, now I can replace (F a a) for (Bar a) in the context of many 
functions. Less typing and it's more readable. Still, I have to define 
instances as:
 
 instance Foo A A where
foo_method1 = bla1
foo_method2 = bla2
 
 instance Bar A where


I'd like to achieve something better than this. I was looking for something 
like class synonyms. So if I declared an instance Foo A A, I automagicaly 
had Bar A, because they'd be the same. Or even better, I could declare

 instance Bar A where
foo_method1 = bla1
foo_method2 = bla2


Is anything like this possible at all?
Thanks,

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Class Synonyms - example 2

2004-12-10 Thread Jorge Adriano Aires
Maybe I should have included a more interesting example in the previous mail. 
So I had this class:

 class Foo a b | a - b where
foo_method1 :: ...
foo_method2 :: ...
...

Besides the case where 'a' is the same as 'b', there is also another 
interesting case. That is when you have both, Foo A B and Foo B A. This is a 
known property (named DoubleFoo), so I'd like to type contexts as,

 DoubleFoo a b =

instead of,

 (Foo a b, Foo b a) =

so I tried:
 class (Foo a b, Foo b a) = DoubleFoo a b where

This works fine if I'm going to define functions which need both instances of 
Foo. Something like:

 testDouble :: DoubleFoo a b = a - b - c 
 testDouble a b = foo_method1 a b  ... foo_method1 b a 

but it doesn't help me with:

 testDouble2 :: DoubleFoo a b = a - b - c 
 testDouble2 a b = foo_method1 a b  ... testDouble2 b a 

now I need DoubleFoo b a as well. Seems to me like there is no way of saying:
 Foo a b , Foo b a = DoubleFoo a b 

right?

J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] why no strictness annotations in labelled fields?

2004-12-01 Thread Jorge Adriano Aires

 Is there a good reason one can't do:
   data Foo = Foo {bar::!String}

Just add a space after the ::
{bar:: !String}

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] foldlWhile

2004-11-20 Thread Jorge Adriano Aires
(opss just noticed I did a reply-to)

  The following is closer to the original, but doesn't work when the whole
  list is folded (i.e., p always satisfied):
  foldlWhile f p a = head . dropWhile p . scanl f a

 Serge's version returns the last 'a' that satisfies 'p', while yours
Not really.

 returns the first 'a' that does not satisfy 'p'.  This should be an
 equivalent version:
Yeap, just like his, 

foldlWhile :: (a - b - a) - (a - Bool) - a - [b] - a
foldlWhilefp  abs  =
snip
(_, False) - a
snip

It tests the accumulator with p, and returns it on false.

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FiniteMap-like module for unordered keys?

2004-11-09 Thread Jorge Adriano Aires
Hello, 

 A hash-table becomes rather useless without mutable state AFAICS.
 Without it, one might almost just as well use a list of pairs...

Could you please elaborate? Is there motive why an Hash Table, implemented as 
FiniteMap of Lists, for instance, wouldn't be worth to using over a simple 
List? (This wouldn't help G. Klyne of course). I've always wondered why a 
non-monadic version of is not provided in the GHC libs... 

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] QuickCheck - Extracting data values from tests

2004-09-04 Thread Jorge Adriano Aires

 The generate function is exported:

 generate :: Int - StdGen - Gen a - a

Thanks, that's the one I was missing.

J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] QuickCheck - Extracting data values from tests

2004-09-02 Thread Jorge Adriano Aires

  Hello all,
  When using Quickcheck, is there some way to extract generated data values
  to the IO Monad?
 
  I know I can collect and print information about test cases, but that's
  not enough. Data may be pretty complex, and there may be no parsers for
  it. If a test suddenly goes wrong, just having it displayed doesn't seem
  that useful.

 You may be interested in a QuickCheck hack of mine that saves the offending
 data value to use immediately in the next test run.

Nice!
It's different from what I was looking for but also quite usefull.

 You can get the current version with
 darcs get http://thunderbird.scannedinavian.com/repos/quickcheck;
 I've only used this for my own code, so I'd be interested in any feedback.

Ok.

 In some cases it's a lot easier to generate a value from a seed and size
 rather than saving the value in some way that you can restore (ie
 functions).

 I've been investigating doing test-driven-development with QuickCheck,
 saving failing test cases is one step towards that goal. If you have more
 ideas on that topic, I'd like to hear about it.

Well, returning (part of) the generated data is one of them :)

  Also, even when I'm implementing a generator, I want to see how it is
  working. Running a verboseCheck on some dummy property helps, but I may
  want to analyse the data, or some parts of it better - for instance, for
  many data structures I have alternative show functions that take
  parameters as arguments.

 This isn't clear to me, can you give other examples?


Not sure which part is not clear... I'll just try to explain each of them.
Lets say I'm implementing a generators for Graphs.

  Also, even when I'm implementing a generator, I want to see how it is
  working.
I want to check if the generated Graphs are like I intended them to be.

  Running a verboseCheck on some dummy property helps, but I may
verboseCheck by default prints all the data.
I can run it on a dummy function that always returns True to see what kind of 
data I'm getting.


  want to analyse the data, or some parts of it better
May want to print the 'actual graphs' on the screen (ASCII art, or maybe using 
some function that calls Gnuplot). Then I may want to check in more detail 
the info in contained in some of the nodes. Then I may decide to run some 
functions on it.

  many data structures I have alternative show functions that take
  parameters as arguments.
Like I just said, I may want to show the graph in many ways.


But there are more possibilities.
Why limitate the usefulness of QuickCheck? Suppose I just implemented 
generators for a few kinds of terms and formulas to test some properties. Now 
I want to benchmark a couple of different unification functions... I'd expect 
to be able to use my generator for that. Unless I'm missing something, I 
cannot. Am I right?

J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] QuickCheck - Extracting data values from tests

2004-09-01 Thread Jorge Adriano Aires
Hello all,
When using Quickcheck, is there some way to extract generated data values to 
the IO Monad? 

I know I can collect and print information about test cases, but that's not 
enough. Data may be pretty complex, and there may be no parsers for it. If a 
test suddenly goes wrong, just having it displayed doesn't seem that useful.

I'd expect quickCheck to have type:
quickCheck :: forall a. (Testable a) = a - IO [a]

Show I could just get the offending data with:
please_be_empty - quickCheck prop_foo

Also, even when I'm implementing a generator, I want to see how it is working. 
Running a verboseCheck on some dummy property helps, but I may want to 
analyse the data, or some parts of it better - for instance, for many data 
structures I have alternative show functions that take parameters as 
arguments. 

Thanks in advance,
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Problem with Unboxed Types

2004-08-27 Thread Jorge Adriano Aires

 Just to be sure, I've just compiled and run this code with GHC 6.2.1, on
 a Linux system.  I can't account for your difficulty I'm afraid.

 Simon

Thanks, and nevermind, I think I figured out what was happening. Working now. 

J.A.



 {-# OPTIONS -fglasgow-exts #-}

 module Main where

 import GHC.Exts

 showUnboxedInt :: Int# - String
 showUnboxedInt n = (show $ I# n) ++ #

 main = print (showUnboxedInt 3#)

 | -Original Message-
 | From: [EMAIL PROTECTED]

 [mailto:glasgow-haskell-users-

 | [EMAIL PROTECTED] On Behalf Of Jorge Adriano Aires
 | Sent: 27 August 2004 02:55
 | To: [EMAIL PROTECTED]
 | Subject: Problem with Unboxed Types
 |
 | Hello,
 | I'd like to try using Unboxed types, but I always get a parse error

 on input

 | `#' error. To make sure I wasn't making some mistake I tried the

 example in

 | the wiki:
 |
 | http://www.haskell.org/hawiki/UnboxedType
 | 
 | module Main where
 | import GHC.Exts
 |
 | showUnboxedInt :: Int# - String
 | showUnboxedInt n = (show $ I# n) ++ #
 | 
 |
 | Even tried adding fglasgow-exts, nothing works though. I'm using GHC

 6.2.1 on

 | a SuSE 8.2 system (glibc 2.3) installed using the available RPMs. Any

 idea?

 | Thanks in advance,
 | J.A.
 |
 | ___
 | Glasgow-haskell-users mailing list
 | [EMAIL PROTECTED]
 | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Problem with Unboxed Types

2004-08-26 Thread Jorge Adriano Aires
Hello, 
I'd like to try using Unboxed types, but I always get a parse error on input 
`#' error. To make sure I wasn't making some mistake I tried the example in 
the wiki:

http://www.haskell.org/hawiki/UnboxedType

module Main where 
import GHC.Exts

showUnboxedInt :: Int# - String
showUnboxedInt n = (show $ I# n) ++ #


Even tried adding fglasgow-exts, nothing works though. I'm using GHC 6.2.1 on 
a SuSE 8.2 system (glibc 2.3) installed using the available RPMs. Any idea?

Thanks in advance,
J.A.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: How do I specify the source search path?

2004-06-30 Thread Jorge Adriano Aires
On Wednesday 30 June 2004 16:15, S. Alexander Jacobson wrote:
 I have the working code for my Haskell App Server
 Framework in ~/HAppS/HAppS.hs.  If I want to
 start working on an app that uses this framework
 in e.g. ~/MyApp, how do I tell GHCi to resolve
 import HAppS?

 Note: The HAppS code is in active development so I
 don't want to put it in the system GHC lib
 hierarchy.  I just want to use it add hoc from the
 command line.

Using the -i flag. Unfortunatly relative paths (using '~') don't seem to work, 
so you have to type the full path: ghci -i/home/user/HAppS/

As far as I know, there is also no way to specify the search path in an 
environment var, so my solution was to add to my .alias:
alias ghci='ghci -i/home/jadrian/Program/Haskell/MyLibs'
alias ghc='ghc -i/home/jadrian/Program/Haskell/MyLibs'

J.A.

J.A.

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Initialisation without unsafePerformIO

2004-06-04 Thread Jorge Adriano Aires

 What ideas do people have for getting rid of unsafePerformIO?

Hope my suggestion is not too naive. 
I get along quite fine using implicit parameters in many cases, it's just 
tedious explicitly typing them in every function context. I'd be pretty happy 
if it was possible to define the 'scope' of some implicit parameters in a 
module and/or define their scope as being a whole module. The 2nd option 
would be something like:

 module (?par :: Parameter) = A where 
 ...

Functions in A could have ?par in their context without having it explicitly 
typed. Now the import of A could be done with:

 module B where 

 import A  -- simple, ?par unbound
 import A as Ak where ?par = k -- ?par bound to k
 import A as Am where ?par = m -- ?par bound to m

 ...

 k :: Parameter
 k = ...
 
 m :: Parameter
 m = ...
 ...

Also,

 module (?par :: Parameter) = C where 
 import A  -- both A and C paremeterised by ?par

Since both modules share the same parameter, instantiation on ?par in the 
import of C would propagate to the import of A.

At first glance it seems simple syntactic sugar and therefore doable. 
Along with some options in the interpreter to hide/show (this kind of) 
implicit parameters when displaying signatures, check module context, etc. 
probably also quite usable.

J.A.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Namespace trouble

2004-05-20 Thread Jorge Adriano Aires

 Jorge Adriano Aires [EMAIL PROTECTED] writes:
  I have the following structure:
   MyProgram/A.hs
   MyProgram/Aux/B.hs
   MyProgram/Aux/C.hs

 You have already received replies to your question, so let me make a
 different point.  If you ever intend your program to work on Windows,
 do not use Aux as a file or directory name!  The libraries mailing
 list has some recent experience of this.  (Apparently Aux is a
 reserved filename on Windows and you get strange behaviour if you
 try to use it for anything else.)

Thanks for the tip, I'm working in linux though and Aux was really just an 
example :)

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Namespace trouble

2004-05-19 Thread Jorge Adriano Aires
Hello,
I have the following structure:

 MyProgram/A.hs
 MyProgram/Aux/B.hs
 MyProgram/Aux/C.hs

and:
 A imports C
 B imports C

Can I make this work using namespaces only (i.e. no -i flag)? 
I expected this to work:

 MyProgram/A.hsname: Aimport Aux.C
 MyProgram/Aux/B.hsname: Aux.Bimport C
 MyProgram/Aux/C.hsname: Aux.C

But complains when importing C from B since its name is Aux.C.
What is the most elegant way to deal with such cases?

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Namespace trouble

2004-05-19 Thread Jorge Adriano Aires
 I expected this to work:
  MyProgram/A.hsname: Aimport Aux.C
  MyProgram/Aux/B.hsname: Aux.Bimport C
  MyProgram/Aux/C.hsname: Aux.C

 But complains when importing C from B since its name is Aux.C.
 What is the most elegant way to deal with such cases?


Answering myself, this works:
 MyProgram/A.hsname: Aimport Aux.C
 MyProgram/Aux/B.hsname: Aux.Bimport Aux.C
 MyProgram/Aux/C.hsname: Aux.C

I just have to load B from MyProgram when testing it in ghci, instead of 
loading it in MyProgram/Aux. Thanks to Lunar for the tip.

J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Monadic Composition

2004-05-12 Thread Jorge Adriano Aires
 So, yes, it is useful, but should it be included in a standard Monad
 module? After all, this module contains mostly trivial functions ;)

 BTW. You can write this function using foldM:

 compM l a = foldM (#) a l

 where # is an often used reverse application operator:
 x # f = f x

Right. Now that I look at it, someone probably tried to give me this advice 
before but I failed to understand... (sorry monotonom!). It's all clear now. 
One more question. Isn't the foldM description a bit misleading? From the 
Report and also in GHC documentation:

The foldM function is analogous to foldl, except that its result is 
encapsulated in a monad.(...)
foldM f a1 [x1, x2, ..., xm ] == 
  do
  a2 - f a1 x1
  a3 - f a2 x2
  ...
  f am xm

After reading this I expected left associativity, just like in my first 
definition. That'd mean a fail wouldn't stop a computation immediately but 
instead be passed from function to function. By checking its definition in 
the report I can see this is not the case though.

Cheers,
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monadic Composition

2004-05-11 Thread Jorge Adriano Aires
Hello,
I needed to compose monadic functions, since I couldn't find anything in 
Control.Monad so I defined my own. I first came up with a left associative 
version:

compLM [f1,..., fn] a = (f1 a = f2) = ... = fn
 compLM:: Monad m = [a-m a] - (a-m a)
 compLM mfs a  = foldl (=) (return a) mfs

Later a right associative version, which I believe to be more efficient, 
particularly when some computation returns fail:

compRM [f1,..., fn] a = \x-f1 x = (\x-f2 x = ... = \x-fn x) a
 compRM   :: Monad m = [a-m a] - (a-m a)
 compRM = foldr (\f g- (\x -f x = g)) return 

This higher order function seems quite useful to me and not trivial, so I  
expected it to be available. When this happens I wonder if I'm missing 
something. Am I complicating things? Is it actually available (or some other 
that does the trick) ? Or is it just me who finds this usefull enough to be in 
the libs?
 
J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe