Skip to content
Open
Show file tree
Hide file tree
Changes from 5 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
9 changes: 6 additions & 3 deletions schematic.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ cabal-version: >=1.10
library
exposed-modules: Data.Schematic
, Data.Schematic.DSL
, Data.Schematic.Compat
, Data.Schematic.Generator
, Data.Schematic.Generator.Regex
, Data.Schematic.Instances
Expand All @@ -25,6 +26,7 @@ library
, Data.Schematic.Migration
, Data.Schematic.Path
, Data.Schematic.Schema
, Data.Schematic.Constraints
, Data.Schematic.Validation
, Data.Schematic.Verifier
, Data.Schematic.Verifier.Array
Expand Down Expand Up @@ -65,7 +67,7 @@ library
, TypeOperators
, TypeSynonymInstances
, UndecidableInstances
build-depends: base >=4.11 && <4.13
build-depends: base >=4.10 && <4.13
, bytestring
, aeson >= 1
, containers
Expand All @@ -75,7 +77,8 @@ library
, regex-tdfa
, regex-tdfa-text
, scientific
, singletons >= 2.4
, singletons
-- >= 2.4
, smallcheck
, tagged
, template-haskell
Expand All @@ -95,7 +98,7 @@ test-suite spec
default-language: Haskell2010
build-depends: HUnit
, aeson >= 1
, base >=4.11 && <4.13
, base >=4.10 && <4.13
, bytestring
, containers
, hjsonschema
Expand Down
4 changes: 4 additions & 0 deletions src/Data/Schematic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ module Data.Schematic
, module Data.Schematic.Lens
, module Data.Schematic.Migration
, module Data.Schematic.Schema
, module Data.Schematic.Constraints
, module Data.Schematic.Compat
, decodeAndValidateJson
, parseAndValidateJson
, parseAndValidateJsonBy
Expand All @@ -27,6 +29,8 @@ import Data.Aeson as J
import Data.Aeson.Types as J
import Data.ByteString.Lazy as BL
import Data.Functor.Identity as F
import Data.Schematic.Compat
import Data.Schematic.Constraints
import Data.Schematic.DSL
import Data.Schematic.Helpers
import Data.Schematic.JsonSchema
Expand Down
15 changes: 15 additions & 0 deletions src/Data/Schematic/Compat.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
{-# LANGUAGE CPP #-}
module Data.Schematic.Compat where

import Data.Singletons
import Data.Singletons.Prelude
import Data.Singletons.TypeLits

type DeNat = Demote Nat
-- ^ Demote Nat is depends on version of singletons

#if !MIN_VERSION_base(4,11,0)
type (:+++) a b = (:++) a b
#else
type (:+++) a b = (++) a b
#endif
41 changes: 41 additions & 0 deletions src/Data/Schematic/Constraints.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
{-# LANGUAGE EmptyCase #-}
{-# OPTIONS_GHC -fprint-explicit-kinds #-}

module Data.Schematic.Constraints where

import Data.Schematic.Compat
import Data.Singletons.Prelude
import Data.Singletons.TH
import Data.Singletons.TypeLits
import Data.Text as T
import GHC.Generics (Generic)


singletons [d|
data TextConstraint' s n
= TEq n
| TLt n
| TLe n
| TGt n
| TGe n
| TRegex s
| TEnum [s]
deriving (Eq, Show, Generic)

data NumberConstraint' n
= NLe n
| NLt n
| NGt n
| NGe n
| NEq n
deriving (Eq, Show, Generic)

data ArrayConstraint' n = AEq n deriving (Eq, Show, Generic)
|]

type TextConstraintT = TextConstraint' Text DeNat
type TextConstraint = TextConstraint' Symbol Nat
type NumberConstraintT = NumberConstraint' DeNat
type NumberConstraint = NumberConstraint' Nat
type ArrayConstraintT = ArrayConstraint' DeNat
type ArrayConstraint = ArrayConstraint' Nat
71 changes: 18 additions & 53 deletions src/Data/Schematic/Generator.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,15 @@
module Data.Schematic.Generator where

import Data.Maybe
import Data.Schematic.Generator.Regex
import {-# SOURCE #-} Data.Schematic.Schema
import Data.Schematic.Verifier
import Data.Scientific
import Data.Text (Text, pack)
import qualified Data.Vector as V
import Test.SmallCheck.Series
import Control.Applicative
import Data.Maybe
import Data.Schematic.Constraints
import Data.Schematic.Generator.Regex
import Data.Schematic.Verifier
import Data.Scientific
import Data.Text (Text, pack)
-- import qualified Data.Vector as V
import Test.SmallCheck.Series


maxHigh :: Int
maxHigh = 30
Expand All @@ -30,35 +32,18 @@ textLengthSeries =
textEnumSeries :: Monad m => [Text] -> Series m Text
textEnumSeries enum = generate $ \depth -> take depth enum

textSeries :: Monad m => [DemotedTextConstraint] -> Series m Text
textSeries cs = do
let mvcs = verifyTextConstraints cs
case mvcs of
Just vcs -> do
n <- textSeries' vcs
pure n
Nothing -> pure "error"
textSeries :: Monad m => [TextConstraintT] -> Series m Text
textSeries cs = maybe (pure "error") textSeries' $ verifyTextConstraints cs

textSeries' :: Monad m => [VerifiedTextConstraint] -> Series m Text
textSeries' [] = pure "sample"
textSeries' vcs = do
let enums = listToMaybe [x | VTEnum x <- vcs]
case enums of
Just e -> textEnumSeries e
Nothing -> do
let regexps = listToMaybe [x | VTRegex x _ _ <- vcs]
case regexps of
Just e -> regexSeries e
Nothing -> textLengthSeries vcs
textSeries' vcs
= fromMaybe (textLengthSeries vcs)
$ textEnumSeries <$> listToMaybe [x | VTEnum x <- vcs]
<|> regexSeries <$> listToMaybe [x | VTRegex x _ _ <- vcs]

numberSeries :: Monad m => [DemotedNumberConstraint] -> Series m Scientific
numberSeries cs = do
let mvcs = verifyNumberConstraints cs
case mvcs of
Just vcs -> do
n <- numberSeries' vcs
pure $ n
Nothing -> pure 0
numberSeries :: Monad m => [NumberConstraintT] -> Series m Scientific
numberSeries cs = maybe (pure 0) numberSeries' $ verifyNumberConstraints cs

numberSeries' :: Monad m => VerifiedNumberConstraint -> Series m Scientific
numberSeries' =
Expand All @@ -69,23 +54,3 @@ numberSeries' =
h = fromMaybe maxHigh (fromIntegral <$> mh) - 1
n <- generate $ \depth -> take depth [l .. h]
pure $ fromIntegral n

arraySeries
:: (Monad m, Serial m (JsonRepr s))
=> [DemotedArrayConstraint]
-> Series m (V.Vector (JsonRepr s))
arraySeries cs = do
let mvcs = verifyArrayConstraint cs
case mvcs of
Just vcs -> arraySeries' vcs
Nothing -> pure V.empty

arraySeries'
:: forall m s. (Monad m, Serial m (JsonRepr s))
=> Maybe VerifiedArrayConstraint
-> Series m (V.Vector (JsonRepr s))
arraySeries' ml = do
objs <- V.replicateM (maybe minRepeat f ml) (series :: Series m (JsonRepr s))
pure $ objs
where
f (VAEq l) = fromIntegral l
2 changes: 1 addition & 1 deletion src/Data/Schematic/Helpers.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Data.Schematic.Helpers where

import Data.Schematic.Schema
import Data.Schematic.Constraints
import GHC.TypeLits


Expand Down
63 changes: 32 additions & 31 deletions src/Data/Schematic/JsonSchema.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}

module Data.Schematic.JsonSchema
( toJsonSchema
Expand All @@ -14,6 +14,7 @@ import Data.Foldable as F
import Data.HashMap.Strict as H
import Data.List as L
import Data.List.NonEmpty as NE
import Data.Schematic.Constraints
import Data.Schematic.Schema as S
import Data.Set as Set
import Data.Singletons
Expand All @@ -26,40 +27,40 @@ import JSONSchema.Validator.Draft4 as D4
draft4 :: Text
draft4 = "http://json-schema.org/draft-04/schema#"

textConstraint :: DemotedTextConstraint -> State D4.Schema ()
textConstraint (DTEq n) = modify $ \s -> s
textConstraint :: TextConstraintT -> State D4.Schema ()
textConstraint (TEq n) = modify $ \s -> s
{ _schemaMinLength = pure $ fromIntegral n
, _schemaMaxLength = pure $ fromIntegral n }
textConstraint (DTLt n) = modify $ \s -> s
textConstraint (TLt n) = modify $ \s -> s
{ _schemaMaxLength = pure . fromIntegral $ n + 1 }
textConstraint (DTLe n) = modify $ \s -> s
textConstraint (TLe n) = modify $ \s -> s
{ _schemaMaxLength = pure . fromIntegral $ n }
textConstraint (DTGt n) =
textConstraint (TGt n) =
let n' = if n == 0 then 0 else n - 1
in modify $ \s -> s { _schemaMinLength = pure . fromIntegral $ n' }
textConstraint (DTGe n) = modify $ \s -> s
textConstraint (TGe n) = modify $ \s -> s
{ _schemaMinLength = pure . fromIntegral $ n }
textConstraint (DTRegex r) = modify $ \s -> s { _schemaPattern = pure r }
textConstraint (DTEnum ss) =
textConstraint (TRegex r) = modify $ \s -> s { _schemaPattern = pure r }
textConstraint (TEnum ss) =
let ss' = if F.length ss == 0 then [] else NE.fromList $ J.String <$> ss
in modify $ \s -> s { _schemaEnum = pure ss' }

numberConstraint :: DemotedNumberConstraint -> State D4.Schema ()
numberConstraint (DNLe n) = modify $ \s -> s
numberConstraint :: NumberConstraintT -> State D4.Schema ()
numberConstraint (NLe n) = modify $ \s -> s
{ _schemaMaximum = pure . fromIntegral $ n }
numberConstraint (DNLt n) = modify $ \s -> s
numberConstraint (NLt n) = modify $ \s -> s
{ _schemaMaximum = pure . fromIntegral $ n + 1 }
numberConstraint (DNGt n) = modify $ \s -> s
numberConstraint (NGt n) = modify $ \s -> s
{ _schemaMinimum = pure . fromIntegral $ n }
numberConstraint (DNGe n) =
numberConstraint (NGe n) =
let n' = if n == 0 then 0 else n - 1
in modify $ \s -> s { _schemaMinimum = pure . fromIntegral $ n' }
numberConstraint (DNEq n) = modify $ \s -> s
numberConstraint (NEq n) = modify $ \s -> s
{ _schemaMinimum = pure $ fromIntegral n
, _schemaMaximum = pure $ fromIntegral n }

arrayConstraint :: DemotedArrayConstraint -> State D4.Schema ()
arrayConstraint (DAEq _) = pure ()
arrayConstraint :: ArrayConstraintT -> State D4.Schema ()
arrayConstraint (AEq _) = pure ()

toJsonSchema
:: forall proxy schema
Expand All @@ -71,41 +72,41 @@ toJsonSchema _ = do
pure $ js { _schemaVersion = pure draft4 }

toJsonSchema'
:: DemotedSchema
:: SchemaT
-> Maybe D4.Schema
toJsonSchema' = \case
DSchemaText tcs ->
SchemaText tcs ->
pure $ execState (traverse_ textConstraint tcs) $ emptySchema
{ _schemaType = pure $ TypeValidatorString D4.SchemaString }
DSchemaNumber ncs ->
S.SchemaNumber ncs ->
pure $ execState (traverse_ numberConstraint ncs) $ emptySchema
{ _schemaType = pure $ TypeValidatorString D4.SchemaNumber }
DSchemaBoolean -> pure $ emptySchema
S.SchemaBoolean -> pure $ emptySchema
{ _schemaType = pure $ TypeValidatorString D4.SchemaBoolean }
DSchemaObject objs -> do
S.SchemaObject objs -> do
res <- for objs $ \(n,s) -> do
s' <- toJsonSchema' s
pure (n, s')
let
nonOpt = \case
(_, DSchemaOptional _) -> False
_ -> True
(_, SchemaOptional _) -> False
_ -> True
pure $ emptySchema
{ _schemaType = pure $ TypeValidatorString D4.SchemaObject
, _schemaRequired = pure $ Set.fromList $ fst <$> L.filter nonOpt objs
, _schemaProperties = pure $ H.fromList res }
DSchemaArray acs sch -> do
S.SchemaArray acs sch -> do
res <- toJsonSchema' sch
pure $ execState (traverse_ arrayConstraint acs) $ emptySchema
{ _schemaType = pure $ TypeValidatorString D4.SchemaArray
, _schemaItems = pure $ ItemsObject res }
DSchemaNull -> pure $ emptySchema
S.SchemaNull -> pure $ emptySchema
{ _schemaType = pure $ TypeValidatorString D4.SchemaNull }
DSchemaOptional sch -> do
snull <- toJsonSchema' DSchemaNull
SchemaOptional sch -> do
snull <- toJsonSchema' S.SchemaNull
sres <- toJsonSchema' sch
pure $ emptySchema { _schemaOneOf = pure (snull :| [sres]) }
DSchemaUnion sch -> do
SchemaUnion sch -> do
schemaUnion <- traverse toJsonSchema' sch >>= \case
[] -> Nothing
x -> Just x
Expand Down
5 changes: 3 additions & 2 deletions src/Data/Schematic/Migration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
module Data.Schematic.Migration where

import Data.Kind
import Data.Schematic.Compat
import Data.Schematic.DSL
import Data.Schematic.Lens
import Data.Schematic.Path
Expand Down Expand Up @@ -43,8 +44,8 @@ type family SchemaByKey (fs :: [(Symbol, Schema)]) (s :: Symbol) :: Schema where
SchemaByKey ( '(a, s) ': tl) fn = SchemaByKey tl fn

type family DeleteKey (acc :: [(Symbol, Schema)]) (fn :: Symbol) (fs :: [(Symbol, Schema)]) :: [(Symbol, Schema)] where
DeleteKey acc fn ('(fn, a) ': tl) = acc ++ tl
DeleteKey acc fn (fna ': tl) = acc ++ (fna ': tl)
DeleteKey acc fn ('(fn, a) ': tl) = acc :+++ tl
DeleteKey acc fn (fna ': tl) = acc :+++ (fna ': tl)

type family UpdateKey
(fn :: Symbol)
Expand Down
8 changes: 6 additions & 2 deletions src/Data/Schematic/Path.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,13 @@
{-# LANGUAGE CPP #-}
module Data.Schematic.Path where

import Data.Foldable as F
import Data.Singletons.Prelude
import Data.Singletons.TypeLits
import Data.Text as T
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif


data PathSegment = Key Symbol | Ix Nat
Expand All @@ -23,11 +27,11 @@ demotePath :: Sing (ps :: [PathSegment]) -> [DemotedPathSegment]
demotePath = go []
where
go :: [DemotedPathSegment] -> Sing (ps :: [PathSegment]) -> [DemotedPathSegment]
go acc SNil = acc
go acc SNil = acc
go acc (SCons p ps) = go (acc ++ [demotePathSeg p]) ps
demotePathSeg :: Sing (ps :: PathSegment) -> DemotedPathSegment
demotePathSeg (SKey s) = DKey $ T.pack $ withKnownSymbol s $ symbolVal s
demotePathSeg (SIx n) = DIx $ withKnownNat n $ fromIntegral $ natVal n
demotePathSeg (SIx n) = DIx $ withKnownNat n $ fromIntegral $ natVal n

demotedPathToText :: [DemotedPathSegment] -> JSONPath
demotedPathToText = JSONPath . F.foldl' renderPathSegment ""
Expand Down
Loading