What are FromJSON1 and ToJSON1 used for in aeson? - haskell

Aeson provides FromJSON1 and ToJSON1 type classes. These are similar to the Eq1 and Show1 classes defined in the Data.Functor.Classes module.
My understanding of the Eq1 and Show1 classes is that they are needed to be able to express constraints on arguments of transformers without using extensions like FlexibleContexts and UndecidableInstances.
The example from the documentation in the Data.Functor.Classes module is as follows:
Assume we have a data type that acts as a transformer: T. For an example, let's have it be isomorphic to IdentityT:
data T f a = T (f a)
The kind of T is as follows:
T :: (* -> *) -> * -> *
If there is an Eq1 instance for f, it is possible to use it when writing the Eq1 instance for T f:
instance Eq1 f => Eq1 (T f) where
liftEq :: (a -> b -> Bool) -> T f a -> T f b -> Bool
liftEq eq (T fa1) (T fa2) = liftEq eq fa1 fa2
If we have an Eq1 instance for f, an Eq instance for a, and the Eq1 instance for T f above is in scope, we can easily write the Eq instance for T f a:
instance (Eq1 f, Eq a) => Eq (T f a) where
(==) :: T f a -> T f a -> Bool
(==) = eq1
The type of eq1 is defined as follows:
eq1 :: (Eq1 h, Eq a) => h a -> h a -> Bool
In our instance above, h becomes T f, so the type of eq1 can be thought of as the following:
eq1 :: Eq a => T f a -> T f a -> Bool
Now, the Eq1, Show1, etc classes make sense. It seems like it makes it easier to write instances of Eq, Show, etc for transformers.
However, I'm wondering what types FromJSON1 and ToJSON1 are used for in Aeson? I rarely have transformers that I want to turn to and from JSON.
Most of the data types I end up changing to JSON are normal types (not type constructors). That is to say, types with the kind *. I also uses types like Maybe with a kind of * -> *.
However, I don't think I often create ToJSON or FromJSON instances for transformers, like the T above. What is a transformer that is often used to go to and from JSON? Am I missing out on some helpful transformers?

