config-ini-0.2.3.0: 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

Contents

Description

The 'config-ini' library exports some simple monadic functions to make parsing INI-like configuration easier. INI files have a two-level structure: the top-level named chunks of configuration, and the individual key-value pairs contained within those chunks. For example, the following INI file has two sections, NETWORK and LOCAL, and each contains its own key-value pairs. Comments, which begin with # or ;, are ignored:

[NETWORK]
host = example.com
port = 7878

# here is a comment
[LOCAL]
user = terry

The combinators provided here are designed to write quick and idiomatic parsers for files of this form. Sections are parsed by IniParser computations, like section and its variations, while the fields within sections are parsed by SectionParser computations, like field and its variations. If we want to parse an INI file like the one above, treating the entire LOCAL section as optional, we can write it like this:

data Config = Config
  { cfNetwork :: NetworkConfig, cfLocal :: Maybe LocalConfig }
    deriving (Eq, Show)

data NetworkConfig = NetworkConfig
  { netHost :: String, netPort :: Int }
    deriving (Eq, Show)

data LocalConfig = LocalConfig
  { localUser :: Text }
    deriving (Eq, Show)

configParser :: IniParser Config
configParser = do
  netCf <- section "NETWORK" $ do
    host <- fieldOf "host" string
    port <- fieldOf "port" number
    return NetworkConfig { netHost = host, netPort = port }
  locCf <- sectionMb "LOCAL" $
    LocalConfig <$> field "user"
  return Config { cfNetwork = netCf, cfLocal = locCf }

We can run our computation with parseIniFile, which, when run on our example file above, would produce the following:

>>> parseIniFile example configParser
Right (Config {cfNetwork = NetworkConfig {netHost = "example.com", netPort = 7878}, cfLocal = Just (LocalConfig {localUser = "terry"})})
Synopsis

Parsing Files

parseIniFile :: Text -> IniParser a -> Either String a Source #

Parse a Text value as an INI file and run an IniParser over it

Parser Types

data IniParser a Source #

An IniParser value represents a computation for parsing entire INI-format files.

Instances
Monad IniParser Source # 
Instance details

Defined in Data.Ini.Config

Methods

(>>=) :: IniParser a -> (a -> IniParser b) -> IniParser b #

(>>) :: IniParser a -> IniParser b -> IniParser b #

return :: a -> IniParser a #

fail :: String -> IniParser a #

Functor IniParser Source # 
Instance details

Defined in Data.Ini.Config

Methods

fmap :: (a -> b) -> IniParser a -> IniParser b #

(<$) :: a -> IniParser b -> IniParser a #

Applicative IniParser Source # 
Instance details

Defined in Data.Ini.Config

Methods

pure :: a -> IniParser a #

(<*>) :: IniParser (a -> b) -> IniParser a -> IniParser b #

liftA2 :: (a -> b -> c) -> IniParser a -> IniParser b -> IniParser c #

(*>) :: IniParser a -> IniParser b -> IniParser b #

(<*) :: IniParser a -> IniParser b -> IniParser a #

Alternative IniParser Source # 
Instance details

Defined in Data.Ini.Config

Methods

empty :: IniParser a #

(<|>) :: IniParser a -> IniParser a -> IniParser a #

some :: IniParser a -> IniParser [a] #

many :: IniParser a -> IniParser [a] #

data SectionParser a Source #

A SectionParser value represents a computation for parsing a single section of an INI-format file.

Section-Level Parsing

section :: Text -> SectionParser a -> IniParser a Source #

Find a named section in the INI file and parse it with the provided section parser, failing if the section does not exist. In order to support classic INI files with capitalized section names, section lookup is case-insensitive.

>>> parseIniFile "[ONE]\nx = hello\n" $ section "ONE" (field "x")
Right "hello"
>>> parseIniFile "[ONE]\nx = hello\n" $ section "TWO" (field "x")
Left "No top-level section named \"TWO\""

sections :: Text -> SectionParser a -> IniParser (Seq a) Source #

Find multiple named sections in the INI file and parse them all with the provided section parser. In order to support classic INI files with capitalized section names, section lookup is case-insensitive.

