| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
YamlParse.Applicative
Contents
Description
Yamlparse applicative
Implement Yaml parsing and get documentation for it for free.
Usage example
For more examples, see the `yamlparse-applicative-demo` examples in the github repository
Suppose you have some tool and you want to have it read its configuration from a file. You make a type for the configuration:
data Configuration
  = Configuration
  { confUrl :: Maybe Text
  , confPort :: Int
  , confToken :: Text
  } deriving (Show, Eq)Instead of implementing a FromJSON instance, you now implement a YamlSchema instance like so:
instance YamlSchema Configuration where
  yamlSchema =
    objectParser $ -- Declare that it is a Yaml object
      Configuration
        <$> optionalField -- An optional key may be in the file
            "url"
            "The url to host the server at. It will be hosted on 'localhost' by default."
        <*> optionalFieldWithDefault -- An optional key with default _may_ in the file, the default will be used otherwise
            "port"
            8000
            "The post to host the server at."
        <*> requiredField -- A required field must be in the file
            "token"
            "The authorisation token that clients can use to authenticate themselves."Now you've already documented the configuration in code. This will make sure that your documentation stays correct because it will be type-checked.
Now you can implement FromJSON like so:
instance FromJSON Configuration where parseJSON = viaYamlSchema
And you can get user-facing documentation about the format for free using 'prettySchema . explainParser':
# Configuration url: # optional # The url to host the server at. It will be hosted on 'localhost' by default. <string> port: # optional, default: 8000 # The post to host the server at. <number> token: # required # The authorisation token that clients can use to authenticate themselves. <bool>
If you are also using 'optparse-applicative', you can even add this documentation to your `--help` page as well using confDesc:
argParser :: ParserInfo SomethingElse
argParser =
  info
    (helper <$> parseSomethingElse)
    (confDesc @Configuration)Synopsis
- class YamlSchema a where- yamlSchema :: YamlParser a
- yamlSchemaList :: YamlParser [a]
 
- class YamlKeySchema a where- yamlKeySchema :: KeyParser a
 
- objectParser :: Text -> ObjectParser o -> YamlParser o
- unnamedObjectParser :: ObjectParser o -> YamlParser o
- maybeParser :: Show o => (o -> Maybe u) -> Parser i o -> Parser i u
- eitherParser :: Show o => (o -> Either String u) -> Parser i o -> Parser i u
- extraParser :: (o -> Parser u) -> Parser i o -> Parser i u
- (<?>) :: Parser i a -> Text -> Parser i a
- (<??>) :: Parser i a -> [Text] -> Parser i a
- requiredField :: YamlSchema a => Text -> Text -> ObjectParser a
- requiredField' :: YamlSchema a => Text -> ObjectParser a
- requiredFieldWith :: Text -> Text -> YamlParser a -> ObjectParser a
- requiredFieldWith' :: Text -> YamlParser a -> ObjectParser a
- optionalField :: YamlSchema a => Text -> Text -> ObjectParser (Maybe a)
- optionalField' :: YamlSchema a => Text -> ObjectParser (Maybe a)
- optionalFieldWith :: Text -> Text -> YamlParser a -> ObjectParser (Maybe a)
- optionalFieldWith' :: Text -> YamlParser a -> ObjectParser (Maybe a)
- optionalFieldWithDefault :: (Show a, YamlSchema a) => Text -> a -> Text -> ObjectParser a
- optionalFieldWithDefault' :: (Show a, YamlSchema a) => Text -> a -> ObjectParser a
- optionalFieldWithDefaultWith :: Show a => Text -> a -> Text -> YamlParser a -> ObjectParser a
- optionalFieldWithDefaultWith' :: Show a => Text -> a -> YamlParser a -> ObjectParser a
- viaRead :: Read a => YamlParser a
- literalString :: Text -> YamlParser Text
- literalValue :: ToJSON a => a -> YamlParser a
- literalShowValue :: Show a => a -> YamlParser a
- alternatives :: [Parser i o] -> Parser i o
- type YamlParser a = Parser Value a
- type ObjectParser a = Parser Object a
- data Parser i o where- ParseAny :: Parser i i
- ParseExtra :: (o -> Parser u) -> Parser i o -> Parser i u
- ParseEq :: (Show o, Eq o) => o -> Text -> Parser i o -> Parser i o
- ParseNull :: Parser Value ()
- ParseMaybe :: Parser Value o -> Parser Value (Maybe o)
- ParseBool :: Maybe Text -> Parser Bool o -> Parser Value o
- ParseString :: Maybe Text -> Parser Text o -> Parser Value o
- ParseNumber :: Maybe Text -> Parser Scientific o -> Parser Value o
- ParseArray :: Maybe Text -> Parser Array o -> Parser Value o
- ParseObject :: Maybe Text -> Parser Object a -> Parser Value a
- ParseList :: Parser Value o -> Parser Array (Vector o)
- ParseMap :: Parser Value v -> Parser Object (HashMap Text v)
- ParseMapKeys :: Ord k => Parser Text k -> Parser Object (HashMap Text v) -> Parser Object (Map k v)
- ParseField :: Text -> FieldParser o -> Parser Object o
- ParsePure :: a -> Parser i a
- ParseFmap :: (a -> b) -> Parser i a -> Parser i b
- ParseAp :: Parser i (a -> b) -> Parser i a -> Parser i b
- ParseAlt :: [Parser i o] -> Parser i o
- ParseComment :: Text -> Parser i o -> Parser i o
 
