| Copyright | (c) 2013-2016 Galois, Inc. |
|---|---|
| License | BSD3 |
| Maintainer | cryptol@galois.com |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell98 |
Cryptol.ModuleSystem.Renamer
Description
- data NamingEnv
- shadowing :: NamingEnv -> NamingEnv -> NamingEnv
- class BindsNames a where
- data InModule a = InModule !ModName a
- namingEnv' :: BindsNames a => a -> Supply -> (NamingEnv, Supply)
- checkNamingEnv :: NamingEnv -> ([RenamerError], [RenamerWarning])
- shadowNames :: BindsNames env => env -> RenameM a -> RenameM a
- class Rename f where
- runRenamer :: Supply -> ModName -> NamingEnv -> RenameM a -> (Either [RenamerError] (a, Supply), [RenamerWarning])
- data RenameM a
- data RenamerError
- = MultipleSyms (Located PName) [Name] NameDisp
- | UnboundExpr (Located PName) NameDisp
- | UnboundType (Located PName) NameDisp
- | OverlappingSyms [Name] NameDisp
- | ExpectedValue (Located PName) NameDisp
- | ExpectedType (Located PName) NameDisp
- | FixityError (Located Name) (Located Name) NameDisp
- | InvalidConstraint (Type PName) NameDisp
- | MalformedConstraint (Located (Type PName)) NameDisp
- data RenamerWarning = SymbolShadowed Name [Name] NameDisp
- renameVar :: PName -> RenameM Name
- renameType :: PName -> RenameM Name
- renameModule :: Module PName -> RenameM (NamingEnv, Module Name)
Documentation
shadowing :: NamingEnv -> NamingEnv -> NamingEnv Source
Like mappend, but when merging, prefer values on the lhs.
class BindsNames a where Source
Things that define exported names.
Instances
| BindsNames ImportIface Source | Produce a naming environment from an interface file, that contains a mapping only from unqualified names to qualified ones. |
| BindsNames NamingEnv Source | |
| BindsNames a => BindsNames [a] Source | |
| BindsNames a => BindsNames (Maybe a) Source | |
| BindsNames (TParam PName) Source | Generate the naming environment for a type parameter. |
| BindsNames (Schema PName) Source | Generate a type renaming environment from the parameters that are bound by this schema. |
| BindsNames (Module PName) Source | The naming environment for a single module. This is the mapping from unqualified names to fully qualified names with uniques. |
| BindsNames (InModule (Newtype PName)) Source | |
| BindsNames (InModule (Bind PName)) Source | Introduce the name |
| BindsNames (InModule (Decl PName)) Source | The naming environment for a single declaration. |
| BindsNames (InModule (TopDecl PName)) Source |
Instances
| Functor InModule Source | |
| Foldable InModule Source | |
| Traversable InModule Source | |
| Show a => Show (InModule a) Source | |
| BindsNames (InModule (Newtype PName)) Source | |
| BindsNames (InModule (Bind PName)) Source | Introduce the name |
| BindsNames (InModule (Decl PName)) Source | The naming environment for a single declaration. |
| BindsNames (InModule (TopDecl PName)) Source |
namingEnv' :: BindsNames a => a -> Supply -> (NamingEnv, Supply) Source
Generate a NamingEnv using an explicit supply.
checkNamingEnv :: NamingEnv -> ([RenamerError], [RenamerWarning]) Source
Throw errors for any names that overlap in a rewrite environment.
shadowNames :: BindsNames env => env -> RenameM a -> RenameM a Source
Shadow the current naming environment with some more names.
Instances
| Rename Prop Source | |
| Rename Type Source | Resolve fixity, then rename the resulting type. |
| Rename TParam Source | |
| Rename Schema Source | Rename a schema, assuming that none of its type variables are already in scope. |
| Rename Pattern Source | |
| Rename Match Source | |
| Rename TypeInst Source | |
| Rename Expr Source | |
| Rename Newtype Source | |
| Rename BindDef Source | |
| Rename Bind Source | Rename a binding. |
| Rename TySyn Source | |
| Rename Decl Source | |
| Rename TopDecl Source |
runRenamer :: Supply -> ModName -> NamingEnv -> RenameM a -> (Either [RenamerError] (a, Supply), [RenamerWarning]) Source
data RenamerError Source
Constructors
| MultipleSyms (Located PName) [Name] NameDisp | Multiple imported symbols contain this name |
| UnboundExpr (Located PName) NameDisp | Expression name is not bound to any definition |
| UnboundType (Located PName) NameDisp | Type name is not bound to any definition |
| OverlappingSyms [Name] NameDisp | An environment has produced multiple overlapping symbols |
| ExpectedValue (Located PName) NameDisp | When a value is expected from the naming environment, but one or more types exist instead. |
| ExpectedType (Located PName) NameDisp | When a type is missing from the naming environment, but one or more values exist with the same name. |
| FixityError (Located Name) (Located Name) NameDisp | When the fixity of two operators conflict |
| InvalidConstraint (Type PName) NameDisp | When it's not possible to produce a Prop from a Type. |
| MalformedConstraint (Located (Type PName)) NameDisp | When a constraint appears within another constraint |
Instances
data RenamerWarning Source
Constructors
| SymbolShadowed Name [Name] NameDisp |
renameType :: PName -> RenameM Name Source