schemas-0.4.0.2: schema guided serialization

Safe HaskellNone
LanguageHaskell2010

Schemas.Internal

Synopsis

Documentation

data TypedSchemaFlex from a where Source #

TypedSchemaFlex enc dec is a schema for encoding from enc and decoding to dec. Usually we want enc and dec to be the same type but this flexibility comes in handy for composition.

Constructors

TNamed :: SchemaName -> TypedSchemaFlex from' a' -> (a' -> a) -> (from -> from') -> TypedSchemaFlex from a 
TEnum :: NonEmpty (Text, a) -> (from -> Text) -> TypedSchemaFlex from a 
TArray :: TypedSchemaFlex b b -> (Vector b -> a) -> (from -> Vector b) -> TypedSchemaFlex from a 
TMap :: TypedSchemaFlex b b -> (HashMap Text b -> a) -> (from -> HashMap Text b) -> TypedSchemaFlex from a 
TAllOf :: NonEmpty (TypedSchemaFlex from a) -> TypedSchemaFlex from a

Encoding and decoding support all alternatives

TOneOf :: TypedSchemaFlex from' a' -> TypedSchemaFlex from'' a'' -> (Either a' a'' -> a) -> (from -> Either from' from'') -> TypedSchemaFlex from a

Decoding from all alternatives, but encoding only to one

TEmpty :: (Void -> a) -> (from -> Void) -> TypedSchemaFlex from a 
TPrim :: Text -> (Value -> Result a) -> (from -> Value) -> TypedSchemaFlex from a 
RecordSchema :: RecordFields from a -> TypedSchemaFlex from a 
Instances
Profunctor TypedSchemaFlex Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> TypedSchemaFlex b c -> TypedSchemaFlex a d #

lmap :: (a -> b) -> TypedSchemaFlex b c -> TypedSchemaFlex a c #

rmap :: (b -> c) -> TypedSchemaFlex a b -> TypedSchemaFlex a c #

