config-ini-0.2.0.1: A library for simple INI-based configuration files.

Copyright(c) Getty Ritter 2017
LicenseBSD
MaintainerGetty Ritter <config-ini@infinitenegativeutility.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Ini.Config.Bidir

Contents

Description

This module presents an alternate API for parsing INI files. Unlike the standard API, it is bidirectional: the same declarative structure can be used to parse an INI file to a value, serialize an INI file from a value, or even update an INI file by comparing it against a value and serializing in a way that minimizes the differences between revisions of the file.

This API does make some extra assumptions about your configuration type and the way you interact with it: in particular, it assumes that you have lenses for all the fields you're parsing and that you have some kind of sensible default value of that configuration type. Instead of providing combinators which can extract and parse a field of an INI file into a value, the bidirectional API allows you to declaratively associate a lens into your structure with a field of the INI file.

Consider the following example INI file:

[NETWORK]
host = example.com
port = 7878

[LOCAL]
user = terry

We'd like to parse this INI file into a Config type which we've defined like this, using lens or a similar library to provide lenses:

data Config = Config
  { _cfHost :: String
  , _cfPort :: Int
  , _cfUser :: Maybe Text
  } deriving (Eq, Show)

''makeLenses Config

We can now define a basic specification of the type IniSpec Config () by using the provided operations to declare our top-level sections, and then within those sections we can associate fields with Config lenses.

configSpec :: IniSpec Config ()
configSpec = do
  section "NETWORK" $ do
    cfHost .= field "host" string
    cfPost .= field "port" number
  sectionOpt "LOCAL" $ do
    cfUser .=? field "user" text

There are two operators used to associate lenses with fields:

.=
Associates a lens of type Lens' s a with a field description of type FieldDescription a. By default, this will raise an error when parsing if the field described is missing, but we can mark it as optional, as we'll see.
.=?
Associates a lens of type Lens' s (Maybe a) with a field description of type FieldDescription a. During parsing, if the value does not appear in an INI file, then the lens will be set to Nothing; similarly, during serializing, if the value is Nothing, then the field will not be serialized in the file.

Each field must include the field's name as well as a FieldValue, which describes how to both parse and serialize a value of a given type. Several built-in FieldValue descriptions are provided, but you can always build your own by providing parsing and serialization functions for individual fields.

We can also provide extra metadata about a field, allowing it to be skipped durin parsing, or to provide an explicit default value, or to include an explanatory comment for that value to be used when we serialize an INI file. These are conventionally applied to the field using the & operator:

configSpec :: IniSpec Config ()
configSpec = do
  section "NETWORK" $ do
    cfHost .= field "host" string
                & comment ["The desired hostname (optional)"]
                & optional
    cfPost .= field "port" number
                & comment ["The port number"]
  sectionOpt "LOCAL" $ do
    cfUser .=? field "user" text

When we want to use this specification, we need to create a value of type Ini, which is an abstract representation of an INI specification. To create an Ini value, we need to use the ini function, which combines the spec with the default version of our configuration value.

Once we have a value of type Ini, we can use it for three basic operations:

  • We can parse a textual INI file with parseIni, which will systematically walk the spec and use the provided lens/field associations to create a parsed configuration file. This will give us a new value of type Ini that represents the parsed configuration, and we can extract the actual configuration value with getIniValue.
  • We can update the value contained in an Ini value. If the Ini value is the result of a previous call to parseIni, then this update will attempt to retain as much of the incidental structure of the parsed file as it can: for example, it will attempt to retain comments, whitespace, and ordering. The general strategy is to make the resulting INI file "diff-minimal": the diff between the older INI file and the updated INI file should contain as little noise as possible. Small cosmetic choices such as how to treat generated comments are controlled by a configurable UpdatePolicy value.
  • We can serialize an Ini value to a textual INI file. This will produce the specified INI file (either a default fresh INI, or a modified existing INI) as a textual value.

Synopsis

Parsing, Serializing, and Updating Files

Functions for parsing, serializing, and updating INI files.

data Ini s Source #

An Ini is an abstract representation of an INI file, including both its textual representation and the Haskell value it represents.

ini :: s -> IniSpec s () -> Ini s Source #

Create a basic Ini value from a default value and a spec.

getIniValue :: Ini s -> s Source #

Get the underlying Haskell value associated with the Ini.

getRawIni :: Ini s -> RawIni Source #

