type-combinators-0.2.4.3: A collection of data types for type-level programming

CopyrightCopyright (C) 2015 Kyle Carter
LicenseBSD3
MaintainerKyle Carter <kylcarte@indiana.edu>
Stabilityexperimental
PortabilityRankNTypes
Safe HaskellNone
LanguageHaskell2010

Type.Family.Tuple

Description

Type-level pairs and triples, along with some convenient aliases and type families over them.

Documentation

type (#) = (,) infixr 6 Source #

type family Fst (p :: (k, l)) :: k where ... Source #

Equations

Fst '(a, b) = a 

fstCong :: (p ~ q) :- (Fst p ~ Fst q) Source #

type family Snd (p :: (k, l)) :: l where ... Source #

Equations

Snd '(a, b) = b 

sndCong :: (p ~ q) :- (Snd p ~ Snd q) Source #

type family Fst3 (p :: (k, l, m)) :: k where ... Source #

Equations

Fst3 '(a, b, c) = a 

fst3Cong :: (p ~ q) :- (Fst3 p ~ Fst3 q) Source #

type family Snd3 (p :: (k, l, m)) :: l where ... Source #

Equations

Snd3 '(a, b, c) = b 

snd3Cong :: (p ~ q) :- (Snd3 p ~ Snd3 q) Source #

type family Thd3 (p :: (k, l, m)) :: m where ... Source #

Equations

Thd3 '(a, b, c) = c 

thd3Cong :: (p ~ q) :- (Thd3 p ~ Thd3 q) Source #

type family (f :: k -> l) <$> (a :: (m, k)) :: (m, l) where ... infixr 4 Source #

Equations

f <$> (a # b) = a # f b 

pairMapCong :: (f ~ g, a ~ b) :- ((f <$> a) ~ (g <$> b)) Source #

type family (f :: (m, k -> l)) <&> (a :: k) :: (m, l) where ... infixr 4 Source #

Equations

(r # f) <&> a = r # f a 

type family (f :: (m, k -> l)) <*> (a :: (m, k)) :: (m, l) where ... infixr 4 Source #

Equations

(r # f) <*> (s # a) = (r <> s) # f a