Safe Haskell | None |
---|---|
Language | Haskell2010 |
Definitions and interface for the Context
and AccessContext
types, which
represent namespaces of definitions.
Synopsis
- data Item
- data Module = Module ![Range] !Context
- data AccessModule = AccessModule !Access ![Range] !Context
- data Context
- data AccessContext
- accessContextUnion :: AccessContext -> AccessContext -> AccessContext
- data LookupError where
- contextLookup :: QName -> Context -> Maybe [Range]
- contextLookupItem :: QName -> Context -> Maybe Item
- contextLookupModule :: QName -> Context -> Maybe Module
- accessContextLookup :: QName -> AccessContext -> Either LookupError [Range]
- accessContextLookupModule :: QName -> AccessContext -> Either LookupError Module
- accessContextLookupDefining :: QName -> AccessContext -> Either LookupError (Bool, [Range])
- accessContextLookupSpecial :: QName -> AccessContext -> Maybe Bool
- contextInsertRange :: Name -> Range -> Context -> Context
- contextInsertRangeModule :: Name -> Range -> Context -> Context
- contextInsertRangeAll :: Range -> Context -> Context
- accessContextInsertRangeAll :: Range -> AccessContext -> AccessContext
- contextDelete :: Name -> Context -> Context
- contextDeleteModule :: Name -> Context -> Context
- contextRename :: Name -> Name -> Context -> Context
- contextRenameModule :: Name -> Name -> Context -> Context
- accessContextDefine :: Name -> AccessContext -> AccessContext
- moduleRanges :: Module -> [Range]
- contextRanges :: Context -> [Range]
- accessContextMatch :: [String] -> AccessContext -> [Name]
- item :: [Range] -> Maybe Name -> Item
- itemPattern :: [Range] -> Maybe Name -> Item
- itemConstructor :: [Range] -> Maybe Name -> Item
- contextItem :: Name -> Item -> Context
- contextModule :: Name -> Module -> Context
- accessContextItem :: Name -> Access -> Item -> AccessContext
- accessContextModule :: Name -> AccessModule -> AccessContext
- accessContextModule' :: Name -> Access -> [Range] -> AccessContext -> AccessContext
- accessContextImport :: QName -> Context -> AccessContext
- fromContext :: Access -> Context -> AccessContext
- toContext :: AccessContext -> Context
Definitions
The data associated with a name in context. This includes:
- Whether the name is a constructor, pattern synonym, or ordinary definition.
- A list of ranges associated with the name, which includes the site of the
original definition, as well as any relevant
import
oropen
statements. - Alternative syntax for the name, if any.
The data associated with a module in context. This includes:
- A list of ranges associated with the module, which includes the site of the
original definition, as well as any relevant
import
oropen
statements. - The inner context of the module.
data AccessModule Source #
Like Module
, but also recording whether the module is public or private.
AccessModule !Access ![Range] !Context |
Instances
Show AccessModule Source # | |
Defined in Agda.Unused.Types.Context showsPrec :: Int -> AccessModule -> ShowS # show :: AccessModule -> String # showList :: [AccessModule] -> ShowS # |
A namespace of definitions. Any Agda module produces a Context
.
data AccessContext Source #
A namespace of definitions, which may be public or private. Any collection
of Agda declarations produces an AccessContext
, for example.
Instances
Show AccessContext Source # | |
Defined in Agda.Unused.Types.Context showsPrec :: Int -> AccessContext -> ShowS # show :: AccessContext -> String # showList :: [AccessContext] -> ShowS # | |
Semigroup AccessContext Source # | Prefer values from second access context. |
Defined in Agda.Unused.Types.Context (<>) :: AccessContext -> AccessContext -> AccessContext # sconcat :: NonEmpty AccessContext -> AccessContext # stimes :: Integral b => b -> AccessContext -> AccessContext # | |
Monoid AccessContext Source # | |
Defined in Agda.Unused.Types.Context mempty :: AccessContext # mappend :: AccessContext -> AccessContext -> AccessContext # mconcat :: [AccessContext] -> AccessContext # |
accessContextUnion :: AccessContext -> AccessContext -> AccessContext Source #
Like (<>)
, but public items take precedence over private items. This is
important when combining contexts from successive declarations; for example:
module M where postulate A : Set module N where postulate A : Set open M x : N.A x = ?
This code type-checks, and the identifier N.A
refers to the postulate
declared in the definition of N
, not the definition opened from M
.
Interface
Lookup
data LookupError where Source #
A description of failure for an AccessContext
lookup.
Instances
Show LookupError Source # | |
Defined in Agda.Unused.Types.Context showsPrec :: Int -> LookupError -> ShowS # show :: LookupError -> String # showList :: [LookupError] -> ShowS # |
contextLookup :: QName -> Context -> Maybe [Range] Source #
Get the ranges for the given name, or Nothing
if not in context.
contextLookupItem :: QName -> Context -> Maybe Item Source #
Get the item for the given name, or Nothing
if not in context.
contextLookupModule :: QName -> Context -> Maybe Module Source #
Get the inner module for the given name, or Nothing
if not in context.
accessContextLookup :: QName -> AccessContext -> Either LookupError [Range] Source #
Get the ranges for the given name, or produce a LookupError
.
accessContextLookupModule :: QName -> AccessContext -> Either LookupError Module Source #
Get the inner module for the given name, or produce a LookupError
.
accessContextLookupDefining :: QName -> AccessContext -> Either LookupError (Bool, [Range]) Source #
Like accessContextLookup
, but also return a boolean indicating whether we
are currently defining the referenced item.
accessContextLookupSpecial :: QName -> AccessContext -> Maybe Bool Source #
Determine whether a name represents a constructor or pattern synonym.
Return Nothing
if the name is not in context.
Insert
contextInsertRange :: Name -> Range -> Context -> Context Source #
Insert a range for the given name, if present.
contextInsertRangeModule :: Name -> Range -> Context -> Context Source #
Insert a range for all names in the given module, if present.
contextInsertRangeAll :: Range -> Context -> Context Source #
Insert a range for all names in a context.
accessContextInsertRangeAll :: Range -> AccessContext -> AccessContext Source #
Insert a range for all names in an access context.
Delete
Rename
Define
accessContextDefine :: Name -> AccessContext -> AccessContext Source #
Mark an existing name as in process of being defined.
Ranges
moduleRanges :: Module -> [Range] Source #
Get all ranges associated with names in the given module, including ranges associated with the module itself.
contextRanges :: Context -> [Range] Source #
Get all ranges associated with names in the given context.
Match
accessContextMatch :: [String] -> AccessContext -> [Name] Source #
Find all operators matching the given list of tokens.
Construction
item :: [Range] -> Maybe Name -> Item Source #
Construct an Item
representing an ordinary definition.
itemPattern :: [Range] -> Maybe Name -> Item Source #
Construct an Item
representing a pattern synonym.
itemConstructor :: [Range] -> Maybe Name -> Item Source #
Construct an Item
representing a constructor.
accessContextItem :: Name -> Access -> Item -> AccessContext Source #
Construct an AccessContext
with a single item, along with the relevant
syntax item if applicable.
accessContextModule :: Name -> AccessModule -> AccessContext Source #
Construct an AccessContext
with a single access module.
accessContextModule' :: Name -> Access -> [Range] -> AccessContext -> AccessContext Source #
Like accessContextModule
, but taking an access context. We convert the
given access context to an ordinary context using toContext
:
accessContextModule' n a rs c = accessContextModule n (AccessModule a rs (toContext c))
accessContextImport :: QName -> Context -> AccessContext Source #
Construct an access context with a single import.
Conversion
fromContext :: Access -> Context -> AccessContext Source #
Convert a Context
to AccessContext
. Give all items the given access.
toContext :: AccessContext -> Context Source #
Convert an AccessContext
to Context
. Discard private items and imports.