[Haskell-cafe] Transparent identity instances

2010-11-28 Thread Jafet
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Transparent identity instances

2010-11-28 Thread Erik Hesselink
On Sun, Nov 28, 2010 at 15:59, Jafet jafet.vi...@gmail.com wrote:
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Transparent identity instances

2010-11-28 Thread wren ng thornton

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe