[Haskell-cafe] beginner's problam with a monad

2006-09-03 Thread Julien Oster
Hello,

after succeeding in implementing my first monad (Counter, it increments
a counter every time a computation is performed) I though I'd try
another one and went on to implement Tracker.

Tracker is a monad where a list consisting of the result of every
computation is kept alongside the final value, kind of a computation
history. It really just serves me as an exercise to implement monads.

However, the following source code fails:

{-}

data Tracker a b = Tracker [a] b
 deriving Show

instance Monad (Tracker a) where
m = f =
let Tracker l x = m in
let Tracker l' x' = f x in
Tracker (x':l) x'
return x = Tracker [] x

bar = do
  x - Tracker [] 12
  y - return (x*2)
  z - return (y*3)
  return (z+3)

{-}

Of course, style recommendations and the like are always appreciated.

(by the way, I don't really understand why I have to type
  instance Monad (Tracker a)
instead of
  instance Monad Tracker
which may very well be the problem. If it's not, can someone tell me
anyway?)

Trying to load this piece of code leads to the following error message:

Hugs.Base :load Test.hs
ERROR Test.hs:30 - Inferred type is not general enough
*** Expression: (=)
*** Expected type : Monad (Tracker a) = Tracker a b - (b - Tracker a
c) - Tracker a c
*** Inferred type : Monad (Tracker a) = Tracker a b - (b - Tracker a
a) - Tracker a a

Why does the interpreter infer Tracker a a instead of the more general
Tracker a c?

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


Re: [Haskell-cafe] beginner's problam with a monad

2006-09-03 Thread Dan Doel

On 9/3/06, Julien Oster [EMAIL PROTECTED] wrote:

Hello,

Hi.


Why does the interpreter infer Tracker a a instead of the more general
Tracker a c?


The problem is that you're trying to keep a list of all computations
performed, and lists can only store values of one uniform type. So, if
you have a Tracker storing a list of values of type [a], it must also
represent a computation of type a via the second argument, because
that's the only type it can append to the list.

Thus, unfortunately, you won't be able to implement the general bind
operator. To do so, you'd need to have Tracker use a list that can
store values of heterogeneous types, which is an entire library unto
itself (HList).

Hope that helps some,
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginner's problam with a monad

2006-09-03 Thread Julien Oster
Dan Doel wrote:

 Thus, unfortunately, you won't be able to implement the general bind
 operator. To do so, you'd need to have Tracker use a list that can
 store values of heterogeneous types, which is an entire library unto
 itself (HList).

Telling me that it just won't work was one of the best answers you could
give me, because now I know that I can stop trying (well, I think I will
have a look at HList. If it's easy enough...)

Now if anyone could enlighten me about the instance Monad Tracker a
instead of instance Monad Tracker part, everything will be clear!

Thanks a lot,
Julien
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] beginner's problam with a monad

2006-09-03 Thread Keegan McAllister

Now if anyone could enlighten me about the instance Monad Tracker a
instead of instance Monad Tracker part, everything will be clear!


A Monad always takes one type argument -- the a in IO a, Maybe a, etc. 
So Tracker can't be a Monad (it needs two arguments), but (Tracker a) 
is, for any a.  This is basically partial application at the type level.


Formally, we say a Monad needs to have kind * - *.  Kinds are like 
types for the type level.  A kind of * indicates an actual type which 
can have values, etc.  A kind of k1 - k2 indicates a type operator 
which wants as an argument a type of kind k1, and will produce a type of 
kind k2.  As with types, the kind arrow is right-associative and partial 
application is allowed.


We can see the mismatch in the following (hypothetical) GHCi session:

Prelude :info Monad
class Monad (m::* - *) where
...
Prelude :kind Tracker
Tracker :: * - * - *
Prelude :kind Tracker Bool
Tracker Bool :: * - *


Hope that helps,
keegan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe