Copyright | (C) 2017 Ryan Scott |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Richard Eisenberg (rae@cs.brynmawr.edu) |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Defines Sigma
, a dependent pair data type, and related functions.
Synopsis
- data Sigma (s :: Type) :: (s ~> Type) -> Type where
- type Σ (s :: Type) (t :: s ~> Type) = Sigma s t
- projSigma1 :: forall s t. SingKind s => Sigma s t -> Demote s
- projSigma2 :: forall s t r. (forall (fst :: s). (t @@ fst) -> r) -> Sigma s t -> r
- mapSigma :: Sing (f :: a ~> b) -> (forall (x :: a). (p @@ x) -> q @@ (f @@ x)) -> Sigma a p -> Sigma b q
- 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
Documentation
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.