Portability | see LANGUAGE pragmas (... GHC) |
---|---|
Stability | experimental |
Maintainer | nicolas.frisby@gmail.com |
Type.Yoko.Type
Description
Some fundamental types central to yoko
.
- qK :: QuasiQuoter
- data Proxy p = Proxy
- type family Med m a
- data IdM = IdM
- class Wrapper f where
- type family Unwrap f a
- type family Pred p a
- newtype (f :. g) a = Compose (f (g a))
- composeWith :: Proxy (KTSS g) -> f (g a) -> (f :. g) a
- module Type.Spine.Stage0
- module Type.Booleans
- type IsEQ t = OrdCase t False True False
- type Compare l r = SpineCompare (KS l) (KS r)
- class EqT f where
- data a :=: b where
Documentation
qK :: QuasiQuoter
[qK|...|]
is the a type that takes one parameter of the corresponding
kind. (The name is an encoding of that parameter's kind based on prefix
notation for application.)
The Wrapper
class is used to make term-level programming newtypes a
little more lightweight from the user perspective.
Composition of * -> *
types.
Constructors
Compose (f (g a)) |
composeWith :: Proxy (KTSS g) -> f (g a) -> (f :. g) aSource
Explicitly takes the inner type as a proxy.
module Type.Spine.Stage0
module Type.Booleans
type Compare l r = SpineCompare (KS l) (KS r)
class EqT f where
A type class for constructing equality proofs. This is as close
as we can get to decidable equality on types. Note that f
must be
a GADT to be able to define eqT
.
data a :=: b where
Type equality. A value of a :=: b
is a proof that types a
and
b
are equal. By pattern matching on Refl
this fact is
introduced to the type checker.
Instances
Category :=: | |
a ~ b => b ::: (:=: a) | |
EqT (:=: a) | |
Read (:=: a a) | We can only read values if the result is |
Show (:=: a b) | Any value is just shown as Refl, but this cannot be derived for a GADT, so it is defined here manually. |