quantification-0.1: Data types and typeclasses to deal with universally and existentially quantified types

Safe HaskellNone
LanguageHaskell2010

Data.Exists

Documentation

data Exists f Source #

Constructors

Exists !(f a) 

Instances

BoundedForall k f => Bounded (Exists k f) Source # 

Methods

minBound :: Exists k f #

maxBound :: Exists k f #

EnumForall k f => Enum (Exists k f) Source # 

Methods

succ :: Exists k f -> Exists k f #

pred :: Exists k f -> Exists k f #

toEnum :: Int -> Exists k f #

fromEnum :: Exists k f -> Int #

enumFrom :: Exists k f -> [Exists k f] #

enumFromThen :: Exists k f -> Exists k f -> [Exists k f] #

enumFromTo :: Exists k f -> Exists k f -> [Exists k f] #

enumFromThenTo :: Exists k f -> Exists k f -> Exists k f -> [Exists k f] #

EqForallPoly k f => Eq (Exists k f) Source # 

Methods

(==) :: Exists k f -> Exists k f -> Bool #

(/=) :: Exists k f -> Exists k f -> Bool #

OrdForallPoly k f => Ord (Exists k f) Source # 

Methods

compare :: Exists k f -> Exists k f -> Ordering #

(<) :: Exists k f -> Exists k f -> Bool #

(<=) :: Exists k f -> Exists k f -> Bool #

(>) :: Exists k f -> Exists k f -> Bool #

(>=) :: Exists k f -> Exists k f -> Bool #

max :: Exists k f -> Exists k f -> Exists k f #

min :: Exists k f -> Exists k f -> Exists k f #

ReadForall k f => Read (Exists k f) Source # 
ShowForall k f => Show (Exists k f) Source # 

Methods

showsPrec :: Int -> Exists k f -> ShowS #

show :: Exists k f -> String #

showList :: [Exists k f] -> ShowS #

HashableForall k f => Hashable (Exists k f) Source # 

Methods

hashWithSalt :: Int -> Exists k f -> Int #

hash :: Exists k f -> Int #

ToJSONForall k f => ToJSON (Exists k f) Source # 

Methods

toJSON :: Exists k f -> Value #

toEncoding :: Exists k f -> Encoding #

toJSONList :: [Exists k f] -> Value #

toEncodingList :: [Exists k f] -> Encoding #

(ToJSONKeyForall k f, ToJSONForall k f) => ToJSONKey (Exists k f) Source # 
FromJSONForall k f => FromJSON (Exists k f) Source # 

Methods

parseJSON :: Value -> Parser (Exists k f) #

parseJSONList :: Value -> Parser [Exists k f] #

(FromJSONKeyForall k f, FromJSONForall k f) => FromJSONKey (Exists k f) Source # 
PathPieceForall k f => PathPiece (Exists k f) Source # 

Methods

fromPathPiece :: Text -> Maybe (Exists k f) #

toPathPiece :: Exists k f -> Text #

data Exists2 f Source #

Constructors

Exists2 !(f a b) 

data Exists3 f Source #

Constructors

Exists3 !(f a b c) 

data ToJSONKeyFunctionForall f Source #

Constructors

ToJSONKeyTextForall !(forall a. f a -> Text) !(forall a. f a -> Encoding' Text) 
ToJSONKeyValueForall !(forall a. f a -> Value) !(forall a. f a -> Encoding) 

class EqForall f where Source #

Minimal complete definition

eqForall

Methods

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

Instances

EqForall k (Proxy k) Source # 

Methods

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

Eq a => EqForall k (Const k a) Source # 

Methods

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

EqForall k ((:~:) k a) Source # 

Methods

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

class EqForall f => OrdForall f where Source #

Minimal complete definition

compareForall

Methods

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

Instances

OrdForall k (Proxy k) Source # 

Methods

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

Ord a => OrdForall k (Const k a) Source # 

Methods

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

class EqForall f => EqForallPoly f where Source #

Minimal complete definition

eqForallPoly

Methods

eqForallPoly :: f a -> f b -> Bool Source #

Instances

Eq a => EqForallPoly k (Const k a) Source # 

Methods

eqForallPoly :: f a -> f b -> Bool Source #

class (OrdForall f, EqForallPoly f) => OrdForallPoly f where Source #

Minimal complete definition

compareForallPoly

Methods

compareForallPoly :: f a -> f b -> Ordering Source #

Instances

Ord a => OrdForallPoly k (Const k a) Source # 

Methods

compareForallPoly :: f a -> f b -> Ordering Source #

class ShowForall f where Source #

Minimal complete definition

showsPrecForall

Methods

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

Instances

ShowForall k (Proxy k) Source # 

Methods

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

class ReadForall f where Source #

Minimal complete definition

readPrecForall

Instances

class EqForall2 f where Source #

Minimal complete definition

eqForall2

Methods

eqForall2 :: f a b -> f a b -> Bool Source #

Instances

EqForall2 k k ((:~:) k) Source # 

Methods

eqForall2 :: f a b -> f a b -> Bool Source #

class EqForallPoly2 f where Source #

Minimal complete definition

eqForallPoly2

Methods

eqForallPoly2 :: f a b -> f c d -> Bool Source #

class HashableForall f where Source #

Minimal complete definition

hashWithSaltForall

Methods

hashWithSaltForall :: Int -> f a -> Int Source #

Instances

Hashable a => HashableForall k (Const k a) Source # 

Methods

hashWithSaltForall :: Int -> f a -> Int Source #

class ToJSONKeyForall f where Source #

Minimal complete definition

toJSONKeyForall

class FromJSONKeyForall f where Source #

Minimal complete definition

fromJSONKeyForall

class ToJSONForall f where Source #

Minimal complete definition

toJSONForall

Methods

toJSONForall :: f a -> Value Source #

class FromJSONForall f where Source #

Minimal complete definition

parseJSONForall

class EnumForall f where Source #

Minimal complete definition

toEnumForall, fromEnumForall

class BoundedForall f where Source #

Minimal complete definition

minBoundForall, maxBoundForall

class MonoidForall f where Source #

Minimal complete definition

memptyForall, mappendForall

Methods

memptyForall :: f a Source #

mappendForall :: f a -> f a -> f a Source #

Instances

MonoidForall k (Proxy k) Source # 

Methods

memptyForall :: f a Source #

mappendForall :: f a -> f a -> f a Source #