[Haskell-cafe] {-# LANGUAGE DeriveApplicative #-} ?

Neil Mitchell ndmitchell at gmail.com
Fri May 7 15:32:55 EDT 2010


Hi,

If you think you can write an algorithm for deriving Applicative, I'd
welcome you to try adding it to Derive:
http://community.haskell.org/~ndm/derive

The Functor/Foldable/Traversable derivations all started out in
Derive, got tested/implemented/refined there, then moved to GHC later.
I think that's a reasonable path with any Applicative derivation.

Thanks, Neil

On Thu, May 6, 2010 at 11:53 AM, Ben Millwood <haskell at benmachine.co.uk> wrote:
> On Thu, May 6, 2010 at 8:55 AM, Pavel Perikov <perikov at gmail.com> wrote:
>> Hi, list!.
>>
>> Now in 6.12.1 we have DeriveFunctor, DeriveFoldable and DeriveTraversable. This greatly simplifies the "reuse structure" style of programming. Some structure (not just _data_ structure) got captured in ADT and can be reused for various purposes.
>>
>> Wouldn't it be nice to have the ability to derive Applicative as well? It shouldn't be more difficult than deriving Functor but will provide exciting possibilities. Just think about liftA2.
>>
>
> The difference is that there is at most one law-abiding instance of
> Functor for each type, whereas there are in principle multiple
> possible instances for Applicative for a type. E.g. the following:
>
> instance Applicative [] where
>  pure x = [x]
>  fs <*> xs = concatMap (\f -> map f xs) fs
>
> instance Applicative [] where
>  pure = repeat
>  (f:fs) <*> (x:xs) = f x : fs <*> xs
>  _ <*> _ = []
>
> are both law-abiding instances (although only one has a corresponding
> law-abiding Monad, I believe). Which should GHC choose?
> It's worth noting, though, that there are other derivable classes that
> don't have a single implementation. It's a question of trading off
> complexity of the compiler versus saved effort in code versus
> additional clarity in code, I think.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list