I know that TypeSynomymInstances only allows fully applied type synonyms to be used in instance heads, but it seems like it would be handy if I could use paritally applied t
Partially applied type synonyms are not allowed in Haskell at all. A partially applied synonym is effectively a function whose inputs are the un-applied types and whose output is a type. For example, here is an encoding of boolean logic:
type True x y = x
type False x y = y
type Not b x y = b y x
type And b1 b2 x y = b1 (b2 x y) y
type Or b1 b2 x y = b1 x (b2 x y)
To decide whether two partially applied type synonyms are equal, the type checker would have to decide whether functions are equal. This is a hard problem, and in general it is undecidable.
Another issue with allowing partially applied type synonyms is that they would make type inference and instance selection essentially impossible. For example, suppose in the context of some program I wanted to use thingy
at the type Int -> String -> Int -> (Int, String)
. thingy
has type forall a b e. a -> b -> e a b
, so we can unify a
with Int
and b
with String
, but if e
is allowed to be a partially applied type synonym, we could have
e = FuncSynonym (,)
or
e = FuncSynonym' Int (,) where type FuncSynonym' x f a b = x -> f a b
or even
e = Const2 (Int -> (Int, String)) where Const2 a x y = a
The problem of type inference would become even worse than deciding equality of functions; it would require considering all functions with specified output on a particular input, or similar more complicated problems (imagine simply trying to unify a b
with Int
).
As we known Maybe
's kind is *->*
.
So it could be a instance of Functor
instance Functor Maybe where
fmap :: f -> Maybe a -> Maybe b
fmap f Nothing = Nothing
fmap f (Maybe x) = Maybe (f x)
The first example:
{-# LANGUAGE TypeSynonymInstances #-}
type MaybeAlias a = Maybe
instance {-# OVERLAPPING #-} Functor (MaybeAlias Int) where
fmap f functor = undefined
Under the effect of TypeSynonymInstances
extension (almost like a String replace), it equals
instance {-# OVERLAPPING #-} Functor Maybe where
fmap f functor = undefined
It is ok, because allow fully applied type synonyms to be used in instance heads
See the other example:
{-# LANGUAGE TypeSynonymInstances #-}
type MaybeAlias a b = Maybe
What's the kind of MaybeAlias Int
now? It's kind is *->*->*
.
Why?
As @heatsink comment above:
A partially applied synonym is effectively a function whose inputs are the un-applied types and whose output is a type
Explain it now:
Under the defintion of type MaybeAlias a b = Maybe
:
MaybeAlias
like a partially applied function:
(MaybeAlias) :: a -> b -> Maybe
MaybeAlias Int
like a partially applied function:
(MaybeAlias Int) :: b -> Maybe
The Maybe
's kind is * -> *
, b
's kind is *
.
So MaybeAlias Int
's kind is * -> (* -> *)
.
And * -> (* -> *)
equals * -> * -> *
.
The root cause why the below code not working, because Functor
typeclass only accept type that has kind * -> *
, not * -> * ->*
!
{-# LANGUAGE TypeSynonymInstances #-}
type MaybeAlias a b = Maybe
instance {-# OVERLAPPING #-} Functor (MaybeAlias Int) where
fmap f functor = undefined
Why the below code not working?
class Example e where
thingy :: a -> b -> e a b
-- legit, but awkward
newtype FuncWrapper e a b = FuncWrapper { ap :: a -> e a b }
instance (Example e) => Example (FuncWrapper e) where
thingy _ = FuncWrapper . flip thingy
funcWrapperUse :: (Example e) => e Int String
funcWrapperUse = thingy 1 "two" `ap` 3 `ap` 4 `ap` 5
-- not legal, but a little easier to use
type FuncSynonym e a b = a -> e a b
instance (Example e) => Example (FuncSynonym e) where
thingy _ = flip thingy
funcSynonymUse :: (Example e) => e Int String
funcSynonymUse = thingy 1 "two" 3 4 5
Example
typeclass accept a type that has kind * -> * -> *
FuncSynonym
like a partially applied function:
FuncSynonym :: e -> a -> b -> (a -> e a b)
FuncSynonym e
like a partially applied function:
(FuncSynonym e):: a -> b -> ( a -> e a b)
a
's kind is *
,
b
's kind is *
,
a -> e a b
's kind *
(FuncSynonym e)
's kind is * -> * -> *
Example
typeclass accept a type that has kind * -> * -> *
, but why still not work?
It's the other reason in ghc issue 785 and comment