{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
module Data.Configurator.Parser
( Parser
, runParser
, bool
, int
, string
, value
, list
, optional
, required
, subassocs
) where
import Protolude hiding (bool, list, optional)
import Data.Functor.Compose
import qualified Data.Map.Strict as M
import qualified Data.Scientific as Scientific
import Data.Text (Text)
import qualified Data.Text as T
import Data.Configurator.Types
newtype Parser a b = Parser { getParser :: Compose ((->) a) (Either Text) b }
deriving (Functor, Applicative)
makeParser :: (a -> Either Text b) -> Parser a b
makeParser = Parser . Compose
runParser :: Parser a b -> a -> Either Text b
runParser = getCompose . getParser
instance Monad (Parser a) where
p >>= f = makeParser $ \v -> runParser p v >>= \w -> runParser (f w) v
required :: Key -> Parser Value a -> Parser Config a
required key pv = makeParser $ \cfg ->
case M.lookup key cfg of
Nothing -> Left $ "missing key: " <> key
Just v -> runParser pv v
optional :: Key -> Parser Value a -> Parser Config (Maybe a)
optional key pv = makeParser $ \cfg ->
case M.lookup key cfg of
Nothing -> Right Nothing
Just v -> Just <$> runParser pv v
subassocs :: Key -> Parser Value a -> Parser Config [(Key, a)]
subassocs prefix pv = makeParser $ \cfg ->
M.toList <$> mapM (runParser pv) (M.filterWithKey match cfg)
where
match k _ = if T.null prefix
then not (T.isInfixOf "." k)
else case T.stripPrefix (prefix <> ".") k of
Nothing -> False
Just suff -> not (T.isInfixOf "." suff)
list :: Parser Value a -> Parser Value [a]
list p = makeParser $ \case
List vs -> mapM (runParser p) vs
_ -> Left "expected a list"
value :: Parser Value Value
value = makeParser pure
string :: Parser Value Text
string = makeParser $ \case
String s -> Right s
_ -> Left "expected a string"
int :: Parser Value Int
int = makeParser $ \case
Number n -> if Scientific.isInteger n
then case Scientific.toBoundedInteger n of
Just x -> Right x
Nothing -> Left "int out of bounds"
else Left "expected an integer"
_ -> Left "expected an integer"
bool :: Parser Value Bool
bool = makeParser $ \case
Bool b -> Right b
_ -> Left "expected a boolean"