| Copyright | (c) Matthew Peddie 2014 | 
|---|---|
| License | BSD3 | 
| Maintainer | mpeddie@gmail.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Language.Libconfig.Bindings
Contents
- Doctest example setup
 - Resource management
 - Config I/O
 - Safe (capable of returning an error) getting of primitive
 - Unsafe getting of primitives
 - Setting of primitives
 - Unsafe getting of primitives from a collection
 - Setting of primitives within a collection
 - Direct lookup by path
 - Collection management
 - Miscellaneous
 - Error reporting
 - Config file type system
 
Description
Low-level FFI bindings to the libconfig configuration file library. Please see the libconfig manual for documentation on what the various functions actually do and the underlying model of the libconfig API. The documentation in this module contains many usage examples which double as tests, but the focus is only on FFI details and C-vs.-Haskell impedance mismatches. As a result, there is no explanation of the behavior of many of the functions.
- data Configuration
 - data Setting
 - data ConfigErr
 - data ConfigType
 - isCollectionType :: ConfigType -> Bool
 - isScalarType :: ConfigType -> Bool
 - data ConfigFormat
 - configInit :: IO Configuration
 - configNew :: String -> IO (Maybe Configuration)
 - touchConfiguration :: Configuration -> IO ()
 - configReadFile :: Configuration -> String -> IO (Maybe ())
 - configWriteFile :: Configuration -> String -> IO (Maybe ())
 - configReadString :: Configuration -> String -> IO (Maybe ())
 - configSettingLookupInt :: Setting -> String -> IO (Maybe Int)
 - configSettingLookupInt64 :: Setting -> String -> IO (Maybe Int64)
 - configSettingLookupFloat :: Setting -> String -> IO (Maybe Double)
 - configSettingLookupBool :: Setting -> String -> IO (Maybe Bool)
 - configSettingLookupString :: Setting -> String -> IO (Maybe String)
 - configSettingGetInt :: Setting -> IO Int
 - configSettingGetInt64 :: Setting -> IO Int64
 - configSettingGetFloat :: Setting -> IO Double
 - configSettingGetBool :: Setting -> IO Bool
 - configSettingGetString :: Setting -> IO String
 - configSettingSetInt :: Setting -> Int -> IO (Maybe ())
 - configSettingSetInt64 :: Setting -> Int64 -> IO (Maybe ())
 - configSettingSetFloat :: Setting -> Double -> IO (Maybe ())
 - configSettingSetBool :: Setting -> Bool -> IO (Maybe ())
 - configSettingSetString :: Setting -> String -> IO (Maybe ())
 - configSettingGetIntElem :: Setting -> Int -> IO Int
 - configSettingGetInt64Elem :: Setting -> Int -> IO Int64
 - configSettingGetFloatElem :: Setting -> Int -> IO Double
 - configSettingGetBoolElem :: Setting -> Int -> IO Bool
 - configSettingGetStringElem :: Setting -> Int -> IO String
 - configSettingSetIntElem :: Setting -> Int -> Int -> IO (Maybe Setting)
 - configSettingSetInt64Elem :: Setting -> Int -> Int64 -> IO (Maybe Setting)
 - configSettingSetFloatElem :: Setting -> Int -> Double -> IO (Maybe Setting)
 - configSettingSetBoolElem :: Setting -> Int -> Bool -> IO (Maybe Setting)
 - configSettingSetStringElem :: Setting -> Int -> String -> IO (Maybe Setting)
 - configLookup :: Configuration -> String -> IO (Maybe Setting)
 - configLookupFrom :: Setting -> String -> IO (Maybe Setting)
 - configLookupInt :: Configuration -> String -> IO (Maybe Int)
 - configLookupInt64 :: Configuration -> String -> IO (Maybe Int64)
 - configLookupFloat :: Configuration -> String -> IO (Maybe Double)
 - configLookupBool :: Configuration -> String -> IO (Maybe Bool)
 - configLookupString :: Configuration -> String -> IO (Maybe String)
 - configSettingIndex :: Setting -> IO Int
 - configSettingLength :: Setting -> IO Int
 - configSettingGetElem :: Setting -> Int -> IO (Maybe Setting)
 - configSettingGetMember :: Setting -> String -> IO (Maybe Setting)
 - configSettingAdd :: Setting -> String -> ConfigType -> IO (Maybe Setting)
 - configSettingRemove :: Setting -> String -> IO (Maybe ())
 - configSettingRemoveElem :: Setting -> Int -> IO (Maybe ())
 - configSettingName :: Setting -> IO (Maybe String)
 - configSettingParent :: Setting -> IO (Maybe Setting)
 - configSettingIsRoot :: Setting -> IO Bool
 - configRootSetting :: Configuration -> IO (Maybe Setting)
 - configSettingSourceLine :: Setting -> IO Int
 - configSettingSourceFile :: Setting -> IO String
 - configGetDefaultFormat :: Configuration -> IO ConfigFormat
 - configSetDefaultFormat :: Configuration -> ConfigFormat -> IO ()
 - configSettingGetFormat :: Setting -> IO ConfigFormat
 - configSettingSetFormat :: Setting -> ConfigFormat -> IO (Maybe ())
 - configGetTabWidth :: Configuration -> IO Int
 - configSetTabWidth :: Configuration -> Int -> IO ()
 - configErrorFile :: Configuration -> IO (Maybe String)
 - configErrorText :: Configuration -> IO (Maybe String)
 - configErrorLine :: Configuration -> IO Int
 - configErrorType :: Configuration -> IO ConfigErr
 - configSettingType :: Setting -> IO ConfigType
 - configSettingIsGroup :: Setting -> IO Bool
 - configSettingIsList :: Setting -> IO Bool
 - configSettingIsArray :: Setting -> IO Bool
 - configSettingIsAggregate :: Setting -> IO Bool
 - configSettingIsNumber :: Setting -> IO Bool
 - configSettingIsScalar :: Setting -> IO Bool
 
