yamlparse-applicative-0.1.0.1: Declaritive configuration parsing with free docs

Safe HaskellNone
LanguageHaskell2010

YamlParse.Applicative.Parser

Synopsis

Documentation

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

Fields

ParseNull :: Parser Value ()

Parse null only.

ParseMaybe :: Parser Value o -> Parser Value (Maybe o)

Parse null as Nothing and the rest as Just.

ParseBool :: Maybe Text -> Parser Bool o -> Parser Value o

Parse a boolean value

ParseString

Parse a String value

Fields

  • :: Maybe Text

    Extra info about what the string represents This info will be used during parsing for error messages and in the schema for documentation.

  • -> Parser Text o
     
  • -> Parser Value o
     
ParseNumber

Parse a numeric value

Fields

  • :: Maybe Text

    Extra info about what the number represents This info will be used during parsing for error messages and in the schema for documentation.

  • -> Parser Scientific o
     
  • -> Parser Value o
     
ParseArray

Parse an array

Fields

  • :: Maybe Text

    Extra info about what the array represents This info will be used during parsing for error messages and in the schema for documentation.

  • -> Parser Array o
     
  • -> Parser Value o
     
ParseObject

Parse an object

Fields

  • :: Maybe Text

    Extra info about what the object represents This info will be used during parsing for error messages and in the schema for documentation.

  • -> Parser Object a
     
  • -> Parser Value a
     
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.

Instances
Functor (Parser i) Source # 
Instance details

Defined in YamlParse.Applicative.Parser

Methods

fmap :: (a -> b) -> Parser i a -> Parser i b #

(<$) :: a -> Parser i b -> Parser i a #

Applicative (Parser i) Source # 
Instance details

Defined in YamlParse.Applicative.Parser

Methods

pure :: a -> Parser i a #

(<*>) :: Parser i (a -> b) -> Parser i a -> Parser i b #

liftA2 :: (a -> b -> c) -> Parser i a -> Parser i b -> Parser i c #

(*>) :: Parser i a -> Parser i b -> Parser i b #

(<*) :: Parser i a -> Parser i b -> Parser i a #

Alternative (Parser i) Source # 
Instance details

Defined in YamlParse.Applicative.Parser

Methods

empty :: Parser i a #

(<|>) :: Parser i a -> Parser i a -> Parser i a #

some :: Parser i a -> Parser i [a] #

many :: Parser i a -> Parser i [a] #

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.

viaRead :: Read a => YamlParser a Source #

Parse a string-like thing by Read-ing it

You probably don't want to use Read.

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"

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
     ]

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
     ]

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 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?!"]
    ]

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

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

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.

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.