{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnicodeSyntax #-}
module Configuration.Utils.ConfigFile
(
setProperty
, (..:)
, (!..:)
, updateProperty
, (%.:)
, ConfigFile(..)
, ConfigFilesConfig(..)
#if REMOTE_CONFIGS
, cfcHttpsPolicy
#endif
, defaultConfigFilesConfig
, pConfigFilesConfig
, dropAndUncaml
, module Data.Aeson
) where
import Configuration.Utils.CommandLine
import Configuration.Utils.Internal
import Data.Aeson
import Data.Aeson.Types (Parser)
import Data.Char
import Data.Foldable
#if MIN_VERSION_aeson(2,0,0)
import qualified Data.Aeson.Key as K
import qualified Data.Aeson.KeyMap as H
#else
import qualified Data.HashMap.Strict as H
#endif
import Data.Maybe
import Data.Monoid.Unicode
import Data.String
import qualified Data.Text as T
import Data.Typeable
import Prelude hiding (any, concatMap, mapM_)
#ifdef REMOTE_CONFIGS
import Configuration.Utils.Internal.HttpsCertPolicy
import Configuration.Utils.Operators
#endif
#if MIN_VERSION_aeson(2,0,0)
fromText ∷ T.Text → Key
fromText :: Text -> Key
fromText = Text -> Key
K.fromText
#else
fromText ∷ T.Text → T.Text
fromText = id
#endif
setProperty
∷ Lens' a b
→ T.Text
→ (Value → Parser b)
→ Object
→ Parser (a → a)
setProperty :: Lens' a b
-> Text -> (Value -> Parser b) -> Object -> Parser (a -> a)
setProperty Lens' a b
s Text
k Value -> Parser b
p Object
o = case Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
H.lookup (Text -> Key
fromText Text
k) Object
o of
Maybe Value
Nothing → (a -> a) -> Parser (a -> a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure a -> a
forall a. a -> a
id
Just Value
v → ((b -> Identity b) -> a -> Identity a) -> b -> a -> a
forall a b s t.
((a -> Identity b) -> s -> Identity t) -> b -> s -> t
set (b -> Identity b) -> a -> Identity a
Lens' a b
s (b -> a -> a) -> Parser b -> Parser (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser b
p Value
v
(..:) ∷ FromJSON b ⇒ Lens' a b → T.Text → Object → Parser (a → a)
..: :: Lens' a b -> Text -> Object -> Parser (a -> a)
(..:) Lens' a b
s Text
k = Lens' a b
-> Text -> (Value -> Parser b) -> Object -> Parser (a -> a)
forall a b.
Lens' a b
-> Text -> (Value -> Parser b) -> Object -> Parser (a -> a)
setProperty Lens' a b
s Text
k Value -> Parser b
forall a. FromJSON a => Value -> Parser a
parseJSON
infix 6 ..:
{-# INLINE (..:) #-}
updateProperty
∷ Lens' a b
→ T.Text
→ (Value → Parser (b → b))
→ Object
→ Parser (a → a)
updateProperty :: Lens' a b
-> Text -> (Value -> Parser (b -> b)) -> Object -> Parser (a -> a)
updateProperty Lens' a b
s Text
k Value -> Parser (b -> b)
p Object
o = case Key -> Object -> Maybe Value
forall v. Key -> KeyMap v -> Maybe v
H.lookup (Text -> Key
fromText Text
k) Object
o of
Maybe Value
Nothing → (a -> a) -> Parser (a -> a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure a -> a
forall a. a -> a
id
Just Value
v → ((b -> Identity b) -> a -> Identity a) -> (b -> b) -> a -> a
forall a b s t.
((a -> Identity b) -> s -> Identity t) -> (a -> b) -> s -> t
over (b -> Identity b) -> a -> Identity a
Lens' a b
s ((b -> b) -> a -> a) -> Parser (b -> b) -> Parser (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (b -> b)
p Value
v
{-# INLINE updateProperty #-}
(%.:) ∷ FromJSON (b → b) ⇒ Lens' a b → T.Text → Object → Parser (a → a)
%.: :: Lens' a b -> Text -> Object -> Parser (a -> a)
(%.:) Lens' a b
s Text
k = Lens' a b
-> Text -> (Value -> Parser (b -> b)) -> Object -> Parser (a -> a)
forall a b.
Lens' a b
-> Text -> (Value -> Parser (b -> b)) -> Object -> Parser (a -> a)
updateProperty Lens' a b
s Text
k Value -> Parser (b -> b)
forall a. FromJSON a => Value -> Parser a
parseJSON
infix 6 %.:
{-# INLINE (%.:) #-}
(!..:)
∷ FromJSON b
⇒ Lens' a b
→ T.Text
→ Object
→ Parser (a → a)
!..: :: Lens' a b -> Text -> Object -> Parser (a -> a)
(!..:) Lens' a b
l Text
property Object
o = ((b -> Identity b) -> a -> Identity a) -> b -> a -> a
forall a b s t.
((a -> Identity b) -> s -> Identity t) -> b -> s -> t
set (b -> Identity b) -> a -> Identity a
Lens' a b
l (b -> a -> a) -> Parser b -> Parser (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser b
forall a. FromJSON a => Object -> Key -> Parser a
.: Text -> Key
fromText Text
property)
{-# INLINE (!..:) #-}
data ConfigFile
= ConfigFileRequired { ConfigFile -> Text
getConfigFile ∷ !T.Text }
| ConfigFileOptional { getConfigFile ∷ !T.Text }
deriving (Int -> ConfigFile -> ShowS
[ConfigFile] -> ShowS
ConfigFile -> String
(Int -> ConfigFile -> ShowS)
-> (ConfigFile -> String)
-> ([ConfigFile] -> ShowS)
-> Show ConfigFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigFile] -> ShowS
$cshowList :: [ConfigFile] -> ShowS
show :: ConfigFile -> String
$cshow :: ConfigFile -> String
showsPrec :: Int -> ConfigFile -> ShowS
$cshowsPrec :: Int -> ConfigFile -> ShowS
Show, ReadPrec [ConfigFile]
ReadPrec ConfigFile
Int -> ReadS ConfigFile
ReadS [ConfigFile]
(Int -> ReadS ConfigFile)
-> ReadS [ConfigFile]
-> ReadPrec ConfigFile
-> ReadPrec [ConfigFile]
-> Read ConfigFile
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfigFile]
$creadListPrec :: ReadPrec [ConfigFile]
readPrec :: ReadPrec ConfigFile
$creadPrec :: ReadPrec ConfigFile
readList :: ReadS [ConfigFile]
$creadList :: ReadS [ConfigFile]
readsPrec :: Int -> ReadS ConfigFile
$creadsPrec :: Int -> ReadS ConfigFile
Read, ConfigFile -> ConfigFile -> Bool
(ConfigFile -> ConfigFile -> Bool)
-> (ConfigFile -> ConfigFile -> Bool) -> Eq ConfigFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigFile -> ConfigFile -> Bool
$c/= :: ConfigFile -> ConfigFile -> Bool
== :: ConfigFile -> ConfigFile -> Bool
$c== :: ConfigFile -> ConfigFile -> Bool
Eq, Eq ConfigFile
Eq ConfigFile
-> (ConfigFile -> ConfigFile -> Ordering)
-> (ConfigFile -> ConfigFile -> Bool)
-> (ConfigFile -> ConfigFile -> Bool)
-> (ConfigFile -> ConfigFile -> Bool)
-> (ConfigFile -> ConfigFile -> Bool)
-> (ConfigFile -> ConfigFile -> ConfigFile)
-> (ConfigFile -> ConfigFile -> ConfigFile)
-> Ord ConfigFile
ConfigFile -> ConfigFile -> Bool
ConfigFile -> ConfigFile -> Ordering
ConfigFile -> ConfigFile -> ConfigFile
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConfigFile -> ConfigFile -> ConfigFile
$cmin :: ConfigFile -> ConfigFile -> ConfigFile
max :: ConfigFile -> ConfigFile -> ConfigFile
$cmax :: ConfigFile -> ConfigFile -> ConfigFile
>= :: ConfigFile -> ConfigFile -> Bool
$c>= :: ConfigFile -> ConfigFile -> Bool
> :: ConfigFile -> ConfigFile -> Bool
$c> :: ConfigFile -> ConfigFile -> Bool
<= :: ConfigFile -> ConfigFile -> Bool
$c<= :: ConfigFile -> ConfigFile -> Bool
< :: ConfigFile -> ConfigFile -> Bool
$c< :: ConfigFile -> ConfigFile -> Bool
compare :: ConfigFile -> ConfigFile -> Ordering
$ccompare :: ConfigFile -> ConfigFile -> Ordering
$cp1Ord :: Eq ConfigFile
Ord, Typeable)
#if REMOTE_CONFIGS
data ConfigFilesConfig = ConfigFilesConfig
{ _cfcHttpsPolicy ∷ !HttpsCertPolicy
}
deriving (Show, Eq, Typeable)
cfcHttpsPolicy ∷ Lens' ConfigFilesConfig HttpsCertPolicy
cfcHttpsPolicy = lens _cfcHttpsPolicy $ \a b → a { _cfcHttpsPolicy = b }
defaultConfigFilesConfig ∷ ConfigFilesConfig
defaultConfigFilesConfig = ConfigFilesConfig
{ _cfcHttpsPolicy = defaultHttpsCertPolicy
}
pConfigFilesConfig ∷ MParser ConfigFilesConfig
pConfigFilesConfig = id
<$< cfcHttpsPolicy %:: pHttpsCertPolicy "config-"
#else
data ConfigFilesConfig = ConfigFilesConfig {}
defaultConfigFilesConfig ∷ ConfigFilesConfig
defaultConfigFilesConfig :: ConfigFilesConfig
defaultConfigFilesConfig = ConfigFilesConfig :: ConfigFilesConfig
ConfigFilesConfig {}
pConfigFilesConfig ∷ MParser ConfigFilesConfig
pConfigFilesConfig :: MParser ConfigFilesConfig
pConfigFilesConfig = (ConfigFilesConfig -> ConfigFilesConfig)
-> MParser ConfigFilesConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfigFilesConfig -> ConfigFilesConfig
forall a. a -> a
id
#endif
dropAndUncaml ∷ Int → String → String
dropAndUncaml :: Int -> ShowS
dropAndUncaml Int
_ String
"" = String
""
dropAndUncaml Int
i String
l = case Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
i String
l of
[] → String
l
(Char
h:String
t) → Char -> Char
toLower Char
h Char -> ShowS
forall a. a -> [a] -> [a]
: (Char -> String) -> ShowS
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Char
x → if Char -> Bool
isUpper Char
x then String
"-" String -> ShowS
forall α. Monoid α => α -> α -> α
⊕ [Char -> Char
toLower Char
x] else [Char
x]) String
t