{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveTraversable #-} -- | Allows abstraction over larger groups of termed nodes, by -- associating those nodes with their terms and other specific info. module Descript.BasicInj.Traverse.Termed ( Termed (..) , SymbolEnv (..) ) where import Descript.BasicInj.Traverse.Term (TTerm) import Descript.BasicInj.Data -- | A node associated with a term. data Termed a an = Termed { termedTerm :: TTerm a , termedValue :: a an } -- | A symbol node associated with its term, and context which would -- distinguish it from other symbols with the same term and label. data SymbolEnv an = EnvModulePathElem [Symbol an] (Symbol an) | EnvRecordHead (FSymbol an) | EnvPropertyKey (FSymbol an) (Symbol an) deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable)