quantification-0.5.1: Rage against the quantification

Safe HaskellNone
LanguageHaskell2010

Data.Exists

Contents

Description

Data types and type classes for working with existentially quantified values. When Quantified Class Constraints land in GHC 8.6, the BarForall classes will be considered obsolete. When Dependent Haskell lands, the BarForeach classes will also be obsolete. The benefit that most of the typeclasses in this module provide is that they help populate the instances of Exists and Rec.

Synopsis

Data Types

data Exists (f :: k -> Type) Source #

Hide a type parameter.

Constructors

Exists !(f a) 
Instances
BoundedExists f => Bounded (Exists f) Source # 
Instance details

Defined in Data.Exists

Methods

minBound :: Exists f #

maxBound :: Exists f #

EnumExists f => Enum (Exists f) Source # 
Instance details

Defined in Data.Exists

Methods

succ :: Exists f -> Exists f #

pred :: Exists f -> Exists f #

toEnum :: Int -> Exists f #

fromEnum :: Exists f -> Int #

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

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

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

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

EqForallPoly f => Eq (Exists f) Source # 
Instance details

Defined in Data.Exists

Methods

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

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

OrdForallPoly f => Ord (Exists f) Source # 
Instance details

Defined in Data.Exists

Methods

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

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

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

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

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

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

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

ReadExists f => Read (Exists f) Source # 
Instance details

Defined in Data.Exists

ShowForall f => Show (Exists f) Source # 
Instance details

Defined in Data.Exists

Methods

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

show :: Exists f -> String #

showList :: [Exists f] -> ShowS #

HashableForall f => Hashable (Exists f) Source # 
Instance details

Defined in Data.Exists

Methods

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

hash :: Exists f -> Int #

ToJSONForall f => ToJSON (Exists f) Source # 
Instance details

Defined in Data.Exists

(ToJSONKeyForall f, ToJSONForall f) => ToJSONKey (Exists f) Source # 
Instance details

Defined in Data.Exists

FromJSONExists f => FromJSON (Exists f) Source # 
Instance details

Defined in Data.Exists

(FromJSONKeyExists f, FromJSONExists f) => FromJSONKey (Exists f) Source # 
Instance details

Defined in Data.Exists

BinaryExists f => Binary (Exists f) Source # 
Instance details

Defined in Data.Exists

Methods

put :: Exists f -> Put #

get :: Get (Exists f) #

putList :: [Exists f] -> Put #

PathPieceExists f => PathPiece (Exists f) Source # 
Instance details

Defined in Data.Exists

data Exists2 (f :: k -> j -> Type) Source #

Hide two type parameters.

Constructors

Exists2 !(f a b) 
Instances
EqForallPoly2 f => Eq (Exists2 f) Source # 
Instance details

Defined in Data.Exists

Methods

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

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

ShowForall2 f => Show (Exists2 f) Source # 
Instance details

Defined in Data.Exists

Methods

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

show :: Exists2 f -> String #

showList :: [Exists2 f] -> ShowS #

BinaryExists2 f => Binary (Exists2 f) Source # 
Instance details

Defined in Data.Exists

Methods

put :: Exists2 f -> Put #

get :: Get (Exists2 f) #

putList :: [Exists2 f] -> Put #

data Exists3 (f :: k -> j -> l -> Type) Source #

Hide three type parameters.

Constructors

Exists3 !(f a b c) 

data Some (f :: k -> Type) Source #

A dependent pair in which the first element is a singleton.

Constructors

Some !(Sing a) !(f a) 
Instances
(EqForeach f, EqSing k) => Eq (Some f) Source # 
Instance details

Defined in Data.Exists

Methods

(==) :: Some f -> Some f -> Bool #

(/=) :: Some f -> Some f -> Bool #

(OrdForeach f, OrdSing k) => Ord (Some f) Source # 
Instance details

Defined in Data.Exists

Methods

compare :: Some f -> Some f -> Ordering #

(<) :: Some f -> Some f -> Bool #

(<=) :: Some f -> Some f -> Bool #

(>) :: Some f -> Some f -> Bool #

(>=) :: Some f -> Some f -> Bool #

max :: Some f -> Some f -> Some f #

min :: Some f -> Some f -> Some f #

(ShowForeach f, ShowSing k) => Show (Some f) Source # 
Instance details

