Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- pprintCBs :: [CoreBind] -> Doc
- extractSpecComments :: ParsedModule -> [(Maybe RealSrcLoc, String)]
- extractSpecQuotes' :: (a -> Module) -> (a -> [Annotation]) -> a -> [BPspec]
- makeLogicMap :: IO LogicMap
- classCons :: Maybe [ClsInst] -> [Id]
- derivedVars :: Config -> MGIModGuts -> [Var]
- importVars :: CoreProgram -> [Id]
- allImports :: [LImportDecl GhcRn] -> HashSet Symbol
- qualifiedImports :: [LImportDecl GhcRn] -> QImports
- modSummaryHsFile :: ModSummary -> FilePath
- makeFamInstEnv :: [FamInst] -> ([TyCon], [(Symbol, DataCon)])
- parseSpecFile :: FilePath -> IO (ModName, BareSpec)
- clearSpec :: BareSpec -> BareSpec
- checkFilePragmas :: [Located String] -> IO ()
- keepRawTokenStream :: ModSummary -> ModSummary
- ignoreInline :: ParsedModule -> ParsedModule
- lookupTyThings :: HscEnv -> ModSummary -> TcGblEnv -> IO [(Name, Maybe TyThing)]
- availableTyCons :: HscEnv -> ModSummary -> TcGblEnv -> [AvailInfo] -> IO [TyCon]
- availableVars :: HscEnv -> ModSummary -> TcGblEnv -> [AvailInfo] -> IO [Var]
- updLiftedSpec :: BareSpec -> Maybe BareSpec -> BareSpec
Printer
predicates
Internal exports (provisional)
extractSpecComments :: ParsedModule -> [(Maybe RealSrcLoc, String)] Source #
Extract Specifications from GHC -------------------------------------------
extractSpecQuotes' :: (a -> Module) -> (a -> [Annotation]) -> a -> [BPspec] Source #
classCons :: Maybe [ClsInst] -> [Id] Source #
Extract Ids ---------------------------------------------------------------
derivedVars :: Config -> MGIModGuts -> [Var] Source #
importVars :: CoreProgram -> [Id] Source #
allImports :: [LImportDecl GhcRn] -> HashSet Symbol Source #
qualifiedImports :: [LImportDecl GhcRn] -> QImports Source #
parseSpecFile :: FilePath -> IO (ModName, BareSpec) Source #
Finding & Parsing Files ---------------------------------------------------
Parse a spec file by path.
On a parse error, we fail.
TODO, Andres: It would be better to fail more systematically, but currently we seem to have an option between throwing an error which will be reported badly, or printing the error ourselves.
lookupTyThings :: HscEnv -> ModSummary -> TcGblEnv -> IO [(Name, Maybe TyThing)] Source #
lookupTyThings
grabs all the Name
s and associated TyThing
known to GHC
for this module; we will use this to create our name-resolution environment
(see Resolve
)
availableTyCons :: HscEnv -> ModSummary -> TcGblEnv -> [AvailInfo] -> IO [TyCon] Source #
availableVars :: HscEnv -> ModSummary -> TcGblEnv -> [AvailInfo] -> IO [Var] Source #
updLiftedSpec :: BareSpec -> Maybe BareSpec -> BareSpec Source #
Per-Module Pipeline -------------------------------------------------------
Orphan instances
Show TargetInfo Source # | |
showsPrec :: Int -> TargetInfo -> ShowS # show :: TargetInfo -> String # showList :: [TargetInfo] -> ShowS # | |
PPrint TargetInfo Source # | |
pprintTidy :: Tidy -> TargetInfo -> Doc # pprintPrec :: Int -> Tidy -> TargetInfo -> Doc # | |
PPrint TargetSpec Source # | Pretty Printing ----------------------------------------------------------- |
pprintTidy :: Tidy -> TargetSpec -> Doc # pprintPrec :: Int -> Tidy -> TargetSpec -> Doc # | |
PPrint TargetVars Source # | |
pprintTidy :: Tidy -> TargetVars -> Doc # pprintPrec :: Int -> Tidy -> TargetVars -> Doc # | |
Result SourceError Source # | |