{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExplicitNamespaces #-}
module Data.ConfigFile.B9Extras
( addSectionCP,
setShowCP,
setCP,
readCP,
mergeCP,
toStringCP,
sectionsCP,
emptyCP,
type CPGet,
type CPOptionSpec,
type CPSectionSpec,
type CPDocument,
CPError (),
readCPDocument,
CPReadException (..),
)
where
import Control.Exception
import Control.Monad.Except
import Data.ConfigFile
import Data.Typeable
import System.IO.B9Extras
type CPDocument = ConfigParser
type CPSectionSpec = SectionSpec
type CPOptionSpec = OptionSpec
setShowCP ::
(Show a, MonadError CPError m) =>
CPDocument ->
CPSectionSpec ->
CPOptionSpec ->
a ->
m CPDocument
setShowCP :: CPDocument -> CPSectionSpec -> CPSectionSpec -> a -> m CPDocument
setShowCP = CPDocument -> CPSectionSpec -> CPSectionSpec -> a -> m CPDocument
forall a (m :: * -> *).
(Show a, MonadError CPError m) =>
CPDocument -> CPSectionSpec -> CPSectionSpec -> a -> m CPDocument
setshow
setCP ::
(MonadError CPError m) =>
CPDocument ->
CPSectionSpec ->
CPOptionSpec ->
String ->
m CPDocument
setCP :: CPDocument
-> CPSectionSpec -> CPSectionSpec -> CPSectionSpec -> m CPDocument
setCP = CPDocument
-> CPSectionSpec -> CPSectionSpec -> CPSectionSpec -> m CPDocument
forall (m :: * -> *).
MonadError CPError m =>
CPDocument
-> CPSectionSpec -> CPSectionSpec -> CPSectionSpec -> m CPDocument
set
readCP ::
(CPGet a, MonadError CPError m) =>
CPDocument ->
CPSectionSpec ->
CPOptionSpec ->
m a
readCP :: CPDocument -> CPSectionSpec -> CPSectionSpec -> m a
readCP = CPDocument -> CPSectionSpec -> CPSectionSpec -> m a
forall a (m :: * -> *).
(Get_C a, MonadError CPError m) =>
CPDocument -> CPSectionSpec -> CPSectionSpec -> m a
get
type CPGet a = Get_C a
addSectionCP ::
MonadError CPError m => CPDocument -> CPSectionSpec -> m CPDocument
addSectionCP :: CPDocument -> CPSectionSpec -> m CPDocument
addSectionCP = CPDocument -> CPSectionSpec -> m CPDocument
forall (m :: * -> *).
MonadError CPError m =>
CPDocument -> CPSectionSpec -> m CPDocument
add_section
mergeCP :: CPDocument -> CPDocument -> CPDocument
mergeCP :: CPDocument -> CPDocument -> CPDocument
mergeCP = CPDocument -> CPDocument -> CPDocument
merge
toStringCP :: CPDocument -> String
toStringCP :: CPDocument -> CPSectionSpec
toStringCP = CPDocument -> CPSectionSpec
to_string
sectionsCP :: CPDocument -> [SectionSpec]
sectionsCP :: CPDocument -> [CPSectionSpec]
sectionsCP = CPDocument -> [CPSectionSpec]
sections
readCPDocument :: MonadIO m => SystemPath -> m CPDocument
readCPDocument :: SystemPath -> m CPDocument
readCPDocument SystemPath
cfgFile' = do
CPSectionSpec
cfgFilePath <- SystemPath -> m CPSectionSpec
forall (m :: * -> *). MonadIO m => SystemPath -> m CPSectionSpec
resolve SystemPath
cfgFile'
IO CPDocument -> m CPDocument
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CPDocument -> m CPDocument) -> IO CPDocument -> m CPDocument
forall a b. (a -> b) -> a -> b
$ do
Either CPError CPDocument
res <- CPDocument -> CPSectionSpec -> IO (Either CPError CPDocument)
forall (m :: * -> *).
MonadError CPError m =>
CPDocument -> CPSectionSpec -> IO (m CPDocument)
readfile CPDocument
emptyCP CPSectionSpec
cfgFilePath
case Either CPError CPDocument
res of
Left CPError
e -> CPReadException -> IO CPDocument
forall e a. Exception e => e -> IO a
throwIO (CPSectionSpec -> CPError -> CPReadException
CPReadException CPSectionSpec
cfgFilePath CPError
e)
Right CPDocument
cp -> CPDocument -> IO CPDocument
forall (m :: * -> *) a. Monad m => a -> m a
return CPDocument
cp
data CPReadException = CPReadException FilePath CPError
deriving (Int -> CPReadException -> ShowS
[CPReadException] -> ShowS
CPReadException -> CPSectionSpec
(Int -> CPReadException -> ShowS)
-> (CPReadException -> CPSectionSpec)
-> ([CPReadException] -> ShowS)
-> Show CPReadException
forall a.
(Int -> a -> ShowS)
-> (a -> CPSectionSpec) -> ([a] -> ShowS) -> Show a
showList :: [CPReadException] -> ShowS
$cshowList :: [CPReadException] -> ShowS
show :: CPReadException -> CPSectionSpec
$cshow :: CPReadException -> CPSectionSpec
showsPrec :: Int -> CPReadException -> ShowS
$cshowsPrec :: Int -> CPReadException -> ShowS
Show, Typeable)
instance Exception CPReadException