api-tools-0.10.1.0: DSL for generating API boilerplate and docs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.API.Types

Synopsis

Documentation

type API = [Thing] Source #

an API spec is made up of a list of type/element specs, each specifying a Haskell type and JSON wrappers

data Thing Source #

Instances

Instances details
FromJSON Thing Source # 
Instance details

Defined in Data.API.Types

ToJSON Thing Source # 
Instance details

Defined in Data.API.Types

FromJSONWithErrs Thing Source #

Generate an API spec from the JSON

Instance details

Defined in Data.API.API

Show Thing Source # 
Instance details

Defined in Data.API.Types

Methods

showsPrec :: Int -> Thing -> ShowS #

show :: Thing -> String #

showList :: [Thing] -> ShowS #

NFData Thing Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: Thing -> () #

Eq Thing Source # 
Instance details

Defined in Data.API.Types

Methods

(==) :: Thing -> Thing -> Bool #

(/=) :: Thing -> Thing -> Bool #

Lift Thing Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => Thing -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Thing -> Code m Thing #

data APINode Source #

Specifies an individual element/type of the API

Constructors

APINode 

Fields

Instances

Instances details
FromJSON APINode Source # 
Instance details

Defined in Data.API.Types

ToJSON APINode Source # 
Instance details

Defined in Data.API.Types

Show APINode Source # 
Instance details

Defined in Data.API.Types

NFData APINode Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: APINode -> () #

Eq APINode Source # 
Instance details

Defined in Data.API.Types

Methods

(==) :: APINode -> APINode -> Bool #

(/=) :: APINode -> APINode -> Bool #

Lift APINode Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => APINode -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => APINode -> Code m APINode #

newtype TypeName Source #

TypeName must contain a valid Haskell type constructor

Constructors

TypeName 

Fields

Instances

Instances details
FromJSON TypeName Source # 
Instance details

Defined in Data.API.Types

ToJSON TypeName Source # 
Instance details

Defined in Data.API.Types

PP TypeName Source # 
Instance details

Defined in Data.API.PP

Methods

pp :: TypeName -> String Source #

IsString TypeName Source # 
Instance details

Defined in Data.API.Types

Show TypeName Source # 
Instance details

Defined in Data.API.Types

NFData TypeName Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: TypeName -> () #

Eq TypeName Source # 
Instance details

Defined in Data.API.Types

Ord TypeName Source # 
Instance details

Defined in Data.API.Types

Lift TypeName Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => TypeName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TypeName -> Code m TypeName #

newtype FieldName Source #

FieldName identifies recod fields and union alternatives must contain a valid identifier valid in Haskell and any API client wrappers (e.g., if Ruby wrappers are to be generated the names should easily map into Ruby)

Constructors

FieldName 

Fields

Instances

Instances details
FromJSON FieldName Source # 
Instance details

Defined in Data.API.Types

ToJSON FieldName Source # 
Instance details

Defined in Data.API.Types

PP FieldName Source # 
Instance details

Defined in Data.API.PP

Methods

pp :: FieldName -> String Source #

IsString FieldName Source # 
Instance details

Defined in Data.API.Types

Show FieldName Source # 
Instance details

Defined in Data.API.Types

NFData FieldName Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: FieldName -> () #

Eq FieldName Source # 
Instance details

Defined in Data.API.Types

Ord FieldName Source # 
Instance details

Defined in Data.API.Types

Lift FieldName Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => FieldName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FieldName -> Code m FieldName #

type MDComment = String Source #

Markdown comments are represented by strings

type Prefix = CI String Source #

a distinct case-insensitive short prefix used to form unique record field names and data constructors:

  • must be a valid Haskell identifier
  • must be unique within the API

data Spec Source #

type/element specs are either simple type isomorphisms of basic JSON types, records, unions or enumerated types

Instances

Instances details
FromJSON Spec Source # 
Instance details

Defined in Data.API.Types

ToJSON Spec Source # 
Instance details

Defined in Data.API.Types

Show Spec Source # 
Instance details

Defined in Data.API.Types

Methods

showsPrec :: Int -> Spec -> ShowS #

show :: Spec -> String #

showList :: [Spec] -> ShowS #

NFData Spec Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: Spec -> () #

Eq Spec Source # 
Instance details

Defined in Data.API.Types

Methods

(==) :: Spec -> Spec -> Bool #

(/=) :: Spec -> Spec -> Bool #

Lift Spec Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => Spec -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Spec -> Code m Spec #

data SpecNewtype Source #

SpecNewtype elements are isomorphisms of string, inetgers or booleans

Constructors

SpecNewtype 

Instances

Instances details
FromJSON SpecNewtype Source # 
Instance details

Defined in Data.API.Types

ToJSON SpecNewtype Source # 
Instance details

Defined in Data.API.Types

Show SpecNewtype Source # 
Instance details

