Agda-2.6.2.1.20220320: A dependently typed functional programming language and proof assistant
Safe HaskellSafe-Inferred
LanguageHaskell2010

Agda.Syntax.Scope.Base

Description

This module defines the notion of a scope and operations on scopes.

Synopsis

Scope representation

data Scope Source #

A scope is a named collection of names partitioned into public and private names.

Instances

Instances details
InstantiateFull Scope Source # 
Instance details

Defined in Agda.TypeChecking.Reduce

EmbPrj Scope Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Null Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Pretty Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

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 #

toConstr :: Scope -> Constr #

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 :: forall r r'. (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 #

Generic Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep Scope :: Type -> Type #

Methods

from :: Scope -> Rep Scope x #

to :: Rep Scope x -> Scope #

Show Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

NFData Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: Scope -> () #

Eq Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

(==) :: Scope -> Scope -> Bool #

(/=) :: Scope -> Scope -> Bool #

type Rep Scope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

data DataOrRecordModule Source #

Instances

Instances details
EmbPrj DataOrRecordModule Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Data DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataOrRecordModule -> c DataOrRecordModule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataOrRecordModule #

toConstr :: DataOrRecordModule -> Constr #

dataTypeOf :: DataOrRecordModule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataOrRecordModule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataOrRecordModule) #

gmapT :: (forall b. Data b => b -> b) -> DataOrRecordModule -> DataOrRecordModule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataOrRecordModule -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataOrRecordModule -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataOrRecordModule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataOrRecordModule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataOrRecordModule -> m DataOrRecordModule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataOrRecordModule -> m DataOrRecordModule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataOrRecordModule -> m DataOrRecordModule #

Bounded DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Enum DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Generic DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep DataOrRecordModule :: Type -> Type #

Show DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: DataOrRecordModule -> () #

Eq DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep DataOrRecordModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep DataOrRecordModule = D1 ('MetaData "DataOrRecordModule" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "IsDataModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IsRecordModule" 'PrefixI 'False) (U1 :: Type -> Type))

data NameSpaceId Source #

See Access.

Constructors

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

Instances details
EmbPrj NameSpaceId Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Pretty NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameSpaceId -> c NameSpaceId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameSpaceId #

toConstr :: NameSpaceId -> Constr #

dataTypeOf :: NameSpaceId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameSpaceId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameSpaceId) #

gmapT :: (forall b. Data b => b -> b) -> NameSpaceId -> NameSpaceId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameSpaceId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameSpaceId -> r #

gmapQ :: (forall d. Data d => d -> u) -> NameSpaceId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NameSpaceId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameSpaceId -> m NameSpaceId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpaceId -> m NameSpaceId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpaceId -> m NameSpaceId #

Bounded NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Enum NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Generic NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep NameSpaceId :: Type -> Type #

Show NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: NameSpaceId -> () #

