| Copyright | (c) DPella AB 2025 |
|---|---|
| License | LicenseRef-AllRightsReserved |
| Maintainer | <matti@dpella.io>, <lobo@dpella.io> |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.JSON.JSONSchema
Description
JSON Schema generation for Haskell types.
This module provides a type class and generic implementation for automatically deriving JSON Schema descriptions from Haskell data types. The generated schemas follow the JSON Schema 2020-12 specification.
Usage
Define instances using the default generic implementation:
data Person = Person
{ name :: Text
, age :: Int
} deriving (Generic)
instance ToJSONSchema Person
Or provide custom instances for more control:
instance ToJSONSchema UUID where
toJSONSchema _ = object
[ "type" .= ("string" :: Text)
, "minLength" .= 36
, "maxLength" .= 36
]
Synopsis
- class ToJSONSchema a where
- toJSONSchema :: Proxy a -> Value
- data Proxy (t :: k) = Proxy
- validateJSONSchema :: Value -> Value -> Bool
Documentation
class ToJSONSchema a where Source #
Type class for converting Haskell types to JSON Schema.
The class provides a default implementation using GHC generics, which works for most algebraic data types. Custom instances can be defined for types requiring special schema representations.
Minimal complete definition
Nothing
Methods
toJSONSchema :: Proxy a -> Value Source #
Generate a JSON Schema for the given type.
The Proxy argument carries the type information without requiring an actual value of that type.
>>>toJSONSchema (Proxy :: Proxy Bool){"type": "boolean"}
Instances
| ToJSONSchema Text Source # | Text instance. |
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema String Source # | String instance with overlapping to handle String as a special case, and not as [Char] |
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema Integer Source # | Arbitrary precision integer schema instance. |
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema Bool Source # | Boolean schema instance. |
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema Double Source # | Double precision floating point schema instance. |
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema Float Source # | Single precision floating point schema instance. |
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema Int Source # | Machine integer schema instance. |
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema a => ToJSONSchema (Maybe a) Source # | Maybe schema instance allowing null values. A Maybe value can be either the wrapped type or null:
|
Defined in Data.JSON.ToJSONSchema | |
| ToJSONSchema a => ToJSONSchema [a] Source # | List schema instance for homogeneous arrays. |
Defined in Data.JSON.ToJSONSchema Methods toJSONSchema :: Proxy [a] -> Value Source # | |
| (ToJSONSchema a, ToJSONSchema b) => ToJSONSchema (Either a b) Source # | Either schema instance for tagged unions. Encodes as Aeson's default representation with Left/Right tags:
|
Defined in Data.JSON.ToJSONSchema | |
Proxy is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically, is a safer alternative to the
Proxy :: Proxy a idiom.undefined :: a
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy |
Instances
| Generic1 (Proxy :: k -> Type) | |
| FromJSON1 (Proxy :: Type -> Type) | |
Defined in Data.Aeson.Types.FromJSON | |
| ToJSON1 (Proxy :: Type -> Type) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> Proxy a -> Value # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [Proxy a] -> Value # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> Proxy a -> Encoding # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [Proxy a] -> Encoding # liftOmitField :: (a -> Bool) -> Proxy a -> Bool # | |
| Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
| Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| FromJSON (Proxy a) | |
Defined in Data.Aeson.Types.FromJSON | |
| ToJSON (Proxy a) | |
| Monoid (Proxy s) | Since: base-4.7.0.0 |
| Semigroup (Proxy s) | Since: base-4.9.0.0 |
| Bounded (Proxy t) | Since: base-4.7.0.0 |
| Enum (Proxy s) | Since: base-4.7.0.0 |
| Generic (Proxy t) | |
| Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
| Read (Proxy t) | Since: base-4.7.0.0 |
| Show (Proxy s) | Since: base-4.7.0.0 |
| Eq (Proxy s) | Since: base-4.7.0.0 |
| Ord (Proxy s) | Since: base-4.7.0.0 |
| type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
| type Rep (Proxy t) | Since: base-4.6.0.0 |