singletons-2.4.1: A framework for generating singleton types

Copyright(C) 2017 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (rae@cs.brynmawr.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Sigma

Description

Defines Sigma, a dependent pair data type, and related functions.

Synopsis

Documentation

data Sigma (s :: Type) :: (s ~> Type) -> Type where Source #

A dependent pair.

Constructors

(:&:) :: forall s t fst. Sing (fst :: s) -> (t @@ fst) -> Sigma s t infixr 4 

type Σ (s :: Type) (t :: s ~> Type) = Sigma s t Source #

Unicode shorthand for Sigma.

projSigma1 :: forall s t. SingKind s => Sigma s t -> Demote s Source #

Project the first element out of a dependent pair.

projSigma2 :: forall s t r. (forall (fst :: s). (t @@ fst) -> r) -> Sigma s t -> r Source #

Project the second element out of a dependent pair.

In an ideal setting, the type of projSigma2 would be closer to:

projSigma2 :: Sing (sig :: Sigma s t) -> t @@ ProjSigma1 sig

But promoting projSigma1 to a type family is not a simple task. Instead, we do the next-best thing, which is to use Church-style elimination.

mapSigma :: Sing (f :: a ~> b) -> (forall (x :: a). (p @@ x) -> q @@ (f @@ x)) -> Sigma a p -> Sigma b q Source #

Map across a Sigma value in a dependent fashion.

zipSigma :: Sing (f :: a ~> (b ~> c)) -> (forall (x :: a) (y :: b). (p @@ x) -> (q @@ y) -> r @@ ((f @@ x) @@ y)) -> Sigma a p -> Sigma b q -> Sigma c r Source #

Zip two Sigma values together in a dependent fashion.