[Haskell-cafe] HList, hOccurs and MonadReader
Marc Weber
marco-oweber at gmx.de
Thu Feb 22 23:19:49 EST 2007
Having the module given below I can't see why using
printAndRerun l1
printAndRerun2 l2
but not
printAndRerun l1
printAndRerun l2
?
They only differ in their name.
Can you point me in the right direction?
------------------------------------------------
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-incoherent-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}
module HListTest.MonadReader where
import HList hiding (liftIO)
import Monad
import Control.Monad.Reader
printAndRerun = do v <- liftM hOccursFst ask
liftIO $ print (v :: Int )
v2 <- liftM hOccursFst ask
return (v2 :: String)
printAndRerun2 = do v <- liftM hOccursFst ask
liftIO $ print (v :: Int )
v2 <- liftM hOccursFst ask
return (v2 :: String)
a = (2 :: Int)
b = "str"
l a b = HCons a (HCons b HNil)
--- l1 :: ( HCons Int (HCons String HNil))
l1 = l a b
l2 = l b a
printBoth f l = runReaderT f l >>= print
printBoth2 l = do print (hOccurs l :: Int)
print (hOccurs l :: String)
hlistMonadReaderTest = do
print "hlistMonadReaderTest"
printBoth printAndRerun l1
-- printBoth printAndRerun l2 -- < this doesn't work but the next line ? Where is the difference between printAndRerun printAndRerun2 ?
printBoth printAndRerun2 l2
-- ^
printBoth2 l1 -- here is no trouble..
printBoth2 l2
main = hlistMonadReaderTest
------------------------------------------------
when not commenting the line above I'm getting this error:
HListTest/MonadReader.hs|35| 26:
Couldn't match expected type `Int' against inferred type `[Char]'
Expected type: HCons Int (HCons [Char] HNil)
Inferred type: HCons [Char] (HCons Int HNil)
In the second argument of `printBoth', namely `l2'
In the expression: printBoth printAndRerun l2
Thanks Marc
More information about the Haskell-Cafe
mailing list