I posted the following on stackoverflow, but it hasn't got too much attention so I thought I'd ask here:
I can write the following:
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ConstraintKinds #-} f :: Integral a => (forall b. Num b => b) -> a f = id
And all is good. Presumably GHC can derive
Integral
fromNum
so all is well.I can be a bit tricker, yet I'm still fine:
class Integral x => MyIntegral x instance Integral x => MyIntegral x class Num x => MyNum x instance Num x => MyNum x f' :: MyIntegral a => (forall b. MyNum b => b) -> a f' = id
So lets say I want to generalise this, like so:
g :: c2 a => (forall b. c1 b => b) -> a g = id
Now obviously this will spit the dummy, because GHC can not derive
c2
fromc1
, asc2
is not constrained.What do I need to add to the type signature of
g
to say that "you can derivec2
fromc1
"?
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell- cafe
Only members subscribed via the mailman list are allowed to post.