- viaYamlSchema :: YamlSchema a => Value -> Parser a
- newtype ViaYamlSchema a = ViaYamlSchema a
- implementParser :: Parser i o -> i -> Parser o
- prettySchemaDoc :: forall a. YamlSchema a => Text
- prettyParserDoc :: Parser i o -> Text
- prettyColourisedSchemaDoc :: forall a. YamlSchema a => Text
- prettyColourisedParserDoc :: Parser i o -> Text
- explainParser :: Parser i o -> Schema
- data Schema- = EmptySchema
- | AnySchema
- | ExactSchema Text
- | NullSchema
- | MaybeSchema Schema
- | BoolSchema (Maybe Text)
- | NumberSchema (Maybe Text)
- | StringSchema (Maybe Text)
- | ArraySchema (Maybe Text) Schema
- | ObjectSchema (Maybe Text) Schema
- | FieldSchema Text Bool (Maybe Text) Schema
- | ListSchema Schema
- | MapSchema Schema
- | MapKeysSchema Schema
- | ApSchema Schema Schema
- | AltSchema [Schema]
- | CommentSchema Text Schema
 
- prettySchema :: Schema -> Text
- prettyColourisedSchema :: Schema -> Text
- confDesc :: forall o a. YamlSchema o => InfoMod a
- confDescWith :: Parser i o -> InfoMod a
- readConfigFile :: (YamlSchema a, FromJSON a) => Path r File -> IO (Maybe a)
- readFirstConfigFile :: forall a r. (FromJSON a, YamlSchema a) => [Path r File] -> IO (Maybe a)
The YamlSchema Class
class YamlSchema a where Source #
A class of types for which a schema is defined.
Note that you do not have to use this class and can just use your own parser values. Note also that the parsing of a type of this class should correspond to the parsing of the type in the FromJSON class.
Minimal complete definition
Methods
yamlSchema :: YamlParser a Source #
A yamlschema for one value
See the sections on helper functions for implementing this for plenty of examples.
yamlSchemaList :: YamlParser [a] Source #
Instances
class YamlKeySchema a where Source #
A class of types for which a schema for keys is defined.
Methods
yamlKeySchema :: KeyParser a Source #
Instances
| YamlKeySchema Text Source # | |
| Defined in YamlParse.Applicative.Class Methods | |
| YamlKeySchema String Source # | |
| Defined in YamlParse.Applicative.Class Methods | |
Implementing YamlSchema instances
objectParser :: Text -> ObjectParser o -> YamlParser o Source #
Declare a parser of a named object
unnamedObjectParser :: ObjectParser o -> YamlParser o Source #
Declare a parser of an unnamed object
Prefer objectParser if you can.
maybeParser :: Show o => (o -> Maybe u) -> Parser i o -> Parser i u Source #
Make a parser that parses a value using the given extra parsing function
You can use this to make a parser for a type with a smart constructor.
 Prefer eitherParser if you can so you get better error messages.
Example:
parseUsername :: Text -> Maybe Username instance YamlSchema Username where yamlSchema = maybeParser parseUsername yamlSchema
eitherParser :: Show o => (o -> Either String u) -> Parser i o -> Parser i u Source #
Make a parser that parses a value using the given extra parsing function
You can use this to make a parser for a type with a smart constructor.
 If you don't have a Show instance for your o, then you can use extraParser instead.
Example:
parseUsername :: Text -> Either String Username instance YamlSchema Username where yamlSchema = eitherParser parseUsername yamlSchema
extraParser :: (o -> Parser u) -> Parser i o -> Parser i u Source #
Make a parser that parses a value using the given extra parsing function
You can use this to make a parser for a type with a smart constructor.
 Prefer eitherParser if you can, use this if you don't have a Show instance for your o.
