Re: [Haskell-cafe] trying to understand monad transformers....

2008-09-10 Thread wren ng thornton

wren ng thornton wrote:

Daryoush Mehrtash wrote:

The MaybeT transformer is defined as:

newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}




Question:  What does runMaybeT x mean?


As for what does it do, I think everyone else has handled that pretty 
well. As far as what does it mean, it may help to think categorically.


For every monad |m| we have another monad |MaybeT m|. If we ignore some 
details, we can think of the transformed monad as |Maybe| composed with 
|m|, sic: |Maybe . m|. With this perspective, runMaybeT is inverting 
|MaybeT m| into |m . Maybe| by pushing the Maybe down over/through the 
monad m. Hence we can envision the function as:


 | runMaybeT   :: (MaybeT m) a - (m . Maybe) a
 | runMaybeT NothingT   = return Nothing
 | runMaybeT (JustT ma) = fmap Just ma



Erh, whoops, I said that backwards. |MaybeT m| is like |m . Maybe| and 
runMaybeT breaks apart the implicit composition into an explicit one. 
The MaybeT monad just gives the additional possibility of a Nothing 
value at *each* object in |m a|.


To see why this is different than the above, consider where |m| is a 
list or Logic. |MaybeT []| says that each element of the list 
independently could be Nothing, whereas |ListT Maybe| says that we have 
either Nothing or Just xs. The pseudocode above gives the latter case 
since it assumes a top level Nothing means Nothing everywhere, which is 
wrong for |MaybeT m|.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] trying to understand monad transformers....

2008-09-09 Thread Daryoush Mehrtash
The MaybeT transformer is defined as:

newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Maybe
a)}

instance Functor
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Functor
m = Functor 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Functor
(MaybeT m) where
  fmap 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fmap
f x = MaybeT $ 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.
fmap 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fmap
(fmap 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fmap
f) $ http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:.
runMaybeT x




Question:  What does runMaybeT x mean?


Thanks,

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


Re: [Haskell-cafe] trying to understand monad transformers....

2008-09-09 Thread Magnus Therning
2008/9/9 Daryoush Mehrtash [EMAIL PROTECTED]:
 The MaybeT transformer is defined as:

 newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}


 instance Functor m = Functor (MaybeT m) where

   fmap f x = MaybeT $ fmap (fmap f) $ runMaybeT x


 

 Question:  What does runMaybeT x mean?

If you mean what does it do? then the answer is that it unwraps the
MaybeT so that you can get to the inner value.  If you mean how does
it do it? then I believe the best thing is to read some of the
chapters in RWH because I think I recognise a rather common
Haskell-pattern here.  I don't remember which ones, but I'm sure
others on this list have better memory than I do ;-)

If this isn't what you were looking for, then I haven't understood the
question :-)

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


Re: [Haskell-cafe] trying to understand monad transformers....

2008-09-09 Thread Ryan Ingram
2008/9/8 Daryoush Mehrtash [EMAIL PROTECTED]:
 The MaybeT transformer is defined as:

  newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}

 Question:  What does runMaybeT x mean?

This is just shorthand for the following:

 newtype MaybeT m a = MaybeT (m (Maybe a))
 runMaybeT :: MaybeT m a - m (Maybe a)
 runMaybeT (MaybeT x) = x

(with some minor differences to automated deriving of Show instances)

At runtime, runMaybeT and MaybeT are just really fast identity
functions (they should get optimized out of existence, even!)

So, if you have x :: MaybeT m a at runtime, you really just have
runMaybeT x :: m (Maybe a)

 instance Functor m = Functor (MaybeT m) where
   fmap f x = MaybeT $ fmap (fmap f) $ runMaybeT x

This code is a bit confusing at first because each fmap is at a different type.

The first (in the function declaration) is
 fmap :: Functor m = (a - b) - MaybeT m a - MaybeT m b

The second (*fmap* (fmap f)) is
 fmap :: Functor m = (Maybe a - Maybe b) - m (Maybe a) - m (Maybe b)

The third (fmap (*fmap* f)) is
 fmap :: (a - b) - Maybe a - Maybe b

When you work with functors a lot you start to be able to read this
stuff more easily.

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


Re: [Haskell-cafe] trying to understand monad transformers....

2008-09-09 Thread Paul Johnson

Daryoush Mehrtash wrote:

The MaybeT transformer is defined as:
newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Maybe 
a)}

 
instance Functor http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Functor m = Functor http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#t:Functor (MaybeT m) where


  fmap http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fmap f x = MaybeT $ 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. fmap 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fmap (fmap 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:fmap f) $ 
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:. runMaybeT x



  


Question:  What does runMaybeT x mean?

All monads (except IO) have a run function.  E.g. runST for the ST 
monad, runState for the state function, and so on.  A monadic action 
is actually a function that (typically) takes extra arguments and 
returns extra results.  In the monadic action form these extra data are 
hidden, and its up to the monad bind function to thread them from one 
action to the next.  The runX function for some monad X converts a 
monadic action into the underlying function with that data exposed.  In 
most cases the monad is defined as a newtype wrapper around the 
function, so the run function is just the inverse of the constructor.


In the case of a monad transformer the result of the function is not a 
value, its an action in another monad.  Thats what you see in the case 
of MaybeT.  A MaybeT action is actually a monadic action that itself 
returns a Maybe value.  So you use runMaybeT to turn your MaybeT action 
into an action in the inner monad, and then run that action using its 
run function to finally get a Maybe result.


Make sense?

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


Re: [Haskell-cafe] trying to understand monad transformers....

2008-09-09 Thread wren ng thornton

Daryoush Mehrtash wrote:

The MaybeT transformer is defined as:

newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}




Question:  What does runMaybeT x mean?


As for what does it do, I think everyone else has handled that pretty 
well. As far as what does it mean, it may help to think categorically.


For every monad |m| we have another monad |MaybeT m|. If we ignore some 
details, we can think of the transformed monad as |Maybe| composed with 
|m|, sic: |Maybe . m|. With this perspective, runMaybeT is inverting 
|MaybeT m| into |m . Maybe| by pushing the Maybe down over/through the 
monad m. Hence we can envision the function as:


 | runMaybeT   :: (MaybeT m) a - (m . Maybe) a
 | runMaybeT NothingT   = return Nothing
 | runMaybeT (JustT ma) = fmap Just ma

The reason this is useful at all is that Maybe is not just any monad, 
but is also a primitive value in the system. That is, once we have a 
Maybe value we can treat it as a normal pure value that we can pattern 
match on etc. For other monads like Set, [ ], and LogicMonad this means 
that we can iterate over their elements rather than just treating them 
as functors. Whereas a |MaybeT m| value can't be accessed directly.


This explanation is leaving out details about transformers in general. 
The Maybe/MaybeT type is defined by Maybe(a)=a+1, which is to say it's 
the same as the type |a| plus one additional value. Given this 
definition it's easy to define runMaybeT like above. For other monads 
and monad transformers this conversion might not be so trivial because 
we'll need to thread state through the computation.


This is also the reason why the ordering of your transformer stack is 
important. When converting from the transformer to the composition, how 
to thread the state is non-trivial. This is just the same as saying that 
we can't reorder function compositions and still have the same results. 
A large class of functions do have reorderable compositions[1] just like 
a large class of monads have trivial state, but in general that's not 
the case for either of them.



[1] 
http://haskell.org/haskellwiki/The_Monad.Reader/Issue4/Why_Attribute_Grammars_Matter


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe