{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE OverloadedStrings #-}
module OpenAPI.Generate.OptParse.Configuration
( Configuration (..),
getConfiguration,
)
where
import Autodocodec
import Autodocodec.Yaml (readYamlConfigFile)
import Data.Aeson (FromJSON, ToJSON)
import Data.Text (Text)
import qualified Data.Text as T
import qualified OpenAPI.Generate.Log as OAL
import OpenAPI.Generate.OptParse.Types
import Path.IO
data Configuration = Configuration
{ Configuration -> Maybe Text
configOpenApiSpecification :: !(Maybe Text),
Configuration -> Maybe Text
configOutputDir :: !(Maybe Text),
Configuration -> Maybe Text
configPackageName :: !(Maybe Text),
Configuration -> Maybe Text
configModuleName :: !(Maybe Text),
Configuration -> Maybe LogSeverity
configLogLevel :: !(Maybe OAL.LogSeverity),
Configuration -> Maybe Bool
configForce :: !(Maybe Bool),
Configuration -> Maybe Bool
configIncremental :: !(Maybe Bool),
Configuration -> Maybe Bool
configDryRun :: !(Maybe Bool),
Configuration -> Maybe Bool
configDoNotGenerateStackProject :: !(Maybe Bool),
Configuration -> Maybe Bool
configGenerateNixFiles :: !(Maybe Bool),
Configuration -> Maybe Bool
configOmitAdditionalOperationFunctions :: !(Maybe Bool),
Configuration -> Maybe Bool
configGenerateOptionalEmptyRequestBody :: !(Maybe Bool),
Configuration -> Maybe Bool
configUseNumberedVariantConstructors :: !(Maybe Bool),
Configuration -> Maybe Bool
configUseFloatWithArbitraryPrecision :: !(Maybe Bool),
Configuration -> Maybe Bool
configUseIntWithArbitraryPrecision :: !(Maybe Bool),
Configuration -> Maybe Bool
configUseDateTypesAsString :: !(Maybe Bool),
Configuration -> Maybe Bool
configConvertToCamelCase :: !(Maybe Bool),
Configuration -> Maybe Text
configPropertyTypeSuffix :: !(Maybe Text),
Configuration -> Maybe Text
configResponseTypeSuffix :: !(Maybe Text),
Configuration -> Maybe Text
configResponseBodyTypeSuffix :: !(Maybe Text),
Configuration -> Maybe Text
configRequestBodyTypeSuffix :: !(Maybe Text),
Configuration -> Maybe Text
configArrayItemTypeSuffix :: !(Maybe Text),
Configuration -> Maybe Text
configNonNullableTypeSuffix :: !(Maybe Text),
Configuration -> Maybe Text
configParametersTypeSuffix :: !(Maybe Text),
Configuration -> Maybe Text
configParameterQueryPrefix :: !(Maybe Text),
Configuration -> Maybe Text
configParameterPathPrefix :: !(Maybe Text),
Configuration -> Maybe Text
configParameterCookiePrefix :: !(Maybe Text),
:: !(Maybe Text),
Configuration -> Maybe [Text]
configOperationsToGenerate :: !(Maybe [Text]),
Configuration -> Maybe [Text]
configOpaqueSchemas :: !(Maybe [Text]),
Configuration -> Maybe [Text]
configWhiteListedSchemas :: !(Maybe [Text]),
Configuration -> Maybe Bool
configOutputAllSchemas :: !(Maybe Bool),
Configuration -> Maybe FixedValueStrategy
configFixedValueStrategy :: !(Maybe FixedValueStrategy),
Configuration -> Maybe Bool
configShortenSingleFieldObjects :: !(Maybe Bool)
}
deriving stock (Int -> Configuration -> ShowS
[Configuration] -> ShowS
Configuration -> String
(Int -> Configuration -> ShowS)
-> (Configuration -> String)
-> ([Configuration] -> ShowS)
-> Show Configuration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Configuration -> ShowS
showsPrec :: Int -> Configuration -> ShowS
$cshow :: Configuration -> String
show :: Configuration -> String
$cshowList :: [Configuration] -> ShowS
showList :: [Configuration] -> ShowS
Show, Configuration -> Configuration -> Bool
(Configuration -> Configuration -> Bool)
-> (Configuration -> Configuration -> Bool) -> Eq Configuration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Configuration -> Configuration -> Bool
== :: Configuration -> Configuration -> Bool
$c/= :: Configuration -> Configuration -> Bool
/= :: Configuration -> Configuration -> Bool
Eq)
deriving (Maybe Configuration
Value -> Parser [Configuration]
Value -> Parser Configuration
(Value -> Parser Configuration)
-> (Value -> Parser [Configuration])
-> Maybe Configuration
-> FromJSON Configuration
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Configuration
parseJSON :: Value -> Parser Configuration
$cparseJSONList :: Value -> Parser [Configuration]
parseJSONList :: Value -> Parser [Configuration]
$comittedField :: Maybe Configuration
omittedField :: Maybe Configuration
FromJSON, [Configuration] -> Value
[Configuration] -> Encoding
Configuration -> Bool
Configuration -> Value
Configuration -> Encoding
(Configuration -> Value)
-> (Configuration -> Encoding)
-> ([Configuration] -> Value)
-> ([Configuration] -> Encoding)
-> (Configuration -> Bool)
-> ToJSON Configuration
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Configuration -> Value
toJSON :: Configuration -> Value
$ctoEncoding :: Configuration -> Encoding
toEncoding :: Configuration -> Encoding
$ctoJSONList :: [Configuration] -> Value
toJSONList :: [Configuration] -> Value
$ctoEncodingList :: [Configuration] -> Encoding
toEncodingList :: [Configuration] -> Encoding
$comitField :: Configuration -> Bool
omitField :: Configuration -> Bool
ToJSON) via (Autodocodec Configuration)
instance HasCodec Configuration where
codec :: JSONCodec Configuration
codec =
Text
-> ObjectCodec Configuration Configuration
-> JSONCodec Configuration
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"Configuration" (ObjectCodec Configuration Configuration
-> JSONCodec Configuration)
-> ObjectCodec Configuration Configuration
-> JSONCodec Configuration
forall a b. (a -> b) -> a -> b
$
Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"specification" Text
"The OpenAPI 3 specification file which code should be generated for." ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configOpenApiSpecification
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"outputDir" Text
"The directory where the generated output is stored." ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configOutputDir
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"packageName" Text
"Name of the stack project" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configPackageName
Codec
Object
Configuration
(Maybe Text
-> Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"moduleName" Text
"Name of the module" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configModuleName
Codec
Object
Configuration
(Maybe LogSeverity
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe LogSeverity)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe LogSeverity) (Maybe LogSeverity)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"logLevel" Text
"Set the minium log level (e. g. WARN to only print warnings and errors). Possible values: TRACE, INFO, WARN, ERROR" ObjectCodec (Maybe LogSeverity) (Maybe LogSeverity)
-> (Configuration -> Maybe LogSeverity)
-> Codec Object Configuration (Maybe LogSeverity)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe LogSeverity
configLogLevel
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"force" Text
"Overwrite output directory without question" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configForce
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"incremental" Text
"Only write new/changed files. Does not need --force flag to overwrite files." ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configIncremental
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"dryRun" Text
"Do not generate the output files but only print the generated code" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configDryRun
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"doNotGenerateStackProject" Text
"Do not generate a stack project alongside the raw Haskell files" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configDoNotGenerateStackProject
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"generateNixFiles" Text
"Generate Nix files alongside the raw Haskell files" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configGenerateNixFiles
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"omitAdditionalOperationFunctions" Text
"Omit the additional operation functions, which are: with explicit configuration and raw variants (returning the plain ByteString) for both with and without explicit configuration" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configOmitAdditionalOperationFunctions
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"generateOptionalEmptyRequestBody" Text
"Force the generator to create types for empty request bodies which are optional (e. g. no properties and required equals false)" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configGenerateOptionalEmptyRequestBody
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"useNumberedVariantConstructors" Text
"Use numbered data constructors (e. g. Variant1, Variant 2, etc.) for one-of types" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configUseNumberedVariantConstructors
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"useFloatWithArbitraryPrecision" Text
"Use Data.Scientific instead of Double to support arbitary number precision" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configUseFloatWithArbitraryPrecision
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"useIntWithArbitraryPrecision" Text
"Use 'Integer' instead of 'Int' to support arbitrary number precision" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configUseIntWithArbitraryPrecision
Codec
Object
Configuration
(Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"useDateTypesAsString" Text
"Convert strings formatted as date / date-time to date types" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configUseDateTypesAsString
Codec
Object
Configuration
(Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"convertToCamelCase" Text
"Convert names to CamelCase instead of using names which are as close as possible to the names provided in the specification" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configConvertToCamelCase
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"propertyTypeSuffix" Text
"Add a suffix to property types to prevent naming conflicts" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configPropertyTypeSuffix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"responseTypeSuffix" Text
"The suffix which is added to the response data types" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configResponseTypeSuffix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"responseBodyTypeSuffix" Text
"The suffix which is added to the response body data types" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configResponseBodyTypeSuffix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"requestBodyTypeSuffix" Text
"The suffix which is added to the request body data types" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configRequestBodyTypeSuffix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"arrayItemTypeSuffix" Text
"The suffix which is added to the item type of an array. This is only applied to item types of top level array types which an alias is generated for." ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configArrayItemTypeSuffix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"nonNullableTypeSuffix" Text
"The suffix which is added to the non-nullable part of a nullable type. This is only applied to top level nullable schemas as they are the only ones which need to be referencable by name." ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configNonNullableTypeSuffix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"parametersTypeSuffix" Text
"The suffix which is added to the parameters type of operations" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configParametersTypeSuffix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"parameterQueryPrefix" Text
"The prefix which is added to query parameters" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configParameterQueryPrefix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"parameterPathPrefix" Text
"The prefix which is added to path parameters" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configParameterPathPrefix
Codec
Object
Configuration
(Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"parameterCookiePrefix" Text
"The prefix which is added to cookie parameters" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configParameterCookiePrefix
Codec
Object
Configuration
(Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe Text)
-> Codec
Object
Configuration
(Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"parameterHeaderPrefix" Text
"The prefix which is added to header parameters" ObjectCodec (Maybe Text) (Maybe Text)
-> (Configuration -> Maybe Text)
-> Codec Object Configuration (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Text
configParameterHeaderPrefix
Codec
Object
Configuration
(Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe [Text])
-> Codec
Object
Configuration
(Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe [Text]) (Maybe [Text])
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"operationsToGenerate" Text
"If not all operations should be generated, this option can be used to specify all of them which should be generated. The value has to correspond to the value in the 'operationId' field in the OpenAPI 3 specification." ObjectCodec (Maybe [Text]) (Maybe [Text])
-> (Configuration -> Maybe [Text])
-> Codec Object Configuration (Maybe [Text])
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe [Text]
configOperationsToGenerate
Codec
Object
Configuration
(Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe [Text])
-> Codec
Object
Configuration
(Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe [Text]) (Maybe [Text])
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"opaqueSchemas" Text
"A list of schema names (exactly as they are named in the components.schemas section of the corresponding OpenAPI 3 specification) which are not further investigated while generating code from the specification. Only a type alias to 'Aeson.Value' is created for these schemas." ObjectCodec (Maybe [Text]) (Maybe [Text])
-> (Configuration -> Maybe [Text])
-> Codec Object Configuration (Maybe [Text])
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe [Text]
configOpaqueSchemas
Codec
Object
Configuration
(Maybe [Text]
-> Maybe Bool
-> Maybe FixedValueStrategy
-> Maybe Bool
-> Configuration)
-> Codec Object Configuration (Maybe [Text])
-> Codec
Object
Configuration
(Maybe Bool
-> Maybe FixedValueStrategy -> Maybe Bool -> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe [Text]) (Maybe [Text])
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"whiteListedSchemas" Text
"A list of schema names (exactly as they are named in the components.schemas section of the corresponding OpenAPI 3 specification) which need to be generated. For all other schemas only a type alias to 'Aeson.Value' is created." ObjectCodec (Maybe [Text]) (Maybe [Text])
-> (Configuration -> Maybe [Text])
-> Codec Object Configuration (Maybe [Text])
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe [Text]
configWhiteListedSchemas
Codec
Object
Configuration
(Maybe Bool
-> Maybe FixedValueStrategy -> Maybe Bool -> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> Codec
Object
Configuration
(Maybe FixedValueStrategy -> Maybe Bool -> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"outputAllSchemas" Text
"Output all component schemas" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configOutputAllSchemas
Codec
Object
Configuration
(Maybe FixedValueStrategy -> Maybe Bool -> Configuration)
-> Codec Object Configuration (Maybe FixedValueStrategy)
-> Codec Object Configuration (Maybe Bool -> Configuration)
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> Text
-> ObjectCodec
(Maybe FixedValueStrategy) (Maybe FixedValueStrategy)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"fixedValueStrategy" Text
"In OpenAPI 3, fixed values can be defined as an enum with only one allowed value. If such a constant value is encountered as a required property of an object, the generator excludes this property by default ('exclude' strategy) and adds the value in the 'ToJSON' instance and expects the value to be there in the 'FromJSON' instance. This setting allows to change this behavior by including all fixed value fields instead ('include' strategy), i.e. just not trying to do anything smart." ObjectCodec (Maybe FixedValueStrategy) (Maybe FixedValueStrategy)
-> (Configuration -> Maybe FixedValueStrategy)
-> Codec Object Configuration (Maybe FixedValueStrategy)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe FixedValueStrategy
configFixedValueStrategy
Codec Object Configuration (Maybe Bool -> Configuration)
-> Codec Object Configuration (Maybe Bool)
-> ObjectCodec Configuration Configuration
forall a b.
Codec Object Configuration (a -> b)
-> Codec Object Configuration a -> Codec Object Configuration b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField Text
"shortenSingleFieldObjects" Text
"When encountering an object with a single field, shorten the field of that object to be the schema name. Respects property type suffix." ObjectCodec (Maybe Bool) (Maybe Bool)
-> (Configuration -> Maybe Bool)
-> Codec Object Configuration (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Configuration -> Maybe Bool
configShortenSingleFieldObjects
getConfiguration :: Text -> IO (Maybe Configuration)
getConfiguration :: Text -> IO (Maybe Configuration)
getConfiguration Text
path = String -> IO (Path Abs File)
forall (m :: * -> *). MonadIO m => String -> m (Path Abs File)
resolveFile' (Text -> String
T.unpack Text
path) IO (Path Abs File)
-> (Path Abs File -> IO (Maybe Configuration))
-> IO (Maybe Configuration)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Path Abs File -> IO (Maybe Configuration)
forall a r. HasCodec a => Path r File -> IO (Maybe a)
readYamlConfigFile