configurator-export-0.1.0.0: Pretty printer and exporter for configurations from the "configurator" library.

Copyright(c) Justin Le 2016
LicenseBSD3
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Configurator.Export

Contents

Description

Pretty printers and exporters for Configs from the configurator library, in Data.Configurator.

All results are intended to be valid parsing files in the configuration file syntax of the library.

For a full round trip:

main = do
  cfg <- load [Required "config.cfg"]
  writeConf "config.cfg" cfg

This should load the config file, parse it, and then re-export it, rewriting the original config file. The result should be an identical configuration file (with keys potentially re-arranged and re-sorted, comments removed, etc.)

Print/export your own dynmically generated configuration files by manipulating the HashMap Name Value that a Config gives with getMap.

Sample output:

foo {
    bar {
        baz1  = true
        baz2  = [1, 0.6, "hello", true]
    }
    aardvark  = "banana"
    monkey    = [true, false, 1.9e-3]
    zebra     = 24
}

foo2 {
    bar = 8.1e-8
}

apple   = ["cake", true]
orange  = 8943

Further configuration on sorting of keys, displaying of bools and floats, etc. is possible by passing in custom ConfStyle values.

Synopsis

Default styles

Pretty printing / Exporting

renderConf :: Config -> IO String Source

Render/pretty print the current contents of the given Config to a String.

displayConf :: Config -> IO () Source

Print out a pretty printed rendering of the current contents of the Config to stdout.

writeConf :: FilePath -> Config -> IO () Source

Write the current contents of the given Config to the given FilePath.

renderHashMap :: HashMap Name Value -> String Source

Render/pretty print the contents of a HashMap of keys and Values to a String.

Doc

confDoc :: Config -> IO Doc Source

Convert the current contents of the given Config to a Doc from the pretty package. This allows more fine-grained control over printing it.

hashMapDoc :: HashMap Name Value -> Doc Source

Convert a HashMap of keys and Values into a Doc, from the pretty package. This allows more fine-grained control over printing it.

Expects keys to be in the format exported from a Config using getMap. "foo.bar.baz.x" is "x" in group "baz" in group "bar" in group "foo", etc.

With styles

Describing styles

confStyle :: ConfStyle Source

Sensible defaults for a ConfStyle:

confStyle :: ConfStyle
confStyle = ConfStyle { confStyleIndent     = 4
                      , confStyleAlign      = AlignOn 2
                      , confStyleBraceStyle = SameLineBrace
                      , confStyleBoolStyle  = TrueFalse
                      , confStyleForceDec   = False
                      , confStyleShowInts   = True
                        -- sort by "type" of key, then sort alphabetically
                      , confStyleSortBy     = comparing snd <> comparing fst
                      , confStyleGroupSep   = 0
                      , confStyleValueSep   = 0
                      , confStyleTopSep     = 1
                      }

It's recommended that you create ConfStyles by modifying this value using record syntax rather than create your own from scratch:

myStyle = confStyle { confStyleBraceStyle = NewLineBrace
                    , confStyleBoolStyle  = OnOff
                    }

data ConfStyle Source

Style options for pretty-printing the contents of a Config. Sensible defaults are given as confStyle; it's recommended that you start with confStyle as a default and use record syntax to modify it to what you want. See confStyle for more details.

Constructors

ConfStyle 

Fields

confStyleIndent :: Int

Number of columns to indent each tested group.

confStyleAlign :: AlignStyle

Style of aligning the equals signs for keys with values.

confStyleBraceStyle :: BraceStyle

Style of opening brace (curly bracket) placement.

confStyleBoolStyle :: BoolStyle

Style of displaying Bools as boolean literals.

confStyleForceDec :: Bool

Force full decimals to be rendered, instead of truncating to scientific notation for numbers less than 0.1.

confStyleShowInts :: Bool

Whether or not to show "whole numbers" as integer literals (without the trailing .0)

confStyleSortBy :: (Name, KeyType) -> (Name, KeyType) -> Ordering

Function to sort keys by, with information on whether or not the key contains a group or a single value.

confStyleGroupSep :: Int

Newline seperators between groups.

confStyleValueSep :: Int

Newline seperators between chunks of contiguous values.

confStyleTopSep :: Int

Newline seperators between groups and chunks of contiguous values at the top level.

data AlignStyle Source

Alignment style of equals signs on contiguous sets of keys of values.

Constructors

NoAlign

Don't align equals signs at all.

AlignAny

Align them to the longest key.

AlignOn Int

Align to the longest key, but make sure the identation is a multiple of this number. okay.

data BraceStyle Source

Placement style of opening braces (curly brackets) for groups.

Constructors

SameLineBrace

Opening braces go on the same line as the key name.

NewLineBrace

Opening braces go on a new line after the key name.

data BoolStyle Source

The style of boolean literals display Bools as. Both are accepted by configurator's parser.

Constructors

OnOff

on and off

TrueFalse

true and false

data KeyType Source

The type of structure that the key contains. Used for sorting.

Constructors

KeyGroup

Key is associated with a group.

KeyValue

Key is associated with a single value.

Pretty printing / Exporting

renderConf' :: ConfStyle -> Config -> IO String Source

Render/pretty print the current contents of the given Config to a String, providing a ConfStyle with the rendering style.

displayConf' :: ConfStyle -> Config -> IO () Source

Print out a pretty printed rendering of the current contents of the Config to stdout, providing a ConfStyle with the rendering style.

writeConf' :: ConfStyle -> FilePath -> Config -> IO () Source

Write the current contents of the given Config to the given FilePath, providing a ConfStyle with the rendering style.

renderHashMap' :: ConfStyle -> HashMap Name Value -> String Source

Render/pretty print the contents of a HashMap of keys and Values to a String, providing a ConfStyle with the rendering style.

Doc

confDoc' :: ConfStyle -> Config -> IO Doc Source

Convert the current contents of the given Config to a Doc from the pretty package. This allows more fine-grained control over printing it. Takes a ConfStyle with the rendering style.

hashMapDoc' :: ConfStyle -> HashMap Name Value -> Doc Source

Convert a HashMap of keys and Values into a Doc, from the pretty package. This allows more fine-grained control over printing it. Takes a ConfStyle with the rendering style.

Expects keys to be in the format exported from a Config using getMap. "foo.bar.baz.x" is "x" in group "baz" in group "bar" in group "foo", etc.