{-# LANGUAGE RecordWildCards #-}
-- |
-- Module:      Data.OpenApi.SchemaOptions
-- Maintainer:  Nickolay Kudasov <nickolay@getshoptv.com>
-- Stability:   experimental
--
-- Generic deriving options for @'ToParamSchema'@ and @'ToSchema'@.
module Data.OpenApi.SchemaOptions where

import qualified Data.Aeson.Types as Aeson

-- | Options that specify how to encode your type to Swagger schema.
data SchemaOptions = SchemaOptions
  { -- | Function applied to field labels. Handy for removing common record prefixes for example.
    SchemaOptions -> String -> String
fieldLabelModifier :: String -> String
    -- | Function applied to constructor tags which could be handy for lower-casing them for example.
  , SchemaOptions -> String -> String
constructorTagModifier :: String -> String
    -- | Function applied to datatype name.
  , SchemaOptions -> String -> String
datatypeNameModifier :: String -> String
    -- | If @'True'@ the constructors of a datatype, with all nullary constructors,
    -- will be encoded to a string enumeration schema with the constructor tags as possible values.
  , SchemaOptions -> Bool
allNullaryToStringTag :: Bool
    -- | Hide the field name when a record constructor has only one field, like a newtype.
  , SchemaOptions -> Bool
unwrapUnaryRecords :: Bool
    -- | Specifies how to encode constructors of a sum datatype.
  , SchemaOptions -> SumEncoding
sumEncoding :: Aeson.SumEncoding
  }

-- | Default encoding @'SchemaOptions'@.
--
-- @
-- 'SchemaOptions'
-- { 'fieldLabelModifier'     = id
-- , 'constructorTagModifier' = id
-- , 'datatypeNameModifier'   = id
-- , 'allNullaryToStringTag'  = True
-- , 'unwrapUnaryRecords'     = False
-- , 'sumEncoding'            = 'Aeson.defaultTaggedObject'
-- }
-- @
defaultSchemaOptions :: SchemaOptions
defaultSchemaOptions :: SchemaOptions
defaultSchemaOptions = SchemaOptions :: (String -> String)
-> (String -> String)
-> (String -> String)
-> Bool
-> Bool
-> SumEncoding
-> SchemaOptions
SchemaOptions
  { fieldLabelModifier :: String -> String
fieldLabelModifier = String -> String
forall a. a -> a
id
  , constructorTagModifier :: String -> String
constructorTagModifier = String -> String
forall a. a -> a
id
  , datatypeNameModifier :: String -> String
datatypeNameModifier = String -> String
forall a. a -> a
id
  , allNullaryToStringTag :: Bool
allNullaryToStringTag = Bool
True
  , unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
False
  , sumEncoding :: SumEncoding
sumEncoding = SumEncoding
Aeson.defaultTaggedObject
  }

-- | Convert 'Aeson.Options' to 'SchemaOptions'.
--
-- Specifically the following fields get copied:
--
-- * 'fieldLabelModifier'
-- * 'constructorTagModifier'
-- * 'allNullaryToStringTag'
-- * 'unwrapUnaryRecords'
--
-- Note that these fields have no effect on `SchemaOptions`:
--
-- * 'Aeson.omitNothingFields'
-- * 'Aeson.tagSingleConstructors'
--
-- The rest is defined as in 'defaultSchemaOptions'.
--
-- @since 2.2.1
--
fromAesonOptions :: Aeson.Options -> SchemaOptions
fromAesonOptions :: Options -> SchemaOptions
fromAesonOptions Options
opts = SchemaOptions
defaultSchemaOptions
  { fieldLabelModifier :: String -> String
fieldLabelModifier     = Options -> String -> String
Aeson.fieldLabelModifier     Options
opts
  , constructorTagModifier :: String -> String
constructorTagModifier = Options -> String -> String
Aeson.constructorTagModifier Options
opts
  , allNullaryToStringTag :: Bool
allNullaryToStringTag  = Options -> Bool
Aeson.allNullaryToStringTag  Options
opts
  , unwrapUnaryRecords :: Bool
unwrapUnaryRecords     = Options -> Bool
Aeson.unwrapUnaryRecords     Options
opts
  , sumEncoding :: SumEncoding
sumEncoding            = Options -> SumEncoding
Aeson.sumEncoding            Options
opts
  }