Copyright | (c) 2015-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Cryptol.ModuleSystem.Name
Description
Synopsis
- data Name
- data NameInfo
- data NameSource
- nameUnique :: Name -> Int
- nameIdent :: Name -> Ident
- mapNameIdent :: (Ident -> Ident) -> Name -> Name
- nameInfo :: Name -> NameInfo
- nameLoc :: Name -> Range
- nameFixity :: Name -> Maybe Fixity
- nameNamespace :: Name -> Namespace
- nameToDefPName :: Name -> PName
- asPrim :: Name -> Maybe PrimIdent
- asOrigName :: Name -> Maybe OrigName
- nameModPath :: Name -> ModPath
- nameModPathMaybe :: Name -> Maybe ModPath
- nameTopModule :: Name -> ModName
- nameTopModuleMaybe :: Name -> Maybe ModName
- ppLocName :: Name -> Doc
- data Namespace
- data ModPath
- cmpNameDisplay :: NameDisp -> Name -> Name -> Ordering
- mkDeclared :: Namespace -> ModPath -> NameSource -> Ident -> Maybe Fixity -> Range -> Supply -> (Name, Supply)
- mkLocal :: Namespace -> Ident -> Range -> Supply -> (Name, Supply)
- asLocal :: Namespace -> Name -> Name
- mkModParam :: ModPath -> Ident -> Range -> Name -> Supply -> (Name, Supply)
- class Monad m => FreshM m where
- liftSupply :: (Supply -> (a, Supply)) -> m a
- nextUniqueM :: FreshM m => m Int
- data SupplyT m a
- runSupplyT :: Monad m => Supply -> SupplyT m a -> m (a, Supply)
- runSupply :: Supply -> (forall m. FreshM m => m a) -> (a, Supply)
- data Supply
- emptySupply :: Supply
- nextUnique :: Supply -> (Int, Supply)
- freshNameFor :: ModPath -> Name -> Supply -> (Name, Supply)
- data PrimMap = PrimMap {}
- lookupPrimDecl :: PrimIdent -> PrimMap -> Name
- lookupPrimType :: PrimIdent -> PrimMap -> Name
Names
Instances
Constructors
GlobalName NameSource OrigName | |
LocalName Namespace Ident |
Instances
Generic NameInfo Source # | |
Show NameInfo Source # | |
NFData NameInfo Source # | |
Defined in Cryptol.ModuleSystem.Name | |
type Rep NameInfo Source # | |
Defined in Cryptol.ModuleSystem.Name type Rep NameInfo = D1 ('MetaData "NameInfo" "Cryptol.ModuleSystem.Name" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "GlobalName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NameSource) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OrigName)) :+: C1 ('MetaCons "LocalName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Namespace) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) |
data NameSource Source #
Constructors
SystemName | |
UserName |
Instances
Generic NameSource Source # | |
Defined in Cryptol.ModuleSystem.Name Associated Types type Rep NameSource :: Type -> Type # | |
Show NameSource Source # | |
Defined in Cryptol.ModuleSystem.Name Methods showsPrec :: Int -> NameSource -> ShowS # show :: NameSource -> String # showList :: [NameSource] -> ShowS # | |
NFData NameSource Source # | |
Defined in Cryptol.ModuleSystem.Name Methods rnf :: NameSource -> () # | |
Eq NameSource Source # | |
Defined in Cryptol.ModuleSystem.Name | |
type Rep NameSource Source # | |
nameUnique :: Name -> Int Source #
nameNamespace :: Name -> Namespace Source #
nameToDefPName :: Name -> PName Source #
asPrim :: Name -> Maybe PrimIdent Source #
Primtiives must be in a top level module, at least for now.
nameModPath :: Name -> ModPath Source #
Get the module path for the given name. The name should be a top-level name.
nameTopModule :: Name -> ModName Source #
Get the name of the top-level module that introduced this name. Works only for top-level names (i.e., that have original names)
nameTopModuleMaybe :: Name -> Maybe ModName Source #
Get the name of the top-level module that introduced this name.
Namespaces for names
Constructors
NSValue | |
NSConstructor | This is for enum and newtype constructors |
NSType | |
NSModule |
Instances
Identifies a possibly nested module
Instances
Generic ModPath Source # | |
Show ModPath Source # | |
PP ModPath Source # | |
NFData ModPath Source # | |
Defined in Cryptol.Utils.Ident | |
Eq ModPath Source # | |
Ord ModPath Source # | |
type Rep ModPath Source # | |
Defined in Cryptol.Utils.Ident type Rep ModPath = D1 ('MetaData "ModPath" "Cryptol.Utils.Ident" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "TopModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModName)) :+: C1 ('MetaCons "Nested" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModPath) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) |
cmpNameDisplay :: NameDisp -> Name -> Name -> Ordering Source #
Compare two names by the way they would be displayed. This is used to order names nicely when showing what's in scope
Creation
mkDeclared :: Namespace -> ModPath -> NameSource -> Ident -> Maybe Fixity -> Range -> Supply -> (Name, Supply) Source #
Make a new name for a declaration.
mkLocal :: Namespace -> Ident -> Range -> Supply -> (Name, Supply) Source #
Make a new parameter name.
asLocal :: Namespace -> Name -> Name Source #
Make a local name derived from the given name. This is a bit questionable, but it is used by the translation to SAW Core
Unique Supply
class Monad m => FreshM m where Source #
Methods
liftSupply :: (Supply -> (a, Supply)) -> m a Source #
Instances
FreshM RenameM Source # | |
Defined in Cryptol.ModuleSystem.Renamer.Monad | |
FreshM REPL Source # | |
Defined in Cryptol.REPL.Monad | |
FreshM InferM Source # | |
Defined in Cryptol.TypeCheck.Monad | |
Monad m => FreshM (ModuleT m) Source # | |
Defined in Cryptol.ModuleSystem.Monad | |
Monad m => FreshM (SupplyT m) Source # | |
Defined in Cryptol.ModuleSystem.Name | |
FreshM m => FreshM (ExceptionT i m) Source # | |
Defined in Cryptol.ModuleSystem.Name Methods liftSupply :: (Supply -> (a, Supply)) -> ExceptionT i m a Source # | |
FreshM m => FreshM (ReaderT i m) Source # | |
Defined in Cryptol.ModuleSystem.Name | |
FreshM m => FreshM (StateT i m) Source # | |
Defined in Cryptol.ModuleSystem.Name | |
(Monoid i, FreshM m) => FreshM (WriterT i m) Source # | |
Defined in Cryptol.ModuleSystem.Name |
nextUniqueM :: FreshM m => m Int Source #
Retrieve the next unique from the supply.
A monad for easing the use of the supply.
Instances
MonadT SupplyT Source # | |
Defined in Cryptol.ModuleSystem.Name | |
Monad m => Applicative (SupplyT m) Source # | |
Defined in Cryptol.ModuleSystem.Name | |
Monad m => Functor (SupplyT m) Source # | |
Monad m => Monad (SupplyT m) Source # | |
Monad m => FreshM (SupplyT m) Source # | |
Defined in Cryptol.ModuleSystem.Name | |
BaseM m n => BaseM (SupplyT m) n Source # | |
Defined in Cryptol.ModuleSystem.Name | |
RunM m (a, Supply) r => RunM (SupplyT m) a (Supply -> r) Source # | |
Defined in Cryptol.ModuleSystem.Name |
emptySupply :: Supply Source #
This should only be used once at library initialization, and threaded through the rest of the session. The supply is started at 0x1000 to leave us plenty of room for names that the compiler needs to know about (wired-in constants).
freshNameFor :: ModPath -> Name -> Supply -> (Name, Supply) Source #
This is used when instantiating functors
PrimMap
A mapping from an identifier defined in some module to its real name.
Instances
Semigroup PrimMap Source # | |
Generic PrimMap Source # | |
Show PrimMap Source # | |
NFData PrimMap Source # | |
Defined in Cryptol.ModuleSystem.Name | |
type Rep PrimMap Source # | |
Defined in Cryptol.ModuleSystem.Name type Rep PrimMap = D1 ('MetaData "PrimMap" "Cryptol.ModuleSystem.Name" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "PrimMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "primDecls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PrimIdent Name)) :*: S1 ('MetaSel ('Just "primTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PrimIdent Name)))) |