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 #-}
Related
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]
Consider following definition of a HList:
infixr 5 :>
data HList (types :: [*]) where
HNil :: HList '[]
(:>) :: a -> HList l -> HList (a:l)
And a type family Map to map over typelevel lists:
type family Map (f :: * -> *) (xs :: [*]) where
Map f '[] = '[]
Map f (x ': xs) = (f x) ': xs
Now I would like to define sequence equivalence for HLists. My attempt looks like
hSequence :: Applicative m => HList (Map m ins) -> m (HList ins)
hSequence HNil = pure HNil
hSequence (x :> rest) = (:>) <$> x <*> hSequence rest
But I get errors like this:
Could not deduce: ins ~ '[]
from the context: Map m ins ~ '[]
bound by a pattern with constructor: HNil :: HList '[]
For me it looks like the compiler isn't sure that if Map m returns [] on some list then the list is empty. Sadly, I don't see any way to convince it to that fact. What should I do in this situation?
I am using GHC 8.6.5 with following extensions:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
First, there's an error here:
type family Map (f :: * -> *) (xs :: [*]) where
Map f '[] = '[]
Map f (x ': xs) = (f x) ': Map f xs
--^^^^^-- we need this
After that is fixed, the issue here is that we need to proceed by induction on ins, not on Map f ins. To achieve that, we need a singleton type:
data SList :: [*] -> * where
SNil :: SList '[]
SCons :: SList zs -> SList ( z ': zs )
and then an additional argument:
hSequence :: Applicative m => SList ins -> HList (Map m ins) -> m (HList ins)
hSequence SNil HNil = pure HNil
hSequence (SCons ins') (x :> rest) = (:>) <$> x <*> hSequence ins' rest
This now compiles. Matching on SNil / SCons refines ins to either '[] or z ': zs, so Map m ins can be unfolded one step as well. This allows us to make the recursive call.
As usual, we can remove the additional singleton argument through a suitable typeclass. I'm reasonably sure that some of this can be automated exploiting the singletons library.
class SingList ins where
singList :: SList ins
instance SingList '[] where
singList = SNil
instance SingList zs => SingList (z ': zs) where
singList = SCons singList
hSequence2 :: (Applicative m, SingList ins)
=> HList (Map m ins) -> m (HList ins)
hSequence2 = hSequence singList
This GADT preserves the spine ("length") of type level lists past type erasure:
data Spine (xs :: [k]) :: Type where
NilSpine :: Spine '[]
ConsSpine :: Spine xs -> Spine (x : xs)
From this, we can prove these lemmas:
mapNil' :: forall f xs. Map f xs ~ '[] => Spine xs -> xs :~: '[]
mapNil' NilSpine = Refl
type family Head (xs :: [k]) :: k where Head (x : _) = x
type family Tail (xs :: [k]) :: [k] where Tail (_ : xs) = xs
data MapCons f y ys xs =
forall x xs'. (xs ~ (x : xs'), y ~ f x, ys ~ Map f xs') => MapCons
mapCons' :: forall f xs y ys. Map f xs ~ (y : ys) => Spine xs -> MapCons f y ys xs
mapCons' (ConsSpine _) = MapCons
Now, Spine is a singleton family: Spine xs has exactly one value for each xs. We can therefore erase it.
mapNil :: forall f xs. Map f xs ~ '[] => xs :~: '[]
mapNil = unsafeCoerce Refl -- safe because mapNil' exists
mapCons :: forall f xs y ys. Map f xs ~ (y : ys) => MapCons f y ys xs
mapCons = unsafeCoerce MapCons -- safe because mapCons' exists
These lemmas can then be used to define your function:
hSequence :: forall m ins. Applicative m => HList (Map m ins) -> m (HList ins)
hSequence HNil | Refl <- mapNil #m #ins = pure HNil
hSequence (x :> rest) | MapCons <- mapCons #m #ins = (:>) <$> x <*> hSequence rest
By starting with Spine, we can build a justification for why our logic works. Then, we can erase all the singleton junk we don't need at runtime. This is an extension of how we use types to build a justification for why our programs work, and then we erase them for the runtime. It's important to write mapNil' and mapCons' so we know what we're doing works.
HList is quite an unwieldy type. I recommend using something like this one instead, which is similar to one from vinyl.
{-# language PolyKinds, DataKinds, GADTs, ScopedTypeVariables, RankNTypes, TypeOperators #-}
import Data.Kind
import Control.Applicative
infixr 4 :>
-- Type is the modern spelling of the * kind
data Rec :: [k] -> (k -> Type) -> Type
where
Nil :: Rec '[] f
(:>) :: f a -> Rec as f -> Rec (a ': as) f
htraverse
:: forall (xs :: [k]) (f :: k -> Type) (g :: k -> Type) m.
Applicative m
=> (forall t. f t -> m (g t))
-> Rec xs f -> m (Rec xs g)
htraverse _f Nil = pure Nil
htraverse f (x :> xs) =
liftA2 (:>) (f x) (htraverse f xs)
If you like, you can define
hsequence
:: forall (xs :: [k]) (g :: k -> Type) m.
Applicative m
=> Rec xs (Compose m g) -> m (Rec xs g)
hsequence = htraverse getCompose
Note that
HList xs ~= Rec xs Identity
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.
I'm trying to write a type family I can use to constrain the elements of a type level list. I have this code:
{-# LANGUAGE PolyKinds, DataKinds, TypeOperators, TypeFamilies #-}
import GHC.TypeLits (KnownSymbol, symbolVal)
import GHC.Exts (Constraint)
import Data.Proxy (Proxy(..))
type family AllHave (c :: k -> Constraint) (xs :: [k]) :: Constraint
type instance AllHave c '[] = ()
type instance AllHave c (x ': xs) = (c x, AllHave c xs)
type family Head (xs :: [k]) :: k where
Head (x ': xs) = x
headProxy :: proxy xs -> Proxy (Head xs)
headProxy _ = Proxy
test :: AllHave KnownSymbol xs => proxy xs -> String
test p = symbolVal (headProxy p)
main :: IO ()
main = putStrLn $ test (Proxy :: Proxy '["a", "b"])
From what I understand this should work, but when I compile ghc spits out this:
Test.hs:18:10:
Could not deduce (KnownSymbol (Head xs))
arising from a use of ‘symbolVal’
from the context (AllHave KnownSymbol xs)
bound by the type signature for
test :: AllHave KnownSymbol xs => proxy xs -> String
at Test.hs:17:9-52
In the expression: symbolVal (headProxy p)
In an equation for ‘test’: test p = symbolVal (headProxy p)
The problem here is that Head does not reduce when fed xs in test so Haskell has no way to deduce KnownSymbol (Head xs) from AllHave KnownSymbol xs. And it shouldn't: what should happen in case xs is empty?
To solve this problem, you can make it explicit that xs is not empty like so:
test :: AllHave KnownSymbol (x ': xs) => proxy (x ': xs) -> String
I don't know much about type families, so I'll point you to gallais's answer for an explanation of what went wrong in your code. Here is a very different approach, with a number of demo functions. There might be better ways; I don't know.
data CList :: (k -> Constraint) -> [k] -> * where
CNil :: CList c '[]
CCons :: c t => proxy t -> CList c ts -> CList c (t ': ts)
mapCSimple :: (forall a . c a => Proxy a -> b) -> CList c as -> [b]
mapCSimple f CNil = []
mapCSimple f (CCons (t :: proxy t) ts) = f (Proxy :: Proxy t) : mapCSimple f ts
toStrings :: CList KnownSymbol v -> [String]
toStrings = mapCSimple symbolVal
class KnownSymbols (xs :: [Symbol]) where
known :: proxy xs -> CList KnownSymbol xs
instance KnownSymbols '[] where
known _ = CNil
instance (KnownSymbol x, KnownSymbols xs) => KnownSymbols (x ': xs) where
known _ = CCons Proxy $ known Proxy
exampleG :: KnownSymbols xs => proxy xs -> String
exampleG p = show . toStrings $ known p
This gives
> putStrLn $ exampleG (Proxy :: Proxy '["Hello", "Darkness"])
["Hello","Darkness"]
To get something more like what you sought,
cHead :: CList c (a ': as) -> Dict (c a)
cHead (CCons prox _) = Dict
test :: forall x xs . CList KnownSymbol (x ': xs) -> String
test xs = case cHead xs of Dict -> symbolVal (Proxy :: Proxy x)
test2 :: (KnownSymbols xs, xs ~ (y ': ys)) => proxy xs -> String
test2 prox = test (known prox)
This gets
> putStrLn $ test2 (Proxy :: Proxy '["Hello", "Darkness"])
Hello
And here's another fun function:
data HList :: (k -> *) -> [k] -> * where
HNil :: HList f '[]
HCons :: f a -> HList f as -> HList f (a ': as)
mapC :: (forall a . c a => Proxy a -> f a) -> CList c as -> HList f as
mapC f CNil = HNil
mapC f (CCons (t :: proxy t) ts) = HCons (f (Proxy :: Proxy t)) (mapC f ts)
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.