Here is the code where ImpredicativeTypes
is enabled for a feature I am exploring:
{-# LANGUAGE ImpredicativeTypes #-}
data Fn a b = MkFn a b deriving Show
data AnyFn = forall a b. (Show a, Show b) => MkAnyFn (Fn a b)
instance Show AnyFn where show (MkAnyFn fn) = show fn
data AnyFn' = MkAnyFn' (forall a b. (Show a, Show b) => Fn a b)
-- This doesn't typecheck:
-- instance Show AnyFn' where show (MkAnyFn' fn) = show fn
-- This doesn't typecheck:
-- toAnyFns :: [forall a b. Fn a b] -> [AnyFn]
-- toAnyFns = fmap MkAnyFn
toAnyFns' :: [forall a b. (Show a, Show b) => Fn a b] -> [AnyFn']
toAnyFns' = fmap MkAnyFn'
-
The
AnyFn
is a rather standard way of defining existential type (an alternative form is in GADT). -
The
AnyFn'
is rather different, it doesnât require theImpredicativeTypes
extension, but I donât know how to call it. And I canât quite define a show instance for it:
impredicativetypes.hs:10:49: error: [GHC-39999]
⢠Ambiguous type variable âa0â arising from a use of âshowâ
prevents the constraint â(Show a0)â from being solved.
Probable fix: use a type annotation to specify what âa0â should be.
Potentially matching instances:
instance Show Ordering -- Defined in âGHC.Showâ
instance Show AnyFn -- Defined at impredicativetypes.hs:6:10
...plus 28 others
...plus 13 instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
⢠In the expression: show fn
In an equation for âshowâ: show (MkAnyFn' fn) = show fn
In the instance declaration for âShow AnyFn'â
|
10 | instance Show AnyFn' where show (MkAnyFn' fn) = show fn
| ^^^^
-
toAnyFns
attempts to convert a list ofFn a b
with impredicativea
andb
, but it fails to typecheck:
impredicativetypes.hs:14:12: error: [GHC-83865]
⢠Couldn't match type: Fn a0 b0
with: forall a b. Fn a b
Expected: [forall a b. Fn a b] -> [AnyFn]
Actual: [Fn a0 b0] -> [AnyFn]
⢠In the expression: fmap MkAnyFn
In an equation for âtoAnyFnsâ: toAnyFns = fmap MkAnyFn
|
14 | toAnyFns = fmap MkAnyFn
-
toAnyFns'
though typechecks.
So how can I have toAnyFns'
and also the Show instance?
Edit: Though I am ready to accept that maybe it is what impredicative types for, where the type information is simply âgoneâ. But I donât have the right words and intuition to describe that yet.