{-# LANGUAGE OverloadedStrings #-}

-- |
-- Module:      Data.ConfigManager
-- License:     GPL-3
-- Maintainer:  Joris Guyonvarch <joris@guyonvarch.me>
-- Stability:   experimental
--
-- A configuration management library.

module Data.ConfigManager
  (
  -- * Configuration file format
  -- $format

  -- ** Binding a name to a value
  -- $bindings

  -- ** Import other files
  -- $import

  -- ** Comments
  -- $comments

  -- ** Example
  -- $example

  -- * Configuration loading
  readConfig

  -- * Lookup functions
  , lookup
  , lookupDefault
  ) where

import Prelude hiding (lookup)

import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.HashMap.Strict as M

import qualified Data.ConfigManager.Reader as R
import Data.ConfigManager.Types
import Data.ConfigManager.Instances ()

-- | Load a 'Config' from a given 'FilePath'.

readConfig :: FilePath -> IO (Either Text Config)
readConfig = R.readConfig Required

-- | Lookup for the value associated to a name.

lookup :: Configured a => Name -> Config -> Either Text a
lookup name config =
  case M.lookup name (hashMap config) of
    Nothing ->
      Left . T.concat $ ["Value not found for Key ", name]
    Just value ->
      case convert value of
        Nothing -> Left . T.concat $ ["Reading error for key ", name]
        Just result -> Right result

-- | Lookup for the value associated to a name and return the default value if
-- no binding exists with the given name.

lookupDefault :: Configured a => a -> Name -> Config -> a
lookupDefault defaultValue name config = foldl (flip const) defaultValue $ lookup name config

-- $format
--
-- A configuration file consists of a series of:
--
-- * bindings,
-- * imports,
-- * and comments.

-- $bindings
--
-- A binding associates a name to a value:
--
-- > number = 1
-- > my-string = "Hello"
-- > a_double = 4.0
-- > thatIsABoolean = True
-- > a_double = 5.0
-- > diffTime = 1 day
-- > otherDiffTime = 3 hours
--
-- * If two or more bindings have the same name, only the last one is kept.
-- * Accepted duration values are seconds, minutes, hours, days and weeks.

-- $import
--
-- An import is either required or optional:
--
-- > import "database.conf"
-- > importMaybe "local.conf"

-- $comments
--
-- A comment begins with '#' and continues to the end of the line:
--
-- > # Comment
-- > x = 8 # Another comment

-- $example
--
-- From application.conf:
--
-- > port = 3000
-- > mailFrom = "no-reply@mail.com"
-- > currency = "$"
-- > expiration = 30 minutes
--
-- Read the configuration:
--
-- > import qualified Data.ConfigManager as Conf
-- > import Data.Time.Clock (DiffTime)
-- >
-- > data Conf = Conf
-- >   { port :: Int
-- >   , mailFrom :: String
-- >   , currency :: String
-- >   , expiration :: DiffTime
-- >   } deriving (Eq, Show)
-- >
-- > getConfig :: IO (Either Text Conf)
-- > getConfig =
-- >   (flip fmap) (Conf.readConfig "application.conf") (\configOrError -> do
-- >     conf <- configOrError
-- >     Conf <$>
-- >       Conf.lookup "port" conf <*>
-- >       Conf.lookup "mailFrom" conf <*>
-- >       Conf.lookup "currency" conf <*>
-- >       Conf.lookup "expiration" conf
-- >   )