Making a wrapper over a generic Rep - haskell

I have a Rep A for some type that I modify using some forall x. Rep A x -> F (Rep A) x function where F is a type family. Let's say this wraps all the fields in a Maybe. What I want to do is to serialize that F (Rep A) to JSON. aeson provides functions that serialize generic types, but it doesn't provide the functions that operate on the actual generic representation.
To solve this problem I thought I could write something like this
newtype RepWrapper a = RepWrapper (F (Rep a))
with a generic instance
instance Generic a => Generic (RepWrapper a) where
type Rep (RepWrapper a) = F (Rep a)
Then I can just use the aeson functions on this wrapped value.
The problem with the above is the extra type parameter that needs to be given to a Rep. There are three ways of doing that, as far as I can tell
newtype RepWrapper a = RepWrapper (forall x. F (Rep a) x)
data RepWrapper a = forall x. RepWrapper (F (Rep a) x)
newtype RepWrapper a x = RepWrapper (F (Rep a) x)
The first way lets me write the from function, the second way lets me write the to function and the third way seems useless.
Is there a way to define the wrapper so I can implement the whole Generic instance?

Given a data type A, Generic gives an isomorphism to a generic representation Rep A. Here we want to go the other way around. Given a generic representation r (here r ~ F (Rep A) for some A) we want a data type B such that Rep B ~ r. We define B as Data r:
data Data r = Data (r ())
The type parameter of r :: * -> * is phantom (actually, it's used by Generic1, and nobody uses Generic1), so we can instantiate it with anything, and we pick () as an arbitrary default.
We will need to express that phantom-ness as a constraint. One way is to take the conjunction of Functor and Contravariant.
type Bivariant f = (Functor f, Contravariant f)
phantom :: Bivariant f => f a -> f b -- Data.Functor.Contravariant
instance Bivariant r => Generic (Data r) where
type Rep (Data r) = r
from (Data r) = phantom r
to = Data . phantom
Also I have defined Data in generic-data where I kept the extra parameter instead of instantiating it, since it is actually cheap to do so.

Related

How to coerce functors applied to coercible arguments

Consider the following Haskell code:
import Data.Coerce
newtype Decorated s a = Decorated a
fancyFunction :: Ctx s => f (Decorated s a) -> r
fancyFunction = ...
instance Ctx s => SomeClass (Decorated s a)
myFunction :: Functor f => f a -> r
myFunction = fancyFunction . fmap coerce
I'd like to make myFunction faster by replacing fmap coerce with coerce. The rationale is that coerce behaves like id and one of the functor laws is fmap id = id.
The only way I can see of doing this is to add Coercible (f a) (f (Decorated s a)) to the context but it refers to s which is not referred to anywhere else. Even worse, if a is bound in a universal type, I cannot express the constraint. Is there a constraint I could express in terms of f only to let me use coerce to convert between f a and f (Decorated s a)?
Is this something that the compiler figures out on its own from the fact that f is a functor? If so, does it also work with bifunctors, traversables and bitraverables?
Unfortunately, Coercible (f a) (f (Decorated s a)) really what you want in your constraint given the current state of GHC. Now, the fact that s and a don't show up elsewhere is not something good - it means GHC won't know what to do with them (they are ambiguous)! I won't get into that...
Depending on the role of the type parameter fed to the type constructor f, Coercible a b may or may not imply Coercible (f a) (f b). In this case, we'd want that role to be nominal - but there isn't (yet at least) a way to express this in a constraint. To explain what I mean, consider the following two data definitions:
{-# LANGUAGE TypeFamilies #-}
import Data.Coerce
-- type role of `a` is "representational"
data Data1 a = Data1 a
-- type role of `a` is "nominal"
data Data2 a = Data2 (TypeFunction a)
type family TypeFunction x where
TypeFunction Bool = Char
TypeFunction _ = ()
Then, while it is true that Coercible a b entails Coercible (Data1 a) (Data1 b), it does not entail Coercible (Data2 a) (Data2 b). To make this concrete, load up the above in GHCi, then try:
ghci> newtype MyInt = My Int
ghci> let c1 = coerce :: (Data1 MyInt) -> (Data1 Int)
ghci> let c2 = coerce :: (Data2 MyInt) -> (Data2 Int) -- This doesn't work!
Unfortunately, there is no built-in constraint based way of enforcing that the role of a type variable is representational. You can make your own classes for this, as Edward Kmett has done, but GHC doesn't automatically create instances of some of these classes the way class instances for Coercible are.
This led to this trac ticket where they discuss the possibility of having a class Representational f with instances generated like for Coercible which could have things like
instance (Representational f, Coercible a b) => Coercible (f a) (f b)
If this was actually a thing today, all you would need in your constraint would be Representational f. Furthermore, as Richard Eisenberg observes on the ticket, we really ought to be able to figure out that a in f a has a representational role for any reasonable functor f. Then, we might not even need any constraint on top of Functor f as Representational could be a superclass of Functor.
Here is a good discussion of the current limitations of roles.
Now that you have QuantifiedConstraints, I think you can do this:
type Parametric f = (forall a b. (Coercible a b => Coercible (f a) (f b)) :: Constraint)
newtype Foo = Foo Int
myFunction :: (Parametric f) => f Foo -> f Int
myFunction = coerce
test :: [Int]
test = myFunction [Foo 1, Foo 2, Foo 3]
This is nice, because an instance of Parametric f witnesses that f is an endofunctor on a category where the objects are types and a morphism between types A and B is an instance of Coercible A B.

Switch order of arguments for instance declaration in Haskell

I want to make an instance declaration, but the free type variable is not the last variable. For example, I have a class declaration
class Poppable m where
tryPop :: m a -> Maybe (a, m a)
Now I want to make Q.PSQ (priority queue) an instance of Poppable. Specifically I want something like this:
instance (Ord p) => Poppable (\a -> Q.PSQ a p) where
tryPop = fmap (first Q.key) . Q.minView
However, this is not legal Haskell code. If the order of arguments to PSQ were switched, then I would have no problem:
instance (Ord p) => Poppable (Q.PSQ p) where
tryPop = fmap (first Q.key) . Q.minView
How do I switch the order of arguments for the instance declaration?
Now I could wrap PSQ with a newtype:
newtype PSQ'' a b = PSQ'' (Q.PSQ b a)
However this seems clunky to me because I have to constantly wrap/unwrap it. Is there an easier way?
*
I tried using data/type families, but both give errors.
(1) Using a data family declaration:
data family PSQ' a b
data instance PSQ' a b = PSQ b a
instance (Ord p) => Poppable (PSQ' p) where
tryPop = fmap (first Q.key) . Q.minView
However this gives the error
Couldn't match type `Q.PSQ a p0' with `PSQ' p a'
even though they can match by setting p=p0.
(2) Type families won't work either.
type family PSQ' a b where
PSQ' b a = Q.PSQ a b
gives
Illegal type synonym family application in instance: PSQ' p
Now I could wrap PSQ with a newtype:
newtype PSQ'' a b = PSQ'' (Q.PSQ b a)
However this seems clunky to me because I have to constantly wrap/unwrap it. Is there an easier way?
Nope, not really. You could, of course, write your Poppable class to make it match PSQ. And if you like, you can generalize your newtype to
newtype Flip f a b = Flip (f b a)
at which point you could write
instance Poppable (Flip Q.PSQ a)
but none of this will get rid of the underlying annoyance factor. There are reasons Haskell doesn't support this (apparently, it makes inference much harder, sometimes impossible, etc.), so you'll just have to deal with it.
P.S., that type synonym may be more useful poly-kinded, with {-# LANGUAGE PolyKinds #-}, where it ends up meaning
newtype Flip (f :: k1 -> k2 -> *) (a :: k2) (b :: k1) = Flip (f b a)
You could simply abandon parametricity and use a type family to project whichever argument correspond to the 'element type':
class Poppable q where
type Elem q
tryPop :: q -> Maybe (Elem q, q)
data PSQ a p = ...
instance Ord p => Poppable (PSQ a p) where
type Elem (PSQ a p) = a
tryPop = ...
Note this is a more general formulation, but it may be harder to work with.

Function from `mappend` function to `Monoid` instance?

I have a data structure (it's a specific subclass of rose-tree that forms a lattice with greatest-lower bound and lowest-upper bound functions), and it supports two perfectly reasonable functions to serve as the Monoid class's mappend.
Is there any way to support anonymous Monoid instances in haskell? Is this an instance where I should consider using something like Template-Haskell to generate my typeclasses for me?
What I'd love is a makeMonoid :: (RT a -> RT a -> RT a) -> Monoid a to let me create the instance on the fly, but I understand that that's incoherent with the stock typesystem as I understand it.
I'm okay with it if I just need to pick a default merge function and write newtypes for other merges, just curious
You can create "local" instances of Monoid on the fly, using the tools in the reflection package. There's a ready-made example in the repository. This answer explains it a little.
This is a newtype wrapper over values of type a, on which we will define our Monoid instance.
newtype M a s = M { runM :: a } deriving (Eq,Ord)
Notice that there is a phantom type s that does not appear in the right hand side. It will carry extra information necessary for the local Monoid instance to work.
This is a record whose fields represent the two operation of the Monoid class:
data Monoid_ a = Monoid_ { mappend_ :: a -> a -> a, mempty_ :: a }
The following is the Monoid instance definition for M:
instance Reifies s (Monoid_ a) => Monoid (M a s) where
mappend a b = M $ mappend_ (reflect a) (runM a) (runM b)
mempty = a where a = M $ mempty_ (reflect a)
It says: "whenever s is a type-level representation of our Monoid dictionary Monoid_, we can reflect it back to obtain the dictionary, and use the fields to implement the Monoid operations for M".
Notice that the actual value a passed to reflect is not used, it is passed only as a "proxy" of type M a s that tells reflect which type (s) to use to "bring back the record".
The actual local instance is constructed using the reify function:
withMonoid :: (a -> a -> a) -> a -> (forall s. Reifies s (Monoid_ a) => M a s) -> a
withMonoid f z v = reify (Monoid_ f z) (runM . asProxyOf v)
asProxyOf :: f s -> Proxy s -> f s
asProxyOf a _ = a
The asProxyOf function is a trick to convince the compiler that the phantom type used in the monoid is the same as the one in the Proxy supplied by reify.

instance of "Type constructed with type argument" need not be constructed with data of that type, in Haskell

In Haskell, a type constructor can take a type argument, of course.
A function a -> b, when looked at as a "type with a funny constructor name", has type (->) a b. That makes it a type constructor (->) with two arguments, a and b. This is frequently encountered in the "reader" pattern as in its Functor and Applicative instances:
instance Functor ((->) a) where
fmap = (.)
instance Applicative ((->) a) where
pure = const
(<*>) f g x = f x (g x)
When I first tried to understand uses of this instance, as in
fmap (+1) (*2) 3 (=== (+1) . (*2) $ 3 === 3*2+1 === 7)
my reaction was "Ok, (+1) has type Int -> Int, which is (->) Int Int, so that matches Functor.... but where is the Int? I make a Maybe Int by calling Just 1, but I don't ever make a (->) Int Int by applying anything to an Int. In fact, I destroy a ((->) Int Int) by applying it to an Int! (Yeah, there's Nothing, but that seems... degenerate.)"
This all works (of course), as long as I remember that just because a type is built from a constructor+argument, that doesn't mean its values are built from a correspondingly typed constructor+argument. And some of the most interesting and powerful (and tricky to understand) type constructors are like this ((->), Lens, Arrow, etc)
(OK, really it's Num a => a, not Int, but let's ignore that, not relevant)
Is there a name for this concept? What is the appropriate mental model for thinking about type constructors, without leaning on the misleading and disempowering crutch interpretation "Foo a is a structure Foo containing value(s) of type a)?
This concept is known as a contravariant functor, on in Haskell-speak a Contravariant type.
class Contravariant f where
contramap :: (b -> a) -> f a -> f b
-- compare
class Functor f where
fmap :: (a -> b) -> f a -> f b
More generally, we can think of type variables in a type as having contravariant or covariant nature (at its simplest). For instance, by default we have
newtype Reader t a = Reader (t -> a)
instance Functor (Reader t) where
fmap ab (Reader ta) = Reader (ab . ta)
Which indicates that the second type parameter to Reader is covariant, while if we reverse the order
newtype RevReader a t = RevReader (t -> a)
instance Contravariant (RevReader a) where
contramap st (RevReader ta) = RevReader (ta . st)
A useful intuition for Contravariant types is that they have the ability to consume zero, one, or many values of the contravariant parameter instead of containing zero, one, or many values of the covariant parameter like we often think of when considering Functors.
Combining these two notions is the Profunctor
class Profunctor p where
dimap :: (a -> b) -> (c -> d) -> p b c -> p a d
which, as we notice, demands that p is of kind * -> * -> * where the first type parameter is contravariant and the second covariant. This class well characterizes the (->) type constructor
instance Profuntor (->) where
dimap f g h = g . h . f
Again, if we think of contravariant type parameters as being consumed and covariant ones as being produced this is quite amenable of the typical intuition around (->) types.
A few more examples of types which contravariant parameters include Relation
newtype Relation t = Relation (t -> t -> Bool)
instance Contravariant Relation where
contramap g (Relation pred) = Relation $ \a b -> pred (g a) (g b)
Or Fold which represents a left fold as a data type
newtype Fold a b = Fold b (a -> Fold a b)
instance Profunctor Fold where
dimap f g (Fold b go) = Fold (g b) (go . f)
sumF :: Num a => Fold a a
sumF = go 0 where
go n = Fold n (\i -> go (n + i))
With Fold a b we see that it consumes an arbitrary number of a types to produce one b type.
Generally what we find is that while it's often the case that we have covariant and "container" (strictly positive) types where values of some type c a are produced from a constructor of type a -> c a and some filler values a, in general that doesn't hold. In particular we have covariant types like that, but also contravariant ones which are often processes which somehow consume values of their parameterized type variables, or even more exotic ones like phantom types which utterly ignore their type variables
newtype Proxy a = Proxy -- need no `a`, produce no `a`
-- we have both this instance
instance Functor Proxy where
fmap _ Proxy = Proxy
-- and this one, though both instances ignore the passed function
instance Contravariant Proxy where
contramap _ Proxy = Proxy
and... "nothing special" type variables which cannot have any sort of nature, usually because they're being used as both covariant and contravariant types.
data Endo a = Endo (a -> a)
-- no instance Functor Endo or Contravariant Endo, it needs to treat
-- the input `a` differently from the output `a` such as in
--
-- instance Profunctor (->) where
Finally, a type constructor which takes multiple arguments may have different natures for each argument. In Haskell, the final type parameter is usually treated specially, though.

An example of a Foldable which is not a Functor (or not Traversable)?

A Foldable instance is likely to be some sort of container, and so is likely to be a Functor as well. Indeed, this says
A Foldable type is also a container (although the class does not technically require Functor, interesting Foldables are all Functors).
So is there an example of a Foldable which is not naturally a Functor or a Traversable? (which perhaps the Haskell wiki page missed :-) )
Here's a fully parametric example:
data Weird a = Weird a (a -> a)
instance Foldable Weird where
foldMap f (Weird a b) = f $ b a
Weird is not a Functor because a occurs in a negative position.
Here's an easy example: Data.Set.Set. See for yourself.
The reason for this should be apparent if you examine the types of the specialized fold and map functions defined for Set:
foldr :: (a -> b -> b) -> b -> Set a -> b
map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b
Because the data structure relies on a binary search tree internally, an Ord constraint is needed for elements. Functor instances must allow any element type, so that's not viable, alas.
Folding, on the other hand, always destroys the tree to produce the summary value, so there's no need to sort the intermediate results of the fold. Even if the fold is actually building a new Set, the responsibility for satisfying the Ord constraint lies on the accumulation function passed to the fold, not the fold itself.
The same will probably apply to any container type that's not fully parametric. And given the utility of Data.Set, this makes the remark you quoted about "interesting" Foldables seem a bit suspect, I think!
Reading Beautiful folding
I realized that any Foldable can be made a Functor by wrapping it into
data Store f a b = Store (f a) (a -> b)
with a simple smart contructor:
store :: f a -> Store f a a
store x = Store x id
(This is just a variant of the Store comonad data type.)
Now we can define
instance Functor (Store f a) where
fmap f (Store x g) = Store x (f . g)
instance (F.Foldable f) => F.Foldable (Store f a) where
foldr f z (Store x g) = F.foldr (f . g) z x
This way, we can make both Data.Set.Set and Sjoerd Visscher's Weird a functor. (However, since the structure doesn't memoize its values, repeatedly folding over it could be very inefficient, if the function that we used in fmap is complex.)
Update: This also provides an example of a structure that is a functor, foldable but not traversable. To make Store traversable, we would need to make (->) r traversable. So we'd need to implement
sequenceA :: Applicative f => (r -> (f a)) -> f (r -> a)
Let's take Either b for f. Then we'd need to implement
sequenceA' :: (r -> Either b a) -> Either b (r -> a)
Clearly, there is no such function (you can verify with Djinn). So we can neither realize sequenceA.

Resources