[Haskell-cafe] Re: Transparent identity instances

Jafet jafet.vixle at gmail.com
Mon Nov 29 10:47:21 CET 2010


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


More information about the Haskell-Cafe mailing list