Recently, I came up with the idea that one could potentially emulate "intersection types" in Haskell. Specifically, I mean intersection of "interfaces", as they are usually conceived in OOP languages. For instance, to use some pseudo-code for a language with interfaces and intersection types to see what I mean:
interface HasName {
val name: String
}
interface HasAge {
val age: Int
}
-- An object of type HasName & HasAge can call the methods of both
type HasNameAndAge = HasName & HasAge
-- For example:
val myObject: HasNameAndAge = ...
val example = "My name is: ${myObject.name}. My age is ${myObject.age}"
I am looking to do something similar with Haskell typeclasses. My approach was to replace interfaces with elements of kind * -> Constraint in Haskell (so, for instance, single parameter type classes):
class HasName a where
name :: a -> String
class HasAge a where
age :: a -> Int
Now, given such type classes, the idea is that elements of types of the form exists a. C a => a (where c :: * -> Constraint) correspond to implementations of the "interface" C. Given such an identification, we can easily construct non-anonymous intersection types by appending constraints, for instance:
{-# LANGUAGE ExistentialQuantification, RankNTypes #-}
-- The intersection of HasName and HasAge:
data HasNameAndAge = forall a. HasNameAndAge ((HasName a, HasAge a) => a)
-- Example:
data Person = Person {
personName :: String,
personAge :: Int
}
instance HasName Person where
name = personName
instance HasAge Person where
age = personAge
myObject :: HasNameAndAge
myObject = HasNameAndAge (Person "Nathan" 27)
The issue is, trying to generalize this and make this generic in a list [* -> Constraint] of interfaces that an "object" implements, I am having trouble getting GHC to deduce what it needs to get this to work properly. This is my latest attempt:
{-# LANGUAGE
ConstraintKinds,
KindSignatures,
ExistentialQuantification,
DataKinds,
TypeFamilies,
TypeOperators,
RankNTypes,
AllowAmbiguousTypes,
TypeSynonymInstances,
FlexibleInstances,
MultiParamTypeClasses,
FlexibleContexts,
UndecidableInstances
#-}
import Data.Kind
class Elem (x :: * -> Constraint) (xs :: [* -> Constraint]) where
instance Elem x (x ': xs) where
instance Elem x xs => Elem x (y ': xs) where
type family All (cs :: [* -> Constraint]) a :: Constraint where
All '[] x = ()
All (c ': cs) x = (c x, All cs x)
-- The type of "objects" implementing all interfaces cs.
data AbstractType (cs :: [* -> Constraint])
= forall a. All cs a => AbstractType a
-- An example object of type HasName & HasAge.
myObject :: AbstractType '[HasName, HasAge]
myObject = AbstractType $ Person "Nathan" 27
-- Instances needed for every "interface" to get this to work.
instance Elem HasName cs => HasString (AbstractType cs) where
name (AbstractType x) = name x
instance Elem HasAge cs => HasAge (AbstractType cs) where
age (AbstractType x) = age x
-- Example:
myObject :: AbstractType '[HasName, HasAge]
myObject = AbstractType $ Person "Nathan" 27
example = do
print $ age myObject
putStrLn $ name myObject
It seems that I need to do a little more prodding to make GHC accept the instances I want at the end here. When I try compiling the above, I get errors like:
* Could not deduce (HasName a) arising from a use of `name'
from the context: Elem HasName cs
Intuitively, HasName should hold for AbstractType cs whenever HasName is in cs, since AbstractType cs is an existential type with the constraint All cs a. For instance, All '[HasName, HasAge] a = (HasName a, HasAge a), however, I am unsure of how to convince the GHC typechecker of this fact.
I am also getting errors like:
* No instance for (Elem HasName '[HasName, HasAge])
arising from a use of `name'
So it appears that either my implementation of a type-level elem is incorrect, or GHC just can't test equality between terms of kind * -> Constraint, so I am not sure if what I am trying to do is even possible with current versions of GHC.
Just having a class with instances for when
cis an element ofcsis not enough. GHC actually needs access to the dictionaries associated with these constraints in order to do any computation with them, but the class you wrote doesn't provide that. What you need to do is extend the class with a function that captures this context. Something like this:(EDIT NOTE: Weirdly, GHC doesn't require that we put in the
OVERLAPSpragma here, but if we don't include it, then we can never actually use this type class. Thanks to @dfeuer in the comments for figuring this out!)This
withCfunction says that if we know that all of the constraints incsare satisfied by somea, then surely this particularcis satisfied. Therefore, if we have a function froma -> xthat requires the constraintc a, then we can convert anainto anx.With this, we can then write the
HasNameandHasAgeinstances you want:This all type checks (although it is a little annoying that we have to do some explicit type annotations).
As @dfeuer points out in the comments, we can make the
Elemclass even more general by changing the type ofwithCas follows:Note that for this to type check, we need to enable
AllowAmbiguousTypesbecause theatype inwithCis otherwise impossible for GHC to deduce at this point.This seems great and is definitely more general (we can recover the old behavior by simply considering the specification that
ris a function typea -> x), but having to specify the type ofais a little cumbersome. Consider our new instances forAbstractType:We now need to capture the type of
xin the pattern so that we can provide it towithC.