
Hello *, For simple-kinded type variables, instances of the type instance NFData a => NFData [a] instance NFData a => NFData (Maybe a) instance (NFData a, NFData b) => NFData (a, b) are common and can be defined effortless; now I wanted do something similiar for a type with a phantom type parameter: {-# LANGUAGE KindSignatures, TypeSynonymInstances #-} import Control.Applicative import Control.Monad data DataBase = DataBase -- specific type not relevant here data Res data Unres -- provides operation to transform an unresolved `Foo_ Unres` to a resolved `Foo_ Res` class Resolvable (e :: * -> *) where resolve :: DataBase -> e Unres -> Either String (e Res) -- trivial /resolvable/ type data Foo_ r = Foo instance Resolvable Foo_ where resolve _ x = return Foo ...it was no problem to define the polymorphic operations outside of an instance: -- Maybe (polymorphic 0 or 1 element container) resolveMaybe :: Resolvable e => DataBase -> Maybe (e Unres) -> Either String (Maybe (e Res)) resolveMaybe db (Just x) = Just <$> resolve db x resolveMaybe db Nothing = pure Nothing -- Pairs resolvePair :: (Resolvable e0, Resolvable e1) => DataBase -> (e0 Unres, e1 Unres) -> Either String (e0 Res, e1 Res) resolvePair db (x,y) = (,) <$> resolve db x <*> resolve db y ...but when I tried to wrap those into polymorphic instances in the style of the instances at the beginning of this mail, I wasn't able to convince GHC: The following attempts wouldn't work: instance Resolvable e => Resolvable (Maybe e) where resolve = resolveMaybe -- GHC fails with: -- Expecting one more argument to `e' -- In the instance declaration for `Resolvable (Maybe e)' Fair enough, but trying to workaround this by defining a type-synonym to get an (*->*)-kinded expression didn't work either, as currying doesn't seem to be supported at the type-level (is there a language-extension for that?): type Maybe_ e r = Maybe (e r) instance Resolvable e => Resolvable (Maybe_ e) where resolve = resolveMaybe -- GHC fails with: -- Type synonym `Maybe_' should have 2 arguments, but has been given 1 -- In the instance declaration for `Resolvable (Maybe_ e)' So, am I really out of luck here, wanting to define polymorphic instances in combination with phantom-types, or is there a trick I haven't thought of yet? PS: while experimenting, I accidentally triggered the following GHC exception: *** Exception: compiler/rename/RnSource.lhs:429:14-81: Irrefutable pattern failed for pattern Data.Maybe.Just (inst_tyvars, _, SrcLoc.L _ cls, _) ...alas I lost the Haskell-code causing this; is this a known issue? Should I try harder to reproduce it again? cheers, hvr --