Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- module Liquid.GHC.API.StableModule
- data ApiComment
- apiComments :: ParsedModule -> [Located ApiComment]
- apiCommentsParsedSource :: Located HsModule -> [Located ApiComment]
- dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type)
- desugarModuleIO :: HscEnv -> ModSummary -> TypecheckedModuleLH -> IO ModGuts
- fsToUnitId :: FastString -> UnitId
- getDependenciesModuleNames :: Dependencies -> [ModuleNameWithIsBoot]
- isPatErrorAlt :: CoreAlt -> Bool
- lookupModSummary :: HscEnv -> ModuleName -> Maybe ModSummary
- modInfoLookupNameIO :: HscEnv -> ModuleInfoLH -> Name -> IO (Maybe TyThing)
- moduleInfoTc :: HscEnv -> ModSummary -> TcGblEnv -> IO ModuleInfoLH
- moduleUnitId :: Module -> UnitId
- parseModuleIO :: HscEnv -> ModSummary -> IO ParsedModule
- qualifiedNameFS :: Name -> FastString
- relevantModules :: ModGuts -> Set Module
- renderWithStyle :: DynFlags -> SDoc -> PprStyle -> String
- showPprQualified :: Outputable a => a -> String
- showSDocQualified :: SDoc -> String
- thisPackage :: DynFlags -> UnitId
- tyConRealArity :: TyCon -> Int
- typecheckModuleIO :: HscEnv -> ParsedModule -> IO TypecheckedModuleLH
Documentation
module Liquid.GHC.API.StableModule
data ApiComment Source #
Abstraction of EpaComment
.
Instances
Show ApiComment Source # | |
Defined in Liquid.GHC.API.Extra showsPrec :: Int -> ApiComment -> ShowS # show :: ApiComment -> String # showList :: [ApiComment] -> ShowS # | |
Eq ApiComment Source # | |
Defined in Liquid.GHC.API.Extra (==) :: ApiComment -> ApiComment -> Bool # (/=) :: ApiComment -> ApiComment -> Bool # |
apiComments :: ParsedModule -> [Located ApiComment] Source #
Extract top-level comments from a module.
desugarModuleIO :: HscEnv -> ModSummary -> TypecheckedModuleLH -> IO ModGuts Source #
Desugar a typechecked module.
fsToUnitId :: FastString -> UnitId Source #
isPatErrorAlt :: CoreAlt -> Bool Source #
Tells if a case alternative calls to patError
lookupModSummary :: HscEnv -> ModuleName -> Maybe ModSummary Source #
moduleInfoTc :: HscEnv -> ModSummary -> TcGblEnv -> IO ModuleInfoLH Source #
moduleUnitId :: Module -> UnitId Source #
parseModuleIO :: HscEnv -> ModSummary -> IO ParsedModule Source #
qualifiedNameFS :: Name -> FastString Source #
relevantModules :: ModGuts -> Set Module Source #
The collection of dependencies and usages modules which are relevant for liquidHaskell
showPprQualified :: Outputable a => a -> String Source #
showSDocQualified :: SDoc -> String Source #
thisPackage :: DynFlags -> UnitId Source #
tyConRealArity :: TyCon -> Int Source #
typecheckModuleIO :: HscEnv -> ParsedModule -> IO TypecheckedModuleLH Source #