Here is what my problem boils down to: I have a class, and I want every Floating and every Integral to instantiate it, but in different ways. In a minimal code example:
class MyClass a where
func :: a -> Bool
instance (Floating a) => MyClass a where
func _ = True
instance (Integral b) => MyClass b where
func _ = False
This by itself throws an error, saying "Duplicate instance declarations". As far as I know, the underlying reason for this is that a type which implements both Floating and Integral would produce undefined behaviour, so haskell does not take constraints into consideration.
To start off, pragmas such as {-# INCOHERENT #-} do not help.
There are some tricks that can be done with type families. I have seen this approach in other places:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
import Data.Data (Proxy(..))
-- My class, for which I want two classes of instances
class MyClass a where
func :: a -> Bool
-- A type family providing a value depending on the type variable
data FromFloatingOrIntegralResult = FromFloating | FromIntegral
type family FromFloatingOrIntegral a :: FromFloatingOrIntegralResult where
FromFloatingOrIntegral (Floating a) = 'FromFloating
FromFloatingOrIntegral (Integral a) = 'FromIntegral
-- A class implementation with a proxy to differentiate between the two classes
class MyClassImpl (r :: FromFloatingOrIntegralResult) a where
funcImpl :: Proxy r -> a -> Bool
-- Implementing the previous instances
instance (Floating a) => MyClassImpl FromFloating a where
funcImpl _ floating = True
instance (Integral b) => MyClassImpl FromIntegral b where
funcImpl _ integral = False
Now I need to actually make MyClassImpl be an instance of MyClass.
instance (MyClassImpl FromFloating a) => MyClass a where
func = funcImpl (Proxy :: Proxy FromFloating)
instance (MyClassImpl FromIntegral a) => MyClass a where
func = funcImpl (Proxy :: Proxy FromIntegral)
This results in the exact problem I started with. Somehow, I need to instantiate FromFloating and FromIntegral at the same time.
instance (MyClassImpl (FromFloatingOrIntegral a) a) => MyClass a where
func = funcImpl (Proxy :: Proxy (FromFloatingOrIntegral a))
Here, 'a' has a kind of 'constraint' instead of a type
instance (MyClassImpl (FromFloatingOrIntegral b) a) => MyClass a where
func = funcImpl (Proxy :: Proxy (FromFloatingOrIntegral b))
someRandomFunction :: (MyClass a) => a -> Bool
someRandomFunction a = func a
The second argument could be left ambiguous with the AllowAmbiguousTypes extention, but then the compiler will complain about the ambiguous variable.
class MyClassImpl (r :: FromFloatingOrIntegralResult) a | a -> r where
funcImpl :: Proxy r -> a -> Bool
Adding functional dependencies just makes the starting problem appear when making the two instances.
The issue seems to come from the fact that in
type family FromFloatingOrIntegral a :: FromFloatingOrIntegralResult where
FromFloatingOrIntegral (Floating a) = 'FromFloating
FromFloatingOrIntegral (Integral a) = 'FromIntegral
FromFloatingOrIntegral expects to take in a value with a Constraint type. But there doesn't seem to be a way to apply constraints regurarly to a type family.
Is this an impossible task I've stumbled upon, or is there some language extension or technique that could help me out?
There are some things you can do that sort of hack around this to an extent that may or may not be useful, but it's just not really an intended use of the type class system to ever write instances like instance SomeConstraint t => SomeClass t
. You are intended to write instances for types, not for whole other classes.
It's not just the question of what to do in the overlapping zone with your two constraints. It's designed to try to maintain the property that any time the compiler tries to solve a constraint for a type anywhere in a program (even across independent library packages that don't directly import each other but are used together in one program) it will always select the exact same instance, even in the face of other instances existing that aren't visible while it's compiling this module. This property is relied upon by core libraries like Data.Map
; if it were ever possible to resolve two different Ord
instances for a given type in different parts of the same program, then the Map
API would have to be designed quite differently.
So the compiler can never, for example, commit to the instance (Integral b) => MyClass b
instance for some type T
merely because it can't see any instance Floating T
right now; such an instance might exist elsewhere. Instead the design is that a single possible instance has to be identifiable just from looking at the heads of the instances that are visible, ignoring the constraints. If that single instance has constraints then those also have to be solved afterwards, but they can't be used as part of identifying the single possible instance.
There are ways to drop some of restrictions (such as using overlapping or incoherent pragmas), but you're fundamentally working against the system when you do this; it makes you responsible for avoiding all the subtle problems that the normal system is designed to prevent. So I generally would not recommend trying these features to anyone who isn't already an expert at using type classes in "normal" ways.
It's generally much easier to work with the system. Instead of adding all the complexity of extra implementation classes and type families so that you can try to route types to your catch-all instances properly, you can just make it very easy to declare an instance for each individual type. Using things like DerivingVia
you can usually get it down to a one-liner instance declaration for each type; there's not that many built in types that are Integral
or Floating
, so it's not hard to this to end up with less boilerplate than a much more complex setup that tries to get the whole-class instances (and it's all very easy and mechanical; you could easily generate it if you want, but there's usually not enough of it to be worth that either). For example:
{-# LANGUAGE DerivingVia #-}
class MyClass a where
func :: a -> Bool
-- Declare a simple newtype for each of the whole-class instances you wanted.
-- Don't worry, you never actually have to use these types.
newtype FloatingMyClass a = FloatingMyClass a
newtype IntegralMyClass a = IntegralMyClass a
-- Write the whole-class instances you wanted but for the *newtypes* instead
-- of actually covering every type. You can write the code basically exactly
-- the same way you wanted; no additional complexity with type families etc,
-- only a boring newtype wrapper.
instance Floating a => MyClass (FloatingMyClass a) where
func _ = True
instance Integral a => MyClass (IntegralMyClass a) where
func _ = False
-- Now for each type, write a one liner declaring which of the newtype
-- instances should be used to used to produce the instance for the actual
-- type.
deriving via IntegralMyClass Int instance MyClass Int
deriving via IntegralMyClass Integer instance MyClass Integer
deriving via FloatingMyClass Float instance MyClass Float
deriving via FloatingMyClass Double instance MyClass Double
Effectively the newtypes with your intended instances attached to them become names for "template instances". While you still have to declare an instance for every type individually, you don't have to actually write the implementation for each one; you can just name the "template" you want to use.
A big advantage of this scheme is that when you find that MyClass
would be useful with a type in a way that isn't solely determined by whether it's Integral
or Fractional
, nothing stops you writing a specific instance for that type instead of deriving via
one of the newtype instances. With your original idea you would be blocked at that point.
Or of course, if you know that you intend func
to always be determined by whether a type is Integral
or Floating
, there's an argument to be made that you don't even need a class:
funcF :: Floating a => a -> Bool
funcF _ = True
funcI :: Integral a => a -> Bool
funcI _ = False
This requires differentiating the names and choosing one at each use-site, but the compiler tells you if you get it wrong and it takes a quite a lot of uses before the time you spend typing a short suffix adds up to more than the time you would have spent on the setup of fancier methods. It doesn't feel "clever", but it's easy and fast. Sometimes you're better off getting the compiler to choose between options by just giving them different names and telling the compiler, instead of using a class and trying to make sure the compiler can always infer what you meant when you used an overloaded name.