Get the underlying RawIni value for the file.

Parsing INI files

parseIni :: Text -> Ini s -> Either String (Ini s) Source #

Parse a textual representation of an Ini file. If the file is malformed or if an obligatory field is not found, this will produce a human-readable error message. If an optional field is not found, then it will fall back on the existing value contained in the provided Ini structure.

Serializing INI files

serializeIni :: Ini s -> Text Source #

Get the textual representation of an Ini value. If this Ini value is the result of parseIni, then it will attempt to retain the textual characteristics of the parsed version as much as possible (e.g. by retaining comments, ordering, and whitespace in a way that will minimize the overall diff footprint.) If the Ini value was created directly from a value and a specification, then it will pretty-print an initial version of the file with the comments and placeholder text specified in the spec.

Updating INI Files

updateIni :: s -> Ini s -> Ini s Source #

Update the internal value of an Ini file. If this Ini value is the result of parseIni, then the resulting Ini value will attempt to retain the textual characteristics of the parsed version as much as possible (e.g. by retaining comments, ordering, and whitespace in a way that will minimize the overall diff footprint.)

setIniUpdatePolicy :: UpdatePolicy -> Ini s -> Ini s Source #

Use the provided UpdatePolicy as a guide when creating future updated versions of the given Ini value.

data UpdatePolicy Source #

An UpdatePolicy guides certain choices made when an Ini file is updated: for example, how to add comments to the generated fields, or how to treat fields which are optional.

Constructors

UpdatePolicy 

Fields

data UpdateCommentPolicy Source #

An UpdateCommentPolicy describes what comments should accompany a field added to or modified in an existing INI file when using updateIni.

Constructors

CommentPolicyNone

Do not add comments to new fields

CommentPolicyAddFieldComment

Add the same comment which appears in the IniSpec value for the field we're adding or modifying.

CommentPolicyAddDefaultComment (Seq Text)

Add a common comment to all new fields added or modified by an updateIni call.

defaultUpdatePolicy :: UpdatePolicy Source #

A set of sensible UpdatePolicy defaults which keep the diffs between file versions minimal.

Bidirectional Parser Types

Types which represent declarative specifications for INI file structure.

data IniSpec s a Source #

An IniSpec value represents the structure of an entire INI-format file in a declarative way. The s parameter represents the type of a Haskell structure which is being serialized to or from.

Instances

Monad (IniSpec s) Source # 

Methods

(>>=) :: IniSpec s a -> (a -> IniSpec s b) -> IniSpec s b #

(>>) :: IniSpec s a -> IniSpec s b -> IniSpec s b #

return :: a -> IniSpec s a #

fail :: String -> IniSpec s a #

Functor (IniSpec s) Source # 

Methods

fmap :: (a -> b) -> IniSpec s a -> IniSpec s b #

(<$) :: a -> IniSpec s b -> IniSpec s a #

Applicative (IniSpec s) Source # 

Methods

pure :: a -> IniSpec s a #

(<*>) :: IniSpec s (a -> b) -> IniSpec s a -> IniSpec s b #

(*>) :: IniSpec s a -> IniSpec s b -> IniSpec s b #

(<*) :: IniSpec s a -> IniSpec s b -> IniSpec s a #

data SectionSpec s a Source #

A SectionSpec value represents the structure of a single section of an INI-format file in a declarative way. The s parameter represents the type of a Haskell structure which is being serialized to or from.

Instances

Monad (SectionSpec s) Source # 

Methods

(>>=) :: SectionSpec s a -> (a -> SectionSpec s b) -> SectionSpec s b #

(>>) :: SectionSpec s a -> SectionSpec s b -> SectionSpec s b #

return :: a -> SectionSpec s a #

fail :: String -> SectionSpec s a #

Functor (SectionSpec s) Source # 

Methods

fmap :: (a -> b) -> SectionSpec s a -> SectionSpec s b #

(<$) :: a -> SectionSpec s b -> SectionSpec s a #

Applicative (SectionSpec s) Source # 

Methods

pure :: a -> SectionSpec s a #

(<*>) :: SectionSpec s (a -> b) -> SectionSpec s a -> SectionSpec s b #

(*>) :: SectionSpec s a -> SectionSpec s b -> SectionSpec s b #

(<*) :: SectionSpec s a -> SectionSpec s b -> SectionSpec s a #

Section-Level Parsing

Declaring sections of an INI file specification

