Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Cryptol.ModuleSystem.Binds
Synopsis
- class BindsNames a
- data TopDef
- data Mod a = Mod {}
- data ModKind
- modNested :: Mod a -> Set Name
- modBuilder :: ModBuilder a -> Supply -> ((a, [RenamerError]), Supply)
- topModuleDefs :: Module PName -> ModBuilder TopDef
- topDeclsDefs :: ModPath -> [TopDecl PName] -> ModBuilder (Mod ())
- newModParam :: FreshM m => ModPath -> Ident -> Range -> Name -> m Name
- newFunctorInst :: FreshM m => ModPath -> Name -> m Name
- data InModule a = InModule (Maybe ModPath) a
- ifaceToMod :: IfaceG name -> Mod ()
- ifaceSigToMod :: ModParamNames -> Mod ()
- modToMap :: ImpName Name -> Mod () -> Map (ImpName Name) (Mod ()) -> Map (ImpName Name) (Mod ())
- defsOf :: BindsNames a => a -> Supply -> (NamingEnv, Supply)
Documentation
class BindsNames a Source #
Things that define exported names.
Minimal complete definition
namingEnv
Instances
Things defined by a module
Constructors
Mod | |
Fields
|
Constructors
AFunctor | |
ASignature | |
AModule |
Instances
Generic ModKind Source # | |
Show ModKind Source # | |
PP ModKind Source # | |
NFData ModKind Source # | |
Defined in Cryptol.ModuleSystem.Renamer.Error | |
Eq ModKind Source # | |
Ord ModKind Source # | |
Defined in Cryptol.ModuleSystem.Renamer.Error | |
type Rep ModKind Source # | |
Defined in Cryptol.ModuleSystem.Renamer.Error type Rep ModKind = D1 ('MetaData "ModKind" "Cryptol.ModuleSystem.Renamer.Error" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "AFunctor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ASignature" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AModule" 'PrefixI 'False) (U1 :: Type -> Type))) |
modBuilder :: ModBuilder a -> Supply -> ((a, [RenamerError]), Supply) Source #
newModParam :: FreshM m => ModPath -> Ident -> Range -> Name -> m Name Source #
Given a name in a signature, make a name for the parameter corresponding to the signature.
newFunctorInst :: FreshM m => ModPath -> Name -> m Name Source #
Given a name in a functor, make a fresh name for the corresponding thing in the instantiation.
The DepName
should be the instantiation not the functor.
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
ifaceToMod :: IfaceG name -> Mod () Source #
Make a Mod
from the public declarations in an interface.
This is used to handle imports.
ifaceSigToMod :: ModParamNames -> Mod () Source #