
Ketil, Thanks for the response. It seems that defining them as a pair only postphones the error.GHC will give an error when you extract the components of the pair, no matter whether you addthe "NoMonomorphismRestriction" flag or not. --{-# LANGUAGE NoMonomorphismRestriction #-}p :: (Show a, Ord b) => (a -> String, b -> b -> Bool) p = (id . show, flip (<))f1 = fst p f2 = snd p-----------------------Without NoMonomorphismRestriction, I got: D:\work\test1.hs:6:10: Ambiguous type variable `a0' in the constraint: (Show a0) arising from a use of `p' Possible cause: the monomorphism restriction applied to the following: f1 :: a0 -> String (bound at D:\work\hsOcaml\test1.hs:6:1) Probable fix: give these definition(s) an explicit type signature or use -XNoMonomorphismRestriction In the first argument of `fst', namely `p' In the expression: fst p In an equation for `f1': f1 = fst pD:\work\hsOcaml\test1.hs:6:10: Ambiguous type variable `b0' in the constraint: (Ord b0) arising from a use of `p' Probable fix: add a type signature that fixes these type variable(s) ...... Failed, modules loaded: none. ------------------With NoMonomorphismRestriction, I got: D:\work\test1.hs:6:10: Ambiguous type variable `b0' in the constraint: (Ord b0) arising from a use of `p' Probable fix: add a type signature that fixes these type variable(s) In the first argument of `fst', namely `p' In the expression: fst p In an equation for `f1': f1 = fst pD:\work\test1.hs:7:10: Ambiguous type variable `a0' in the constraint: (Show a0) arising from a use of `p' Probable fix: add a type signature that fixes these type variable(s) In the first argument of `snd', namely `p' In the expression: snd p In an equation for `f2': f2 = snd p Failed, modules loaded: none. Thanks, Ting > From: ketil@malde.org
To: tinlyx@hotmail.com CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] a code that cannot compile with or without NoMonomorphismRestriction Date: Thu, 29 Mar 2012 12:27:04 +0200
Ting Lei
writes: (f1, f2) = let commond_definitions = undefined in let f1 = id.show f2 x = (< x) in (f1, f2)
I think the type signatures should be:
f1 :: Show a => a -> String
and
f2 :: Ord b => b -> b -> Bool
When I define these separately, this works:
f1 :: Show a => a -> String f1 = id . show
f2 :: Ord b => b -> b -> Bool f2 = flip (<)
But when I define them as a pair
f1 :: Show a => a -> String f2 :: Ord b => b -> b -> Bool (f1,f2) = (id . show, flip (<))
I get an error message:
Line 9: 1 error(s), 0 warning(s)
Couldn't match expected type `forall a. Show a => a -> String' with actual type `a -> String' When checking that `f1' has the specified type `forall a1. Show a1 => a1 -> String'
Defining the pair at once works:
p :: (Show a, Ord b) => (a -> String, b -> b -> Bool) p = (id . show, flip (<))
I guess that didn't help a lot, somebody with deeper GHC-fu than me will have to step in.
-k -- If I haven't seen further, it is by standing in the footprints of giants