Safe Haskell | Safe |
---|
- data DSum tag = forall a . !(tag a) :=> a
- class GShow tag => ShowTag tag where
- showTaggedPrec :: tag a -> Int -> a -> ShowS
- class GRead tag => ReadTag tag where
- readTaggedPrec :: tag a -> Int -> ReadS a
- class GEq tag => EqTag tag where
- class (EqTag tag, GCompare tag) => OrdTag tag where
- compareTagged :: tag a -> tag a -> a -> 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 DSum Tag
:
AString :=> "hello!" AnInt :=> 42
And we can write functions that consume DSum Tag
values by matching,
such as:
toString :: DSum Tag -> String toString (AString :=> str) = str toString (AnInt :=> 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 :=> operator has very low precedence and binds to
the right, so if the Tag
GADT is extended with an additional constructor
Rec :: Tag (DSum Tag)
, then Rec :=> AnInt :=> 3 + 4
is parsed as
would be expected (Rec :=> (AnInt :=> (3 + 4))
) and has type DSum Tag
.
Its precedence is just above that of $
, so foo bar $ AString :=> eep
is equivalent to foo bar (AString :=> eep)
.
forall a . !(tag a) :=> a |
class GShow tag => ShowTag tag whereSource
In order to make a Show
instance for DSum tag
, tag
must be able
to show itself as well as any value of the tagged type. GShow
together
with this class provides the interface by which it can do so.
ShowTag tag => t
is conceptually equivalent to something like this
imaginary syntax: (forall a. Inhabited (tag a) => Show a) => t
,
where Inhabited
is an imaginary predicate that characterizes
non-empty types, and a
does not occur free in t
.
The Tag
example type introduced in the DSum
section could be given the
following instances:
instance GShow Tag where gshowsPrec _p AString = showString "AString" gshowsPrec _p AnInt = showString "AnInt" instance ShowTag Tag where showTaggedPrec AString = showsPrec showTaggedPrec AnInt = showsPrec
showTaggedPrec :: tag a -> Int -> a -> ShowSSource
Given a value of type tag a
, return the showsPrec
function for
the type parameter a
.
class GRead tag => ReadTag tag whereSource
readTaggedPrec :: tag a -> Int -> ReadS aSource
Read a => ReadTag (:= a) | In order to make a
The instance GRead Tag where greadsPrec _p str = case tag of "AString" -> [(\k -> k AString, rest)] "AnInt" -> [(\k -> k AnInt, rest)] _ -> [] where (tag, rest) = break isSpace str instance ReadTag Tag where readTaggedPrec AString = readsPrec readTaggedPrec AnInt = readsPrec |
class GEq tag => EqTag tag whereSource
In order to test DSum tag
for equality, tag
must know how to test
both itself and its tagged values for equality. EqTag
defines
the interface by which they are expected to do so.
Continuing the Tag
example from the DSum
section, we can define:
instance GEq Tag where geq AString AString = Just Refl geq AnInt AnInt = Just Refl geq _ _ = Nothing instance EqTag Tag where eqTagged AString AString = (==) eqTagged AnInt AnInt = (==)
Note that eqTagged
is not called until after the tags have been
compared, so it only needs to consider the cases where gcompare
returns GEQ
.
class (EqTag tag, GCompare tag) => OrdTag tag whereSource
In order to compare DSum tag
values, tag
must know how to compare
both itself and its tagged values. OrdTag
defines the
interface by which they are expected to do so.
Continuing the Tag
example from the EqTag
section, we can define:
instance GCompare Tag where gcompare AString AString = GEQ gcompare AString AnInt = GLT gcompare AnInt AString = GGT gcompare AnInt AnInt = GEQ instance OrdTag Tag where compareTagged AString AString = compare compareTagged AnInt AnInt = compare
As with eqTagged
, compareTagged
only needs to consider cases where
gcompare
returns GEQ
.
compareTagged :: tag a -> tag a -> a -> a -> OrderingSource