Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines the notion of a scope and operations on scopes.
Synopsis
- data Scope = Scope {}
- data NameSpaceId
- allNameSpaces :: [NameSpaceId]
- type ScopeNameSpaces = [(NameSpaceId, NameSpace)]
- localNameSpace :: Access -> NameSpaceId
- nameSpaceAccess :: NameSpaceId -> Access
- scopeNameSpace :: NameSpaceId -> Scope -> NameSpace
- updateScopeNameSpaces :: (ScopeNameSpaces -> ScopeNameSpaces) -> Scope -> Scope
- updateScopeNameSpacesM :: Functor m => (ScopeNameSpaces -> m ScopeNameSpaces) -> Scope -> m Scope
- data ScopeInfo = ScopeInfo {}
- type NameMap = Map QName (NonEmpty QName)
- type ModuleMap = Map ModuleName [QName]
- type LocalVars = AssocList Name LocalVar
- data BindingSource
- data LocalVar = LocalVar {}
- shadowLocal :: [AbstractName] -> LocalVar -> LocalVar
- patternToModuleBound :: LocalVar -> LocalVar
- notShadowedLocal :: LocalVar -> Maybe Name
- notShadowedLocals :: LocalVars -> AssocList Name Name
- scopeCurrent :: Lens' ModuleName ScopeInfo
- scopeModules :: Lens' (Map ModuleName Scope) ScopeInfo
- scopeVarsToBind :: Lens' LocalVars ScopeInfo
- scopeLocals :: Lens' LocalVars ScopeInfo
- scopePrecedence :: Lens' PrecedenceStack ScopeInfo
- scopeInverseName :: Lens' NameMap ScopeInfo
- scopeInverseModule :: Lens' ModuleMap ScopeInfo
- scopeInScope :: Lens' InScopeSet ScopeInfo
- scopeFixities :: Lens' Fixities ScopeInfo
- scopePolarities :: Lens' Polarities ScopeInfo
- scopeFixitiesAndPolarities :: Lens' (Fixities, Polarities) ScopeInfo
- updateVarsToBind :: (LocalVars -> LocalVars) -> ScopeInfo -> ScopeInfo
- setVarsToBind :: LocalVars -> ScopeInfo -> ScopeInfo
- updateScopeLocals :: (LocalVars -> LocalVars) -> ScopeInfo -> ScopeInfo
- setScopeLocals :: LocalVars -> ScopeInfo -> ScopeInfo
- data NameSpace = NameSpace {}
- type ThingsInScope a = Map Name [a]
- type NamesInScope = ThingsInScope AbstractName
- type ModulesInScope = ThingsInScope AbstractModule
- type InScopeSet = Set QName
- data InScopeTag a where
- class Ord a => InScope a where
- inScopeTag :: InScopeTag a
- inNameSpace :: forall a. InScope a => NameSpace -> ThingsInScope a
- data NameOrModule
- data KindOfName
- isDefName :: KindOfName -> Bool
- data KindsOfNames
- elemKindsOfNames :: KindOfName -> KindsOfNames -> Bool
- allKindsOfNames :: KindsOfNames
- someKindsOfNames :: [KindOfName] -> KindsOfNames
- exceptKindsOfNames :: [KindOfName] -> KindsOfNames
- data WhyInScope
- data AbstractName = AbsName {}
- data NameMetadata
- data AbstractModule = AbsModule {}
- lensAnameName :: Functor m => (QName -> m QName) -> AbstractName -> m AbstractName
- lensAmodName :: Functor m => (ModuleName -> m ModuleName) -> AbstractModule -> m AbstractModule
- data ResolvedName
- mergeNames :: Eq a => ThingsInScope a -> ThingsInScope a -> ThingsInScope a
- mergeNamesMany :: Eq a => [ThingsInScope a] -> ThingsInScope a
- emptyNameSpace :: NameSpace
- mapNameSpace :: (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet) -> NameSpace -> NameSpace
- zipNameSpace :: (NamesInScope -> NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet -> InScopeSet) -> NameSpace -> NameSpace -> NameSpace
- mapNameSpaceM :: Applicative m => (NamesInScope -> m NamesInScope) -> (ModulesInScope -> m ModulesInScope) -> (InScopeSet -> m InScopeSet) -> NameSpace -> m NameSpace
- emptyScope :: Scope
- emptyScopeInfo :: ScopeInfo
- mapScope :: (NameSpaceId -> NamesInScope -> NamesInScope) -> (NameSpaceId -> ModulesInScope -> ModulesInScope) -> (NameSpaceId -> InScopeSet -> InScopeSet) -> Scope -> Scope
- mapScope_ :: (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet) -> Scope -> Scope
- mapScopeNS :: NameSpaceId -> (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet) -> Scope -> Scope
- mapScopeM :: Applicative m => (NameSpaceId -> NamesInScope -> m NamesInScope) -> (NameSpaceId -> ModulesInScope -> m ModulesInScope) -> (NameSpaceId -> InScopeSet -> m InScopeSet) -> Scope -> m Scope
- mapScopeM_ :: Applicative m => (NamesInScope -> m NamesInScope) -> (ModulesInScope -> m ModulesInScope) -> (InScopeSet -> m InScopeSet) -> Scope -> m Scope
- zipScope :: (NameSpaceId -> NamesInScope -> NamesInScope -> NamesInScope) -> (NameSpaceId -> ModulesInScope -> ModulesInScope -> ModulesInScope) -> (NameSpaceId -> InScopeSet -> InScopeSet -> InScopeSet) -> Scope -> Scope -> Scope
- zipScope_ :: (NamesInScope -> NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet -> InScopeSet) -> Scope -> Scope -> Scope
- recomputeInScopeSets :: Scope -> Scope
- filterScope :: (Name -> Bool) -> (Name -> Bool) -> Scope -> Scope
- allNamesInScope :: InScope a => Scope -> ThingsInScope a
- allNamesInScope' :: InScope a => Scope -> ThingsInScope (a, Access)
- exportedNamesInScope :: InScope a => Scope -> ThingsInScope a
- namesInScope :: InScope a => [NameSpaceId] -> Scope -> ThingsInScope a
- allThingsInScope :: Scope -> NameSpace
- thingsInScope :: [NameSpaceId] -> Scope -> NameSpace
- mergeScope :: Scope -> Scope -> Scope
- mergeScopes :: [Scope] -> Scope
- setScopeAccess :: NameSpaceId -> Scope -> Scope
- setNameSpace :: NameSpaceId -> NameSpace -> Scope -> Scope
- modifyNameSpace :: NameSpaceId -> (NameSpace -> NameSpace) -> Scope -> Scope
- addNameToScope :: NameSpaceId -> Name -> AbstractName -> Scope -> Scope
- removeNameFromScope :: NameSpaceId -> Name -> Scope -> Scope
- addModuleToScope :: NameSpaceId -> Name -> AbstractModule -> Scope -> Scope
- data UsingOrHiding
- usingOrHiding :: ImportDirective -> UsingOrHiding
- applyImportDirective :: ImportDirective -> Scope -> Scope
- applyImportDirective_ :: ImportDirective -> Scope -> (Scope, (Set Name, Set Name))
- renameCanonicalNames :: Map QName QName -> Map ModuleName ModuleName -> Scope -> Scope
- restrictPrivate :: Scope -> Scope
- restrictLocalPrivate :: ModuleName -> Scope -> Scope
- disallowGeneralizedVars :: Scope -> Scope
- inScopeBecause :: (WhyInScope -> WhyInScope) -> Scope -> Scope
- publicModules :: ScopeInfo -> Map ModuleName Scope
- publicNames :: ScopeInfo -> Set AbstractName
- everythingInScope :: ScopeInfo -> NameSpace
- everythingInScopeQualified :: ScopeInfo -> NameSpace
- flattenScope :: [[Name]] -> ScopeInfo -> Map QName [AbstractName]
- concreteNamesInScope :: ScopeInfo -> Set QName
- scopeLookup :: InScope a => QName -> ScopeInfo -> [a]
- scopeLookup' :: forall a. InScope a => QName -> ScopeInfo -> [(a, Access)]
- data AllowAmbiguousNames
- isNameInScope :: QName -> ScopeInfo -> Bool
- inverseScopeLookup :: Either ModuleName QName -> ScopeInfo -> [QName]
- inverseScopeLookup' :: AllowAmbiguousNames -> Either ModuleName QName -> ScopeInfo -> [QName]
- recomputeInverseScopeMaps :: ScopeInfo -> ScopeInfo
- inverseScopeLookupName :: QName -> ScopeInfo -> [QName]
- inverseScopeLookupName' :: AllowAmbiguousNames -> QName -> ScopeInfo -> [QName]
- inverseScopeLookupModule :: ModuleName -> ScopeInfo -> [QName]
- class SetBindingSite a where
- setBindingSite :: Range -> a -> a
- prettyNameSpace :: NameSpace -> [Doc]
- blockOfLines :: Doc -> [Doc] -> [Doc]
Scope representation
A scope is a named collection of names partitioned into public and private names.
Instances
Eq Scope Source # | |
Data Scope Source # | |
Defined in Agda.Syntax.Scope.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scope -> c Scope # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scope # dataTypeOf :: Scope -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scope) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scope) # gmapT :: (forall b. Data b => b -> b) -> Scope -> Scope # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scope -> r # gmapQ :: (forall d. Data d => d -> u) -> Scope -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Scope -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scope -> m Scope # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scope -> m Scope # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scope -> m Scope # | |
Show Scope Source # | |
Pretty Scope Source # | |
EmbPrj Scope Source # | |
InstantiateFull Scope Source # | |
Defined in Agda.TypeChecking.Reduce |
data NameSpaceId Source #
See Access
.
PrivateNS | Things not exported by this module. |
PublicNS | Things defined and exported by this module. |
ImportedNS | Things from open public, exported by this module. |
Instances
allNameSpaces :: [NameSpaceId] Source #
type ScopeNameSpaces = [(NameSpaceId, NameSpace)] Source #
localNameSpace :: Access -> NameSpaceId Source #
nameSpaceAccess :: NameSpaceId -> Access Source #
scopeNameSpace :: NameSpaceId -> Scope -> NameSpace Source #
updateScopeNameSpaces :: (ScopeNameSpaces -> ScopeNameSpaces) -> Scope -> Scope Source #
A lens for scopeNameSpaces
updateScopeNameSpacesM :: Functor m => (ScopeNameSpaces -> m ScopeNameSpaces) -> Scope -> m Scope Source #
`Monadic'
lens (Functor sufficient).
The complete information about the scope at a particular program point includes the scope stack, the local variables, and the context precedence.
ScopeInfo | |
|
Instances
Eq ScopeInfo Source # | |
Data ScopeInfo Source # | |
Defined in Agda.Syntax.Scope.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScopeInfo -> c ScopeInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScopeInfo # toConstr :: ScopeInfo -> Constr # dataTypeOf :: ScopeInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScopeInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScopeInfo) # gmapT :: (forall b. Data b => b -> b) -> ScopeInfo -> ScopeInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScopeInfo -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScopeInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> ScopeInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ScopeInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScopeInfo -> m ScopeInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScopeInfo -> m ScopeInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScopeInfo -> m ScopeInfo # | |
Show ScopeInfo Source # | |
Pretty ScopeInfo Source # | |
KillRange ScopeInfo Source # | |
Defined in Agda.Syntax.Scope.Base | |
EmbPrj ScopeInfo Source # | |
data BindingSource Source #
For each bound variable, we want to know whether it was bound by a
λ, Π, module telescope, pattern, or let
.
LambdaBound |
|
PatternBound | f ... = |
LetBound | let ... in |
Instances
A local variable can be shadowed by an import. In case of reference to a shadowed variable, we want to report a scope error.
LocalVar | |
|
Instances
Eq LocalVar Source # | |
Data LocalVar Source # | |
Defined in Agda.Syntax.Scope.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalVar -> c LocalVar # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalVar # toConstr :: LocalVar -> Constr # dataTypeOf :: LocalVar -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LocalVar) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalVar) # gmapT :: (forall b. Data b => b -> b) -> LocalVar -> LocalVar # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalVar -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalVar -> r # gmapQ :: (forall d. Data d => d -> u) -> LocalVar -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalVar -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalVar -> m LocalVar # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalVar -> m LocalVar # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalVar -> m LocalVar # | |
Ord LocalVar Source # | |
Defined in Agda.Syntax.Scope.Base | |
Show LocalVar Source # | |
Pretty LocalVar Source # | We show shadowed variables as prefixed by a ".", as not in scope. |
EmbPrj LocalVar Source # | |
shadowLocal :: [AbstractName] -> LocalVar -> LocalVar Source #
Shadow a local name by a non-empty list of imports.
patternToModuleBound :: LocalVar -> LocalVar Source #
Treat patternBound variable as a module parameter
notShadowedLocals :: LocalVars -> AssocList Name Name Source #
Get all locals that are not shadowed by imports.
scopeCurrent :: Lens' ModuleName ScopeInfo Source #
Lenses for ScopeInfo components
updateVarsToBind :: (LocalVars -> LocalVars) -> ScopeInfo -> ScopeInfo Source #
Lens for scopeVarsToBind
.
updateScopeLocals :: (LocalVars -> LocalVars) -> ScopeInfo -> ScopeInfo Source #
Lens for scopeLocals
.
Name spaces
A NameSpace
contains the mappings from concrete names that the user can
write to the abstract fully qualified names that the type checker wants to
read.
NameSpace | |
|
Instances
Eq NameSpace Source # | |
Data NameSpace Source # | |
Defined in Agda.Syntax.Scope.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameSpace -> c NameSpace # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameSpace # toConstr :: NameSpace -> Constr # dataTypeOf :: NameSpace -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameSpace) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameSpace) # gmapT :: (forall b. Data b => b -> b) -> NameSpace -> NameSpace # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r # gmapQ :: (forall d. Data d => d -> u) -> NameSpace -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NameSpace -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace # | |
Show NameSpace Source # | |
Pretty NameSpace Source # | |
EmbPrj NameSpace Source # | |
type ThingsInScope a = Map Name [a] Source #
type NamesInScope = ThingsInScope AbstractName Source #
type InScopeSet = Set QName Source #
data InScopeTag a where Source #
Set of types consisting of exactly AbstractName
and AbstractModule
.
A GADT just for some dependent-types trickery.
class Ord a => InScope a where Source #
Type class for some dependent-types trickery.
inScopeTag :: InScopeTag a Source #
Instances
InScope AbstractModule Source # | |
Defined in Agda.Syntax.Scope.Base | |
InScope AbstractName Source # | |
Defined in Agda.Syntax.Scope.Base |
inNameSpace :: forall a. InScope a => NameSpace -> ThingsInScope a Source #
inNameSpace
selects either the name map or the module name map from
a NameSpace
. What is selected is determined by result type
(using the dependent-type trickery).
data NameOrModule Source #
Non-dependent tag for name or module.
Instances
Decorated names
data KindOfName Source #
For the sake of parsing left-hand sides, we distinguish constructor and record field names from defined names.
ConName | Constructor name. |
FldName | Record field name. |
PatternSynName | Name of a pattern synonym. |
GeneralizeName | Name to be generalized |
DisallowedGeneralizeName | Generalizable variable from a let open |
MacroName | Name of a macro |
QuotableName | A name that can only be quoted.
Previous category |
DataName | Name of a |
RecName | Name of a |
FunName | Name of a defined function. |
AxiomName | Name of a |
PrimName | Name of a |
OtherDefName | A |
Instances
isDefName :: KindOfName -> Bool Source #
data KindsOfNames Source #
A set of KindOfName
, for the sake of elemKindsOfNames
.
AllKindsOfNames | |
SomeKindsOfNames (Set KindOfName) | Only these kinds. |
ExceptKindsOfNames (Set KindOfName) | All but these Kinds. |
elemKindsOfNames :: KindOfName -> KindsOfNames -> Bool Source #
someKindsOfNames :: [KindOfName] -> KindsOfNames Source #
exceptKindsOfNames :: [KindOfName] -> KindsOfNames Source #
data WhyInScope Source #
Where does a name come from?
This information is solely for reporting to the user,
see whyInScope
.
Defined | Defined in this module. |
Opened QName WhyInScope | Imported from another module. |
Applied QName WhyInScope | Imported by a module application. |
Instances
Data WhyInScope Source # | |
Defined in Agda.Syntax.Scope.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WhyInScope -> c WhyInScope # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WhyInScope # toConstr :: WhyInScope -> Constr # dataTypeOf :: WhyInScope -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WhyInScope) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WhyInScope) # gmapT :: (forall b. Data b => b -> b) -> WhyInScope -> WhyInScope # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WhyInScope -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WhyInScope -> r # gmapQ :: (forall d. Data d => d -> u) -> WhyInScope -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WhyInScope -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WhyInScope -> m WhyInScope # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WhyInScope -> m WhyInScope # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WhyInScope -> m WhyInScope # | |
Show WhyInScope Source # | |
Defined in Agda.Syntax.Scope.Base showsPrec :: Int -> WhyInScope -> ShowS # show :: WhyInScope -> String # showList :: [WhyInScope] -> ShowS # | |
EmbPrj WhyInScope Source # | |
data AbstractName Source #
A decoration of QName
.
AbsName | |
|
Instances
data NameMetadata Source #
Instances
Data NameMetadata Source # | |
Defined in Agda.Syntax.Scope.Base gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameMetadata -> c NameMetadata # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameMetadata # toConstr :: NameMetadata -> Constr # dataTypeOf :: NameMetadata -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameMetadata) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameMetadata) # gmapT :: (forall b. Data b => b -> b) -> NameMetadata -> NameMetadata # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameMetadata -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameMetadata -> r # gmapQ :: (forall d. Data d => d -> u) -> NameMetadata -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NameMetadata -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameMetadata -> m NameMetadata # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameMetadata -> m NameMetadata # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameMetadata -> m NameMetadata # | |
Show NameMetadata Source # | |
Defined in Agda.Syntax.Scope.Base showsPrec :: Int -> NameMetadata -> ShowS # show :: NameMetadata -> String # showList :: [NameMetadata] -> ShowS # | |
EmbPrj NameMetadata Source # | |
data AbstractModule Source #
A decoration of abstract syntax module names.
AbsModule | |
|
Instances
lensAnameName :: Functor m => (QName -> m QName) -> AbstractName -> m AbstractName Source #
Van Laarhoven lens on anameName
.
lensAmodName :: Functor m => (ModuleName -> m ModuleName) -> AbstractModule -> m AbstractModule Source #
Van Laarhoven lens on amodName
.
data ResolvedName Source #
VarName | Local variable bound by λ, Π, module telescope, pattern, |
| |
DefinedName Access AbstractName | Function, data/record type, postulate. |
FieldName (NonEmpty AbstractName) | Record field name. Needs to be distinguished to parse copatterns. |
ConstructorName (NonEmpty AbstractName) | Data or record constructor name. |
PatternSynResName (NonEmpty AbstractName) | Name of pattern synonym. |
UnknownName | Unbound name. |
Instances
Operations on name and module maps.
mergeNames :: Eq a => ThingsInScope a -> ThingsInScope a -> ThingsInScope a Source #
mergeNamesMany :: Eq a => [ThingsInScope a] -> ThingsInScope a Source #
Operations on name spaces
emptyNameSpace :: NameSpace Source #
The empty name space.
mapNameSpace :: (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet) -> NameSpace -> NameSpace Source #
Map functions over the names and modules in a name space.
zipNameSpace :: (NamesInScope -> NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet -> InScopeSet) -> NameSpace -> NameSpace -> NameSpace Source #
Zip together two name spaces.
mapNameSpaceM :: Applicative m => (NamesInScope -> m NamesInScope) -> (ModulesInScope -> m ModulesInScope) -> (InScopeSet -> m InScopeSet) -> NameSpace -> m NameSpace Source #
Map monadic function over a namespace.
General operations on scopes
emptyScope :: Scope Source #
The empty scope.
emptyScopeInfo :: ScopeInfo Source #
The empty scope info.
mapScope :: (NameSpaceId -> NamesInScope -> NamesInScope) -> (NameSpaceId -> ModulesInScope -> ModulesInScope) -> (NameSpaceId -> InScopeSet -> InScopeSet) -> Scope -> Scope Source #
Map functions over the names and modules in a scope.
mapScope_ :: (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet) -> Scope -> Scope Source #
Same as mapScope
but applies the same function to all name spaces.
mapScopeNS :: NameSpaceId -> (NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet) -> Scope -> Scope Source #
Same as mapScope
but applies the function only on the given name space.
mapScopeM :: Applicative m => (NameSpaceId -> NamesInScope -> m NamesInScope) -> (NameSpaceId -> ModulesInScope -> m ModulesInScope) -> (NameSpaceId -> InScopeSet -> m InScopeSet) -> Scope -> m Scope Source #
Map monadic functions over the names and modules in a scope.
mapScopeM_ :: Applicative m => (NamesInScope -> m NamesInScope) -> (ModulesInScope -> m ModulesInScope) -> (InScopeSet -> m InScopeSet) -> Scope -> m Scope Source #
Same as mapScopeM
but applies the same function to both the public and
private name spaces.
zipScope :: (NameSpaceId -> NamesInScope -> NamesInScope -> NamesInScope) -> (NameSpaceId -> ModulesInScope -> ModulesInScope -> ModulesInScope) -> (NameSpaceId -> InScopeSet -> InScopeSet -> InScopeSet) -> Scope -> Scope -> Scope Source #
Zip together two scopes. The resulting scope has the same name as the first scope.
zipScope_ :: (NamesInScope -> NamesInScope -> NamesInScope) -> (ModulesInScope -> ModulesInScope -> ModulesInScope) -> (InScopeSet -> InScopeSet -> InScopeSet) -> Scope -> Scope -> Scope Source #
Same as zipScope
but applies the same function to both the public and
private name spaces.
recomputeInScopeSets :: Scope -> Scope Source #
Recompute the inScope sets of a scope.
filterScope :: (Name -> Bool) -> (Name -> Bool) -> Scope -> Scope Source #
Filter a scope keeping only concrete names matching the predicates. The first predicate is applied to the names and the second to the modules.
allNamesInScope :: InScope a => Scope -> ThingsInScope a Source #
Return all names in a scope.
allNamesInScope' :: InScope a => Scope -> ThingsInScope (a, Access) Source #
exportedNamesInScope :: InScope a => Scope -> ThingsInScope a Source #
Returns the scope's non-private names.
namesInScope :: InScope a => [NameSpaceId] -> Scope -> ThingsInScope a Source #
allThingsInScope :: Scope -> NameSpace Source #
thingsInScope :: [NameSpaceId] -> Scope -> NameSpace Source #
mergeScope :: Scope -> Scope -> Scope Source #
Merge two scopes. The result has the name of the first scope.
mergeScopes :: [Scope] -> Scope Source #
Merge a non-empty list of scopes. The result has the name of the first scope in the list.
Specific operations on scopes
setScopeAccess :: NameSpaceId -> Scope -> Scope Source #
Move all names in a scope to the given name space (except never move from Imported to Public).
setNameSpace :: NameSpaceId -> NameSpace -> Scope -> Scope Source #
Update a particular name space.
modifyNameSpace :: NameSpaceId -> (NameSpace -> NameSpace) -> Scope -> Scope Source #
Modify a particular name space.
addNameToScope :: NameSpaceId -> Name -> AbstractName -> Scope -> Scope Source #
Add a name to a scope.
removeNameFromScope :: NameSpaceId -> Name -> Scope -> Scope Source #
Remove a name from a scope. Caution: does not update the nsInScope set. This is only used by rebindName and in that case we add the name right back (but with a different kind).
addModuleToScope :: NameSpaceId -> Name -> AbstractModule -> Scope -> Scope Source #
Add a module to a scope.
data UsingOrHiding Source #
When we get here we cannot have both using
and hiding
.
applyImportDirective :: ImportDirective -> Scope -> Scope Source #
Apply an ImportDirective
to a scope:
- rename keys (C.Name) according to
renaming
; - for untouched keys, either of
a) remove keys according to hiding
, or
b) filter keys according to using
.
Both steps could be done in one pass, by first preparing key-filtering
functions C.Name -> Maybe C.Name
for defined names and module names.
However, the penalty of doing it in two passes should not be too high.
(Doubling the run time.)
applyImportDirective_ Source #
:: ImportDirective | |
-> Scope | |
-> (Scope, (Set Name, Set Name)) | Merged scope, clashing names, clashing module names. |
Version of applyImportDirective
that also returns sets of name
and module name clashes introduced by renaming
to identifiers
that are already imported by using
or lack of hiding
.
renameCanonicalNames :: Map QName QName -> Map ModuleName ModuleName -> Scope -> Scope Source #
Rename the abstract names in a scope.
restrictPrivate :: Scope -> Scope Source #
Remove private name space of a scope.
Should be a right identity for exportedNamesInScope
.
exportedNamesInScope . restrictPrivate == exportedNamesInScope
.
restrictLocalPrivate :: ModuleName -> Scope -> Scope Source #
Remove private things from the given module from a scope.
disallowGeneralizedVars :: Scope -> Scope Source #
Disallow using generalized variables from the scope
inScopeBecause :: (WhyInScope -> WhyInScope) -> Scope -> Scope Source #
Add an explanation to why things are in scope.
publicModules :: ScopeInfo -> Map ModuleName Scope Source #
Get the public parts of the public modules of a scope
publicNames :: ScopeInfo -> Set AbstractName Source #
flattenScope :: [[Name]] -> ScopeInfo -> Map QName [AbstractName] Source #
Compute a flattened scope. Only include unqualified names or names qualified by modules in the first argument.
concreteNamesInScope :: ScopeInfo -> Set QName Source #
Get all concrete names in scope. Includes bound variables.
Inverse look-up
data AllowAmbiguousNames Source #
AmbiguousAnything | Used for instance arguments to check whether a name is in scope, but we do not care whether is is ambiguous |
AmbiguousConProjs | Ambiguous constructors, projections, or pattern synonyms. |
AmbiguousNothing |
Instances
Eq AllowAmbiguousNames Source # | |
Defined in Agda.Syntax.Scope.Base (==) :: AllowAmbiguousNames -> AllowAmbiguousNames -> Bool # (/=) :: AllowAmbiguousNames -> AllowAmbiguousNames -> Bool # |
inverseScopeLookup :: Either ModuleName QName -> ScopeInfo -> [QName] Source #
Find the concrete names that map (uniquely) to a given abstract name. Sort by length, shortest first.
inverseScopeLookup' :: AllowAmbiguousNames -> Either ModuleName QName -> ScopeInfo -> [QName] Source #
inverseScopeLookupName :: QName -> ScopeInfo -> [QName] Source #
Find the concrete names that map (uniquely) to a given abstract qualified name. Sort by length, shortest first.
inverseScopeLookupName' :: AllowAmbiguousNames -> QName -> ScopeInfo -> [QName] Source #
inverseScopeLookupModule :: ModuleName -> ScopeInfo -> [QName] Source #
Find the concrete names that map (uniquely) to a given abstract module name. Sort by length, shortest first.
Update binding site
class SetBindingSite a where Source #
Set the nameBindingSite
in an abstract name.
Nothing
setBindingSite :: Range -> a -> a Source #
setBindingSite :: (SetBindingSite b, Functor t, t b ~ a) => Range -> a -> a Source #
Instances
SetBindingSite ModuleName Source # | Sets the binding site of all names in the path. |
Defined in Agda.Syntax.Scope.Base setBindingSite :: Range -> ModuleName -> ModuleName Source # | |
SetBindingSite QName Source # | |
Defined in Agda.Syntax.Scope.Base | |
SetBindingSite Name Source # | |
Defined in Agda.Syntax.Scope.Base | |
SetBindingSite AbstractModule Source # | |
Defined in Agda.Syntax.Scope.Base setBindingSite :: Range -> AbstractModule -> AbstractModule Source # | |
SetBindingSite AbstractName Source # | |
Defined in Agda.Syntax.Scope.Base setBindingSite :: Range -> AbstractName -> AbstractName Source # | |
SetBindingSite a => SetBindingSite [a] Source # | |
Defined in Agda.Syntax.Scope.Base setBindingSite :: Range -> [a] -> [a] Source # |
(Debug) printing
prettyNameSpace :: NameSpace -> [Doc] Source #