| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Data.API.Types
Contents
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
Constructors
| APINode | |
TypeName must contain a valid Haskell type constructor
Instances
| FromJSON TypeName Source # | |
| ToJSON TypeName Source # | |
| Defined in Data.API.Types | |
| PP TypeName Source # | |
| IsString TypeName Source # | |
| Defined in Data.API.Types Methods fromString :: String -> TypeName # | |
| Show TypeName Source # | |
| NFData TypeName Source # | |
| Defined in Data.API.Types | |
| Eq TypeName Source # | |
| Ord TypeName Source # | |
| Defined in Data.API.Types | |
| 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)
Constructors
| FieldName | |
| Fields 
 | |
Instances
| FromJSON FieldName Source # | |
| ToJSON FieldName Source # | |
| Defined in Data.API.Types | |
| PP FieldName Source # | |
| IsString FieldName Source # | |
| Defined in Data.API.Types Methods fromString :: String -> FieldName # | |
| Show FieldName Source # | |
| NFData FieldName Source # | |
| Defined in Data.API.Types | |
| Eq FieldName Source # | |
| Ord 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
Constructors
| SpNewtype SpecNewtype | |
| SpRecord SpecRecord | |
| SpUnion SpecUnion | |
| SpEnum SpecEnum | |
| SpSynonym APIType | 
data SpecNewtype Source #
SpecNewtype elements are isomorphisms of string, inetgers or booleans
Instances
| FromJSON SpecNewtype Source # | |
| Defined in Data.API.Types | |
| ToJSON SpecNewtype Source # | |
| Defined in Data.API.Types Methods toJSON :: SpecNewtype -> Value # toEncoding :: SpecNewtype -> Encoding # toJSONList :: [SpecNewtype] -> Value # toEncodingList :: [SpecNewtype] -> Encoding # | |
| Show SpecNewtype Source # | |
| Defined in Data.API.Types Methods showsPrec :: Int -> SpecNewtype -> ShowS # show :: SpecNewtype -> String # showList :: [SpecNewtype] -> ShowS # | |
| NFData SpecNewtype Source # | |
| Defined in Data.API.Types Methods rnf :: SpecNewtype -> () # | |
| Eq SpecNewtype Source # | |
| Defined in Data.API.Types | |
| Lift SpecNewtype Source # | |
| 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 | |
Instances
| FromJSON SpecRecord Source # | |
| Defined in Data.API.Types | |
| ToJSON SpecRecord Source # | |
| Defined in Data.API.Types Methods toJSON :: SpecRecord -> Value # toEncoding :: SpecRecord -> Encoding # toJSONList :: [SpecRecord] -> Value # toEncodingList :: [SpecRecord] -> Encoding # | |
| Show SpecRecord Source # | |
| Defined in Data.API.Types Methods showsPrec :: Int -> SpecRecord -> ShowS # show :: SpecRecord -> String # showList :: [SpecRecord] -> ShowS # | |
| NFData SpecRecord Source # | |
| Defined in Data.API.Types Methods rnf :: SpecRecord -> () # | |
| Eq SpecRecord Source # | |
| Defined in Data.API.Types | |
| Lift SpecRecord Source # | |
| Defined in Data.API.Types Methods lift :: Quote m => SpecRecord -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => SpecRecord -> Code m 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.
Constructors
| FieldType | |
| Fields 
 | |
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
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
| FromJSON APIType Source # | |
| ToJSON APIType Source # | |
| Defined in Data.API.Types | |
| PP APIType Source # | |
| IsString APIType Source # | It is sometimes helpful to write a type name directly as a string | 
| Defined in Data.API.Types Methods fromString :: String -> APIType # | |
| Show APIType Source # | |
| NFData APIType Source # | |
| Defined in Data.API.Types | |
| Eq APIType Source # | |
| Lift APIType Source # | |
data DefaultValue Source #
A default value for a field
Constructors
| DefValList | |
| DefValMaybe | |
| DefValString Text | |
| DefValBool Bool | |
| DefValInt Int | |
| DefValUtc UTCTime | 
Instances
| FromJSON DefaultValue Source # | |
| Defined in Data.API.Types | |
| ToJSON DefaultValue Source # | |
| Defined in Data.API.Types Methods toJSON :: DefaultValue -> Value # toEncoding :: DefaultValue -> Encoding # toJSONList :: [DefaultValue] -> Value # toEncodingList :: [DefaultValue] -> Encoding # | |
| PP DefaultValue Source # | |
| Defined in Data.API.PP Methods pp :: DefaultValue -> String Source # | |
| Show DefaultValue Source # | |
| Defined in Data.API.Types Methods showsPrec :: Int -> DefaultValue -> ShowS # show :: DefaultValue -> String # showList :: [DefaultValue] -> ShowS # | |
| NFData DefaultValue Source # | |
| Defined in Data.API.Types Methods rnf :: DefaultValue -> () # | |
| Eq DefaultValue Source # | |
| Defined in Data.API.Types | |
| Lift DefaultValue Source # | |
| Defined in Data.API.Types Methods lift :: Quote m => DefaultValue -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => DefaultValue -> Code m DefaultValue # | |
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 | 
Binary data is represented in JSON format as a base64-encoded string
Constructors
| Binary | |
| Fields | |
Instances
| Arbitrary Binary Source # | |
| FromJSON Binary Source # | |
| ToJSON Binary Source # | |
| Defined in Data.API.Types | |
| FromJSONWithErrs Binary Source # | |
| Defined in Data.API.JSON Methods parseJSONWithErrs :: Value -> ParserWithErrs Binary Source # | |
| Example Binary Source # | |
| Show Binary Source # | |
| NFData Binary Source # | |
| Defined in Data.API.Types | |
| Eq Binary Source # | |
| Ord Binary Source # | |
| SafeCopy Binary Source # | |
| Serialise Binary Source # | |