Doctest example setup
All the examples run on the included test file test/test.conf,
 which is reproduced here from the
 libconfig manual.
     # Example application configuration file
     version = "1.0";
     application:
     {
       window:
       {
         title = "My Application";
         size = { w = 640; h = 480; };
         pos = { x = 350; y = 250; };
       };
       list = ( ( "abc", 123, true ), 1.234, ( * an empty list *) );
       books = ( { title  = "Treasure Island";
                   author = "Robert Louis Stevenson";
                   price  = 29.95;
                   qty    = 5; },
                 { title  = "Snow Crash";
                   author = "Neal Stephenson";
                   price  = 9.99;
                   qty    = 8; } );
       misc:
       {
         pi = 3.141592654;
         bigint = 9223372036854775807L;
         columns = [ "Last Name", "First Name", MI ];
         bitmask = 0x1FC3;
       };
     };
The following setup actions are assumed for many of the usage examples below.
>>>Just conf <- configNew "test/test.conf">>>Just app <- configLookup conf "application">>>Just misc <- configLookupFrom app "misc">>>Just winsize <- configLookupFrom app "window.size"
conf' is used for modifying values.
>>>Just conf' <- configNew "test/test.conf"
data Configuration Source
Top-level configuration value, corresponding to the libconfig
 config_t.  Wrapped opaquely for pointer-safety.
Instances
Corresponds to a libconfig config_setting_t value; wrapped
 opaquely for pointer safety.
This is a set of possible errors that can occur when libconfig
 tries to read in a config file.
Constructors
| ConfigErrNone | |
| ConfigErrFileIo | |
| ConfigErrParse | 
data ConfigType Source
isCollectionType :: ConfigType -> Bool Source
Tells whether a ConfigType value is a collection (ListType,
 ArrayType or GroupType).
>>>isCollectionType GroupTypeTrue>>>isCollectionType BoolTypeFalse
isScalarType :: ConfigType -> Bool Source
Tells whether a ConfigType value is a scalar (i.e. not a
 collection).
