Skip to content

Commit d3f49da

Browse files
committed
Add schemaGenWithFormats to support custom string generators
1 parent 340d86f commit d3f49da

File tree

2 files changed

+32
-11
lines changed

2 files changed

+32
-11
lines changed

src/Data/OpenApi/Schema/Generator.hs

Lines changed: 19 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ import Prelude ()
88
import Prelude.Compat
99

1010
import Control.Lens.Operators
11-
import Control.Monad (filterM)
1211
import Data.Aeson
1312
import Data.Aeson.Types
1413
import qualified Data.HashMap.Strict.InsOrd as M
@@ -19,8 +18,10 @@ import qualified Data.Set as S
1918
import Data.OpenApi
2019
import Data.OpenApi.Declare
2120
import Data.OpenApi.Internal.Schema.Validation (inferSchemaTypes)
21+
import Data.Text (Text)
2222
import qualified Data.Text as T
2323
import qualified Data.Vector as V
24+
import GHC.Stack (HasCallStack)
2425
import Test.QuickCheck (arbitrary)
2526
import Test.QuickCheck.Gen
2627
import Test.QuickCheck.Property
@@ -29,16 +30,19 @@ import Data.OpenApi.Aeson.Compat (fromInsOrdHashMap)
2930

3031
-- | Note: 'schemaGen' may 'error', if schema type is not specified,
3132
-- and cannot be inferred.
32-
schemaGen :: Definitions Schema -> Schema -> Gen Value
33-
schemaGen _ schema
33+
schemaGen :: HasCallStack => Definitions Schema -> Schema -> Gen Value
34+
schemaGen = schemaGenWithFormats (const Nothing)
35+
36+
schemaGenWithFormats :: HasCallStack => (Format -> Maybe (Gen Text)) -> Definitions Schema -> Schema -> Gen Value
37+
schemaGenWithFormats _ _ schema
3438
| Just cases <- schema ^. enum_ = elements cases
35-
schemaGen defns schema
39+
schemaGenWithFormats _ defns schema
3640
| Just variants <- schema ^. oneOf = schemaGen defns =<< elements (dereference defns <$> variants)
37-
schemaGen defns schema =
41+
schemaGenWithFormats formatGen defns schema =
3842
case schema ^. type_ of
3943
Nothing ->
4044
case inferSchemaTypes schema of
41-
[ inferredType ] -> schemaGen defns (schema & type_ ?~ inferredType)
45+
[ inferredType ] -> schemaGenWithFormats formatGen defns (schema & type_ ?~ inferredType)
4246
-- Gen is not MonadFail
4347
_ -> error "unable to infer schema type"
4448
Just OpenApiBoolean -> Bool <$> elements [True, False]
@@ -65,12 +69,16 @@ schemaGen defns schema =
6569
minLength' = fromMaybe 0 $ fromInteger <$> schema ^. minItems
6670
maxLength' = fromMaybe size $ fromInteger <$> schema ^. maxItems
6771
arrayLength <- choose (minLength', max minLength' maxLength')
68-
generatedArray <- vectorOf arrayLength $ schemaGen defns itemSchema
72+
generatedArray <- vectorOf arrayLength $ schemaGenWithFormats formatGen defns itemSchema
6973
return . Array $ V.fromList generatedArray
7074
OpenApiItemsArray refs ->
71-
let itemGens = schemaGen defns . dereference defns <$> refs
75+
let itemGens = schemaGenWithFormats formatGen defns . dereference defns <$> refs
7276
in fmap (Array . V.fromList) $ sequence itemGens
73-
Just OpenApiString -> do
77+
| otherwise -> error "invalid array"
78+
Just OpenApiString
79+
| Just gen <- formatGen =<< schema ^. format ->
80+
String <$> gen
81+
| otherwise -> do
7482
size <- getSize
7583
let minLength' = fromMaybe 0 $ fromInteger <$> schema ^. minLength
7684
let maxLength' = fromMaybe size $ fromInteger <$> schema ^. maxLength
@@ -90,11 +98,11 @@ schemaGen defns schema =
9098
numProps <- choose (minProps', max minProps' maxProps')
9199
let presentKeys = take numProps $ S.toList reqKeys ++ shuffledOptional
92100
let presentProps = M.filterWithKey (\k _ -> k `elem` presentKeys) props
93-
let gens = schemaGen defns <$> presentProps
101+
let gens = schemaGenWithFormats formatGen defns <$> presentProps
94102
additionalGens <- case schema ^. additionalProperties of
95103
Just (AdditionalPropertiesSchema addlSchema) -> do
96104
additionalKeys <- sequence . take (numProps - length presentProps) . repeat $ T.pack <$> arbitrary
97-
return . M.fromList $ zip additionalKeys (repeat . schemaGen defns $ dereference defns addlSchema)
105+
return . M.fromList $ zip additionalKeys (repeat . schemaGenWithFormats formatGen defns $ dereference defns addlSchema)
98106
_ -> return []
99107
x <- sequence $ gens <> additionalGens
100108
return . Object $ fromInsOrdHashMap x

test/Data/OpenApi/Schema/GeneratorSpec.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -91,6 +91,19 @@ spec = do
9191
prop "MissingProperty" $ shouldNotValidate (Proxy :: Proxy MissingProperty)
9292
prop "WrongPropType" $ shouldNotValidate (Proxy :: Proxy WrongPropType)
9393

94+
describe "schemaGenWithFormats" $ do
95+
it "supports custom string format generators" $ do
96+
let sch = mempty
97+
& type_ ?~ OpenApiString
98+
& format ?~ "custom"
99+
100+
let formatGen fmt = case fmt of
101+
"custom" -> Just (pure "custom")
102+
_ -> Nothing
103+
104+
value <- generate $ schemaGenWithFormats formatGen mempty sch
105+
value `shouldBe` String "custom"
106+
94107
-- =============================
95108
-- Data types and bunk instances
96109
-- =============================

0 commit comments

Comments
 (0)