I am trying to use this blogpost's approach to higher-kinded data without dangling Identity functors for the trival case together with quantified-constraint deriving:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE QuantifiedConstraints, StandaloneDeriving, UndecidableInstances #-}
module HKD2 where
import Control.Monad.Identity
type family HKD f a where
HKD Identity a = a
HKD f a = f a
data Result f = MkResult
{ foo :: HKD f Int
, bar :: HKD f Bool
}
deriving instance (forall a. Show a => Show (HKD f a)) => Show (Result f)
This results in the infuriatingly self-contradicting error message:
Could not deduce Show (HKD f a)
from the context: forall a. Show a => Show (HKD f a)
Is there a way to do this without being long-winded about it and doing
deriving instance (Show (HKD f Int), Show (HKD f Bool)) => Show (Result f)
?
tl;dr, gist: https://gist.github.com/Lysxia/7f955fe5f2024529ba691785a0fe4439
Boilerplate constraints
First, if the question is about avoiding repetitive code, this is mostly addressed by generics alone, without QuantifiedConstraints. The constraint (Show (HKD f Int), Show (HKD f Bool)) can be computed from the generic representation Rep (Result f). The generic-data package (disclaimer: that I wrote) implements this:
data Result f = MkResult (HKD f Int) (HKD f Bool)
deriving Generic
-- GShow0 and gshowsPrec from Generic.Data
instance GShow0 (Rep (Result f)) => Show (Result f) where
showsPrec = gshowsPrec
or with DerivingVia:
-- Generically and GShow0 from Generic.Data
deriving via Generically (Result f) instance GShow0 (Rep (Result f)) => Show (Result f)
Quantified constraints with type families
Nevertheless, the constraint (Show (HKD f Int), Show (HKD f Bool)) may be less than ideal for various reasons. The QuantifiedConstraints extension may seem to provide a more natural constraint forall x. Show (HKD f x):
it would entail the tuple (Show (HKD f Int), Show (HKD f Bool));
contrary to that tuple, it does not blow up in size when the record gets big, and does not leak the field types of Result as they may be subject to change.
Unfortunately, that constraint is actually not well-formed. The following GHC issue discusses the problem in detail: https://gitlab.haskell.org/ghc/ghc/issues/14840 I don't understand all of the reasons yet, but in brief:
Quantified constraints won't work directly with type families for the foreseeable future, for reasons both theoretical and practical;
But there is a workaround for most use cases.
A quantified constraint should be viewed as a sort of "local instance". The general rule then is that type families are not allowed in the head of any instance ("instance head" = the HEAD in the following instance ... => HEAD where). So forall a. Show (HKD f a) (viewed as a "local" instance Show (HKD f a)) is illegal.
Quantified constraint smuggler
The following solution is credited to Icelandjack (Source: this comment from the ticket linked earlier; thanks also to Ryan Scott for relaying it.)
We can define another class that's equivalent to Show (HKD f a):
class Show (HKD f a) => ShowHKD f a
instance Show (HKD f a) => ShowHKD f a
Now forall x. ShowHKD f x is a legal constraint that morally expresses the intended forall x. Show (HKD f x). But it's not at all obvious how to use it. For example, the following snippet fails to type check (note: we can easily ignore the ambiguity issues):
showHKD :: forall f. (forall x. ShowHKD f x) => HKD f Int -> String
showHKD = show
-- Error:
-- Could not deduce (Show (HKD f Int)) from the context (forall x. ShowHKD f x)
This is counterintuitive, because ShowHKD f x is equivalent to Show (HKD f x) which can of course be instantiated with Show (HKD f Int). So why is that rejected? The constraint solver reasons backwards: the use of show first requires a constraint Show (HKD f Int), but the solver is immediately stuck. It sees forall x. ShowHKD f x in the context, but there is no clue for the solver to know that it should instantiate x to Int. You should imagine that at this point, the constraint solver has no idea of any relationship between Show and ShowHKD. It just wants a Show constraint, and there is none in the context.
We can help the constraint solver as follows, by annotating the body of the function with the needed instantiation(s) of ShowHKD f x, here ShowHKD f Int:
showHKD :: forall f. (forall x. ShowHKD f x) => HKD f Int -> String
showHKD = show :: ShowHKD f Int => HKD f Int -> String
This annotation provides the constraint ShowHKD f Int to the body show, which in turn makes the superclass available Show (HKD f Int) so show can be immediately satisfied. On the other side, the annotation requires the constraint ShowHKD f Int from its context, which provides forall x. ShowHKD f x. Those constraints match, and that leads the constraint solver to instantiate x appropriately.
Deriving Show with quantified constraints
With this, we can implement Show with a quantified constraint, using generics to fill out the body, and with some annotations to instantiate the quantified constraint,
(ShowHKD f Int, ShowHKD f Bool):
instance (forall a. Show a => ShowHKD f a) => Show (Result f) where
showsPrec = gshowsPrec :: (ShowHKD f Int, ShowHKD f Bool) => Int -> Result f -> ShowS
As before, those constraints can be automated with generics, so the only thing that changes in this implementation from one type to another is the name Result:
instance (forall a. Show a => ShowHKD f a) => Show (Result f) where
showsPrec = gshowsPrec :: ShowHKDFields f (Rep (Result HKDTag)) => Int -> Result f -> ShowS
-- New definitions: ShowHKDFields and HKDTag; see gist at the end.
And with a bit more effort, we can have DerivingVia too:
deriving via GenericallyHKD Result f instance (forall a. Show a => ShowHKD f a) => Show (Result f)
-- New definition: GenericallyHKD; see gist.
Full gist: https://gist.github.com/Lysxia/7f955fe5f2024529ba691785a0fe4439
I don't think you can do such thing, but I could certainly be wrong. In your example you are missing an extra constraint Show (f a) in order for it to be complete:
deriving instance (forall a. (Show a, Show (f a)) =>
Show (HKD f a)) => Show (Result f)
But that would mean that Show instance for f a cannot depend on a, which can be true for specific f, but not in general.
Edit
But at the same time it is possible to write something like that without the TypeFamilies:
data Bar f = MkBar (f Int)
deriving instance (forall a . Show a => Show (f a)) => Show (Bar f)
So, I am not sure why GHC can't figure it out.
Edit 2
Here is an interesting observation, this compiles:
type family HKD f a where
-- HKD Identity a = a
HKD f Int = Int
HKD f a = f a
data Result f = MkResult
{ foo :: HKD f Int
, bar :: HKD f Bool
}
deriving instance (forall a. Show a => Show (f a)) => Show (Result f)
and works as expected:
λ> show $ MkResult 5 (Just True)
"MkResult {foo = 5, bar = Just True}"
So, it looks like matching on f somehow messes up the type checker.
Worth noting, that restricting to Show (HDK f a) even for the simplified example also gives the same compile time error as in the question:
deriving instance (forall a. Show a => Show (HKD f a)) => Show (Result f)
Related
Usually I reckon type-families are similarly expressive as compared with typeclasses/instances -- the difference is awkwardness/ergonomics of the code. In this case I have code working with type-families to raise a constraint, but the equivalent typeclass code won't compile. (* Could not deduce (Eq a) ... when (Eq a) is exactly the constraint I'm supplying.) Is this a case typeclasses just can't express, or am I doing something wrong?
data Set a = NilSet | ConsSet a (Set a) deriving (Eq, Show, Read)
-- fmap over a Set, squishing out duplicates
fmapSet :: (Eq a, Eq b ) => (a -> b) -> Set a -> Set b
fmapSet f NilSet = NilSet
fmapSet f (ConsSet x xs) = uqCons (f x) (fmapSet f xs)
uqCons fx fxs | sElem fx fxs = fxs
| otherwise = ConsSet fx fxs
sElem fx NilSet = False
sElem fx (ConsSet fy fys) = fx == fy || sElem fx fys
I want to call that fmap via a Functor-like class, with a constraint that the data-structure is well-formed. Either of these approaches with type-families work (based on this answer, but preferring a standalone family).
{-# LANGUAGE ConstraintKinds, TypeFamilies #-}
import Data.Kind (Type, Constraint)
type family WFTF (f :: * -> *) a :: Constraint
type instance WFTF Set a = Eq a
class WFTFFunctor f where
wftFfmap :: (WFTF f a, WFTF f b) => (a -> b) -> f a -> f b
instance WFTFFunctor Set where
wftFfmap = fmapSet
type family WFTF2 c_a :: Constraint
type instance WFTF2 (Set a) = Eq a
class WFTF2Functor f where
wftF2fmap :: (WFTF2 (f a), WFTF2 (f b)) => (a -> b) -> f a -> f b
instance WFTF2Functor Set where
wftF2fmap = fmapSet
The equivalent (I think) typeclass at least compiles providing I don't give an implementation for the method:
class WFT c_a where
instance Eq a => WFT (Set a)
class WFTFunctor f where
wftfmap :: (WFT (f a), WFT (f b)) => (a -> b) -> f a -> f b
instance WFTFunctor Set where wftfmap f xss = undefined -- s/b fmapSet f xss
Inferred :t (\ f (xss :: Set a) -> wftfmap f xss) :: (Eq a, Eq b) => (a -> b) -> Set a -> Set b -- which is exactly the type of fmapSet. But if I put that call to fmapSet f xss in place of undefined, rejected:
* Could not deduce (Eq a) arising from a use of `fmapSet'
from the context: (WFT (Set a), WFT (Set b))
bound by the type signature for:
wftfmap :: forall a b.
(WFT (Set a), WFT (Set b)) =>
(a -> b) -> Set a -> Set b
at ...
Possible fix:
add (Eq a) to the context of
the type signature for:
wftfmap :: forall a b.
(WFT (Set a), WFT (Set b)) =>
(a -> b) -> Set a -> Set b
WFT (Set a) implies raises Wanted (Eq a), so I shouldn't need to add it. (And if I do via InstanceSignatures, rejected because it's not as general as the inferred constraint.) [In response to #dfeuer's answer/my comment] True that there's nothing in the instance decl to Satisfy (Eq a), but fmapSet's sig also Wants (Eq a) so (why) doesn't that ensure the constraint gets satisfied at the call site?
I've tried decorating everything with ScopedTypeVariables/PatternSignatures to make the constraints more explicit. I've tried switching on ImpredicativeTypes (GHC 8.10.2). I sometimes get different rejection messages, but nothing that compiles.
If I take away the WFT (Set a) and (Eq a) from fmapSet's signature, I get a similar rejection * Could not deduce (Eq b) .... Yes I know that rejection message is a FAQ. In the q's I've looked through, the constraint is indeed unsatisfiable. But then in this case
a) why does the version with implementation undefined typecheck;
b) isn't the constraint wanted from WFT (Set a) getting satisfied
by fmapSet having the (Eq a)?)
Addit: To explain a bit more about what I'm expecting in terms of Wanted/Satisfied constraints:
There's no signature given for uqCons, nor for sElem, which it calls. In sElem there's a call to (==), that raises Wanted (Eq b) in sElem's sig, which gets passed as a Wanted in the sig for uqCons, which gets passed as a Wanted in the sig for fmapSet, which does have a sig given including (Eq b).
Similarly the Set instance for method wftfmap raises Wanted (Eq a, Eq b); I expect it can use that to Satisfy the Wanted arising from the call to fmapSet.
There's a huge difference between superclass constraints and instance constraints. A superclass constraint is something required to form any instance of the class, and is available whenever the subclass constraint is in force. An instance constraint is required to form a specific instance, and is not automatically available when the class constraint is in force. This difference is pretty deeply wired into the system, and is reflected in the Core representations. In Core:
A class is a type of records of class methods and superclasses.
An instance is a value of a class type or a function from its instance constraints to such a value.
Once a "dictionary function" is called to produce an instance dictionary, you only have the dictionary, not the arguments that were used to create it.
[re #Ben's comment to #dfeuer's answer] not something you have on the inside to implement wftfmap.
OK I can have the right sig on the inside:
-- class/instance WFT, funcs fmapSet, uqCons, sElem as before
{-# LANGUAGE InstanceSigs, QuantifiedConstraints #-}
class WFTQFunctor f where
wftQfmap :: (WFT (f a), WFT (f b)) => (a -> b) -> f a -> f b
instance (forall b. (WFT (Set b) => Eq b)) => WFTQFunctor Set where
wftQfmap :: (Eq a, Eq b) => (a -> b) -> (Set a) -> (Set b) -- yay
wftQfmap f xss = fmapSet f xss
Compiles with a warning that I can suppress with -XMonoLocalBinds:
* The constraint `WFT (Set b)' matches
instance Eq a => WFT (Set a)
This makes type inference for inner bindings fragile;
either use MonoLocalBinds, or simplify it using the instance
* In the instance declaration for `WFTQFunctor Set'
I appreciate that QuantifiedConstraint is a fib. I might have instance {-# OVERLAPPING #-} WFT (Set (b -> c)) for which Eq does not hold; but I don't; and/or at least if I use a Set element for which Eq holds, I'll get away with it(?)
But no:
*> wftQfmap toUpper mySet -- mySet :: Set Char
<interactive>:2:1: error:
* Could not deduce (Eq b) arising from a use of `wftQfmap'
from the context: WFT (Set b)
bound by a quantified context at <interactive>:2:1-22
Possible fix: add (Eq b) to the context of a quantified context
* In the expression: wftQfmap toUpper mySet
In an equation for `it': it = wftQfmap toUpper mySet
So why does that instance WFTQFunctor Set compile? And can it ever do anything useful?
OK I have something working. It's ugly and clunky, and not scalable, but answers the q as put:
class WFT c_a where
isWF :: c_a -> Bool -- is c_a well-formed?
mkWF :: c_a -> c_a -- edit c_a to make it well-formed
mkWF = id
instance Eq a => WFT (Set a) -- instance types same as q
isWF NilSet = True
isWF (ConsSet x xs) = not (sElem x xs) && isWF xs -- sElem decl'd in the q
mkWF = fmapSet id -- fmapSet also
class WFTFunctor f where -- class as decl'd in the q
wftfmap :: (WFT (f a), WFT (f b)) => (a -> b) -> f a -> f b
instance WFTFunctor Set where wftfmap f xss = mkWF $ fmap f xss
instance Functor Set where -- conventional/unconstrained fmap
fmap f NilSet = NilSet
fmap f (ConsSet x xs) = ConsSet (f x) (fmap f xs)
If I'm using fmap, generalise:
class Functor f => WFTFunctor f where
wftfmap :: (WFT (f a), WFT (f b)) => (a -> b) -> f a -> f b
wftfmap f xss = mkWF $ fmap f xss
This is not far off H2010 compliant. (Needs FlexibleConstraints.) So I can get the Eq constraint effective 'inside' the WFTFunctor instance; it needs a method call from WFT to pull it through.
I could have heaps of other methods in class WFT, but I say "not scalable" because you couldn't in general 'edit' an ill-formed structure to well-formed. Hmm since it's a Functor: could unload to a List then load back to the structure.
Suppose we have some class Foo such that an instance of Foo f gives us everything necessary to implement Functor f, Foldable f and Traversable f. To avoid overlapping instances, can witness this relationship between Foo and Functor, Foldable, Traversable under a newtype wrapper:
type Foo :: (Type -> Type) -> Constraint
class Foo f
where
{- ... -}
type FoonessOf :: (Type -> Type) -> Type -> Type
newtype FoonessOf f a = FoonessOf (f a)
instance Foo f => Functor (FoonessOf f)
where
fmap = _
instance Foo f => Foldable (FoonessOf f)
where
foldMap = _
instance Foo f => Traversable (FoonessOf f)
where
traverse = _
Now suppose we have some type constructor:
data Bar a = Bar {- ... -}
such that there is an:
instance Foo Bar
where
{- ... -}
We'd like to equip Bar with the instances implied by its "Foo-ness". Since Bar a is Coercible to FoonessOf Bar a, we'd expect to be able to derive the instances via the FoonessOf Bar:
deriving via (FoonessOf Bar) instance Functor Bar
deriving via (FoonessOf Bar) instance Foldable Bar
And this works handily for typeclasses such as Functor and Foldable
Unfortunately when we try to do the same thing with Traversable, things go awry:
[typecheck -Wdeferred-type-errors] [E] • Couldn't match representation of type ‘f1 (Foo Bar a1)’
with that of ‘f1 (Bar a1)’
arising from a use of ‘ghc-prim-0.6.1:GHC.Prim.coerce’
NB: We cannot know what roles the parameters to ‘f1’ have;
we must assume that the role is nominal
• In the expression:
ghc-prim-0.6.1:GHC.Prim.coerce
#(Foo Bar (f a) -> f (Foo Bar a)) #(Bar (f a) -> f (Bar a))
(sequenceA #(Foo Bar)) ::
forall (f :: TYPE ghc-prim-0.6.1:GHC.Types.LiftedRep
-> TYPE ghc-prim-0.6.1:GHC.Types.LiftedRep)
(a :: TYPE ghc-prim-0.6.1:GHC.Types.LiftedRep).
Applicative f => Bar (f a) -> f (Bar a)
In an equation for ‘sequenceA’:
sequenceA
= ghc-prim-0.6.1:GHC.Prim.coerce
#(Foo Bar (f a) -> f (Foo Bar a)) #(Bar (f a) -> f (Bar a))
(sequenceA #(Foo Bar)) ::
forall (f :: TYPE ghc-prim-0.6.1:GHC.Types.LiftedRep
-> TYPE ghc-prim-0.6.1:GHC.Types.LiftedRep)
(a :: TYPE ghc-prim-0.6.1:GHC.Types.LiftedRep).
Applicative f => Bar (f a) -> f (Bar a)
When typechecking the code for ‘sequenceA’
in a derived instance for ‘Traversable Bar’:
To see the code I am typechecking, use -ddump-deriv
In the instance declaration for ‘Traversable Bar’
——————————————————————————————————————————————————————————————————————————————
...
So the questions I have are:
Is it possible to come up with some other scheme for deriving-via the instance Traversable Bar?
Is it possible to come up with some modification of the Traversable class that can be derived via a newtype?
I suspect the answer to 1. is: no, the situation cannot be salvaged, and it is impossible to obtain an instance of Traversable using DerivingVia.
As far as 2. goes, it's useful to try and reproduce the problem in a simpler context. Consider the following:
-- Remember to turn on ScopedTypeVariables!
data A = A
newtype B = B A
a :: forall f. f A -> f A
a = id
b :: forall f. f B -> f B
b = coerce $ a #f
It seems like this should work, but alas:
[typecheck -Wdeferred-type-errors] [E] • Couldn't match representation of type ‘f A’ with that of ‘f B’
arising from a use of ‘coerce’
NB: We cannot know what roles the parameters to ‘f’ have;
we must assume that the role is nominal
• In the expression: coerce $ a #f
In an equation for ‘b’: b = coerce $ a #f
• Relevant bindings include
b :: f B -> f B
The problem has to do with the "roles" of type constructors' parameters, and the way role inference works. For our purposes, roles come in two varieties: "representational" and "non-representational". Also for our purposes, the difference between the two can be approximated to the following: a type constructor F :: Type -> Type has a parameter of a "representational" role if there is an instance of Representational F, where:
type Representational :: (Type -> Type) -> Constraint
type Representational f = forall x y. Coercible x y => Coercible (f x) (f y)
Otherwise, the parameter of F is non-representational.
The typechecker lets you annotate the roles of type parameters in various places (although strangely enough, not in the kind). Sadly, there is no way to annotate the roles of a higher kinded type variable. What we can do however is just ask for Representational f directly:
b' :: forall f. Representational f => f B -> f B
b' = coerce $ a #f
which now typechecks. This suggests a possible way to tweak the Traversable typeclass to make it derivable via coercions.
Now let's look at the type of the Traversable operation sequenceA:
class Traversable t
where
sequenceA :: forall f. Applicative f => forall a. t (f a) -> f (t a)
{- ... -}
NB: There's that pesky forall f again, meaning f is taken to have a type parameter of a nominal role.
What DerivingVia is going to do is attempt to coerce between:
sequenceA #T1 :: forall f. Applicative f => forall a. T1 (f a) -> f (T2 a)
and:
sequenceA #T2 :: forall f. Applicative f => forall a. T2 (f a) -> f (T2 a)
Despite T1 (FoonessOf Bar) and T2 (Bar) being "parametrically" coercible, this coercion will fail, because the coercion of the entire operation will decompose eventually to the coercion the typechecker complained about:
Couldn't match representation of type
‘f1 (Foo Bar a1)’
with that of
‘f1 (Bar a1)’
This doesn't work because of f's parameter being considered to have a nominal role, as we discussed.
As with our simplified example above, the fix is straightforward: just ask for Representational f:
type Traversable' :: (Type -> Type) -> Constraint
class Traversable' t
where
traverse :: (Representational f, Applicative f) => (a -> f b) -> t (f a) -> f (t b)
And now at last we can derive an instance of Traversable' via the FoonessOf Bar:
instance Foo f => Traversable' (FoonessOf f)
where
traverse = _
deriving via (FoonessOf Bar) instance Traversable' Bar
In general, I'm wondering if there's a way to write a generic fold that generalizes a function that applies a forall type like:
f :: forall a. Data (D a) => D a -> b
given some datatype D for which instance Data (D a) (possibly with constraints on a). To be concrete, consider something even as simple as False `mkQ` isJust, or generally, a query on the constructor of a higher-kinded datatype. Similarly, consider a transformation mkT (const Nothing) that only affects one particular higher-kinded type.
Without explicit type signatures, they fail with No instance for Typeable a0, which is probably the monomorphism restriction at work. Fair enough. However, if we add explicit type signatures:
t :: GenericT
t = mkT (const Nothing :: forall a. Data a => Maybe a -> Maybe a)
q :: GenericQ Bool
q = False `mkQ` (isJust :: forall a. Data a => Maybe a -> Bool)
instead we are told that the forall type of the outer signatures are ambiguous:
Could not deduce (Typeable a0)
arising from a use of ‘mkT’
from the context: Data a
bound by the type signature for:
t :: GenericT
The type variable ‘a0’ is ambiguous
I can't wrap my head around this. If I'm really understanding correctly that a0 is the variable in t :: forall a0. Data a0 => a0 -> a0, how is it any more ambiguous than in say mkT not? If anything, I would've expected mkT to complain because it is the one that interacts with isJust. Additionally, these functions are more polymorphic than the branching on concrete types.
I'm curious to know if this is a limitation of proving the inner constraint isJust :: Data a => ... — my understanding is that any type of instance Data inhabited with Maybe a must also have Data a to be valid by the instance constraint instance Data a => Data (Maybe a).
tldr: You need to create a different function.
mkT has the following signature:
mkT :: (Typeable a, Typeable b) => (a -> a) -> (b -> b)
And you want to apply it to a polymorphic function of type (forall x. Maybe x -> Maybe x). It is not possible: there is no way to instantiate a in (a -> a) to obtain (forall x. Maybe x -> Maybe x).
It's not just a limitation of the type system, the implementation of mkT wouldn't support such an instantiation either.
mkT simply compares concrete types a and b for equality at run time. But what you want is to be able to test whether b is equal to Maybe x for some x. The logic this requires is fundamentally more involved. But it is certainly still possible.
Below, mkT1 first matches the type b against the App pattern to know whether b is some type application g y, and then tests equality of g and f:
{-# LANGUAGE ScopedTypeVariables, RankNTypes, TypeApplications, GADTs #-}
import Type.Reflection
-- N.B.: You can add constraints on (f x), but you must do the same for b.
mkT1 :: forall f b. (Typeable f, Typeable b) => (forall x. f x -> f x) -> (b -> b)
mkT1 h =
case typeRep #b of
App g y ->
case eqTypeRep g (typeRep #f) of
Just HRefl -> h
_ -> id
_ -> id
Compilable example with mkQ1 as well:
{-# LANGUAGE ScopedTypeVariables, RankNTypes, TypeApplications, GADTs #-}
import Type.Reflection
mkT1 :: forall f b. (Typeable f, Typeable b) => (forall x. f x -> f x) -> (b -> b)
mkT1 h =
case typeRep #b of
App g y ->
case eqTypeRep g (typeRep #f) of
Just HRefl -> h
_ -> id
_ -> id
mkQ1 :: forall f b q. (Typeable f, Typeable b) => (forall x. f x -> q) -> (b -> q) -> (b -> q)
mkQ1 h =
case typeRep #b of
App g y ->
case eqTypeRep g (typeRep #f) of
Just HRefl -> const h
_ -> id
_ -> id
f :: Maybe x -> String
f _ = "matches"
main :: IO ()
main = do
print (mkQ1 f (\_ -> "doesn't match") (Just 3 :: Maybe Int)) -- matches
print (mkQ1 f (\_ -> "doesn't match") (3 :: Int)) -- doesn't match
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.
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.