>>>isScalarType FloatTypeTrue
>>>isScalarType ListTypeFalse
Note:
>>>isScalarType NoneTypeTrue
data ConfigFormat Source
This is used for fine-grained configuration of how integers are
 output when a config file is written.  See configGetDefaultFormat
 and the libconfig manual.
Constructors
| DefaultFormat | |
| HexFormat | 
Resource management
configInit :: IO Configuration Source
This function allocates a new Configuration and initializes it.
configNew :: String -> IO (Maybe Configuration) Source
Create a new Configuration and read in the data from the
 specified configuration file.
> configNew s = configInit >>= \c -> configReadFile c s
touchConfiguration :: Configuration -> IO () Source
libconfig manages storage for all Setting objects via the
 Configuration, so if a Configuration goes out of scope, GHC may
 get rid of it, and any Setting objects may become invalid.  This
 function can be used to ensure that a Configuration doesn't get
 automatically garbage-collected too early.
Config I/O
configReadFile :: Configuration -> String -> IO (Maybe ()) Source
Read in a Configuration from the specified configuration file.
 The Configuration should already be initialized with
 configInit.
configWriteFile :: Configuration -> String -> IO (Maybe ()) Source
Write out a Configuration to the specified configuration file.
configReadString :: Configuration -> String -> IO (Maybe ()) Source
Read configuration data from a string.
Safe (capable of returning an error) getting of primitive
These Haskell functions return Nothing if the lookup fails,
 there is a type mismatch, etc.
configSettingLookupInt :: Setting -> String -> IO (Maybe Int) Source
>>>configSettingLookupInt winsize "w"Just 640
configSettingLookupInt64 :: Setting -> String -> IO (Maybe Int64) Source
>>>configSettingLookupInt64 misc "bigint"Just 9223372036854775807
configSettingLookupFloat :: Setting -> String -> IO (Maybe Double) Source
>>>configSettingLookupFloat misc "pi"Just 3.141592654
configSettingLookupBool :: Setting -> String -> IO (Maybe Bool) Source
(The example configuration file does not contain any boolean
 values that are direct children of a config_setting_t.)
configSettingLookupString :: Setting -> String -> IO (Maybe String) Source
>>>Just win <- configLookupFrom app "window">>>configSettingLookupString win "title"Just "My Application"
Unsafe getting of primitives
These functions are sketchy if used directly, because there is
 no way to distinguish between a successful result and a failure
 (at the libconfig level).  Take care to only ever use these
 once you've already checked the ConfigType of the Setting
 using configSettingType.
configSettingGetInt :: Setting -> IO Int Source
>>>Just appwinwidth <- configLookup conf "application.window.size.w">>>configSettingGetInt appwinwidth640
configSettingGetInt64 :: Setting -> IO Int64 Source
>>>Just miscbigint <- configLookup conf "application.misc.bigint">>>configSettingGetInt64 miscbigint9223372036854775807
configSettingGetFloat :: Setting -> IO Double Source
>>>Just miscpi <- configLookup conf "application.misc.pi">>>configSettingGetFloat miscpi3.141592654
configSettingGetBool :: Setting -> IO Bool Source
>>>Just listbool <- configLookup conf "application.list.[0].[2]">>>configSettingGetBool listboolTrue
configSettingGetString :: Setting -> IO String Source
>>>Just wintitle <- configLookup conf "application.window.title">>>configSettingGetString wintitle"My Application"
Setting of primitives
These functions return a value of type Maybe (), indicating
 whether the action was successful.  (It may fail if, for
 example, there is a setting type mismatch.)
