Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data NamingEnv
- shadowing :: NamingEnv -> NamingEnv -> NamingEnv
- class BindsNames a
- data InModule a = InModule (Maybe ModPath) a
- shadowNames :: BindsNames env => env -> RenameM a -> RenameM a
- class Rename f where
- runRenamer :: RenamerInfo -> RenameM a -> (Either [RenamerError] (a, Supply), [RenamerWarning])
- data RenameM a
- data RenamerError
- = MultipleSyms (Located PName) [Name]
- | UnboundName Namespace (Located PName)
- | OverlappingSyms [Name]
- | WrongNamespace Namespace Namespace (Located PName)
- | FixityError (Located Name) Fixity (Located Name) Fixity
- | OverlappingRecordUpdate (Located [Selector]) (Located [Selector])
- | InvalidDependency [DepName]
- | MultipleModParams Ident [Range]
- | InvalidFunctorImport (ImpName Name)
- | UnexpectedNest Range PName
- | ModuleKindMismatch Range (ImpName Name) ModKind ModKind
- data RenamerWarning
- = SymbolShadowed PName Name [Name]
- | UnusedName Name
- | PrefixAssocChanged PrefixOp (Expr Name) (Located Name) Fixity (Expr Name)
- renameVar :: NameType -> PName -> RenameM Name
- renameType :: NameType -> PName -> RenameM Name
- renameModule :: Module PName -> RenameM RenamedModule
- renameTopDecls :: ModName -> [TopDecl PName] -> RenameM (NamingEnv, [TopDecl Name])
- data RenamerInfo = RenamerInfo {}
- data NameType
- data RenamedModule = RenamedModule {}
Documentation
The NamingEnv
is used by the renamer to determine what
identifiers refer to.
Instances
Monoid NamingEnv Source # | |
Semigroup NamingEnv Source # | |
Generic NamingEnv Source # | |
Show NamingEnv Source # | |
BindsNames NamingEnv Source # | |
Defined in Cryptol.ModuleSystem.Binds | |
ModuleInstance NamingEnv Source # | |
Defined in Cryptol.TypeCheck.ModuleInstance moduleInstance :: NamingEnv -> NamingEnv Source # | |
PP NamingEnv Source # | |
NFData NamingEnv Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv.Types | |
type Rep NamingEnv Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv.Types type Rep NamingEnv = D1 ('MetaData "NamingEnv" "Cryptol.ModuleSystem.NamingEnv.Types" "cryptol-3.1.0-276efOa9Q2aIFSEzDdp2Mp" 'True) (C1 ('MetaCons "NamingEnv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Namespace (Map PName Names))))) |
shadowing :: NamingEnv -> NamingEnv -> NamingEnv Source #
Like mappend, but when merging, prefer values on the lhs.
class BindsNames a Source #
Things that define exported names.
namingEnv
Instances
Do something in the context of a module.
If Nothing
than we are working with a local declaration.
Otherwise we are at the top-level of the given module.
By wrapping types with this, we can pass the module path to methods that need the extra information.
Instances
shadowNames :: BindsNames env => env -> RenameM a -> RenameM a Source #
Shadow the current naming environment with some more names.
Instances
runRenamer :: RenamerInfo -> RenameM a -> (Either [RenamerError] (a, Supply), [RenamerWarning]) Source #
data RenamerError Source #
MultipleSyms (Located PName) [Name] | Multiple imported symbols contain this name |
UnboundName Namespace (Located PName) | Some name not bound to any definition |
OverlappingSyms [Name] | An environment has produced multiple overlapping symbols |
WrongNamespace Namespace Namespace (Located PName) | expected, actual. When a name is missing from the expected namespace, but exists in another |
FixityError (Located Name) Fixity (Located Name) Fixity | When the fixity of two operators conflict |
OverlappingRecordUpdate (Located [Selector]) (Located [Selector]) | When record updates overlap (e.g., |
InvalidDependency [DepName] | Things that can't depend on each other |
MultipleModParams Ident [Range] | Module parameters with the same name |
InvalidFunctorImport (ImpName Name) | Can't import functors directly |
UnexpectedNest Range PName | Nested modules were not supposed to appear here |
ModuleKindMismatch Range (ImpName Name) ModKind ModKind | Exepcted one kind (first one) but found the other (second one) |
Instances
data RenamerWarning Source #
SymbolShadowed PName Name [Name] | |
UnusedName Name | |
PrefixAssocChanged PrefixOp (Expr Name) (Located Name) Fixity (Expr Name) |
Instances
renameModule :: Module PName -> RenameM RenamedModule Source #
Entry point. This is used for renaming a top-level module.
renameTopDecls :: ModName -> [TopDecl PName] -> RenameM (NamingEnv, [TopDecl Name]) Source #
Entry point. Rename a list of top-level declarations. This is used for declaration that don't live in a module (e.g., define on the command line.)
We assume that these declarations do not contain any nested modules.
data RenamedModule Source #
The result of renaming a module
RenamedModule | |
|
Instances
PP RenamedModule Source # | |
Defined in Cryptol.ModuleSystem.Renamer |