
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

This really smells like a violation of the "monomorphism restriction"[1]. Try again with -fno-monomorphism-restriction, and if that fixes it, add a type signature to fix it for good. [1] http://haskell.org/onlinereport/decls.html#sect4.5.5 Stefan

On Thu, Feb 22, 2007 at 07:34:36PM -0800, Stefan O'Rear wrote:
This really smells like a violation of the "monomorphism restriction"[1]. Try again with -fno-monomorphism-restriction, and if that fixes it, add a type signature to fix it for good.
[1] http://haskell.org/onlinereport/decls.html#sect4.5.5
Stefan Thanks Stefan
participants (2)
-
Marc Weber
-
Stefan O'Rear