Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
TypeLits related utilities.
Lots of this could be avoided by adding singletons
as dependency.
Uses symbols
library for its ToList type family.
Currently this is spread out in different modules
TODO these will need to get consolidated here
Synopsis
- type family AcceptEq (msg :: ErrorMessage) (c :: Ordering) :: Bool where ...
- type family And (b1 :: Bool) (b2 :: Bool) :: Bool where ...
- type family Or (b1 :: Bool) (b2 :: Bool) :: Bool where ...
- type family Repeat (n :: Nat) (s :: Symbol) :: Symbol where ...
- type family Fst (s :: (k, h)) :: k where ...
- type family Dupl (s :: k) :: (k, k) where ...
- type family Concat (s :: [Symbol]) :: Symbol where ...
- type family Drop (n :: Nat) (s :: Symbol) :: Symbol where ...
- type family LDrop (n :: Nat) (s :: [k]) :: [k] where ...
- type family Take (n :: Nat) (s :: Symbol) :: Symbol where ...
- type family LTake (n :: Nat) (s :: [k]) :: [k] where ...
- type family TakeUntil (s :: Symbol) (stop :: Symbol) :: Symbol where ...
- type family LTakeUntil (s :: [Symbol]) (stop :: Symbol) :: [Symbol] where ...
- type family LTakeUntilHelper (s :: [Symbol]) (o :: Ordering) :: [Symbol] where ...
- type family Length (s :: Symbol) :: Nat where ...
- type family LLengh (s :: [k]) :: Nat where ...
Documentation
>>>
:set -XScopedTypeVariables -XTypeFamilies -XKindSignatures -XDataKinds
type family Repeat (n :: Nat) (s :: Symbol) :: Symbol where ... Source #
Repeat 0 s = "" | |
Repeat n s = AppendSymbol s (Repeat (n - 1) s) |
type family Concat (s :: [Symbol]) :: Symbol where ... Source #
:kind! Concat (LDrop 6 (ToList "bool: "r-ban:ff-ff" | "r-ban:ffff""))
Concat '[] = "" | |
Concat (x ': xs) = AppendSymbol x (Concat xs) |
type family LDrop (n :: Nat) (s :: [k]) :: [k] where ... Source #
:kind! LDrop 6 (ToList "bool: "r-ban:ff-ff" | "r-ban:ffff"")
type family TakeUntil (s :: Symbol) (stop :: Symbol) :: Symbol where ... Source #
TakeUntil s stop = Concat (LTakeUntil (ToList s) stop) |
type family LTakeUntil (s :: [Symbol]) (stop :: Symbol) :: [Symbol] where ... Source #
LTakeUntil '[] _ = '[] | |
LTakeUntil (x ': xs) stop = LTakeUntilHelper (x ': LTakeUntil xs stop) (CmpSymbol x stop) |
type family LTakeUntilHelper (s :: [Symbol]) (o :: Ordering) :: [Symbol] where ... Source #
LTakeUntilHelper '[] _ = '[] | |
LTakeUntilHelper (x ': xs) EQ = '[] | |
LTakeUntilHelper (x ': xs) _ = x ': xs |