[Haskell-beginners] Re: Re: in which monad am I?

Maciej Piechotka uzytkownik2 at gmail.com
Sun Jan 3 18:14:27 EST 2010


On Sun, 2010-01-03 at 23:44 +0100, Francesco Guerrieri wrote:
> On Sun, Jan 3, 2010 at 11:21 PM, Maciej Piechotka <uzytkownik2 at gmail.com> wrote:
> > Except for syntax sugar (do) monads are nothing special in Haskell. Not
> > more special then Read or Show classes.
> >
> > For example (for type system):
> >
> >> f :: [String] -> [String]
> >> f = map show . map read
> >>
> >> main = interact (unlines . f . lines)
> >
> > test.lhs:6:21:
> >    Ambiguous type variable `a' in the constraints:
> >      `Read a' arising from a use of `read' at test.lhs:6:21-24
> >      `Show a' arising from a use of `show' at test.lhs:6:10-13
> >    Probable fix: add a type signature that fixes these type variable(s)
> 
> Ok, I understand it this way:
> f takes a list of string, maps "read" to it and maps "show"
> (converting them to their string representation) to the resulting
> list. f  never explicitly bothers with the type to which the strings
> were "read", since it shows them asap. BUT if the compiler is to pick
> an implementation of read, the type must be known.
> 

Yes. It knows that he should call some read and some show functions but
have no idea which function.

> >
> > With monad it is harder (as monad is one-way) but it is possible to do
> > it:
> >
> >> extract $ liftM (+1) (return 0)
> >
> > results in:
> >
> >    Ambiguous type variable `f' in the constraints:
> >      `Monad f' arising from a use of `liftM' at <interactive>:1:10-30
> >      `Copointed f'
> >        arising from a use of `extract' at <interactive>:1:0-6
> >    Probable fix: add a type signature that fixes these type variable(s)
> >
> > We only know that we operate on some monad which is copointed. But we
> > have no idea what is it. However in 99% of cases we don't have to.
> >
> > (You man notice the signature of extract is - extract :: (Copointed f)
> > => f a -> a so the problem is when we remove type [type does not occures
> > on RHS of last ->])
> 
> 
> Ok, you're losing me a bit with the "copointed f".

It's one more strange class. The definition (from category-extras
package if you need to know):

class Copointed f where
  extract :: f a -> a

Sorry if I mess a bit. You got the main point so read further only if
you want to know a bit about copointed

> Could you please clarify further the example? I assume that extract is
> the "inverse" of liftM.

It's rather inverse of return. However it is unlikely that you'll ever
use it (at least - I haven't and many programs/libraries have not). It
was just an example.

> I have not yet found it and searching for
> "haskell extract monad" doesn't find a specific reference link.

http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/Control-Functor-Pointed.html#t%3ACopointed

Generally use hayoo[1] (hoogle stop working for me lately) inserting for
example 'extract'. 

[1] http://holumbus.fh-wedel.de/hayoo/hayoo.html

> If
> extract "unlifts" a value out of a Monad I think that it cannot be
> defined for every monad

Yest. Hence we know that it is monad which is copointed. I.e. we look
for such m that (Copointed m, Monad m) - m that it member of both
classes.

> (you cannot get out from the IO monad....
> right?).

Well. You can get out of IO monad. But you shouldn't (it creates lot's
of problems). But generally you cannot.

Imagine extractM :: Monad m => m a -> a

What would be extractM []

> In this sense you are first lifting and then unlifting like
> earlier you were first reading and then showing...? and so in
> principle you are "monad agnostic" but the type system is puzzled
> because it doesn't know to which monad you want to lift?
> 

Yes. However as long you're in Functor/Monad/Applicative range you are
quite safe as they are like Alcatraz - no escape (see however PS).

However Identity is both monad and Copointed (it is somewhere defined)

> newtype Identity a = Identity a
> instance Monad Identity where
>   (Identity v) >>= f   = f v
>   return               = Identity
> instance Copointed Identity where
>   extract (Identity v) = v

So:

> extract $ (liftM (+1) (return 0) :: Identity Int)

will work

> Thanks,
> Francesco

Regards

PS. Possibly simpler example:

> liftNull :: (Monad m, Monad n) => m () -> n ()
> liftNull _ = return ()

> liftNull $ liftM (+1) (return 0)




More information about the Beginners mailing list