List of Functors - haskell

This might apply for any type class, but lets do it for Functors as I know them better. I wan't to construct this list.
l = [Just 1, [1,2,3], Nothing, Right 4]
and then
map (fmap (+1)) l
to get
[Just 2, [2,3,4], Nothing, Right 5]
I know they are all Functors that contain Ints so it might be possible. How can I do this?
Edit
This is turning out to be messier than it would seem. In Java or C# you'd declare the IFunctor interface and then just write
List<IFunctor> l = new List<IFunctor> () {
new Just (1),
new List<Int>() {1,2,3},
new Nothing<Int>(),
new Right (5)
}
assuming Maybe, List and Either implement the IFunctor. Naturally Just and Nothing extend Maybe and Right and Left extend Either. Not satisfied with this problem being easier to resolve on these languages!!!
There should cleaner way in Haskell :(

In Haskell, downcasting is not allowed. You can use AnyFunctor, but the trouble with that is there is no longer any way to get back to a functor that you know. When you have an AnyFunctor a, all you know is that you have an f a for some f, so all you can do is fmap (getting you another AnyFunctor). Thus, AnyFunctor a is in fact equivalent to ().
You can add structure to AnyFunctor to make it more useful, and we'll see a bit of that later on.
Functor Coproducts
But first, I'll share the way that I would probably end up doing this in a real program: by using functor combinators.
{-# LANGUAGE TypeOperators #-}
infixl 1 :+: -- declare this to be a left-associative operator
data (f :+: g) a = FLeft (f a) | FRight (g a)
instance (Functor f, Functor g) => Functor (f :+: g) where
-- left as an exercise
As the data type reads, f :+: g is a functor whose values can be either f a or g a.
Then you can use, for example:
l :: [ (Maybe :+: []) Int ]
l = [ FLeft (Just 1), FRight [2,3,4], FLeft Nothing ]
And you can observe by pattern matching:
getMaybe :: (Maybe :+: g) a -> Maybe a
getMaybe (FLeft v) = v
getMaybe (FRight _) = Nothing
It gets ugly as you add more functors:
l :: [ (Maybe :+: [] :+: Either Int) Int ]
l = [ FLeft (FLeft Nothing), FRight (Right 42) ]
-- Remember that we declared :+: left-associative.
But I recommend it as long as you can handle the ugliness, because it tracks the list of possible functors in the type, which is an advantage. (Perhaps you eventually need more structure beyond what Functor can provide; as long as you can provide it for (:+:), you're in good territory.)
You can make the terms a bit cleaner by creating an explicit union, as Ganesh recommends:
data MyFunctors a
= FMaybe (Maybe a)
| FList [a]
| FEitherInt (Either Int a)
| ...
But you pay by having to re-implement Functor for it ({-# LANGUAGE DeriveFunctor #-} can help). I prefer to put up with the ugliness, and work at a high enough level of abstraction where it doesn't get too ugly (i.e. once you start writing FLeft (FLeft ...) it's time to refactor & generalize).
Coproduct can be found in the comonad-transformers package if you don't want to implement it yourself (it's good exercise though). Other common functor combinators are in the Data.Functor. namespace in the transformers package.
Existentials with Downcasting
AnyFunctor can also be extended to allow downcasting. Downcasting must be explicitly enabled by adding the Typeable class to whatever you intend to downcast. Every concrete type is an instance of Typeable; type constructors are instances of Typeable1 (1 argument); etc. But it doesn't come for free on type variables, so you need to add class constraints. So the AnyFunctor solution becomes:
{-# LANGUAGE GADTs #-}
import Data.Typeable
data AnyFunctor a where
AnyFunctor :: (Functor f, Typeable1 f) => f a -> AnyFunctor a
instance Functor AnyFunctor where
fmap f (AnyFunctor v) = AnyFunctor (fmap f v)
Which allows downcasting:
downcast :: (Typeable1 f, Typeable a) => AnyFunctor a -> Maybe (f a)
downcast (AnyFunctor f) = cast f
This solution is actually cleaner than I had expected to be, and may be worth pursuing.

One approach is to use existentials:
{-# LANGUAGE GADTs #-}
data AnyFunctor v where
AnyFunctor :: Functor f => f v -> AnyFunctor v
instance Functor AnyFunctor where
fmap f (AnyFunctor fv) = AnyFunctor (fmap f fv)
The input list you ask for in your question isn't possible as it stands because it's not correctly typed, so some wrapping like AnyFunctor is likely to be necessary however you approach it.
You can make the input list by wrapping each value in the AnyFunctor data constructor:
[AnyFunctor (Just 1), AnyFunctor [1,2,3],
AnyFunctor Nothing, AnyFunctor (Right 4)]
Note that when you use fmap (+1) it's a good idea to use an explicit type signature for the 1 to avoid any problems with numeric overloading, e.g. fmap (+(1::Integer)).
The difficulty with AnyFunctor v as it stands is that you can't actually do much with it - you can't even look at the results because it isn't an instance of Show, let alone extract a value for future use.
It's a little tricky to make it into an instance of Show. If we add a Show (f v) constraint to the AnyFunctor data constructor, then the Functor instance stops working because there's no guarantee it'll produce an instance of Show itself. Instead we need to use a sort of "higher-order" typeclass Show1, as discussed in this answer:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GADTs #-}
data AnyFunctor v where
AnyFunctor :: (Show1 f, Functor f) => f v -> AnyFunctor v
instance Functor AnyFunctor where
fmap f (AnyFunctor fv) = AnyFunctor (fmap f fv)
data ShowDict a where
ShowDict :: Show a => ShowDict a
class Show1 a where
show1Dict :: ShowDict b -> ShowDict (a b)
instance Show v => Show (AnyFunctor v) where
show (AnyFunctor (v :: f v)) =
case show1Dict ShowDict :: ShowDict (f v) of
ShowDict -> "AnyFunctor (" ++ show v ++ ")"
instance Show1 [] where
show1Dict ShowDict = ShowDict
instance Show1 Maybe where
show1Dict ShowDict = ShowDict
instance Show a => Show1 (Either a) where
show1Dict ShowDict = ShowDict
In ghci this gives the following (I've broken the lines for readability):
*Main> map (fmap (+1)) [AnyFunctor (Just 1), AnyFunctor [1,2,3],
AnyFunctor Nothing, AnyFunctor (Right 4)]
[AnyFunctor (Just 2),AnyFunctor ([2,3,4]),
AnyFunctor (Nothing),AnyFunctor (Right 5)]
The basic idea is to express the idea that a type constructor like Nothing, [] or Either a "preserves" the Show constraint, using the Show1 class to say that Show (f v) is available whenever Show v is available.
The same trick applies with other typeclasses. For example #luqui's answer shows how you can extract values using the Typeable class, which already has a built-in Typeable1 variant. Each type class that you add limits the things that you can put into AnyFunctor, but also means you can do more things with it.

One option would be to create a specific data type for your use case, with the additional advantage of having proper names for things.
Another would be to create a specialized * -> * tuples as:
newtype FTuple4 fa fb fc fd r = FTuple4 (fa r, fb r, fc r, fd r)
deriving (Eq, Ord, Show)
So the tuple is homogeneous in values, but heterogeneous in functors.
Then you can define
instance (Functor fa, Functor fb, Functor fc, Functor fd) =>
Functor (FTuple4 fa fb fc fd) where
fmap f (FTuple4 (a, b, c, d)) =
FTuple4 (fmap f a, fmap f b, fmap f c, fmap f d)
and
main = let ft = FTuple4 (Just 1,
[1,2,3],
Nothing,
Right 4 :: Either String Int)
in print $ fmap (+ 1) ft
With this approach, you can pattern match on the result easily, without losing information about the types of the individual elements, their order etc. And, you can have similar instances for Foldable, Traversable, Applicative etc.
Also you don't need to implement the Functor instance yourself, you can use GHC's deriving extensions, so all you need to write to get all the instances is is just
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
import Data.Foldable
import Data.Traversable
newtype FTuple4 fa fb fc fd r = FTuple4 (fa r, fb r, fc r, fd r)
deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
And even this can be further automated for arbitrary length using Template Haskell.
The advantage of this approach is mainly in the fact that it just wraps ordinary tuples, so you can seamlessly switch between (,,,) and FTuple4, if you need.
Another alternative, without having your own data type, would be to use nested functor products, since what you're describing is just a product of 4 functors.
import Data.Functor.Product
main = let ft = Pair (Just 1)
(Pair [1,2,3]
(Pair Nothing
(Right 4 :: Either String Int)
))
(Pair a (Pair b (Pair c d))) = fmap (+ 1) ft
in print (a, b, c, d)
This is somewhat verbose, but you can do much better by creating your own functor product using type operators:
{-# LANGUAGE TypeOperators, DeriveFunctor #-}
data (f :*: g) a = f a :*: g a
deriving (Eq, Ord, Show, Functor)
infixl 1 :*:
main = let a :*: b :*: c :*: d = fmap (+ 1) $ Just 1 :*:
[1,2,3] :*:
Nothing :*:
(Right 4 :: Either String Int)
in print (a, b, c, d)
This gets probably as terse and universal as possible.

Related

Applicative Instance of Pair Data Type in Haskell

I am trying to implement this pair data type as an applicative functor but I am told that 'a' is not in scope. I thought already stated what 'a' was in the instance declaration.
data Pair a b = Pair a b deriving (Show)
instance Functor (Pair a) where
fmap f (Pair a b) = Pair a (f b)
instance Applicative (Pair a) where
pure x = Pair a x
Pair a f <*> Pair a' x = Pair (a + a') (f x)
a is a type variable, not something you can use in the definition of pure. pure needs some way of getting a value of type a to pair with x. There are a few ways you could do that:
A function of type b -> a that you could apply to x.
A function of type () -> a that you could apply to ().
Some predefined value of type a.
The Applicative instance of (,) a takes the third approach, by requiring that a have a Monoid instance so that you can define pure in terms of mempty.
instance Monoid a => Applicative (Pair a) where
pure x = Pair mempty x
Pair a f <*> Pair a' x = Pair (a <> a') (f x)
In your definition, you assumed that (+) is defined for the a values, which means you are missing a Num constraint, but also that you could simply use 0 in your definition of pure.
instance Num a => Applicative (Pair a) where
pure x = Pair 0 x
Pair a f <*> Pair a' x = Pair (a + a') (f x)
You can also derive it via the new Generically1 applied to Sum a
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
import GHC.Generics (Generic1, Generically1(..))
import Data.Monoid (Sum(..))
data Pair a b = Pair a b
deriving
stock (Show, Generic1)
deriving (Functor, Applicative)
via Generically1 (Pair (Sum a))

For what Alt in Monoid instance needed?

In Monoid and Semigroup instances of Alternative Alt used.
Why we can't write instance without it?
{-# LANGUAGE FlexibleInstances #-}
instance Alternative f => Semigroup (f a) where
(<>) = <|>
instance Alternative f => Monoid (f a) where
mempty = empty
And if we can write that, can we then replace Alternative with (Monoid (f a), Applicative f) in functions?
You use it for deriving Monoid for any Alternative
{-# Language DerivingVia #-}
data F a = ..
deriving (Semigroup, Monoid)
via Alt F a
instance Functor F where ..
instance Applicative F where ..
instance Alternative F where ..
Alt is a newtype for good reason as there are many ways to describe Monoid behaviour for an applied type f a. For example Applicative lifting: Ap.
{-# Language DerivingVia #-}
data G a = ..
deriving (Semigroup, Monoid, Num, Bounded)
via Ap G a
instance Functor G where ..
instance Applicative G where ..
The instances you give are maximally overlapping, the Monoid instance of any applied type is now forced to be the Alternative instance, completely ignoring the a parameter.
There are many instances where this would not be correct, for example Semigroup a => Semigroup (Maybe a) is not the same as the Semigroup you would get from Alternative Maybe.
It is possible using a rather new feature QuantifiedConstraints to quantify over the argument of a type constructor forall x. Monoid (f x). This is not the same as Alternative but similar
{-# Language QuantifiedConstraints #-}
..
type Alternative' :: (Type -> Type) -> Constraint
class (forall x. Monoid (f x)) => Alternative' f
instance (forall x. Monoid (f x)) => Alternative' f
You use the (<|>) :: Alternative f => f a -> f a -> f a and empty :: Alternative f => f a. As the signatures suggest, these are defined for items of type Applicative f => f a. You thus can only use these functions to process such items, and this thus requires that if you work with an f a, for eample to define mempty :: f a with mempty = empty, then that requires that f is a member of the Alternative typeclass.
That being said, while a lot data types can have a Semigroup and Monoid instance defined as how the Alternative is implemented, this is not per se the best instance. Yes Alternative is a monoid on applicative functors, but that should not per se be the monoid instance on these data types.
If the instances you propose existed in that form, every type that matches f a would immediately defer to it. That includes types where it makes sense, but consider
newtype ResultsSum a = ResultsSum {funToSum :: a -> Int}
instance Semigroup (ResultsSum a) where
ResultsSum p <> ResultsSum q = ResultsSum $ \x -> p x + q x
Unfortunately though, ResultsSum a matches f a. But it is not an Alternative; it isn't even a functor, and can't be (rather, it is Contravariant). However, the compiler doesn't take that into account when resolving instances: it just sees two instance declarations whose heads both purport to enable ResultsSum being a semigroup, which triggers an ambiguous-instance error.
Granted, this example could be addressed with {-# OVERLAPPING #-} pragmas, but it's always best to avoid instance overlaps as they can lead to strange. It's unnecessary, since you can also also derive those instances via the Alternative one. Though I personally would actually rather do it the other way around: define the Monoid instance first and then Alternative in terms of it.

Applicative instance trying to use monoidal functors

I'm learning Haskell and trying to do exercises from book Haskell Programming from first principles and I'm stack trying to write applicative for Pair type
data Pair a = Pair a a deriving Show
I have seen some other examples on web but I'm trying somewhat different applicative functor, I'm trying to utilize monoidal structure of this type. Here is what I have
data Pair a = Pair a a deriving (Show, Eq)
instance Functor Pair where
fmap f (Pair x y) = Pair (f x) (f y)
instance Semigroup a => Semigroup (Pair a) where
(Pair x y) <> (Pair x' y') = Pair (x <> x') (y <> y')
instance Applicative Pair where
pure x = Pair x x
(Pair f g) <*> p = fmap f p <> fmap g p
Unfortunately this will not compile:
* No instance for (Semigroup b) arising from a use of `<>'
Possible fix:
add (Semigroup b) to the context of
the type signature for:
(<*>) :: forall a b. Pair (a -> b) -> Pair a -> Pair b
* In the expression: fmap f p <> fmap g p
In an equation for `<*>': (Pair f g) <*> p = fmap f p <> fmap g p
In the instance declaration for `Applicative Pair'
And this is where I'm stack; I don't see how can I add typeclass constraint to Applicative definition and I thought that making type Pair instance of Semigroup is enough.
Other solutions that I have seen are like
Pair (f g) <*> Pair x y = Pair (f x) (g y)
but these solutions don't utilize monoidal part of Pair type
Is it even possible to make this applicative the way I't trying?
Although it's true that Applicative is the class representing monoidal functors (specifically, Hask endofunctors which are monoidal), Allen&Moronuki present this unfortunately in a way that seems to suggest a direct relation between the Monoid and Applicative classes. There is, in general, no such relation! (The Writer type does define one particular Applicative instance based on the Monoid class, but that's an extremely special case.)
This spawned a rather extended discussion at another SO question.
What the “monoidal” in “monoidal functor” refers to is a monoidal structure on the category's objects, i.e. on Haskell types. Namely, you can combine any two types to a tuple-type. This has per se nothing whatsoever to do with the Monoid class, which is about combining two values of a single type to a value of the same type.
Pair does allow an Applicative instance, but you can't base it on the Semigroup instance, although the definition actually looks quite similar:
instance Applicative Pair where
pure x = Pair x x
Pair f g <*> Pair p q = Pair (f p) (g q)
However, you can now define the Semigroup instance in terms of this:
instance Semigroup a => Semigroup (Pair a) where
(<>) = liftA2 (<>)
That, indeed, is a valid Semigroup instance for any applicative, but it's usually not the definition you want (often, containers have a natural combination operation that never touches the contained elements, e.g. list concatenation).
I don't think that Pair is an Applicative the way you want it to be, Applicative states that
(<*>) :: f (a -> b) -> f a -> f b
should work for all functions in first position whereas you want
(<*>) :: Semigroup b => f (a -> b) -> f a -> f b.
If Pair was always a Semigroup (like Maybe or List for example) your reasoning would be sound, but you need the pre-requisite of the Pair-containee to be Semigroup.
Correct: Pair can't be made an Applicative in the way you want, because Applicative f demands that f a "feel applicative-y" for any a, even non-Semigroup as. Consider writing an alternative class and implementing it:
class CApplicative f where
type C f
pure :: C f a => a -> f a
app :: C f b => f (a -> b) -> f a -> f b
instance CApplicative Pair where
type C Pair = Semigroup
pure x = Pair x x
app (Pure f g) p = fmap f p <> fmap g p
This can be derive since base 4.17.0.0, which includes the via types Generically and Generically1. This will derive the same instances as leftaroundabout writes:
{-# Language DeriveGeneric #-}
{-# Language DerivingStrategies #-}
{-# Language DerivingVia #-}
import Data.Monoid
import GHC.Generics
data Pair a = Pair a a
deriving
stock (Generic, Generic1)
deriving (Semigroup, Monoid)
via Generically (Pair a)
deriving (Functor, Applicative)
via Generically1 Pair
Alternatively you can lift Semigroup and Monoid through the Applicative
deriving (Semigroup, Monoid, Num)
via Ap Pair a

Endofunction as Monoid

I'm trying this (for learning purposes):
{-# LANGUAGE FlexibleInstances #-}
instance Monoid (a -> a) where
mempty = id
mappend f g = f . g
expecting id <> id to be equal to id . id
However, with (id <> id) 1 I receive this error:
Non type-variable argument in the constraint: Monoid (a -> a)
What should I change to run it?
It's just to understand monoids and Haskell typeclasses better, not for any practical usage.
This will need {-# OVERLAPPING #-} pragma since GHC.Base has an instance for Monoid (a -> b) when b is a Monoid:
{-# LANGUAGE FlexibleInstances #-}
import Data.Monoid (Monoid, mempty, mappend, (<>))
instance {-# OVERLAPPING #-} Monoid (a -> a) where
mempty = id
mappend f g = f . g
then, above instance will be invoked for a -> a, even if a is a Monoid:
\> (id <> id) 1
1
\> (id <> id) [1]
[1]
whereas with Monoid b => a -> b the instance from GHC.Base will be invoked:
\> ((:[]) <> (:[])) 1
[1,1]
Note that Data.Monoid provides an exact same instance as yours for a -> a but there the overlap is bypassed using newtype Endo a.
The Haskell Category class offers methods to work with categories whose objects are precisely the Haskell types of some kind. Specifically,
class Category c where
id :: c x x
(.) :: c y z -> c x y -> c x z
The names of the methods should look very familiar. Notably,
instance Category (->) where
id x = x
f . g = \x -> f (g x)
You probably know that monoids are semigroups with identities, expressed in Haskell using
class Monoid a where
mappend :: a -> a -> a
mempty :: a
But another mathematical perspective is that they're categories with exactly one object. If we have a monoid, we can easily turn it into a category:
-- We don't really need this extension, but
-- invoking it will make the code below more useful.
{-# LANGUAGE PolyKinds #-}
import Control.Category
import Data.Monoid
import Prelude hiding ((.), id)
newtype Mon m a b = Mon m
instance Monoid m => Category (Mon m) where
id = Mon mempty
Mon x . Mon y = Mon (x `mappend` y)
Going the other way is a little bit trickier. One way to do it is to choose a kind with exactly one type, and look at categories whose sole object is that type (prepare for yucky code, which you can skip if you like; the bit below is less scary). This shows that we can freely convert between a Category whose object is the type '() in the () kind and a Monoid. The arrows of the category become the elements of the monoid.
{-# LANGUAGE DataKinds, GADTs, PolyKinds #-}
data Cat (c :: () -> () -> *) where
Cat :: c '() '() -> Cat c
instance Category c => Monoid (Cat c) where
mempty = Cat id
Cat f `mappend` Cat g = Cat (f . g)
But this is yucky! Ew! And pinning things down so tightly doesn't usually accomplish anything from a practical perspective. But we can get the functionality without so much mess, by playing a little trick!
{-# LANGUAGE GADTs, PolyKinds #-}
import Control.Category
import Data.Monoid
import Prelude hiding ((.), id)
newtype Cat' (c :: k -> k -> *) (a :: k) (b :: k) = Cat' (c a b)
instance (a ~ b, Category c) => Monoid (Cat' c a b) where
mempty = Cat' id
Cat' f `mappend` Cat' g = Cat' (f . g)
Instead of confining ourselves to a Category that really only has one object, we simply confine ourselves to looking at one object at a time.
The existing Monoid instance for functions makes me sad. I think it would be much more natural to use a Monoid instance for functions based on their Category instance, using the Cat' approach:
instance a ~ b => Monoid (a -> b) where
mempty = id
mappend = (.)
Since there's already a Monoid instance, and overlapping instances are evil, we have to make do with a newtype. We could just use
newtype Morph a b = Morph {appMorph :: a -> b}
and then write
instance a ~ b => Monoid (Morph a b) where
mempty = Morph id
Morph f `mappend` Morph g = Morph (f . g)
and for some purposes maybe this is the way to go, but since we're using a newtype already we usually might as well drop the non-standard equality context and use Data.Monoid.Endo, which builds that equality into the type:
newtype Endo a = Endo {appEndo :: a -> a}
instance Monoid (Endo a) where
mempty = Endo id
Endo f `mappend` Endo g = Endo (f . g)

Why there is no way to derive Applicative Functors in Haskell?

In Haskell, you can derive Functor, Foldable and Traversable automatically using deriving. There is no way to derive Applicative, though. Considering there is one obvious way to define an Applicative instance (which would amount to a zipped application), isn't there any way to enable deriving Applicative?
No, this is not obvious at all. Compare the following Applicative instances:
[]
ZipList
Data.Sequence.Seq, whose Applicative instance declaration runs to several hundred lines.
IO
(->) r
Parsers in parsec, attoparsec, regex-applicative.
Proxy in the pipes package.
There very little uniformity here, and most of the instances are non-obvious.
As David Young comments, the [] and ZipList instances "are both, ultimately, two different, equally valid Applicative instances for the list type."
Now that DerivingVia has been released (GHC-8.6 or newer) it is actually possible to derive Applicative with the help of DeriveGeneric for any deterministic data type! That is to say, any data type with exactly one variant:
data Foo x = Foo x | Fe -- This is non-deterministic and can't derive Applicative
data Bar x = Bar x x (Bar x) -- This is deterministic and can derive Applicative
data Baz x = Baz (Either Int x) [x] -- This is also ok, since [] and Either Int
-- are both Applicative
data Void x -- This is not ok, since pure would be impossible to define.
To derive Applicative, we first need to define a wrapper for deriving via generics:
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DeriveGeneric #-}
module Generically1 where
import GHC.Generics
newtype Generically1 f x = Generically1 { generically1 :: f x }
fromg1 :: Generic1 f => Generically1 f a -> Rep1 f a
fromg1 = from1 . generically1
tog1 :: Generic1 f => Rep1 f x -> Generically1 f x
tog1 = Generically1 . to1
instance (Functor f, Generic1 f, Functor (Rep1 f))
=> Functor (Generically1 f) where
fmap f (Generically1 x) = Generically1 $ fmap f x
instance (Functor f, Generic1 f, Applicative (Rep1 f))
=> Applicative (Generically1 f) where
pure = tog1 . pure
f <*> x = tog1 $ fromg1 f <*> fromg1 x
instance (Functor f, Generic1 f, Monad (Rep1 f)) => Monad (Generically1 f) where
return = pure
m >>= f = tog1 $ fromg1 m >>= fromg1 . f
and to use it we first derive Generic1 for our data type and then derive Applicative via our new Generically1 wrapper:
data Foo x = Foo x (Int -> x) (Foo x)
deriving (Functor, Generic1)
deriving (Applicative, Monad) via Generically1 Foo
data Bar x = Bar x (IO x)
deriving (Functor, Generic1)
deriving (Applicative, Monad) via Generically1 Bar
data Baz f x = Baz (f x) (f x)
deriving (Show, Functor, Generic1)
deriving (Applicative, Monad) via Generically1 (Baz f)
As you can see, we did not only derive Applicative for our data types but could also derive Monad.
The reason that this works is that there are instances for Applicative and Monad for the Generic1 representations of these data types. See for example the Product type (:*:). There is however no instance of Applicative for the Sum type (:+:), which is why we can't derive it for non-deterministic types.
You can see the Generic1 representation of a data type by writing :kind! Rep1 Foo in GHCi. Here are simplified versions (excluding meta-data) of the representations for the types above:
type family Simplify x where
Simplify (M1 i c f) = Simplify f
Simplify (f :+: g) = Simplify f :+: Simplify g
Simplify (f :*: g) = Simplify f :*: Simplify g
Simplify x = x
λ> :kind! Simplify (Rep1 Foo)
Simplify (Rep1 Foo) :: * -> *
= Par1 :*: (Rec1 ((->) Int) :*: Rec1 Foo)
λ> :kind! Simplify (Rep1 Bar)
Simplify (Rep1 Bar) :: * -> *
= Par1 :*: Rec1 IO
λ> :kind! forall f. Simplify (Rep1 (Baz f))
forall f. Simplify (Rep1 (Baz f)) :: k -> *
= forall (f :: k -> *). Rec1 f :*: Rec1 f
Edit: The Generically1 wrapper is also available here: https://hackage.haskell.org/package/generic-data-0.7.0.0/docs/Generic-Data.html#t:Generically1

Resources