Copyright | (c) Getty Ritter 2017 |
---|---|
License | BSD |
Maintainer | Getty Ritter <config-ini@infinitenegativeutility.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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
by using the provided operations to declare our top-level
sections, and then within those sections we can associate fields with
IniSpec
Config
()Config
lenses.
configSpec
::IniSpec
Config ()configSpec
= dosection
"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 typeFieldDescription 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 typeFieldDescription a
. During parsing, if the value does not appear in an INI file, then the lens will be set toNothing
; similarly, during serializing, if the value isNothing
, 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 = dosection
"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 typeIni
that represents the parsed configuration, and we can extract the actual configuration value withgetIniValue
. - We can update the value contained in an
Ini
value. If theIni
value is the result of a previous call toparseIni
, 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 configurableUpdatePolicy
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.
- data Ini s
- ini :: s -> IniSpec s () -> Ini s
- getIniValue :: Ini s -> s
- getRawIni :: Ini s -> RawIni
- parseIni :: Text -> Ini s -> Either String (Ini s)
- serializeIni :: Ini s -> Text
- updateIni :: s -> Ini s -> Ini s
- setIniUpdatePolicy :: UpdatePolicy -> Ini s -> Ini s
- data UpdatePolicy = UpdatePolicy {}
- data UpdateCommentPolicy
- defaultUpdatePolicy :: UpdatePolicy
- data IniSpec s a
- data SectionSpec s a
- section :: Text -> SectionSpec s () -> IniSpec s ()
- allOptional :: (SectionSpec s () -> IniSpec s ()) -> SectionSpec s () -> IniSpec s ()
- data FieldDescription t
- (.=) :: Eq t => Lens s s t t -> FieldDescription t -> SectionSpec s ()
- (.=?) :: Eq t => Lens s s (Maybe t) (Maybe t) -> FieldDescription t -> SectionSpec s ()
- field :: Text -> FieldValue a -> FieldDescription a
- flag :: Text -> FieldDescription Bool
- comment :: [Text] -> FieldDescription t -> FieldDescription t
- placeholderValue :: Text -> FieldDescription t -> FieldDescription t
- optional :: FieldDescription t -> FieldDescription t
- data FieldValue a = FieldValue {}
- text :: FieldValue Text
- string :: FieldValue String
- number :: (Show a, Read a, Num a, Typeable a) => FieldValue a
- bool :: FieldValue Bool
- readable :: forall a. (Show a, Read a, Typeable a) => FieldValue a
- listWithSeparator :: IsList l => Text -> FieldValue (Item l) -> FieldValue l
- pairWithSeparator :: FieldValue l -> Text -> FieldValue r -> FieldValue (l, r)
- (&) :: a -> (a -> b) -> b
- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
Parsing, Serializing, and Updating Files
Functions for parsing, serializing, and updating INI files.
An Ini
is an abstract representation of an INI file, including
both its textual representation and the Haskell value it
represents.
getIniValue :: Ini s -> s Source #
Get the underlying Haskell value associated with the Ini
.
Parsing INI files
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.
UpdatePolicy | |
|
data UpdateCommentPolicy Source #
An UpdateCommentPolicy
describes what comments should accompany
a field added to or modified in an existing INI file when using
updateIni
.
CommentPolicyNone | Do not add comments to new fields |
CommentPolicyAddFieldComment | Add the same comment which appears in the |
CommentPolicyAddDefaultComment (Seq Text) | Add a common comment to all new fields added or modified
by an |
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.
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.
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.
Monad (SectionSpec s) Source # | |
Functor (SectionSpec s) Source # | |
Applicative (SectionSpec s) Source # | |
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 #
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.
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.
bool :: FieldValue Bool Source #
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.