Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Cryptol.ModuleSystem.Interface
Description
Synopsis
- type Iface = IfaceG ModName
- data IfaceG name = Iface {
- ifNames :: IfaceNames name
- ifParams :: FunctorParams
- ifDefines :: IfaceDecls
- data IfaceDecls = IfaceDecls {
- ifTySyns :: Map Name TySyn
- ifNominalTypes :: Map Name NominalType
- ifDecls :: Map Name IfaceDecl
- ifModules :: !(Map Name (IfaceNames Name))
- ifSignatures :: !(Map Name ModParamNames)
- ifFunctors :: !(Map Name (IfaceG Name))
- data IfaceDecl = IfaceDecl {
- ifDeclName :: !Name
- ifDeclSig :: Schema
- ifDeclIsPrim :: !Bool
- ifDeclPragmas :: [Pragma]
- ifDeclInfix :: Bool
- ifDeclFixity :: Maybe Fixity
- ifDeclDoc :: Maybe Text
- data IfaceNames name = IfaceNames {}
- ifModName :: IfaceG name -> name
- emptyIface :: ModName -> Iface
- ifacePrimMap :: Iface -> PrimMap
- ifaceForgetName :: IfaceG name -> IfaceG ()
- ifaceIsFunctor :: IfaceG name -> Bool
- filterIfaceDecls :: (Name -> Bool) -> IfaceDecls -> IfaceDecls
- ifaceDeclsNames :: IfaceDecls -> Set Name
- ifaceOrigNameMap :: IfaceG name -> Map Namespace (Map OrigName Name)
- ifaceNameToModuleMap :: Iface -> Map Name (ImpName Name)
Documentation
The interface repersenting a typecheck top-level module.
Constructors
Iface | |
Fields
|
Instances
Functor IfaceG Source # | |
Generic (IfaceG name) Source # | |
Show name => Show (IfaceG name) Source # | |
NFData name => NFData (IfaceG name) Source # | |
Defined in Cryptol.ModuleSystem.Interface | |
type Rep (IfaceG name) Source # | |
Defined in Cryptol.ModuleSystem.Interface type Rep (IfaceG name) = D1 ('MetaData "IfaceG" "Cryptol.ModuleSystem.Interface" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "Iface" 'PrefixI 'True) (S1 ('MetaSel ('Just "ifNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IfaceNames name)) :*: (S1 ('MetaSel ('Just "ifParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunctorParams) :*: S1 ('MetaSel ('Just "ifDefines") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IfaceDecls)))) |
data IfaceDecls Source #
Declarations in a module. Note that this includes things from nested
modules, but not things from nested functors, which are in ifFunctors
.
Constructors
IfaceDecls | |
Fields
|
Instances
Constructors
IfaceDecl | |
Fields
|
Instances
data IfaceNames name Source #
Information about the names in a module.
Constructors
IfaceNames | |
Instances
emptyIface :: ModName -> Iface Source #
ifacePrimMap :: Iface -> PrimMap Source #
Produce a PrimMap from an interface.
NOTE: the map will expose both public and private names. NOTE: this is a bit misnamed, as it is used to resolve known names that Cryptol introduces (e.g., during type checking). These names need not be primitives. A better way to do this in the future might be to use original names instead (see #1522).
ifaceForgetName :: IfaceG name -> IfaceG () Source #
Remove the name of a module. This is useful for dealing with collections of modules, as in `Map (ImpName Name) (IfaceG ())`.
ifaceIsFunctor :: IfaceG name -> Bool Source #
Is this interface for a functor.
filterIfaceDecls :: (Name -> Bool) -> IfaceDecls -> IfaceDecls Source #
ifaceDeclsNames :: IfaceDecls -> Set Name Source #