Sudden monomorphism with -XTypeFamilies

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

On Thu, Jan 5, 2012 at 3:32 PM, Rian Hunter
hello
i'm getting inconsistent monomorphism behavior with the same code only depending on whether or not -XTypeFamilies is enabled:
Which version of GHC are you using? Starting with GHC 7.0, the TypeFamilies extension implies the MonoLocalBinds language feature, which looks like what you're running into. Here's a blog post from the GHC folks about it: http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7 Antoine
---- {-# 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Antoine Latter
-
Rian Hunter