Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data NamingEnv = NamingEnv {}
- lookupValNames :: PName -> NamingEnv -> [Name]
- lookupTypeNames :: PName -> NamingEnv -> [Name]
- merge :: [Name] -> [Name] -> [Name]
- toPrimMap :: NamingEnv -> PrimMap
- toNameDisp :: NamingEnv -> NameDisp
- visibleNames :: NamingEnv -> (Set Name, Set Name)
- qualify :: ModName -> NamingEnv -> NamingEnv
- filterNames :: (PName -> Bool) -> NamingEnv -> NamingEnv
- singletonT :: PName -> Name -> NamingEnv
- singletonE :: PName -> Name -> NamingEnv
- shadowing :: NamingEnv -> NamingEnv -> NamingEnv
- travNamingEnv :: Applicative f => (Name -> f Name) -> NamingEnv -> f NamingEnv
- data InModule a = InModule !ModName a
- namingEnv' :: BindsNames a => a -> Supply -> (NamingEnv, Supply)
- newTop :: FreshM m => ModName -> PName -> Maybe Fixity -> Range -> m Name
- newLocal :: FreshM m => PName -> Range -> m Name
- newtype BuildNamingEnv = BuildNamingEnv {}
- class BindsNames a where
- interpImport :: Import -> IfaceDecls -> NamingEnv
- unqualifiedEnv :: IfaceDecls -> NamingEnv
- modParamsNamingEnv :: IfaceParams -> NamingEnv
- data ImportIface = ImportIface Import Iface
Documentation
Instances
Show NamingEnv Source # | |
Generic NamingEnv Source # | |
Semigroup NamingEnv Source # | |
Monoid NamingEnv Source # | |
NFData NamingEnv Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv | |
BindsNames NamingEnv Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv namingEnv :: NamingEnv -> BuildNamingEnv Source # | |
type Rep NamingEnv Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv type Rep NamingEnv = D1 (MetaData "NamingEnv" "Cryptol.ModuleSystem.NamingEnv" "cryptol-2.6.0-24w5HMDd2znGLrodkM4xJM" False) (C1 (MetaCons "NamingEnv" PrefixI True) (S1 (MetaSel (Just "neExprs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map PName [Name])) :*: (S1 (MetaSel (Just "neTypes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map PName [Name])) :*: S1 (MetaSel (Just "neFixity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map Name Fixity))))) |
lookupValNames :: PName -> NamingEnv -> [Name] Source #
Return a list of value-level names to which this parsed name may refer.
lookupTypeNames :: PName -> NamingEnv -> [Name] Source #
Return a list of type-level names to which this parsed name may refer.
merge :: [Name] -> [Name] -> [Name] Source #
Merge two name maps, collapsing cases where the entries are the same, and producing conflicts otherwise.
toNameDisp :: NamingEnv -> NameDisp Source #
Generate a display format based on a naming environment.
visibleNames :: NamingEnv -> (Set Name, 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.
shadowing :: NamingEnv -> NamingEnv -> NamingEnv Source #
Like mappend, but when merging, prefer values on the lhs.
travNamingEnv :: Applicative f => (Name -> f Name) -> NamingEnv -> f NamingEnv Source #
Instances
namingEnv' :: BindsNames a => a -> Supply -> (NamingEnv, Supply) Source #
Generate a NamingEnv
using an explicit supply.
newtype BuildNamingEnv Source #
Instances
Semigroup BuildNamingEnv Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv (<>) :: BuildNamingEnv -> BuildNamingEnv -> BuildNamingEnv # sconcat :: NonEmpty BuildNamingEnv -> BuildNamingEnv # stimes :: Integral b => b -> BuildNamingEnv -> BuildNamingEnv # | |
Monoid BuildNamingEnv Source # | |
Defined in Cryptol.ModuleSystem.NamingEnv mappend :: BuildNamingEnv -> BuildNamingEnv -> BuildNamingEnv # mconcat :: [BuildNamingEnv] -> BuildNamingEnv # |
class BindsNames a where Source #
Things that define exported names.
namingEnv :: a -> BuildNamingEnv Source #
Instances
interpImport :: Import -> IfaceDecls -> NamingEnv Source #
Interpret an import in the context of an interface, to produce a name
environment for the renamer, and a NameDisp
for pretty-printing.
unqualifiedEnv :: IfaceDecls -> NamingEnv Source #
Generate a naming environment from a declaration interface, where none of the names are qualified.
modParamsNamingEnv :: IfaceParams -> NamingEnv Source #
Compute an unqualified naming environment, containing the various module parameters.
data ImportIface Source #
Instances
BindsNames ImportIface Source # | Produce a naming environment from an interface file, that contains a mapping only from unqualified names to qualified ones. |
Defined in Cryptol.ModuleSystem.NamingEnv |