[Haskell-cafe] Re: A free monad theorem?

Andrea Rossato mailing_list at istitutocolli.org
Fri Sep 1 04:16:51 EDT 2006


Il Fri, Sep 01, 2006 at 07:22:02AM +0200, Tomasz Zielonka ebbe a scrivere:
> On Fri, Sep 01, 2006 at 01:13:14AM +0200, Benjamin Franksen wrote:
> > So getting the value out of the monad is not a pure function (extract ::
> > Monad m => m a -> a). I think I stated that, already, in my previous post.
> 
> The only generic way of "extracting" values from a monadic value is
> the bind operator. The lack of extract function is a feature :-)
> But now I know that you are not really claiming such a function exists.

I do not understand this discussion, but I'd like to.

Can you please tell me what you are talking about in terms of this
example?
Thanks,
Andrea

module Test where

newtype M a = TypeConstructor {unpack::(a, String)}
    deriving (Show)

instance Monad M where
    return a = (TypeConstructor (a,""))
    (>>=) m f = TypeConstructor (a1,b++b1)
                where (a,b) = unpack m
                      (a1,b1) = unpack (f a)

putB b = TypeConstructor ((),b)
putA a = (TypeConstructor (a,""))
getA (TypeConstructor (a,b)) = a
getB (TypeConstructor (a,b)) = b

transformM :: Int -> M Int
transformM a = do putA 3
                  putB "ciao"
                  putA 6
                  putB " cosa?"
                  return 4

{-
*Test> let a = transformM 1
*Test> a
TypeConstructor {unpack = (4,"ciao cosa?")}
*Test> getA a
4
*Test> getB a
"ciao cosa?"
*Test> 
-}


More information about the Haskell-Cafe mailing list