summaryrefslogtreecommitdiff
path: root/src/Conftrack
diff options
context:
space:
mode:
Diffstat (limited to 'src/Conftrack')
-rw-r--r--src/Conftrack/Source.hs16
-rw-r--r--src/Conftrack/Source/Aeson.hs7
-rw-r--r--src/Conftrack/Source/Trivial.hs1
-rw-r--r--src/Conftrack/Source/Yaml.hs1
-rw-r--r--src/Conftrack/Value.hs18
5 files changed, 41 insertions, 2 deletions
diff --git a/src/Conftrack/Source.hs b/src/Conftrack/Source.hs
index ecfa20d..ab13172 100644
--- a/src/Conftrack/Source.hs
+++ b/src/Conftrack/Source.hs
@@ -12,11 +12,27 @@ import Control.Monad.State (StateT (..))
import Data.Text (Text)
+-- | An abstraction over "config sources". This might mean file formats,
+-- environment variables, or any other kind of format that can be seen as a
+-- key-value store.
class ConfigSource s where
+ -- | Some sources require state, e.g. to keep track of which values were
+ -- already read.
type SourceState s
+
+ -- | read a single value from the source.
fetchValue :: Key -> s -> StateT (SourceState s) IO (Either ConfigError (Value, Text))
+
+ -- | given @s@, determine if any keys are "left over" and were not used.
+ -- This is used to produce warnings for unknown configuration options;
+ -- since not all sources can support this, this function's return type
+ -- includes @Maybe@ and sources are free to return @Nothing@ if they
+ -- cannot determine if any unknown keys are present.
leftovers :: s -> StateT (SourceState s) IO (Maybe [Key])
+-- | An opaque type for any kind of config sources. Values of this type can be
+-- acquired from they @Conftrack.Source.*@ modules, or by implementing the
+-- 'ConfigSource' type class.
data SomeSource = forall source. ConfigSource source
=> SomeSource (source, SourceState source)
diff --git a/src/Conftrack/Source/Aeson.hs b/src/Conftrack/Source/Aeson.hs
index 97353d0..17ea4ee 100644
--- a/src/Conftrack/Source/Aeson.hs
+++ b/src/Conftrack/Source/Aeson.hs
@@ -7,7 +7,8 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
-module Conftrack.Source.Aeson (JsonSource(..), mkJsonSource, mkJsonSourceWith, mkJsonFileSource) where
+-- | Functions for producing sources reading from json strings or files, using the aeson library.
+module Conftrack.Source.Aeson (mkJsonSource, mkJsonSourceWith, mkJsonFileSource, JsonSource(..)) where
import Conftrack.Value (Key (..), ConfigError(..), Value (..), KeyPart)
import Conftrack.Source (SomeSource(..), ConfigSource (..))
@@ -37,13 +38,17 @@ data JsonSource = JsonSource
, jsonSourceDescription :: Text
} deriving (Show)
+-- | Make a source from an aeson value
mkJsonSource :: A.Value -> SomeSource
mkJsonSource value = mkJsonSourceWith ("JSON string " <> LT.toStrict (A.encodeToLazyText value)) value
+-- | same as 'mkJsonSource', but with an additional description to be shown
+-- in output of 'Conftrack.Pretty.printConfigOrigins'.
mkJsonSourceWith :: Text -> A.Value -> SomeSource
mkJsonSourceWith description value = SomeSource (source, [])
where source = JsonSource value description
+-- | Make a source from a json file.
mkJsonFileSource :: OsPath -> IO (Maybe SomeSource)
mkJsonFileSource path = do
bytes <- readFile path
diff --git a/src/Conftrack/Source/Trivial.hs b/src/Conftrack/Source/Trivial.hs
index d4151c2..842ca46 100644
--- a/src/Conftrack/Source/Trivial.hs
+++ b/src/Conftrack/Source/Trivial.hs
@@ -5,6 +5,7 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE OverloadedStrings #-}
+-- | A trivial source reading from a @Map Key Value@, only useful as a demonstration or for tests.
module Conftrack.Source.Trivial where
import Conftrack.Value (Key, Value(..), ConfigError(..))
diff --git a/src/Conftrack/Source/Yaml.hs b/src/Conftrack/Source/Yaml.hs
index 6adc798..4642922 100644
--- a/src/Conftrack/Source/Yaml.hs
+++ b/src/Conftrack/Source/Yaml.hs
@@ -6,6 +6,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE UndecidableInstances #-}
+-- | Functions for producing sources reading from yaml strings or files, using the aeson library.
module Conftrack.Source.Yaml (YamlSource(..), mkYamlSource, mkYamlSourceWith, mkYamlFileSource) where
import Conftrack.Source (SomeSource(..), ConfigSource (..))
diff --git a/src/Conftrack/Value.hs b/src/Conftrack/Value.hs
index 3eda24a..1d6e6a7 100644
--- a/src/Conftrack/Value.hs
+++ b/src/Conftrack/Value.hs
@@ -8,7 +8,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DefaultSignatures #-}
-module Conftrack.Value (key, Value(..), ConfigError(..), Key(..), ConfigValue(..), Origin(..), KeyPart, prefixedWith) where
+module Conftrack.Value (key, Value(..), ConfigError(..), Key(..), ConfigValue(..), Origin(..), KeyPart, prefixedWith, withString) where
import Data.Text(Text)
import qualified Data.Text as T
@@ -21,9 +21,13 @@ import qualified Data.Text.Encoding as BS
import Language.Haskell.TH.Quote (QuasiQuoter(..))
import Language.Haskell.TH.Syntax (Lift(lift))
+-- | A generic value read from a config source, to be parsed into a more useful type
+-- (see the 'ConfigValue' class).
data Value =
ConfigString BS.ByteString
| ConfigInteger Integer
+ -- | A value which may be an integer, but the source cannot say for sure, e.g. because
+ -- its values are entirely untyped. Use 'withString' to handle such cases.
| ConfigMaybeInteger BS.ByteString Integer
| ConfigOther Text Text
| ConfigBool Bool
@@ -32,6 +36,14 @@ data Value =
type KeyPart = Text
+-- | A configuration key is a non-empty list of parts. By convention, these parts
+-- are separated by dots when written, although dots withing parts are not disallowed.
+--
+-- For writing values easily, consider enabling the @QuasiQuotes@ language extension
+-- to use 'key':
+--
+-- >>> [key|foo.bar|]
+-- foo.bar
newtype Key = Key (NonEmpty KeyPart)
deriving newtype (Eq, Ord)
deriving (Lift)
@@ -39,6 +51,7 @@ newtype Key = Key (NonEmpty KeyPart)
instance Show Key where
show (Key parts) = T.unpack (T.intercalate "." (NonEmpty.toList parts))
+-- | to write values of 'Key' easily
key :: QuasiQuoter
key = QuasiQuoter
{ quoteExp = lift . Key . NonEmpty.fromList . T.splitOn "." . T.pack
@@ -57,8 +70,11 @@ data ConfigError =
| Shadowed
deriving Show
+-- | Values which can be read from a config source must implement this class
class ConfigValue a where
fromConfig :: Value -> Either ConfigError a
+ -- | optionally, a function to pretty-print values of this type, used by the
+ -- functions of "Conftrack.Pretty". If not given, defaults to @a@'s 'Show' instance.
prettyValue :: a -> Text
default prettyValue :: Show a => a -> Text