Copyright | (c) 2018-2021 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Experimental |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Contains useful utilities to work with Types.
Since: 0.4.0
Synopsis
- typeName :: forall a. Typeable a => Text
- type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ...
- type family AllHave (f :: k -> Constraint) (xs :: [k]) :: Constraint where ...
- type family Elem (e :: t) (es :: [t]) :: Bool where ...
- type family Fst (t :: k) :: k' where ...
- type family Snd (t :: k) :: k' where ...
Documentation
typeName :: forall a. Typeable a => Text Source #
Gets a string representation of a type.
NOTE: This must be used with TypeApplications language extension.
>>>
typeName @()
"()">>>
typeName @Int
"Int">>>
typeName @String
"[Char]">>>
typeName @(Maybe Int)
"Maybe Int"
Since: 0.4.0
type family (xs :: [k]) ++ (ys :: [k]) :: [k] where ... infixr 5 Source #
Concatenates type-level lists.
>>>
:kind! '[ 'Just 5, 'Nothing] ++ '[ 'Just 3, 'Nothing, 'Just 1]
'[ 'Just 5, 'Nothing] ++ '[ 'Just 3, 'Nothing, 'Just 1] :: [Maybe Nat] = '[ 'Just 5, 'Nothing, 'Just 3, 'Nothing, 'Just 1]
>>>
:kind! '[] ++ '[ 'Just 3, 'Nothing, 'Just 1]
'[] ++ '[ 'Just 3, 'Nothing, 'Just 1] :: [Maybe Nat] = '[ 'Just 3, 'Nothing, 'Just 1]
Since: 0.6.0.0
type family AllHave (f :: k -> Constraint) (xs :: [k]) :: Constraint where ... Source #
Builds combined Constraint
by applying Constraint constructor to all
elements of type-level list.
>>>
:kind! AllHave Show '[Int, Text, Double]
AllHave Show '[Int, Text, Double] :: Constraint = (Show Int, (Show Text, (Show Double, () :: Constraint)))
which is equivalent to:
(Show Int, Show Text, Show Double) :: Constraint
Since: 0.6.0.0
type family Elem (e :: t) (es :: [t]) :: Bool where ... Source #
Check that a type is an element of a list:
>>>
:kind! Elem String '[]
Elem String '[] :: Bool = 'False
>>>
:kind! Elem String '[Int, String]
Elem String '[Int, String] :: Bool = 'True
>>>
:kind! Elem String '[Int, Bool]
Elem String '[Int, Bool] :: Bool = 'False
Since: 0.6.0.0
type family Fst (t :: k) :: k' where ... Source #
Returns first element of tuple type (with kind *
) or type-level tuple
(with kind (k1, k2)
, marked by prefix quote).
>>>
:kind! Maybe (Fst '(Int, Text))
Maybe (Fst '(Int, Text)) :: * = Maybe Int
>>>
:kind! Maybe (Fst (Int, Text))
Maybe (Fst (Int, Text)) :: * = Maybe Int
Since: 0.6.0.0
type family Snd (t :: k) :: k' where ... Source #
Returns second element of tuple type (with kind *
) or type-level tuple
(with kind (k1, k2)
, marked by prefix quote).
>>>
:kind! Maybe (Snd '(Int, Text))
Maybe (Snd '(Int, Text)) :: * = Maybe Text>>>
:kind! Maybe (Snd (Int, Text))
Maybe (Snd (Int, Text)) :: * = Maybe Text
Since: 0.6.0.0