summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Conftrack.hs76
-rw-r--r--src/Conftrack/Source.hs46
-rw-r--r--src/Conftrack/Value.hs38
3 files changed, 160 insertions, 0 deletions
diff --git a/src/Conftrack.hs b/src/Conftrack.hs
new file mode 100644
index 0000000..3003115
--- /dev/null
+++ b/src/Conftrack.hs
@@ -0,0 +1,76 @@
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+{-# LANGUAGE OverloadedLists #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE LambdaCase #-}
+
+module Conftrack where
+
+import Conftrack.Value (ConfigError(..), ConfigValue(..), Key, Origin(..))
+import Conftrack.Source (SomeSource (..), ConfigSource (..))
+
+import Prelude hiding (unzip)
+import Control.Monad.State (get, StateT (..), MonadState (..), gets)
+import Data.Functor ((<&>))
+import Control.Monad.Reader (MonadIO (liftIO))
+import Data.List.NonEmpty (NonEmpty, unzip)
+import qualified Data.List.NonEmpty as NonEmpty
+import Control.Monad (forM)
+import Data.Either (isRight)
+import Control.Monad.Trans.Except (ExceptT(..), runExceptT, throwE)
+import Control.Monad.Trans (lift)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Maybe (isJust)
+
+
+class Config a where
+ readConfig :: FetchMonad a
+
+type FetchMonad = StateT (NonEmpty SomeSource, [Origin], [Warning]) (ExceptT [ConfigError] IO)
+
+newtype Warning = Warning Text
+ deriving Show
+
+runFetchConfig :: Config a => NonEmpty SomeSource -> IO (Either [ConfigError] (a, [Origin], [Warning]))
+runFetchConfig sources = do
+ results <- runExceptT $ runStateT readConfig (sources, [], [])
+
+ case results of
+ Left a -> pure $ Left a
+ Right (result, (sources, origins, warnings)) -> do
+ unusedWarnings <- collectUnused sources
+ pure $ Right (result, origins, unusedWarnings <> warnings)
+
+readValue :: ConfigValue a => Key -> FetchMonad a
+readValue key = do
+ (sources, origins, warnings) <- get
+
+ -- TODO: this should short-curcuit here (so we have correct unused key sets)
+ stuff <- liftIO $ forM sources $ \(SomeSource (source, sourceState)) -> do
+ (eitherValue, newState) <- runStateT (fetchValue key source) sourceState
+ pure (eitherValue, SomeSource (source, newState))
+
+ let (maybeValues, states) = Data.List.NonEmpty.unzip stuff
+
+ let values = maybeValues <&> \case
+ Right (val, text) -> fromConfig val <&> (\val -> (val, Origin key text))
+ Left e -> Left e
+
+ val <- case fmap (\(Right a) -> a) $ NonEmpty.filter isRight values of
+ [] -> lift $ throwE [NotPresent]
+ val:_ -> pure val
+
+ put (states, snd val : origins, warnings)
+
+ pure (fst val)
+
+collectUnused :: NonEmpty SomeSource -> IO [Warning]
+collectUnused sources = do
+ forM sources (\(SomeSource (source, sourceState)) ->
+ runStateT (leftovers source) sourceState <&> fst)
+ <&> fmap (\(Just a) -> Warning $ "Unused Keys " <> T.pack (show a))
+ . NonEmpty.filter isJust
diff --git a/src/Conftrack/Source.hs b/src/Conftrack/Source.hs
new file mode 100644
index 0000000..df6f82c
--- /dev/null
+++ b/src/Conftrack/Source.hs
@@ -0,0 +1,46 @@
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE OverloadedStrings #-}
+
+module Conftrack.Source (ConfigSource(..), SomeSource(..), Trivial(..)) where
+
+import Conftrack.Value (Key, Value(..), ConfigError(..), Origin)
+
+import Control.Monad.State (get, modify, StateT (..), MonadState (..))
+import Data.Map.Strict (Map)
+import qualified Data.Map.Strict as M
+import Data.Function ((&))
+import Data.Text (Text)
+import qualified Data.Text as T
+
+
+class ConfigSource s where
+ type ConfigState s
+ fetchValue :: Key -> s -> StateT (ConfigState s) IO (Either ConfigError (Value, Text))
+ leftovers :: s -> StateT (ConfigState s) IO (Maybe [Key])
+
+data SomeSource = forall source. ConfigSource source
+ => SomeSource (source, ConfigState source)
+
+
+newtype Trivial = Trivial (Map Key Value)
+
+instance ConfigSource Trivial where
+ type ConfigState Trivial = [Key]
+ fetchValue key (Trivial tree) = do
+ case M.lookup key tree of
+ Nothing -> pure $ Left NotPresent
+ Just val -> do
+ modify (key :)
+ pure $ Right (val, "Trivial source with keys "<> T.pack (show (M.keys tree)))
+
+ leftovers (Trivial tree) = do
+ used <- get
+
+ M.keys tree
+ & filter (`notElem` used)
+ & Just
+ & pure
diff --git a/src/Conftrack/Value.hs b/src/Conftrack/Value.hs
new file mode 100644
index 0000000..c5768cc
--- /dev/null
+++ b/src/Conftrack/Value.hs
@@ -0,0 +1,38 @@
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE QuantifiedConstraints #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE AllowAmbiguousTypes #-}
+
+module Conftrack.Value (Value(..), ConfigError(..), Key(..), ConfigValue(..), Origin(..)) where
+
+import Data.Text(Text)
+import Data.List.NonEmpty (NonEmpty)
+
+data Value =
+ ConfigText Text
+ | ConfigInteger Integer
+ | ConfigOther Text Text
+ deriving Show
+
+newtype Key = Key (NonEmpty Text)
+ deriving newtype (Eq, Ord, Show)
+
+data ConfigError =
+ ParseError
+ | NotPresent
+ deriving Show
+
+class ConfigValue a where
+ fromConfig :: Value -> Either ConfigError a
+
+data Origin = Origin Key Text
+ deriving Show
+
+instance ConfigValue Text where
+ fromConfig (ConfigText a) = Right a
+ fromConfig _ = Left ParseError
+
+instance ConfigValue Integer where
+ fromConfig (ConfigInteger a) = Right a
+ fromConfig _ = Left ParseError