| Copyright | (c) Copyright Pedro Tacla Yamada 2016 |
|---|---|
| License | MIT |
| Maintainer | tacla.yamada@gmail.com |
| Stability | experimental |
| Portability | unknown |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Conf
Description
This modules contains the conf Megaparsec parser for .conf files and Pretty
instance.
- conf :: Parser Conf
- pPrintConf :: Conf -> Doc
- runParser :: Parsec e s a -> String -> s -> Either (ParseError (Token s) e) a
- type Conf = [ConfStatement]
- data ConfStatement
- data Block = Block [Text] [ConfStatement]
- data Comment = Comment Text
- data Expression = Expression Text [Text]
- confStatement :: Parser ConfStatement
- confStatementLines :: Parser [ConfStatement]
- block :: Parser Block
- expression :: Parser Expression
- argument :: Parser Text
- class Pretty a where
- pPrint :: Pretty a => a -> Doc
Entry-points
pPrintConf :: Conf -> Doc Source #
Arguments
| :: Parsec e s a | Parser to run |
| -> String | Name of source file |
| -> s | Input for parser |
| -> Either (ParseError (Token s) e) a |
runParser p file input runs parser p on the input list of tokens
input, obtained from source file. The file is only used in error
messages and may be the empty string. Returns either a ParseError
(Left) or a value of type a (Right).
parseFromFile p file = runParser p file <$> readFile file
Types
type Conf = [ConfStatement] Source #
data ConfStatement Source #
Constructors
| ConfStatementComment Comment | |
| ConfStatementBlock Block | |
| ConfStatementEmptyLine | We store empty lines while parsing so we can reconstruct the document when pretty-printing |
| ConfStatementExpression Expression |
Instances
Constructors
| Block [Text] [ConfStatement] |
Parser
Pretty-printer
Pretty printing class. The precedence level is used in a similar way as in
the Show class. Minimal complete definition is either pPrintPrec or
pPrint.
Minimal complete definition
Instances
| Pretty Bool | |
| Pretty Char | |
| Pretty Double | |
| Pretty Float | |
| Pretty Int | |
| Pretty Integer | |
| Pretty Ordering | |
| Pretty () | |
| Pretty a => Pretty [a] | |
| Pretty a => Pretty (Maybe a) | |
| (Pretty a, Pretty b) => Pretty (Either a b) | |
| (Pretty a, Pretty b) => Pretty (a, b) | |
| (Pretty a, Pretty b, Pretty c) => Pretty (a, b, c) | |
| (Pretty a, Pretty b, Pretty c, Pretty d) => Pretty (a, b, c, d) | |
| (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e) => Pretty (a, b, c, d, e) | |
| (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f) => Pretty (a, b, c, d, e, f) | |
| (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g) => Pretty (a, b, c, d, e, f, g) | |
| (Pretty a, Pretty b, Pretty c, Pretty d, Pretty e, Pretty f, Pretty g, Pretty h) => Pretty (a, b, c, d, e, f, g, h) | |