mu-schema-0.1.0.0: Format-independent schemas for serialization

Safe HaskellNone
LanguageHaskell2010

Mu.Schema.Interpretation

Contents

Description

This module defines Terms which comply with a given Schema. These Terms are the main form of values used internally by mu-haskell.

This module follows the ideas of higher-kinded data. In particular, each interpretation of a Field wraps its contents into a "wrapper" type w, which may add additional behavior to it. For example, in Protocol Buffers every field is optional, and this is expressed by setting w to Maybe.

In this module we make use of NP and NS as defined by sop-core. These are the n-ary versions of a pair and Either, respectively. In other words, NP puts together a bunch of values of different types, NS allows you to choose from a bunch of types.

Synopsis

Interpretation

data Term w (sch :: Schema typeName fieldName) (t :: TypeDef typeName fieldName) where Source #

Interpretation of a type in a schema.

Constructors

TRecord :: NP (Field w sch) args -> Term w sch (DRecord name args)

A record given by the value of its fields.

TEnum :: NS Proxy choices -> Term w sch (DEnum name choices)

An enumeration given by one choice.

TSimple :: FieldValue w sch t -> Term w sch (DSimple t)

A primitive value.

Instances
Eq (FieldValue w sch t) => Eq (Term w sch (DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Term w sch (DSimple t) -> Term w sch (DSimple t) -> Bool #

(/=) :: Term w sch (DSimple t) -> Term w sch (DSimple t) -> Bool #

All (Compose Eq (Proxy :: ChoiceDef fieldName -> Type)) choices => Eq (Term w sch (DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Term w sch (DEnum name choices) -> Term w sch (DEnum name choices) -> Bool #

(/=) :: Term w sch (DEnum name choices) -> Term w sch (DEnum name choices) -> Bool #

All (Compose Eq (Field w sch)) args => Eq (Term w sch (DRecord name args)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Term w sch (DRecord name args) -> Term w sch (DRecord name args) -> Bool #

(/=) :: Term w sch (DRecord name args) -> Term w sch (DRecord name args) -> Bool #

Show (FieldValue w sch t) => Show (Term w sch (DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Term w sch (DSimple t) -> ShowS #

show :: Term w sch (DSimple t) -> String #

showList :: [Term w sch (DSimple t)] -> ShowS #

(KnownName name, All (KnownName :: ChoiceDef fieldName -> Constraint) choices, All (Compose Show (Proxy :: ChoiceDef fieldName -> Type)) choices) => Show (Term w sch (DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Term w sch (DEnum name choices) -> ShowS #

show :: Term w sch (DEnum name choices) -> String #

showList :: [Term w sch (DEnum name choices)] -> ShowS #

(KnownName name, All (Compose Show (Field w sch)) args) => Show (Term w sch (DRecord name args)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Term w sch (DRecord name args) -> ShowS #

show :: Term w sch (DRecord name args) -> String #

showList :: [Term w sch (DRecord name args)] -> ShowS #

ToJSON (FieldValue w sch t) => ToJSON (Term w sch (DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: Term w sch (DSimple t) -> Value #

toEncoding :: Term w sch (DSimple t) -> Encoding #

toJSONList :: [Term w sch (DSimple t)] -> Value #

toEncodingList :: [Term w sch (DSimple t)] -> Encoding #

ToJSONFields sch args => ToJSON (Term Identity sch (DRecord name args)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: Term Identity sch (DRecord name args) -> Value #

toEncoding :: Term Identity sch (DRecord name args) -> Encoding #

toJSONList :: [Term Identity sch (DRecord name args)] -> Value #

toEncodingList :: [Term Identity sch (DRecord name args)] -> Encoding #

ToJSONEnum choices => ToJSON (Term w sch (DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: Term w sch (DEnum name choices) -> Value #

toEncoding :: Term w sch (DEnum name choices) -> Encoding #

toJSONList :: [Term w sch (DEnum name choices)] -> Value #

toEncodingList :: [Term w sch (DEnum name choices)] -> Encoding #

FromJSON (FieldValue w sch t) => FromJSON (Term w sch (DSimple t :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (Term w sch (DSimple t)) #

parseJSONList :: Value -> Parser [Term w sch (DSimple t)] #

FromJSONFields w sch args => FromJSON (Term w sch (DRecord name args)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (Term w sch (DRecord name args)) #

parseJSONList :: Value -> Parser [Term w sch (DRecord name args)] #

FromJSONEnum choices => FromJSON (Term w sch (DEnum name choices :: TypeDefB Type typeName fieldName)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (Term w sch (DEnum name choices)) #

parseJSONList :: Value -> Parser [Term w sch (DEnum name choices)] #

data Field w (sch :: Schema typeName fieldName) (f :: FieldDef typeName fieldName) where Source #

Interpretation of a field.

Constructors

Field :: w (FieldValue w sch t) -> Field w sch (FieldDef name t)

A single field. Note that the contents are wrapped in a w type constructor.

Instances
Eq (w (FieldValue w sch t)) => Eq (Field w sch (FieldDef name t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: Field w sch (FieldDef name t) -> Field w sch (FieldDef name t) -> Bool #

(/=) :: Field w sch (FieldDef name t) -> Field w sch (FieldDef name t) -> Bool #

(KnownName name, Show (w (FieldValue w sch t))) => Show (Field w sch (FieldDef name t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> Field w sch (FieldDef name t) -> ShowS #

show :: Field w sch (FieldDef name t) -> String #

showList :: [Field w sch (FieldDef name t)] -> ShowS #

data FieldValue w (sch :: Schema typeName fieldName) (t :: FieldType typeName) where Source #

Interpretation of a field type, by giving a value of that type.

Constructors

FNull :: FieldValue w sch TNull

Null value, as found in Avro and JSON.

FPrimitive :: t -> FieldValue w sch (TPrimitive t)

Value of a primitive type.

FSchematic :: Term w sch (sch :/: t) -> FieldValue w sch (TSchematic t)

Term of another type in the schema.

FOption :: Maybe (FieldValue w sch t) -> FieldValue w sch (TOption t)

Optional value.

FList :: [FieldValue w sch t] -> FieldValue w sch (TList t)

List of values.

FMap :: Ord (FieldValue w sch k) => Map (FieldValue w sch k) (FieldValue w sch v) -> FieldValue w sch (TMap k v)

Dictionary (key-value map) of values.

FUnion :: NS (FieldValue w sch) choices -> FieldValue w sch (TUnion choices)

One single value of one of the specified types.

Instances
All (Compose Eq (FieldValue w sch)) choices => Eq (FieldValue w sch (TUnion choices)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> Bool #

(/=) :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> Bool #

(Eq (FieldValue w sch k), Eq (FieldValue w sch v)) => Eq (FieldValue w sch (TMap k v)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> Bool #

(/=) :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> Bool #

Eq (FieldValue w sch t) => Eq (FieldValue w sch (TList t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> Bool #

(/=) :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> Bool #

Eq (FieldValue w sch t) => Eq (FieldValue w sch (TOption t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> Bool #

(/=) :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> Bool #

Eq (Term w sch (sch :/: t)) => Eq (FieldValue w sch (TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> Bool #

(/=) :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> Bool #

Eq t => Eq (FieldValue w sch (TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> Bool #

(/=) :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> Bool #

Eq (FieldValue w sch (TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

(==) :: FieldValue w sch TNull -> FieldValue w sch TNull -> Bool #

(/=) :: FieldValue w sch TNull -> FieldValue w sch TNull -> Bool #

(All (Compose Ord (FieldValue w sch)) choices, All (Compose Eq (FieldValue w sch)) choices) => Ord (FieldValue w sch (TUnion choices)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> Ordering #

(<) :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> Bool #

(<=) :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> Bool #

(>) :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> Bool #

(>=) :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> Bool #

max :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) #

min :: FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) -> FieldValue w sch (TUnion choices) #

(Ord (FieldValue w sch k), Ord (FieldValue w sch v)) => Ord (FieldValue w sch (TMap k v)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> Ordering #

(<) :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> Bool #

(<=) :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> Bool #

(>) :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> Bool #

(>=) :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> Bool #

max :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) #

min :: FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) -> FieldValue w sch (TMap k v) #

Ord (FieldValue w sch t) => Ord (FieldValue w sch (TList t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> Ordering #

(<) :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> Bool #

(<=) :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> Bool #

(>) :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> Bool #

(>=) :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> Bool #

max :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> FieldValue w sch (TList t) #

min :: FieldValue w sch (TList t) -> FieldValue w sch (TList t) -> FieldValue w sch (TList t) #

Ord (FieldValue w sch t) => Ord (FieldValue w sch (TOption t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> Ordering #

(<) :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> Bool #

(<=) :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> Bool #

(>) :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> Bool #

(>=) :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> Bool #

max :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) #

min :: FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) -> FieldValue w sch (TOption t) #

Ord (Term w sch (sch :/: t)) => Ord (FieldValue w sch (TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> Ordering #

(<) :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> Bool #

(<=) :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> Bool #

(>) :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> Bool #

(>=) :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> Bool #

max :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) #

min :: FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) -> FieldValue w sch (TSchematic t) #

Ord t => Ord (FieldValue w sch (TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> Ordering #

(<) :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> Bool #

(<=) :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> Bool #

(>) :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> Bool #

(>=) :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> Bool #

max :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) #

min :: FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) -> FieldValue w sch (TPrimitive t) #

Ord (FieldValue w sch (TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

compare :: FieldValue w sch TNull -> FieldValue w sch TNull -> Ordering #

(<) :: FieldValue w sch TNull -> FieldValue w sch TNull -> Bool #

(<=) :: FieldValue w sch TNull -> FieldValue w sch TNull -> Bool #

(>) :: FieldValue w sch TNull -> FieldValue w sch TNull -> Bool #

(>=) :: FieldValue w sch TNull -> FieldValue w sch TNull -> Bool #

max :: FieldValue w sch TNull -> FieldValue w sch TNull -> FieldValue w sch TNull #

min :: FieldValue w sch TNull -> FieldValue w sch TNull -> FieldValue w sch TNull #

All (Compose Show (FieldValue w sch)) choices => Show (FieldValue w sch (TUnion choices)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue w sch (TUnion choices) -> ShowS #

show :: FieldValue w sch (TUnion choices) -> String #

showList :: [FieldValue w sch (TUnion choices)] -> ShowS #

(Show (FieldValue w sch k), Show (FieldValue w sch v)) => Show (FieldValue w sch (TMap k v)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue w sch (TMap k v) -> ShowS #

show :: FieldValue w sch (TMap k v) -> String #

showList :: [FieldValue w sch (TMap k v)] -> ShowS #

Show (FieldValue w sch t) => Show (FieldValue w sch (TList t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue w sch (TList t) -> ShowS #

show :: FieldValue w sch (TList t) -> String #

showList :: [FieldValue w sch (TList t)] -> ShowS #

Show (FieldValue w sch t) => Show (FieldValue w sch (TOption t)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue w sch (TOption t) -> ShowS #

show :: FieldValue w sch (TOption t) -> String #

showList :: [FieldValue w sch (TOption t)] -> ShowS #

Show (Term w sch (sch :/: t)) => Show (FieldValue w sch (TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue w sch (TSchematic t) -> ShowS #

show :: FieldValue w sch (TSchematic t) -> String #

showList :: [FieldValue w sch (TSchematic t)] -> ShowS #

Show t => Show (FieldValue w sch (TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue w sch (TPrimitive t) -> ShowS #

show :: FieldValue w sch (TPrimitive t) -> String #

showList :: [FieldValue w sch (TPrimitive t)] -> ShowS #

Show (FieldValue w sch (TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Schema.Interpretation

Methods

showsPrec :: Int -> FieldValue w sch TNull -> ShowS #

show :: FieldValue w sch TNull -> String #

showList :: [FieldValue w sch TNull] -> ShowS #

(ToJSONKey (FieldValue w sch k), ToJSON (FieldValue w sch v)) => ToJSON (FieldValue w sch (TMap k v)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: FieldValue w sch (TMap k v) -> Value #

toEncoding :: FieldValue w sch (TMap k v) -> Encoding #

toJSONList :: [FieldValue w sch (TMap k v)] -> Value #

toEncodingList :: [FieldValue w sch (TMap k v)] -> Encoding #

ToJSON (FieldValue w sch t) => ToJSON (FieldValue w sch (TList t)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: FieldValue w sch (TList t) -> Value #

toEncoding :: FieldValue w sch (TList t) -> Encoding #

toJSONList :: [FieldValue w sch (TList t)] -> Value #

toEncodingList :: [FieldValue w sch (TList t)] -> Encoding #

ToJSON (FieldValue w sch t) => ToJSON (FieldValue w sch (TOption t)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSON (Term w sch (sch :/: t)) => ToJSON (FieldValue w sch (TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSON t => ToJSON (FieldValue w sch (TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSON (FieldValue w sch (TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

ToJSONUnion w sch us => ToJSON (FieldValue w sch (TUnion us)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

toJSON :: FieldValue w sch (TUnion us) -> Value #

toEncoding :: FieldValue w sch (TUnion us) -> Encoding #

toJSONList :: [FieldValue w sch (TUnion us)] -> Value #

toEncodingList :: [FieldValue w sch (TUnion us)] -> Encoding #

ToJSONKey t => ToJSONKey (FieldValue w sch (TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

(FromJSONKey (FieldValue w sch k), FromJSON (FieldValue w sch v), Ord (FieldValue w sch k)) => FromJSON (FieldValue w sch (TMap k v)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (FieldValue w sch (TMap k v)) #

parseJSONList :: Value -> Parser [FieldValue w sch (TMap k v)] #

FromJSON (FieldValue w sch t) => FromJSON (FieldValue w sch (TList t)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (FieldValue w sch (TList t)) #

parseJSONList :: Value -> Parser [FieldValue w sch (TList t)] #

FromJSON (FieldValue w sch t) => FromJSON (FieldValue w sch (TOption t)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSON (Term w sch (sch :/: t)) => FromJSON (FieldValue w sch (TSchematic t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSON t => FromJSON (FieldValue w sch (TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSON (FieldValue w sch (TNull :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

FromJSONUnion w sch us => FromJSON (FieldValue w sch (TUnion us)) Source # 
Instance details

Defined in Mu.Adapter.Json

Methods

parseJSON :: Value -> Parser (FieldValue w sch (TUnion us)) #

parseJSONList :: Value -> Parser [FieldValue w sch (TUnion us)] #

FromJSONKey t => FromJSONKey (FieldValue w sch (TPrimitive t :: FieldTypeB Type typeName)) Source # 
Instance details

Defined in Mu.Adapter.Json

data NS (a :: k -> Type) (b :: [k]) :: forall k. (k -> Type) -> [k] -> Type where #

An n-ary sum.

The sum is parameterized by a type constructor f and indexed by a type-level list xs. The length of the list determines the number of choices in the sum and if the i-th element of the list is of type x, then the i-th choice of the sum is of type f x.

The constructor names are chosen to resemble Peano-style natural numbers, i.e., Z is for "zero", and S is for "successor". Chaining S and Z chooses the corresponding component of the sum.

Examples:

Z         :: f x -> NS f (x ': xs)
S . Z     :: f y -> NS f (x ': y ': xs)
S . S . Z :: f z -> NS f (x ': y ': z ': xs)
...

Note that empty sums (indexed by an empty list) have no non-bottom elements.

Two common instantiations of f are the identity functor I and the constant functor K. For I, the sum becomes a direct generalization of the Either type to arbitrarily many choices. For K a, the result is a homogeneous choice type, where the contents of the type-level list are ignored, but its length specifies the number of options.

In the context of the SOP approach to generic programming, an n-ary sum describes the top-level structure of a datatype, which is a choice between all of its constructors.

Examples:

Z (I 'x')      :: NS I       '[ Char, Bool ]
S (Z (I True)) :: NS I       '[ Char, Bool ]
S (Z (K 1))    :: NS (K Int) '[ Char, Bool ]

Constructors

Z :: forall k (a :: k -> Type) (b :: [k]) (x :: k) (xs :: [k]). a x -> NS a (x ': xs) 
S :: forall k (a :: k -> Type) (b :: [k]) (xs :: [k]) (x :: k). NS a xs -> NS a (x ': xs) 
Instances
HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys #

hcoerce :: (AllZipN (Prod NS) (LiftedCoercible f g) xs ys, HTrans NS NS) => NS f xs -> NS g ys #

HAp (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hap :: Prod NS (f -.-> g) xs -> NS f xs -> NS g xs #

HCollapse (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: SListIN NS xs => NS (K a) xs -> CollapseTo NS a #

HTraverse_ (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () #

htraverse_ :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () #

HSequence (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) #

hctraverse' :: (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

htraverse' :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

HIndex (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: NS f xs -> Int #

HApInjs (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: SListIN NS xs => Prod NS f xs -> [NS f xs] #

HExpand (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: SListIN (Prod NS) xs => (forall (x :: k0). f x) -> NS f xs -> Prod NS f xs #

hcexpand :: AllN (Prod NS) c xs => proxy c -> (forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs #

All (Compose Eq f) xs => Eq (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

(==) :: NS f xs -> NS f xs -> Bool #

(/=) :: NS f xs -> NS f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

compare :: NS f xs -> NS f xs -> Ordering #

(<) :: NS f xs -> NS f xs -> Bool #

(<=) :: NS f xs -> NS f xs -> Bool #

(>) :: NS f xs -> NS f xs -> Bool #

(>=) :: NS f xs -> NS f xs -> Bool #

max :: NS f xs -> NS f xs -> NS f xs #

min :: NS f xs -> NS f xs -> NS f xs #

All (Compose Show f) xs => Show (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

showsPrec :: Int -> NS f xs -> ShowS #

show :: NS f xs -> String #

showList :: [NS f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NS f xs)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.NS

Methods

rnf :: NS f xs -> () #

type Same (NS :: (k1 -> Type) -> [k1] -> Type) 
Instance details

Defined in Data.SOP.NS

type Same (NS :: (k1 -> Type) -> [k1] -> Type) = (NS :: (k2 -> Type) -> [k2] -> Type)
type Prod (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type Prod (NS :: (k -> Type) -> [k] -> Type) = (NP :: (k -> Type) -> [k] -> Type)
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NS

type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a = a
type SListIN (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type SListIN (NS :: (k -> Type) -> [k] -> Type) = (SListI :: [k] -> Constraint)
type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NS

type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c

data NP (a :: k -> Type) (b :: [k]) :: forall k. (k -> Type) -> [k] -> Type where #

An n-ary product.

The product is parameterized by a type constructor f and indexed by a type-level list xs. The length of the list determines the number of elements in the product, and if the i-th element of the list is of type x, then the i-th element of the product is of type f x.

The constructor names are chosen to resemble the names of the list constructors.

Two common instantiations of f are the identity functor I and the constant functor K. For I, the product becomes a heterogeneous list, where the type-level list describes the types of its components. For K a, the product becomes a homogeneous list, where the contents of the type-level list are ignored, but its length still specifies the number of elements.

In the context of the SOP approach to generic programming, an n-ary product describes the structure of the arguments of a single data constructor.

Examples:

I 'x'    :* I True  :* Nil  ::  NP I       '[ Char, Bool ]
K 0      :* K 1     :* Nil  ::  NP (K Int) '[ Char, Bool ]
Just 'x' :* Nothing :* Nil  ::  NP Maybe   '[ Char, Bool ]

Constructors

Nil :: forall k (a :: k -> Type) (b :: [k]). NP a ([] :: [k]) 
(:*) :: forall k (a :: k -> Type) (b :: [k]) (x :: k) (xs :: [k]). a x -> NP a xs -> NP a (x ': xs) infixr 5 
Instances
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: (AllZipN (Prod NP) (LiftedCoercible f g) xs ys, HTrans NP NP) => NP f xs -> NP g ys #

HPure (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

HAp (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hap :: Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

HCollapse (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

HTraverse_ (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () #

htraverse_ :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () #

HSequence (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) #

hctraverse' :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

htraverse' :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

All (Compose Eq f) xs => Eq (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

(==) :: NP f xs -> NP f xs -> Bool #

(/=) :: NP f xs -> NP f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

compare :: NP f xs -> NP f xs -> Ordering #

(<) :: NP f xs -> NP f xs -> Bool #

(<=) :: NP f xs -> NP f xs -> Bool #

(>) :: NP f xs -> NP f xs -> Bool #

(>=) :: NP f xs -> NP f xs -> Bool #

max :: NP f xs -> NP f xs -> NP f xs #

min :: NP f xs -> NP f xs -> NP f xs #

All (Compose Show f) xs => Show (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

showsPrec :: Int -> NP f xs -> ShowS #

show :: NP f xs -> String #

showList :: [NP f xs] -> ShowS #

All (Compose Semigroup f) xs => Semigroup (NP f xs)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

(<>) :: NP f xs -> NP f xs -> NP f xs #

sconcat :: NonEmpty (NP f xs) -> NP f xs #

stimes :: Integral b => b -> NP f xs -> NP f xs #

(All (Compose Monoid f) xs, All (Compose Semigroup f) xs) => Monoid (NP f xs)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

mempty :: NP f xs #

mappend :: NP f xs -> NP f xs -> NP f xs #

mconcat :: [NP f xs] -> NP f xs #

All (Compose NFData f) xs => NFData (NP f xs)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.NP

Methods

rnf :: NP f xs -> () #

type Same (NP :: (k1 -> Type) -> [k1] -> Type) 
Instance details

Defined in Data.SOP.NP

type Same (NP :: (k1 -> Type) -> [k1] -> Type) = (NP :: (k2 -> Type) -> [k2] -> Type)
type Prod (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

type Prod (NP :: (k -> Type) -> [k] -> Type) = (NP :: (k -> Type) -> [k] -> Type)
type UnProd (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type UnProd (NP :: (k -> Type) -> [k] -> Type) = (NS :: (k -> Type) -> [k] -> Type)
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NP

type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a = [a]
type SListIN (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

type SListIN (NP :: (k -> Type) -> [k] -> Type) = (SListI :: [k] -> Constraint)
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c
type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) = AllZip c

data Proxy (t :: k) :: forall k. k -> Type #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the 'undefined :: a' idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 
Instances
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

fail :: String -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a #

(>$) :: b -> Proxy b -> Proxy a #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

ToJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Proxy a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding #

FromJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy a] #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: k -> Type))
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: Type -> Type))

Transforming the wrapper type

transWrap :: forall tn fn (sch :: Schema tn fn) t u v. (Functor u, forall k. Ord (FieldValue u sch k) => Ord (FieldValue v sch k)) => (forall a. u a -> v a) -> Term u sch t -> Term v sch t Source #

Change the underlying wrapper of a term.

transWrapNoMaps :: forall tn fn (sch :: Schema tn fn) t u v. Functor u => (forall a. u a -> v a) -> Term u sch t -> Term v sch t Source #

Change the underlying wrapper of a term. This version assumes that no field is a map, which allows for a more general type. If a map is found, an exception is raised.

For internal use only

transFields :: forall tn fn (sch :: Schema tn fn) args u v. (Functor u, forall k. Ord (FieldValue u sch k) => Ord (FieldValue v sch k)) => (forall a. u a -> v a) -> NP (Field u sch) args -> NP (Field v sch) args Source #

Change the underlying wrapper of a list of fields.

transFieldsNoMaps :: forall tn fn (sch :: Schema tn fn) args u v. Functor u => (forall a. u a -> v a) -> NP (Field u sch) args -> NP (Field v sch) args Source #

Change the underlying wrapper of a list of fields. This version assumes no maps are present as fields.

transValue :: forall tn fn (sch :: Schema tn fn) l u v. (Functor u, forall k. Ord (FieldValue u sch k) => Ord (FieldValue v sch k)) => (forall a. u a -> v a) -> FieldValue u sch l -> FieldValue v sch l Source #

Change the underlying wrapper of a value.

transValueNoMaps :: forall tn fn (sch :: Schema tn fn) l u v. Functor u => (forall a. u a -> v a) -> FieldValue u sch l -> FieldValue v sch l Source #

Change the underlying wrapper of a value. This version assumes that the value is not a map.