>>> parseIniFile "[ONE]\nx = hello\n[ONE]\nx = goodbye\n" $ sections "ONE" (field "x")
Right (fromList ["hello","goodbye"])
>>> parseIniFile "[ONE]\nx = hello\n" $ sections "TWO" (field "x")
Right (fromList [])

sectionOf :: (Text -> Maybe b) -> (b -> SectionParser a) -> IniParser a Source #

A call to sectionOf f will apply f to each section name and, if f produces a Just value, pass the extracted value in order to get the SectionParser to use for that section. This will find at most one section, and will produce an error if no section exists.

>>> parseIniFile "[FOO]\nx = hello\n" $ sectionOf (T.stripSuffix "OO") (\ l -> fmap ((,) l) (field "x"))
Right ("F","hello")
>>> parseIniFile "[BAR]\nx = hello\n" $ sectionOf (T.stripSuffix "OO") (\ l -> fmap ((,) l) (field "x"))
Left "No matching top-level section"

sectionsOf :: (Text -> Maybe b) -> (b -> SectionParser a) -> IniParser (Seq a) Source #

A call to sectionsOf f will apply f to each section name and, if f produces a Just value, pass the extracted value in order to get the SectionParser to use for that section. This will return every section for which the call to f produces a Just value.

>>> parseIniFile "[FOO]\nx = hello\n[BOO]\nx = goodbye\n" $ sectionsOf (T.stripSuffix "OO") (\ l -> fmap ((,) l) (field "x"))
Right (fromList [("F","hello"),("B","goodbye")])
>>> parseIniFile "[BAR]\nx = hello\n" $ sectionsOf (T.stripSuffix "OO") (\ l -> fmap ((,) l) (field "x"))
Right (fromList [])

sectionMb :: Text -> SectionParser a -> IniParser (Maybe a) Source #

Find a named section in the INI file and parse it with the provided section parser, returning Nothing if the section does not exist. In order to support classic INI files with capitalized section names, section lookup is case-insensitive.

>>> parseIniFile "[ONE]\nx = hello\n" $ sectionMb "ONE" (field "x")
Right (Just "hello")
>>> parseIniFile "[ONE]\nx = hello\n" $ sectionMb "TWO" (field "x")
Right Nothing

sectionDef :: Text -> a -> SectionParser a -> IniParser a Source #

Find a named section in the INI file and parse it with the provided section parser, returning a default value if the section does not exist. In order to support classic INI files with capitalized section names, section lookup is case-insensitive.

>>> parseIniFile "[ONE]\nx = hello\n" $ sectionDef "ONE" "def" (field "x")
Right "hello"
>>> parseIniFile "[ONE]\nx = hello\n" $ sectionDef "TWO" "def" (field "x")
Right "def"

Field-Level Parsing

field :: Text -> SectionParser Text Source #

Retrieve a field, failing if it doesn't exist, and return its raw value.

>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (field "x")
Right "hello"
>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (field "y")
Left "Missing field \"y\" in section \"MAIN\""

fieldOf :: Text -> (Text -> Either String a) -> SectionParser a Source #

Retrieve a field and use the supplied parser to parse it as a value, failing if the field does not exist, or if the parser fails to produce a value.

>>> parseIniFile "[MAIN]\nx = 72\n" $ section "MAIN" (fieldOf "x" number)
Right 72
>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldOf "x" number)
Left "Line 2, in section \"MAIN\": Unable to parse \"hello\" as a value of type Integer"
>>> parseIniFile "[MAIN]\nx = 72\n" $ section "MAIN" (fieldOf "y" number)
Left "Missing field \"y\" in section \"MAIN\""

fieldMb :: Text -> SectionParser (Maybe Text) Source #

Retrieve a field, returning a Nothing value if it does not exist.

>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldMb "x")
Right (Just "hello")
>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldMb "y")
Right Nothing

fieldMbOf :: Text -> (Text -> Either String a) -> SectionParser (Maybe a) Source #

Retrieve a field and parse it according to the given parser, returning Nothing if it does not exist. If the parser fails, then this will fail.

>>> parseIniFile "[MAIN]\nx = 72\n" $ section "MAIN" (fieldMbOf "x" number)
Right (Just 72)
>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldMbOf "x" number)
Left "Line 2, in section \"MAIN\": Unable to parse \"hello\" as a value of type Integer"
>>> parseIniFile "[MAIN]\nx = 72\n" $ section "MAIN" (fieldMbOf "y" number)
Right Nothing

