summaryrefslogtreecommitdiff
path: root/src/Conftrack/Value.hs
diff options
context:
space:
mode:
authorstuebinm2024-07-21 17:55:36 +0200
committerstuebinm2024-07-21 17:55:36 +0200
commitb8df907e76b8ac7cdf59b26f0e75a477d926f122 (patch)
tree8e01c42c992ed2f313837e337aff06fbf5c38083 /src/Conftrack/Value.hs
parent16575597093923ac46839128b2676da92496d598 (diff)
document publicly exposed interface
this documents most functions that might be used by downstream consumers of this library, except for those in Conftrack.Pretty, which aren't done yet.
Diffstat (limited to 'src/Conftrack/Value.hs')
-rw-r--r--src/Conftrack/Value.hs18
1 files changed, 17 insertions, 1 deletions
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