Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type ClsInst = ClsInst
- mkTarget :: TargetId -> Bool -> Maybe (StringBuffer, UTCTime) -> Target
- withStyle :: DynFlags -> PprStyle -> SDoc -> Doc
- type GmLogAction = WarnReason -> DynFlags -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- setLogAction :: DynFlags -> GmLogAction -> DynFlags
- getSrcSpan :: SrcSpan -> Maybe (Int, Int, Int, Int)
- getSrcFile :: SrcSpan -> Maybe String
- withInteractiveContext :: GhcMonad m => m a -> m a
- ghcCmdOptions :: [String]
- toStringBuffer :: GhcMonad m => [String] -> m StringBuffer
- showSeverityCaption :: Severity -> String
- setCabalPkg :: DynFlags -> DynFlags
- setHideAllPackages :: DynFlags -> DynFlags
- setDeferTypeErrors :: DynFlags -> DynFlags
- setDeferTypedHoles :: DynFlags -> DynFlags
- setWarnTypedHoles :: DynFlags -> DynFlags
- setDumpSplices :: DynFlags -> DynFlags
- setNoMaxRelevantBindings :: DynFlags -> DynFlags
- isDumpSplices :: DynFlags -> Bool
- filterOutChildren :: (a -> TyThing) -> [a] -> [a]
- infoThing :: GhcMonad m => (FilePath -> FilePath) -> Expression -> m SDoc
- pprInfo :: (FilePath -> FilePath) -> Bool -> (TyThing, Fixity, [ClsInst], [FamInst]) -> SDoc
- class HasType a where
- errorMsgSpan :: ErrMsg -> SrcSpan
- setErrorMsgSpan :: ErrMsg -> SrcSpan -> ErrMsg
- typeForUser :: Type -> SDoc
- nameForUser :: Name -> SDoc
- occNameForUser :: OccName -> SDoc
- deSugar :: TypecheckedModule -> LHsExpr Id -> HscEnv -> IO (Maybe CoreExpr)
- showDocWith :: DynFlags -> Mode -> Doc -> String
- data GapThing
- fromTyThing :: TyThing -> GapThing
- fileModSummary :: GhcMonad m => FilePath -> m ModSummary
- type WarnFlags = IntSet
- emptyWarnFlags :: WarnFlags
- type GLMatch = LMatch RdrName (LHsExpr RdrName)
- type GLMatchI = LMatch Id (LHsExpr Id)
- getClass :: [LInstDecl Name] -> Maybe (Name, SrcSpan)
- occName :: HasOccName name => name -> OccName
- listVisibleModuleNames :: DynFlags -> [ModuleName]
- listVisibleModules :: DynFlags -> [Module]
- lookupModulePackageInAllPackages :: DynFlags -> ModuleName -> [String]
- isSynTyCon :: TyCon -> Bool
- parseModuleHeader :: String -> DynFlags -> FilePath -> Either ErrorMessages (WarningMessages, Located (HsModule RdrName))
- mkErrStyle' :: DynFlags -> PrintUnqualified -> PprStyle
- everythingStagedWithContext :: Stage -> s -> (r -> r -> r) -> r -> GenericQ (s -> (r, s)) -> GenericQ r
Documentation
type GmLogAction = WarnReason -> DynFlags -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO () Source #
setLogAction :: DynFlags -> GmLogAction -> DynFlags Source #
withInteractiveContext :: GhcMonad m => m a -> m a Source #
ghcCmdOptions :: [String] Source #
toStringBuffer :: GhcMonad m => [String] -> m StringBuffer Source #
showSeverityCaption :: Severity -> String Source #
setCabalPkg :: DynFlags -> DynFlags Source #
setWarnTypedHoles :: DynFlags -> DynFlags Source #
setDumpSplices :: DynFlags -> DynFlags Source #
setNoMaxRelevantBindings :: DynFlags -> DynFlags Source #
Set DynFlags
equivalent to "-fno-max-relevant-bindings".
isDumpSplices :: DynFlags -> Bool Source #
filterOutChildren :: (a -> TyThing) -> [a] -> [a] Source #
pprInfo :: (FilePath -> FilePath) -> Bool -> (TyThing, Fixity, [ClsInst], [FamInst]) -> SDoc Source #
errorMsgSpan :: ErrMsg -> SrcSpan Source #
typeForUser :: Type -> SDoc Source #
nameForUser :: Name -> SDoc Source #
occNameForUser :: OccName -> SDoc Source #
fromTyThing :: TyThing -> GapThing Source #
fileModSummary :: GhcMonad m => FilePath -> m ModSummary Source #
occName :: HasOccName name => name -> OccName #
listVisibleModuleNames :: DynFlags -> [ModuleName] #
listVisibleModules :: DynFlags -> [Module] Source #
lookupModulePackageInAllPackages :: DynFlags -> ModuleName -> [String] Source #
isSynTyCon :: TyCon -> Bool Source #
:: String | Haskell module source text (full Unicode is supported) |
-> DynFlags | |
-> FilePath | the filename (for source locations) |
-> Either ErrorMessages (WarningMessages, Located (HsModule RdrName)) |
mkErrStyle' :: DynFlags -> PrintUnqualified -> PprStyle Source #