configSettingSetInt :: Setting -> Int -> IO (Maybe ()) Source
>>>Just treasureqty <- configLookup conf' "application.books.[0].qty">>>configSettingSetInt treasureqty 222Just ()>>>configSettingGetInt treasureqty222
configSettingSetInt64 :: Setting -> Int64 -> IO (Maybe ()) Source
>>>Just miscbigint <- configLookup conf' "application.misc.bigint">>>configSettingSetInt64 miscbigint 92233720368547758Just ()>>>configSettingGetInt64 miscbigint92233720368547758
configSettingSetFloat :: Setting -> Double -> IO (Maybe ()) Source
>>>Just treasureprice <- configLookup conf' "application.books.[0].price">>>configSettingSetFloat treasureprice 22.22Just ()>>>configSettingGetFloat treasureprice22.22
configSettingSetBool :: Setting -> Bool -> IO (Maybe ()) Source
>>>Just listbool <- configLookup conf' "application.list.[0].[2]">>>configSettingSetBool listbool FalseJust ()>>>configSettingGetBool listboolFalse
configSettingSetString :: Setting -> String -> IO (Maybe ()) Source
>>>Just treasureauthor <- configLookup conf' "application.books.[0].author">>>configSettingSetString treasureauthor "Robert L. Stevenson"Just ()>>>configSettingGetString treasureauthor"Robert L. Stevenson"
Unsafe getting of primitives from a collection
These functions are sketchy if used directly, because there is
 no way to distinguish between a successful result and a failure
 (at the libconfig level).  Take care to only ever use these
 once you've already checked the ConfigType of the element
 using configSettingType or verified it for other elements of
 an array.
These functions may be used on collections with type
 GroupType, ArrayType or ListType.
configSettingGetIntElem :: Setting -> Int -> IO Int Source
>>>Just treasure <- configLookup conf "application.books.[0]">>>configSettingGetIntElem treasure 35
configSettingGetInt64Elem :: Setting -> Int -> IO Int64 Source
>>>Just misc <- configLookup conf "application.misc">>>configSettingGetInt64Elem misc 19223372036854775807
configSettingGetFloatElem :: Setting -> Int -> IO Double Source
>>>Just list <- configLookup conf "application.list">>>configSettingGetFloatElem list 11.234
configSettingGetBoolElem :: Setting -> Int -> IO Bool Source
(The example configuration does not contain any boolean values
 that are direct children of collections of type
 config_setting_t).
configSettingGetStringElem :: Setting -> Int -> IO String Source
>>>Just win <- configLookup conf "application.window">>>configSettingGetStringElem win 0"My Application"
Setting of primitives within a collection
In the event of an out-of-bounds index or a type mismatch,
 these functions return Nothing.  If the function succeeds,
 the Setting that is returned will be either the same Setting
 that previously existed at that spot or a newly allocated one.
These functions may be used on collections with type
 ArrayType or ListType (but not GroupType).
configSettingSetIntElem :: Setting -> Int -> Int -> IO (Maybe Setting) Source
(This example appends a new value of type IntType to
 application.list, because the example file contains no suitable
 example values for us to modify.)
>>>Just list <- configLookup conf' "application.list">>>Just new3 <- configSettingSetIntElem list (-1) 22>>>configSettingGetIntElem list 322>>>configSettingGetInt new322
configSettingSetInt64Elem :: Setting -> Int -> Int64 -> IO (Maybe Setting) Source
(This example appends a new value of type Int64Type to
 application.list, because the example file contains no suitable
 example values for us to modify.)
>>>Just list <- configLookup conf' "application.list">>>Just new3 <- configSettingSetInt64Elem list (-1) 92233720368547758>>>configSettingGetInt64Elem list 392233720368547758>>>configSettingGetInt64 new392233720368547758
configSettingSetFloatElem :: Setting -> Int -> Double -> IO (Maybe Setting) Source
>>>Just list <- configLookup conf' "application.list">>>Just new1 <- configSettingSetFloatElem list 1 0.2222>>>configSettingGetFloatElem list 10.2222>>>configSettingGetFloat new10.2222
configSettingSetBoolElem :: Setting -> Int -> Bool -> IO (Maybe Setting) Source
(This example appends a new value of type BoolType to
 application.list, because the example file contains no suitable
 example values for us to modify.)
