jsonschema: JSON Schema derivation and validation

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Provides the ToJSONSchema type class and validation helpers for generating JSON Schema 2020-12 documents from Haskell types and validating JSON values at runtime. The library includes a generic deriving strategy that handles recursive data types, sum-tag encoding, and refined handling of arrays and enumerations. Validation implements the core and applicator vocabularies, including `$defs` and local `$ref` resolution, pragmatic support for `unevaluated*` keywords, and detailed error traces.


[Skip to Readme]

Properties

Versions 0.2.0.0, 0.2.0.0
Change log CHANGELOG.md
Dependencies aeson (>=2.2 && <2.3), base (>=4.18 && <4.19), containers (>=0.6.7 && <0.6.8), regex-tdfa (>=1.3.2 && <1.3.3), scientific (>=0.3.8 && <0.3.9), text (>=2.0 && <2.1), vector (>=0.13 && <0.14) [details]
License MPL-2.0
Author DPella AB
Maintainer matti@dpella.io, lobo@dpella.io
Category Data, JSON
Home page https://github.com/DPella/jsonschema
Bug tracker https://github.com/DPella/jsonschema/issues
Uploaded by tritlo at 2025-10-21T14:26:10Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for jsonschema-0.2.0.0

[back to package description]

jsonschema

Haskell library for deriving and validating JSON Schema (2020-12).

This library provides:

Features

Notes and limits:

Quick Start

Add the library to your build, then import the high-level module:

import GHC.Generics (Generic)
import Data.Aeson (ToJSON, Value, object, (.=))
import Data.Proxy (Proxy(..))
import Data.Text (Text)
import Data.JSON.JSONSchema      -- ToJSONSchema(..), Proxy(..), validateJSONSchema
import JSONSchema.Validation     -- validate / validateWithErrors (optional)

1) Derive a schema for your type

data Person = Person
  { name :: Text
  , age  :: Int
  } deriving (Show, Eq, Generic)

instance ToJSON Person
instance ToJSONSchema Person

-- Produce the JSON Schema (as an Aeson Value)
personSchema :: Value
personSchema = toJSONSchema (Proxy :: Proxy Person)

What you get (shape, simplified):

{
  "$defs": {
    "Person": {
      "type": "object",
      "properties": {
        "name": {"type": "string"},
        "age":  {"type": "integer"}
      },
      "additionalProperties": false,
      "required": ["name", "age"]
    }
  },
  "$ref": "#/$defs/Person"
}

Sum types are tagged. For example:

data Shape
  = Circle Double
  | Rectangle Double Double
  deriving (Show, Eq, Generic)

instance ToJSON Shape
instance ToJSONSchema Shape

shapeSchema :: Value
shapeSchema = toJSONSchema (Proxy :: Proxy Shape)

Non-record constructors encode as objects like { tag: { const: "Circle" }, contents: <payload> }. Record constructors encode as objects with a tag plus their named fields.

2) Validate data against a schema

Use the simple boolean check:

import Data.Aeson (toJSON)

valid :: Bool
valid = validateJSONSchema personSchema (toJSON (Person "Alice" 30))

Or collect all validation errors:

import JSONSchema.Validation (validate, validateWithErrors, ValidationError(..))

case validate personSchema (toJSON (Person "Alice" 30)) of
  Right ()   -> putStrLn "OK"
  Left errs  -> mapM_ print errs  -- includes JSON Pointer-like paths

You can validate any Value against any schema, including hand-written schemas:

let schema = object
      [ "type" .= ("object" :: Text)
      , "properties" .= object ["name" .= object ["type" .= ("string" :: Text)]]
      , "required" .= (["name"] :: [Text])
      ]
in validateJSONSchema schema (object ["name" .= ("Bob" :: Text)])

3) Custom schemas for special types

Provide an explicit instance when you need a specific schema shape:

newtype UUID = UUID Text

instance ToJSONSchema UUID where
  toJSONSchema _ = object
    [ "type"      .= ("string" :: Text)
    , "minLength" .= (36 :: Int)
    , "maxLength" .= (36 :: Int)
    ]

Tips

Development

License

Released under the Mozilla Public License 2.0 by DPella AB. See LICENSE for details.