module Data.Ini where
import qualified Data.Map as M
import Data.Maybe
import Data.Ini.Types
emptyConfig :: Config
emptyConfig = M.empty
hasSection :: SectionName -> Config -> Bool
hasSection = M.member
getSection :: SectionName -> Config -> Maybe Section
getSection = M.lookup
sections :: Config -> [SectionName]
sections = M.keys
delSection :: SectionName -> Config -> Config
delSection = M.delete
hasOption :: SectionName -> OptionName -> Config -> Bool
hasOption sn on cfg = isJust $ getSection sn cfg >>= M.lookup on
getOption :: SectionName -> OptionName -> Config -> Maybe OptionValue
getOption sn on cfg = getSection sn cfg >>= M.lookup on
options :: SectionName -> Config -> [OptionName]
options sn cfg = maybe [] M.keys (getSection sn cfg)
setOption :: SectionName -> OptionName -> OptionValue -> Config -> Config
setOption sn on ov cfg = maybe (M.insert sn new_s cfg) (\ sec -> M.insert sn (M.insert on ov sec) cfg) s
where
s = getSection sn cfg
new_s = M.insert on ov M.empty
delOption :: SectionName -> OptionName -> Config -> Config
delOption sn on cfg = if sEmptyAfterDelete
then M.delete sn cfg
else maybe cfg (\ sec -> M.insert sn (M.delete on sec) cfg) s
where
s = getSection sn cfg
sEmptyAfterDelete = maybe True (\ sec -> M.empty == M.delete on sec) s
allItems :: SectionName -> Config -> [(OptionName, OptionValue)]
allItems sn cfg = maybe [] M.toList (getSection sn cfg)