{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE StrictData #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE DefaultSignatures #-} module Conftrack.Value (key, Value(..), ConfigError(..), Key(..), ConfigValue(..), Origin(..), KeyPart, prefixedWith, withString) where import Data.Text(Text) import qualified Data.Text as T import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LB import Data.List.NonEmpty (NonEmpty, prependList) import qualified Data.List.NonEmpty as NonEmpty import System.OsPath (OsPath, encodeUtf) 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 | ConfigNull deriving Show 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) 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 , quotePat = \_ -> fail "key quoter cannot be used in patterns" , quoteType = \_ -> fail "key quasi-quote cannot be used for types" , quoteDec = \_ -> fail "key quasi-quote cannot be used in declarations"} prefixedWith :: Key -> [KeyPart] -> Key prefixedWith (Key k) prefix = Key (prependList prefix k) data ConfigError = ParseError Text | TypeMismatch Text Value | NotPresent Key | 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 prettyValue = T.pack . show data Origin = forall a. ConfigValue a => Origin a Text instance Show Origin where show (Origin a text) = "Origin " <> T.unpack (prettyValue a) <> " " <> T.unpack text withString :: (BS.ByteString -> Either ConfigError a) -> Value -> Either ConfigError a withString f (ConfigString a) = f a withString f (ConfigMaybeInteger a _) = f a withString _ val = Left (TypeMismatch "text" val) withInteger :: (Integer -> Either ConfigError a) -> Value -> Either ConfigError a withInteger f (ConfigInteger a) = f a withInteger f (ConfigMaybeInteger _ a) = f a withInteger _ val = Left (TypeMismatch "integer" val) instance ConfigValue Text where fromConfig = withString (Right . BS.decodeUtf8) instance ConfigValue Integer where fromConfig = withInteger Right instance ConfigValue Int where fromConfig = withInteger (Right . fromInteger) instance ConfigValue Bool where fromConfig (ConfigBool b) = Right b fromConfig val = Left (TypeMismatch "bool" val) instance ConfigValue a => ConfigValue (Maybe a) where fromConfig ConfigNull = Right Nothing fromConfig just = fmap Just (fromConfig just) prettyValue Nothing = "null" prettyValue (Just a) = prettyValue a instance ConfigValue OsPath where fromConfig = \case (ConfigString text) -> stringToPath text (ConfigMaybeInteger text _) -> stringToPath text val -> Left (TypeMismatch "path" val) where stringToPath text = case encodeUtf (T.unpack (BS.decodeUtf8 text)) of Right path -> Right path Left err -> Left (ParseError (T.pack $ show err)) instance ConfigValue LB.ByteString where fromConfig = withString (Right . LB.fromStrict) instance ConfigValue BS.ByteString where fromConfig = withString Right