relude-1.2.1.0: Safe, performant, user-friendly and lightweight Haskell Standard Library
Copyright(c) 2018-2023 Kowainik
LicenseMIT
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellSafe
LanguageHaskell2010

Relude.Extra.Type

Description

Contains useful utilities to work with Types.

Since: 0.4.0

Synopsis

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
                                                              Natural]
= '[ 'Just 5, 'Nothing, 'Just 3, 'Nothing, 'Just 1]
>>> :kind! '[] ++ '[ 'Just 3, 'Nothing, 'Just 1]
'[] ++ '[ 'Just 3, 'Nothing, 'Just 1] :: [Maybe Natural]
= '[ 'Just 3, 'Nothing, 'Just 1]

# 91 "srcReludeExtra/Type.hs"

Since: 0.6.0.0

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

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

Equations

AllHave _ '[] = () 
AllHave f (x ': xs) = (f x, AllHave f xs) 

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

Equations

Elem _ '[] = 'False 
Elem x (x ': xs) = 'True 
Elem x (_ ': xs) = Elem x xs 

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

Equations

Fst '(x, _) = x 
Fst (x, _) = x 

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

Equations

Snd '(_, y) = y 
Snd (_, y) = y