Copyright | (c) 2015 Shohei Murayama |
---|---|
License | BSD3 |
Maintainer | Shohei Murayama <shohei.murayama@gmail.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
A generator for JSON Schemas from ADT.
- data Options = Options {}
- data FieldType = JSONSchemaPrim a => FieldType (Proxy a)
- defaultOptions :: Options
- generate :: JSONSchemaGen a => Proxy a -> ByteString
- generate' :: JSONSchemaGen a => Options -> Options -> Proxy a -> ByteString
- class JSONSchemaGen a where
- class JSONSchemaPrim a where
- convert :: Options -> Schema -> Value
- class GJSONSchemaGen f where
- genericToSchema :: (Generic a, GJSONSchemaGen (Rep a)) => Options -> Proxy a -> Schema
How to use this library
Example:
{-# LANGUAGE DeriveGeneric #-} import qualified Data.ByteString.Lazy.Char8 as BL import Data.JSON.Schema.Generator import Data.Proxy import GHC.Generics data User = User { name :: String , age :: Int , email :: Maybe String } deriving Generic instance JSONSchemaGen User main :: IO () main = BL.putStrLn $ generate (Proxy :: Proxy User)
Let's run the above script, we can get on stdout (the following json is formatted with jq):
{ "required": [ "name", "age", "email" ], "$schema": "http://json-schema.org/draft-04/schema#", "id": "Main.User", "title": "Main.User", "type": "object", "properties": { "email": { "type": [ "string", "null" ] }, "age": { "type": "integer" }, "name": { "type": "string" } } }
Genenerating JSON Schema
Options that specify how to generate schema definition automatically from your datatype.
Options | |
|
defaultOptions :: Options Source #
Default geerating Options
:
Options
{baseUri
= "" ,schemaIdSuffix
= "" ,refSchemaMap
= Map.empty }
:: JSONSchemaGen a | |
=> Proxy a | A proxy value of the type from which a schema will be generated. |
-> ByteString |
Generate a JSON Schema from a proxy value of a type. This uses the default options to generate schema in json format.
:: JSONSchemaGen a | |
=> Options | Schema generation |
-> Options | Encoding |
-> Proxy a | A proxy value of the type from which a schema will be generated. |
-> ByteString |
Generate a JSON Schema from a proxy vaulue of a type. This uses the specified options to generate schema in json format.
Type conversion
class JSONSchemaGen a where Source #
class JSONSchemaPrim a where Source #
Generic Schema class
class GJSONSchemaGen f where Source #
genericToSchema :: (Generic a, GJSONSchemaGen (Rep a)) => Options -> Proxy a -> Schema Source #