(#.) :: Coercible c b => q b c -> TypedSchemaFlex a b -> TypedSchemaFlex a c #

(.#) :: Coercible b a => TypedSchemaFlex b c -> q a b -> TypedSchemaFlex a c #

Functor (TypedSchemaFlex from) Source # 
Instance details

Defined in Schemas.Internal

Methods

fmap :: (a -> b) -> TypedSchemaFlex from a -> TypedSchemaFlex from b #

(<$) :: a -> TypedSchemaFlex from b -> TypedSchemaFlex from a #

Show (TypedSchemaFlex from a) Source # 
Instance details

Defined in Schemas.Internal

Methods

showsPrec :: Int -> TypedSchemaFlex from a -> ShowS #

show :: TypedSchemaFlex from a -> String #

showList :: [TypedSchemaFlex from a] -> ShowS #

Semigroup (TypedSchemaFlex f a) Source # 
Instance details

Defined in Schemas.Internal

Monoid (TypedSchemaFlex Void Void) Source # 
Instance details

Defined in Schemas.Internal

named :: SchemaName -> TypedSchemaFlex from' a -> TypedSchemaFlex from' a Source #

named n sc annotates a schema with a name, allowing for circular schemas.

enum :: Eq a => (a -> Text) -> NonEmpty a -> TypedSchema a Source #

enum values mapping construct a schema for a non empty set of values with a Text mapping

stringMap :: TypedSchema a -> TypedSchema (HashMap Text a) Source #

stringMap sc is the schema for a stringmap where the values have schema sc

list :: IsList l => TypedSchema (Item l) -> TypedSchema l Source #

list sc is the schema for a list of values with schema sc

vector :: TypedSchema a -> TypedSchema (Vector a) Source #

vector sc is the schema for a vector of values with schema sc

viaJSON :: (FromJSON a, ToJSON a) => Text -> TypedSchema a Source #

viaJson label constructs a schema reusing existing aeson instances. The resulting schema is opaque and cannot be subtyped and/or versioned, so this constructor should be used sparingly. The label is used to describe the extracted Schema.

viaIso :: Iso' a b -> TypedSchema a -> TypedSchema b Source #

Apply an isomorphism to a schema

string :: TypedSchema String Source #

The schema of String values

readShow :: (Read a, Show a) => TypedSchema a Source #

A schema for types that can be parsed and pretty-printed. The resulting schema is opaque and cannot be subtyped/versioned, so this constructor is best used for primitive value

eitherSchema :: TypedSchemaFlex from a -> TypedSchemaFlex from' a' -> TypedSchemaFlex (Either from from') (Either a a') Source #

eitherSchema and emptySchema make TypedSchemaFlex an almost instance of SumProfunctor (no Choice)

emptySchema :: TypedSchema Void Source #

The vacuous schema

pureSchema :: a -> TypedSchemaFlex a a Source #

The schema that can be trivially decoded and encoded

data RecordField from a where Source #

Constructors

RequiredAp 

Fields

OptionalAp 

Fields

Instances
Profunctor RecordField Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> RecordField b c -> RecordField a d #

lmap :: (a -> b) -> RecordField b c -> RecordField a c #

rmap :: (b -> c) -> RecordField a b -> RecordField a c #

(#.) :: Coercible c b => q b c -> RecordField a b -> RecordField a c #

(.#) :: Coercible b a => RecordField b c -> q a b -> RecordField a c #

fieldNameL :: Lens' (RecordField from a) Text Source #

Lens for the fieldName attribute

newtype RecordFields from a Source #

An Alternative profunctor for defining record schemas with versioning.

 schemaPerson = Person
            <$> (field "name" name <|> field "full name" name)
            <*> (field "age" age <|> pure -1)

Alternatives are searched greedily in a top-down order.

Constructors

RecordFields 

Fields

Instances
Profunctor RecordFields Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> RecordFields b c -> RecordFields a d #

lmap :: (a -> b) -> RecordFields b c -> RecordFields a c #

rmap :: (b -> c) -> RecordFields a b -> RecordFields a c #

(#.) :: Coercible c b => q b c -> RecordFields a b -> RecordFields a c #

(.#) :: Coercible b a => RecordFields b c -> q a b -> RecordFields a c #

Functor (RecordFields from) Source # 
Instance details

Defined in Schemas.Internal

Methods

fmap :: (a -> b) -> RecordFields from a -> RecordFields from b #

(<$) :: a -> RecordFields from b -> RecordFields from a #

Applicative (RecordFields from) Source # 
Instance details

Defined in Schemas.Internal

Methods

pure :: a -> RecordFields from a #

(<*>) :: RecordFields from (a -> b) -> RecordFields from a -> RecordFields from b #

liftA2 :: (a -> b -> c) -> RecordFields from a -> RecordFields from b -> RecordFields from c #

(*>) :: RecordFields from a -> RecordFields from b -> RecordFields from b #

(<*) :: RecordFields from a -> RecordFields from b -> RecordFields from a #

Alternative (RecordFields from) Source # 
Instance details

Defined in Schemas.Internal

Methods

empty :: RecordFields from a #

(<|>) :: RecordFields from a -> RecordFields from a -> RecordFields from a #

some :: RecordFields from a -> RecordFields from [a] #

many :: RecordFields from a -> RecordFields from [a] #

Semigroup (RecordFields from a) Source # 
Instance details

Defined in Schemas.Internal

Methods

(<>) :: RecordFields from a -> RecordFields from a -> RecordFields from a #

sconcat :: NonEmpty (RecordFields from a) -> RecordFields from a #

stimes :: Integral b => b -> RecordFields from a -> RecordFields from a #

Monoid (RecordFields from a) Source # 
Instance details

Defined in Schemas.Internal

Methods

mempty :: RecordFields from a #

mappend :: RecordFields from a -> RecordFields from a -> RecordFields from a #

mconcat :: [RecordFields from a] -> RecordFields from a #

overFieldNames :: (Text -> Text) -> RecordFields from a -> RecordFields from a Source #

Map a function over all the field names

record :: RecordFields from a -> TypedSchemaFlex from a Source #

Wrap an applicative record schema

fieldWith :: TypedSchema a -> Text -> (from -> a) -> RecordFields from a Source #

fieldWith sc n get introduces a field

fieldWith' :: TypedSchemaFlex from a -> Text -> RecordFields from a Source #

Generalised version of fieldWith

liftPrism :: Prism s t a b -> TypedSchemaFlex a b -> TypedSchemaFlex t t -> TypedSchemaFlex s t Source #

Project a schema through a Prism.

liftJust :: TypedSchemaFlex a b -> TypedSchemaFlex (Maybe a) (Maybe b) Source #

Returns a partial schema. When encoding/decoding a Nothing value, an optional field will be omitted, and a required field will cause this alternative to be aborted.

liftRight :: TypedSchemaFlex a b -> TypedSchemaFlex (Either c a) (Either c b) Source #

Returns a partial schema. When encoding/decoding a Left value, an optional field will be omitted, and a required field will cause this alternative to be aborted.

optFieldWith :: forall a from. TypedSchemaFlex from (Maybe a) -> Text -> RecordFields from (Maybe a) Source #

optFieldGeneral :: forall a from. a -> TypedSchemaFlex from a -> Text -> RecordFields from a Source #

The most general introduction form for optional alts

optFieldEitherWith :: TypedSchemaFlex from (Either e a) -> Text -> e -> RecordFields from (Either e a) Source #

A generalized version of optFieldEither.

extractFieldsHelper :: Alternative f => (forall a. RecordField from a -> f b) -> RecordFields from a -> f [b] Source #

data UnionAlt from where Source #

An alternative in a union type

Constructors

UnionAlt :: Prism' from b -> TypedSchema b -> UnionAlt from 

altWith :: TypedSchema a -> Prism' from a -> UnionAlt from Source #

Declare an alternative in a union type

union :: NonEmpty (Text, UnionAlt from) -> TypedSchema from Source #

Discriminated unions that record the name of the chosen constructor in the schema

  data Education = Degree Text | PhD Text | NoEducation

  schemaEducation = union'
    [ ("NoEducation", alt #_NoEducation)
    , ("Degree"     , alt #_Degree)
    , ("PhD"        , alt #_PhD)
    ]
  

oneOf :: NonEmpty (UnionAlt from) -> TypedSchema from Source #

Undiscriminated union that do not record the name of the constructor in the schema

  data Education = Degree Text | PhD Text | NoEducation

  schemaEducation = oneOf
    [ alt #_NoEducation
    , alt #_Degree
    , alt #_PhD
    ]
  

Alternatives are searched greedily in a top-down order.

extractSchema :: TypedSchemaFlex from a -> NonEmpty Schema Source #

Extract an untyped schema that can be serialized.

For schemas with alternatives, this enumerates all the possible versions lazily. Beware when using on schemas with multiple alternatives, as the number of versions is exponential.

extractFields :: RecordFields from to -> [[(Text, Field)]] Source #

Extract all the field groups (from alternatives) in the record

extractValidators :: TypedSchemaFlex from a -> Validators Source #

Returns all the primitive validators embedded in this typed schema

newtype IterAltT m a Source #

Constructors

IterAlt 

Fields

Instances
MonadTrans IterAltT Source # 
Instance details

Defined in Schemas.Internal

Methods

lift :: Monad m => m a -> IterAltT m a #

MonadState s m => MonadState s (IterAltT m) Source # 
Instance details

Defined in Schemas.Internal

Methods

get :: IterAltT m s #

put :: s -> IterAltT m () #

state :: (s -> (a, s)) -> IterAltT m a #

Monad m => MonadFree Identity (IterAltT m) Source # 
Instance details

Defined in Schemas.Internal

Methods

wrap :: Identity (IterAltT m a) -> IterAltT m a #

MonadError e m => MonadError e (IterAltT m) Source # 
Instance details

Defined in Schemas.Internal

Methods

throwError :: e -> IterAltT m a #

catchError :: IterAltT m a -> (e -> IterAltT m a) -> IterAltT m a #

Monad m => Monad (IterAltT m) Source # 
Instance details

Defined in Schemas.Internal

Methods

(>>=) :: IterAltT m a -> (a -> IterAltT m b) -> IterAltT m b #

(>>) :: IterAltT m a -> IterAltT m b -> IterAltT m b #

return :: a -> IterAltT m a #

fail :: String -> IterAltT m a #

Monad m => Functor (IterAltT m) Source # 
Instance details

Defined in Schemas.Internal

Methods

fmap :: (a -> b) -> IterAltT m a -> IterAltT m b #

(<$) :: a -> IterAltT m b -> IterAltT m a #

Monad m => Applicative (IterAltT m) Source # 
Instance details

Defined in Schemas.Internal

Methods

pure :: a -> IterAltT m a #

(<*>) :: IterAltT m (a -> b) -> IterAltT m a -> IterAltT m b #

liftA2 :: (a -> b -> c) -> IterAltT m a -> IterAltT m b -> IterAltT m c #

(*>) :: IterAltT m a -> IterAltT m b -> IterAltT m b #

(<*) :: IterAltT m a -> IterAltT m b -> IterAltT m a #

MonadPlus m => Alternative (IterAltT m) Source # 
Instance details

Defined in Schemas.Internal

Methods

empty :: IterAltT m a #

(<|>) :: IterAltT m a -> IterAltT m a -> IterAltT m a #

some :: IterAltT m a -> IterAltT m [a] #

many :: IterAltT m a -> IterAltT m [a] #

(Eq1 m, Eq a) => Eq (IterAltT m a) Source # 
Instance details

Defined in Schemas.Internal

Methods

(==) :: IterAltT m a -> IterAltT m a -> Bool #

(/=) :: IterAltT m a -> IterAltT m a -> Bool #

(Show1 m, Show a) => Show (IterAltT m a) Source # 
Instance details

Defined in Schemas.Internal

Methods

showsPrec :: Int -> IterAltT m a -> ShowS #

show :: IterAltT m a -> String #

showList :: [IterAltT m a] -> ShowS #

runDelay :: Monad m => Natural -> IterAltT m a -> m (Maybe a) Source #

newtype Result a Source #

A monad encapsulating failure as well as non-termination

Constructors

Result 
Instances
Monad Result Source # 
Instance details

Defined in Schemas.Internal

Methods

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

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

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 
Instance details

Defined in Schemas.Internal

Methods

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

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

Applicative Result Source # 
Instance details

Defined in Schemas.Internal

Methods

pure :: a -> Result a #

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

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

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

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

Alternative Result Source # 
Instance details

Defined in Schemas.Internal

Methods

empty :: Result a #

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

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

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

MonadFree Identity Result Source # 
Instance details

Defined in Schemas.Internal

Methods

wrap :: Identity (Result a) -> Result a #

MonadError TracedMismatches Result Source # 
Instance details

Defined in Schemas.Internal

Eq a => Eq (Result a) Source # 
Instance details

Defined in Schemas.Internal

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Show a => Show (Result a) Source # 
Instance details

Defined in Schemas.Internal

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

runResult :: MonadError TracedMismatches g => Natural -> Result a -> g (Maybe a) Source #

Run a Result up with bounded depth. Returns nothing if it runs out of steps.

encodeWith :: TypedSchemaFlex from a -> from -> Value Source #

Given a typed schema, produce a JSON encoder to the first version produced by extractSchema

encodeToWith :: TypedSchemaFlex from a -> Schema -> Either TracedMismatches (from -> Value) Source #

Given source and target schemas, produce a JSON encoder

runSchema :: TypedSchemaFlex enc dec -> enc -> Either [Mismatch] dec Source #

Runs a schema as a function enc -> dec. Loops for infinite/circular data

evalSchema :: forall enc dec. TypedSchemaFlex enc dec -> Maybe dec Source #

Evaluates a schema as a value of type dec. Can only succeed if the schema contains a TPure alternative

decodeWith :: TypedSchemaFlex from a -> Value -> Result a Source #

Given a JSON Value and a typed schema, extract a Haskell value

runAlt_ :: (Alternative g, Monoid m) => (forall a. f a -> g m) -> Alt f b -> g m Source #

(<.>) :: Functor f => (b -> c) -> (a -> f b) -> a -> f c infixr 8 Source #