In opposition of Functor as super-class of Monad

Tony Morris tonymorris at gmail.com
Wed Jan 5 06:08:41 CET 2011


{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Prelude hiding (Monad(..), Functor(..))

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

class Functor m => Monad m where
  return :: a -> m a
  (>>=) :: m a -> (a -> m b) -> m b

instance Functor Maybe where
  fmap f m = m >>= (return . f)
instance Monad Maybe where
  return = Just
  Nothing >>= _ = Nothing
  Just x  >>= f = f x

newtype MMaybe a = MMaybe (Maybe a)
  deriving (Functor, Monad)

mjust =
  MMaybe . Just

mnothing =
  MMaybe Nothing

-- No instance for (GHC.Base.Monad MMaybe)
f =
  do x <- mjust 7
     return x


On 04/01/11 23:46, Alexey Khudyakov wrote:
> On 04.01.2011 16:38, Tony Morris wrote:
>> I think you'll find a problem using do-notation with your Monad.
>>
>> Tony Morris
>>
> Do you mean that fail is absent? That's irrelevant here.
>
> I tried to demonstrate that fmap could be defined in terms of monad
> and that definition will work.


-- 
Tony Morris
http://tmorris.net/





More information about the Haskell-prime mailing list