| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
OpenAPI.Generate.Monad
Description
Synopsis
- data GeneratorEnvironment = GeneratorEnvironment {
- currentPath :: [Text]
- references :: ReferenceMap
- flags :: Flags
- data GeneratorLogSeverity
- data GeneratorLogEntry = GeneratorLogEntry {}
- type GeneratorLogs = [GeneratorLogEntry]
- newtype Generator a = Generator {}
- runGenerator :: GeneratorEnvironment -> Generator a -> (a, GeneratorLogs)
- createEnvironment :: Flags -> ReferenceMap -> GeneratorEnvironment
- logMessage :: GeneratorLogSeverity -> Text -> Generator ()
- logError :: Text -> Generator ()
- logWarning :: Text -> Generator ()
- logInfo :: Text -> Generator ()
- transformGeneratorLogs :: GeneratorLogs -> [Text]
- transformSeverity :: GeneratorLogSeverity -> Text
- transformPath :: [Text] -> Text
- nested :: Text -> Generator a -> Generator a
- createReferenceLookupM :: (Text -> ReferenceMap -> Maybe a) -> Text -> Generator (Maybe a)
- getSchemaReferenceM :: Text -> Generator (Maybe SchemaObject)
- getResponseReferenceM :: Text -> Generator (Maybe ResponseObject)
- getParameterReferenceM :: Text -> Generator (Maybe ParameterObject)
- getExampleReferenceM :: Text -> Generator (Maybe ExampleObject)
- getRequestBodyReferenceM :: Text -> Generator (Maybe RequestBodyObject)
- getHeaderReferenceM :: Text -> Generator (Maybe HeaderObject)
- getSecuritySchemeReferenceM :: Text -> Generator (Maybe SecuritySchemeObject)
- getFlags :: Generator Flags
- getFlag :: (Flags -> a) -> Generator a
Documentation
data GeneratorEnvironment Source #
The reader environment of the Generator monad
The currentPath is updated using the nested function to track the current position within the specification.
This is used to produce tracable log messages.
The references map is a lookup table for references within the OpenAPI specification.
Constructors
| GeneratorEnvironment | |
Fields
| |
Instances
| Eq GeneratorEnvironment Source # | |
Defined in OpenAPI.Generate.Monad Methods (==) :: GeneratorEnvironment -> GeneratorEnvironment -> Bool # (/=) :: GeneratorEnvironment -> GeneratorEnvironment -> Bool # | |
| Show GeneratorEnvironment Source # | |
Defined in OpenAPI.Generate.Monad Methods showsPrec :: Int -> GeneratorEnvironment -> ShowS # show :: GeneratorEnvironment -> String # showList :: [GeneratorEnvironment] -> ShowS # | |
| MonadReader GeneratorEnvironment Generator Source # | |
Defined in OpenAPI.Generate.Monad Methods ask :: Generator GeneratorEnvironment # local :: (GeneratorEnvironment -> GeneratorEnvironment) -> Generator a -> Generator a # reader :: (GeneratorEnvironment -> a) -> Generator a # | |
data GeneratorLogSeverity Source #
Data type representing the log severities
Constructors
| ErrorSeverity | |
| WarningSeverity | |
| InfoSeverity |
Instances
| Eq GeneratorLogSeverity Source # | |
Defined in OpenAPI.Generate.Monad Methods (==) :: GeneratorLogSeverity -> GeneratorLogSeverity -> Bool # (/=) :: GeneratorLogSeverity -> GeneratorLogSeverity -> Bool # | |
| Show GeneratorLogSeverity Source # | |
Defined in OpenAPI.Generate.Monad Methods showsPrec :: Int -> GeneratorLogSeverity -> ShowS # show :: GeneratorLogSeverity -> String # showList :: [GeneratorLogSeverity] -> ShowS # | |
data GeneratorLogEntry Source #
A log entry containing the location within the OpenAPI specification where the message was produced, a severity and the actual message.
Constructors
| GeneratorLogEntry | |
Instances
| Eq GeneratorLogEntry Source # | |
Defined in OpenAPI.Generate.Monad Methods (==) :: GeneratorLogEntry -> GeneratorLogEntry -> Bool # (/=) :: GeneratorLogEntry -> GeneratorLogEntry -> Bool # | |
| Show GeneratorLogEntry Source # | |
Defined in OpenAPI.Generate.Monad Methods showsPrec :: Int -> GeneratorLogEntry -> ShowS # show :: GeneratorLogEntry -> String # showList :: [GeneratorLogEntry] -> ShowS # | |
| MonadWriter GeneratorLogs Generator Source # | |
Defined in OpenAPI.Generate.Monad Methods writer :: (a, GeneratorLogs) -> Generator a # tell :: GeneratorLogs -> Generator () # listen :: Generator a -> Generator (a, GeneratorLogs) # pass :: Generator (a, GeneratorLogs -> GeneratorLogs) -> Generator a # | |
type GeneratorLogs = [GeneratorLogEntry] Source #
The type contained in the writer of the Generator used to collect log entries
The Generator monad is used to pass a Reader environment to functions in need of resolving references
and collects log messages.
Constructors
| Generator | |
Fields | |
Instances
| Monad Generator Source # | |
| Functor Generator Source # | |
| Applicative Generator Source # | |
| MonadWriter GeneratorLogs Generator Source # | |
Defined in OpenAPI.Generate.Monad Methods writer :: (a, GeneratorLogs) -> Generator a # tell :: GeneratorLogs -> Generator () # listen :: Generator a -> Generator (a, GeneratorLogs) # pass :: Generator (a, GeneratorLogs -> GeneratorLogs) -> Generator a # | |
| MonadReader GeneratorEnvironment Generator Source # | |
Defined in OpenAPI.Generate.Monad Methods ask :: Generator GeneratorEnvironment # local :: (GeneratorEnvironment -> GeneratorEnvironment) -> Generator a -> Generator a # reader :: (GeneratorEnvironment -> a) -> Generator a # | |
runGenerator :: GeneratorEnvironment -> Generator a -> (a, GeneratorLogs) Source #
Runs the generator monad within a provided environment.
createEnvironment :: Flags -> ReferenceMap -> GeneratorEnvironment Source #
Create an environment based on a ReferenceMap and Flags
logMessage :: GeneratorLogSeverity -> Text -> Generator () Source #
Writes a log message to a Generator monad
transformGeneratorLogs :: GeneratorLogs -> [Text] Source #
Transforms a log returned from runGenerator to a list of Text values for easier printing.
transformSeverity :: GeneratorLogSeverity -> Text Source #
Transforms the severity to a Text representation
transformPath :: [Text] -> Text Source #
Transforms the path to a Text representation (parts are seperated with a dot)
nested :: Text -> Generator a -> Generator a Source #
This function can be used to tell the Generator monad where in the OpenAPI specification the generator currently is
createReferenceLookupM :: (Text -> ReferenceMap -> Maybe a) -> Text -> Generator (Maybe a) Source #
Helper function to create a lookup function for a specific type
getSchemaReferenceM :: Text -> Generator (Maybe SchemaObject) Source #
Resolve a SchemaObject reference from within the Generator monad
getResponseReferenceM :: Text -> Generator (Maybe ResponseObject) Source #
Resolve a ResponseObject reference from within the Generator monad
getParameterReferenceM :: Text -> Generator (Maybe ParameterObject) Source #
Resolve a ParameterObject reference from within the Generator monad
getExampleReferenceM :: Text -> Generator (Maybe ExampleObject) Source #
Resolve a ExampleObject reference from within the Generator monad
getRequestBodyReferenceM :: Text -> Generator (Maybe RequestBodyObject) Source #
Resolve a RequestBodyObject reference from within the Generator monad
getHeaderReferenceM :: Text -> Generator (Maybe HeaderObject) Source #
Resolve a HeaderObject reference from within the Generator monad
getSecuritySchemeReferenceM :: Text -> Generator (Maybe SecuritySchemeObject) Source #
Resolve a SecuritySchemeObject reference from within the Generator monad