Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type API = [Thing]
- data Thing
- data APINode = APINode {}
- newtype TypeName = TypeName {}
- newtype FieldName = FieldName {
- _FieldName :: Text
- type MDComment = String
- type Prefix = CI String
- data Spec
- data SpecNewtype = SpecNewtype {}
- data SpecRecord = SpecRecord {}
- data FieldType = FieldType {}
- data SpecUnion = SpecUnion {}
- data SpecEnum = SpecEnum {}
- type Conversion = Maybe (FieldName, FieldName)
- data APIType
- data DefaultValue
- data BasicType
- data Filter
- data IntRange = IntRange {}
- data UTCRange = UTCRange {}
- data RegEx = RegEx {}
- newtype Binary = Binary {}
- defaultValueAsJsValue :: DefaultValue -> Value
- mkRegEx :: Text -> RegEx
- inIntRange :: Int -> IntRange -> Bool
- inUTCRange :: UTCTime -> UTCRange -> Bool
- base64ToBinary :: Text -> Either String Binary
Documentation
an API spec is made up of a list of type/element specs, each specifying a Haskell type and JSON wrappers
Specifies an individual element/type of the API
TypeName must contain a valid Haskell type constructor
Instances
Eq TypeName Source # | |
Ord TypeName Source # | |
Defined in Data.API.Types | |
Show TypeName Source # | |
IsString TypeName Source # | |
Defined in Data.API.Types fromString :: String -> TypeName # | |
ToJSON TypeName Source # | |
Defined in Data.API.Types | |
FromJSON TypeName Source # | |
NFData TypeName Source # | |
Defined in Data.API.Types | |
PP TypeName Source # | |
Lift TypeName 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)
Instances
Eq FieldName Source # | |
Ord FieldName Source # | |
Defined in Data.API.Types | |
Show FieldName Source # | |
IsString FieldName Source # | |
Defined in Data.API.Types fromString :: String -> FieldName # | |
ToJSON FieldName Source # | |
Defined in Data.API.Types | |
FromJSON FieldName Source # | |
NFData FieldName Source # | |
Defined in Data.API.Types | |
PP FieldName Source # | |
Lift FieldName Source # | |
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
type/element specs are either simple type isomorphisms of basic JSON types, records, unions or enumerated types
data SpecNewtype Source #
SpecNewtype elements are isomorphisms of string, inetgers or booleans
Instances
Eq SpecNewtype Source # | |
Defined in Data.API.Types (==) :: SpecNewtype -> SpecNewtype -> Bool # (/=) :: SpecNewtype -> SpecNewtype -> Bool # | |
Show SpecNewtype Source # | |
Defined in Data.API.Types showsPrec :: Int -> SpecNewtype -> ShowS # show :: SpecNewtype -> String # showList :: [SpecNewtype] -> ShowS # | |
ToJSON SpecNewtype Source # | |
Defined in Data.API.Types toJSON :: SpecNewtype -> Value # toEncoding :: SpecNewtype -> Encoding # toJSONList :: [SpecNewtype] -> Value # toEncodingList :: [SpecNewtype] -> Encoding # | |
FromJSON SpecNewtype Source # | |
Defined in Data.API.Types parseJSON :: Value -> Parser SpecNewtype # parseJSONList :: Value -> Parser [SpecNewtype] # | |
NFData SpecNewtype Source # | |
Defined in Data.API.Types rnf :: SpecNewtype -> () # | |
Lift SpecNewtype Source # | |
Defined in Data.API.Types lift :: SpecNewtype -> Q Exp # liftTyped :: SpecNewtype -> Q (TExp SpecNewtype) # |
data SpecRecord Source #
SpecRecord is your classsic product type.
Instances
Eq SpecRecord Source # | |
Defined in Data.API.Types (==) :: SpecRecord -> SpecRecord -> Bool # (/=) :: SpecRecord -> SpecRecord -> Bool # | |
Show SpecRecord Source # | |
Defined in Data.API.Types showsPrec :: Int -> SpecRecord -> ShowS # show :: SpecRecord -> String # showList :: [SpecRecord] -> ShowS # | |
ToJSON SpecRecord Source # | |
Defined in Data.API.Types toJSON :: SpecRecord -> Value # toEncoding :: SpecRecord -> Encoding # toJSONList :: [SpecRecord] -> Value # toEncodingList :: [SpecRecord] -> Encoding # | |
FromJSON SpecRecord Source # | |
Defined in Data.API.Types parseJSON :: Value -> Parser SpecRecord # parseJSONList :: Value -> Parser [SpecRecord] # | |
NFData SpecRecord Source # | |
Defined in Data.API.Types rnf :: SpecRecord -> () # | |
Lift SpecRecord Source # | |
Defined in Data.API.Types lift :: SpecRecord -> Q Exp # liftTyped :: SpecRecord -> Q (TExp SpecRecord) # |
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.
FieldType | |
|
SpecUnion is your classsic union type
SpecEnum is your classic enumerated type
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.
Type is either a list, Maybe, a named element of the API or a basic type
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
Eq APIType Source # | |
Show APIType Source # | |
IsString APIType Source # | It is sometimes helpful to write a type name directly as a string |
Defined in Data.API.Types fromString :: String -> APIType # | |
ToJSON APIType Source # | |
Defined in Data.API.Types | |
FromJSON APIType Source # | |
NFData APIType Source # | |
Defined in Data.API.Types | |
PP APIType Source # | |
Lift APIType Source # | |
data DefaultValue Source #
A default value for a field
Instances
Eq DefaultValue Source # | |
Defined in Data.API.Types (==) :: DefaultValue -> DefaultValue -> Bool # (/=) :: DefaultValue -> DefaultValue -> Bool # | |
Show DefaultValue Source # | |
Defined in Data.API.Types showsPrec :: Int -> DefaultValue -> ShowS # show :: DefaultValue -> String # showList :: [DefaultValue] -> ShowS # | |
ToJSON DefaultValue Source # | |
Defined in Data.API.Types toJSON :: DefaultValue -> Value # toEncoding :: DefaultValue -> Encoding # toJSONList :: [DefaultValue] -> Value # toEncodingList :: [DefaultValue] -> Encoding # | |
FromJSON DefaultValue Source # | |
Defined in Data.API.Types parseJSON :: Value -> Parser DefaultValue # parseJSONList :: Value -> Parser [DefaultValue] # | |
NFData DefaultValue Source # | |
Defined in Data.API.Types rnf :: DefaultValue -> () # | |
PP DefaultValue Source # | |
Defined in Data.API.PP pp :: DefaultValue -> String Source # | |
Lift DefaultValue Source # | |
Defined in Data.API.Types lift :: DefaultValue -> Q Exp # liftTyped :: DefaultValue -> Q (TExp DefaultValue) # |
the basic JSON types (N.B., no floating point numbers, yet)
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 |
Binary data is represented in JSON format as a base64-encoded string
Instances
Eq Binary Source # | |
Ord Binary Source # | |
Show Binary Source # | |
Arbitrary Binary Source # | |
ToJSON Binary Source # | |
Defined in Data.API.Types | |
FromJSON Binary Source # | |
NFData Binary Source # | |
Defined in Data.API.Types | |
SafeCopy Binary Source # | |
Serialise Binary Source # | |
Example Binary Source # | |
FromJSONWithErrs Binary Source # | |
Defined in Data.API.JSON |