[Haskell-beginners] monad transformer show help

rickmurphy rick at rickmurphy.org
Tue May 29 14:35:29 CEST 2012


Hello All:

Over the past few days I got my first exposure to monad transformers.

I worked through the sample below. 

The witness w displays IC 0 as expected, but even after providing the
instance of show for type O I a, witness w' causes ghci to display

    No instance for (Num (I' a0))
      arising from a use of w'
    Possible fix: add an instance declaration for (Num (I' a0))

Would someone be able to explain why after providing the instance of
show on O I a, w' does not print the expected result (OC (IC 0)) ?

BTW - You will notice the sample intentionally avoids the use of
deriving (Show) on newtype I.

--
Rick


{-# LANGUAGE NoMonomorphismRestriction, DatatypeContexts,
FlexibleContexts, FlexibleInstances #-}

module Main where

import Control.Monad
import Control.Monad.Trans.Class

<snip>

-- |A parameterized new type I representing an "inner type" with one
constructor IC               
newtype I a = IC a -- deriving (Show)

-- |Unwraps the value in the inner type 
unI (IC x) = x

-- |A monad instance on the inner type
instance Monad I where
 return = IC
 m >>= f = f (unI m)

instance Show a => Show (I a) where
 show (IC x) = "IC " ++ show x

-- |Witness on inner type
w :: Num a => I a
w = (IC 0) >>= return . id

-- |A parameterized new type O m a representing an "outer type" with a
named constructor 
newtype O m a = OC {runO :: m (I a)} -- deriving (Show)

-- |?
instance Show a => Show (O I a) where
 show (OC x) = "OC (IC " ++ show (unI x) ++ "))" -- show (OC (IC 0))

-- |Unwraps the value in the outer type 
unO (OC (IC a)) = a

-- |A monad transformer instance on type O m a 
instance Monad m => Monad (O m) where
 return = OC . return . IC 
 m >>= f = OC $ do {v <- runO m; runO (f (unI v))}

-- | Witness on monad transformer
w' :: Num (I a) => O I a
w' = (OC (IC 0)) >>= return . id

-- | Executes addition on the zero in IC
w'' :: Num a => I a
w'' = liftM (+1) (IC' 0)

-- |Instance of monad transformer lift on O m a
instance MonadTrans O where
 lift m = OC (m >>= return . IC)

-- |Executes addition on the zero in IC and lifts to O m a
w''' :: (Num a, MonadTrans t) => t I a
w''' = lift ((IC 0) >>= return . (+1))




More information about the Beginners mailing list