[Haskell-cafe] Sudden monomorphism with -XTypeFamilies

Rian Hunter rian at thelig.ht
Thu Jan 5 22:32:01 CET 2012


hello

i'm getting inconsistent monomorphism behavior with the same code only depending on whether or not -XTypeFamilies is enabled:

----
{-# LANGUAGE TypeFamilies #-}

snda :: a -> b -> b
snda ba = id

main = do
 let ma = (return () :: IO ())
     mBox bb = snda ma bb

 mBox $ return (4 :: Int)
 mBox $ return "G"

 return ()
----

in the preceding example, if -XTypeFamilies is enabled then "mBox" is
monomorphic and the program will terminate early, otherwise,
it's polymorphic and the program will complete successfully.

i think i understand why this is the case but i couldn't find documentation on this inconsistency anywhere. is this expected behavior or is this a bug in GHC? thanks!

rian
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120105/37773ed8/attachment.htm>


More information about the Haskell-Cafe mailing list