fieldDef :: Text -> Text -> SectionParser Text Source #

Retrieve a field and supply a default value for if it doesn't exist.

>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldDef "x" "def")
Right "hello"
>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldDef "y" "def")
Right "def"

fieldDefOf :: Text -> (Text -> Either String a) -> a -> SectionParser a Source #

Retrieve a field, parsing it according to the given parser, and returning a default value if it does not exist. If the parser fails, then this will fail.

>>> parseIniFile "[MAIN]\nx = 72\n" $ section "MAIN" (fieldDefOf "x" number 99)
Right 72
>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldDefOf "x" number 99)
Left "Line 2, in section \"MAIN\": Unable to parse \"hello\" as a value of type Integer"
>>> parseIniFile "[MAIN]\nx = 72\n" $ section "MAIN" (fieldDefOf "y" number 99)
Right 99

fieldFlag :: Text -> SectionParser Bool Source #

Retrieve a field and treat it as a boolean, failing if it does not exist.

>>> parseIniFile "[MAIN]\nx = yes\n" $ section "MAIN" (fieldFlag "x")
Right True
>>> parseIniFile "[MAIN]\nx = yes\n" $ section "MAIN" (fieldFlag "y")
Left "Missing field \"y\" in section \"MAIN\""

fieldFlagDef :: Text -> Bool -> SectionParser Bool Source #

Retrieve a field and treat it as a boolean, subsituting a default value if it doesn't exist.

>>> parseIniFile "[MAIN]\nx = yes\n" $ section "MAIN" (fieldFlagDef "x" False)
Right True
>>> parseIniFile "[MAIN]\nx = hello\n" $ section "MAIN" (fieldFlagDef "x" False)
Left "Line 2, in section \"MAIN\": Unable to parse \"hello\" as a boolean"
>>> parseIniFile "[MAIN]\nx = yes\n" $ section "MAIN" (fieldFlagDef "y" False)
Right False

Reader Functions

readable :: forall a. (Read a, Typeable a) => Text -> Either String a Source #

Try to use the Read instance for a type to parse a value, failing with a human-readable error message if reading fails.

>>> readable "(5, 7)" :: Either String (Int, Int)
Right (5,7)
>>> readable "hello" :: Either String (Int, Int)
Left "Unable to parse \"hello\" as a value of type (Int,Int)"

number :: (Num a, Read a, Typeable a) => Text -> Either String a Source #

Try to use the Read instance for a numeric type to parse a value, failing with a human-readable error message if reading fails.

>>> number "5" :: Either String Int
Right 5
>>> number "hello" :: Either String Int
Left "Unable to parse \"hello\" as a value of type Int"

string :: IsString a => Text -> Either String a Source #

Convert a textual value to the appropriate string type. This will never fail.

>>> string "foo" :: Either String String
Right "foo"

flag :: Text -> Either String Bool Source #

Convert a string that represents a boolean to a proper boolean. This is case-insensitive, and matches the words true, false, yes, no, as well as single-letter abbreviations for all of the above. If the input does not match, then this will fail with a human-readable error message.

>>> flag "TRUE"
Right True
>>> flag "y"
Right True
>>> flag "no"
Right False
>>> flag "F"
Right False
>>> flag "That's a secret!"
Left "Unable to parse \"That's a secret!\" as a boolean"

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

Convert a reader for a value into a reader for a list of those values, separated by a chosen separator. This will split apart the string on that separator, get rid of leading and trailing whitespace on the individual chunks, and then attempt to parse each of them according to the function provided, turning the result into a list.

This is overloaded with the IsList typeclass, so it can be used transparently to parse other list-like types.

>>> listWithSeparator "," number "2, 3, 4" :: Either String [Int]
Right [2,3,4]
>>> listWithSeparator " " number "7 8 9" :: Either String [Int]
Right [7,8,9]
>>> listWithSeparator ":" string "/bin:/usr/bin" :: Either String [FilePath]
Right ["/bin","/usr/bin"]
>>> listWithSeparator "," number "7 8 9" :: Either String [Int]
Left "Unable to parse \"7 8 9\" as a value of type Int"