Defined in Data.Exists

Methods

showsPrec :: Int -> Some f -> ShowS #

show :: Some f -> String #

showList :: [Some f] -> ShowS #

(ToJSONForeach f, ToJSONSing k) => ToJSON (Some f) Source # 
Instance details

Defined in Data.Exists

(FromJSONForeach f, FromJSONSing k) => FromJSON (Some f) Source # 
Instance details

Defined in Data.Exists

data DependentPair (f :: k -> Type) (g :: k -> Type) Source #

A pair in which the type of the second element can only be discovered by looking at the first element. The type instance does not enforce this, but all of its typeclass instances make this assumption.

Constructors

DependentPair (f a) (g a) 
Instances
(EqForallPoly f, ToSing f, EqForeach g) => Eq (DependentPair f g) Source # 
Instance details

Defined in Data.Exists

Methods

(==) :: DependentPair f g -> DependentPair f g -> Bool #

(/=) :: DependentPair f g -> DependentPair f g -> Bool #

(OrdForallPoly f, ToSing f, OrdForeach g) => Ord (DependentPair f g) Source # 
Instance details

Defined in Data.Exists

(ShowForall f, ToSing f, ShowForeach g) => Show (DependentPair f g) Source # 
Instance details

Defined in Data.Exists

newtype ApplyForall f a Source #

Constructors

ApplyForall 

Fields

