1 {-# LANGUAGE AllowAmbiguousTypes #-}
3 {-# LANGUAGE PolyKinds #-}
4 {-# LANGUAGE UndecidableInstances #-}
5 -- | List utilities at the type-level.
6 module Language.Symantic.Typing.List where
8 import GHC.Exts (Constraint)
10 import Language.Symantic.Typing.Peano
13 -- | Return the position of a type within a list of them.
14 -- This is useful to work around @OverlappingInstances@.
15 type family Index xs x where
16 Index (x ': xs) x = Zero
17 Index (not_x ': xs) x = Succ (Index xs x)
19 -- * Type family @(++)@
20 type family (++) xs ys where
23 (x ': xs) ++ ys = x ': xs ++ ys
26 -- * Type family 'Concat'
27 type family Concat (xs::[[k]]) :: [k] where
29 Concat (x ': xs) = x ++ Concat xs
31 -- * Type family 'Concat_Constraints'
32 type family Concat_Constraints (cs::[Constraint]) :: Constraint where
33 Concat_Constraints '[] = ()
34 Concat_Constraints (c ': cs) = (c, Concat_Constraints cs)
36 -- * Type family 'DeleteAll'
37 type family DeleteAll (x::k) (xs::[k]) :: [k] where
39 DeleteAll x (x ': xs) = DeleteAll x xs
40 DeleteAll x (y ': xs) = y ': DeleteAll x xs
42 -- * Type family 'Head'
43 type family Head (xs::[k]) :: k where
46 -- * Type family 'Tail'
47 type family Tail (xs::[k]) :: [k] where
51 -- * Type family 'Map'
52 type family Map (f::a -> b) (cs::[a]) :: [b] where
54 Map f (c ': cs) = f c ': Map f cs
57 -- * Type family 'Nub'
58 type family Nub (xs::[k]) :: [k] where
60 Nub (x ': xs) = x ': Nub (DeleteAll x xs)
64 type family L (xs::[k]) :: Nat where
66 L (x ': xs) = 'S (L xs)
69 class Inj_L (as::[k]) where
71 instance Inj_L '[] where
73 instance Inj_L as => Inj_L (a ': as) where
74 inj_L = SNatS (inj_L @_ @as)
78 data Len (xs::[k]) where
80 LenS :: Len xs -> Len (x ': xs)
82 instance Show (Len vs) where
83 showsPrec _p = showsPrec 10 . intLen
85 addLen :: Len a -> Len b -> Len (a ++ b)
87 addLen (LenS a) b = LenS $ addLen a b
94 shiftLen LenZ b = LenS b
95 shiftLen (LenS a) (LenS b) = LenS $ shiftLen @t @b a b
97 intLen :: Len xs -> Int
100 go :: Int -> Len xs -> Int
102 go i (LenS l) = go (1 + i) l
104 -- ** Class 'Inj_Len'
105 class Inj_Len (vs::[k]) where
107 instance Inj_Len '[] where
109 instance Inj_Len as => Inj_Len (a ': as) where
110 inj_Len = LenS inj_Len