{-# LANGUAGE DeriveAnyClass #-}
module Toml.Type.TOML
( TOML (..)
, insertKeyVal
, insertKeyAnyVal
, insertTable
, insertTableArrays
) where
import Control.DeepSeq (NFData)
import Data.HashMap.Strict (HashMap)
import Data.List.NonEmpty (NonEmpty)
import Data.Semigroup (Semigroup (..))
import GHC.Generics (Generic)
import Toml.PrefixTree (Key (..), PrefixMap)
import Toml.Type.AnyValue (AnyValue (..))
import Toml.Type.Value (Value)
import qualified Data.HashMap.Strict as HashMap
import qualified Toml.PrefixTree as Prefix
data TOML = TOML
{ tomlPairs :: HashMap Key AnyValue
, tomlTables :: PrefixMap TOML
, tomlTableArrays :: HashMap Key (NonEmpty TOML)
} deriving (Show, Eq, NFData, Generic)
instance Semigroup TOML where
(TOML pairsA tablesA arraysA) <> (TOML pairsB tablesB arraysB) = TOML
(pairsA <> pairsB)
(HashMap.unionWith (<>) tablesA tablesB)
(arraysA <> arraysB)
instance Monoid TOML where
mappend = (<>)
mempty = TOML mempty mempty mempty
insertKeyVal :: Key -> Value a -> TOML -> TOML
insertKeyVal k v = insertKeyAnyVal k (AnyValue v)
insertKeyAnyVal :: Key -> AnyValue -> TOML -> TOML
insertKeyAnyVal k av toml =toml { tomlPairs = HashMap.insert k av (tomlPairs toml) }
insertTable :: Key -> TOML -> TOML -> TOML
insertTable k inToml toml = toml
{ tomlTables = Prefix.insert k inToml (tomlTables toml)
}
insertTableArrays :: Key -> NonEmpty TOML -> TOML -> TOML
insertTableArrays k arr toml = toml
{ tomlTableArrays = HashMap.insert k arr (tomlTableArrays toml)
}