Defined in Data.API.Types

NFData SpecNewtype Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: SpecNewtype -> () #

Eq SpecNewtype Source # 
Instance details

Defined in Data.API.Types

Lift SpecNewtype Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => SpecNewtype -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SpecNewtype -> Code m SpecNewtype #

data SpecRecord Source #

SpecRecord is your classsic product type.

Constructors

SpecRecord 

Fields

Instances

Instances details
FromJSON SpecRecord Source # 
Instance details

Defined in Data.API.Types

ToJSON SpecRecord Source # 
Instance details

Defined in Data.API.Types

Show SpecRecord Source # 
Instance details

Defined in Data.API.Types

NFData SpecRecord Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: SpecRecord -> () #

Eq SpecRecord Source # 
Instance details

Defined in Data.API.Types

Lift SpecRecord Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => SpecRecord -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SpecRecord -> Code m SpecRecord #

data FieldType Source #

In addition to the type and comment, record fields may carry a flag indicating that they are read-only, and may have a default value, which must be of a compatible type.

Instances

Instances details
FromJSON FieldType Source # 
Instance details

Defined in Data.API.Types

ToJSON FieldType Source # 
Instance details

Defined in Data.API.Types

Show FieldType Source # 
Instance details

Defined in Data.API.Types

NFData FieldType Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: FieldType -> () #

Eq FieldType Source # 
Instance details

Defined in Data.API.Types

Lift FieldType Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => FieldType -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FieldType -> Code m FieldType #

data SpecUnion Source #

SpecUnion is your classsic union type

Constructors

SpecUnion 

Fields

Instances

Instances details
FromJSON SpecUnion Source # 
Instance details

Defined in Data.API.Types

ToJSON SpecUnion Source # 
Instance details

Defined in Data.API.Types

Show SpecUnion Source # 
Instance details

Defined in Data.API.Types

NFData SpecUnion Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: SpecUnion -> () #

Eq SpecUnion Source # 
Instance details

Defined in Data.API.Types

Lift SpecUnion Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => SpecUnion -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SpecUnion -> Code m SpecUnion #

data SpecEnum Source #

SpecEnum is your classic enumerated type

Constructors

SpecEnum 

Fields

Instances

Instances details
FromJSON SpecEnum Source # 
Instance details

Defined in Data.API.Types

ToJSON SpecEnum Source # 
Instance details

Defined in Data.API.Types

Show SpecEnum Source # 
Instance details

Defined in Data.API.Types

NFData SpecEnum Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: SpecEnum -> () #

Eq SpecEnum Source # 
Instance details

Defined in Data.API.Types

Lift SpecEnum Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => SpecEnum -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SpecEnum -> Code m SpecEnum #

type Conversion = Maybe (FieldName, FieldName) Source #

Conversion possibly converts to an internal representation. If specified, a conversion is a pair of an injection function name and a projection function name.

data APIType Source #

Type is either a list, Maybe, a named element of the API or a basic type

Constructors

TyList APIType

list elements are types

TyMaybe APIType

Maybe elements are types

TyName TypeName

the referenced type must be defined by the API

TyBasic BasicType

a JSON string, int, bool etc.

TyJSON

a generic JSON value

Instances

Instances details
FromJSON APIType Source # 
Instance details

Defined in Data.API.Types

ToJSON APIType Source # 
Instance details

Defined in Data.API.Types

PP APIType Source # 
Instance details

Defined in Data.API.PP

Methods

pp :: APIType -> String Source #

IsString APIType Source #

It is sometimes helpful to write a type name directly as a string

Instance details

Defined in Data.API.Types

Methods

fromString :: String -> APIType #

Show APIType Source # 
Instance details

Defined in Data.API.Types

NFData APIType Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: APIType -> () #

Eq APIType Source # 
Instance details

Defined in Data.API.Types

Methods

(==) :: APIType -> APIType -> Bool #

(/=) :: APIType -> APIType -> Bool #

Lift APIType Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => APIType -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => APIType -> Code m APIType #

data DefaultValue Source #

A default value for a field

Instances

Instances details
FromJSON DefaultValue Source # 
Instance details

Defined in Data.API.Types

ToJSON DefaultValue Source # 
Instance details

Defined in Data.API.Types

PP DefaultValue Source # 
Instance details

Defined in Data.API.PP

Show DefaultValue Source # 
Instance details

Defined in Data.API.Types

NFData DefaultValue Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: DefaultValue -> () #

Eq DefaultValue Source # 
Instance details

Defined in Data.API.Types

Lift DefaultValue Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => DefaultValue -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DefaultValue -> Code m DefaultValue #

data BasicType Source #

the basic JSON types (N.B., no floating point numbers, yet)

Constructors

BTstring

a JSON UTF-8 string

BTbinary

a base-64-encoded byte string

BTbool

a JSON bool

BTint

a JSON integral number

BTutc

a JSON UTC string

Instances

Instances details
FromJSON BasicType Source # 
Instance details

Defined in Data.API.Types

ToJSON BasicType Source # 
Instance details

Defined in Data.API.Types

PP BasicType Source # 
Instance details

Defined in Data.API.PP

Methods

pp :: BasicType -> String Source #

Show BasicType Source # 
Instance details

Defined in Data.API.Types

NFData BasicType Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: BasicType -> () #

Eq BasicType Source # 
Instance details

Defined in Data.API.Types

Lift BasicType Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => BasicType -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => BasicType -> Code m BasicType #

data Filter Source #

Instances

Instances details
FromJSON Filter Source # 
Instance details

Defined in Data.API.Types

ToJSON Filter Source # 
Instance details

Defined in Data.API.Types

Show Filter Source # 
Instance details

Defined in Data.API.Types

NFData Filter Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: Filter -> () #

Eq Filter Source # 
Instance details

Defined in Data.API.Types

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

Lift Filter Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => Filter -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Filter -> Code m Filter #

data IntRange Source #

Constructors

IntRange 

Fields

Instances

Instances details
FromJSON IntRange Source # 
Instance details

Defined in Data.API.Types

ToJSON IntRange Source # 
Instance details

Defined in Data.API.Types

Show IntRange Source # 
Instance details

Defined in Data.API.Types

NFData IntRange Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: IntRange -> () #

Eq IntRange Source # 
Instance details

Defined in Data.API.Types

Lift IntRange Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => IntRange -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => IntRange -> Code m IntRange #

data UTCRange Source #

Constructors

UTCRange 

Instances

Instances details
FromJSON UTCRange Source # 
Instance details

Defined in Data.API.Types

ToJSON UTCRange Source # 
Instance details

Defined in Data.API.Types

Show UTCRange Source # 
Instance details

Defined in Data.API.Types

NFData UTCRange Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: UTCRange -> () #

Eq UTCRange Source # 
Instance details

Defined in Data.API.Types

Lift UTCRange Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => UTCRange -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => UTCRange -> Code m UTCRange #

data RegEx Source #

Constructors

RegEx 

Fields

Instances

Instances details
FromJSON RegEx Source # 
Instance details

Defined in Data.API.Types

ToJSON RegEx Source # 
Instance details

Defined in Data.API.Types

Show RegEx Source # 
Instance details

Defined in Data.API.Types

Methods

showsPrec :: Int -> RegEx -> ShowS #

show :: RegEx -> String #

showList :: [RegEx] -> ShowS #

NFData RegEx Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: RegEx -> () #

Eq RegEx Source # 
Instance details

Defined in Data.API.Types

Methods

(==) :: RegEx -> RegEx -> Bool #

(/=) :: RegEx -> RegEx -> Bool #

Lift RegEx Source # 
Instance details

Defined in Data.API.Types

Methods

lift :: Quote m => RegEx -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RegEx -> Code m RegEx #

newtype Binary Source #

Binary data is represented in JSON format as a base64-encoded string

Constructors

Binary 

Fields

Instances

Instances details
Arbitrary Binary Source # 
Instance details

Defined in Data.API.Types

FromJSON Binary Source # 
Instance details

Defined in Data.API.Types

ToJSON Binary Source # 
Instance details

Defined in Data.API.Types

FromJSONWithErrs Binary Source # 
Instance details

Defined in Data.API.JSON

Example Binary Source # 
Instance details

Defined in Data.API.Tools.Example

Show Binary Source # 
Instance details

Defined in Data.API.Types

NFData Binary Source # 
Instance details

Defined in Data.API.Types

Methods

rnf :: Binary -> () #

Eq Binary Source # 
Instance details

Defined in Data.API.Types

Methods

(==) :: Binary -> Binary -> Bool #

(/=) :: Binary -> Binary -> Bool #

Ord Binary Source # 
Instance details

Defined in Data.API.Types

SafeCopy Binary Source # 
Instance details

Defined in Data.API.Types

Serialise Binary Source # 
Instance details

Defined in Data.API.Types

defaultValueAsJsValue :: DefaultValue -> Value Source #

Convert a default value to an Aeson Value. This differs from toJSON as it will not round-trip with fromJSON: UTC default values are turned into strings.

Orphan instances

Arbitrary Text Source # 
Instance details

Methods

arbitrary :: Gen Text #

shrink :: Text -> [Text] #

FromJSON s => FromJSON (CI s) Source # 
Instance details

Methods

parseJSON :: Value -> Parser (CI s) #

parseJSONList :: Value -> Parser [CI s] #

ToJSON s => ToJSON (CI s) Source # 
Instance details

Methods

toJSON :: CI s -> Value #

toEncoding :: CI s -> Encoding #

toJSONList :: [CI s] -> Value #

toEncodingList :: [CI s] -> Encoding #