-- | This module contains the 'Prefixes' type, which is used to store environment variable name prefix mappings, and its typeclass instances.
module RichEnv.Types.Prefixes (Prefixes (Prefixes, unPrefixes), fromList) where

import Data.Aeson (FromJSON (parseJSON), Options (unwrapUnaryRecords), ToJSON (toJSON), Value, defaultOptions, genericParseJSON)
import Data.Aeson.Types (Parser)
import Data.HashMap.Strict qualified as HM
import Data.Text (Text)
import GHC.Generics (Generic)

-- | A list of key-value pairs representing environment variable name prefix mappings. The internal representation is a 'HashMap Text [Text]', where the key is the final prefix and the value is the list of prefixes that will be replaced.
newtype Prefixes = Prefixes {Prefixes -> HashMap Text [Text]
unPrefixes :: HM.HashMap Text [Text]}
  deriving stock (Prefixes -> Prefixes -> Bool
(Prefixes -> Prefixes -> Bool)
-> (Prefixes -> Prefixes -> Bool) -> Eq Prefixes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Prefixes -> Prefixes -> Bool
== :: Prefixes -> Prefixes -> Bool
$c/= :: Prefixes -> Prefixes -> Bool
/= :: Prefixes -> Prefixes -> Bool
Eq, Int -> Prefixes -> ShowS
[Prefixes] -> ShowS
Prefixes -> String
(Int -> Prefixes -> ShowS)
-> (Prefixes -> String) -> ([Prefixes] -> ShowS) -> Show Prefixes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Prefixes -> ShowS
showsPrec :: Int -> Prefixes -> ShowS
$cshow :: Prefixes -> String
show :: Prefixes -> String
$cshowList :: [Prefixes] -> ShowS
showList :: [Prefixes] -> ShowS
Show, (forall x. Prefixes -> Rep Prefixes x)
-> (forall x. Rep Prefixes x -> Prefixes) -> Generic Prefixes
forall x. Rep Prefixes x -> Prefixes
forall x. Prefixes -> Rep Prefixes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Prefixes -> Rep Prefixes x
from :: forall x. Prefixes -> Rep Prefixes x
$cto :: forall x. Rep Prefixes x -> Prefixes
to :: forall x. Rep Prefixes x -> Prefixes
Generic)

instance FromJSON Prefixes where
  parseJSON :: Value -> Parser Prefixes
  parseJSON :: Value -> Parser Prefixes
parseJSON = Options -> Value -> Parser Prefixes
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Prefixes)
-> Options -> Value -> Parser Prefixes
forall a b. (a -> b) -> a -> b
$ Options
defaultOptions {unwrapUnaryRecords :: Bool
unwrapUnaryRecords = Bool
True}

instance ToJSON Prefixes where
  toJSON :: Prefixes -> Value
  toJSON :: Prefixes -> Value
toJSON = HashMap Text [Text] -> Value
forall a. ToJSON a => a -> Value
toJSON (HashMap Text [Text] -> Value)
-> (Prefixes -> HashMap Text [Text]) -> Prefixes -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Prefixes -> HashMap Text [Text]
unPrefixes

instance Semigroup Prefixes where
  (<>) :: Prefixes -> Prefixes -> Prefixes
  <> :: Prefixes -> Prefixes -> Prefixes
(<>) (Prefixes HashMap Text [Text]
a) (Prefixes HashMap Text [Text]
b) = HashMap Text [Text] -> Prefixes
Prefixes (HashMap Text [Text]
a HashMap Text [Text] -> HashMap Text [Text] -> HashMap Text [Text]
forall a. Semigroup a => a -> a -> a
<> HashMap Text [Text]
b)

instance Monoid Prefixes where
  mempty :: Prefixes
  mempty :: Prefixes
mempty = HashMap Text [Text] -> Prefixes
Prefixes HashMap Text [Text]
forall a. Monoid a => a
mempty

-- | Build a 'Prefixes' object from a list of key-value pairs.
fromList :: [(Text, [Text])] -> Prefixes
fromList :: [(Text, [Text])] -> Prefixes
fromList = HashMap Text [Text] -> Prefixes
Prefixes (HashMap Text [Text] -> Prefixes)
-> ([(Text, [Text])] -> HashMap Text [Text])
-> [(Text, [Text])]
-> Prefixes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, [Text])] -> HashMap Text [Text]
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList