Safe Haskell | None |
---|---|
Language | Haskell98 |
This module contains the functions that convert from descriptions of
symbols, names and types (over freshly parsed bare Strings),
to representations connected to GHC vars, names, and types.
The actual representations of bare and real (refinement) types are all
in RefType
-- they are different instances of RType
- data GhcSpec = SP {
- gsTySigs :: ![(Var, LocSpecType)]
- gsAsmSigs :: ![(Var, LocSpecType)]
- gsInSigs :: ![(Var, LocSpecType)]
- gsCtors :: ![(Var, LocSpecType)]
- gsLits :: ![(Symbol, LocSpecType)]
- gsMeas :: ![(Symbol, LocSpecType)]
- gsInvariants :: ![(Maybe Var, LocSpecType)]
- gsIaliases :: ![(LocSpecType, LocSpecType)]
- gsDconsP :: ![Located DataCon]
- gsTconsP :: ![(TyCon, TyConP)]
- gsFreeSyms :: ![(Symbol, Var)]
- gsTcEmbeds :: TCEmb TyCon
- gsQualifiers :: ![Qualifier]
- gsADTs :: ![DataDecl]
- gsTgtVars :: ![Var]
- gsDecr :: ![(Var, [Int])]
- gsTexprs :: ![(Var, [Located Expr])]
- gsNewTypes :: ![(TyCon, LocSpecType)]
- gsLvars :: !(HashSet Var)
- gsLazy :: !(HashSet Var)
- gsAutosize :: !(HashSet TyCon)
- gsAutoInst :: !(HashMap Var (Maybe Int))
- gsConfig :: !Config
- gsExports :: !NameSet
- gsMeasures :: [Measure SpecType DataCon]
- gsTyconEnv :: HashMap TyCon RTyCon
- gsDicts :: DEnv Var SpecType
- gsAxioms :: [AxiomEq]
- gsReflects :: [Var]
- gsLogicMap :: LogicMap
- gsProofType :: Maybe Type
- gsRTAliases :: !RTEnv
- makeGhcSpec :: Config -> FilePath -> ModName -> [CoreBind] -> [TyCon] -> Maybe [ClsInst] -> [Var] -> [Var] -> NameSet -> HscEnv -> Either Error LogicMap -> [(ModName, BareSpec)] -> IO GhcSpec
- loadLiftedSpec :: Config -> FilePath -> IO BareSpec
- saveLiftedSpec :: FilePath -> ModName -> BareSpec -> IO ()
Documentation
The following is the overall type for specifications obtained from parsing the target source and dependent libraries
SP | |
|
makeGhcSpec :: Config -> FilePath -> ModName -> [CoreBind] -> [TyCon] -> Maybe [ClsInst] -> [Var] -> [Var] -> NameSet -> HscEnv -> Either Error LogicMap -> [(ModName, BareSpec)] -> IO GhcSpec Source #