jsonschema-gen-0.3.0.1: JSON Schema generator from Algebraic data type

Copyright(c) 2015 Shohei Murayama
LicenseBSD3
MaintainerShohei Murayama <shohei.murayama@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.JSON.Schema.Generator

Contents

Description

A generator for JSON Schemas from ADT.

Synopsis

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

data Options Source

Options that specify how to generate schema definition automatically from your datatype.

Constructors

Options 

Fields

baseUri :: String

schema id prefix.

schemaIdSuffix :: String

schema id suffix. File extension for example.

typeRefMap :: Map TypeRep String

a mapping from datatypes to referenced schema ids.

fieldTypeMap :: Map String FieldType

a mapping to assign a preffered type to a field.

Instances

data FieldType Source

Constructors

forall a . JSONSchemaPrim a => FieldType (Proxy a) 

defaultOptions :: Options Source

Default geerating Options:

Options
{ baseUri        = ""
, schemaIdSuffix = ""
, refSchemaMap   = Map.empty
}

generate Source

Arguments

:: 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.

generate' Source

Arguments

:: JSONSchemaGen a 
=> Options

Schema generation Options.

-> Options

Encoding Options of aeson.

-> 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

Minimal complete definition

Nothing

Methods

toSchema :: Options -> Proxy a -> Schema Source

convert :: Options -> Schema -> Value Source

Generic Schema class

class GJSONSchemaGen f where Source

Methods

gToSchema :: Options -> Proxy (f a) -> Schema Source

Instances

(Datatype d, SchemaType f) => GJSONSchemaGen (D1 d f)