cryptol-3.0.0: Cryptol: The Language of Cryptography
Copyright(c) 2013-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cryptol.ModuleSystem.NamingEnv

Description

 
Synopsis

Documentation

newtype NamingEnv Source #

The NamingEnv is used by the renamer to determine what identifiers refer to.

Constructors

NamingEnv (Map Namespace (Map PName Names)) 

Instances

Instances details
Monoid NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

Semigroup NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

Generic NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

Associated Types

type Rep NamingEnv :: Type -> Type #

Show NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

BindsNames NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.Binds

Methods

namingEnv :: NamingEnv -> BuildNamingEnv

PP NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

Methods

ppPrec :: Int -> NamingEnv -> Doc Source #

NFData NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

Methods

rnf :: NamingEnv -> () #

type Rep NamingEnv Source # 
Instance details

Defined in Cryptol.ModuleSystem.NamingEnv

type Rep NamingEnv = D1 ('MetaData "NamingEnv" "Cryptol.ModuleSystem.NamingEnv" "cryptol-3.0.0-CoAB0rhRDtyEduZtDlyHHM" 'True) (C1 ('MetaCons "NamingEnv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Namespace (Map PName Names)))))

zipByTextName :: NamingEnv -> NamingEnv -> Map Name Name Source #

This "joins" two naming environments by matching the text name. The result maps the unique names from the first environment with the matching names in the second. This is used to compute the naming for an instantiated functor: * if the left environment has the defined names of the functor, and * the right one has the defined names of the instantiation, then * the result maps functor names to instance names.

without :: NamingEnv -> NamingEnv -> NamingEnv Source #

Keep only the bindings in the 1st environment that are *NOT* in the second.

namingEnvNames :: NamingEnv -> Set Name Source #

All names mentioned in the environment

namingEnvFromNames :: Set Name -> NamingEnv Source #

Get a unqualified naming environment for the given names

namespaceMap :: Namespace -> NamingEnv -> Map PName Names Source #

Get the names in a given namespace

lookupNS :: Namespace -> PName -> NamingEnv -> Maybe Names Source #

Resolve a name in the given namespace.

lookupListNS :: Namespace -> PName -> NamingEnv -> [Name] Source #

Resolve a name in the given namespace.

singletonNS :: Namespace -> PName -> Name -> NamingEnv Source #

Singleton renaming environment for the given namespace.

toPrimMap :: NamingEnv -> PrimMap Source #

Generate a mapping from PrimIdent to Name for a given naming environment.

toNameDisp :: NamingEnv -> NameDisp Source #

Generate a display format based on a naming environment.

visibleNames :: NamingEnv -> Map Namespace (Set Name) Source #

Produce sets of visible names for types and declarations.

NOTE: if entries in the NamingEnv would have produced a name clash, they will be omitted from the resulting sets.

qualify :: ModName -> NamingEnv -> NamingEnv Source #

Qualify all symbols in a NamingEnv with the given prefix.

findAmbig :: NamingEnv -> [[Name]] Source #

Find the ambiguous entries in an environmet. A name is ambiguous if it might refer to multiple entities.

findShadowing :: NamingEnv -> NamingEnv -> [(PName, Name, [Name])] Source #

Get the subset of the first environment that shadows something in the second one.

forceUnambig :: NamingEnv -> NamingEnv Source #

Do an arbitrary choice for ambiguous names. We do this to continue checking afetr we've reported an ambiguity error.

shadowing :: NamingEnv -> NamingEnv -> NamingEnv Source #

Like mappend, but when merging, prefer values on the lhs.

modParamsNamingEnv :: ModParamNames -> NamingEnv Source #

Compute an unqualified naming environment, containing the various module parameters.

unqualifiedEnv :: IfaceDecls -> NamingEnv Source #

Generate a naming environment from a declaration interface, where none of the names are qualified.

interpImportEnv Source #

Arguments

:: ImportG name

The import declarations

-> NamingEnv

All public things coming in

-> NamingEnv 

Adapt the things exported by something to the specific import/open.