I have a class Cyc c r
which has functions for datas of the form c m r
, where m
is a phantom type. For example,
class Cyc c r where
cyc :: (Foo m, Foo m') => c m r -> c m' r
I do have good reasons for not making m
a class parameter. For the purposes of this example, the primary reason is that it reduces the number of constraints on functions. In my actual example, a more compelling need for this interface is that I work with changing and hidden phantom types, so this interface lets me get a Cyc
constraint for any phantom type.
One downside to that choice is that I can't make Num (c m r)
a superclass constraint of Cyc
. My intention is that c m r
should be a Num
whenever (Cyc c r, Foo m)
. The current solution is very annoying: I added method to class Cyc
witNum :: (Foo m) => c m r -> Dict (Num (c m r))
which sort-of accomplishes the same thing. Now when I have a function that takes a generic Cyc
and needs a Num (c m r)
constraint, I can write:
foo :: (Cyc c r, Foo m) => c m r -> c m r
foo c = case witNum c of
Dict -> c*2
Of courses I could add a Num (c m r)
constraint to foo
, but I'm trying to reduce the number of constraints, remember? (Cyc c r, Foo m)
is supposed to imply a Num (c m r)
constraint (and I need Cyc c r
and Foo m
for other purposes), so I don't want to have to write out the Num
constraint also.
In the process of writing this question, I found a better(?) way to accomplish this, but it has its own drawbacks.
Module Foo:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, ScopedTypeVariables #-}
module Foo where
import Data.Constraint
class Foo m
class Cyc c r where
cyc :: (Foo m, Foo m') => c m r -> c m' r
witNum :: (Foo m) => c m r -> Dict (Num (c m r))
instance (Foo m, Cyc c r) => Num (c m r) where
a * b = case witNum a of
Dict -> a * b
fromInteger a = case witNum (undefined :: c m r) of
Dict -> fromInteger a
-- no Num constraint and no Dict, best of both worlds
foo :: (Foo m, Cyc c r) => c m r -> c m r
foo = (*2)
Module Bar:
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, OverlappingInstances #-}
module Bar where
import Foo
import Data.Constraint
data Bar m r = Bar r deriving (Show)
instance (Num r) => Cyc Bar r where
witNum _ = Dict
instance (Num r, Foo m) => Num (Bar m r) where
(Bar a) * (Bar b) = Bar $ a*b
fromInteger = Bar . fromInteger
instance Foo ()
bar :: Bar () Int
bar = foo 3
While this approach gets me everything I'm looking for, it seems fragile. My main concerns are:
Num
in module Foo
.Foo
, I suddenly need IncoherentInstances
or the Num
constraint on foo
to defer instance selection to runtime.Is there an alternative way to avoid using Dict
in every function that needs Num (c m r)
that avoids either of these downsides?
After 6 months of thought, I finally have an answer to my dangling comment above: add a newtype
wrapper!
I split the Cyc
class in two:
class Foo m
class Cyc c where
cyc :: (Foo m, Foo m') => c m r -> c m' r
class EntailCyc c where
entailCyc :: Tagged (c m r) ((Foo m, Num r) :- (Num (c m r)))
Then I define my Cyc
instance as above:
data Bar m r = ...
instance Cyc Bar where ...
instance (Num r, Foo m) => Num (Bar m r) where ...
instance EntailCyc Bar where
witNum _ = Dict
Then I define a newtype wrapper and give a generic Cyc
instance for it:
newtype W c m r = W (c m r)
instance Cyc (W c m r) where cyc (W a) = W $ cyc a
instance (EntailCyc c, Foo m, Num r) => Num (W c m r) where
(W a) + (W b) = a + b \\ witness entailCyc a
Finally, I change all functions that used a generic c m r
type to use a W c m r
type:
foo :: (Cyc c, EntailCyc c, Foo m, Num r) => W c m r -> W c m r
foo = (*2)
The point here is that foo
might need many constraints (e.g., Eq (W c m r)
, Show (W c m r)
, etc) that would each individually require their own constraints. However, the generic instances for W c m r
for Eq
, Show
, etc all have exactly the constraints (EntailCyc c, Foo m, Eq/Show/... a)
, so the constraints on foo
above are the only constraints I need to write!
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With