summaryrefslogtreecommitdiff
path: root/src/Conftrack.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Conftrack.hs')
-rw-r--r--src/Conftrack.hs172
1 files changed, 164 insertions, 8 deletions
diff --git a/src/Conftrack.hs b/src/Conftrack.hs
index e1652b1..4e1f17a 100644
--- a/src/Conftrack.hs
+++ b/src/Conftrack.hs
@@ -9,19 +9,39 @@
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
+{-|
+Module: Conftrack
+Stability: experimental
+
+A typeclass-based library for reading in configuration values from multiple sources,
+attempting to be simple, avoid unecessarily complex types, and be able to track where
+each value came from.
+
+-}
module Conftrack
- ( Config(..)
- , Warning(..)
- , runFetchConfig
+ ( -- * How to use this library
+ -- $use
+
+ -- * Defining a configuration format
+ Config(..)
, readValue
, readOptionalValue
, readRequiredValue
, readNested
, readNestedOptional
+ -- * Defining sources
, SomeSource
- , ConfigError(..)
- , Key(..)
+ -- * Reading a config
+ , runFetchConfig
+ , Fetch
+ -- * Parsing config values
, Value(..)
+ , ConfigValue(..)
+ -- * Basic types
+ , Key(..)
+ , Warning(..)
+ , ConfigError(..)
+ -- * Utilities
, configKeysOf
, key
) where
@@ -43,6 +63,7 @@ import Data.Map (Map)
import qualified Data.Map.Strict as M
+-- | A class to model configurations. See "Conftrack"'s documention for a usage example
class Config a where
readConfig :: Fetch a
@@ -54,6 +75,16 @@ data FetcherState = FetcherState
, fetcherErrors :: [ConfigError]
}
+-- | A value of type @Fetch a@ can be used to read in a value @a@, with configuration
+-- sources handled implicitly.
+--
+-- Note that this is an instance of 'Applicative' but not 'Monad'. In practical terms
+-- this means that values read from the configuration sources cannot be inspected while
+-- reading the rest of the config, and in particular which keys are read cannot depend
+-- on another key's value. This allows for introspection functions like 'configKeysOf'.
+--
+-- For configuration keys whose presence depends on each other, use
+-- 'Conftrack.readNestedOptional' to model similar behaviour.
newtype Fetch a = Fetch (FetcherState -> IO (a, FetcherState))
deriving (Functor)
@@ -84,6 +115,10 @@ runFetchConfig sources = do
then pure $ Right (result, origins, unusedWarnings <> warnings)
else pure $ Left errors
+-- | a list of all keys which will be read when running @runFetchConfig@ to
+-- produce a value of type @a@.
+--
+-- This runs inside the 'IO' monad, but does not do any actual IO.
configKeysOf :: forall a. Config a => IO [Key]
configKeysOf = do
let (Fetch m) = readConfig @a
@@ -92,8 +127,12 @@ configKeysOf = do
let keys = mapMaybe (\case {(NotPresent k) -> Just k; _ -> Nothing }) errors
pure keys
-
-
+-- | read an optional config value, resulting in a @Just@ if it is present
+-- and a @Nothing@ if it is not.
+--
+-- This is distinct from using 'readValue' to produce a value of type @Maybe a@:
+-- the latter will require the key to be present, but allow it to be @null@
+-- or similarly empty.
readOptionalValue :: forall a. ConfigValue a => Key -> Fetch (Maybe a)
readOptionalValue bareKey = Fetch $ \s1@FetcherState{..} -> do
@@ -114,7 +153,7 @@ readOptionalValue bareKey = Fetch $ \s1@FetcherState{..} -> do
pure (fst val, s1 { fetcherSources = sources
, fetcherOrigins = M.insertWith (<>) k (snd val) fetcherOrigins })
-
+-- | read in a config value, and produce an error if it is not present.
readRequiredValue :: ConfigValue a => Key -> Fetch a
readRequiredValue k =
let
@@ -128,6 +167,7 @@ readRequiredValue k =
pure (dummy, s { fetcherErrors = NotPresent (k `prefixedWith` fetcherPrefix s) : fetcherErrors s })
Just v -> pure (v, s)))
+-- | read in a config value, or give the given default value if it is not present.
readValue :: forall a. ConfigValue a => a -> Key -> Fetch a
readValue defaultValue k =
let
@@ -156,12 +196,19 @@ firstMatchInSources k (SomeSource (source, sourceState):sources) = do
Right _ ->
pure $ (eitherValue, SomeSource (source, newState)) : fmap (Left Shadowed ,) sources
+-- | read a nested set of configuration values, prefixed by a given key. This
+-- corresponds to nested objects in json.
readNested :: forall a. Config a => Key -> Fetch a
readNested (Key prefix') = Fetch $ \s1 -> do
let (Fetch nested) = readConfig @a
(config, s2) <- nested (s1 { fetcherPrefix = fetcherPrefix s1 <> NonEmpty.toList prefix' })
pure (config, s2 { fetcherPrefix = fetcherPrefix s1 })
+-- | same as 'readNested', but produce @Nothing@ if the nested keys are not present.
+-- This can be used for optionally configurable sub-systems or similar constructs.
+--
+-- If only some but not all keys of the nested configuration are given, this will
+-- produce an error.
readNestedOptional :: forall a. (Show a, Config a) => Key -> Fetch (Maybe a)
readNestedOptional (Key prefix) = Fetch $ \s1 -> do
let (Fetch nested) = readConfig @a
@@ -200,3 +247,112 @@ collectUnused sources = do
<&> fmap (\(Just a) -> Warning $ "Unused Keys " <> T.pack (show a))
. filter (\(Just a) -> not (null a))
. filter isJust
+
+
+{- $use
+
+This library models configuration files as a list of configuration 'Key's,
+for which values can be retrieved from generic sources, such as environment
+variables, a program's cli arguments, or a yaml (or json, etc.) file.
+
+As a simple example, assume a program interacting with some API. We want it
+to read the API's base url (falling back to a default value if it is not
+given) and an API key (and error out if it is missing) from its config:
+
+> data ProgramConfig =
+> { configBaseUrl :: URL
+> , configApiKey :: Text
+> }
+
+Then we can write an appropriate instance of 'Config' for it:
+
+> instance Config ProgramConfig where
+> readConfig = ProgramConfig
+> <$> readValue "http://example.org" [key|baseUrl|]
+> <*> readRequiredValue [key|apiKey|]
+
+'Config' is an instance of 'Applicative'. With the @ApplicativeDo@ language
+extension enabled, the above can be equivalently written as:
+
+> instance Config ProgramConfig where
+> readConfig = do
+> configBaseUrl <- readValue "http://example.org" [key|baseUrl|]
+> configApiKey <- readRequiredValue [key|apiKey|]
+> pure (ProgramConfig {..})
+
+Note that 'Config' is not a 'Monad', so we cannot inspect the config values here,
+or make the reading of further keys depend on the value of earlier ones. This is
+to enable introspection-like uses as in 'configKeysOf'.
+
+To read our config we must provide a non-empty list of sources. Functions to
+construct these live in the @Conftrack.Source.*@ modules; here we use
+'Conftrack.Source.Yaml.mkYamlFileSource' and 'Conftrack.Source.Env.mkEnvSource'
+(from "Conftrac.Source.Yaml" and "Conftrack.Source.Env" respectively) to read
+values from either a yaml file or environment variables:
+
+> main = do
+> result <- runFetchConfig
+> [ mkEnvSource "CONFTRACK"
+> , mkYamlFileSource [path|./config.yaml|]
+> ]
+> case result of
+> Left _ -> ..
+> Right (config, origins, warnings) -> ..
+
+Now we can read in a config file like
+
+> baseUrl: http://localhost/api/v1
+> apiKey: very-very-secret
+
+or from environment variables
+
+> CONFTRACK_BASEURL=http://localhost/api/v1
+> CONFTRACK_APIKEY=very-very-secret
+
+Of course, sources can be mixed: Perhaps we do not want to have our program's api
+key inside the configuration file. Then we can simply omit it there and provide it
+via the @CONFTRACK_APIKEY@ environment variable instead.
+
+== Multiple sources
+
+The order of sources given to 'runFetchConfig' matters: values given in earlier
+sources shadow values of the same key in all following sources.
+
+Thus even if we have
+
+> apiKey: will-not-be-used
+
+in our @config.yaml@ file, it will be ignored if the @CONFTRACK_APIKEY@ environment
+variable also has a value.
+
+== Keeping track of things
+
+Conftrack is written to always keep track of the configuration values it reads. In
+particular, it is intended to avoid frustrating questions of the kind "I have
+clearly set this config key in the file, why does my software not use it?".
+
+This is reflected in 'runFetchConfig'\'s return type: if it does not produce an error,
+it will not only return a set of config values, but also a map of 'Origin's and a list
+of 'Warning's indicating likely misconfiguration:
+
+> main = do
+> result <- runFetchConfig
+> [ mkEnvSource "CONFTRACK"
+> , mkYamlFileSource [path|./config.yaml|]
+> ]
+> case result of
+> Left _ -> ..
+> Right (config, origins, warnings) -> do
+> printConfigOrigins origins
+> ...
+
+May print something like this:
+
+> Environment variable CONFTRACK_APIKEY
+> apiKey = "very-very-secret"
+> YAML file ./config.yaml
+> baseUrl = "http://localhost/api/v1"
+
+It is recommended that programs making use of conftrack include a @--show-config@
+option (or a similar method of introspection) to help in debugging such cases.
+-}