{- FOURMOLU_DISABLE -}
-- The MIT License (MIT)

-- Copyright (c) 2016-2024 Objectionary.com

-- Permission is hereby granted, free of charge, to any person obtaining a copy
-- of this software and associated documentation files (the "Software"), to deal
-- in the Software without restriction, including without limitation the rights
-- to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
-- copies of the Software, and to permit persons to whom the Software is
-- furnished to do so, subject to the following conditions:

-- The above copyright notice and this permission notice shall be included
-- in all copies or substantial portions of the Software.

-- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
-- IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
-- FITNESS FOR A PARTICULAR PURPOSE AND NON-INFRINGEMENT. IN NO EVENT SHALL THE
-- AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
-- LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
-- OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
-- SOFTWARE.
{- FOURMOLU_ENABLE -}
module Language.EO.Phi.Dataize.Context where

import Data.HashMap.Strict qualified as HashMap
import Data.HashSet as HashSet (difference, fromList, intersection, member)
import Data.List.NonEmpty qualified as NonEmpty
import Language.EO.Phi.Dataize.Atoms as Atoms
import Language.EO.Phi.Rules.Common
import Language.EO.Phi.Syntax.Abs

knownAtomsMap :: Atoms
knownAtomsMap :: Atoms
knownAtomsMap = [(String,
  String
  -> Object
  -> EvaluationState
  -> DataizeChain (Object, EvaluationState))]
-> Atoms
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(String,
  String
  -> Object
  -> EvaluationState
  -> DataizeChain (Object, EvaluationState))]
knownAtomsList

defaultContext :: [NamedRule] -> Object -> Context
defaultContext :: [NamedRule] -> Object -> Context
defaultContext [NamedRule]
rules Object
obj =
  Context
    { builtinRules :: Bool
builtinRules = Bool
False
    , allRules :: [NamedRule]
allRules = [NamedRule]
rules
    , enabledAtoms :: Atoms
enabledAtoms = [String] -> [String] -> Atoms
mkEnabledAtoms [] []
    , knownAtoms :: Atoms
knownAtoms = Atoms
knownAtomsMap
    , outerFormations :: NonEmpty Object
outerFormations = Object -> NonEmpty Object
forall a. a -> NonEmpty a
NonEmpty.singleton Object
obj
    , currentAttr :: Attribute
currentAttr = Attribute
Phi
    , insideFormation :: Bool
insideFormation = Bool
False
    , insideAbstractFormation :: Bool
insideAbstractFormation = Bool
False
    , dataizePackage :: Bool
dataizePackage = Bool
True
    , minimizeTerms :: Bool
minimizeTerms = Bool
False
    , insideSubObject :: Bool
insideSubObject = Bool
False
    }

mkEnabledAtoms :: [String] -> [String] -> Atoms
mkEnabledAtoms :: [String] -> [String] -> Atoms
mkEnabledAtoms [String]
enabled [String]
disabled = Atoms
enabledAtoms'
 where
  knownAtomsSet :: HashSet String
knownAtomsSet = [String] -> HashSet String
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList (Atoms -> [String]
forall k v. HashMap k v -> [k]
HashMap.keys Atoms
knownAtomsMap)
  disabledSet :: HashSet String
disabledSet = [String] -> HashSet String
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList [String]
disabled
  enabledSet :: HashSet String
enabledSet =
    case [String]
enabled of
      [] -> HashSet String
knownAtomsSet
      [String]
_ -> [String] -> HashSet String
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HashSet.fromList [String]
enabled
  enabled' :: HashSet String
enabled' = HashSet String -> HashSet String -> HashSet String
forall a. Eq a => HashSet a -> HashSet a -> HashSet a
HashSet.intersection (HashSet String -> HashSet String -> HashSet String
forall a. (Eq a, Hashable a) => HashSet a -> HashSet a -> HashSet a
HashSet.difference HashSet String
enabledSet HashSet String
disabledSet) HashSet String
knownAtomsSet
  enabledAtoms' :: Atoms
enabledAtoms' = (String
 -> (String
     -> Object
     -> EvaluationState
     -> DataizeChain (Object, EvaluationState))
 -> Bool)
-> Atoms -> Atoms
forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
HashMap.filterWithKey (\String
k String
-> Object
-> EvaluationState
-> DataizeChain (Object, EvaluationState)
_ -> String
k String -> HashSet String -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
`HashSet.member` HashSet String
enabled') Atoms
knownAtomsMap