summaryrefslogtreecommitdiff
path: root/src/Conftrack
diff options
context:
space:
mode:
authorstuebinm2024-06-10 22:30:08 +0200
committerstuebinm2024-06-10 23:56:54 +0200
commit3e71d0ab05c7f5fd71a75b86eeac6f8a1edc3a44 (patch)
treee8f630f7838bb2c316d9aa0d4d65af9ded81ed2c /src/Conftrack
parente46b45526f8b9869aac1296d26b9fe80d8a8bb18 (diff)
pretty-printing of config value sources
Diffstat (limited to 'src/Conftrack')
-rw-r--r--src/Conftrack/Pretty.hs40
-rw-r--r--src/Conftrack/Value.hs14
2 files changed, 52 insertions, 2 deletions
diff --git a/src/Conftrack/Pretty.hs b/src/Conftrack/Pretty.hs
new file mode 100644
index 0000000..8a11204
--- /dev/null
+++ b/src/Conftrack/Pretty.hs
@@ -0,0 +1,40 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Conftrack.Pretty where
+
+
+import Conftrack.Value (Origin (..), ConfigError, ConfigValue (..))
+import Conftrack (Warning)
+import Data.Map (Map)
+import Conftrack.Value (Key)
+import qualified Data.Map.Strict as M
+import qualified Data.Text.IO as T
+import qualified Data.Text as T
+import Data.List (sortOn)
+import GHC.Exts (groupWith)
+
+
+printConfigErrors :: [ConfigError] -> IO ()
+printConfigErrors = mapM_ print
+
+-- TODO: perhaps sort it by source, not by key?
+-- also, shadowed values are currently never read
+printConfigOrigins :: Map Key [Origin] -> IO ()
+printConfigOrigins =
+ mapM_ (T.putStrLn . prettyOrigin)
+ . groupWith ((\(Origin _ s) -> s) . head . snd)
+ . filter (not . null . snd)
+ . M.toList
+ where prettyOrigin origins =
+ T.concat $ originSource (snd (head origins)) : fmap prettyKey origins
+ prettyKey (key, []) = "\n " <> T.pack (show key)
+ prettyKey (key, (Origin val _):shadowed) = T.concat $
+ ["\n ", T.pack $ show key, " = ", prettyValue val]
+ <> fmap (\(Origin _ text) -> "\n (occurrance in "<>text<>" shadowed)") shadowed
+ originSource [] = "default value"
+ originSource (Origin _ text:_) = text
+
+
+
+printConfigWarnings :: [Warning] -> IO ()
+printConfigWarnings = mapM_ print
diff --git a/src/Conftrack/Value.hs b/src/Conftrack/Value.hs
index fef8f87..50e4e30 100644
--- a/src/Conftrack/Value.hs
+++ b/src/Conftrack/Value.hs
@@ -6,6 +6,7 @@
{-# LANGUAGE StrictData #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE DefaultSignatures #-}
module Conftrack.Value (key, Value(..), ConfigError(..), Key(..), ConfigValue(..), Origin(..), KeyPart, prefixedWith) where
@@ -58,9 +59,15 @@ data ConfigError =
class ConfigValue a where
fromConfig :: Value -> Either ConfigError a
+ prettyValue :: a -> Text
-data Origin = Origin Key Text
- deriving Show
+ 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
@@ -89,6 +96,9 @@ 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