Instances
MonoidForall f => MonoidForall (ApplyForall f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

SemigroupForall f => SemigroupForall (ApplyForall f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

ShowForall f => Show (ApplyForall f a) Source # 
Instance details

Defined in Data.Exists

Methods

showsPrec :: Int -> ApplyForall f a -> ShowS #

show :: ApplyForall f a -> String #

showList :: [ApplyForall f a] -> ShowS #

SemigroupForall f => Semigroup (ApplyForall f a) Source # 
Instance details

Defined in Data.Exists

Methods

(<>) :: ApplyForall f a -> ApplyForall f a -> ApplyForall f a #

sconcat :: NonEmpty (ApplyForall f a) -> ApplyForall f a #

stimes :: Integral b => b -> ApplyForall f a -> ApplyForall f a #

MonoidForall f => Monoid (ApplyForall f a) Source # 
Instance details

Defined in Data.Exists

Methods

mempty :: ApplyForall f a #

mappend :: ApplyForall f a -> ApplyForall f a -> ApplyForall f a #

mconcat :: [ApplyForall f a] -> ApplyForall f a #

newtype ApplyForeach f a Source #

This is useful for recovering an instance of a typeclass when we have the pi-quantified variant and a singleton in scope.

Constructors

ApplyForeach 

Fields

Instances
MonoidForeach f => MonoidForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

SemigroupForeach f => SemigroupForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

FromJSONForeach f => FromJSONForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

ToJSONForeach f => ToJSONForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

FromJSONKeyForeach f => FromJSONKeyForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

ToJSONKeyForeach f => ToJSONKeyForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

OrdForeach f => OrdForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

EqForeach f => EqForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

eqForeach :: Sing a -> ApplyForeach f a -> ApplyForeach f a -> Bool Source #

(EqForeach f, Reify a) => Eq (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

Methods

(==) :: ApplyForeach f a -> ApplyForeach f a -> Bool #

(/=) :: ApplyForeach f a -> ApplyForeach f a -> Bool #

(OrdForeach f, Reify a) => Ord (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

(ShowForeach f, Reify a) => Show (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

(SemigroupForeach f, Reify a) => Semigroup (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

Methods

(<>) :: ApplyForeach f a -> ApplyForeach f a -> ApplyForeach f a #

sconcat :: NonEmpty (ApplyForeach f a) -> ApplyForeach f a #

stimes :: Integral b => b -> ApplyForeach f a -> ApplyForeach f a #

(MonoidForeach f, Reify a) => Monoid (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

(ToJSONForeach f, Reify a) => ToJSON (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

(ToJSONKeyForeach f, Reify a) => ToJSONKey (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

(FromJSONForeach f, Reify a) => FromJSON (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

(FromJSONKeyForeach f, Reify a) => FromJSONKey (ApplyForeach f a) Source # 
Instance details

Defined in Data.Exists

newtype ApplyLifted f a Source #

Constructors

ApplyLifted 

Fields

Instances
Eq1 f => Eq1 (ApplyLifted f) Source # 
Instance details

Defined in Data.Exists

Methods

liftEq :: (a -> b -> Bool) -> ApplyLifted f a -> ApplyLifted f b -> Bool #

Ord1 f => Ord1 (ApplyLifted f) Source # 
Instance details

Defined in Data.Exists

Methods

liftCompare :: (a -> b -> Ordering) -> ApplyLifted f a -> ApplyLifted f b -> Ordering #

Monoid1 f => Monoid1 (ApplyLifted f) Source # 
Instance details

Defined in Data.Exists

Methods

liftEmpty :: a -> ApplyLifted f a Source #

Semigroup1 f => Semigroup1 (ApplyLifted f) Source # 
Instance details

Defined in Data.Exists

Methods

liftAppend :: (a -> a -> a) -> ApplyLifted f a -> ApplyLifted f a -> ApplyLifted f a Source #

(Eq1 f, Eq a) => Eq (ApplyLifted f a) Source # 
Instance details

Defined in Data.Exists

Methods

(==) :: ApplyLifted f a -> ApplyLifted f a -> Bool #

(/=) :: ApplyLifted f a -> ApplyLifted f a -> Bool #

(Ord1 f, Ord a) => Ord (ApplyLifted f a) Source # 
Instance details

Defined in Data.Exists

Methods

compare :: ApplyLifted f a -> ApplyLifted f a -> Ordering #

(<) :: ApplyLifted f a -> ApplyLifted f a -> Bool #

(<=) :: ApplyLifted f a -> ApplyLifted f a -> Bool #

(>) :: ApplyLifted f a -> ApplyLifted f a -> Bool #

(>=) :: ApplyLifted f a -> ApplyLifted f a -> Bool #

max :: ApplyLifted f a -> ApplyLifted f a -> ApplyLifted f a #

min :: ApplyLifted f a -> ApplyLifted f a -> ApplyLifted f a #

(Semigroup1 f, Semigroup a) => Semigroup (ApplyLifted f a) Source # 
Instance details

Defined in Data.Exists

Methods

(<>) :: ApplyLifted f a -> ApplyLifted f a -> ApplyLifted f a #

sconcat :: NonEmpty (ApplyLifted f a) -> ApplyLifted f a #

stimes :: Integral b => b -> ApplyLifted f a -> ApplyLifted f a #

(Monoid1 f, Monoid a) => Monoid (ApplyLifted f a) Source # 
Instance details

Defined in Data.Exists

Methods

mempty :: ApplyLifted f a #

mappend :: ApplyLifted f a -> ApplyLifted f a -> ApplyLifted f a #

mconcat :: [ApplyLifted f a] -> ApplyLifted f a #

Type Classes

class EqForall f where Source #

Methods

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

Instances
EqForall (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

Eq a => EqForall (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

eqForall :: Const a a0 -> Const a a0 -> Bool Source #

EqForall ((:~:) a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

eqForall :: (a :~: a0) -> (a :~: a0) -> Bool Source #

EqHetero h => EqForall (HFix h :: k -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

eqForall :: HFix h a -> HFix h a -> Bool Source #

(EqForall f, EqForall g) => EqForall (Sum f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

(EqForall f, EqForall g) => EqForall (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

(Eq1 f, EqForall g) => EqForall (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

EqForall (SingList :: [k] -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

EqForall f => EqForall (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

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

class EqForall f => EqForallPoly f where Source #

Minimal complete definition

Nothing

Methods

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

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

Instances
(EqForallPoly f, EqForallPoly g) => EqForallPoly (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

eqForallPoly :: Product f g a -> Product f g b -> WitnessedEquality a b Source #

EqSing k => EqForallPoly (SingList :: [k] -> Type) Source # 
Instance details

Defined in Data.Exists

EqForallPoly f => EqForallPoly (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

eqForallPoly :: Rec f a -> Rec f b -> WitnessedEquality a b Source #

class EqForeach f where Source #

Variant of EqForall that requires a pi-quantified type.

Methods

eqForeach :: Sing a -> f a -> f a -> Bool Source #

Instances
EqForeach f => EqForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

eqForeach :: Sing a -> ApplyForeach f a -> ApplyForeach f a -> Bool Source #

(Eq1 f, EqForeach g) => EqForeach (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

eqForeach :: Sing a -> Compose f g a -> Compose f g a -> Bool Source #

EqForeach f => EqForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

eqForeach :: Sing a -> Rec f a -> Rec f a -> Bool Source #

class EqForall f => OrdForall f where Source #

Methods

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

Instances
OrdForall (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Ord a => OrdForall (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

compareForall :: Const a a0 -> Const a a0 -> Ordering Source #

(OrdForall f, OrdForall g) => OrdForall (Sum f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

(OrdForall f, OrdForall g) => OrdForall (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

OrdForall f => OrdForall (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

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

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

Methods

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

Instances
(OrdForallPoly f, OrdForallPoly g) => OrdForallPoly (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

compareForallPoly :: Product f g a -> Product f g b -> WitnessedOrdering a b Source #

class EqForeach f => OrdForeach f where Source #

Variant of OrdForall that requires a pi-quantified type.

Methods

compareForeach :: Sing a -> f a -> f a -> Ordering Source #

Instances
OrdForeach f => OrdForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

(Ord1 f, OrdForeach g) => OrdForeach (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

compareForeach :: Sing a -> Compose f g a -> Compose f g a -> Ordering Source #

OrdForeach f => OrdForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

compareForeach :: Sing a -> Rec f a -> Rec f a -> Ordering Source #

class ShowForall f where Source #

Methods

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

Instances
ShowForall (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Show a => ShowForall (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

showsPrecForall :: Int -> Const a a0 -> ShowS Source #

(ShowForall f, ShowForall g) => ShowForall (Product f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

(Show1 f, ShowForall g) => ShowForall (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

ShowForall f => ShowForall (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

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

class ShowForeach f where Source #

Methods

showsPrecForeach :: Sing a -> Int -> f a -> ShowS Source #

Instances
(Show1 f, ShowForeach g) => ShowForeach (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

showsPrecForeach :: Sing a -> Int -> Compose f g a -> ShowS Source #

ShowForeach f => ShowForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

showsPrecForeach :: Sing a -> Int -> Rec f a -> ShowS Source #

class ReadExists f where Source #

Instances
ReadExists (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.Exists

class EnumForall f where Source #

Methods

toEnumForall :: Int -> f a Source #

fromEnumForall :: f a -> Int Source #

class SemigroupForall f where Source #

Methods

appendForall :: f a -> f a -> f a Source #

Instances
SemigroupForall (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

appendForall :: Proxy a -> Proxy a -> Proxy a Source #

Semigroup a => SemigroupForall (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

appendForall :: Const a a0 -> Const a a0 -> Const a a0 Source #

SemigroupForall f => SemigroupForall (ApplyForall f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

(Semigroup1 f, SemigroupForall g) => SemigroupForall (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

appendForall :: Compose f g a -> Compose f g a -> Compose f g a Source #

SemigroupForall f => SemigroupForall (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

appendForall :: Rec f a -> Rec f a -> Rec f a Source #

class SemigroupForeach f where Source #

Methods

appendForeach :: Sing a -> f a -> f a -> f a Source #

Instances
SemigroupForeach f => SemigroupForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

(Semigroup1 f, SemigroupForeach g) => SemigroupForeach (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

appendForeach :: Sing a -> Compose f g a -> Compose f g a -> Compose f g a Source #

SemigroupForeach f => SemigroupForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

appendForeach :: Sing a -> Rec f a -> Rec f a -> Rec f a Source #

class SemigroupForall f => MonoidForall f where Source #

Methods

emptyForall :: f a Source #

Instances
Monoid a => MonoidForall (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

emptyForall :: Const a a0 Source #

MonoidForall f => MonoidForall (ApplyForall f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

class SemigroupForeach f => MonoidForeach f where Source #

Methods

emptyForeach :: Sing a -> f a Source #

Instances
MonoidForeach f => MonoidForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

MonoidForeach f => MonoidForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

emptyForeach :: Sing a -> Rec f a Source #

class HashableForall f where Source #

Methods

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

Instances
Hashable a => HashableForall (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

hashWithSaltForall :: Int -> Const a a0 -> Int Source #

HashableForall f => HashableForall (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

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

class HashableForeach f where Source #

Methods

hashWithSaltForeach :: Sing a -> Int -> f a -> Int Source #

class FromJSONForall f where Source #

Methods

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

Instances
(FromJSON1 f, FromJSONForall g) => FromJSONForall (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

class FromJSONForeach f where Source #

Methods

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

Instances
FromJSON a => FromJSONForeach (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

parseJSONForeach :: Sing a0 -> Value -> Parser (Const a a0) Source #

FromJSONForeach f => FromJSONForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

(FromJSON1 f, FromJSONForeach g) => FromJSONForeach (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

parseJSONForeach :: Sing a -> Value -> Parser (Compose f g a) Source #

FromJSONForeach f => FromJSONForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

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

class FromJSONExists f where Source #

Instances
FromJSONExists f => FromJSONExists (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

class ToJSONForall f where Source #

Methods

toJSONForall :: f a -> Value Source #

Instances
(ToJSON1 f, ToJSONForall g) => ToJSONForall (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

toJSONForall :: Compose f g a -> Value Source #

ToJSONForall f => ToJSONForall (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

toJSONForall :: Rec f a -> Value Source #

class ToJSONForeach f where Source #

Methods

toJSONForeach :: Sing a -> f a -> Value Source #

Instances
ToJSON a => ToJSONForeach (Const a :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

toJSONForeach :: Sing a0 -> Const a a0 -> Value Source #

ToJSONForeach f => ToJSONForeach (ApplyForeach f :: k -> Type) Source # 
Instance details

Defined in Data.Exists

(ToJSON1 f, ToJSONForeach g) => ToJSONForeach (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

toJSONForeach :: Sing a -> Compose f g a -> Value Source #

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) 

data FromJSONKeyFunctionForeach f Source #

Constructors

FromJSONKeyTextParserForeach !(forall a. Sing a -> Text -> Parser (f a)) 
FromJSONKeyValueForeach !(forall a. Sing a -> Value -> Parser (f a)) 

class StorableForeach (f :: k -> Type) where Source #

Methods

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

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

sizeOfForeach :: forall (a :: k). Proxy f -> Sing a -> Int Source #

Instances
StorableForeach f => StorableForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

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

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

sizeOfForeach :: Proxy (Rec f) -> Sing a -> Int Source #

class StorableForall (f :: k -> Type) where Source #

This is like StorableForall except that the type constructor must ignore its argument (for purposes of representation).

Methods

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

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

sizeOfForall :: Proxy f -> Int Source #

class PrimForall (f :: k -> Type) where Source #

Be careful with this typeclass. It is more unsafe than Prim. With writeByteArray# and readByteArray#, one can implement unsafeCoerce.

class BinaryExists (f :: k -> Type) where Source #

Instances
(SingKind k, Binary k) => BinaryExists (SingList :: [k] -> Type) Source # 
Instance details

Defined in Data.Exists

class BinaryForeach (f :: k -> Type) where Source #

Methods

putForeach :: Sing a -> f a -> Put Source #

getForeach :: Sing a -> Get (f a) Source #

Instances
(Binary1 f, BinaryForeach g) => BinaryForeach (Compose f g :: k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

putForeach :: Sing a -> Compose f g a -> Put Source #

getForeach :: Sing a -> Get (Compose f g a) Source #

BinaryForeach f => BinaryForeach (Rec f :: [k] -> Type) Source # 
Instance details

Defined in Topaz.Types

Methods

putForeach :: Sing a -> Rec f a -> Put Source #

getForeach :: Sing a -> Get (Rec f a) Source #

Higher Rank Classes

class EqForall2 f where Source #

Methods

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

Instances
EqForall2 ((:~:) :: k -> k -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

eqForall2 :: (a :~: b) -> (a :~: b) -> Bool Source #

class EqForallPoly2 (f :: k -> j -> Type) where Source #

Methods

eqForallPoly2 :: forall (a :: k) (b :: j) (c :: k) (d :: j). f a b -> f c d -> WitnessedEquality '(a, b) '(c, d) Source #

class ShowForall2 f where Source #

Methods

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

class ShowForeach2 f where Source #

Methods

showsPrecForeach2 :: Sing a -> Sing b -> Int -> f a b -> ShowS Source #

class BinaryExists2 (f :: k -> j -> Type) where Source #

More Type Classes

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

Instances
type Sing Source # 
Instance details

Defined in Topaz.Types

type Sing = SingNat
type Sing Source # 
Instance details

Defined in Data.Exists

type Sing = (SingList :: [k] -> Type)
type Sing Source # 
Instance details

Defined in Data.Exists

type Sing = (SingMaybe :: Maybe k -> Type)

data SingList :: forall (k :: Type). [k] -> Type where Source #

Constructors

SingListNil :: SingList '[] 
SingListCons :: Sing r -> SingList rs -> SingList (r ': rs) 
Instances
(SingKind k, Binary k) => BinaryExists (SingList :: [k] -> Type) Source # 
Instance details

Defined in Data.Exists

EqSing k => EqForallPoly (SingList :: [k] -> Type) Source # 
Instance details

Defined in Data.Exists

EqForall (SingList :: [k] -> Type) Source # 
Instance details

Defined in Data.Exists

Methods

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

ShowSing k => Show (SingList xs) Source # 
Instance details

Defined in Data.Exists

Methods

showsPrec :: Int -> SingList xs -> ShowS #

show :: SingList xs -> String #

showList :: [SingList xs] -> ShowS #

data SingMaybe :: Maybe k -> Type where Source #

class Reify a where Source #

Methods

reify :: Sing a Source #

Instances
Reify ([] :: [k]) Source # 
Instance details

Defined in Data.Exists

Methods

reify :: Sing [] Source #

Reify (Nothing :: Maybe a) Source # 
Instance details

Defined in Data.Exists

Reify a2 => Reify (Just a2 :: Maybe a1) Source # 
Instance details

Defined in Data.Exists

Methods

reify :: Sing (Just a2) Source #

(Reify a2, Reify as) => Reify (a2 ': as :: [a1]) Source # 
Instance details

Defined in Data.Exists

Methods

reify :: Sing (a2 ': as) Source #

class Unreify k where Source #

Methods

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

Instances
Unreify k => Unreify [k] Source # 
Instance details

Defined in Data.Exists

Methods

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

Sing Type Classes

class EqSing k where Source #

Methods

eqSing :: forall (a :: k) (b :: k). Sing a -> Sing b -> Maybe (a :~: b) Source #

Instances
EqSing a => EqSing [a] Source # 
Instance details

Defined in Data.Exists

Methods

eqSing :: Sing a0 -> Sing b -> Maybe (a0 :~: b) Source #

class EqSing k => OrdSing k where Source #

Methods

compareSing :: forall (a :: k) (b :: k). Sing a -> Sing b -> WitnessedOrdering a b Source #

class ShowSing k where Source #

Methods

showsPrecSing :: forall (a :: k). Int -> Sing a -> ShowS Source #

Instances
ShowSing k => ShowSing [k] Source # 
Instance details

Defined in Data.Exists

Methods

showsPrecSing :: Int -> Sing a -> ShowS Source #

class ToJSONSing k where Source #

Methods

toJSONSing :: forall (a :: k). Sing a -> Value Source #

class FromJSONSing k where Source #

Methods

parseJSONSing :: Value -> Parser (Exists (Sing :: k -> Type)) Source #

class ToSing (f :: k -> Type) where Source #

Methods

toSing :: f a -> Sing a Source #

class SingKind k where Source #

The two functions must form an isomorphism.

Methods

demoteSing :: Sing (a :: k) -> k Source #

promoteSing :: k -> Exists (Sing :: k -> Type) Source #

Instances
SingKind k => SingKind [k] Source # 
Instance details

Defined in Data.Exists

Methods

demoteSing :: Sing a -> [k] Source #

promoteSing :: [k] -> Exists Sing Source #

Functions

Show

Defaulting

parseJSONMapForeachKey :: forall k (f :: k -> Type) (a :: k) v. (FromJSONKeyForeach f, OrdForeach f, Unreify k) => (Value -> Parser v) -> Sing a -> Value -> Parser (Map (f a) v) Source #

Parse a Map whose key type is higher-kinded. This only creates a valid Map if the OrdForeach instance agrees with the Ord instance.

Weakening

strengthenOrdering :: Ordering -> WitnessedOrdering a a Source #

Given that we already know two types are equal, promote an Ordering.

strengthenUnequalOrdering :: Ordering -> WitnessedOrdering a b Source #

Given that we already know two types to be unequal, promote an Ordering. The argument should not be EQ.

Other

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