(<?>) :: Parser i a -> Text -> Parser i a Source #
Add a comment to a parser
This info will be used in the schema for documentation.
For example:
data Result = Error | Ok
instance YamlSchema Result where
  yamlSchema = alternatives
    [ Error <$ literalString "Error" <?> "An error"
    , Ok <$ literalString "Ok" <?> "Oll Klear"
    ](<??>) :: Parser i a -> [Text] -> Parser i a Source #
Add a list of lines of comments to a parser
This info will be used in the schema for documentation.
For example:
data Result = Error | Ok
instance YamlSchema Result where
  yamlSchema = alternatives
    [ Error <$ literalString "Error" <??> ["Just an error", "but I've got a lot to say about this"]
    , Ok <$ literalString "Ok" <??> ["Oll Klear", "I really don't know where 'OK' comes from?!"]
    ]requiredField :: YamlSchema a => Text -> Text -> ObjectParser a Source #
A parser for a required field in an object at a given key
requiredField' :: YamlSchema a => Text -> ObjectParser a Source #
A parser for a required field in an object at a given key without a help text
requiredFieldWith :: Text -> Text -> YamlParser a -> ObjectParser a Source #
A parser for a required field at a given key with a parser for what is found at that key
requiredFieldWith' :: Text -> YamlParser a -> ObjectParser a Source #
A parser for a required field at a given key with a parser for what is found at that key without a help text
optionalField :: YamlSchema a => Text -> Text -> ObjectParser (Maybe a) Source #
A parser for an optional field in an object at a given key
optionalField' :: YamlSchema a => Text -> ObjectParser (Maybe a) Source #
A parser for an optional field in an object at a given key without a help text
optionalFieldWith :: Text -> Text -> YamlParser a -> ObjectParser (Maybe a) Source #
A parser for an optional field at a given key with a parser for what is found at that key
optionalFieldWith' :: Text -> YamlParser a -> ObjectParser (Maybe a) Source #
A parser for an optional field at a given key with a parser for what is found at that key without a help text
optionalFieldWithDefault :: (Show a, YamlSchema a) => Text -> a -> Text -> ObjectParser a Source #
A parser for an optional field in an object at a given key with a default value
optionalFieldWithDefault' :: (Show a, YamlSchema a) => Text -> a -> ObjectParser a Source #
A parser for an optional field in an object at a given key with a default value without a help text
optionalFieldWithDefaultWith :: Show a => Text -> a -> Text -> YamlParser a -> ObjectParser a Source #
A parser for an optional field at a given key with a default value and a parser for what is found at that key
For the sake of documentation, the default value needs to be showable.
optionalFieldWithDefaultWith' :: Show a => Text -> a -> YamlParser a -> ObjectParser a Source #
A parser for an optional field at a given key with a default value and a parser for what is found at that key without a help text
For the sake of documentation, the default value needs to be showable.
viaRead :: Read a => YamlParser a Source #
literalString :: Text -> YamlParser Text Source #
Declare a parser for an exact string.
You can use this to parse a constructor in an enum for example:
data Fruit = Apple | Banana instance YamlSchema Fruit where yamlSchema = Apple <$ literalString "Apple" <|> Banana <$ literalString "Banana"
literalValue :: ToJSON a => a -> YamlParser a Source #
Declare a parser for a value using its show instance
Note that no value is read. The parsed string is just compared to the shown given value.
You can use this to parse a constructor in an enum when it has a ToJSON instance.
For example
data Fruit = Apple | Banana | Melon
  deriving (Eq, Generic)
instance ToJSON Fruit
instance YamlSchema Fruit where
  yamlSchema = alternatives
     [ literalValue Apple
     , literalValue Banana
     , literalValue Melon
     ]literalShowValue :: Show a => a -> YamlParser a Source #
Declare a parser for a value using its show instance
Note that no value is read. The parsed string is just compared to the shown given value.
You can use this to parse a constructor in an enum when it has a Show instance.
For example:
data Fruit = Apple | Banana | Melon
  deriving (Show, Eq)
instance YamlSchema Fruit where
  yamlSchema = alternatives
     [ literalShowString Apple
     , literalShowString Banana
     , literalShowString Melon
     ]alternatives :: [Parser i o] -> Parser i o Source #
Use the first parser of the given list that succeeds
You can use this to parse a constructor in an enum.
For example:
data Fruit = Apple | Banana | Melon
instance YamlSchema Fruit where
  yamlSchema = alternatives
     [ Apple <$ literalString "Apple"
     , Banana <$ literalString "Banana"
     , Melon <$ literalString "Melon"
     ]Parser
