module Language.Haskell.Names.Open.Base where
import qualified Language.Haskell.Names.GlobalSymbolTable as Global
import qualified Language.Haskell.Names.LocalSymbolTable as Local
import Language.Haskell.Names.GetBound
import Language.Haskell.Names.RecordWildcards
import Language.Haskell.Exts
import Control.Monad.Identity
import Data.List
import Data.Lens.Light
import Data.Generics.Traversable
import Data.Typeable
import Data.Monoid
import Data.Functor.Constant
data NameContext
= BindingT
| BindingV
| ReferenceT
| ReferenceV
| ReferenceUV
| ReferenceUT
| ReferenceRS
| SignatureV
| Other
data PatSynMode
= PatSynLeftHandSide
| PatSynRightHandSide
data Scope = Scope
{ _moduName :: ModuleName ()
, _gTable :: Global.Table
, _lTable :: Local.Table
, _nameCtx :: NameContext
, _instClassName :: Maybe (QName ())
, _wcNames :: WcNames
, _patSynMode :: Maybe PatSynMode
}
makeLens ''Scope
initialScope :: ModuleName () -> Global.Table -> Scope
initialScope moduleName tbl = Scope moduleName tbl Local.empty Other Nothing [] Nothing
mergeLocalScopes :: Scope -> Scope -> Scope
mergeLocalScopes sc1 sc2 =
modL lTable (<> sc2 ^. lTable) sc1
newtype Alg w = Alg
{ runAlg :: forall d . Resolvable d => d -> Scope -> w d }
alg :: (?alg :: Alg w, Resolvable d) => d -> Scope -> w d
alg = runAlg ?alg
defaultRtraverse
:: (GTraversable Resolvable a, Applicative f, ?alg :: Alg f)
=> a -> Scope -> f a
defaultRtraverse a sc = gtraverse @Resolvable (\d -> alg d sc) a
class Typeable a => Resolvable a where
rtraverse
:: (Applicative f, ?alg :: Alg f)
=> a -> Scope -> f a
instance (Typeable a, GTraversable Resolvable a) => Resolvable a where
rtraverse = defaultRtraverse
rmap
:: Resolvable a
=> (forall b. Resolvable b => Scope -> b -> b)
-> Scope -> a -> a
rmap f sc =
let ?alg = Alg $ \a sc -> Identity (f sc a)
in runIdentity . flip rtraverse sc
rfoldMap
:: (Monoid r, Resolvable a)
=> (forall b. Resolvable b => Scope -> b -> r)
-> Scope -> a -> r
rfoldMap f sc =
let ?alg = Alg $ \a sc -> Constant (f sc a)
in getConstant . flip rtraverse sc
intro :: (SrcInfo l, GetBound a l) => a -> Scope -> Scope
intro node sc =
modL lTable
(\tbl -> foldl' (flip Local.addValue) tbl $
getBound (sc ^. gTable) node)
sc
setNameCtx :: NameContext -> Scope -> Scope
setNameCtx = setL nameCtx
setWcNames :: WcNames -> Scope -> Scope
setWcNames = setL wcNames
getWcNames :: Scope -> WcNames
getWcNames = getL wcNames
binderV :: Scope -> Scope
binderV = setNameCtx BindingV
binderT :: Scope -> Scope
binderT = setNameCtx BindingT
exprV :: Scope -> Scope
exprV = setNameCtx ReferenceV
exprT :: Scope -> Scope
exprT = setNameCtx ReferenceT
signatureV :: Scope -> Scope
signatureV = setNameCtx SignatureV
exprUV :: Scope -> Scope
exprUV = setNameCtx ReferenceUV
exprUT :: Scope -> Scope
exprUT = setNameCtx ReferenceUT
exprRS :: Scope -> Scope
exprRS = setNameCtx ReferenceRS
setInstClassName :: Maybe (QName ()) -> Scope -> Scope
setInstClassName m = setL instClassName m
setPatSynMode :: PatSynMode -> Scope -> Scope
setPatSynMode = setL patSynMode . Just