
Hi, Does it make sense to declare a transparent identity instance for Functor, Applicative, Monad, etc? For example, I might want to generalize ($) = (<*>) where
($) :: (a -> b) -> a -> b (<*>) :: (Functor f) => f (a -> b) -> f a -> f b
The traditional definition makes Identity a newtype:
newtype Identity a = Identity a instance Applicative Identity where pure a = Identity a (Identity f) <*> (Identity a) = Identity (f a)
But using this instance becomes unwieldy. If using Identity was transparent, eg. if it was a type synonym
{-# LANGUAGE TypeSynonymInstances #-} type Identity a = a instance Applicative Identity where -- something like pure a = a f <*> a = f a
But GHC does not accept type synonym instances unless they are fully applied. Is it sound for such an instance to exist? If so, how might it be defined? -- Jafet

On Sun, Nov 28, 2010 at 15:59, Jafet
But using this instance becomes unwieldy. If using Identity was transparent, eg. if it was a type synonym
{-# LANGUAGE TypeSynonymInstances #-} type Identity a = a instance Applicative Identity where -- something like pure a = a f <*> a = f a
But GHC does not accept type synonym instances unless they are fully applied.
Is it sound for such an instance to exist? If so, how might it be defined?
Type synonym instances are nothing special, they are just shorthand for writing an instance for the type they are a synonym for. So an instance for 'Identity a' would actually be an instance for 'a' (which isn't such a good idea). An instance for 'Identity' is indeed not possible. Erik

On 11/28/10 9:59 AM, Jafet wrote:
But GHC does not accept type synonym instances unless they are fully applied.
That's precisely the problem, and why a newtype is used. More than GHC implementation details, there's the deeper problem that allowing general type-level functions causes decidability problems in type checking/inference. Using a newtype with its explicit wrapping and unwrapping solves the problem of inference by, essentially, adding type annotations. Similar tricks are involved in making recursive types work. -- Live well, ~wren

On Sun, Nov 28, 2010 at 10:59 PM, Jafet wrote:
Hi,
Does it make sense to declare a transparent identity instance for Functor, Applicative, Monad, etc? For example, I might want to generalize ($) = (<*>) where
($) :: (a -> b) -> a -> b (<*>) :: (Functor f) => f (a -> b) -> f a -> f b
[...]
Is it sound for such an instance to exist? If so, how might it be defined?
Hi again, This is my partial progress. I tried to stuff the Identity concept into another typeclass
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
class FunctorApply a b a' b' where
fmap' :: (a -> b) -> a' -> b'
instance (Functor f) => FunctorApply a b (f a) (f b) where
fmap' = fmap
instance FunctorApply a b a b where
fmap' = id
FunctorApply does work... on purely monomorphic arguments, so that the only thing that needs to be inferred is the instance to use:
monosucc :: Int -> Int
monosucc = succ
foo :: Int
foo = fmap' monosucc (1 :: Int)
bar :: [Int]
bar = fmap' monosucc ([1,2,3] :: [Int])
It does not work with even the slightest polymorphism, because FunctorApply, like other typeclasses, is open:
foo_bad = fmap' monosucc (1 :: Int)
bar_bad = fmap' succ ([1,2,3] :: [Int]) :: [Int]
foo_bad expects a fictional instance FunctorApply Int Int Int b, and similarly for bar_bad. PS: The replies stating that overlapping or undecidable instances would be required are probably true. Here is my failed attempt to generalize FunctorApply with Oleg magick:
{-# LANGUAGE EmptyDataDecls, ScopedTypeVariables, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, FunctionalDependencies, UndecidableInstances #-}
class FunctorApply a b a' b' where
fmap' :: (a -> b) -> a' -> b'
class FunctorApply' af bf a b a' b' where
fmap'' :: af -> bf -> (a -> b) -> a' -> b'
instance (Classify a a' af, Classify b b' bf, FunctorApply' af bf a b a' b') => FunctorApply a b a' b' where
fmap' = fmap'' (undefined::af) (undefined::bf)
instance FunctorApply' HId HId a b a b where
fmap'' _ _ = id
instance (Functor f, Classify a (f a) HFunctor, Classify b (f b) HFunctor) => FunctorApply' HFunctor HFunctor a b (f a) (f b) where
fmap'' _ _ f = fmap f
data HFunctor
data HId
class Classify a f x
instance (Functor f, TypeCast x HFunctor) => Classify a (f a) x
instance (TypeCast x HId) => Classify a a x
-- from HList
class TypeCast a b | a -> b, b -> a where typeCast :: a -> b
class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b
class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b
instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x
instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast''
instance TypeCast'' () a a where typeCast'' _ x = x
But fmap' still cannot be used polymorphically. What is wrong with the above code? PPS: In the initial post, (<*>) is of course a method of Applicative, not Functor. -- Jafet

On Sun, 2010-11-28 at 22:59 +0800, Jafet wrote:
{-# LANGUAGE TypeSynonymInstances #-} type Identity a = a instance Applicative Identity where -- something like pure a = a f <*> a = f a
But GHC does not accept type synonym instances unless they are fully applied.
Is it sound for such an instance to exist? If so, how might it be defined?
data Tag a = Tag
instance Applicative Tag where pure _ = Tag Tag <*> Tag = Tag
cast :: Tag a -> Tag b cast Tag = Tag
1. pure id <*> Tag = Tag 2. I'm too lazy to prove it 3. pure f <*> pure x = Tag <*> Tag = Tag = pure (f x) 4. u <*> pure y = u <*> Tag = u = Tag <*> u = pure ($ y) <*> u
x = pure undefined y = x :: Tag ()
Is y defined? pure!Tag undefined = Tag pure!Identity undefined = undefined Regards
participants (4)
-
Erik Hesselink
-
Jafet
-
Maciej Piechotka
-
wren ng thornton