type YamlParser a = Parser Value a Source #
type ObjectParser a = Parser Object a Source #
data Parser i o where Source #
A parser that takes values of type i as input and parses them into values of type o
Note that there is no Monad instance.
Constructors
| ParseAny :: Parser i i | Return the input | 
| ParseExtra :: (o -> Parser u) -> Parser i o -> Parser i u | Parse via an extra parsing function | 
| ParseEq | Match an exact value | 
| ParseNull :: Parser Value () | Parse  | 
| ParseMaybe :: Parser Value o -> Parser Value (Maybe o) | |
| ParseBool :: Maybe Text -> Parser Bool o -> Parser Value o | Parse a boolean value | 
| ParseString | Parse a String value | 
| ParseNumber | Parse a numeric value | 
| ParseArray | Parse an array | 
| ParseObject | Parse an object | 
| ParseList :: Parser Value o -> Parser Array (Vector o) | Parse a list of elements all in the same way | 
| ParseMap :: Parser Value v -> Parser Object (HashMap Text v) | Parse a map where the keys are the yaml keys | 
| ParseMapKeys :: Ord k => Parser Text k -> Parser Object (HashMap Text v) -> Parser Object (Map k v) | Parse a map's keys via a given parser | 
| ParseField | Parse a field of an object | 
| Fields 
 | |
| ParsePure :: a -> Parser i a | A pure value | 
| ParseFmap :: (a -> b) -> Parser i a -> Parser i b | To implement Functor | 
| ParseAp :: Parser i (a -> b) -> Parser i a -> Parser i b | To implement Applicative | 
| ParseAlt :: [Parser i o] -> Parser i o | To implement Alternative | 
| ParseComment :: Text -> Parser i o -> Parser i o | Add comments to the parser. This info will be used in the schema for documentation. | 
Using a yaml schema
Parsing Yaml via a YamlSchema instance
viaYamlSchema :: YamlSchema a => Value -> Parser a Source #
Helper function to implement FromJSON via YamlSchema
Example:
instance FromJSON Config where parseJSON = viaYamlSchema
newtype ViaYamlSchema a Source #
A helper newtype to parse a yaml value using the YamlSchema parser.
Example:
case Data.Yaml.decodeEither' contents of Left e -> die $ show e Right (ViaYamlSchema res) -> print res
This only helps you when you really don't want to implement a FromJSON instance.
 See viaYamlSchema if you do.
Constructors
| ViaYamlSchema a | 
Instances
Getting a parser implemntation from a Parser
implementParser :: Parser i o -> i -> Parser o Source #
Use a Parser to parse a value from Yaml.
A 'Parser i o' corresponds exactly to a 'i -> Yaml.Parser o' and this function servers as evidence for that.
Documentation for a Parser
prettySchemaDoc :: forall a. YamlSchema a => Text Source #
Render pretty documentation about the yamlSchema of a type
This is meant for humans. The output may look like YAML but it is not.
prettyParserDoc :: Parser i o -> Text Source #
Render pretty documentation about a parser
This is meant for humans. The output may look like YAML but it is not.
prettyColourisedSchemaDoc :: forall a. YamlSchema a => Text Source #
Render pretty colourised documentation about the yamlSchema of a type
This is meant for humans. The output may look like YAML but it is not.
prettyColourisedParserDoc :: Parser i o -> Text Source #
Render pretty colourised documentation about a parser
This is meant for humans. The output may look like YAML but it is not.
Parser schemas
explainParser :: Parser i o -> Schema Source #
Use a parser to produce a schema that describes it for documentation.
Nothing means that nothing even needs to be parsed, you just get the a without parsing anything.
 This is for the pure case.
Constructors
Instances
Showing the schema to the user
prettySchema :: Schema -> Text Source #
Render a schema as pretty text.
This is meant for humans. The output may look like YAML but it is not.
prettyColourisedSchema :: Schema -> Text Source #
Render a schema as pretty and colourised text.
This is meant for humans. The output may look like YAML but it is not.
Interface with 'optparse-applicative'
confDesc :: forall o a. YamlSchema o => InfoMod a Source #
Helper function to add the schema documentation for a YamlSchema parser to the optparse applicative help output
confDescWith :: Parser i o -> InfoMod a Source #
Helper function to add the schema documentation for a given parser to the optparse applicative help output
Parsing a file
readConfigFile :: (YamlSchema a, FromJSON a) => Path r File -> IO (Maybe a) Source #
Helper function to read a config file for a type in YamlSchema
readFirstConfigFile :: forall a r. (FromJSON a, YamlSchema a) => [Path r File] -> IO (Maybe a) Source #
Helper function to read the first in a list of config files