Safe Haskell | None |
---|---|
Language | Haskell2010 |
Utils for type lists
Synopsis
- type family Snoc (xs :: [k]) (x :: k) :: [k] where ...
- type family Concat (xs :: [k]) (ys :: [k]) :: [k] where ...
- type family Replicate (n :: Nat) (s :: k) :: [k] where ...
- type family Zip (l :: [*]) (l2 :: [*]) where ...
- type family RemoveAt (n :: Nat) (l :: [k]) :: [k] where ...
- type family RemoveAt1 (n :: Nat) (l :: [k]) :: [k] where ...
- type family RemoveAtN (ns :: [Nat]) (l :: [k]) :: [k] where ...
- type family Remove (a :: k) (l :: [k]) :: [k] where ...
- type family Nub (l :: [k]) :: [k] where ...
- type family NubHead (l :: [k]) :: [k] where ...
- type family Head (xs :: [k]) :: k where ...
- type family Last (xs :: [k]) :: k where ...
- type family Tail (xs :: [k]) :: [k] where ...
- type family Init (xs :: [k]) :: [k] where ...
- type family Take (n :: Nat) (xs :: [k]) :: [k] where ...
- type family Drop (n :: Nat) (xs :: [k]) :: [k] where ...
- type family InsertAt (n :: Nat) (l :: [k]) (l2 :: [k]) :: [k] where ...
- type family ReplaceAt (n :: Nat) (l :: [k]) (l2 :: [k]) :: [k] where ...
- type family Replace (t1 :: k) (t2 :: k) (l :: [k]) :: [k] where ...
- type family ReplaceN (n :: Nat) (t :: k) (l :: [k]) :: [k] where ...
- type family ReplaceNS (ns :: [Nat]) (t :: k) (l :: [k]) :: [k] where ...
- type family Subset (t :: b) (f :: b) (xs :: [a]) (ys :: [a]) :: b where ...
- type family SetEq (t :: b) (f :: b) (xs :: [a]) (ys :: [a]) :: b where ...
- type family CheckMember (a :: k) (l :: [k]) :: Constraint where ...
- type family CheckMembers (l1 :: [k]) (l2 :: [k]) :: Constraint where ...
- type family Union (xs :: [k]) (ys :: [k]) :: [k] where ...
- type family Complement (xs :: [k]) (ys :: [k]) :: [k] where ...
- type family Product (xs :: [*]) (ys :: [*]) :: [*] where ...
- type family Member x xs :: Constraint where ...
- type family Members xs ys :: Constraint where ...
- type CheckNub (l :: [k]) = CheckNubEx l (Nub l) ~ True
- type IndexOf (x :: k) (xs :: [k]) = IndexOf' (MaybeIndexOf x xs) x xs
- type family IndexesOf (a :: k) (l :: [k]) :: [Nat] where ...
- type family MaybeIndexOf (a :: k) (l :: [k]) where ...
- type Index (n :: Nat) (l :: [k]) = Index' n l l
- type family Elem (t :: b) (f :: b) (x :: k) (xs :: [k]) :: b where ...
- type family MapElem (t :: b) (f :: b) (xs :: [a]) (ys :: [a]) :: [b] where ...
- type family Reverse (l :: [k]) :: [k] where ...
- type family Generate (n :: Nat) (m :: Nat) :: [Nat] where ...
- type family Map (f :: a -> k) (xs :: [a]) :: [k] where ...
- type family ListMax (xs :: [Nat]) where ...
- type family ListMin (xs :: [Nat]) where ...
- type family Length (xs :: [k]) :: Nat where ...
- type family Indexes (l :: [k]) :: [Nat] where ...
- type family MapTest (a :: k) (l :: [k]) :: [Nat] where ...
Construction
type family Replicate (n :: Nat) (s :: k) :: [k] where ... Source #
Replicate
Replicate n s = Replicate' s n '[] |
Removal
type family RemoveAt1 (n :: Nat) (l :: [k]) :: [k] where ... Source #
Remove a type at index (0 == don't remove)
type family RemoveAtN (ns :: [Nat]) (l :: [k]) :: [k] where ... Source #
Remove types at several indexes
Sublist
Insert/replace
type family ReplaceAt (n :: Nat) (l :: [k]) (l2 :: [k]) :: [k] where ... Source #
replace l[n] with l2 (folded)
type family Replace (t1 :: k) (t2 :: k) (l :: [k]) :: [k] where ... Source #
replace a type by another in l
type family ReplaceN (n :: Nat) (t :: k) (l :: [k]) :: [k] where ... Source #
replace a type at offset n in l
type family ReplaceNS (ns :: [Nat]) (t :: k) (l :: [k]) :: [k] where ... Source #
replace types at offsets ns in l
Set operations
type family CheckMember (a :: k) (l :: [k]) :: Constraint where ... Source #
Check that a type is member of a type list
CheckMember a l = CheckMember' (MaybeIndexOf a l) a l |
type family CheckMembers (l1 :: [k]) (l2 :: [k]) :: Constraint where ... Source #
Check that a list is a subset of another
CheckMembers '[] l1 = () | |
CheckMembers (x ': xs) l2 = CheckMembers' (MaybeIndexOf x l2) x xs (x ': xs) l2 |
type family Complement (xs :: [k]) (ys :: [k]) :: [k] where ... Source #
Complement xs ys
Complement xs '[] = xs | |
Complement xs (y ': ys) = Complement (Remove y xs) ys |
type family Member x xs :: Constraint where ... Source #
Constraint: x member of xs
type family Members xs ys :: Constraint where ... Source #
Constraint: all the xs are members of ys
type CheckNub (l :: [k]) = CheckNubEx l (Nub l) ~ True Source #
Check that a list only contain a value of each type
Index operations
type IndexOf (x :: k) (xs :: [k]) = IndexOf' (MaybeIndexOf x xs) x xs Source #
Get the first index of a type
type family IndexesOf (a :: k) (l :: [k]) :: [Nat] where ... Source #
Get all the indexes of a type
IndexesOf x xs = IndexesOf' 0 x xs |
type family MaybeIndexOf (a :: k) (l :: [k]) where ... Source #
Get the first index (starting from 1) of a type or 0 if none
MaybeIndexOf x xs = MaybeIndexOf' 0 x xs |
type family MapElem (t :: b) (f :: b) (xs :: [a]) (ys :: [a]) :: [b] where ... Source #
MapElem t f xs ys = Map (x -> Elem t f x ys) xs
Nat list
type family Generate (n :: Nat) (m :: Nat) :: [Nat] where ... Source #
Generate a list of Nat [n..m-1]
Others
type family ListMax (xs :: [Nat]) where ... Source #
Get the max of a list of Nats
ListMax (x ': xs) = Max' x xs |
type family ListMin (xs :: [Nat]) where ... Source #
Get the min of a list of Nats
ListMin (x ': xs) = Min' x xs |