>>>Just list <- configLookup conf' "application.list">>>Just new3 <- configSettingSetBoolElem list (-1) False>>>configSettingGetBoolElem list 3False>>>configSettingGetBool new3False
configSettingSetStringElem :: Setting -> Int -> String -> IO (Maybe Setting) Source
>>>Just misccols <- configLookup conf' "application.misc.columns">>>Just new0 <- configSettingSetStringElem misccols 0 "butts">>>configSettingGetStringElem misccols 0"butts">>>configSettingGetString new0"butts"
Direct lookup by path
In the event of a name lookup failure or type mismatch, these
 functions return Nothing.
configLookup :: Configuration -> String -> IO (Maybe Setting) Source
>>>Just app <- configLookup conf "application">>>configSettingName appJust "application"
configLookupFrom :: Setting -> String -> IO (Maybe Setting) Source
>>>Just list <- configLookupFrom app "list">>>configSettingName listJust "list"
configLookupInt :: Configuration -> String -> IO (Maybe Int) Source
>>>configLookupInt conf "application.window.size.w"Just 640
configLookupInt64 :: Configuration -> String -> IO (Maybe Int64) Source
>>>configLookupInt64 conf "application.misc.bigint"Just 9223372036854775807
configLookupFloat :: Configuration -> String -> IO (Maybe Double) Source
>>>configLookupFloat conf "application.misc.pi"Just 3.141592654
configLookupBool :: Configuration -> String -> IO (Maybe Bool) Source
>>>configLookupBool conf "application.list.[0].[2]"Just True
configLookupString :: Configuration -> String -> IO (Maybe String) Source
>>>configLookupString conf "application.window.title"Just "My Application"
Collection management
configSettingIndex :: Setting -> IO Int Source
>>>Just col0 <- configLookup conf "application.misc.columns.[0]">>>configSettingIndex col00
configSettingLength :: Setting -> IO Int Source
>>>Just cols <- configLookup conf "application.misc.columns">>>configSettingLength cols3
configSettingGetElem :: Setting -> Int -> IO (Maybe Setting) Source
>>>Just cols <- configLookup conf "application.misc.columns">>>Just col0 <- configSettingGetElem cols 0>>>configSettingGetString col0"Last Name"
configSettingGetMember :: Setting -> String -> IO (Maybe Setting) Source
>>>Just miscpi <- configSettingGetMember misc "pi">>>configSettingGetFloat miscpi3.141592654
configSettingAdd :: Setting -> String -> ConfigType -> IO (Maybe Setting) Source
>>>Just misc' <- configLookup conf' "application.misc">>>Just randSeed <- configSettingAdd misc' "random_seed" IntType>>>configSettingSetInt randSeed 55Just ()>>>configSettingGetInt randSeed55>>>configSettingLookupInt misc' "random_seed"Just 55>>>configSettingGetIntElem misc' 455
configSettingRemove :: Setting -> String -> IO (Maybe ()) Source
>>>Just misc' <- configLookup conf' "application.misc">>>configSettingLength misc'4>>>configSettingRemove misc' "bitmask"Just ()>>>configSettingLength misc'3
configSettingRemoveElem :: Setting -> Int -> IO (Maybe ()) Source
>>>Just misc' <- configLookup conf' "application.misc">>>configSettingLength misc'4>>>configSettingRemoveElem misc' 2Just ()>>>configSettingLength misc'3>>>Just new2 <- configSettingGetElem misc' 2>>>configSettingType new2IntType>>>configSettingGetInt new28131
Miscellaneous
configSettingName :: Setting -> IO (Maybe String) Source
>>>Just list <- configLookup conf "application.list">>>configSettingName listJust "list"
>>>Just list1 <- configLookup conf "application.list.[0]">>>configSettingName list1Nothing
configSettingParent :: Setting -> IO (Maybe Setting) Source
>>>Just list <- configLookup conf "application.list">>>Just app <- configSettingParent list>>>configSettingName appJust "application"
configSettingIsRoot :: Setting -> IO Bool Source
>>>configSettingIsRoot appFalse>>>Just root <- configRootSetting conf>>>configSettingIsRoot rootTrue
configRootSetting :: Configuration -> IO (Maybe Setting) Source
>>>Just root <- configRootSetting conf>>>Just version <- configSettingGetMember root "version">>>configSettingGetString version"1.0"
configSettingSourceLine :: Setting -> IO Int Source
>>>configSettingSourceLine app5
configSettingSourceFile :: Setting -> IO String Source
>>>configSettingSourceFile app"test/test.conf"
Formatting
configGetDefaultFormat :: Configuration -> IO ConfigFormat Source
>>>configGetDefaultFormat confDefaultFormat
configSetDefaultFormat :: Configuration -> ConfigFormat -> IO () Source
>>>configGetDefaultFormat conf'DefaultFormat>>>configSetDefaultFormat conf' HexFormat>>>configGetDefaultFormat conf'HexFormat
configSettingGetFormat :: Setting -> IO ConfigFormat Source
>>>Just appwinwidth <- configLookup conf "application.window.size.w">>>configSettingGetFormat appwinwidthDefaultFormat
configSettingSetFormat :: Setting -> ConfigFormat -> IO (Maybe ()) Source
>>>Just appwinwidth' <- configLookup conf' "application.window.size.w">>>configSettingGetFormat appwinwidth'DefaultFormat>>>configSettingSetFormat appwinwidth' HexFormatJust ()>>>configSettingGetFormat appwinwidth'HexFormat
configGetTabWidth :: Configuration -> IO Int Source
>>>configGetTabWidth conf2
configSetTabWidth :: Configuration -> Int -> IO () Source
>>>configGetTabWidth conf'2>>>configSetTabWidth conf' 8>>>configGetTabWidth conf'8
Error reporting
configErrorFile :: Configuration -> IO (Maybe String) Source
configErrorText :: Configuration -> IO (Maybe String) Source
configErrorLine :: Configuration -> IO Int Source
Config file type system
configSettingType :: Setting -> IO ConfigType Source
>>>Just list <- configLookup conf "application.list">>>configSettingType listListType
configSettingIsGroup :: Setting -> IO Bool Source
>>>Just grp <- configLookup conf "application.window">>>configSettingIsGroup grpTrue
configSettingIsList :: Setting -> IO Bool Source
>>>Just list <- configLookup conf "application.list">>>configSettingIsList listTrue
configSettingIsArray :: Setting -> IO Bool Source
>>>Just arr <- configLookup conf "application.misc.columns">>>configSettingIsArray arrTrue
configSettingIsAggregate :: Setting -> IO Bool Source
>>>Just grp <- configLookup conf "application.window">>>Just arr <- configLookup conf "application.misc.columns">>>Just list <- configLookup conf "application.list">>>Just width <- configLookup conf "application.window.size.w">>>mapM configSettingIsAggregate [grp, arr, list, width][True,True,True,False]
configSettingIsNumber :: Setting -> IO Bool Source
>>>Just int <- configLookup conf "application.window.pos.x">>>Just bigint <- configLookup conf "application.misc.bigint">>>Just float <- configLookup conf "application.misc.pi">>>Just grp <- configLookup conf "application.window">>>mapM configSettingIsNumber [int, bigint, float, grp][True,True,True,False]
configSettingIsScalar :: Setting -> IO Bool Source
>>>Just int <- configLookup conf "application.window.pos.x">>>Just bigint <- configLookup conf "application.misc.bigint">>>Just float <- configLookup conf "application.misc.pi">>>Just bool <- configLookup conf "application.list.[0].[2]">>>Just str <- configLookup conf "application.window.title">>>Just grp <- configLookup conf "application.window">>>mapM configSettingIsScalar [int, bigint, float, bool, str, grp][True,True,True,True,True,False]