tini-0.1.0.0: Tiny INI file and configuration library with a minimal dependency footprint.

Safe HaskellNone
LanguageHaskell2010

Data.Tini

Contents

Synopsis

De/serializing INI files

data Ini Source #

An ordered, comment-preserving representation of an INI file.

Instances
Eq Ini Source # 
Instance details

Defined in Data.Tini.Types

Methods

(==) :: Ini -> Ini -> Bool #

(/=) :: Ini -> Ini -> Bool #

Read Ini Source # 
Instance details

Defined in Data.Tini.Types

Show Ini Source # 
Instance details

Defined in Data.Tini.Types

Methods

showsPrec :: Int -> Ini -> ShowS #

show :: Ini -> String #

showList :: [Ini] -> ShowS #

parseIni :: (Alternative m, MonadFail m) => String -> m Ini Source #

Parses an INI file from the given string.

A valid INI file may contain zero or more lines, where each line is any of the following:

  • A [section header] in square brackets;
  • a key = value pair;
  • a comment, starting with either ; or #; or
  • whitespace.

Note that a valid INI file must not contain duplicate section headers, and keys must be unique within their section. Section headers and keys are case-sensitive. Values must be contained on a single line. Whitespace is ignored at the start and end of each line, section header, key, and value.

showIni :: Ini -> String Source #

Serialize an Ini to a String.

Reading and modifying properties

data Key Source #

A key into an INI file.

A valid key is either of the format "sect.prop" or just "prop". The first key will match the property prop in section sect, and the second will match the property prop outside of any section. prop must not begin with ; or # or contain a =, and sect must not contain ]. Both parts are case-sensitive.

Instances
Eq Key Source # 
Instance details

Defined in Data.Tini.Types

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Ord Key Source # 
Instance details

Defined in Data.Tini.Types

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Data.Tini.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source # 
Instance details

Defined in Data.Tini.Types

Methods

fromString :: String -> Key #

empty :: Ini Source #

An INI with no sections or properties.

get :: IniValue a => Ini -> Key -> Maybe a Source #

Returns the value at the given key, if it exists and is valid at the function's result type. See IniValue for more information regarding how Haskell values are encoded in INI files.

set :: IniValue a => Ini -> Key -> a -> Ini Source #

Sets the given key to the given value. If the key already exists, it will be overwritten.

New sections are added at the end of the given INI, and new properties are added at the end of their respective sections.

remove :: Key -> Ini -> Ini Source #

Removes the given key from the given INI.

modify :: (Maybe String -> Maybe String) -> Key -> Ini -> Ini Source #

Modify the value at the given key in the given INI.

If the key exists, the given function will receive Just value as its argument, otherwise it will receive Nothing.

If the given function returns Just new_value, the given key will be created or overwritten with new_value. If it returns Nothing, the key will be deleted.

toList :: Ini -> [(Key, String)] Source #

Convert the given INI to s list of (key, value) pairs.

fromList :: [(Key, String)] -> Ini Source #

Create an INI from the given list of (key, value) pairs.

merge :: Ini -> Ini -> Ini Source #

Merge the given INIs. Values from the second INI override values from the first in cases where a key exists in both. Comments from the second INI are discarded.

Working with files

readIniFile :: FilePath -> IO (Maybe Ini) Source #

Attempt to read the given file as an INI. Returns Nothing if the file does not exist or can not be parsed as an INI file.

writeIniFile :: FilePath -> Ini -> IO () Source #

Atomically write the given INI to the given file.

Adding new types of INI properties

class IniValue a where Source #

Valid types for values of INI properties. Default implementation uses show and reads for showValue and readValue respectively.

Minimal complete definition

Nothing

Instances
IniValue Bool Source #

Valid values for booleans (case-insensitive): true, false, yes, no, t, f, y, n, 1, 0, on, off.

Instance details

Defined in Data.Tini.IniValue

IniValue Char Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Double Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Float Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Int Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Int8 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Int16 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Int32 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Int64 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Integer Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Word Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Word8 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Word16 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Word32 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue Word64 Source # 
Instance details

Defined in Data.Tini.IniValue

IniValue String Source #

Strings are the raw values of properties, with whitespace trimmed on both ends. They are not enclosed in quotes.

Instance details

Defined in Data.Tini.IniValue

IniValue a => IniValue [a] Source #

Lists are zero or more valid values, separated by commas. To include a comma in a string within a list, escape it using \,.

Instance details

Defined in Data.Tini.IniValue

Methods

showValue :: [a] -> String Source #

readValue :: String -> Maybe [a] Source #

IniValue a => IniValue (Maybe a) Source #

Nothing is encoded as the empty string, and any non-empty value of the correct type encodes Just val.

Instance details

Defined in Data.Tini.IniValue

(IniValue a, IniValue b) => IniValue (Either a b) Source #

readValue returns Left val If the value is readable at the type on the left, Right val if it's readable at the type on the right, and Nothing if it's not readable as either.

Instance details

Defined in Data.Tini.IniValue

(IniValue a, IniValue b) => IniValue (a, b) Source #

Tuples follow the same rules as lists, but must be of the correct length.

Instance details

Defined in Data.Tini.IniValue

Methods

showValue :: (a, b) -> String Source #

readValue :: String -> Maybe (a, b) Source #

(IniValue a, IniValue b, IniValue c) => IniValue (a, b, c) Source # 
Instance details

Defined in Data.Tini.IniValue

Methods

showValue :: (a, b, c) -> String Source #

readValue :: String -> Maybe (a, b, c) Source #