Eq NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameSpaceId Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameSpaceId = D1 ('MetaData "NameSpaceId" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "PrivateNS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PublicNS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImportedNS" 'PrefixI 'False) (U1 :: Type -> Type)))

updateScopeNameSpacesM :: Functor m => (ScopeNameSpaces -> m ScopeNameSpaces) -> Scope -> m Scope Source #

`Monadic' lens (Functor sufficient).

data ScopeInfo Source #

The complete information about the scope at a particular program point includes the scope stack, the local variables, and the context precedence.

Constructors

ScopeInfo 

Fields

Instances

Instances details
KillRange ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

EmbPrj ScopeInfo Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Null ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Pretty ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

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 :: forall r r'. (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 #

Generic ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep ScopeInfo :: Type -> Type #

Show ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: ScopeInfo -> () #

Eq ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep ScopeInfo Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

data NameMapEntry Source #

For the sake of highlighting, the _scopeInverseName map also stores the KindOfName of an A.QName.

Constructors

NameMapEntry 

Fields

Instances

Instances details
Data NameMapEntry Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameMapEntry -> c NameMapEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameMapEntry #

toConstr :: NameMapEntry -> Constr #

dataTypeOf :: NameMapEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameMapEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameMapEntry) #

gmapT :: (forall b. Data b => b -> b) -> NameMapEntry -> NameMapEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameMapEntry -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameMapEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> NameMapEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NameMapEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameMapEntry -> m NameMapEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameMapEntry -> m NameMapEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameMapEntry -> m NameMapEntry #

Semigroup NameMapEntry Source #

Invariant: the KindOfName components should be equal whenever we have to concrete renderings of an abstract name.

Instance details

Defined in Agda.Syntax.Scope.Base

Generic NameMapEntry Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep NameMapEntry :: Type -> Type #

Show NameMapEntry Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData NameMapEntry Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: NameMapEntry -> () #

type Rep NameMapEntry Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameMapEntry = D1 ('MetaData "NameMapEntry" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "NameMapEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "qnameKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KindOfName) :*: S1 ('MetaSel ('Just "qnameConcrete") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 QName))))

type LocalVars = AssocList Name LocalVar Source #

Local variables.

data BindingSource Source #

For each bound variable, we want to know whether it was bound by a λ, Π, module telescope, pattern, or let.

Constructors

LambdaBound

λ (currently also used for Π and module parameters)

PatternBound
f ... =
LetBound
let ... in
WithBound
| ... in q

Instances

Instances details
EmbPrj BindingSource Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Pretty BindingSource Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data BindingSource Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BindingSource -> c BindingSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BindingSource #

toConstr :: BindingSource -> Constr #

dataTypeOf :: BindingSource -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BindingSource) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BindingSource) #

gmapT :: (forall b. Data b => b -> b) -> BindingSource -> BindingSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BindingSource -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BindingSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> BindingSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BindingSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BindingSource -> m BindingSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BindingSource -> m BindingSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BindingSource -> m BindingSource #

Generic BindingSource Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep BindingSource :: Type -> Type #

Show BindingSource Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData BindingSource Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: BindingSource -> () #

Eq BindingSource Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep BindingSource Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep BindingSource = D1 ('MetaData "BindingSource" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) ((C1 ('MetaCons "LambdaBound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PatternBound" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LetBound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WithBound" 'PrefixI 'False) (U1 :: Type -> Type)))

data LocalVar Source #

A local variable can be shadowed by an import. In case of reference to a shadowed variable, we want to report a scope error.

Constructors

LocalVar 

Fields

Instances

Instances details
EmbPrj LocalVar Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Pretty LocalVar Source #

We show shadowed variables as prefixed by a ".", as not in scope.

Instance details

Defined in Agda.Syntax.Scope.Base

Data LocalVar Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

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 :: forall r r'. (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 #

Generic LocalVar Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep LocalVar :: Type -> Type #

Methods

from :: LocalVar -> Rep LocalVar x #

to :: Rep LocalVar x -> LocalVar #

Show LocalVar Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData LocalVar Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: LocalVar -> () #

Eq LocalVar Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Ord LocalVar Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep LocalVar Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep LocalVar = D1 ('MetaData "LocalVar" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "LocalVar" 'PrefixI 'True) (S1 ('MetaSel ('Just "localVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Just "localBindingSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BindingSource) :*: S1 ('MetaSel ('Just "localShadowedBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AbstractName]))))

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

notShadowedLocal :: LocalVar -> Maybe Name Source #

Project name of unshadowed local variable.

notShadowedLocals :: LocalVars -> AssocList Name Name Source #

Get all locals that are not shadowed by imports.

scopeCurrent :: Lens' ModuleName ScopeInfo Source #

Lenses for ScopeInfo components

Name spaces

data NameSpace Source #

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.

Constructors

NameSpace 

Fields

Instances

Instances details
EmbPrj NameSpace Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Pretty NameSpace Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data NameSpace Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

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 :: forall r r'. (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 #

Generic NameSpace Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep NameSpace :: Type -> Type #

Show NameSpace Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData NameSpace Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: NameSpace -> () #

Eq NameSpace Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameSpace Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameSpace = D1 ('MetaData "NameSpace" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "NameSpace" 'PrefixI 'True) (S1 ('MetaSel ('Just "nsNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NamesInScope) :*: (S1 ('MetaSel ('Just "nsModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModulesInScope) :*: S1 ('MetaSel ('Just "nsInScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InScopeSet))))

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.

Instances

Instances details
InScope AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

InScope AbstractName Source # 
Instance details

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

Instances details
EmbPrj NameOrModule Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Data NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameOrModule -> c NameOrModule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameOrModule #

toConstr :: NameOrModule -> Constr #

dataTypeOf :: NameOrModule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameOrModule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameOrModule) #

gmapT :: (forall b. Data b => b -> b) -> NameOrModule -> NameOrModule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameOrModule -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameOrModule -> r #

gmapQ :: (forall d. Data d => d -> u) -> NameOrModule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NameOrModule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameOrModule -> m NameOrModule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameOrModule -> m NameOrModule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameOrModule -> m NameOrModule #

Bounded NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Enum NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Generic NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep NameOrModule :: Type -> Type #

Show NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: NameOrModule -> () #

Eq NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Ord NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameOrModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameOrModule = D1 ('MetaData "NameOrModule" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "NameNotModule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModuleNotName" 'PrefixI 'False) (U1 :: Type -> Type))

Decorated names

data KindOfName Source #

For the sake of parsing left-hand sides, we distinguish constructor and record field names from defined names.

Constructors

ConName

Constructor name (Inductive or don't know).

CoConName

Constructor name (definitely CoInductive).

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 DefName: (Refined in a flat manner as Enum and Bounded are not hereditary.)

DataName

Name of a data.

RecName

Name of a record.

FunName

Name of a defined function.

AxiomName

Name of a postulate.

PrimName

Name of a primitive.

OtherDefName

A DefName, but either other kind or don't know which kind. End DefName. Keep these together in sequence, for sake of isDefName!

Instances

Instances details
EmbPrj KindOfName Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Data KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KindOfName -> c KindOfName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KindOfName #

toConstr :: KindOfName -> Constr #

dataTypeOf :: KindOfName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KindOfName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KindOfName) #

gmapT :: (forall b. Data b => b -> b) -> KindOfName -> KindOfName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KindOfName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KindOfName -> r #

gmapQ :: (forall d. Data d => d -> u) -> KindOfName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KindOfName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KindOfName -> m KindOfName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KindOfName -> m KindOfName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KindOfName -> m KindOfName #

Bounded KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Enum KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Generic KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep KindOfName :: Type -> Type #

Show KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: KindOfName -> () #

Eq KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Ord KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep KindOfName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep KindOfName = D1 ('MetaData "KindOfName" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (((C1 ('MetaCons "ConName" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CoConName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FldName" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PatternSynName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeneralizeName" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DisallowedGeneralizeName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MacroName" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "QuotableName" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecName" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FunName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AxiomName" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrimName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherDefName" 'PrefixI 'False) (U1 :: Type -> Type)))))

conKindOfName' :: Foldable t => t Induction -> KindOfName Source #

For ambiguous constructors, we might have both alternatives of Induction. In this case, we default to ConName.

approxConInduction :: Foldable t => t Induction -> Induction Source #

For ambiguous constructors, we might have both alternatives of Induction. In this case, we default to Inductive.

exactConName :: Foldable t => t Induction -> Maybe KindOfName Source #

Only return [Co]ConName if no ambiguity.

data KindsOfNames Source #

A set of KindOfName, for the sake of elemKindsOfNames.

Constructors

AllKindsOfNames 
SomeKindsOfNames (Set KindOfName)

Only these kinds.

ExceptKindsOfNames (Set KindOfName)

All but these Kinds.

data WithKind a Source #

Decorate something with KindOfName

Constructors

WithKind 

Fields

Instances

Instances details
DeclaredNames KName Source # 
Instance details

Defined in Agda.Syntax.Abstract.Views

Foldable WithKind Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

fold :: Monoid m => WithKind m -> m #

foldMap :: Monoid m => (a -> m) -> WithKind a -> m #

foldMap' :: Monoid m => (a -> m) -> WithKind a -> m #

foldr :: (a -> b -> b) -> b -> WithKind a -> b #

foldr' :: (a -> b -> b) -> b -> WithKind a -> b #

foldl :: (b -> a -> b) -> b -> WithKind a -> b #

foldl' :: (b -> a -> b) -> b -> WithKind a -> b #

foldr1 :: (a -> a -> a) -> WithKind a -> a #

foldl1 :: (a -> a -> a) -> WithKind a -> a #

toList :: WithKind a -> [a] #

null :: WithKind a -> Bool #

length :: WithKind a -> Int #

elem :: Eq a => a -> WithKind a -> Bool #

maximum :: Ord a => WithKind a -> a #

minimum :: Ord a => WithKind a -> a #

sum :: Num a => WithKind a -> a #

product :: Num a => WithKind a -> a #

Traversable WithKind Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

traverse :: Applicative f => (a -> f b) -> WithKind a -> f (WithKind b) #

sequenceA :: Applicative f => WithKind (f a) -> f (WithKind a) #

mapM :: Monad m => (a -> m b) -> WithKind a -> m (WithKind b) #

sequence :: Monad m => WithKind (m a) -> m (WithKind a) #

Functor WithKind Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

fmap :: (a -> b) -> WithKind a -> WithKind b #

(<$) :: a -> WithKind b -> WithKind a #

Data a => Data (WithKind a) Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithKind a -> c (WithKind a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WithKind a) #

toConstr :: WithKind a -> Constr #

dataTypeOf :: WithKind a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WithKind a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WithKind a)) #

gmapT :: (forall b. Data b => b -> b) -> WithKind a -> WithKind a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithKind a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithKind a -> r #

gmapQ :: (forall d. Data d => d -> u) -> WithKind a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WithKind a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithKind a -> m (WithKind a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithKind a -> m (WithKind a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithKind a -> m (WithKind a) #

Show a => Show (WithKind a) Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

showsPrec :: Int -> WithKind a -> ShowS #

show :: WithKind a -> String #

showList :: [WithKind a] -> ShowS #

Eq a => Eq (WithKind a) Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

(==) :: WithKind a -> WithKind a -> Bool #

(/=) :: WithKind a -> WithKind a -> Bool #

Ord a => Ord (WithKind a) Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

compare :: WithKind a -> WithKind a -> Ordering #

(<) :: WithKind a -> WithKind a -> Bool #

(<=) :: WithKind a -> WithKind a -> Bool #

(>) :: WithKind a -> WithKind a -> Bool #

(>=) :: WithKind a -> WithKind a -> Bool #

max :: WithKind a -> WithKind a -> WithKind a #

min :: WithKind a -> WithKind a -> WithKind a #

data WhyInScope Source #

Where does a name come from?

This information is solely for reporting to the user, see whyInScope.

Constructors

Defined

Defined in this module.

Opened QName WhyInScope

Imported from another module.

Applied QName WhyInScope

Imported by a module application.

Instances

Instances details
EmbPrj WhyInScope Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Data WhyInScope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

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 :: forall r r'. (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 #

Generic WhyInScope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep WhyInScope :: Type -> Type #

Show WhyInScope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData WhyInScope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: WhyInScope -> () #

type Rep WhyInScope Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

data AbstractName Source #

A decoration of QName.

Constructors

AbsName 

Fields

Instances

Instances details
NameToExpr AbstractName Source #

Turn an AbstractName into an expression.

Instance details

Defined in Agda.Syntax.Abstract

LensFixity AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

HasRange AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

SetRange AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

InScope AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

SetBindingSite AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

ToConcrete AbstractName Source # 
Instance details

Defined in Agda.Syntax.Translation.AbstractToConcrete

Associated Types

type ConOfAbs AbstractName Source #

PrettyTCM AbstractName Source # 
Instance details

Defined in Agda.TypeChecking.Pretty

EmbPrj AbstractName Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Pretty AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AbstractName -> c AbstractName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AbstractName #

toConstr :: AbstractName -> Constr #

dataTypeOf :: AbstractName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AbstractName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AbstractName) #

gmapT :: (forall b. Data b => b -> b) -> AbstractName -> AbstractName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AbstractName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AbstractName -> r #

gmapQ :: (forall d. Data d => d -> u) -> AbstractName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AbstractName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AbstractName -> m AbstractName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AbstractName -> m AbstractName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AbstractName -> m AbstractName #

Generic AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep AbstractName :: Type -> Type #

Show AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: AbstractName -> () #

Eq AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Ord AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type ConOfAbs AbstractName Source # 
Instance details

Defined in Agda.Syntax.Translation.AbstractToConcrete

type Rep AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep AbstractName = D1 ('MetaData "AbstractName" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "AbsName" 'PrefixI 'True) ((S1 ('MetaSel ('Just "anameName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QName) :*: S1 ('MetaSel ('Just "anameKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KindOfName)) :*: (S1 ('MetaSel ('Just "anameLineage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WhyInScope) :*: S1 ('MetaSel ('Just "anameMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NameMetadata))))

data NameMetadata Source #

Instances

Instances details
EmbPrj NameMetadata Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Data NameMetadata Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

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 :: forall r r'. (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 #

Generic NameMetadata Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep NameMetadata :: Type -> Type #

Show NameMetadata Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData NameMetadata Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: NameMetadata -> () #

type Rep NameMetadata Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep NameMetadata = D1 ('MetaData "NameMetadata" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "NoMetadata" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeneralizedVarsMetadata" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map QName Name))))

data AbstractModule Source #

A decoration of abstract syntax module names.

Constructors

AbsModule 

Fields

Instances

Instances details
InScope AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

SetBindingSite AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

EmbPrj AbstractModule Source # 
Instance details

Defined in Agda.TypeChecking.Serialise.Instances.Abstract

Pretty AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AbstractModule -> c AbstractModule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AbstractModule #

toConstr :: AbstractModule -> Constr #

dataTypeOf :: AbstractModule -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AbstractModule) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AbstractModule) #

gmapT :: (forall b. Data b => b -> b) -> AbstractModule -> AbstractModule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AbstractModule -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AbstractModule -> r #

gmapQ :: (forall d. Data d => d -> u) -> AbstractModule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AbstractModule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AbstractModule -> m AbstractModule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AbstractModule -> m AbstractModule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AbstractModule -> m AbstractModule #

Generic AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep AbstractModule :: Type -> Type #

Show AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: AbstractModule -> () #

Eq AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Ord AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep AbstractModule = D1 ('MetaData "AbstractModule" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) (C1 ('MetaCons "AbsModule" 'PrefixI 'True) (S1 ('MetaSel ('Just "amodName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName) :*: S1 ('MetaSel ('Just "amodLineage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WhyInScope)))

data ResolvedName Source #

Constructors

VarName

Local variable bound by λ, Π, module telescope, pattern, let.

Fields

DefinedName

Function, data/record type, postulate.

FieldName

Record field name. Needs to be distinguished to parse copatterns.

Fields

ConstructorName

Data or record constructor name.

Fields

PatternSynResName

Name of pattern synonym.

Fields

UnknownName

Unbound name.

Instances

Instances details
NameToExpr ResolvedName Source #

Turn a ResolvedName into an expression.

Assumes name is not UnknownName.

Instance details

Defined in Agda.Syntax.Abstract

ToConcrete ResolvedName Source #

Assumes name is not UnknownName.

Instance details

Defined in Agda.Syntax.Translation.AbstractToConcrete

Associated Types

type ConOfAbs ResolvedName Source #

Pretty ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Data ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResolvedName -> c ResolvedName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResolvedName #

toConstr :: ResolvedName -> Constr #

dataTypeOf :: ResolvedName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ResolvedName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResolvedName) #

gmapT :: (forall b. Data b => b -> b) -> ResolvedName -> ResolvedName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResolvedName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResolvedName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResolvedName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResolvedName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResolvedName -> m ResolvedName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResolvedName -> m ResolvedName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResolvedName -> m ResolvedName #

Generic ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Associated Types

type Rep ResolvedName :: Type -> Type #

Show ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

NFData ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

rnf :: ResolvedName -> () #

Eq ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type ConOfAbs ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Translation.AbstractToConcrete

type Rep ResolvedName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

type Rep ResolvedName = D1 ('MetaData "ResolvedName" "Agda.Syntax.Scope.Base" "Agda-2.6.2.1.20220320-inplace" 'False) ((C1 ('MetaCons "VarName" 'PrefixI 'True) (S1 ('MetaSel ('Just "resolvedVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "resolvedBindingSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BindingSource)) :+: (C1 ('MetaCons "DefinedName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Access) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbstractName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Suffix))) :+: C1 ('MetaCons "FieldName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 AbstractName))))) :+: (C1 ('MetaCons "ConstructorName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Induction)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 AbstractName))) :+: (C1 ('MetaCons "PatternSynResName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (List1 AbstractName))) :+: C1 ('MetaCons "UnknownName" 'PrefixI 'False) (U1 :: Type -> Type))))

Operations on name and module maps.

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.

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.

exportedNamesInScope :: InScope a => Scope -> ThingsInScope a Source #

Returns the scope's non-private names.

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:

  1. rename keys (C.Name) according to renaming;
  2. 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 #

Arguments

:: 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.

withoutPrivates :: ScopeInfo -> ScopeInfo Source #

Filter privates out of a ScopeInfo

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

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.

scopeLookup :: InScope a => QName -> ScopeInfo -> [a] Source #

Look up a name in the scope

scopeLookup' :: forall a. InScope a => QName -> ScopeInfo -> [(a, Access)] Source #

Inverse look-up

data AllowAmbiguousNames Source #

Constructors

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 

inverseScopeLookupName :: QName -> ScopeInfo -> [QName] Source #

Find the concrete names that map (uniquely) to a given abstract qualified name. Sort by number of modules in the qualified name, unqualified names first.

inverseScopeLookupName'' :: AllowAmbiguousNames -> QName -> ScopeInfo -> Maybe NameMapEntry Source #

A version of inverseScopeLookupName that also delivers the KindOfName. Used in highlighting.

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.

Minimal complete definition

Nothing

Methods

setBindingSite :: Range -> a -> a Source #

default setBindingSite :: (SetBindingSite b, Functor t, t b ~ a) => Range -> a -> a Source #

Instances

Instances details
SetBindingSite ModuleName Source #

Sets the binding site of all names in the path.

Instance details

Defined in Agda.Syntax.Scope.Base

SetBindingSite Name Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

SetBindingSite QName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

SetBindingSite AbstractModule Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

SetBindingSite AbstractName Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

SetBindingSite a => SetBindingSite [a] Source # 
Instance details

Defined in Agda.Syntax.Scope.Base

Methods

setBindingSite :: Range -> [a] -> [a] Source #

(Debug) printing

blockOfLines :: Doc -> [Doc] -> [Doc] Source #

Add first string only if list is non-empty.

Boring instances

Orphan instances

Pretty Suffix Source # 
Instance details