dependent-sum-0.4: Dependent sum type

Safe HaskellSafe
LanguageHaskell98

Data.GADT.Compare

Contents

Synopsis

Documentation

type (:=) = (:~:) Source #

Backwards compatibility alias; as of GHC 7.8, this is the same as `(:~:)`.

class GEq f where Source #

A class for type-contexts which contain enough information to (at least in some cases) decide the equality of types occurring within them.

Minimal complete definition

geq

Methods

geq :: f a -> f b -> Maybe (a := b) Source #

Produce a witness of type-equality, if one exists.

A handy idiom for using this would be to pattern-bind in the Maybe monad, eg.:

extract :: GEq tag => tag a -> DSum tag -> Maybe a
extract t1 (t2 :=> x) = do
    Refl <- geq t1 t2
    return x

Or in a list comprehension:

extractMany :: GEq tag => tag a -> [DSum tag] -> [a]
extractMany t1 things = [ x | (t2 :=> x) <- things, Refl <- maybeToList (geq t1 t2)]

(Making use of the DSum type from Data.Dependent.Sum in both examples)

Instances

GEq k ((:=) k a) Source # 

Methods

geq :: f a -> f b -> Maybe (((k := a) := a) b) Source #

defaultEq :: GEq f => f a -> f b -> Bool Source #

If f has a GEq instance, this function makes a suitable default implementation of '(==)'.

defaultNeq :: GEq f => f a -> f b -> Bool Source #

If f has a GEq instance, this function makes a suitable default implementation of '(/=)'.

data GOrdering a b where Source #

A type for the result of comparing GADT constructors; the type parameters of the GADT values being compared are included so that in the case where they are equal their parameter types can be unified.

Constructors

GLT :: GOrdering a b 
GEQ :: GOrdering t t 
GGT :: GOrdering a b 

Instances

GRead k (GOrdering k a) Source # 

Methods

greadsPrec :: Int -> GReadS (GOrdering k a) t Source #

GShow k (GOrdering k a) Source # 

Methods

gshowsPrec :: Int -> t a -> ShowS Source #

Show (f a) => ShowTag k (GOrdering k a) f Source # 

Methods

showTaggedPrec :: f a -> Int -> f a -> ShowS Source #

Eq (GOrdering k a b) Source # 

Methods

(==) :: GOrdering k a b -> GOrdering k a b -> Bool #

(/=) :: GOrdering k a b -> GOrdering k a b -> Bool #

Ord (GOrdering k a b) Source # 

Methods

compare :: GOrdering k a b -> GOrdering k a b -> Ordering #

(<) :: GOrdering k a b -> GOrdering k a b -> Bool #

(<=) :: GOrdering k a b -> GOrdering k a b -> Bool #

(>) :: GOrdering k a b -> GOrdering k a b -> Bool #

(>=) :: GOrdering k a b -> GOrdering k a b -> Bool #

max :: GOrdering k a b -> GOrdering k a b -> GOrdering k a b #

min :: GOrdering k a b -> GOrdering k a b -> GOrdering k a b #

Show (GOrdering k a b) Source # 

Methods

showsPrec :: Int -> GOrdering k a b -> ShowS #

show :: GOrdering k a b -> String #

showList :: [GOrdering k a b] -> ShowS #

weakenOrdering :: GOrdering a b -> Ordering Source #

TODO: Think of a better name

This operation forgets the phantom types of a GOrdering value.

class GEq f => GCompare f where Source #

Type class for comparable GADT-like structures. When 2 things are equal, must return a witness that their parameter types are equal as well (GEQ).

Minimal complete definition

gcompare

Methods

gcompare :: f a -> f b -> GOrdering a b Source #

Instances

GCompare k ((:=) k a) Source # 

Methods

gcompare :: f a -> f b -> GOrdering (k := a) a b Source #

defaultCompare :: GCompare f => f a -> f b -> Ordering Source #

data (k :~: a) b :: forall k. k -> k -> * where infix 4 #

