module Data.Configurator
(
Worth(..)
, autoReload
, autoReloadGroups
, autoConfig
, empty
, lookup
, lookupDefault
, require
, prefix
, exact
, subscribe
, load
, loadGroups
, reload
, subconfig
, addToConfig
, addGroupsToConfig
, display
, getMap
) where
import Control.Applicative ((<$>))
import Control.Concurrent (ThreadId, forkIO, threadDelay)
import Control.Exception (SomeException, evaluate, handle, throwIO, try)
import Control.Monad (foldM, forM, forM_, join, when)
import Data.Configurator.Instances ()
import Data.Configurator.Parser (interp, topLevel)
import Data.Configurator.Types.Internal
import Data.IORef (atomicModifyIORef, newIORef, readIORef)
import Data.Maybe (fromMaybe, isJust)
import Data.Monoid (mconcat)
import Data.Ratio (denominator, numerator)
import Data.Text.Lazy.Builder (fromString, fromText, toLazyText)
import Data.Text.Lazy.Builder.Int (decimal)
import Data.Text.Lazy.Builder.RealFloat (realFloat)
import Prelude hiding (lookup)
import System.Environment (getEnv)
import System.IO (hPutStrLn, stderr)
import System.IO.Unsafe (unsafePerformIO)
import System.Posix.Types (EpochTime, FileOffset)
import System.PosixCompat.Files (fileSize, getFileStatus, modificationTime)
import qualified Control.Exception as E
import qualified Data.Attoparsec.Text as T
import qualified Data.Attoparsec.Text.Lazy as L
import qualified Data.HashMap.Lazy as H
import qualified Data.Text as T
import qualified Data.Text.Lazy as L
import qualified Data.Text.Lazy.IO as L
loadFiles :: [Worth Path] -> IO (H.HashMap (Worth Path) [Directive])
loadFiles = foldM go H.empty
where
go seen path = do
let rewrap n = const n <$> path
wpath = worth path
path' <- rewrap <$> interpolate wpath H.empty
ds <- loadOne (T.unpack <$> path')
let !seen' = H.insert path ds seen
notSeen n = not . isJust . H.lookup n $ seen
foldM go seen' . filter notSeen . importsOf wpath $ ds
load :: [Worth FilePath] -> IO Config
load files = fmap (Config "") $ load' Nothing (map (\f -> ("", f)) files)
loadGroups :: [(Name, Worth FilePath)] -> IO Config
loadGroups files = fmap (Config "") $ load' Nothing files
load' :: Maybe AutoConfig -> [(Name, Worth FilePath)] -> IO BaseConfig
load' auto paths0 = do
let second f (x,y) = (x, f y)
paths = map (second (fmap T.pack)) paths0
ds <- loadFiles (map snd paths)
p <- newIORef paths
m <- newIORef =<< flatten paths ds
s <- newIORef H.empty
return BaseConfig {
cfgAuto = auto
, cfgPaths = p
, cfgMap = m
, cfgSubs = s
}
subconfig :: Name -> Config -> Config
subconfig g (Config root cfg) = Config (T.concat [root, g, "."]) cfg
reload :: Config -> IO ()
reload (Config _ cfg@BaseConfig{..}) = reloadBase cfg
reloadBase :: BaseConfig -> IO ()
reloadBase cfg@BaseConfig{..} = do
paths <- readIORef cfgPaths
m' <- flatten paths =<< loadFiles (map snd paths)
m <- atomicModifyIORef cfgMap $ \m -> (m', m)
notifySubscribers cfg m m' =<< readIORef cfgSubs
addToConfig :: [Worth FilePath] -> Config -> IO ()
addToConfig paths0 cfg = addGroupsToConfig (map (\x -> ("",x)) paths0) cfg
addGroupsToConfig :: [(Name, Worth FilePath)] -> Config -> IO ()
addGroupsToConfig paths0 (Config root cfg@BaseConfig{..}) = do
let fix (x,y) = (root `T.append` x, fmap T.pack y)
paths = map fix paths0
atomicModifyIORef cfgPaths $ \prev -> (prev ++ paths, ())
reloadBase cfg
autoConfig :: AutoConfig
autoConfig = AutoConfig {
interval = 1
, onError = const $ return ()
}
autoReload :: AutoConfig
-> [Worth FilePath]
-> IO (Config, ThreadId)
autoReload auto paths = autoReloadGroups auto (map (\x -> ("", x)) paths)
autoReloadGroups :: AutoConfig
-> [(Name, Worth FilePath)]
-> IO (Config, ThreadId)
autoReloadGroups AutoConfig{..} _
| interval < 1 = error "autoReload: negative interval"
autoReloadGroups _ [] = error "autoReload: no paths to load"
autoReloadGroups auto@AutoConfig{..} paths = do
cfg <- load' (Just auto) paths
let files = map snd paths
loop meta = do
threadDelay (max interval 1 * 1000000)
meta' <- getMeta files
if meta' == meta
then loop meta
else (reloadBase cfg `E.catch` onError) >> loop meta'
tid <- forkIO $ loop =<< getMeta files
return (Config "" cfg, tid)
type Meta = (FileOffset, EpochTime)
getMeta :: [Worth FilePath] -> IO [Maybe Meta]
getMeta paths = forM paths $ \path ->
handle (\(_::SomeException) -> return Nothing) . fmap Just $ do
st <- getFileStatus (worth path)
return (fileSize st, modificationTime st)
lookup :: Configured a => Config -> Name -> IO (Maybe a)
lookup (Config root BaseConfig{..}) name =
(join . fmap convert . H.lookup (root `T.append` name)) <$> readIORef cfgMap
require :: Configured a => Config -> Name -> IO a
require cfg name = do
val <- lookup cfg name
case val of
Just v -> return v
_ -> throwIO . KeyError $ name
lookupDefault :: Configured a =>
a
-> Config -> Name -> IO a
lookupDefault def cfg name = fromMaybe def <$> lookup cfg name
display :: Config -> IO ()
display (Config root BaseConfig{..}) = print . (root,) =<< readIORef cfgMap
getMap :: Config -> IO (H.HashMap Name Value)
getMap = readIORef . cfgMap . baseCfg
flatten :: [(Name, Worth Path)]
-> H.HashMap (Worth Path) [Directive]
-> IO (H.HashMap Name Value)
flatten roots files = foldM doPath H.empty roots
where
doPath m (pfx, f) = case H.lookup f files of
Nothing -> return m
Just ds -> foldM (directive pfx (worth f)) m ds
directive pfx _ m (Bind name (String value)) = do
v <- interpolate value m
return $! H.insert (T.append pfx name) (String v) m
directive pfx _ m (Bind name value) =
return $! H.insert (T.append pfx name) value m
directive pfx f m (Group name xs) = foldM (directive pfx' f) m xs
where pfx' = T.concat [pfx, name, "."]
directive pfx f m (Import path) =
let f' = relativize f path
in case H.lookup (Required (relativize f path)) files of
Just ds -> foldM (directive pfx f') m ds
_ -> return m
interpolate :: T.Text -> H.HashMap Name Value -> IO T.Text
interpolate s env
| "$" `T.isInfixOf` s =
case T.parseOnly interp s of
Left err -> throwIO $ ParseError "" err
Right xs -> (L.toStrict . toLazyText . mconcat) <$> mapM interpret xs
| otherwise = return s
where
interpret (Literal x) = return (fromText x)
interpret (Interpolate name) =
case H.lookup name env of
Just (String x) -> return (fromText x)
Just (Number r)
| denominator r == 1 -> return (decimal $ numerator r)
| otherwise -> return $ realFloat (fromRational r :: Double)
Just _ -> error "type error"
_ -> do
e <- try . getEnv . T.unpack $ name
case e of
Left (_::SomeException) ->
throwIO . ParseError "" $ "no such variable " ++ show name
Right x -> return (fromString x)
importsOf :: Path -> [Directive] -> [Worth Path]
importsOf path (Import ref : xs) = Required (relativize path ref)
: importsOf path xs
importsOf path (Group _ ys : xs) = importsOf path ys ++ importsOf path xs
importsOf path (_ : xs) = importsOf path xs
importsOf _ _ = []
relativize :: Path -> Path -> Path
relativize parent child
| T.head child == '/' = child
| otherwise = fst (T.breakOnEnd "/" parent) `T.append` child
loadOne :: Worth FilePath -> IO [Directive]
loadOne path = do
es <- try . L.readFile . worth $ path
case es of
Left (err::SomeException) -> case path of
Required _ -> throwIO err
_ -> return []
Right s -> do
p <- evaluate (L.eitherResult $ L.parse topLevel s)
`E.catch` \(e::ConfigError) ->
throwIO $ case e of
ParseError _ err -> ParseError (worth path) err
case p of
Left err -> throwIO (ParseError (worth path) err)
Right ds -> return ds
subscribe :: Config -> Pattern -> ChangeHandler -> IO ()
subscribe (Config root BaseConfig{..}) pat act = do
m' <- atomicModifyIORef cfgSubs $ \m ->
let m' = H.insertWith (++) (localPattern root pat) [act] m in (m', m')
evaluate m' >> return ()
localPattern :: Name -> Pattern -> Pattern
localPattern pfx (Exact s) = Exact (pfx `T.append` s)
localPattern pfx (Prefix s) = Prefix (pfx `T.append` s)
notifySubscribers :: BaseConfig -> H.HashMap Name Value -> H.HashMap Name Value
-> H.HashMap Pattern [ChangeHandler] -> IO ()
notifySubscribers BaseConfig{..} m m' subs = H.foldrWithKey go (return ()) subs
where
changedOrGone = H.foldrWithKey check [] m
where check n v nvs = case H.lookup n m' of
Just v' | v /= v' -> (n,Just v'):nvs
| otherwise -> nvs
_ -> (n,Nothing):nvs
new = H.foldrWithKey check [] m'
where check n v nvs = case H.lookup n m of
Nothing -> (n,v):nvs
_ -> nvs
notify p n v a = a n v `E.catch` maybe report onError cfgAuto
where report e = hPutStrLn stderr $
"*** a ChangeHandler threw an exception for " ++
show (p,n) ++ ": " ++ show e
go p@(Exact n) acts next = (const next =<<) $ do
let v' = H.lookup n m'
when (H.lookup n m /= v') . mapM_ (notify p n v') $ acts
go p@(Prefix n) acts next = (const next =<<) $ do
let matching = filter (T.isPrefixOf n . fst)
forM_ (matching new) $ \(n',v) -> mapM_ (notify p n' (Just v)) acts
forM_ (matching changedOrGone) $ \(n',v) -> mapM_ (notify p n' v) acts
empty :: Config
empty = Config "" $ unsafePerformIO $ do
p <- newIORef []
m <- newIORef H.empty
s <- newIORef H.empty
return BaseConfig {
cfgAuto = Nothing
, cfgPaths = p
, cfgMap = m
, cfgSubs = s
}