Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Synopsis
- data DSum tag f = !(tag a) :=> (f a)
- (==>) :: Applicative f => tag a -> a -> DSum tag f
- type ShowTag tag f = (GShow tag, Has' Show tag f)
- showTaggedPrec :: forall tag f a. (GShow tag, Has' Show tag f) => tag a -> Int -> f a -> ShowS
- type ReadTag tag f = (GRead tag, Has' Read tag f)
- readTaggedPrec :: forall tag f a. (GRead tag, Has' Read tag f) => tag a -> Int -> ReadS (f a)
- type EqTag tag f = (GEq tag, Has' Eq tag f)
- eqTaggedPrec :: forall tag f a. (GEq tag, Has' Eq tag f) => tag a -> tag a -> f a -> f a -> Bool
- type OrdTag tag f = (GCompare tag, Has' Ord tag f)
- compareTaggedPrec :: forall tag f a. (GCompare tag, Has' Ord tag f) => tag a -> tag a -> f a -> f a -> Ordering
Documentation
A basic dependent sum type; the first component is a tag that specifies the type of the second; for example, think of a GADT such as:
data Tag a where AString :: Tag String AnInt :: Tag Int
Then, we have the following valid expressions of type Applicative f => DSum Tag f
:
AString ==> "hello!" AnInt ==> 42
And we can write functions that consume DSum Tag f
values by matching,
such as:
toString :: DSum Tag Identity -> String toString (AString :=> Identity str) = str toString (AnInt :=> Identity int) = show int
By analogy to the (key => value) construction for dictionary entries in
many dynamic languages, we use (key :=> value) as the constructor for
dependent sums. The :=> and ==> operators have very low precedence and
bind to the right, so if the Tag
GADT is extended with an additional
constructor Rec :: Tag (DSum Tag Identity)
, then Rec ==> AnInt ==> 3 + 4
is parsed as would be expected (Rec ==> (AnInt ==> (3 + 4))
) and has type
DSum Identity Tag
. Its precedence is just above that of $
, so
foo bar $ AString ==> "eep"
is equivalent to foo bar (AString ==> "eep")
.
!(tag a) :=> (f a) infixr 1 |
Instances
(GEq tag, Has' Eq tag f) => Eq (DSum tag f) Source # | |
(GCompare tag, Has' Eq tag f, Has' Ord tag f) => Ord (DSum tag f) Source # | |
(GRead tag, Has' Read tag f) => Read (DSum tag f) Source # | |
(GShow tag, Has' Show tag f) => Show (DSum tag f) Source # | |
(==>) :: Applicative f => tag a -> a -> DSum tag f infixr 1 Source #
type ShowTag tag f = (GShow tag, Has' Show tag f) Source #
Deprecated: Instead of 'ShowTag tag f', use '(GShow tag, Has' Show tag f)'
showTaggedPrec :: forall tag f a. (GShow tag, Has' Show tag f) => tag a -> Int -> f a -> ShowS Source #
type ReadTag tag f = (GRead tag, Has' Read tag f) Source #
Deprecated: Instead of 'ReadTag tag f', use '(GRead tag, Has' Read tag f)'
readTaggedPrec :: forall tag f a. (GRead tag, Has' Read tag f) => tag a -> Int -> ReadS (f a) Source #
type EqTag tag f = (GEq tag, Has' Eq tag f) Source #
Deprecated: Instead of 'EqTag tag f', use '(GEq tag, Has' Eq tag f)'
eqTaggedPrec :: forall tag f a. (GEq tag, Has' Eq tag f) => tag a -> tag a -> f a -> f a -> Bool Source #