On 2015-12-20 08:01 PM, Noon Silk wrote:
{-# LANGUAGE NoMonomorphismRestriction #-}
data Status = Foo | Bar
data Rec m a = Rec {
get :: m a
, status :: Status
}
defRec :: (Monad m) => Rec m a
defRec = undefined
myRec :: (Monad m) => Rec m a
myRec = Rec x y
where
Rec x y = defRec
Why this is an ambiguous-type error is a really long story. But a factor is analogous to "show . read". Another factor is that since you turn off the monomorphism restriction, there is a type generalization step, and the generalizing of y's type is separate from the generalization of x's type.
I have found this solution, it works by connecting types to suppress the generalize step:
{-# LANGUAGE NoMonomorphismRestriction, ScopedTypeVariables #-}
...
myRec :: forall m a. (Monad m) => Rec m a
myRec = Rec x y
where
Rec x y = defRec :: Rec m a
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe