jordan-openapi-0.2.0.0: OpenAPI Definitions for Jordan, Automatically
Safe HaskellNone
LanguageHaskell2010

Jordan.OpenAPI.Internal

Description

Internal module that provides JSON parser and serializers that convert to OpenAPI documentation.

Note that this module is full of internal-use-only functions and should probably n ever actually be imported.

Synopsis

Documentation

newtype ConstDeclare env r a Source #

Declare with a phantom type parameter.

Constructors

ConstDeclare 

Fields

Instances

Instances details
Functor (ConstDeclare env r) Source #

Fmap ignores argument

Instance details

Defined in Jordan.OpenAPI.Internal

Methods

fmap :: (a -> b) -> ConstDeclare env r a -> ConstDeclare env r b #

(<$) :: a -> ConstDeclare env r b -> ConstDeclare env r a #

(Monoid r, Monoid env) => Applicative (ConstDeclare env r) Source #

Applicative combines declarations.

Instance details

Defined in Jordan.OpenAPI.Internal

Methods

pure :: a -> ConstDeclare env r a #

(<*>) :: ConstDeclare env r (a -> b) -> ConstDeclare env r a -> ConstDeclare env r b #

liftA2 :: (a -> b -> c) -> ConstDeclare env r a -> ConstDeclare env r b -> ConstDeclare env r c #

(*>) :: ConstDeclare env r a -> ConstDeclare env r b -> ConstDeclare env r b #

(<*) :: ConstDeclare env r a -> ConstDeclare env r b -> ConstDeclare env r a #

Contravariant (ConstDeclare env r) Source #

Contravariant ignores argument.

Instance details

Defined in Jordan.OpenAPI.Internal

Methods

contramap :: (a -> b) -> ConstDeclare env r b -> ConstDeclare env r a #

(>$) :: b -> ConstDeclare env r b -> ConstDeclare env r a #

(Monoid r, Monoid env) => Divisible (ConstDeclare env r) Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

divide :: (a -> (b, c)) -> ConstDeclare env r b -> ConstDeclare env r c -> ConstDeclare env r a #

conquer :: ConstDeclare env r a #

data PropertyDeclare Source #

Instances

Instances details
Show PropertyDeclare Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Generic PropertyDeclare Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Associated Types

type Rep PropertyDeclare :: Type -> Type #

Semigroup PropertyDeclare Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Monoid PropertyDeclare Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

type Rep PropertyDeclare Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

type Rep PropertyDeclare = D1 ('MetaData "PropertyDeclare" "Jordan.OpenAPI.Internal" "jordan-openapi-0.2.0.0-Cvuxkno0q4FDtgEwvaS3Zz" 'False) (C1 ('MetaCons "PropertyDeclare" 'PrefixI 'True) (S1 ('MetaSel ('Just "requiredProperties") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "propertyTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InsOrdHashMap Text (Referenced Schema)))))

newtype ObjectSchema a Source #

Instances

Instances details
Functor ObjectSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

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

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

Applicative ObjectSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Contravariant ObjectSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

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

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

Divisible ObjectSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

divide :: (a -> (b, c)) -> ObjectSchema b -> ObjectSchema c -> ObjectSchema a #

conquer :: ObjectSchema a #

JSONObjectSerializer ObjectSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

serializeFieldWith :: Text -> (forall (jsonSerializer :: Type -> Type). JSONSerializer jsonSerializer => jsonSerializer a) -> ObjectSchema a #

serializeField :: ToJSON a => Text -> ObjectSchema a #

serializeDescribeFieldWith :: Text -> Text -> (forall (valueSerializer :: Type -> Type). JSONSerializer valueSerializer => valueSerializer a) -> ObjectSchema a #

serializeJust :: Text -> (forall (jsonSerializer :: Type -> Type). JSONSerializer jsonSerializer => jsonSerializer a) -> ObjectSchema (Maybe a) #

JSONObjectParser ObjectSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

parseFieldWith :: Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> ObjectSchema a #

parseDescribeFieldWith :: Text -> Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> ObjectSchema a #

parseField :: FromJSON v => Text -> ObjectSchema v #

parseDescribeField :: FromJSON v => Text -> Text -> ObjectSchema v #

parseFieldWithDefault :: Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> a -> ObjectSchema a #

parseDescribeFieldWithDefault :: Text -> Text -> (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> a -> ObjectSchema a #

newtype TupleSchema a Source #

Instances

Instances details
Functor TupleSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

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

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

Applicative TupleSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

pure :: a -> TupleSchema a #

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

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

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

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

Contravariant TupleSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

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

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

Divisible TupleSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

divide :: (a -> (b, c)) -> TupleSchema b -> TupleSchema c -> TupleSchema a #

conquer :: TupleSchema a #

JSONTupleSerializer TupleSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

serializeItemWith :: (forall (jsonSerializer :: Type -> Type). JSONSerializer jsonSerializer => jsonSerializer a) -> TupleSchema a #

serializeItem :: ToJSON a => TupleSchema a #

JSONTupleParser TupleSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

consumeItemWith :: (forall (valueParser :: Type -> Type). JSONParser valueParser => valueParser a) -> TupleSchema a #

consumeItem :: FromJSON v => TupleSchema v #

newtype JSONSchema a Source #

Instances

Instances details
Functor JSONSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

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

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

Contravariant JSONSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

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

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

Selectable JSONSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

giveUp :: (arg -> Void) -> JSONSchema arg #

select :: (arg -> Either lhs rhs) -> JSONSchema lhs -> JSONSchema rhs -> JSONSchema arg #

JSONSerializer JSONSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

serializeObject :: (forall (objSerializer :: Type -> Type). JSONObjectSerializer objSerializer => objSerializer a) -> JSONSchema a #

serializeDictionary :: Foldable t => (forall (jsonSerializer :: Type -> Type). JSONSerializer jsonSerializer => jsonSerializer a) -> JSONSchema (t (Text, a)) #

serializeText :: JSONSchema Text #

serializeTextConstant :: Text -> JSONSchema a #

serializeNull :: JSONSchema any #

serializeNumber :: JSONSchema Scientific #

serializeBool :: JSONSchema Bool #

serializeTuple :: (forall (tupleSerializer :: Type -> Type). JSONTupleSerializer tupleSerializer => tupleSerializer a) -> JSONSchema a #

serializeArray :: ToJSON a => JSONSchema [a] #

nameSerializer :: Text -> JSONSchema a -> JSONSchema a #

JSONParser JSONSchema Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Methods

parseObject :: (forall (objectParser :: Type -> Type). JSONObjectParser objectParser => objectParser a) -> JSONSchema a #

parseObjectStrict :: (forall (objectParser :: Type -> Type). JSONObjectParser objectParser => objectParser a) -> JSONSchema a #

parseDictionary :: (forall (jsonParser :: Type -> Type). JSONParser jsonParser => jsonParser a) -> JSONSchema [(Text, a)] #

parseText :: JSONSchema Text #

parseTextConstant :: Text -> JSONSchema () #

parseTuple :: (forall (arrayParser :: Type -> Type). JSONTupleParser arrayParser => arrayParser o) -> JSONSchema o #

parseArray :: FromJSON a => JSONSchema [a] #

parseArrayWith :: (forall (jsonParser :: Type -> Type). JSONParser jsonParser => jsonParser a) -> JSONSchema [a] #

parseNumber :: JSONSchema Scientific #

parseInteger :: JSONSchema Integer #

parseNull :: JSONSchema () #

parseBool :: JSONSchema Bool #

validateJSON :: JSONSchema (Either Text a) -> JSONSchema a #

nameParser :: Text -> JSONSchema a -> JSONSchema a #

addFormat :: Text -> JSONSchema a -> JSONSchema a #

Semigroup (JSONSchema a) Source # 
Instance details

Defined in Jordan.OpenAPI.Internal

Monoid (JSONSchema a) Source #

Empty instance: must be both a boolean and a text value, which is not possible (obviously!)

Instance details

Defined in Jordan.OpenAPI.Internal

getFromNamed :: forall a. FromJSON a => Proxy a -> Declare (Definitions Schema) NamedSchema Source #

Get documentation for a type that implements FromJSON, in the Declare environment.

This will be inline documention, IE, it will be named but not stored in the schema definitions.

getFromRef :: forall a. FromJSON a => Proxy a -> Declare (Definitions Schema) (Referenced Schema) Source #

Get documention for a type that implements FromJSON.

This will store the type in the schemas key of the schema definitions, and give back a reference to it.

getToNamed :: forall a. ToJSON a => Proxy a -> Declare (Definitions Schema) NamedSchema Source #

Get documentation for a type that implements ToJSON.

This will be inline documentation, IE, it will be named but not stored in the schema definitions.

getToRef :: forall a. ToJSON a => Proxy a -> Declare (Definitions Schema) (Referenced Schema) Source #

Get documentation for a type that implements ToJSON.

This will store the type in the schemas key of the schemas definitions, then give back a reference to it.