Propositional equality. If a :~: b is inhabited by some terminating value, then the type a is the same as the type b. To use this equality in practice, pattern-match on the a :~: b to get out the Refl constructor; in the body of the pattern-match, the compiler knows that a ~ b.

Since: 4.7.0.0

Constructors

Refl :: (:~:) k a a 

Instances

TestEquality k ((:~:) k a) 

Methods

testEquality :: f a -> f b -> Maybe (((k :~: a) :~: a) b) #

GCompare k ((:=) k a) Source # 

Methods

gcompare :: f a -> f b -> GOrdering (k := a) a b Source #

GEq k ((:=) k a) Source # 

Methods

geq :: f a -> f b -> Maybe (((k := a) := a) b) Source #

Ord (f a) => OrdTag k ((:=) k a) f Source # 

Methods

compareTagged :: f a -> f a -> f a -> f a -> Ordering Source #

Eq (f a) => EqTag k ((:=) k a) f Source # 

Methods

eqTagged :: f a -> f a -> f a -> f a -> Bool Source #

Read (f a) => ReadTag k ((:=) k a) f Source #

In order to make a Read instance for DSum tag f, tag must be able to parse itself as well as any value of the tagged type. GRead together with this class provides the interface by which it can do so.

ReadTag tag f => t is conceptually equivalent to something like this imaginary syntax: (forall a. Inhabited (tag a) => Read (f a)) => t, where Inhabited is an imaginary predicate that characterizes non-empty types, and f and a do not occur free in t.

The Tag example type introduced in the DSum section could be given the following instances, among others:

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

Methods

readTaggedPrec :: f a -> Int -> ReadS (f a) Source #

Show (f a) => ShowTag k ((:=) k a) f Source # 

Methods

showTaggedPrec :: f a -> Int -> f a -> ShowS Source #

(~) k a b => Bounded ((:~:) k a b) 

Methods

minBound :: (k :~: a) b #

maxBound :: (k :~: a) b #

(~) k a b => Enum ((:~:) k a b) 

Methods

succ :: (k :~: a) b -> (k :~: a) b #

pred :: (k :~: a) b -> (k :~: a) b #

toEnum :: Int -> (k :~: a) b #

fromEnum :: (k :~: a) b -> Int #

enumFrom :: (k :~: a) b -> [(k :~: a) b] #

enumFromThen :: (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

enumFromTo :: (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

enumFromThenTo :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b -> [(k :~: a) b] #

Eq ((:~:) k a b) 

Methods

(==) :: (k :~: a) b -> (k :~: a) b -> Bool #

(/=) :: (k :~: a) b -> (k :~: a) b -> Bool #

Ord ((:~:) k a b) 

Methods

compare :: (k :~: a) b -> (k :~: a) b -> Ordering #

(<) :: (k :~: a) b -> (k :~: a) b -> Bool #

(<=) :: (k :~: a) b -> (k :~: a) b -> Bool #

(>) :: (k :~: a) b -> (k :~: a) b -> Bool #

(>=) :: (k :~: a) b -> (k :~: a) b -> Bool #

max :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b #

min :: (k :~: a) b -> (k :~: a) b -> (k :~: a) b #

(~) k a b => Read ((:~:) k a b) 

Methods

readsPrec :: Int -> ReadS ((k :~: a) b) #

readList :: ReadS [(k :~: a) b] #

readPrec :: ReadPrec ((k :~: a) b) #

readListPrec :: ReadPrec [(k :~: a) b] #

Show ((:~:) k a b) 

Methods

showsPrec :: Int -> (k :~: a) b -> ShowS #

show :: (k :~: a) b -> String #

showList :: [(k :~: a) b] -> ShowS #

Orphan instances

GRead k ((:=) k a) Source # 

Methods

greadsPrec :: Int -> GReadS (k := a) t Source #

GShow k ((:=) k a) Source # 

Methods

gshowsPrec :: Int -> t a -> ShowS Source #