Find an element in an HList - haskell

I'm trying to write two functions to extract a value from an HList, but I can't seem to make GHC happy.
The first function would have signature extract :: HList a -> [b] which extracts all the elements of type b from the list. I only succeeded in writing it by asking the types in a to have Typeable instances.
class OfType a b where
oftype :: a -> [Maybe b]
instance OfType (HList '[]) b where
oftype = const []
instance (Typeable t, Typeable b, OfType (HList ts) b) => OfType (HList (t ': ts)) b where
oftype (x :- xs) = (cast x :: Maybe b) : oftype xs
extract :: OfType a b => a -> [b]
extract = catMaybes . oftype
Which is suboptimal, as one doesn't really need the Typeable constraint to write any instance of extract.
I tried to use type equalities and inequalities in constraints, but this only gave me overlapping instances.
The second function I'm trying to write would have signature extract' :: Contains h n => HList h -> n which extracts the first element of type n in the list, and the context says that the list actually contains one element of that type.
Is it possible to write extract without Typeable constraints?
Is it possible to write extract' without Typeable constraints?
How can one write Contains?

Since you want to check for type equality at compile time, I believe overlapping instances are unavoidable (and I'm not a fan of those...).
Also, I'm not 100% sure I got the overlapping pragmas right.
{-# LANGUAGE DataKinds, TypeOperators, ScopedTypeVariables,
MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-}
{-# OPTIONS -Wall #-}
module HListFilter where
import Data.HList.HList
class OfType a b where
oftype :: a -> [b]
instance OfType (HList '[]) b where
oftype = const []
instance {-# OVERLAPS #-} (OfType (HList ts) t) => OfType (HList (t ': ts)) t where
oftype (HCons x xs) = x : oftype xs
instance {-# OVERLAPPABLE #-} (OfType (HList ts) b) => OfType (HList (t ': ts)) b where
oftype (HCons _ xs) = oftype xs
test :: HList '[Int, Char, [Char], Char, Bool]
test = HCons (1::Int) (HCons 'a' (HCons "foo" (HCons 'b' (HCons True HNil))))
test_result :: [Char]
test_result = oftype test -- "ab"

András Kovács referred to a type family approach. This is one way to do it:
type family Equal (x :: *) (y :: *) where
Equal x x = 'True
Equal x y = 'False
type family Check (b :: *) (as :: [*]) :: [Bool] where
Check b '[] = '[]
Check b (a ': as) = (b `Equal` a) ': Check b as
class ps ~ Check b as =>
OfType (ps :: [Bool]) (as :: [*]) b where
extract :: HList as -> [b]
The ps ~ Check b as superclass context is critical here, as a matter of timing. GHC always commits to an instance before checking the instance constraints, but it doesn't even try to find an instance until after solving the superclass constraints. So we need to use the superclass constraint to fix which instances to select.
instance OfType '[] '[] b where
extract HNil = []
instance (OfType ps as b, a ~ b) =>
OfType ('True ': ps) (a ': as) b where
extract (HCons x xs) = x : extract xs
instance (OfType ps as b, Equal b a ~ 'False) =>
OfType ('False ': ps) (a ': as) b where
extract (HCons _ xs) = extract xs
Once you've done this, you can actually write an interface that avoids the "extra" class parameter:
class OfType' (as :: [*]) (b :: *) where
extract' :: HList as -> [b]
instance OfType ps as b => OfType' as b where
extract' = extract
It's quite easy to write Contains and extract'. However, writing good instances of Contains necessitates exactly the same sort of hoop jumping as OfType. The class you'd like to have is this:
class Contains xs y where
contains :: y `Elem` xs
-- Elem is part of the dependently typed folklore.
data Elem y xs where
Here :: Elem y (y ': xs)
There :: Elem y xs -> Elem y (x ': xs)
But writing instances will again force you into overlapping or closed type families. I know I've written this code somewhere around SO, but you should probably be able to work out the overlapping version pretty easily; the type family version will follow the same pattern as OfType, generally.

Related

Homogenize a heterogenous list with a funtion that has a particular kind of context

I am fiddling with the basics of type-level programming in Haskell, and I was trying to write a function that "homogenizes" a heterogeneous list using a function with a context of kind (* -> *) -> Constraint (e.g., length or fmap (/= x)).
The heterogeneous list is defined as follows:
data HList ls where
HNil :: HList '[]
(:::) :: a -> HList as -> HList (a ': as)
And I have defined a type family AllKind2:
type family AllKind2 c t li :: Constraint where
AllKind2 _ _ '[] = ()
AllKind2 c t ((t _) : xs)) = (c t, AllKind2 c t xs)
The type family works as intended (as far as I can tell with my limited knowledge) as demonstrated with this function that simply returns unit if supplied with a heterogeneous list that can satisfy AllKind2:
unitIfAllIsWell :: forall c t li. AllKind2 c t li => Proxy c -> Proxy t -> HList li -> ()
unitIfAllIsWell _ _ _ = ()
>>> unitIfAllIsWell (Proxy :: Proxy Foldable) (Proxy :: Proxy []) ([] ::: "ok" ::: [1,2] ::: HNil)
()
>>> unitIfAllIsWell (Proxy :: Proxy Foldable) (Proxy :: Proxy []) ("is_list" ::: 10 ::: HNil)
<interactive>:414:1: error:
• Could not deduce: AllKind2 Foldable [] '[Integer]
arising from a use of ‘unitIfAllIsWell’
However, the homogenize function I've written fails at the typecheck:
homogenize
:: forall c t li q. AllKind2 c t li
=> Proxy c
-> Proxy t
-> (forall p q. c t => t p -> q)
-> HList li
-> [q]
homogenize _ _ _ HNil = []
homogenize _ _ f (x ::: xs) = f x : homogenize (Proxy :: Proxy c) (Proxy :: Proxy t) f xs
• Could not deduce: a ~ t p0
from the context: AllKind2 c t li
bound by the type signature for:
homogenize :: forall (c :: (* -> *) -> Constraint)
(t :: * -> *) (li :: [*]) q.
AllKind2 c t li =>
Proxy c
-> Proxy t
-> (forall p q1. c t => t p -> q1)
-> HList li
-> [q]
at HList.hs:(134,1)-(140,8)
or from: li ~ (a : as)
bound by a pattern with constructor:
::: :: forall a (as :: [*]). a -> HList as -> HList (a : as),
in an equation for ‘homogenize’
at HList.hs:142:24-31
‘a’ is a rigid type variable bound by
a pattern with constructor:
::: :: forall a (as :: [*]). a -> HList as -> HList (a : as),
in an equation for ‘homogenize’
at HList.hs:142:24-31
Is the constraint AllKind2 not sufficient to tell the compiler that any element from the HList li will satisfy constraint c t and thus, applying the supplied function f should be valid at the type level?
Am I missing something here? Is what I am attempting even possible?
Even though e.g. AllKind2 Foldable [] '[Int] does not match any equation for AllKind2, it is not understood to be an unsatisifiable constraint. (The general principle is undefined type family applications are just that: undefined, in the sense it could be something but you have no idea what it is.) That's why, even if you know AllKind2 c t (x : xs), you can not deduce x ~ t y for some y by saying "that's the only way to get a defined constraint from AllKind2." You need an equation for the general AllKind2 c t (x : xs) case that dispatches to a class that will contain the actual information.
-- if you know some types satisfy a typeclass, you know they satisfy the superclasses
-- this lets us store and extract the information that x needs to be of form t _
class (c t, x ~ t (UnwrapAllKind2 t x)) => AllKind2Aux c t x where
type UnwrapAllKind2 t x
instance c t => AllKind2Aux c t (t y) where
type UnwrapAllKind2 t (t y) = y
type family AllKind2 c t xs :: Constraint where
AllKind2 c t '[] = ()
AllKind2 c t (x : xs) = (AllKind2Aux c t x, AllKind2 c t xs)
Then your homogenize passes without modification.
Do note that homogenize is overcomplicated. The c is simply not doing anything: homogenize is taking the c t instance as input and just forwarding it to the function being mapped. That function can just use its own c t instance, since t is fixed. There's nothing homogenize can do that the following function cannot do more clearly (note that your homogenize fails even to "restrict" the mapped function to only using c t and not any other properties of t, so it can muddle much more than it can clarify):
class x ~ t (UnApp t x) => IsApp t x where
type UnApp t x
instance IsApp t (t y) where
type UnApp t (t y) = y
type family AllApp t xs :: Constraint where
AllApp t '[] = ()
AllApp t (x : xs) = (IsApp t x, AllApp t xs)
homogenize' :: AllApp t xs => Proxy t -> (forall x. t x -> r) -> HList xs -> [r] -- also, the Proxy t is not strictly necessary
homogenize' t f HNil = []
homogenize' t f (x ::: xs) = f x : homogenize' t f xs -- note that dealing with Proxys is much nicer if you treat them as things that can be named and passed around instead of rebuilding them every time
-- homogenize' (Proxy :: Proxy []) length ([] ::: "ok" ::: [1,2] ::: HNil) = [0, 2, 2]

Converting between heterogeneous lists

I have two heterogeneous list structures. The first HList is a normal heterogeneous list, the second Representation is a heterogeneous list where all the members are sets.
{-# Language KindSignatures, DataKinds, TypeOperators, TypeFamilies, GADTs, FlexibleInstances, FlexibleContexts #-}
import Data.Kind
import Data.Set
data Representation (a :: [Type]) where
NewRep :: Representation '[]
AddAttribute :: (Ord a, Eq a) => Set a -> Representation b -> Representation (a ': b)
(%>) :: (Ord a, Eq a) => [a] -> Representation b -> Representation (a ': b)
(%>) = AddAttribute . fromList
infixr 6 %>
-- | A HList is a heterogenenous list.
data HList (a :: [Type]) where
HEmpty :: HList '[]
(:>) :: a -> HList b -> HList (a ': b)
infixr 6 :>
(I've made these instances of Show at the bottom if that is helpful.)
Now I have a bunch of functions that work on HLists but don't work on Representations. I could rewrite all the functions but that's a big pain. I'd rather if there was some way to make Representations in HLists and back. That way I can use all the relevant functions without having to redefine them. So I started to do this. It was pretty easy to make a function that goes from Representations to HLists:
type family Map (f :: Type -> Type) (xs :: [Type]) :: [Type] where
Map f '[] = '[]
Map f (a ': b) = f a ': Map f b
-- | soften takes an attribute representation and converts it to a heterogeneous list.
soften :: Representation a -> HList (Map Set a)
soften NewRep = HEmpty
soften (AddAttribute a b) = a :> soften b
However the other way is quite a bit harder. I tried the following:
-- | rigify takes a heterogeneous list and converts it to a representation
rigify :: HList (Map Set a) -> Representation a
rigify HEmpty = NewRep
rigify (a :> b) = AddAttribute a $ rigify b
However this fails, the compiler is not able to deduce that a ~ '[] in the first line. And fails in a similar fashion on the second.
It appears to me that the compiler can't reason backwards in the same way it can forward. This is not really very surprising, but I don't know exactly what the issue is, so I'm not really very sure how to get the compiler to reason correctly. My thought was to make a type family that is the reverse of Map like so:
type family UnMap (f :: Type -> Type) (xs :: [Type]) :: [Type] where
UnMap f '[] = '[]
UnMap f ((f a) ': b) = a ': UnMap f b
and then rewrite rigify in terms of UnMap instead of Map:
-- | rigify takes a heterogeneous list and converts it to a representation
rigify :: HList a -> Representation (UnMap Set a)
rigify HEmpty = NewRep
rigify (a :> b) = AddAttribute a $ rigify b
This seems to reduce the problem but it still doesn't compile. This time we are having the issue that a in the second line cannot be shown to be of type Set x which is required for AddAttribute. This makes total sense to me but I don't know how I could remedy the issue.
How can I convert from a heterogeneous list to a Representation?
Show instances:
instance Show (HList '[]) where
show HEmpty = "HEmpty"
instance Show a => Show (HList '[a]) where
show (a :> HEmpty) = "(" ++ show a ++ " :> HEmpty)"
instance (Show a, Show (HList (b ': c))) => Show (HList (a ': b ': c)) where
show (a :> b) = "(" ++ show a ++ " :> " ++ tail (show b)
instance Show (Representation '[]) where
show NewRep = "NewRep"
instance Show a => Show (Representation '[a]) where
show (AddAttribute h NewRep) = '(' : show (toList h) ++ " %> NewRep)"
instance (Show a, Show (Representation (b ': c))) => Show (Representation (a ': b ': c)) where
show (AddAttribute h t) = '(' : show (toList h) ++ " %> " ++ tail (show t)
HList is usually wrong. What I mean is that as soon as you try to do very much, you're likely to end up with lots of problems. You can solve the problems, but it's annoying and often inefficient. There's another, very similar, construction that can go a lot further before it falls down.
data Rec :: [k] -> (k -> Type) -> Type where
Nil :: Rec '[] f
(:::) :: f x -> Rec xs f -> Rec (x ': xs) f
type f ~> g = forall x. f x -> g x
mapRec :: (f ~> g) -> Rec xs f -> Rec xs g
mapRec _ Nil = Nil
mapRec f (x ::: xs) = f x ::: mapRec f xs
Note that you can do a certain sort of mapping without bringing in any type families at all!
Now you can define
data OSet a = Ord a => OSet (Set a)
newtype Representation as = Representation (Rec as OSet)
An awful lot of generic HList functions can be rewritten very easily to support Rec instead.
You can write bidirectional pattern synonyms to simulate your current interface if you like.
Ord a makes Eq a redundant: Ord a implies Eq a because class Eq a => Ord a.
data Representation (a :: [Type]) where
...
AddAttribute :: Ord a => Set a -> Representation b -> Representation (a ': b)
(%>) :: Ord a => [a] -> Representation b -> Representation (a ': b)
You can't write rigify with quite this type: soften throws away the Ord-ness stored at each AddAttribute. You can use
data OSet a where OSet :: Ord a => Set a -> OSet a
soften :: Representation xs -> HList (Map OSet xs)
rigify :: HList (Map OSet xs) -> Representation xs
and you may apply the age old "list of pairs is a pair of lists" trick on top of that
type family AllCon (xs :: [Constraint]) :: Constraint where
AllCon '[] = ()
AllCon (x : xs) = (x, AllCon xs)
data Dict c = c => Dict
soften :: Representation xs -> (HList (Map Set xs), Dict (AllCon (Map Ord xs)))
rigify :: AllCon (Map Ord xs) => HList (Map Set xs) -> Representation xs
though I shall go with the former because it is more concise.
Use unsafeCoerce. The alternative is to reify some type information with a GADT and write a proof. While that is good practice, that requires you to drag around (potentially large) values that represent things that are simply true, so you'll end up using unsafeCoerce anyway to avoid them. You can skip the proofs and go to the end products directly.
-- note how I always wrap the unsafeCoerce with a type signature
-- this means that I reduce the chance of introducing something actually bogus
-- I use these functions instead of raw unsafeCoerce in rigify, because I trust
-- these to be correct more than I trust unsafeCoerce.
mapNil :: forall f xs. Map f xs :~: '[] -> xs :~: '[]
mapNil Refl = unsafeCoerce Refl
data IsCons xs where IsCons :: IsCons (x : xs)
mapCons :: forall f xs. IsCons (Map f xs) -> IsCons xs
mapCons IsCons = unsafeCoerce IsCons
rigify :: HList (Map OSet xs) -> Representation xs
rigify HEmpty = case mapNil #OSet #xs Refl of Refl -> NewRep
rigify (x :> xs) = case mapCons #OSet #xs IsCons of
IsCons -> case x of OSet x' -> AddAttribute x' (rigify xs)
A proper proof would go as follows:
data Spine :: [k] -> Type where
SpineN :: Spine '[]
SpineC :: Spine xs -> Spine (x : xs)
mapNil' :: forall f xs. Spine xs -> Map f xs :~: '[] -> xs :~: '[]
mapNil' SpineN Refl = Refl
mapNil' (SpineC _) impossible = case impossible of {}
mapCons' :: forall f xs. Spine xs -> IsCons (Map f xs) -> IsCons xs
mapCons' SpineN impossible = case impossible of {}
mapCons' (SpineC _) IsCons = IsCons
For every list xs, there is one and only one (fully defined) value of Spine xs (it is a singleton type). To get from real proofs (like mapNil') to their convenience versions (like mapNil), remove all the singleton arguments and make sure the return type is a mere proposition. (A mere proposition is a type with 0 or 1 values.) Replace the body with one that deeply evaluates the remaining arguments and uses unsafeCoerce for the return value.
Use a type class
The desired behavior for rigify can be obtained by using a multi paramater type class instead.
class Rigible (xs :: [Type]) (ys :: [Type]) | xs -> ys where
rigify :: HList xs -> Representation ys
instance Rigible '[] '[] where
rigify HEmpty = NewRep
instance (Ord h, Rigible t t') => Rigible (Set h ': t) (h ': t') where
rigify (a :> b) = AddAttribute a $ rigify b
Here we use a multiparam type class Rigible with an attached function rigify. Our two parameters are the type for the representation and the type for the heterogeneous list. They are functionally dependent to avoid ambiguity.
In this way only HLists that are composed entirely of sets are Rigible. From here you can even add the definition of soften to Rigible as well.
-- | soften takes a representation and converts it to a heterogeneous list.
-- | rigify takes a heterogeneous list and converts it to a representation.
class Rigible (xs :: [Type]) (ys :: [Type]) | xs -> ys where
rigify :: HList xs -> Representation ys
soften :: Representation ys -> HList xs
instance Rigible '[] '[] where
rigify HEmpty = NewRep
soften NewRep = HEmpty
instance (Ord h, Rigible t t') => Rigible (Set h ': t) (h ': t') where
rigify (a :> b) = AddAttribute a $ rigify b
soften (AddAttribute a b) = a :> soften b
This requires the additional pragma
{-# Language MultiParamTypeClasses, FunctionalDependencies, UndecidableInstances #-}

Extensible records (I think)

What I roughly want is this:
data A = ...
data B = ...
data C = ...
class HasA t where
getA :: t -> A
class HasB t where
getB :: t -> B
class HasC t where
getC :: t -> C
So I can do something like this (pseudocode follows):
a :: A
b :: B
x = mkRecord { elemA a, elemB b }
y = mkRecord { elemB b, elemA a }
-- type of `x` == type of `y`
Naturally, only the appropriate get functions work, in the above case getA and getB.
I'd also like the following functions
slice :: Subset a b => a -> b
slice x = -- just remove the bits of x that aren't in type b.
add :: e -> a -> a ++ e
add e x = -- add an element to the "record" (compile error if it's already there)
I feel like this is not a new problem so perhaps a resolution for this already exists. Note that I don't require the solution to be extensible, the amount of types I need to deal with is finite and known, but of course and extensible one wouldn't hurt.
I've found a couple of packages that seem to be in the field of what I'm looking for, namely HList and extensible (perhaps extensible is better because I want my records unordered). I got a bit lost in the Hackage docs so I'd like just some sample code (or a link to some sample code) that roughly achieves what I'm looking for.
This is exactly what HList is good for. However, since I don't have the right setup to test something with the HList package right now (and besides, it has more confusing data definitions), here is a minimal example of HList that uses singletons for the type-level list stuff.
{-# LANGUAGE DataKinds, TypeOperators, GADTs,TypeFamilies, UndecidableInstances,
PolyKinds, FlexibleInstances, MultiParamTypeClasses
#-}
import Data.Singletons
import Data.Promotion.Prelude.List
data HList (l :: [*]) where
HNil :: HList '[]
HCons :: x -> HList xs -> HList (x ': xs)
The add function is the simplest: it is just HCons:
add :: x -> HList xs -> HList (x ': xs)
add = HCons
Something more interesting is combining two records:
-- Notice we are using `:++` from singletons
combine :: HList xs -> HList ys -> HList (xs :++ ys)
combine HNil xs = xs
combine (x `HCons` xs) ys = x `HCons` (xs `combine` ys)
Now, for your get function, you need to dispatch based on the type-level list. To do this, you need an overlapping type class.
class Has x xs where
get :: xs -> x
instance {-# OVERLAPS #-} Has x (HList (x ': xs)) where
get (x `HCons` _) = x
instance Has x (HList xs) => Has x (HList (y ': xs)) where
get (_ `HCons` xs) = get xs
Finally, we can use Has to define a similar Subset class. Same idea as before.
class Subset ys xs where
slice :: xs -> ys
instance Subset (HList '[]) (HList xs) where
slice _ = HNil
instance (Get y (HList xs), Subset (HList ys) (HList xs)) =>
Subset (HList (y ': ys)) (HList xs) where
slice xs = get xs `HCons` slice xs
As you mention in parens, the simple HList form does not ensure you have only one of any type of field (so get just returns the first field, ignoring the rest). If you want uniqueness, you can just add a constraint to the HList constructor.
data Record (l :: [*]) where
Nil :: Record '[]
Cons :: (NotElem x xs ~ 'True) => x -> Record xs -> Record (x ': xs)
However, defining Subset using Record looks like it involves some proofs. :)

Deconstruct type level list into nested tuple without sentinel for '[]

I'm trying to deconstruct a list of types (e.g. '[Int, Int]) into both a type and a way to create that type via type operators (isomorphic to nested tuples but nicer to write). For example:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
import Data.Kind (Type)
data a :<> b = a :<> b
infixr 8 :<>
class Construct a where
type Result a :: Type
instance forall a as. (Show a, Construct as) => Construct (a:as) where
type Result (a:as) = a :<> (Result as)
instance Construct '[] where
type Result '[] = ()
When using this I get e.g.
λ :kind! Result '[Int, Int, Int]
Result '[Int, Int, Int] :: *
= Int :<> (Int :<> (Int :<> ()))
Note the :<> () at the end which I don't want. At first I tried matching more specifically on the length of the list elements, e.g. '[a, b]:
instance forall a b. (Show a, Show b) => Construct ('[a,b]) where
type Result '[a,b] = a :<> b
But of course that doesn't work:
Conflicting family instance declarations:
Result (a : as) = a :<> Result as -- Defined at test.hs:14:8
Result '[a, b] = a :<> b -- Defined at test.hs:22:8
I can always construct up to N specific instances:
instance forall a. (Show a) => Construct '[a] where
type Result '[a] = a
instance forall a b. (Show a, Show b) => Construct '[a,b] where
type Result '[a, b] = a :<> b
instance forall a b c. (Show a, Show b, Show c) => Construct '[a,b,c] where
type Result '[a, b, c] = a :<> b :<> c
-- etc. up to N
but that seems very unsatisfying.
Is there a way to unpack to Int :<> (Int :<> Int) instead of Int :<> (Int :<> (Int :<> ()))) using the recursive definition?
Use closed type families. They match top-to-bottom, so there's no conflict.
type family Construct (xs :: [Type]) :: Type where
Construct '[x] = x
Construct (x ': xs) = x :<> Construct xs
Now Construct [Int, Int, Int] reduces to Int :<> (Int :<> Int).
However, if I'm roughly right about how you intend to use this, you're much better off with heterogeneous lists, as they're easier to work with and have better type inference.
{-# language
UndecidableInstances, RankNTypes, TypeOperators, TypeFamilies,
TypeApplications, ScopedTypeVariables, GADTs, DataKinds, PolyKinds,
ConstraintKinds, AllowAmbiguousTypes #-}
import Data.List
import Data.Kind
data HList (ts :: [Type]) :: Type where
Nil :: HList '[]
(:>) :: t -> HList ts -> HList (t ': ts)
infixr 5 :>
-- example
foo :: HList [Int, String, Bool]
foo = 0 :> "foo" :> True :> Nil
As an example for a useful operation on HList, if we know that each element type satisfies a class constraint, we can map over the list, either collecting it into a homogeneous list or preserving the element types:
type family AllC c (xs :: [a]) :: Constraint where
AllC c '[] = ()
AllC c (x ': xs) = (c x, AllC c xs)
hmap :: forall c ts. AllC c ts => (forall x. c x => x -> x) -> HList ts -> HList ts
hmap f Nil = Nil
hmap f (x :> xs) = f x :> hmap #c f xs
hmap' :: forall c ts r. AllC c ts => (forall x. c x => x -> r) -> HList ts -> [r]
hmap' f Nil = []
hmap' f (x :> xs) = f x : hmap' #c f xs
We can use TypeApplications to set the c constraints. We can implement the Show instance for HList simply with the use of hmap':
instance AllC Show ts => Show (HList ts) where
show xs = "[" ++ intercalate ", " (hmap' #Show show xs) ++ "]"
Now we have in ghci:
> foo
[0, "foo", True]
which works because all element types of foo have Show instances.

Shared constraint for items of an HList

Suppose we have a following definition of HList:
data HL spec where
HLNil :: HL ()
HLCons :: h -> HL t -> HL (h, t)
Is it possible to somehow enforce a shared constraint on its items?
As an example, following is my attempt to constrain the items to have Show instances, which fails with Couldn't match type `Char' with `Int':
class HLSpecEach spec item
instance HLSpecEach () item
instance (HLSpecEach t item, h ~ item) => HLSpecEach (h, t) item
a :: (Show item, HLSpecEach spec item) => HL spec -> Int
a = undefined
b :: HL (Int, (Char, ()))
b = undefined
c = a b
Easy to do if you have constraint kinds and type families. First, let me say I prefer using DataKinds for clarity
data HList ls where
HNil :: HList '[]
HCons :: x -> HList xs -> HList (x ': xs)
type family ConstrainAll (c :: * -> Constraint) (ls :: [*]) :: Constraint
type instance ConstrainAll c '[] = ()
type instance ConstrainAll c (x ': xs) = (c x, ConstrainAll c xs)
showAll :: ConstrainAll Show xs => HList xs -> [String]
showAll HNil = []
showAll (HCons x xs) = (show x) : showAll xs
if you don't use the new extensions it is possible, but much uglier. One option is to define custom classes for everything
class ShowAll ls where
showAll :: HList ls -> [Show]
instance ShowAll () where
showAll _ = []
instance (ShowAll xs, Show x) => ShowAll (x,xs)
showAll (HCons x xs) = (show x) : (showAll xs)
which I find ugly. A more clever approach would be to fake constraint kinds
class Constrained tag aType where
isConstained :: tag aType
data HListT tag ls where
HNilT :: HListT tag ()
HConsT :: x -> tag x -> HListT tag xs -> HListT tag (x,xs)
data Proxy (f :: * -> *) = Proxy
class ConstainedAll tag ls where
tagThem :: Proxy tag -> HList ls -> HListT tag ls
instance ConstainedAll tag () where
tagThem _ _ = HNilT
instance (ConstainedAll tag xs, Constrained tag x) => ConstainedAll tag (x,xs) where
tagThem p (HCons x xs) = HConsT x isConstained (tagThem p xs)
which you can then use like
data Showable x where Showable :: Show x => Showable x
instance Show x => Constrained Showable x where isConstained = Showable
--inferred type showAll' :: HListT Showable xs -> [String]
showAll' HNilT = []
showAll' (HConsT x Showable xs) = (show x) : showAll' xs
--inferred type: showAll :: ConstainedAll Showable xs => HList xs -> [String]
showAll xs = showAll' (tagThem (Proxy :: Proxy Showable) xs)
example = showAll (HCons "hello" (HCons () HNil))
which should (havent tested) work with any GHC with GADTs, MPTC, Flexible Contexts/Instances, and Kind Signatures (you can get rid of the last one easily).
EDIT: In GHC 7.6+ you should use
type family ConstrainAll (c :: k -> Constraint) (ls :: [k]) :: Constraint
(k instead of the *) and turn on PolyKinds, but this won't work with the GHC 7.4 implementation of PolyKinds (hence the monomorphic code). In the same way, defining
data HList f ls where
HNil :: HList f '[]
HCons :: !(f x) -> !(HList f xs) -> HList f (x ': xs)
lets you avoid code duplication when you want things like a lazy vs strict HLists or when you want a list of dictionaries, or universal variants of higher kinded types, etc.

Resources