section :: Text -> SectionSpec s () -> IniSpec s () Source #

Define the specification of a top-level INI section.

allOptional :: (SectionSpec s () -> IniSpec s ()) -> SectionSpec s () -> IniSpec s () Source #

Treat an entire section as containing entirely optional fields.

Field-Level Parsing

Declaring individual fields of an INI file specification.

data FieldDescription t Source #

A FieldDescription is a declarative representation of the structure of a field. This includes the name of the field and the FieldValue used to parse and serialize values of that field, as well as other metadata that might be needed in the course of parsing or serializing a structure.

(.=) :: Eq t => Lens s s t t -> FieldDescription t -> SectionSpec s () infixr 0 Source #

Associate a field description with a field. If this field is not present when parsing, it will attempt to fall back on a default, and if no default value is present, it will fail to parse.

When serializing an INI file, this will produce all the comments associated with the field description followed by the value of the field in the.

(.=?) :: Eq t => Lens s s (Maybe t) (Maybe t) -> FieldDescription t -> SectionSpec s () infixr 0 Source #

Associate a field description with a field of type "Maybe a". When parsing, this field will be initialized to Nothing if it is not found, and to a Just value if it is. When serializing an INI file, this will try to serialize a value

field :: Text -> FieldValue a -> FieldDescription a Source #

Create a description of a field by a combination of the name of the field and a FieldValue describing how to parse and emit values associated with that field.

flag :: Text -> FieldDescription Bool Source #

Create a description of a Bool-valued field.

comment :: [Text] -> FieldDescription t -> FieldDescription t Source #

Associate a multiline comment with a FieldDescription. When serializing a field that has a comment associated, the comment will appear before the field.

placeholderValue :: Text -> FieldDescription t -> FieldDescription t Source #

Choose a placeholder value to be displayed for optional fields. This is used when serializing an optional Ini field: the field will appear commented out in the output using the placeholder text as a value, so a spec that includes

  myLens .=? field "x" & placeholderValue "<val>"
  

will serialize into an INI file that contains the line

  # x = <val>
  

A placeholder value will only appear in the serialized output if the field is optional, but will be preferred over serializing the default value for an optional field. This will not affect INI file updates.

optional :: FieldDescription t -> FieldDescription t Source #

If the field is not found in parsing, simply skip instead of raising an error or setting anything.

FieldValues

Values of type FieldValue represent both a parser and a serializer for a value of a given type. It's possible to manually create FieldValue descriptions, but for simple configurations, but for the sake of convenience, several commonly-needed varieties of FieldValue are defined here.

data FieldValue a Source #

A value of type FieldValue packages up a parser and emitter function into a single value. These are used for bidirectional parsing and emitting of the value of a field.

Constructors

FieldValue 

Fields

  • fvParse :: Text -> Either String a

    The function to use when parsing the value of a field; if the parser fails, then the string will be shown as an error message to the user.

  • fvEmit :: a -> Text

    The function to use when serializing a value into an INI file.

text :: FieldValue Text Source #

Represents a field whose value is a Text value

string :: FieldValue String Source #

Represents a field whose value is a String value

number :: (Show a, Read a, Num a, Typeable a) => FieldValue a Source #

Represents a numeric field whose value is parsed according to the Read implementation for that type, and is serialized according to the Show implementation for that type.

bool :: FieldValue Bool Source #

Represents a field whose value is a Bool value. This parser is case-insensitive, and matches the words true, false, yes, and no, as well as single-letter abbreviations for all of the above. This will serialize as true for True and false for False.

readable :: forall a. (Show a, Read a, Typeable a) => FieldValue a Source #

A FieldValue for parsing and serializing values according to the logic of the Read and Show instances for that type, providing a convenient human-readable error message if the parsing step fails.

listWithSeparator :: IsList l => Text -> FieldValue (Item l) -> FieldValue l Source #

Represents a field whose value is a sequence of other values which are delimited by a given string, and whose individual values are described by another FieldValue value. This uses GHC's IsList typeclass to convert back and forth between sequence types.

pairWithSeparator :: FieldValue l -> Text -> FieldValue r -> FieldValue (l, r) Source #

Represents a field whose value is a pair of two other values separated by a given string, whose individual values are described by two different FieldValue values.

Miscellaneous Helpers

These values and types are exported for compatibility.

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

Since: 4.8.0.0

type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t Source #

This is a lens-compatible type alias