fcf-containers-0.8.2: Data structures and algorithms for first-class-families
Copyright(c) gspia 2020-
LicenseBSD
Maintainergspia
Safe HaskellSafe-Inferred
LanguageHaskell2010

Fcf.Data.Tuple

Description

Fcf.Data.Tuple

Synopsis
  • data Swap :: (a, b) -> Exp (b, a)
  • data Tuple2 :: a -> b -> Exp (a, b)
  • data Tuple3 :: a -> b -> c -> Exp (a, b, c)
  • data Tuple4 :: a -> b -> c -> d -> Exp (a, b, c, d)
  • data Tuple5 :: a -> b -> c -> d -> e -> Exp (a, b, c, d, e)

Documentation

>>> import qualified GHC.TypeLits as TL

data Swap :: (a, b) -> Exp (b, a) Source #

Swap

Example

Expand
>>> :kind! Eval (Swap '(1, 2))
Eval (Swap '(1, 2)) :: (TL.Natural, TL.Natural)
= '(2, 1)

Instances

Instances details
type Eval (Swap '(a, b) :: (k1, k2) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tuple

type Eval (Swap '(a, b) :: (k1, k2) -> Type) = '(b, a)

data Tuple2 :: a -> b -> Exp (a, b) Source #

2-tuple to allow for partial application of 2-tuple at the type level

Instances

Instances details
type Eval (Tuple2 a b :: (k1, k2) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tuple

type Eval (Tuple2 a b :: (k1, k2) -> Type) = '(a, b)

data Tuple3 :: a -> b -> c -> Exp (a, b, c) Source #

3-tuple to allow for partial application of 3-tuple at the type level

Instances

Instances details
type Eval (Tuple3 a b c :: (k1, k2, k3) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tuple

type Eval (Tuple3 a b c :: (k1, k2, k3) -> Type) = '(a, b, c)

data Tuple4 :: a -> b -> c -> d -> Exp (a, b, c, d) Source #

4-tuple to allow for partial application of 4-tuple at the type level

Instances

Instances details
type Eval (Tuple4 a b c d :: (k1, k2, k3, k4) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tuple

type Eval (Tuple4 a b c d :: (k1, k2, k3, k4) -> Type) = '(a, b, c, d)

data Tuple5 :: a -> b -> c -> d -> e -> Exp (a, b, c, d, e) Source #

5-tuple to allow for partial application of 4-tuple at the type level

Instances

Instances details
type Eval (Tuple5 a b c d e :: (k1, k2, k3, k4, k5) -> Type) Source # 
Instance details

Defined in Fcf.Data.Tuple

type Eval (Tuple5 a b c d e :: (k1, k2, k3, k4, k5) -> Type) = '(a, b, c, d, e)