module Config.Schema.Load
( loadValue
, LoadError(..)
, Problem(..)
) where
import Control.Applicative (Alternative, optional)
import Control.Monad (MonadPlus, unless, zipWithM)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State (StateT(..), runStateT)
import Control.Monad.Trans.Except
import Control.Monad.Trans.Reader
import Data.Foldable (asum)
import Data.Monoid ((<>))
import Data.Ratio (numerator, denominator)
import Data.Text (Text)
import qualified Data.Text as Text
import Config
import Config.Schema.Spec
loadValue ::
ValueSpecs a ->
Value ->
Either [LoadError] a
loadValue spec val = runLoad (getValue spec val)
getSection :: SectionSpec a -> StateT [Section] Load a
getSection (ReqSection k _ w) =
do v <- StateT (lookupSection k)
lift (scope k (getValue w v))
getSection (OptSection k _ w) =
do mb <- optional (StateT (lookupSection k))
lift (traverse (scope k . getValue w) mb)
getSections :: SectionSpecs a -> [Section] -> Load a
getSections p xs =
do (a,leftover) <- runStateT (runSections getSection p) xs
unless (null leftover) (loadFail (UnusedSections (map sectionName leftover)))
return a
getValue :: ValueSpecs a -> Value -> Load a
getValue s v = asum (runValueSpecs (getValue1 v) s)
getValue1 :: Value -> ValueSpec a -> Load a
getValue1 (Text t) TextSpec = pure t
getValue1 (Number _ n) IntegerSpec = pure n
getValue1 (Floating a b) IntegerSpec | Just i <- floatingToInteger a b = pure i
getValue1 (Number _ n) RationalSpec = pure (fromInteger n)
getValue1 (Floating a b) RationalSpec = pure (floatingToRational a b)
getValue1 (List xs) (ListSpec w) = getList w xs
getValue1 (Atom b) AnyAtomSpec = pure (atomName b)
getValue1 (Atom b) (AtomSpec a) | a == atomName b = pure ()
getValue1 (Sections s) (SectionSpecs _ w) = getSections w s
getValue1 v (NamedSpec _ w) = getValue w v
getValue1 v (CustomSpec l w) = getCustom l w v
getValue1 _ TextSpec = loadFail (SpecMismatch "text")
getValue1 _ IntegerSpec = loadFail (SpecMismatch "integer")
getValue1 _ RationalSpec = loadFail (SpecMismatch "rational")
getValue1 _ ListSpec{} = loadFail (SpecMismatch "list")
getValue1 _ AnyAtomSpec = loadFail (SpecMismatch "atom")
getValue1 _ (AtomSpec a) = loadFail (SpecMismatch ("`" <> a <> "`"))
getValue1 _ (SectionSpecs l _) = loadFail (SpecMismatch l)
getList :: ValueSpecs a -> [Value] -> Load [a]
getList w = zipWithM (\i x -> scope (Text.pack (show i)) (getValue w x)) [1::Int ..]
getCustom ::
Text ->
ValueSpecs (Maybe a) ->
Value ->
Load a
getCustom l w v =
do x <- getValue w v
case x of
Nothing -> loadFail (SpecMismatch l)
Just y -> pure y
lookupSection ::
Text ->
[Section] ->
Load (Value, [Section])
lookupSection key [] = loadFail (MissingSection key)
lookupSection key (s@(Section k v):xs)
| key == k = pure (v, xs)
| otherwise = do (v',xs') <- lookupSection key xs
return (v',s:xs')
floatingToRational :: Integer -> Integer -> Rational
floatingToRational x y = fromInteger x * 10^^y
floatingToInteger :: Integer -> Integer -> Maybe Integer
floatingToInteger x y
| denominator r == 1 = Just (numerator r)
| otherwise = Nothing
where r = floatingToRational x y
newtype Load a = MkLoad { unLoad :: ReaderT [Text] (Except [LoadError]) a }
deriving (Functor, Applicative, Monad, Alternative, MonadPlus)
data LoadError = LoadError [Text] Problem
deriving (Eq, Ord, Read, Show)
runLoad :: Load a -> Either [LoadError] a
runLoad = runExcept . flip runReaderT [] . unLoad
data Problem
= MissingSection Text
| UnusedSections [Text]
| SpecMismatch Text
deriving (Eq, Ord, Read, Show)
scope :: Text -> Load a -> Load a
scope key (MkLoad m) = MkLoad (local (key:) m)
loadFail :: Problem -> Load a
loadFail cause = MkLoad $
do path <- ask
lift (throwE [LoadError (reverse path) cause])