quantification-0.2: Rage against the quantification

Safe HaskellNone
LanguageHaskell2010

Data.Exists

Contents

Description

Data types and type classes for working with existentially quantified values. In the event that Quantified Class Constraints ever land in GHC, this package will be considered obsolete. The benefit that most of the typeclasses in this module provide is that they help populate the instances of Exists.

Synopsis

Data Types

data Exists f Source #

Hide a type parameter.

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 # 
FromJSONExists k f => FromJSON (Exists k f) Source # 

Methods

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

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

(FromJSONKeyExists k f, FromJSONExists 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) 

Instances

EqForallPoly2 j k f => Eq (Exists2 j k f) Source # 

Methods

(==) :: Exists2 j k f -> Exists2 j k f -> Bool #

(/=) :: Exists2 j k f -> Exists2 j k f -> Bool #

ShowForall2 j k f => Show (Exists2 j k f) Source # 

Methods

showsPrec :: Int -> Exists2 j k f -> ShowS #

show :: Exists2 j k f -> String #

showList :: [Exists2 j k f] -> ShowS #

data Exists3 f Source #

Constructors

Exists3 !(f a b c) 

Type Classes

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 #

(EqForall k f, EqForall k g) => EqForall k (Sum k f g) Source # 

Methods

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

(EqForall k f, EqForall k g) => EqForall k (Product k f g) Source # 

Methods

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

(Eq1 f, EqForall k g) => EqForall k (Compose k * f g) Source # 

Methods

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

EqForall k f => EqForall [k] (Rec k f) Source # 

Methods

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

class EqForall f => EqForallPoly f where Source #

Methods

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

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

Instances

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

Methods

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

(EqForallPoly k f, EqForallPoly k g) => EqForallPoly k (Product k f g) Source # 

Methods

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

(Eq1 f, EqForallPoly k g) => EqForallPoly k (Compose k * f g) Source # 

Methods

eqForallPoly :: f a -> f b -> 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 #

(OrdForall k f, OrdForall k g) => OrdForall k (Sum k f g) Source # 

Methods

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

(OrdForall k f, OrdForall k g) => OrdForall k (Product k f g) Source # 

Methods

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

OrdForall k f => OrdForall [k] (Rec k f) Source # 

Methods

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

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

Methods

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

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

Instances

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

Methods

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

(OrdForallPoly k f, OrdForallPoly k g) => OrdForallPoly k (Product k f g) 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 #

(ShowForall k f, ShowForall k g) => ShowForall k (Product k f g) Source # 

Methods

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

(Show1 f, ShowForall k g) => ShowForall k (Compose k * f g) Source # 

Methods

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

ShowForall k f => ShowForall [k] (Rec k f) Source # 

Methods

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

class ReadForall f where Source #

Minimal complete definition

readPrecForall

Instances

class EnumForall f where Source #

Minimal complete definition

toEnumForall, fromEnumForall

class BoundedForall f where Source #

Minimal complete definition

minBoundForall, maxBoundForall

class SemigroupForall f where Source #

Minimal complete definition

sappendForall

Methods

sappendForall :: f a -> f a -> f a Source #

Instances

SemigroupForall k (Proxy k) Source # 

Methods

sappendForall :: f a -> f a -> f a Source #

SemigroupForall k f => SemigroupForall [k] (Rec k f) Source # 

Methods

sappendForall :: f a -> f a -> f a Source #

class SemigroupForall f => MonoidForall f where Source #

Minimal complete definition

memptyForall

Methods

memptyForall :: Sing a -> f a Source #

Instances

MonoidForall k f => MonoidForall [k] (Rec k f) Source # 

Methods

memptyForall :: Sing (Rec k f) a -> f a 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 #

HashableForall k f => HashableForall [k] (Rec k f) Source # 

Methods

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

class FromJSONForall f where Source #

Minimal complete definition

parseJSONForall

Methods

parseJSONForall :: Sing a -> Value -> Parser (f a) Source #

Instances

FromJSONForall k f => FromJSONForall [k] (Rec k f) Source # 

Methods

parseJSONForall :: Sing (Rec k f) a -> Value -> Parser (f a) Source #

class FromJSONExists f where Source #

Minimal complete definition

parseJSONExists

Instances

class ToJSONForall f where Source #

Minimal complete definition

toJSONForall

Methods

toJSONForall :: f a -> Value Source #

Instances

ToJSONForall k f => ToJSONForall [k] (Rec k f) Source # 

Methods

toJSONForall :: f a -> Value Source #

class ToJSONKeyForall f where Source #

Minimal complete definition

toJSONKeyForall

Methods

toJSONKeyForall :: ToJSONKeyFunctionForall f Source #

class FromJSONKeyExists f where Source #

Minimal complete definition

fromJSONKeyExists

class StorableForall f where Source #

Methods

peekForall :: Sing a -> Ptr (f a) -> IO (f a) Source #

pokeForall :: Ptr (f a) -> f a -> IO () Source #

sizeOfFunctorForall :: f a -> Int Source #

sizeOfForall :: forall a. Proxy f -> Sing a -> Int Source #

Instances

StorableForall k f => StorableForall [k] (Rec k f) Source # 

Methods

peekForall :: Sing (Rec k f) a -> Ptr (f a) -> IO (f a) Source #

pokeForall :: Ptr (f a) -> f a -> IO () Source #

sizeOfFunctorForall :: f a -> Int Source #

sizeOfForall :: Proxy (Rec k f -> *) f -> Sing (Rec k f) a -> Int Source #

Higher Rank Classes

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 ShowForall2 f where Source #

Minimal complete definition

showsPrecForall2

Methods

showsPrecForall2 :: Int -> f a b -> ShowS Source #

More Type Classes

type family Sing = (r :: k -> *) | r -> k Source #

Instances

type Sing [k] Source # 
type Sing [k] = SingList k

data SingList :: [k] -> * where Source #

Constructors

SingListNil :: SingList '[] 
SingListCons :: Sing r -> SingList rs -> SingList (r ': rs) 

class Reify a where Source #

Minimal complete definition

reify

Methods

reify :: Sing a Source #

Instances

Reify [k] ([] k) Source # 

Methods

reify :: Sing [k] a Source #

(Reify a a1, Reify [a] as) => Reify [a] ((:) a a1 as) Source # 

Methods

reify :: Sing ((a ': a1) as) a Source #

class Unreify k where Source #

Minimal complete definition

unreify

Methods

unreify :: forall a b. Sing a -> (Reify a => b) -> b Source #

Functions

Show

Defaulting

Other

unreifyList :: forall as b. Unreify k => SingList as -> (Reify as => b) -> b Source #