Eq1 offers another feature that you haven't discussed in your exposition: it lets you write a function that calls (==) at many different types, without necessarily knowing ahead of time which types you will use it on.
I'll give a toy example; hopefully you can see through the apparent uselessness of this example to the reason Eq1 gives you some interesting powers.
Imagine you want to make a tree that is parameterized on the branching factor, so you parameterize it by the child container. So values might look like this:
{-# LANGUAGE GADTs #-}
data Tree m a where
Branch :: Tree m (m a) -> Tree m a
Leaf :: a -> Tree m a
For example, I can get binary trees with Tree Pair, trinary trees with Tree Triple, finger trees with Tree TwoThree, and rose trees with Tree [], where data Pair a = Pair a a, data Triple a = Triple a a a, and data TwoThree a = Two a a | Three a a a. Now I would like to write an Eq instance for this. If we only rely on Eq constraints, we can't get where we want to go. Let's try:
instance Eq (Tree m a) where
Leaf a == Leaf a' = a == a'
Branch t == Branch t' = t == t'
_ == _ = False
Naturally, GHC complains that it doesn't know how to compare a and a' for equality. So add Eq a to the context:
instance Eq a => Eq (Tree m a) where ...
Now GHC complains that it doesn't know how to compare m as for equality in the Branch case. Makes sense.
instance (Eq a, Eq (m a)) => Eq (Tree m a) where ...
Still no go! Now the implementation of (==) :: Tree m a -> Tree m a -> Bool has a recursive call to (==) :: Tree m (m a) -> Tree m (m a) -> Bool in its Branch case, hence must provide the context (Eq (m a), Eq (m (m a))) to make that recursive call. Okay, let's add that to the instance context...
instance (Eq a, Eq (m a), Eq (m (m a))) => Eq (Tree m a) where ...
Still no good. Now the recursive call has to prove even more stuff! What we'd really like to say is that if we have Eq b, then we have Eq (m b), for all bs and not just for the specific a being used as Tree's second parameter.
instance (Eq a, (forall b. Eq b => Eq (m b))) => Eq (Tree m a) where ...
Of course that's totally not a thing in Haskell. But Eq1 gives us that:
instance Eq1 m => Eq1 (Tree m) where
liftEq (==) (Leaf a) (Leaf a') = a == a'
liftEq (==) (Branch t) (Branch t') = liftEq (liftEq (==)) t t'
liftEq (==) _ _ = False
instance (Eq1 m, Eq a) => Eq (Tree m a) where
(==) = eq1
Here the Eq1 m constraint is serving the role we asked for before, namely, that all of (Eq a, Eq (m a), Eq (m (m a)), ...) are possible.
The ToJSON1 and FromJSON1 classes serve a similar role: they give you a single constraint that you can give that amounts to a potentially infinite collection of ToJSON and FromJSON constraints, so that you can choose which ToJSON or FromJSON constraint you need in a data-driven way and be guaranteed that it's available.

Related

Change in Behaviour of Quantified Constraints in GHC 9

Previously, in order to use quantified constraints on typeclasses like Ord, you had to include the superclass in the instance like so:
newtype A f = A (f Int)
deriving instance (forall a. Eq a => Eq (f a)) => Eq (A f)
deriving instance (forall a. Eq a => Eq (f a), forall a. Ord a => Ord (f a)) => Ord (A f)
(This is in fact precisely the solution given in this question).
In GHC 9, however, the above code doesn't work. It fails with the following error:
• Could not deduce (Eq (f a))
from the context: (forall a. Eq a => Eq (f a),
forall a. Ord a => Ord (f a))
bound by a stand-alone deriving instance declaration:
forall (f :: * -> *).
(forall a. Eq a => Eq (f a), forall a. Ord a => Ord (f a)) =>
Ord (A f)
or from: Eq a
bound by a quantified context
• In the ambiguity check for a stand-alone deriving instance declaration
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
In the stand-alone deriving instance for
‘(forall a. Eq a => Eq (f a), forall a. Ord a => Ord (f a)) =>
Ord (A f)’
Unfortunately the AllowAmbiguousTypes suggestion doesn't work. (you get the same error, followed by the same error for every method on the class)
Does anyone know of a workaround for this?
One simple way to solve it is to change the second deriving clause to:
deriving instance (Eq (A f), forall a. Ord a => Ord (f a)) => Ord (A f)
I don't yet have a good explanation for why this is happening though.

Can I write `foldr` (or `foldMap`) in terms of 'recursion schemes' `cata`?

I recently read about recursion schemes where catamorphisms are described as analogous to generalized foldr.
Is is possible to write an instance of Foldable (via either foldr or foldMap) in terms of cata in all cases?
foldMap, being the fundamental operation of Foldable, is a better candidate for implementation than foldr. The answer is a qualified yes. cata only handles recursion; it doesn't tell you where to "find" all the values in a structure. (In the same way, implementing foldMap #[] with foldr still requires knowing the inner details of [].) Doing so requires a little help:
class Bifoldable f where
bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> f a b -> m
You can then define
foldMapDefault ::
(Recursive (f a), Base (f a) ~ b a, Bifoldable b) =>
Monoid m => (a -> m) -> f a -> m
foldMapDefault f = cata (bifoldMap f id)
This allows you to do things like
data Tree a = Leaf | Branch (Tree a) a (Tree a)
makeBaseFunctor ''Tree
deriveBifoldable ''TreeF
instance Foldable Tree where foldMap = foldMapDefault
(Though you may as well have just said deriving Foldable on Tree.) For maximum genericity, you may want something more like this (I say "want"...)
newtype Fixed f a = Fixed { getFixed :: f a }
newtype Bibase f a b = Bibase { getBibase :: Base (f a) b }
instance (forall a. Recursive (f a), Bifoldable (Bibase f)) =>
Foldable (Fixed f) where
foldMap :: forall a m. Monoid m => (a -> m) -> Fixed f a -> m
foldMap f = cata (bifoldMap f id . Bibase #f #a #m) . getFixed
You can now say things like
data Tree a = Leaf | Branch (Tree a) a (Tree a)
makeBaseFunctor ''Tree
deriveBifoldable ''TreeF
deriving via TreeF instance Bifoldable (Bibase Tree)
deriving via (Fixed Tree) instance Foldable Tree
But now your Base functors can be more irregular:
data List a = Nil | Cons a (List a)
type instance Base (List a) = Compose Maybe ((,) a)
instance Recursive (List a) where
project Nil = Compose Nothing
project (Cons x xs) = Compose (Just (x, xs))
instance Bifoldable (Bibase List) where
bifoldMap f g (Bibase (Compose Nothing)) = mempty
bifoldMap f g (Bibase (Compose (Just (x, xs)))) = f x <> g xs
deriving via (Fixed List) instance Foldable List
You often can, but not universally. All it takes is a single counter-example. Several exist, but consider the simplest one that comes to (my) mind.
While completely unnecessary, you can define Boolean values with an F-algebra:
data BoolF a = TrueF | FalseF deriving (Show, Eq, Read)
instance Functor BoolF where  
fmap _  TrueF =  TrueF
  fmap _ FalseF = FalseF
From this (as the linked article explains) you can derive the catamorphism:
boolF :: a -> a -> Fix BoolF -> a
boolF x y = cata alg
  where alg TrueF = x
 alg FalseF = y
The type Fix BoolF is isomorphic to Bool, which isn't parametrically polymorphic (i.e. it doesn't have a type parameter), yet a catamorphism exists.
The Foldable type class, on the other hand, is defined for a parametrically polymorphic container t, e.g.
foldr :: (a -> b -> b) -> b -> t a -> b
Since Bool isn't parametrically polymorphic, it can't be Foldable, yet a catamorphism exists. The same is true for Peano numbers.
For parametrically polymorphic types, on the other hand, you often (perhaps always?) can. Here's a Foldable instance for a tree defined with its catamorphism:
instance Foldable TreeFix where
  foldMap f = treeF (\x xs -> f x <> fold xs)
Here's one for Maybe:
instance Foldable MaybeFix where
foldMap = maybeF mempty
and one for linked lists:
instance Foldable ListFix where
foldr = listF

Generalised newtype deriving on class functions with Functors

I'm developing a class representing key/value mappings, and I've got a function which is basically like alterF:
class C t where
...
alterF :: Functor f =>
(Maybe (Value t) -> f (Maybe (Value t))) -> Key t -> t -> f t
Unfortunately, this breaks GeneralisedNewtypeDeriving. In some cases, this is reasonable, as GeneralisedNewtypeDeriving from what I understand essentially uses Coercible and the function coerce. Coercible represents types which are representationally equal, i.e. they have the same representation at run time, so we can convert between them for free. For example, given:
newtype T a = T a
we have:
Coercible a (T a)
Coercible (T a) a
but we don't have (in general):
Coercible (f a) (f (T a))
Coercible (f (T a)) (f a)
For example, GADTs violate this representational equality. But there are lots of values of f that do work. For example:
Coercible (Maybe a) (Maybe (T a))
Coercible (Maybe (T a)) (Maybe a)
Coercible [a] [T a]
Coercible [T a] [a]
Coercible (Identity a) (Identity (T a))
Coercible (Identity (T a)) (Identity a)
It also occurs to me that this instance could be written:
Functor f => Coercible (f a) (f (T a))
Functor f => Coercible (f (T a)) (f a)
Just using fmap. Unlike the usual coerce, this wouldn't be free at runtime, but it will work.
So I've got a class with 10 functions, 9 of which work fine with GeneralisedNewtypeDeriving. There's just this final one which doesn't, which could be resolved mechanically using fmap. Do I have to write custom wrapping/unwrapping implementations for all my class functions, or is there a way to either require me to write the implementation for just the problem function or alternatively coax GHC into using fmap as part of it's GeneralisedNewtypeDeriving?
If f is a Functor, you can make a "representational wrapper" for it
data Rep f a where
Rep :: (b -> a) -> f b -> Rep f a
which is isomorphic to f except that it is representational in a, by what is essentially existential quantification over any nominal variance f might have. I think this construction happens to have some fancy category theory name but I don't remember what it is. To get the f a back out of a Rep f a, you need to use f's Functorhood.
You can use this wrapper in your method, ensuring that your class varies representationally.
alterFRep :: (Functor f)
=> (Maybe (Value t) -> Rep f (Maybe (Value t))) -> Key t -> t -> Rep f t
And then make the real "method" just a regular function in terms of it by using the isomorphism with Rep f. You can also make a convenience method for instance authors:
toAlterFRep ::
(forall f t. (Functor f) => (Maybe (Value t) -> f (Maybe (Value t))) -> Key t -> t -> f t)
-> (forall f t. (Functor f) => (Maybe (Value t) -> Rep f (Maybe (Value t))) -> Key t -> t -> Rep f t)
so they don't have to worry about what the heck Rep is, they just implement alterF normally and use toAlterFRep on it.

Typeclass constraints with higher kinded types

I'm trying to write an Eq instance for an EitherT newtype given by:
newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) }
I assumed the following Eq instance would work:
instance (Eq e, Eq a, Eq m) => Eq (EitherT e m a) where
a == b = (runEitherT a) == (runEitherT b)
However, I'm seeing an error:
Expected kind '* -> *', but 'm' has kind '*'
What I'm reading from that error is that my typeclass constraint ( ... Eq m) => ... is confusing the compiler into thinking that I believe m to be of kind *, when my newtype declaration for EitherT expects it to be of kind * -> *.
I'm wondering what I need to do, to declare that I want an Eq instance for some higher kinded type m to implement Eq for my EitherT newtype.
Edit: As pointed out by #AlexisKing, I can get this to work with:
{-# LANGUAGE UndecideableInstances #-}
instance (Eq (m (Either e a))) => Eq (EitherT e m a) where
a == b = (runEitherT a) == (runEitherT b)
However, it seems strange to me to that a language extension is required to write this Eq instance. Is there no other way to express such a typeclass constraint in vanilla Haskell? If not, why?
You're looking for Eq1 which is in Data.Functor.Classes since base 4.9.0.0. Before that it was in one of the -extras packages or transformers? (it's in transformers now since 0.4.0.0)
Eq1 f says that you can compare fs as long as you have a way to compare their contents
class Eq1 f where
liftEq :: (a -> b -> Bool) -> f a -> f b -> Bool
In your case you'd use it like
instance (Eq e, Eq1 m) => Eq1 (EitherT e m) where
liftEq f a b = liftEq (liftEq f) (runEitherT a) (runEitherT b)
The liftEq f is to use the existing Eq1 instance for Either.
And can define an Eq instance as
instance (Eq e, Eq a, Eq1 m) => Eq (EitherT e m a) where
(==) = liftEq (==)
The old Eq1 was
class Eq1 f where
eq1 :: (Eq a) => f a -> f a -> Bool
In your case you'd use it like
instance (Eq e, Eq1 m) => Eq1 (EitherT e m) where
eq1 a b = eq1 (runEitherT a) (runEitherT b)
instance (Eq e, Eq a, Eq1 m) => Eq1 (EitherT e m) where
a == b = eq1 (runEitherT a) (runEitherT b)
It might be worth noting that this instance already exists in current versions of the either package (though not the old EitherT package, which is considered obsolete):
instance Eq (m (Either e a)) => Eq (EitherT e m a) where
(==) = (==) on runEitherT
Of course, as #Alexis King has noted, it requires UndecidableInstances, but the either package is authored by Edward Kmett, a notorious dilettante and amateur who can't write proper Haskell98 like us real programmers. ;)

Define Equality Instance for Free Monad

Given the Free Monad:
data Free f a = Var a
| Node (f (Free f a))
I tried to define an Eq instance for it:
instance (Functor f, Eq (f a)) => Eq (Free f a) where
(==) (Var x) (Var y) = x == y
(==) (Node fu1) (Node fu2) = fu1 == fu2
(==) _ _ = False
But that fails to compile:
FreeMonad.hs:17:10:
Non type-variable argument in the constraint: Eq (f a)
(Use FlexibleContexts to permit this)
In the context: (Functor f, Eq (f a))
While checking an instance declaration
In the instance declaration for ‘Eq (Free f a)’
Failed, modules loaded: none.
Specifying a constraint/pre-condition of (Functor f, Eq (f a)) seems odd to me (at least I don't think that I've seen it as a beginner before).
How can I define an Eq instance for Free f a?
There is nothing wrong with having a constraint like Eq (f a). As the error message says, you will need to enable the (harmless) FlexibleContexts GHC extension to do that, so add...
{-# LANGUAGE FlexibleContexts #-}
... to the top of your source file.
Do note, however, that (Functor f, Eq (f a)) doesn't really reflect what you are doing in your implementation of (==). Firstly, you don't need the supposition that f is a Functor here, so you can safely drop the Functor f constraint. Secondly, the constraints should match what you need to write the different cases. In the first case, you do x == y. x and y are both of type a, and so you need Eq a. For analogous reasons, the second case requires Eq (f (Free f a)) rather than Eq (f a). That means you will end up with...
(Eq (f (Free f a)), Eq a) => Eq (Free f a)
... which matches reference implementations such as the one in Control.Monad.Free.
duplode shows how to do it with flexible contexts. If you want Haskell 2010, the usual approach is to use the Eq1 class from Prelude.Extras or similar.
class Eq1 f where
(==#) :: Eq a => f a -> f a -> Bool
Then you'd use
instance (Eq1 f, Eq a) => Eq (Free f a) where ...
instance Eq1 f => Eq1 (Free f) -- default instance is fine.
I'm not at my computer right now, so I can't test this until later.

Resources