summaryrefslogtreecommitdiff
path: root/src/Conftrack/Value.hs
diff options
context:
space:
mode:
authorstuebinm2024-06-08 00:22:17 +0200
committerstuebinm2024-06-08 00:22:17 +0200
commit33bce0badbeb834cf8c584df56c424fe1c9bff7a (patch)
treeb4e1fbf82e7ea6b9db5bceec471fe36fc4cf7c90 /src/Conftrack/Value.hs
parentd10c2f0dac08fb2cf0a7df2fb6a745a4759a73cf (diff)
quasi-quotes for config keys
Diffstat (limited to 'src/Conftrack/Value.hs')
-rw-r--r--src/Conftrack/Value.hs22
1 files changed, 20 insertions, 2 deletions
diff --git a/src/Conftrack/Value.hs b/src/Conftrack/Value.hs
index 5c8d949..6fe8780 100644
--- a/src/Conftrack/Value.hs
+++ b/src/Conftrack/Value.hs
@@ -6,15 +6,18 @@
{-# LANGUAGE StrictData #-}
{-# LANGUAGE OverloadedStrings #-}
-module Conftrack.Value (Value(..), ConfigError(..), Key(..), ConfigValue(..), Origin(..), KeyPart, prefixedWith) where
+module Conftrack.Value (key, Value(..), ConfigError(..), Key(..), ConfigValue(..), Origin(..), KeyPart, prefixedWith) 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))
data Value =
ConfigString BS.ByteString
@@ -27,7 +30,22 @@ data Value =
type KeyPart = Text
newtype Key = Key (NonEmpty KeyPart)
- deriving newtype (Eq, Ord, Show)
+ deriving newtype (Eq, Ord)
+ deriving (Lift)
+
+instance Show Key where
+ show (Key parts) = T.unpack (T.intercalate "." (NonEmpty.toList parts))
+
+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"}
+
+blub :: String -> Key
+blub = undefined
+
prefixedWith :: Key -> [KeyPart] -> Key
prefixedWith (Key key) prefix = Key (prependList prefix key)