Safe Haskell | None |
---|---|
Language | Haskell2010 |
Attempt at hiding the GHC version differences we can.
Synopsis
- data HieFileResult = HieFileResult {}
- data HieFile = HieFile {}
- newtype NameCacheUpdater = NCU {
- updateNameCache :: forall c. (NameCache -> (NameCache, c)) -> IO c
- hieExportNames :: HieFile -> [(SrcSpan, Name)]
- mkHieFile :: ModSummary -> TcGblEnv -> RenamedSource -> ByteString -> Hsc HieFile
- mkHieFile' :: ModSummary -> [AvailInfo] -> HieASTs Type -> ByteString -> Hsc HieFile
- enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
- type RefMap = Map Identifier [(Span, IdentifierDetails Type)]
- writeHieFile :: FilePath -> HieFile -> IO ()
- readHieFile :: NameCacheUpdater -> FilePath -> IO HieFileResult
- supportsHieFiles :: Bool
- setHieDir :: FilePath -> DynFlags -> DynFlags
- dontWriteHieFiles :: DynFlags -> DynFlags
- hPutStringBuffer :: Handle -> StringBuffer -> IO ()
- addIncludePathsQuote :: FilePath -> DynFlags -> DynFlags
- getModuleHash :: ModIface -> Fingerprint
- getPackageName :: DynFlags -> InstalledUnitId -> Maybe PackageName
- setUpTypedHoles :: DynFlags -> DynFlags
- data ModLocation
- addBootSuffix :: FilePath -> FilePath
- pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> ModLocation
- pattern ExposePackage :: String -> PackageArg -> ModRenaming -> PackageFlag
- type HasSrcSpan = HasSrcSpan
- getLoc :: HasSrcSpan a => a -> SrcSpan
- upNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
- disableWarningsAsErrors :: DynFlags -> DynFlags
- data AvailInfo
- tcg_exports :: TcGblEnv -> [AvailInfo]
- module GHC.Hs.Extension
- module LinkerTypes
- parser :: String -> DynFlags -> FilePath -> (WarningMessages, Either ErrorMessages (Located (HsModule GhcPs)))
- obtainTermFromId :: GhcMonad m => Int -> Bool -> Id -> m Term
- obtainTermFromVal :: GhcMonad m => Int -> Bool -> Type -> a -> m Term
- getHistorySpan :: GhcMonad m => History -> m SrcSpan
- getGHCiMonad :: GhcMonad m => m Name
- setGHCiMonad :: GhcMonad m => String -> m ()
- moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set InstalledUnitId)
- isModuleTrusted :: GhcMonad m => Module -> m Bool
- lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
- findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
- showRichTokenStream :: [(Located Token, String)] -> String
- addSourceToTokens :: RealSrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)]
- getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
- getTokenStream :: GhcMonad m => Module -> m [Located Token]
- pprParenSymName :: NamedThing a => a -> SDoc
- dataConType :: DataCon -> Type
- getNameToInstancesIndex :: GhcMonad m => [Module] -> Maybe [Module] -> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst])))
- getGRE :: GhcMonad m => m GlobalRdrEnv
- findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
- lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing)
- isDictonaryId :: Id -> Bool
- modInfoModBreaks :: ModuleInfo -> ModBreaks
- modInfoSafe :: ModuleInfo -> SafeHaskellMode
- modInfoRdrEnv :: ModuleInfo -> Maybe GlobalRdrEnv
- modInfoIface :: ModuleInfo -> Maybe ModIface
- modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing)
- mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified)
- modInfoIsExportedName :: ModuleInfo -> Name -> Bool
- modInfoInstances :: ModuleInfo -> [ClsInst]
- modInfoExportsWithSelectors :: ModuleInfo -> [Name]
- modInfoExports :: ModuleInfo -> [Name]
- modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
- modInfoTyThings :: ModuleInfo -> [TyThing]
- getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo)
- getPrintUnqual :: GhcMonad m => m PrintUnqualified
- getInsts :: GhcMonad m => m ([ClsInst], [FamInst])
- getBindings :: GhcMonad m => m [TyThing]
- isLoaded :: GhcMonad m => ModuleName -> m Bool
- getModuleGraph :: GhcMonad m => m ModuleGraph
- compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
- compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
- loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
- desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule
- typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
- parseModule :: GhcMonad m => ModSummary -> m ParsedModule
- getModSummary :: GhcMonad m => ModuleName -> m ModSummary
- workingDirectoryChanged :: GhcMonad m => m ()
- guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
- removeTarget :: GhcMonad m => TargetId -> m ()
- addTarget :: GhcMonad m => Target -> m ()
- getTargets :: GhcMonad m => m [Target]
- setTargets :: GhcMonad m => [Target] -> m ()
- parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- getInteractiveDynFlags :: GhcMonad m => m DynFlags
- setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
- getProgramDynFlags :: GhcMonad m => m DynFlags
- setLogAction :: GhcMonad m => LogAction -> m ()
- setProgramDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId]
- setSessionDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId]
- initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
- withCleanupSession :: GhcMonad m => m a -> m a
- runGhcT :: ExceptionMonad m => Maybe FilePath -> GhcT m a -> m a
- runGhc :: Maybe FilePath -> Ghc a -> IO a
- defaultCleanupHandler :: ExceptionMonad m => DynFlags -> m a -> m a
- defaultErrorHandler :: ExceptionMonad m => FatalMessager -> FlushOut -> m a -> m a
- class ParsedMod m where
- parsedSource :: m -> ParsedSource
- class ParsedMod m => TypecheckedMod m where
- renamedSource :: m -> Maybe RenamedSource
- typecheckedSource :: m -> TypecheckedSource
- moduleInfo :: m -> ModuleInfo
- data ParsedModule = ParsedModule {}
- data TypecheckedModule = TypecheckedModule {}
- data DesugaredModule = DesugaredModule {}
- type ParsedSource = Located (HsModule GhcPs)
- type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString)
- type TypecheckedSource = LHsBinds GhcTc
- data CoreModule = CoreModule {
- cm_module :: !Module
- cm_types :: !TypeEnv
- cm_binds :: CoreProgram
- cm_safe :: SafeHaskellMode
- data ModuleInfo
- cyclicModuleErr :: [ModSummary] -> SDoc
- topSortModuleGraph :: Bool -> ModuleGraph -> Maybe ModuleName -> [SCC ModSummary]
- load :: GhcMonad m => LoadHowMuch -> m SuccessFlag
- depanal :: GhcMonad m => [ModuleName] -> Bool -> m ModuleGraph
- data LoadHowMuch
- reconstructType :: HscEnv -> Int -> Id -> IO (Maybe Type)
- moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
- showModule :: GhcMonad m => ModSummary -> m String
- dynCompileExpr :: GhcMonad m => String -> m Dynamic
- compileParsedExpr :: GhcMonad m => LHsExpr GhcPs -> m HValue
- compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue
- compileExprRemote :: GhcMonad m => String -> m ForeignHValue
- compileExpr :: GhcMonad m => String -> m HValue
- parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs)
- parseInstanceHead :: GhcMonad m => String -> m Type
- getInstancesForType :: GhcMonad m => Type -> m [ClsInst]
- typeKind :: GhcMonad m => Bool -> String -> m (Type, Kind)
- exprType :: GhcMonad m => TcRnExprMode -> String -> m Type
- getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString))
- isDecl :: DynFlags -> String -> Bool
- isImport :: DynFlags -> String -> Bool
- hasImport :: DynFlags -> String -> Bool
- isStmt :: DynFlags -> String -> Bool
- parseName :: GhcMonad m => String -> m [Name]
- getRdrNamesInScope :: GhcMonad m => m [RdrName]
- getNamesInScope :: GhcMonad m => m [Name]
- getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
- moduleIsInterpreted :: GhcMonad m => Module -> m Bool
- getContext :: GhcMonad m => m [InteractiveImport]
- setContext :: GhcMonad m => [InteractiveImport] -> m ()
- abandonAll :: GhcMonad m => m Bool
- abandon :: GhcMonad m => m Bool
- forward :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- back :: GhcMonad m => Int -> m ([Name], Int, SrcSpan, String)
- resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m ExecResult
- parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
- runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name]
- runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name]
- runDecls :: GhcMonad m => String -> m [Name]
- execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult
- execStmt :: GhcMonad m => String -> ExecOptions -> m ExecResult
- execOptions :: ExecOptions
- getHistoryModule :: History -> Module
- getResumeContext :: GhcMonad m => m [Resume]
- data GetDocsFailure
- runTcInteractive :: HscEnv -> TcRn a -> IO (Messages, Maybe a)
- data TcRnExprMode
- pprFamInst :: FamInst -> SDoc
- defaultWarnErrLogger :: WarnErrLogger
- printException :: GhcMonad m => SourceError -> m ()
- getSessionDynFlags :: GhcMonad m => m DynFlags
- class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) where
- getSession :: m HscEnv
- setSession :: HscEnv -> m ()
- data Ghc a
- data GhcT (m :: Type -> Type) a
- type WarnErrLogger = forall (m :: Type -> Type). GhcMonad m => Maybe SourceError -> m ()
- ms_mod_name :: ModSummary -> ModuleName
- mkModuleGraph :: [ModSummary] -> ModuleGraph
- emptyMG :: ModuleGraph
- mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
- mgModSummaries :: ModuleGraph -> [ModSummary]
- mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
- needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
- handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a
- data HscEnv
- data Target = Target {}
- data TargetId
- type ModIface = ModIface_ 'ModIfaceFinal
- data ModIface_ (phase :: ModIfacePhase) = ModIface {
- mi_module :: !Module
- mi_sig_of :: !(Maybe Module)
- mi_hsc_src :: !HscSource
- mi_deps :: Dependencies
- mi_usages :: [Usage]
- mi_exports :: ![IfaceExport]
- mi_used_th :: !Bool
- mi_fixities :: [(OccName, Fixity)]
- mi_warns :: Warnings
- mi_anns :: [IfaceAnnotation]
- mi_decls :: [IfaceDeclExts phase]
- mi_globals :: !(Maybe GlobalRdrEnv)
- mi_insts :: [IfaceClsInst]
- mi_fam_insts :: [IfaceFamInst]
- mi_rules :: [IfaceRule]
- mi_hpc :: !AnyHpcUsage
- mi_trust :: !IfaceTrustInfo
- mi_trust_pkg :: !Bool
- mi_complete_sigs :: [IfaceCompleteMatch]
- mi_doc_hdr :: Maybe HsDocString
- mi_decl_docs :: DeclDocMap
- mi_arg_docs :: ArgDocMap
- mi_final_exts :: !(IfaceBackendExts phase)
- data InteractiveImport
- data ModuleGraph
- data ModSummary = ModSummary {
- ms_mod :: Module
- ms_hsc_src :: HscSource
- ms_location :: ModLocation
- ms_hs_date :: UTCTime
- ms_obj_date :: Maybe UTCTime
- ms_iface_date :: Maybe UTCTime
- ms_hie_date :: Maybe UTCTime
- ms_srcimps :: [(Maybe FastString, Located ModuleName)]
- ms_textual_imps :: [(Maybe FastString, Located ModuleName)]
- ms_parsed_mod :: Maybe HsParsedModule
- ms_hspp_file :: FilePath
- ms_hspp_opts :: DynFlags
- ms_hspp_buf :: Maybe StringBuffer
- data HsModule pass = HsModule {
- hsmodName :: Maybe (Located ModuleName)
- hsmodExports :: Maybe (Located [LIE pass])
- hsmodImports :: [LImportDecl pass]
- hsmodDecls :: [LHsDecl pass]
- hsmodDeprecMessage :: Maybe (Located WarningTxt)
- hsmodHaddockModHeader :: Maybe LHsDocString
- lPatImplicits :: LPat GhcRn -> [(SrcSpan, [Name])]
- hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])]
- lStmtsImplicits :: forall (idR :: Pass) body. [LStmtLR GhcRn (GhcPass idR) (Located (body (GhcPass idR)))] -> [(SrcSpan, [Name])]
- hsDataFamInstBinders :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)])
- getPatSynBinds :: [(RecFlag, LHsBinds id)] -> [PatSynBind id id]
- hsPatSynSelectors :: forall (p :: Pass). HsValBinds (GhcPass p) -> [IdP (GhcPass p)]
- hsForeignDeclsBinders :: [LForeignDecl pass] -> [Located (IdP pass)]
- hsLTyClDeclBinders :: forall (p :: Pass). Located (TyClDecl (GhcPass p)) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)])
- hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name]
- hsGroupBinders :: HsGroup GhcRn -> [Name]
- collectPatsBinders :: forall (p :: Pass). [LPat (GhcPass p)] -> [IdP (GhcPass p)]
- collectPatBinders :: forall (p :: Pass). LPat (GhcPass p) -> [IdP (GhcPass p)]
- collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)]
- collectLStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. LStmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)]
- collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [StmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)]
- collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)]
- collectMethodBinders :: LHsBindsLR idL idR -> [Located (IdP idL)]
- collectHsBindListBinders :: forall (p :: Pass) idR. [LHsBindLR (GhcPass p) idR] -> [IdP (GhcPass p)]
- collectHsBindsBinders :: forall (p :: Pass) idR. LHsBindsLR (GhcPass p) idR -> [IdP (GhcPass p)]
- collectHsBindBinders :: (SrcSpanLess (LPat p) ~ Pat p, HasSrcSpan (LPat p)) => HsBindLR p idR -> [IdP p]
- collectHsValBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)]
- collectHsIdBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)]
- collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)]
- isBangedHsBind :: HsBind GhcTc -> Bool
- isUnliftedHsBind :: HsBind GhcTc -> Bool
- mkMatch :: forall (p :: Pass). HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> Located (HsLocalBinds (GhcPass p)) -> LMatch (GhcPass p) (LHsExpr (GhcPass p))
- mkPrefixFunRhs :: Located id -> HsMatchContext id
- mkSimpleGeneratedFunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs
- isInfixFunBind :: HsBindLR id1 id2 -> Bool
- mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat GhcPs -> HsPatSynDir GhcPs -> HsBind GhcPs
- mkVarBind :: forall (p :: Pass). IdP (GhcPass p) -> LHsExpr (GhcPass p) -> LHsBind (GhcPass p)
- mkHsVarBind :: SrcSpan -> RdrName -> LHsExpr GhcPs -> LHsBind GhcPs
- mkTopFunBind :: Origin -> Located Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn
- mkFunBind :: Origin -> Located RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs
- mkHsDictLet :: TcEvBinds -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsWrapPatCo :: forall (id :: Pass). TcCoercionN -> Pat (GhcPass id) -> Type -> Pat (GhcPass id)
- mkHsWrapPat :: forall (id :: Pass). HsWrapper -> Pat (GhcPass id) -> Type -> Pat (GhcPass id)
- mkLHsCmdWrap :: forall (p :: Pass). HsWrapper -> LHsCmd (GhcPass p) -> LHsCmd (GhcPass p)
- mkHsCmdWrap :: forall (p :: Pass). HsWrapper -> HsCmd (GhcPass p) -> HsCmd (GhcPass p)
- mkLHsWrapCo :: forall (id :: Pass). TcCoercionN -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- mkHsWrapCoR :: forall (id :: Pass). TcCoercionR -> HsExpr (GhcPass id) -> HsExpr (GhcPass id)
- mkHsWrapCo :: forall (id :: Pass). TcCoercionN -> HsExpr (GhcPass id) -> HsExpr (GhcPass id)
- mkHsWrap :: forall (id :: Pass). HsWrapper -> HsExpr (GhcPass id) -> HsExpr (GhcPass id)
- mkLHsWrap :: forall (id :: Pass). HsWrapper -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- typeToLHsType :: Type -> LHsType GhcPs
- mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs]
- mkHsSigEnv :: (LSig GhcRn -> Maybe ([Located Name], a)) -> [LSig GhcRn] -> NameEnv a
- mkLHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs
- mkLHsSigType :: LHsType GhcPs -> LHsSigType GhcPs
- chunkify :: [a] -> [[a]]
- mkChunkified :: ([a] -> a) -> [a] -> a
- mkBigLHsPatTup :: [LPat GhcRn] -> LPat GhcRn
- mkBigLHsVarPatTup :: [IdP GhcRn] -> LPat GhcRn
- mkBigLHsTup :: forall (id :: Pass). [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- mkBigLHsVarTup :: forall (id :: Pass). [IdP (GhcPass id)] -> LHsExpr (GhcPass id)
- missingTupArg :: HsTupArg GhcPs
- nlTuplePat :: [LPat GhcPs] -> Boxity -> LPat GhcPs
- mkLHsVarTuple :: forall (a :: Pass). [IdP (GhcPass a)] -> LHsExpr (GhcPass a)
- mkLHsTupleExpr :: forall (a :: Pass). [LHsExpr (GhcPass a)] -> LHsExpr (GhcPass a)
- nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p)
- nlHsTyConApp :: forall (p :: Pass). IdP (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p)
- nlHsParTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlHsTyVar :: forall (p :: Pass). IdP (GhcPass p) -> LHsType (GhcPass p)
- nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- nlList :: [LHsExpr GhcPs] -> LHsExpr GhcPs
- nlHsCase :: LHsExpr GhcPs -> [LMatch GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlHsIf :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsLam :: LMatch GhcPs (LHsExpr GhcPs) -> LHsExpr GhcPs
- nlHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs
- nlHsDo :: HsStmtContext Name -> [LStmt GhcPs (LHsExpr GhcPs)] -> LHsExpr GhcPs
- nlWildPatName :: LPat GhcRn
- nlWildPat :: LPat GhcPs
- nlWildConPat :: DataCon -> LPat GhcPs
- nlNullaryConPat :: forall (p :: Pass). IdP (GhcPass p) -> LPat (GhcPass p)
- nlConPatName :: Name -> [LPat GhcRn] -> LPat GhcRn
- nlConPat :: RdrName -> [LPat GhcPs] -> LPat GhcPs
- nlInfixConPat :: RdrName -> LPat GhcPs -> LPat GhcPs -> LPat GhcPs
- nlConVarPatName :: Name -> [Name] -> LPat GhcRn
- nlConVarPat :: RdrName -> [RdrName] -> LPat GhcPs
- nlHsVarApps :: forall (id :: Pass). IdP (GhcPass id) -> [IdP (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsApps :: forall (id :: Pass). IdP (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsSyntaxApps :: forall (id :: Pass). SyntaxExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlLitPat :: HsLit GhcPs -> LPat GhcPs
- nlVarPat :: forall (id :: Pass). IdP (GhcPass id) -> LPat (GhcPass id)
- nlHsIntLit :: forall (p :: Pass). Integer -> LHsExpr (GhcPass p)
- nlHsLit :: forall (p :: Pass). HsLit (GhcPass p) -> LHsExpr (GhcPass p)
- nlHsDataCon :: DataCon -> LHsExpr GhcTc
- nlHsVar :: forall (id :: Pass). IdP (GhcPass id) -> LHsExpr (GhcPass id)
- mkHsStringPrimLit :: forall (p :: Pass). FastString -> HsLit (GhcPass p)
- mkHsString :: forall (p :: Pass). String -> HsLit (GhcPass p)
- unqualQuasiQuote :: RdrName
- mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice GhcPs
- mkTypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs
- mkUntypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs
- mkHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs
- mkRecStmt :: forall (idL :: Pass) bodyR. [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR
- emptyRecStmtId :: StmtLR GhcTc GhcTc bodyR
- emptyRecStmtName :: StmtLR GhcRn GhcRn bodyR
- emptyRecStmt :: forall (idL :: Pass) bodyR. StmtLR (GhcPass idL) GhcPs bodyR
- unitRecStmtTc :: RecStmtTc
- mkTcBindStmt :: LPat GhcTc -> Located (bodyR GhcTc) -> StmtLR GhcTc GhcTc (Located (bodyR GhcTc))
- mkBindStmt :: forall (idL :: Pass) (idR :: Pass) bodyR. XBindStmt (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) ~ NoExtField => LPat (GhcPass idL) -> Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR)))
- mkBodyStmt :: forall bodyR (idL :: Pass). Located (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (Located (bodyR GhcPs))
- mkLastStmt :: forall bodyR (idR :: Pass) (idL :: Pass). Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR)))
- mkGroupByUsingStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkGroupUsingStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkTransformByStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkTransformStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- emptyTransStmt :: StmtLR GhcPs GhcPs (LHsExpr GhcPs)
- mkNPlusKPat :: Located RdrName -> Located (HsOverLit GhcPs) -> Pat GhcPs
- mkNPat :: Located (HsOverLit GhcPs) -> Maybe (SyntaxExpr GhcPs) -> Pat GhcPs
- mkHsCmdIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsCmd (GhcPass p) -> LHsCmd (GhcPass p) -> HsCmd (GhcPass p)
- mkHsIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> HsExpr (GhcPass p)
- mkHsComp :: HsStmtContext Name -> [ExprLStmt GhcPs] -> LHsExpr GhcPs -> HsExpr GhcPs
- mkHsDo :: HsStmtContext Name -> [ExprLStmt GhcPs] -> HsExpr GhcPs
- mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs
- mkHsFractional :: FractionalLit -> HsOverLit GhcPs
- mkHsIntegral :: IntegralLit -> HsOverLit GhcPs
- nlParPat :: forall (name :: Pass). LPat (GhcPass name) -> LPat (GhcPass name)
- mkParPat :: forall (name :: Pass). LPat (GhcPass name) -> LPat (GhcPass name)
- mkLHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- nlHsTyApps :: forall (id :: Pass). IdP (GhcPass id) -> [Type] -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id)
- nlHsTyApp :: forall (id :: Pass). IdP (GhcPass id) -> [Type] -> LHsExpr (GhcPass id)
- mkHsCaseAlt :: forall (p :: Pass) body. LPat (GhcPass p) -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p)))
- mkHsLams :: [TyVar] -> [EvVar] -> LHsExpr GhcTc -> LHsExpr GhcTc
- mkHsLam :: forall (p :: Pass). XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ NoExtField => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- mkHsAppTypes :: LHsExpr GhcRn -> [LHsWcType GhcRn] -> LHsExpr GhcRn
- mkHsAppType :: forall (id :: Pass). NoGhcTc (GhcPass id) ~ GhcRn => LHsExpr (GhcPass id) -> LHsWcType GhcRn -> LHsExpr (GhcPass id)
- mkHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- mkMatchGroup :: XMG name (Located (body name)) ~ NoExtField => Origin -> [LMatch name (Located (body name))] -> MatchGroup name (Located (body name))
- unguardedRHS :: forall body (p :: Pass). SrcSpan -> Located (body (GhcPass p)) -> [LGRHS (GhcPass p) (Located (body (GhcPass p)))]
- unguardedGRHSs :: forall body (p :: Pass). Located (body (GhcPass p)) -> GRHSs (GhcPass p) (Located (body (GhcPass p)))
- mkSimpleMatch :: forall (p :: Pass) body. HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p)))
- mkHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id)
- pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => HsStmtContext (IdP (GhcPass idL)) -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc
- pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable (NameOrRdrName (NameOrRdrName (IdP (GhcPass idR)))), Outputable body) => Match (GhcPass idR) body -> SDoc
- matchContextErrString :: Outputable id => HsMatchContext id -> SDoc
- pprStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc
- pprAStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc
- pprMatchContextNoun :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc
- pprMatchContext :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc
- matchSeparator :: HsMatchContext id -> SDoc
- isMonadCompContext :: HsStmtContext id -> Bool
- isMonadFailStmtContext :: HsStmtContext id -> Bool
- isComprehensionContext :: HsStmtContext id -> Bool
- isPatSynCtxt :: HsMatchContext id -> Bool
- pp_dotdot :: SDoc
- thTyBrackets :: SDoc -> SDoc
- thBrackets :: SDoc -> SDoc -> SDoc
- pprHsBracket :: forall (p :: Pass). OutputableBndrId p => HsBracket (GhcPass p) -> SDoc
- isTypedBracket :: HsBracket id -> Bool
- ppr_splice :: forall (p :: Pass). OutputableBndrId p => SDoc -> IdP (GhcPass p) -> LHsExpr (GhcPass p) -> SDoc -> SDoc
- ppr_quasi :: OutputableBndr p => p -> p -> FastString -> SDoc
- ppr_splice_decl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SDoc
- pprPendingSplice :: forall (p :: Pass). OutputableBndrId p => SplicePointName -> LHsExpr (GhcPass p) -> SDoc
- isTypedSplice :: HsSplice id -> Bool
- pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc
- pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc
- ppr_do_stmts :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => [LStmtLR (GhcPass idL) (GhcPass idR) body] -> SDoc
- pprDo :: forall (p :: Pass) body any. (OutputableBndrId p, Outputable body) => HsStmtContext any -> [LStmt (GhcPass p) body] -> SDoc
- pprBy :: Outputable body => Maybe body -> SDoc
- pprTransStmt :: Outputable body => Maybe body -> body -> TransForm -> SDoc
- pprTransformStmt :: forall (p :: Pass). OutputableBndrId p => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) -> Maybe (LHsExpr (GhcPass p)) -> SDoc
- pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> SDoc
- pprStmt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc
- pp_rhs :: Outputable body => HsMatchContext idL -> body -> SDoc
- pprGRHS :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHS (GhcPass idR) body -> SDoc
- pprGRHSs :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHSs (GhcPass idR) body -> SDoc
- pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc
- pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc
- hsLMatchPats :: forall (id :: Pass) body. LMatch (GhcPass id) body -> [LPat (GhcPass id)]
- matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity
- isSingletonMatchGroup :: [LMatch id body] -> Bool
- isEmptyMatchGroup :: MatchGroup id body -> Bool
- isInfixMatch :: Match id body -> Bool
- pprCmdArg :: forall (p :: Pass). OutputableBndrId p => HsCmdTop (GhcPass p) -> SDoc
- ppr_cmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc
- ppr_lcmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc
- isQuietHsCmd :: HsCmd id -> Bool
- pprCmd :: forall (p :: Pass). OutputableBndrId p => HsCmd (GhcPass p) -> SDoc
- pprLCmd :: forall (p :: Pass). OutputableBndrId p => LHsCmd (GhcPass p) -> SDoc
- isAtomicHsExpr :: HsExpr id -> Bool
- parenthesizeHsExpr :: forall (p :: Pass). PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p)
- hsExprNeedsParens :: PprPrec -> HsExpr p -> Bool
- pprParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> HsExpr (GhcPass p) -> SDoc
- pprParendLExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc
- pprDebugParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc
- pprExternalSrcLoc :: (StringLiteral, (Int, Int), (Int, Int)) -> SDoc
- ppr_apps :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> [Either (LHsExpr (GhcPass p)) (LHsWcType (NoGhcTc (GhcPass p)))] -> SDoc
- ppr_infix_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> Maybe SDoc
- ppr_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc
- ppr_lexpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc
- pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc
- isQuietHsExpr :: HsExpr id -> Bool
- tupArgPresent :: LHsTupArg id -> Bool
- unboundVarOcc :: UnboundVar -> OccName
- mkRnSyntaxExpr :: Name -> SyntaxExpr GhcRn
- mkSyntaxExpr :: forall (p :: Pass). HsExpr (GhcPass p) -> SyntaxExpr (GhcPass p)
- noSyntaxExpr :: forall (p :: Pass). SyntaxExpr (GhcPass p)
- noExpr :: forall (p :: Pass). HsExpr (GhcPass p)
- type PostTcExpr = HsExpr GhcTc
- type PostTcTable = [(Name, PostTcExpr)]
- type CmdSyntaxTable p = [(Name, HsExpr p)]
- data UnboundVar
- data RecordConTc = RecordConTc {}
- data RecordUpdTc = RecordUpdTc {
- rupd_cons :: [ConLike]
- rupd_in_tys :: [Type]
- rupd_out_tys :: [Type]
- rupd_wrap :: HsWrapper
- type LHsTupArg id = Located (HsTupArg id)
- data HsTupArg id
- type LHsCmd id = Located (HsCmd id)
- data HsArrAppType
- type LHsCmdTop p = Located (HsCmdTop p)
- data HsCmdTop p
- data CmdTopTc = CmdTopTc Type Type (CmdSyntaxTable GhcTc)
- type HsRecordBinds p = HsRecFields p (LHsExpr p)
- data MatchGroupTc = MatchGroupTc {
- mg_arg_tys :: [Type]
- mg_res_ty :: Type
- type LMatch id body = Located (Match id body)
- data Match p body
- type LGRHS id body = Located (GRHS id body)
- data GRHS p body
- = GRHS (XCGRHS p body) [GuardLStmt p] body
- | XGRHS (XXGRHS p body)
- type LStmt id body = Located (StmtLR id id body)
- type LStmtLR idL idR body = Located (StmtLR idL idR body)
- type Stmt id body = StmtLR id id body
- type CmdLStmt id = LStmt id (LHsCmd id)
- type CmdStmt id = Stmt id (LHsCmd id)
- type ExprLStmt id = LStmt id (LHsExpr id)
- type ExprStmt id = Stmt id (LHsExpr id)
- type GuardLStmt id = LStmt id (LHsExpr id)
- type GuardStmt id = Stmt id (LHsExpr id)
- type GhciLStmt id = LStmt id (LHsExpr id)
- type GhciStmt id = Stmt id (LHsExpr id)
- data StmtLR idL idR body
- = LastStmt (XLastStmt idL idR body) body Bool (SyntaxExpr idR)
- | BindStmt (XBindStmt idL idR body) (LPat idL) body (SyntaxExpr idR) (SyntaxExpr idR)
- | ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR))
- | BodyStmt (XBodyStmt idL idR body) body (SyntaxExpr idR) (SyntaxExpr idR)
- | LetStmt (XLetStmt idL idR body) (LHsLocalBindsLR idL idR)
- | ParStmt (XParStmt idL idR body) [ParStmtBlock idL idR] (HsExpr idR) (SyntaxExpr idR)
- | TransStmt { }
- | RecStmt {
- recS_ext :: XRecStmt idL idR body
- recS_stmts :: [LStmtLR idL idR body]
- recS_later_ids :: [IdP idR]
- recS_rec_ids :: [IdP idR]
- recS_bind_fn :: SyntaxExpr idR
- recS_ret_fn :: SyntaxExpr idR
- recS_mfix_fn :: SyntaxExpr idR
- | XStmtLR (XXStmtLR idL idR body)
- data RecStmtTc = RecStmtTc {
- recS_bind_ty :: Type
- recS_later_rets :: [PostTcExpr]
- recS_rec_rets :: [PostTcExpr]
- recS_ret_ty :: Type
- data TransForm
- data ParStmtBlock idL idR
- = ParStmtBlock (XParStmtBlock idL idR) [ExprLStmt idL] [IdP idR] (SyntaxExpr idR)
- | XParStmtBlock (XXParStmtBlock idL idR)
- data ApplicativeArg idL
- = ApplicativeArgOne {
- xarg_app_arg_one :: XApplicativeArgOne idL
- app_arg_pattern :: LPat idL
- arg_expr :: LHsExpr idL
- is_body_stmt :: Bool
- fail_operator :: SyntaxExpr idL
- | ApplicativeArgMany {
- xarg_app_arg_many :: XApplicativeArgMany idL
- app_stmts :: [ExprLStmt idL]
- final_expr :: HsExpr idL
- bv_pattern :: LPat idL
- | XApplicativeArg (XXApplicativeArg idL)
- = ApplicativeArgOne {
- data SpliceDecoration
- newtype ThModFinalizers = ThModFinalizers [ForeignRef (Q ())]
- data DelayedSplice = DelayedSplice TcLclEnv (LHsExpr GhcRn) TcType (LHsExpr GhcTcId)
- data HsSplicedThing id
- = HsSplicedExpr (HsExpr id)
- | HsSplicedTy (HsType id)
- | HsSplicedPat (Pat id)
- type SplicePointName = Name
- data PendingRnSplice = PendingRnSplice UntypedSpliceFlavour SplicePointName (LHsExpr GhcRn)
- data UntypedSpliceFlavour
- data PendingTcSplice = PendingTcSplice SplicePointName (LHsExpr GhcTc)
- data HsBracket p
- data ArithSeqInfo id
- data HsMatchContext id
- = FunRhs { }
- | LambdaExpr
- | CaseAlt
- | IfAlt
- | ProcExpr
- | PatBindRhs
- | PatBindGuards
- | RecUpd
- | StmtCtxt (HsStmtContext id)
- | ThPatSplice
- | ThPatQuote
- | PatSyn
- data HsStmtContext id
- = ListComp
- | MonadComp
- | DoExpr
- | MDoExpr
- | ArrowExpr
- | GhciStmtCtxt
- | PatGuard (HsMatchContext id)
- | ParStmtCtxt (HsStmtContext id)
- | TransStmtCtxt (HsStmtContext id)
- roleAnnotDeclName :: forall (p :: Pass). RoleAnnotDecl (GhcPass p) -> IdP (GhcPass p)
- annProvenanceName_maybe :: AnnProvenance name -> Maybe name
- docDeclDoc :: DocDecl -> HsDocString
- pprFullRuleName :: Located (SourceText, RuleName) -> SDoc
- collectRuleBndrSigTys :: [RuleBndr pass] -> [LHsSigWcType pass]
- flattenRuleDecls :: [LRuleDecls pass] -> [LRuleDecl pass]
- mapDerivStrategy :: forall p (pass :: Pass). p ~ GhcPass pass => (XViaStrategy p -> XViaStrategy p) -> DerivStrategy p -> DerivStrategy p
- foldDerivStrategy :: forall p (pass :: Pass) r. p ~ GhcPass pass => r -> (XViaStrategy p -> r) -> DerivStrategy p -> r
- derivStrategyName :: DerivStrategy a -> SDoc
- instDeclDataFamInsts :: forall (p :: Pass). [LInstDecl (GhcPass p)] -> [DataFamInstDecl (GhcPass p)]
- pprHsFamInstLHS :: forall (p :: Pass). OutputableBndrId p => IdP (GhcPass p) -> Maybe [LHsTyVarBndr (GhcPass p)] -> HsTyPats (GhcPass p) -> LexicalFixity -> LHsContext (GhcPass p) -> SDoc
- pprDataFamInstFlavour :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> SDoc
- pprTyFamInstDecl :: forall (p :: Pass). OutputableBndrId p => TopLevelFlag -> TyFamInstDecl (GhcPass p) -> SDoc
- hsConDeclTheta :: Maybe (LHsContext pass) -> [LHsType pass]
- hsConDeclArgTys :: HsConDeclDetails pass -> [LBangType pass]
- getConArgs :: ConDecl pass -> HsConDeclDetails pass
- getConNames :: forall (p :: Pass). ConDecl (GhcPass p) -> [Located (IdP (GhcPass p))]
- newOrDataToFlavour :: NewOrData -> TyConFlavour
- standaloneKindSigName :: forall (p :: Pass). StandaloneKindSig (GhcPass p) -> IdP (GhcPass p)
- resultVariableName :: forall (a :: Pass). FamilyResultSig (GhcPass a) -> Maybe (IdP (GhcPass a))
- famResultKindSignature :: forall (p :: Pass). FamilyResultSig (GhcPass p) -> Maybe (LHsKind (GhcPass p))
- familyDeclName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> IdP (GhcPass p)
- familyDeclLName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> Located (IdP (GhcPass p))
- tyClGroupKindSigs :: [TyClGroup pass] -> [LStandaloneKindSig pass]
- tyClGroupRoleDecls :: [TyClGroup pass] -> [LRoleAnnotDecl pass]
- tyClGroupInstDecls :: [TyClGroup pass] -> [LInstDecl pass]
- tyClGroupTyClDecls :: [TyClGroup pass] -> [LTyClDecl pass]
- pprTyClDeclFlavour :: forall (p :: Pass). TyClDecl (GhcPass p) -> SDoc
- hsDeclHasCusk :: TyClDecl GhcRn -> Bool
- countTyClDecls :: [TyClDecl pass] -> (Int, Int, Int, Int, Int)
- tyClDeclTyVars :: TyClDecl pass -> LHsQTyVars pass
- tcdName :: forall (p :: Pass). TyClDecl (GhcPass p) -> IdP (GhcPass p)
- tyClDeclLName :: forall (p :: Pass). TyClDecl (GhcPass p) -> Located (IdP (GhcPass p))
- tyFamInstDeclLName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> Located (IdP (GhcPass p))
- tyFamInstDeclName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> IdP (GhcPass p)
- isDataFamilyDecl :: TyClDecl pass -> Bool
- isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool
- isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool
- isTypeFamilyDecl :: TyClDecl pass -> Bool
- isFamilyDecl :: TyClDecl pass -> Bool
- isClassDecl :: TyClDecl pass -> Bool
- isSynDecl :: TyClDecl pass -> Bool
- isDataDecl :: TyClDecl pass -> Bool
- appendGroups :: forall (p :: Pass). HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p)
- hsGroupInstDecls :: HsGroup id -> [LInstDecl id]
- emptyRnGroup :: forall (p :: Pass). HsGroup (GhcPass p)
- emptyRdrGroup :: forall (p :: Pass). HsGroup (GhcPass p)
- type LHsDecl p = Located (HsDecl p)
- data HsDecl p
- = TyClD (XTyClD p) (TyClDecl p)
- | InstD (XInstD p) (InstDecl p)
- | DerivD (XDerivD p) (DerivDecl p)
- | ValD (XValD p) (HsBind p)
- | SigD (XSigD p) (Sig p)
- | KindSigD (XKindSigD p) (StandaloneKindSig p)
- | DefD (XDefD p) (DefaultDecl p)
- | ForD (XForD p) (ForeignDecl p)
- | WarningD (XWarningD p) (WarnDecls p)
- | AnnD (XAnnD p) (AnnDecl p)
- | RuleD (XRuleD p) (RuleDecls p)
- | SpliceD (XSpliceD p) (SpliceDecl p)
- | DocD (XDocD p) DocDecl
- | RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p)
- | XHsDecl (XXHsDecl p)
- data HsGroup p
- = HsGroup {
- hs_ext :: XCHsGroup p
- hs_valds :: HsValBinds p
- hs_splcds :: [LSpliceDecl p]
- hs_tyclds :: [TyClGroup p]
- hs_derivds :: [LDerivDecl p]
- hs_fixds :: [LFixitySig p]
- hs_defds :: [LDefaultDecl p]
- hs_fords :: [LForeignDecl p]
- hs_warnds :: [LWarnDecls p]
- hs_annds :: [LAnnDecl p]
- hs_ruleds :: [LRuleDecls p]
- hs_docs :: [LDocDecl]
- | XHsGroup (XXHsGroup p)
- = HsGroup {
- type LSpliceDecl pass = Located (SpliceDecl pass)
- data SpliceDecl p
- = SpliceDecl (XSpliceDecl p) (Located (HsSplice p)) SpliceExplicitFlag
- | XSpliceDecl (XXSpliceDecl p)
- type LTyClDecl pass = Located (TyClDecl pass)
- data TyClDecl pass
- = FamDecl {
- tcdFExt :: XFamDecl pass
- tcdFam :: FamilyDecl pass
- | SynDecl { }
- | DataDecl {
- tcdDExt :: XDataDecl pass
- tcdLName :: Located (IdP pass)
- tcdTyVars :: LHsQTyVars pass
- tcdFixity :: LexicalFixity
- tcdDataDefn :: HsDataDefn pass
- | ClassDecl {
- tcdCExt :: XClassDecl pass
- tcdCtxt :: LHsContext pass
- tcdLName :: Located (IdP pass)
- tcdTyVars :: LHsQTyVars pass
- tcdFixity :: LexicalFixity
- tcdFDs :: [LHsFunDep pass]
- tcdSigs :: [LSig pass]
- tcdMeths :: LHsBinds pass
- tcdATs :: [LFamilyDecl pass]
- tcdATDefs :: [LTyFamDefltDecl pass]
- tcdDocs :: [LDocDecl]
- | XTyClDecl (XXTyClDecl pass)
- = FamDecl {
- type LHsFunDep pass = Located (FunDep (Located (IdP pass)))
- data DataDeclRn = DataDeclRn {
- tcdDataCusk :: Bool
- tcdFVs :: NameSet
- data TyClGroup pass
- = TyClGroup {
- group_ext :: XCTyClGroup pass
- group_tyclds :: [LTyClDecl pass]
- group_roles :: [LRoleAnnotDecl pass]
- group_kisigs :: [LStandaloneKindSig pass]
- group_instds :: [LInstDecl pass]
- | XTyClGroup (XXTyClGroup pass)
- = TyClGroup {
- type LFamilyResultSig pass = Located (FamilyResultSig pass)
- data FamilyResultSig pass
- = NoSig (XNoSig pass)
- | KindSig (XCKindSig pass) (LHsKind pass)
- | TyVarSig (XTyVarSig pass) (LHsTyVarBndr pass)
- | XFamilyResultSig (XXFamilyResultSig pass)
- type LFamilyDecl pass = Located (FamilyDecl pass)
- data FamilyDecl pass
- = FamilyDecl {
- fdExt :: XCFamilyDecl pass
- fdInfo :: FamilyInfo pass
- fdLName :: Located (IdP pass)
- fdTyVars :: LHsQTyVars pass
- fdFixity :: LexicalFixity
- fdResultSig :: LFamilyResultSig pass
- fdInjectivityAnn :: Maybe (LInjectivityAnn pass)
- | XFamilyDecl (XXFamilyDecl pass)
- = FamilyDecl {
- type LInjectivityAnn pass = Located (InjectivityAnn pass)
- data InjectivityAnn pass = InjectivityAnn (Located (IdP pass)) [Located (IdP pass)]
- data FamilyInfo pass
- = DataFamily
- | OpenTypeFamily
- | ClosedTypeFamily (Maybe [LTyFamInstEqn pass])
- data HsDataDefn pass
- = HsDataDefn {
- dd_ext :: XCHsDataDefn pass
- dd_ND :: NewOrData
- dd_ctxt :: LHsContext pass
- dd_cType :: Maybe (Located CType)
- dd_kindSig :: Maybe (LHsKind pass)
- dd_cons :: [LConDecl pass]
- dd_derivs :: HsDeriving pass
- | XHsDataDefn (XXHsDataDefn pass)
- = HsDataDefn {
- type HsDeriving pass = Located [LHsDerivingClause pass]
- type LHsDerivingClause pass = Located (HsDerivingClause pass)
- data HsDerivingClause pass
- = HsDerivingClause {
- deriv_clause_ext :: XCHsDerivingClause pass
- deriv_clause_strategy :: Maybe (LDerivStrategy pass)
- deriv_clause_tys :: Located [LHsSigType pass]
- | XHsDerivingClause (XXHsDerivingClause pass)
- = HsDerivingClause {
- type LStandaloneKindSig pass = Located (StandaloneKindSig pass)
- data StandaloneKindSig pass
- = StandaloneKindSig (XStandaloneKindSig pass) (Located (IdP pass)) (LHsSigType pass)
- | XStandaloneKindSig (XXStandaloneKindSig pass)
- data NewOrData
- type LConDecl pass = Located (ConDecl pass)
- data ConDecl pass
- = ConDeclGADT {
- con_g_ext :: XConDeclGADT pass
- con_names :: [Located (IdP pass)]
- con_forall :: Located Bool
- con_qvars :: LHsQTyVars pass
- con_mb_cxt :: Maybe (LHsContext pass)
- con_args :: HsConDeclDetails pass
- con_res_ty :: LHsType pass
- con_doc :: Maybe LHsDocString
- | ConDeclH98 {
- con_ext :: XConDeclH98 pass
- con_name :: Located (IdP pass)
- con_forall :: Located Bool
- con_ex_tvs :: [LHsTyVarBndr pass]
- con_mb_cxt :: Maybe (LHsContext pass)
- con_args :: HsConDeclDetails pass
- con_doc :: Maybe LHsDocString
- | XConDecl (XXConDecl pass)
- = ConDeclGADT {
- type HsConDeclDetails pass = HsConDetails (LBangType pass) (Located [LConDeclField pass])
- type LTyFamInstEqn pass = Located (TyFamInstEqn pass)
- type HsTyPats pass = [LHsTypeArg pass]
- type TyFamInstEqn pass = FamInstEqn pass (LHsType pass)
- type TyFamDefltDecl = TyFamInstDecl
- type LTyFamDefltDecl pass = Located (TyFamDefltDecl pass)
- type LTyFamInstDecl pass = Located (TyFamInstDecl pass)
- newtype TyFamInstDecl pass = TyFamInstDecl {
- tfid_eqn :: TyFamInstEqn pass
- type LDataFamInstDecl pass = Located (DataFamInstDecl pass)
- newtype DataFamInstDecl pass = DataFamInstDecl {
- dfid_eqn :: FamInstEqn pass (HsDataDefn pass)
- type LFamInstEqn pass rhs = Located (FamInstEqn pass rhs)
- type FamInstEqn pass rhs = HsImplicitBndrs pass (FamEqn pass rhs)
- data FamEqn pass rhs
- = FamEqn {
- feqn_ext :: XCFamEqn pass rhs
- feqn_tycon :: Located (IdP pass)
- feqn_bndrs :: Maybe [LHsTyVarBndr pass]
- feqn_pats :: HsTyPats pass
- feqn_fixity :: LexicalFixity
- feqn_rhs :: rhs
- | XFamEqn (XXFamEqn pass rhs)
- = FamEqn {
- type LClsInstDecl pass = Located (ClsInstDecl pass)
- data ClsInstDecl pass
- = ClsInstDecl {
- cid_ext :: XCClsInstDecl pass
- cid_poly_ty :: LHsSigType pass
- cid_binds :: LHsBinds pass
- cid_sigs :: [LSig pass]
- cid_tyfam_insts :: [LTyFamInstDecl pass]
- cid_datafam_insts :: [LDataFamInstDecl pass]
- cid_overlap_mode :: Maybe (Located OverlapMode)
- | XClsInstDecl (XXClsInstDecl pass)
- = ClsInstDecl {
- type LInstDecl pass = Located (InstDecl pass)
- data InstDecl pass
- = ClsInstD {
- cid_d_ext :: XClsInstD pass
- cid_inst :: ClsInstDecl pass
- | DataFamInstD {
- dfid_ext :: XDataFamInstD pass
- dfid_inst :: DataFamInstDecl pass
- | TyFamInstD {
- tfid_ext :: XTyFamInstD pass
- tfid_inst :: TyFamInstDecl pass
- | XInstDecl (XXInstDecl pass)
- = ClsInstD {
- type LDerivDecl pass = Located (DerivDecl pass)
- data DerivDecl pass
- = DerivDecl {
- deriv_ext :: XCDerivDecl pass
- deriv_type :: LHsSigWcType pass
- deriv_strategy :: Maybe (LDerivStrategy pass)
- deriv_overlap_mode :: Maybe (Located OverlapMode)
- | XDerivDecl (XXDerivDecl pass)
- = DerivDecl {
- type LDerivStrategy pass = Located (DerivStrategy pass)
- data DerivStrategy pass
- type LDefaultDecl pass = Located (DefaultDecl pass)
- data DefaultDecl pass
- = DefaultDecl (XCDefaultDecl pass) [LHsType pass]
- | XDefaultDecl (XXDefaultDecl pass)
- type LForeignDecl pass = Located (ForeignDecl pass)
- data ForeignDecl pass
- = ForeignImport {
- fd_i_ext :: XForeignImport pass
- fd_name :: Located (IdP pass)
- fd_sig_ty :: LHsSigType pass
- fd_fi :: ForeignImport
- | ForeignExport {
- fd_e_ext :: XForeignExport pass
- fd_name :: Located (IdP pass)
- fd_sig_ty :: LHsSigType pass
- fd_fe :: ForeignExport
- | XForeignDecl (XXForeignDecl pass)
- = ForeignImport {
- data ForeignImport = CImport (Located CCallConv) (Located Safety) (Maybe Header) CImportSpec (Located SourceText)
- data CImportSpec
- data ForeignExport = CExport (Located CExportSpec) (Located SourceText)
- type LRuleDecls pass = Located (RuleDecls pass)
- data RuleDecls pass
- = HsRules {
- rds_ext :: XCRuleDecls pass
- rds_src :: SourceText
- rds_rules :: [LRuleDecl pass]
- | XRuleDecls (XXRuleDecls pass)
- = HsRules {
- type LRuleDecl pass = Located (RuleDecl pass)
- data RuleDecl pass
- data HsRuleRn = HsRuleRn NameSet NameSet
- type LRuleBndr pass = Located (RuleBndr pass)
- data RuleBndr pass
- = RuleBndr (XCRuleBndr pass) (Located (IdP pass))
- | RuleBndrSig (XRuleBndrSig pass) (Located (IdP pass)) (LHsSigWcType pass)
- | XRuleBndr (XXRuleBndr pass)
- type LDocDecl = Located DocDecl
- data DocDecl
- type LWarnDecls pass = Located (WarnDecls pass)
- data WarnDecls pass
- = Warnings {
- wd_ext :: XWarnings pass
- wd_src :: SourceText
- wd_warnings :: [LWarnDecl pass]
- | XWarnDecls (XXWarnDecls pass)
- = Warnings {
- type LWarnDecl pass = Located (WarnDecl pass)
- data WarnDecl pass
- = Warning (XWarning pass) [Located (IdP pass)] WarningTxt
- | XWarnDecl (XXWarnDecl pass)
- type LAnnDecl pass = Located (AnnDecl pass)
- data AnnDecl pass
- = HsAnnotation (XHsAnnotation pass) SourceText (AnnProvenance (IdP pass)) (Located (HsExpr pass))
- | XAnnDecl (XXAnnDecl pass)
- data AnnProvenance name
- = ValueAnnProvenance (Located name)
- | TypeAnnProvenance (Located name)
- | ModuleAnnProvenance
- type LRoleAnnotDecl pass = Located (RoleAnnotDecl pass)
- data RoleAnnotDecl pass
- = RoleAnnotDecl (XCRoleAnnotDecl pass) (Located (IdP pass)) [Located (Maybe Role)]
- | XRoleAnnotDecl (XXRoleAnnotDecl pass)
- collectEvVarsPat :: Pat GhcTc -> Bag EvVar
- collectEvVarsPats :: [Pat GhcTc] -> Bag EvVar
- parenthesizePat :: forall (p :: Pass). PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p)
- patNeedsParens :: PprPrec -> Pat p -> Bool
- isIrrefutableHsPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> Bool
- looksLazyPatBind :: forall (p :: Pass). HsBind (GhcPass p) -> Bool
- isBangedLPat :: forall (p :: Pass). LPat (GhcPass p) -> Bool
- mkCharLitPat :: forall (p :: Pass). SourceText -> Char -> OutPat (GhcPass p)
- mkNilPat :: forall (p :: Pass). Type -> OutPat (GhcPass p)
- mkPrefixConPat :: forall (p :: Pass). DataCon -> [OutPat (GhcPass p)] -> [Type] -> OutPat (GhcPass p)
- pprConArgs :: forall (p :: Pass). OutputableBndrId p => HsConPatDetails (GhcPass p) -> SDoc
- pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc
- hsRecUpdFieldOcc :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> LFieldOcc GhcTc
- hsRecUpdFieldId :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> Located Id
- hsRecUpdFieldRdr :: forall (p :: Pass). HsRecUpdField (GhcPass p) -> Located RdrName
- hsRecFieldId :: HsRecField GhcTc arg -> Located Id
- hsRecFieldSel :: HsRecField pass arg -> Located (XCFieldOcc pass)
- hsRecFieldsArgs :: HsRecFields p arg -> [arg]
- hsRecFields :: HsRecFields p arg -> [XCFieldOcc p]
- hsConPatArgs :: HsConPatDetails p -> [LPat p]
- type InPat p = LPat p
- type OutPat p = LPat p
- data ListPatTc = ListPatTc Type (Maybe (Type, SyntaxExpr GhcTc))
- type HsConPatDetails p = HsConDetails (LPat p) (HsRecFields p (LPat p))
- data HsRecFields p arg = HsRecFields {
- rec_flds :: [LHsRecField p arg]
- rec_dotdot :: Maybe (Located Int)
- type LHsRecField' p arg = Located (HsRecField' p arg)
- type LHsRecField p arg = Located (HsRecField p arg)
- type LHsRecUpdField p = Located (HsRecUpdField p)
- type HsRecField p arg = HsRecField' (FieldOcc p) arg
- type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p)
- data HsRecField' id arg = HsRecField {
- hsRecFieldLbl :: Located id
- hsRecFieldArg :: arg
- hsRecPun :: Bool
- pprMinimalSig :: OutputableBndr name => LBooleanFormula (Located name) -> SDoc
- pprTcSpecPrags :: TcSpecPrags -> SDoc
- pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc
- pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc
- pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc
- pragBrackets :: SDoc -> SDoc
- ppr_sig :: forall (p :: Pass). OutputableBndrId p => Sig (GhcPass p) -> SDoc
- hsSigDoc :: Sig name -> SDoc
- isCompleteMatchSig :: LSig name -> Bool
- isSCCFunSig :: LSig name -> Bool
- isMinimalLSig :: LSig name -> Bool
- isInlineLSig :: LSig name -> Bool
- isPragLSig :: LSig name -> Bool
- isSpecInstLSig :: LSig name -> Bool
- isSpecLSig :: LSig name -> Bool
- isTypeLSig :: LSig name -> Bool
- isFixityLSig :: LSig name -> Bool
- isDefaultMethod :: TcSpecPrags -> Bool
- hasSpecPrags :: TcSpecPrags -> Bool
- noSpecPrags :: TcSpecPrags
- isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool
- isEmptyIPBindsPR :: forall (p :: Pass). HsIPBinds (GhcPass p) -> Bool
- pprTicks :: SDoc -> SDoc -> SDoc
- ppr_monobind :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc
- plusHsValBinds :: forall (a :: Pass). HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a)
- isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool
- emptyLHsBinds :: LHsBindsLR idL idR
- emptyValBindsOut :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b)
- emptyValBindsIn :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b)
- isEmptyValBinds :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) -> Bool
- eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool
- isEmptyLocalBindsPR :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) -> Bool
- isEmptyLocalBindsTc :: forall (a :: Pass). HsLocalBindsLR (GhcPass a) GhcTc -> Bool
- emptyLocalBinds :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b)
- pprDeclList :: [SDoc] -> SDoc
- pprLHsBindsForUser :: forall (idL :: Pass) (idR :: Pass) (id2 :: Pass). (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc]
- pprLHsBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc
- type HsLocalBinds id = HsLocalBindsLR id id
- type LHsLocalBinds id = Located (HsLocalBinds id)
- data HsLocalBindsLR idL idR
- = HsValBinds (XHsValBinds idL idR) (HsValBindsLR idL idR)
- | HsIPBinds (XHsIPBinds idL idR) (HsIPBinds idR)
- | EmptyLocalBinds (XEmptyLocalBinds idL idR)
- | XHsLocalBindsLR (XXHsLocalBindsLR idL idR)
- type LHsLocalBindsLR idL idR = Located (HsLocalBindsLR idL idR)
- type HsValBinds id = HsValBindsLR id id
- data HsValBindsLR idL idR
- = ValBinds (XValBinds idL idR) (LHsBindsLR idL idR) [LSig idR]
- | XValBindsLR (XXValBindsLR idL idR)
- data NHsValBindsLR idL = NValBinds [(RecFlag, LHsBinds idL)] [LSig GhcRn]
- type LHsBind id = LHsBindLR id id
- type LHsBinds id = LHsBindsLR id id
- type HsBind id = HsBindLR id id
- type LHsBindsLR idL idR = Bag (LHsBindLR idL idR)
- type LHsBindLR idL idR = Located (HsBindLR idL idR)
- data HsBindLR idL idR
- = FunBind { }
- | PatBind { }
- | VarBind { }
- | AbsBinds {
- abs_ext :: XAbsBinds idL idR
- abs_tvs :: [TyVar]
- abs_ev_vars :: [EvVar]
- abs_exports :: [ABExport idL]
- abs_ev_binds :: [TcEvBinds]
- abs_binds :: LHsBinds idL
- abs_sig :: Bool
- | PatSynBind (XPatSynBind idL idR) (PatSynBind idL idR)
- | XHsBindsLR (XXHsBindsLR idL idR)
- data NPatBindTc = NPatBindTc {
- pat_fvs :: NameSet
- pat_rhs_ty :: Type
- data ABExport p
- data PatSynBind idL idR
- = PSB { }
- | XPatSynBind (XXPatSynBind idL idR)
- data HsIPBinds id
- = IPBinds (XIPBinds id) [LIPBind id]
- | XHsIPBinds (XXHsIPBinds id)
- type LIPBind id = Located (IPBind id)
- data IPBind id
- type LSig pass = Located (Sig pass)
- data Sig pass
- = TypeSig (XTypeSig pass) [Located (IdP pass)] (LHsSigWcType pass)
- | PatSynSig (XPatSynSig pass) [Located (IdP pass)] (LHsSigType pass)
- | ClassOpSig (XClassOpSig pass) Bool [Located (IdP pass)] (LHsSigType pass)
- | IdSig (XIdSig pass) Id
- | FixSig (XFixSig pass) (FixitySig pass)
- | InlineSig (XInlineSig pass) (Located (IdP pass)) InlinePragma
- | SpecSig (XSpecSig pass) (Located (IdP pass)) [LHsSigType pass] InlinePragma
- | SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass)
- | MinimalSig (XMinimalSig pass) SourceText (LBooleanFormula (Located (IdP pass)))
- | SCCFunSig (XSCCFunSig pass) SourceText (Located (IdP pass)) (Maybe (Located StringLiteral))
- | CompleteMatchSig (XCompleteMatchSig pass) SourceText (Located [Located (IdP pass)]) (Maybe (Located (IdP pass)))
- | XSig (XXSig pass)
- type LFixitySig pass = Located (FixitySig pass)
- data FixitySig pass
- = FixitySig (XFixitySig pass) [Located (IdP pass)] Fixity
- | XFixitySig (XXFixitySig pass)
- data TcSpecPrags
- type LTcSpecPrag = Located TcSpecPrag
- data TcSpecPrag = SpecPrag Id HsWrapper InlinePragma
- type HsPatSynDetails arg = HsConDetails arg [RecordPatSynField arg]
- data RecordPatSynField a = RecordPatSynField {
- recordPatSynSelectorId :: a
- recordPatSynPatVar :: a
- data HsPatSynDir id
- pprInstanceHdr :: ClsInst -> SDoc
- pprInstance :: ClsInst -> SDoc
- instanceDFunId :: ClsInst -> DFunId
- data ClsInst
- data FamInst
- type BreakIndex = Int
- data ModBreaks = ModBreaks {}
- parenthesizeHsContext :: forall (p :: Pass). PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p)
- parenthesizeHsType :: forall (p :: Pass). PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- hsTypeNeedsParens :: PprPrec -> HsType pass -> Bool
- pprHsType :: forall (p :: Pass). OutputableBndrId p => HsType (GhcPass p) -> SDoc
- pprConDeclFields :: forall (p :: Pass). OutputableBndrId p => [LConDeclField (GhcPass p)] -> SDoc
- pprLHsContext :: forall (p :: Pass). OutputableBndrId p => LHsContext (GhcPass p) -> SDoc
- pprHsExplicitForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> Maybe [LHsTyVarBndr (GhcPass p)] -> SDoc
- pprHsForAllExtra :: forall (p :: Pass). OutputableBndrId p => Maybe SrcSpan -> ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc
- pprHsForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc
- pprAnonWildCard :: SDoc
- ambiguousFieldOcc :: FieldOcc GhcTc -> AmbiguousFieldOcc GhcTc
- unambiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> FieldOcc GhcTc
- selectorAmbiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> Id
- rdrNameAmbiguousFieldOcc :: forall (p :: Pass). AmbiguousFieldOcc (GhcPass p) -> RdrName
- mkAmbiguousFieldOcc :: Located RdrName -> AmbiguousFieldOcc GhcPs
- mkFieldOcc :: Located RdrName -> FieldOcc GhcPs
- getLHsInstDeclClass_maybe :: forall (p :: Pass). LHsSigType (GhcPass p) -> Maybe (Located (IdP (GhcPass p)))
- getLHsInstDeclHead :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
- splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], LHsContext GhcRn, LHsType GhcRn)
- splitLHsQualTy :: LHsType pass -> (LHsContext pass, LHsType pass)
- splitLHsForAllTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass)
- splitLHsSigmaTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass)
- splitLHsPatSynTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, [LHsTyVarBndr pass], LHsContext pass, LHsType pass)
- numVisibleArgs :: [HsArg tm ty] -> Arity
- hsTyGetAppHead_maybe :: forall (p :: Pass). LHsType (GhcPass p) -> Maybe (Located (IdP (GhcPass p)))
- splitHsFunType :: LHsType GhcRn -> ([LHsType GhcRn], LHsType GhcRn)
- mkHsAppKindTy :: forall (p :: Pass). XAppKindTy (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- mkHsAppTys :: forall (p :: Pass). LHsType (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p)
- mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p)
- mkHsOpTy :: forall (p :: Pass). LHsType (GhcPass p) -> Located (IdP (GhcPass p)) -> LHsType (GhcPass p) -> HsType (GhcPass p)
- mkAnonWildCardTy :: HsType GhcPs
- isLHsForAllTy :: LHsType p -> Bool
- ignoreParens :: LHsType pass -> LHsType pass
- hsTyKindSig :: LHsType pass -> Maybe (LHsKind pass)
- hsLTyVarBndrsToTypes :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [LHsType (GhcPass p)]
- hsLTyVarBndrToType :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> LHsType (GhcPass p)
- hsLTyVarLocNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [Located (IdP (GhcPass p))]
- hsLTyVarLocName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> Located (IdP (GhcPass p))
- hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name]
- hsExplicitLTyVarNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [IdP (GhcPass p)]
- hsLTyVarNames :: forall (p :: Pass). [LHsTyVarBndr (GhcPass p)] -> [IdP (GhcPass p)]
- hsLTyVarName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> IdP (GhcPass p)
- hsTyVarName :: forall (p :: Pass). HsTyVarBndr (GhcPass p) -> IdP (GhcPass p)
- hsScopedTvs :: LHsSigType GhcRn -> [Name]
- hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name]
- hsConDetailsArgs :: HsConDetails (LHsType a) (Located [LConDeclField a]) -> [LHsType a]
- hsTvbAllKinded :: LHsQTyVars pass -> Bool
- isHsKindedTyVar :: HsTyVarBndr pass -> Bool
- hsIPNameFS :: HsIPName -> FastString
- mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing
- mkEmptyImplicitBndrs :: thing -> HsImplicitBndrs GhcRn thing
- mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing
- mkHsImplicitBndrs :: thing -> HsImplicitBndrs GhcPs thing
- dropWildCards :: LHsSigWcType pass -> LHsSigType pass
- hsSigWcType :: LHsSigWcType pass -> LHsType pass
- hsSigType :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p)
- hsImplicitBody :: forall (p :: Pass) thing. HsImplicitBndrs (GhcPass p) thing -> thing
- isEmptyLHsQTvs :: LHsQTyVars GhcRn -> Bool
- emptyLHsQTvs :: LHsQTyVars GhcRn
- hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr pass]
- mkHsQTvs :: [LHsTyVarBndr GhcPs] -> LHsQTyVars GhcPs
- noLHsContext :: LHsContext pass
- getBangStrictness :: LHsType a -> HsSrcBang
- getBangType :: LHsType a -> LHsType a
- type LBangType pass = Located (BangType pass)
- type BangType pass = HsType pass
- type LHsContext pass = Located (HsContext pass)
- type HsContext pass = [LHsType pass]
- type LHsType pass = Located (HsType pass)
- type HsKind pass = HsType pass
- type LHsKind pass = Located (HsKind pass)
- type LHsTyVarBndr pass = Located (HsTyVarBndr pass)
- data LHsQTyVars pass
- = HsQTvs {
- hsq_ext :: XHsQTvs pass
- hsq_explicit :: [LHsTyVarBndr pass]
- | XLHsQTyVars (XXLHsQTyVars pass)
- = HsQTvs {
- data HsImplicitBndrs pass thing
- = HsIB { }
- | XHsImplicitBndrs (XXHsImplicitBndrs pass thing)
- data HsWildCardBndrs pass thing
- = HsWC { }
- | XHsWildCardBndrs (XXHsWildCardBndrs pass thing)
- type LHsSigType pass = HsImplicitBndrs pass (LHsType pass)
- type LHsWcType pass = HsWildCardBndrs pass (LHsType pass)
- type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass)
- newtype HsIPName = HsIPName FastString
- data HsTyVarBndr pass
- = UserTyVar (XUserTyVar pass) (Located (IdP pass))
- | KindedTyVar (XKindedTyVar pass) (Located (IdP pass)) (LHsKind pass)
- | XTyVarBndr (XXTyVarBndr pass)
- data HsType pass
- = HsForAllTy {
- hst_xforall :: XForAllTy pass
- hst_fvf :: ForallVisFlag
- hst_bndrs :: [LHsTyVarBndr pass]
- hst_body :: LHsType pass
- | HsQualTy { }
- | HsTyVar (XTyVar pass) PromotionFlag (Located (IdP pass))
- | HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass)
- | HsAppKindTy (XAppKindTy pass) (LHsType pass) (LHsKind pass)
- | HsFunTy (XFunTy pass) (LHsType pass) (LHsType pass)
- | HsListTy (XListTy pass) (LHsType pass)
- | HsTupleTy (XTupleTy pass) HsTupleSort [LHsType pass]
- | HsSumTy (XSumTy pass) [LHsType pass]
- | HsOpTy (XOpTy pass) (LHsType pass) (Located (IdP pass)) (LHsType pass)
- | HsParTy (XParTy pass) (LHsType pass)
- | HsIParamTy (XIParamTy pass) (Located HsIPName) (LHsType pass)
- | HsStarTy (XStarTy pass) Bool
- | HsKindSig (XKindSig pass) (LHsType pass) (LHsKind pass)
- | HsSpliceTy (XSpliceTy pass) (HsSplice pass)
- | HsDocTy (XDocTy pass) (LHsType pass) LHsDocString
- | HsBangTy (XBangTy pass) HsSrcBang (LHsType pass)
- | HsRecTy (XRecTy pass) [LConDeclField pass]
- | HsExplicitListTy (XExplicitListTy pass) PromotionFlag [LHsType pass]
- | HsExplicitTupleTy (XExplicitTupleTy pass) [LHsType pass]
- | HsTyLit (XTyLit pass) HsTyLit
- | HsWildCardTy (XWildCardTy pass)
- | XHsType (XXType pass)
- = HsForAllTy {
- data NewHsTypeX = NHsCoreTy Type
- data HsTyLit
- data HsTupleSort
- type LConDeclField pass = Located (ConDeclField pass)
- data ConDeclField pass
- = ConDeclField {
- cd_fld_ext :: XConDeclField pass
- cd_fld_names :: [LFieldOcc pass]
- cd_fld_type :: LBangType pass
- cd_fld_doc :: Maybe LHsDocString
- | XConDeclField (XXConDeclField pass)
- = ConDeclField {
- data HsConDetails arg rec
- data HsArg tm ty
- type LHsTypeArg p = HsArg (LHsType p) (LHsKind p)
- type LFieldOcc pass = Located (FieldOcc pass)
- data FieldOcc pass
- = FieldOcc {
- extFieldOcc :: XCFieldOcc pass
- rdrNameFieldOcc :: Located RdrName
- | XFieldOcc (XXFieldOcc pass)
- = FieldOcc {
- data AmbiguousFieldOcc pass
- = Unambiguous (XUnambiguous pass) (Located RdrName)
- | Ambiguous (XAmbiguous pass) (Located RdrName)
- | XAmbiguousFieldOcc (XXAmbiguousFieldOcc pass)
- data ExecOptions = ExecOptions {}
- data SingleStep
- data ExecResult
- = ExecComplete { }
- | ExecBreak {
- breakNames :: [Name]
- breakInfo :: Maybe BreakInfo
- data BreakInfo
- data Resume = Resume {
- resumeStmt :: String
- resumeContext :: ForeignRef (ResumeContext [HValueRef])
- resumeBindings :: ([TyThing], GlobalRdrEnv)
- resumeFinalIds :: [Id]
- resumeApStack :: ForeignHValue
- resumeBreakInfo :: Maybe BreakInfo
- resumeSpan :: SrcSpan
- resumeDecl :: String
- resumeCCS :: RemotePtr CostCentreStack
- resumeHistory :: [History]
- resumeHistoryIx :: Int
- data History
- isBottomingId :: Var -> Bool
- isDeadBinder :: Id -> Bool
- isImplicitId :: Id -> Bool
- idDataCon :: Id -> DataCon
- isDataConWorkId :: Id -> Bool
- isFCallId :: Id -> Bool
- isPrimOpId :: Id -> Bool
- isClassOpId_maybe :: Id -> Maybe Class
- isRecordSelector :: Id -> Bool
- recordSelectorTyCon :: Id -> RecSelParent
- idType :: Id -> Kind
- isVanillaDataCon :: DataCon -> Bool
- dataConUserType :: DataCon -> Type
- dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type)
- dataConSrcBangs :: DataCon -> [HsSrcBang]
- dataConIsInfix :: DataCon -> Bool
- isMarkedStrict :: StrictnessMark -> Bool
- data HsSrcBang = HsSrcBang SourceText SrcUnpackedness SrcStrictness
- data HsImplBang
- data SrcStrictness
- data SrcUnpackedness
- data StrictnessMark
- hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool
- hsLitNeedsParens :: PprPrec -> HsLit x -> Bool
- pmPprHsLit :: forall (x :: Pass). HsLit (GhcPass x) -> SDoc
- pp_st_suffix :: SourceText -> SDoc -> SDoc -> SDoc
- convertLit :: ConvertIdX a b => HsLit a -> HsLit b
- overLitType :: HsOverLit GhcTc -> Type
- negateOverLitVal :: OverLitVal -> OverLitVal
- data HsLit x
- = HsChar (XHsChar x) Char
- | HsCharPrim (XHsCharPrim x) Char
- | HsString (XHsString x) FastString
- | HsStringPrim (XHsStringPrim x) ByteString
- | HsInt (XHsInt x) IntegralLit
- | HsIntPrim (XHsIntPrim x) Integer
- | HsWordPrim (XHsWordPrim x) Integer
- | HsInt64Prim (XHsInt64Prim x) Integer
- | HsWord64Prim (XHsWord64Prim x) Integer
- | HsInteger (XHsInteger x) Integer Type
- | HsRat (XHsRat x) FractionalLit Type
- | HsFloatPrim (XHsFloatPrim x) FractionalLit
- | HsDoublePrim (XHsDoublePrim x) FractionalLit
- | XLit (XXLit x)
- data HsOverLit p
- = OverLit {
- ol_ext :: XOverLit p
- ol_val :: OverLitVal
- ol_witness :: HsExpr p
- | XOverLit (XXOverLit p)
- = OverLit {
- data OverLitTc = OverLitTc {
- ol_rebindable :: Bool
- ol_type :: Type
- data OverLitVal
- splitForAllTys :: Type -> ([TyCoVar], Type)
- funResultTy :: Type -> Type
- pprTypeApp :: TyCon -> [Type] -> SDoc
- pprForAll :: [TyCoVarBinder] -> SDoc
- pprThetaArrowTy :: ThetaType -> SDoc
- pprParendType :: Type -> SDoc
- alphaTyVars :: [TyVar]
- tyConClass_maybe :: TyCon -> Maybe Class
- isClassTyCon :: TyCon -> Bool
- synTyConRhs_maybe :: TyCon -> Maybe Type
- synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type)
- tyConDataCons :: TyCon -> [DataCon]
- isOpenTypeFamilyTyCon :: TyCon -> Bool
- isTypeFamilyTyCon :: TyCon -> Bool
- isOpenFamilyTyCon :: TyCon -> Bool
- isFamilyTyCon :: TyCon -> Bool
- isTypeSynonymTyCon :: TyCon -> Bool
- isNewTyCon :: TyCon -> Bool
- isPrimTyCon :: TyCon -> Bool
- pprFundeps :: Outputable a => [FunDep a] -> SDoc
- classTvsFds :: Class -> ([TyVar], [FunDep TyVar])
- classSCTheta :: Class -> [PredType]
- classATs :: Class -> [TyCon]
- classMethods :: Class -> [Id]
- data Class
- dataConTyCon :: DataCon -> TyCon
- dataConFieldLabels :: DataCon -> [FieldLabel]
- data DataCon
- pprLExpr :: forall (p :: Pass). OutputableBndrId p => LHsExpr (GhcPass p) -> SDoc
- pprExpr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> SDoc
- pprSplice :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SDoc
- pprSpliceDecl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SpliceExplicitFlag -> SDoc
- pprPatBind :: forall (bndr :: Pass) (p :: Pass) body. (OutputableBndrId bndr, OutputableBndrId p, Outputable body) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) body -> SDoc
- pprFunBind :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc
- data HsExpr p
- = HsVar (XVar p) (Located (IdP p))
- | HsUnboundVar (XUnboundVar p) UnboundVar
- | HsConLikeOut (XConLikeOut p) ConLike
- | HsRecFld (XRecFld p) (AmbiguousFieldOcc p)
- | HsOverLabel (XOverLabel p) (Maybe (IdP p)) FastString
- | HsIPVar (XIPVar p) HsIPName
- | HsOverLit (XOverLitE p) (HsOverLit p)
- | HsLit (XLitE p) (HsLit p)
- | HsLam (XLam p) (MatchGroup p (LHsExpr p))
- | HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p))
- | HsApp (XApp p) (LHsExpr p) (LHsExpr p)
- | HsAppType (XAppTypeE p) (LHsExpr p) (LHsWcType (NoGhcTc p))
- | OpApp (XOpApp p) (LHsExpr p) (LHsExpr p) (LHsExpr p)
- | NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p)
- | HsPar (XPar p) (LHsExpr p)
- | SectionL (XSectionL p) (LHsExpr p) (LHsExpr p)
- | SectionR (XSectionR p) (LHsExpr p) (LHsExpr p)
- | ExplicitTuple (XExplicitTuple p) [LHsTupArg p] Boxity
- | ExplicitSum (XExplicitSum p) ConTag Arity (LHsExpr p)
- | HsCase (XCase p) (LHsExpr p) (MatchGroup p (LHsExpr p))
- | HsIf (XIf p) (Maybe (SyntaxExpr p)) (LHsExpr p) (LHsExpr p) (LHsExpr p)
- | HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)]
- | HsLet (XLet p) (LHsLocalBinds p) (LHsExpr p)
- | HsDo (XDo p) (HsStmtContext Name) (Located [ExprLStmt p])
- | ExplicitList (XExplicitList p) (Maybe (SyntaxExpr p)) [LHsExpr p]
- | RecordCon {
- rcon_ext :: XRecordCon p
- rcon_con_name :: Located (IdP p)
- rcon_flds :: HsRecordBinds p
- | RecordUpd {
- rupd_ext :: XRecordUpd p
- rupd_expr :: LHsExpr p
- rupd_flds :: [LHsRecUpdField p]
- | ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p))
- | ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p)
- | HsSCC (XSCC p) SourceText StringLiteral (LHsExpr p)
- | HsCoreAnn (XCoreAnn p) SourceText StringLiteral (LHsExpr p)
- | HsBracket (XBracket p) (HsBracket p)
- | HsRnBracketOut (XRnBracketOut p) (HsBracket GhcRn) [PendingRnSplice]
- | HsTcBracketOut (XTcBracketOut p) (HsBracket GhcRn) [PendingTcSplice]
- | HsSpliceE (XSpliceE p) (HsSplice p)
- | HsProc (XProc p) (LPat p) (LHsCmdTop p)
- | HsStatic (XStatic p) (LHsExpr p)
- | HsTick (XTick p) (Tickish (IdP p)) (LHsExpr p)
- | HsBinTick (XBinTick p) Int Int (LHsExpr p)
- | HsTickPragma (XTickPragma p) SourceText (StringLiteral, (Int, Int), (Int, Int)) ((SourceText, SourceText), (SourceText, SourceText)) (LHsExpr p)
- | HsWrap (XWrap p) HsWrapper (HsExpr p)
- | XExpr (XXExpr p)
- data HsCmd id
- = HsCmdArrApp (XCmdArrApp id) (LHsExpr id) (LHsExpr id) HsArrAppType Bool
- | HsCmdArrForm (XCmdArrForm id) (LHsExpr id) LexicalFixity (Maybe Fixity) [LHsCmdTop id]
- | HsCmdApp (XCmdApp id) (LHsCmd id) (LHsExpr id)
- | HsCmdLam (XCmdLam id) (MatchGroup id (LHsCmd id))
- | HsCmdPar (XCmdPar id) (LHsCmd id)
- | HsCmdCase (XCmdCase id) (LHsExpr id) (MatchGroup id (LHsCmd id))
- | HsCmdIf (XCmdIf id) (Maybe (SyntaxExpr id)) (LHsExpr id) (LHsCmd id) (LHsCmd id)
- | HsCmdLet (XCmdLet id) (LHsLocalBinds id) (LHsCmd id)
- | HsCmdDo (XCmdDo id) (Located [CmdLStmt id])
- | HsCmdWrap (XCmdWrap id) HsWrapper (HsCmd id)
- | XCmd (XXCmd id)
- data HsSplice id
- = HsTypedSplice (XTypedSplice id) SpliceDecoration (IdP id) (LHsExpr id)
- | HsUntypedSplice (XUntypedSplice id) SpliceDecoration (IdP id) (LHsExpr id)
- | HsQuasiQuote (XQuasiQuote id) (IdP id) (IdP id) SrcSpan FastString
- | HsSpliced (XSpliced id) ThModFinalizers (HsSplicedThing id)
- | HsSplicedT DelayedSplice
- | XSplice (XXSplice id)
- data MatchGroup p body
- = MG { }
- | XMatchGroup (XXMatchGroup p body)
- data GRHSs p body
- = GRHSs {
- grhssExt :: XCGRHSs p body
- grhssGRHSs :: [LGRHS p body]
- grhssLocalBinds :: LHsLocalBinds p
- | XGRHSs (XXGRHSs p body)
- = GRHSs {
- data SyntaxExpr p = SyntaxExpr {
- syn_expr :: HsExpr p
- syn_arg_wraps :: [HsWrapper]
- syn_res_wrap :: HsWrapper
- type LHsExpr p = Located (HsExpr p)
- pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc
- replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2
- replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2
- ieLWrappedName :: LIEWrappedName name -> Located name
- lieWrappedName :: LIEWrappedName name -> name
- ieWrappedName :: IEWrappedName name -> name
- ieNames :: forall (p :: Pass). IE (GhcPass p) -> [IdP (GhcPass p)]
- ieName :: forall (p :: Pass). IE (GhcPass p) -> IdP (GhcPass p)
- simpleImportDecl :: forall (p :: Pass). ModuleName -> ImportDecl (GhcPass p)
- isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
- importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle
- type LImportDecl pass = Located (ImportDecl pass)
- data ImportDeclQualifiedStyle
- data ImportDecl pass
- = ImportDecl {
- ideclExt :: XCImportDecl pass
- ideclSourceSrc :: SourceText
- ideclName :: Located ModuleName
- ideclPkgQual :: Maybe StringLiteral
- ideclSource :: Bool
- ideclSafe :: Bool
- ideclQualified :: ImportDeclQualifiedStyle
- ideclImplicit :: Bool
- ideclAs :: Maybe (Located ModuleName)
- ideclHiding :: Maybe (Bool, Located [LIE pass])
- | XImportDecl (XXImportDecl pass)
- = ImportDecl {
- data IEWrappedName name
- type LIEWrappedName name = Located (IEWrappedName name)
- type LIE pass = Located (IE pass)
- data IE pass
- = IEVar (XIEVar pass) (LIEWrappedName (IdP pass))
- | IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP pass))
- | IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass))
- | IEThingWith (XIEThingWith pass) (LIEWrappedName (IdP pass)) IEWildcard [LIEWrappedName (IdP pass)] [Located (FieldLbl (IdP pass))]
- | IEModuleContents (XIEModuleContents pass) (Located ModuleName)
- | IEGroup (XIEGroup pass) Int HsDocString
- | IEDoc (XIEDoc pass) HsDocString
- | IEDocNamed (XIEDocNamed pass) String
- | XIE (XXIE pass)
- data IEWildcard
- data Pat p
- = WildPat (XWildPat p)
- | VarPat (XVarPat p) (Located (IdP p))
- | LazyPat (XLazyPat p) (LPat p)
- | AsPat (XAsPat p) (Located (IdP p)) (LPat p)
- | ParPat (XParPat p) (LPat p)
- | BangPat (XBangPat p) (LPat p)
- | ListPat (XListPat p) [LPat p]
- | TuplePat (XTuplePat p) [LPat p] Boxity
- | SumPat (XSumPat p) (LPat p) ConTag Arity
- | ConPatIn (Located (IdP p)) (HsConPatDetails p)
- | ConPatOut { }
- | ViewPat (XViewPat p) (LHsExpr p) (LPat p)
- | SplicePat (XSplicePat p) (HsSplice p)
- | LitPat (XLitPat p) (HsLit p)
- | NPat (XNPat p) (Located (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p)
- | NPlusKPat (XNPlusKPat p) (Located (IdP p)) (Located (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p)
- | SigPat (XSigPat p) (LPat p) (LHsSigWcType (NoGhcTc p))
- | CoPat (XCoPat p) HsWrapper (Pat p) Type
- | XPat (XXPat p)
- type LPat p = XRec p Pat
- noExtCon :: NoExtCon -> a
- noExtField :: NoExtField
- data NoExtField = NoExtField
- data NoExtCon
- data GhcPass (c :: Pass)
- data Pass
- = Parsed
- | Renamed
- | Typechecked
- type GhcPs = GhcPass 'Parsed
- type GhcRn = GhcPass 'Renamed
- type GhcTc = GhcPass 'Typechecked
- type GhcTcId = GhcTc
- type family XRec p (f :: Type -> Type) = (r :: Type) | r -> p f
- type family IdP p
- type LIdP p = Located (IdP p)
- type family NoGhcTc p where ...
- type family NoGhcTcPass (p :: Pass) :: Pass where ...
- type family XHsValBinds x x'
- type family XHsIPBinds x x'
- type family XEmptyLocalBinds x x'
- type family XXHsLocalBindsLR x x'
- type ForallXHsLocalBindsLR (c :: Type -> Constraint) x x' = (c (XHsValBinds x x'), c (XHsIPBinds x x'), c (XEmptyLocalBinds x x'), c (XXHsLocalBindsLR x x'))
- type family XValBinds x x'
- type family XXValBindsLR x x'
- type ForallXValBindsLR (c :: Type -> Constraint) x x' = (c (XValBinds x x'), c (XXValBindsLR x x'))
- type family XFunBind x x'
- type family XPatBind x x'
- type family XVarBind x x'
- type family XAbsBinds x x'
- type family XPatSynBind x x'
- type family XXHsBindsLR x x'
- type ForallXHsBindsLR (c :: Type -> Constraint) x x' = (c (XFunBind x x'), c (XPatBind x x'), c (XVarBind x x'), c (XAbsBinds x x'), c (XPatSynBind x x'), c (XXHsBindsLR x x'))
- type family XABE x
- type family XXABExport x
- type ForallXABExport (c :: Type -> Constraint) x = (c (XABE x), c (XXABExport x))
- type family XPSB x x'
- type family XXPatSynBind x x'
- type ForallXPatSynBind (c :: Type -> Constraint) x x' = (c (XPSB x x'), c (XXPatSynBind x x'))
- type family XIPBinds x
- type family XXHsIPBinds x
- type ForallXHsIPBinds (c :: Type -> Constraint) x = (c (XIPBinds x), c (XXHsIPBinds x))
- type family XCIPBind x
- type family XXIPBind x
- type ForallXIPBind (c :: Type -> Constraint) x = (c (XCIPBind x), c (XXIPBind x))
- type family XTypeSig x
- type family XPatSynSig x
- type family XClassOpSig x
- type family XIdSig x
- type family XFixSig x
- type family XInlineSig x
- type family XSpecSig x
- type family XSpecInstSig x
- type family XMinimalSig x
- type family XSCCFunSig x
- type family XCompleteMatchSig x
- type family XXSig x
- type ForallXSig (c :: Type -> Constraint) x = (c (XTypeSig x), c (XPatSynSig x), c (XClassOpSig x), c (XIdSig x), c (XFixSig x), c (XInlineSig x), c (XSpecSig x), c (XSpecInstSig x), c (XMinimalSig x), c (XSCCFunSig x), c (XCompleteMatchSig x), c (XXSig x))
- type family XFixitySig x
- type family XXFixitySig x
- type ForallXFixitySig (c :: Type -> Constraint) x = (c (XFixitySig x), c (XXFixitySig x))
- type family XStandaloneKindSig x
- type family XXStandaloneKindSig x
- type family XTyClD x
- type family XInstD x
- type family XDerivD x
- type family XValD x
- type family XSigD x
- type family XKindSigD x
- type family XDefD x
- type family XForD x
- type family XWarningD x
- type family XAnnD x
- type family XRuleD x
- type family XSpliceD x
- type family XDocD x
- type family XRoleAnnotD x
- type family XXHsDecl x
- type ForallXHsDecl (c :: Type -> Constraint) x = (c (XTyClD x), c (XInstD x), c (XDerivD x), c (XValD x), c (XSigD x), c (XKindSigD x), c (XDefD x), c (XForD x), c (XWarningD x), c (XAnnD x), c (XRuleD x), c (XSpliceD x), c (XDocD x), c (XRoleAnnotD x), c (XXHsDecl x))
- type family XCHsGroup x
- type family XXHsGroup x
- type ForallXHsGroup (c :: Type -> Constraint) x = (c (XCHsGroup x), c (XXHsGroup x))
- type family XSpliceDecl x
- type family XXSpliceDecl x
- type ForallXSpliceDecl (c :: Type -> Constraint) x = (c (XSpliceDecl x), c (XXSpliceDecl x))
- type family XFamDecl x
- type family XSynDecl x
- type family XDataDecl x
- type family XClassDecl x
- type family XXTyClDecl x
- type ForallXTyClDecl (c :: Type -> Constraint) x = (c (XFamDecl x), c (XSynDecl x), c (XDataDecl x), c (XClassDecl x), c (XXTyClDecl x))
- type family XCTyClGroup x
- type family XXTyClGroup x
- type ForallXTyClGroup (c :: Type -> Constraint) x = (c (XCTyClGroup x), c (XXTyClGroup x))
- type family XNoSig x
- type family XCKindSig x
- type family XTyVarSig x
- type family XXFamilyResultSig x
- type ForallXFamilyResultSig (c :: Type -> Constraint) x = (c (XNoSig x), c (XCKindSig x), c (XTyVarSig x), c (XXFamilyResultSig x))
- type family XCFamilyDecl x
- type family XXFamilyDecl x
- type ForallXFamilyDecl (c :: Type -> Constraint) x = (c (XCFamilyDecl x), c (XXFamilyDecl x))
- type family XCHsDataDefn x
- type family XXHsDataDefn x
- type ForallXHsDataDefn (c :: Type -> Constraint) x = (c (XCHsDataDefn x), c (XXHsDataDefn x))
- type family XCHsDerivingClause x
- type family XXHsDerivingClause x
- type ForallXHsDerivingClause (c :: Type -> Constraint) x = (c (XCHsDerivingClause x), c (XXHsDerivingClause x))
- type family XConDeclGADT x
- type family XConDeclH98 x
- type family XXConDecl x
- type ForallXConDecl (c :: Type -> Constraint) x = (c (XConDeclGADT x), c (XConDeclH98 x), c (XXConDecl x))
- type family XCFamEqn x r
- type family XXFamEqn x r
- type ForallXFamEqn (c :: Type -> Constraint) x r = (c (XCFamEqn x r), c (XXFamEqn x r))
- type family XCClsInstDecl x
- type family XXClsInstDecl x
- type ForallXClsInstDecl (c :: Type -> Constraint) x = (c (XCClsInstDecl x), c (XXClsInstDecl x))
- type family XClsInstD x
- type family XDataFamInstD x
- type family XTyFamInstD x
- type family XXInstDecl x
- type ForallXInstDecl (c :: Type -> Constraint) x = (c (XClsInstD x), c (XDataFamInstD x), c (XTyFamInstD x), c (XXInstDecl x))
- type family XCDerivDecl x
- type family XXDerivDecl x
- type ForallXDerivDecl (c :: Type -> Constraint) x = (c (XCDerivDecl x), c (XXDerivDecl x))
- type family XViaStrategy x
- type family XCDefaultDecl x
- type family XXDefaultDecl x
- type ForallXDefaultDecl (c :: Type -> Constraint) x = (c (XCDefaultDecl x), c (XXDefaultDecl x))
- type family XForeignImport x
- type family XForeignExport x
- type family XXForeignDecl x
- type ForallXForeignDecl (c :: Type -> Constraint) x = (c (XForeignImport x), c (XForeignExport x), c (XXForeignDecl x))
- type family XCRuleDecls x
- type family XXRuleDecls x
- type ForallXRuleDecls (c :: Type -> Constraint) x = (c (XCRuleDecls x), c (XXRuleDecls x))
- type family XHsRule x
- type family XXRuleDecl x
- type ForallXRuleDecl (c :: Type -> Constraint) x = (c (XHsRule x), c (XXRuleDecl x))
- type family XCRuleBndr x
- type family XRuleBndrSig x
- type family XXRuleBndr x
- type ForallXRuleBndr (c :: Type -> Constraint) x = (c (XCRuleBndr x), c (XRuleBndrSig x), c (XXRuleBndr x))
- type family XWarnings x
- type family XXWarnDecls x
- type ForallXWarnDecls (c :: Type -> Constraint) x = (c (XWarnings x), c (XXWarnDecls x))
- type family XWarning x
- type family XXWarnDecl x
- type ForallXWarnDecl (c :: Type -> Constraint) x = (c (XWarning x), c (XXWarnDecl x))
- type family XHsAnnotation x
- type family XXAnnDecl x
- type ForallXAnnDecl (c :: Type -> Constraint) x = (c (XHsAnnotation x), c (XXAnnDecl x))
- type family XCRoleAnnotDecl x
- type family XXRoleAnnotDecl x
- type ForallXRoleAnnotDecl (c :: Type -> Constraint) x = (c (XCRoleAnnotDecl x), c (XXRoleAnnotDecl x))
- type family XVar x
- type family XUnboundVar x
- type family XConLikeOut x
- type family XRecFld x
- type family XOverLabel x
- type family XIPVar x
- type family XOverLitE x
- type family XLitE x
- type family XLam x
- type family XLamCase x
- type family XApp x
- type family XAppTypeE x
- type family XOpApp x
- type family XNegApp x
- type family XPar x
- type family XSectionL x
- type family XSectionR x
- type family XExplicitTuple x
- type family XExplicitSum x
- type family XCase x
- type family XIf x
- type family XMultiIf x
- type family XLet x
- type family XDo x
- type family XExplicitList x
- type family XRecordCon x
- type family XRecordUpd x
- type family XExprWithTySig x
- type family XArithSeq x
- type family XSCC x
- type family XCoreAnn x
- type family XBracket x
- type family XRnBracketOut x
- type family XTcBracketOut x
- type family XSpliceE x
- type family XProc x
- type family XStatic x
- type family XTick x
- type family XBinTick x
- type family XTickPragma x
- type family XWrap x
- type family XXExpr x
- type ForallXExpr (c :: Type -> Constraint) x = (c (XVar x), c (XUnboundVar x), c (XConLikeOut x), c (XRecFld x), c (XOverLabel x), c (XIPVar x), c (XOverLitE x), c (XLitE x), c (XLam x), c (XLamCase x), c (XApp x), c (XAppTypeE x), c (XOpApp x), c (XNegApp x), c (XPar x), c (XSectionL x), c (XSectionR x), c (XExplicitTuple x), c (XExplicitSum x), c (XCase x), c (XIf x), c (XMultiIf x), c (XLet x), c (XDo x), c (XExplicitList x), c (XRecordCon x), c (XRecordUpd x), c (XExprWithTySig x), c (XArithSeq x), c (XSCC x), c (XCoreAnn x), c (XBracket x), c (XRnBracketOut x), c (XTcBracketOut x), c (XSpliceE x), c (XProc x), c (XStatic x), c (XTick x), c (XBinTick x), c (XTickPragma x), c (XWrap x), c (XXExpr x))
- type family XUnambiguous x
- type family XAmbiguous x
- type family XXAmbiguousFieldOcc x
- type ForallXAmbiguousFieldOcc (c :: Type -> Constraint) x = (c (XUnambiguous x), c (XAmbiguous x), c (XXAmbiguousFieldOcc x))
- type family XPresent x
- type family XMissing x
- type family XXTupArg x
- type ForallXTupArg (c :: Type -> Constraint) x = (c (XPresent x), c (XMissing x), c (XXTupArg x))
- type family XTypedSplice x
- type family XUntypedSplice x
- type family XQuasiQuote x
- type family XSpliced x
- type family XXSplice x
- type ForallXSplice (c :: Type -> Constraint) x = (c (XTypedSplice x), c (XUntypedSplice x), c (XQuasiQuote x), c (XSpliced x), c (XXSplice x))
- type family XExpBr x
- type family XPatBr x
- type family XDecBrL x
- type family XDecBrG x
- type family XTypBr x
- type family XVarBr x
- type family XTExpBr x
- type family XXBracket x
- type ForallXBracket (c :: Type -> Constraint) x = (c (XExpBr x), c (XPatBr x), c (XDecBrL x), c (XDecBrG x), c (XTypBr x), c (XVarBr x), c (XTExpBr x), c (XXBracket x))
- type family XCmdTop x
- type family XXCmdTop x
- type ForallXCmdTop (c :: Type -> Constraint) x = (c (XCmdTop x), c (XXCmdTop x))
- type family XMG x b
- type family XXMatchGroup x b
- type ForallXMatchGroup (c :: Type -> Constraint) x b = (c (XMG x b), c (XXMatchGroup x b))
- type family XCMatch x b
- type family XXMatch x b
- type ForallXMatch (c :: Type -> Constraint) x b = (c (XCMatch x b), c (XXMatch x b))
- type family XCGRHSs x b
- type family XXGRHSs x b
- type ForallXGRHSs (c :: Type -> Constraint) x b = (c (XCGRHSs x b), c (XXGRHSs x b))
- type family XCGRHS x b
- type family XXGRHS x b
- type ForallXGRHS (c :: Type -> Constraint) x b = (c (XCGRHS x b), c (XXGRHS x b))
- type family XLastStmt x x' b
- type family XBindStmt x x' b
- type family XApplicativeStmt x x' b
- type family XBodyStmt x x' b
- type family XLetStmt x x' b
- type family XParStmt x x' b
- type family XTransStmt x x' b
- type family XRecStmt x x' b
- type family XXStmtLR x x' b
- type ForallXStmtLR (c :: Type -> Constraint) x x' b = (c (XLastStmt x x' b), c (XBindStmt x x' b), c (XApplicativeStmt x x' b), c (XBodyStmt x x' b), c (XLetStmt x x' b), c (XParStmt x x' b), c (XTransStmt x x' b), c (XRecStmt x x' b), c (XXStmtLR x x' b))
- type family XCmdArrApp x
- type family XCmdArrForm x
- type family XCmdApp x
- type family XCmdLam x
- type family XCmdPar x
- type family XCmdCase x
- type family XCmdIf x
- type family XCmdLet x
- type family XCmdDo x
- type family XCmdWrap x
- type family XXCmd x
- type ForallXCmd (c :: Type -> Constraint) x = (c (XCmdArrApp x), c (XCmdArrForm x), c (XCmdApp x), c (XCmdLam x), c (XCmdPar x), c (XCmdCase x), c (XCmdIf x), c (XCmdLet x), c (XCmdDo x), c (XCmdWrap x), c (XXCmd x))
- type family XParStmtBlock x x'
- type family XXParStmtBlock x x'
- type ForallXParStmtBlock (c :: Type -> Constraint) x x' = (c (XParStmtBlock x x'), c (XXParStmtBlock x x'))
- type family XApplicativeArgOne x
- type family XApplicativeArgMany x
- type family XXApplicativeArg x
- type ForallXApplicativeArg (c :: Type -> Constraint) x = (c (XApplicativeArgOne x), c (XApplicativeArgMany x), c (XXApplicativeArg x))
- type family XHsChar x
- type family XHsCharPrim x
- type family XHsString x
- type family XHsStringPrim x
- type family XHsInt x
- type family XHsIntPrim x
- type family XHsWordPrim x
- type family XHsInt64Prim x
- type family XHsWord64Prim x
- type family XHsInteger x
- type family XHsRat x
- type family XHsFloatPrim x
- type family XHsDoublePrim x
- type family XXLit x
- type ForallXHsLit (c :: Type -> Constraint) x = (c (XHsChar x), c (XHsCharPrim x), c (XHsDoublePrim x), c (XHsFloatPrim x), c (XHsInt x), c (XHsInt64Prim x), c (XHsIntPrim x), c (XHsInteger x), c (XHsRat x), c (XHsString x), c (XHsStringPrim x), c (XHsWord64Prim x), c (XHsWordPrim x), c (XXLit x))
- type family XOverLit x
- type family XXOverLit x
- type ForallXOverLit (c :: Type -> Constraint) x = (c (XOverLit x), c (XXOverLit x))
- type family XWildPat x
- type family XVarPat x
- type family XLazyPat x
- type family XAsPat x
- type family XParPat x
- type family XBangPat x
- type family XListPat x
- type family XTuplePat x
- type family XSumPat x
- type family XConPat x
- type family XViewPat x
- type family XSplicePat x
- type family XLitPat x
- type family XNPat x
- type family XNPlusKPat x
- type family XSigPat x
- type family XCoPat x
- type family XXPat x
- type ForallXPat (c :: Type -> Constraint) x = (c (XWildPat x), c (XVarPat x), c (XLazyPat x), c (XAsPat x), c (XParPat x), c (XBangPat x), c (XListPat x), c (XTuplePat x), c (XSumPat x), c (XViewPat x), c (XSplicePat x), c (XLitPat x), c (XNPat x), c (XNPlusKPat x), c (XSigPat x), c (XCoPat x), c (XXPat x))
- type family XHsQTvs x
- type family XXLHsQTyVars x
- type ForallXLHsQTyVars (c :: Type -> Constraint) x = (c (XHsQTvs x), c (XXLHsQTyVars x))
- type family XHsIB x b
- type family XXHsImplicitBndrs x b
- type ForallXHsImplicitBndrs (c :: Type -> Constraint) x b = (c (XHsIB x b), c (XXHsImplicitBndrs x b))
- type family XHsWC x b
- type family XXHsWildCardBndrs x b
- type ForallXHsWildCardBndrs (c :: Type -> Constraint) x b = (c (XHsWC x b), c (XXHsWildCardBndrs x b))
- type family XForAllTy x
- type family XQualTy x
- type family XTyVar x
- type family XAppTy x
- type family XAppKindTy x
- type family XFunTy x
- type family XListTy x
- type family XTupleTy x
- type family XSumTy x
- type family XOpTy x
- type family XParTy x
- type family XIParamTy x
- type family XStarTy x
- type family XKindSig x
- type family XSpliceTy x
- type family XDocTy x
- type family XBangTy x
- type family XRecTy x
- type family XExplicitListTy x
- type family XExplicitTupleTy x
- type family XTyLit x
- type family XWildCardTy x
- type family XXType x
- type ForallXType (c :: Type -> Constraint) x = (c (XForAllTy x), c (XQualTy x), c (XTyVar x), c (XAppTy x), c (XAppKindTy x), c (XFunTy x), c (XListTy x), c (XTupleTy x), c (XSumTy x), c (XOpTy x), c (XParTy x), c (XIParamTy x), c (XStarTy x), c (XKindSig x), c (XSpliceTy x), c (XDocTy x), c (XBangTy x), c (XRecTy x), c (XExplicitListTy x), c (XExplicitTupleTy x), c (XTyLit x), c (XWildCardTy x), c (XXType x))
- type family XUserTyVar x
- type family XKindedTyVar x
- type family XXTyVarBndr x
- type ForallXTyVarBndr (c :: Type -> Constraint) x = (c (XUserTyVar x), c (XKindedTyVar x), c (XXTyVarBndr x))
- type family XConDeclField x
- type family XXConDeclField x
- type ForallXConDeclField (c :: Type -> Constraint) x = (c (XConDeclField x), c (XXConDeclField x))
- type family XCFieldOcc x
- type family XXFieldOcc x
- type ForallXFieldOcc (c :: Type -> Constraint) x = (c (XCFieldOcc x), c (XXFieldOcc x))
- type family XCImportDecl x
- type family XXImportDecl x
- type ForallXImportDecl (c :: Type -> Constraint) x = (c (XCImportDecl x), c (XXImportDecl x))
- type family XIEVar x
- type family XIEThingAbs x
- type family XIEThingAll x
- type family XIEThingWith x
- type family XIEModuleContents x
- type family XIEGroup x
- type family XIEDoc x
- type family XIEDocNamed x
- type family XXIE x
- type ForallXIE (c :: Type -> Constraint) x = (c (XIEVar x), c (XIEThingAbs x), c (XIEThingAll x), c (XIEThingWith x), c (XIEModuleContents x), c (XIEGroup x), c (XIEDoc x), c (XIEDocNamed x), c (XXIE x))
- class Convertable a b | a -> b where
- convert :: a -> b
- type ConvertIdX a b = (XHsDoublePrim a ~ XHsDoublePrim b, XHsFloatPrim a ~ XHsFloatPrim b, XHsRat a ~ XHsRat b, XHsInteger a ~ XHsInteger b, XHsWord64Prim a ~ XHsWord64Prim b, XHsInt64Prim a ~ XHsInt64Prim b, XHsWordPrim a ~ XHsWordPrim b, XHsIntPrim a ~ XHsIntPrim b, XHsInt a ~ XHsInt b, XHsStringPrim a ~ XHsStringPrim b, XHsString a ~ XHsString b, XHsCharPrim a ~ XHsCharPrim b, XHsChar a ~ XHsChar b, XXLit a ~ XXLit b)
- type OutputableX p = (Outputable (XIPBinds p), Outputable (XViaStrategy p), Outputable (XViaStrategy GhcRn))
- type OutputableBndrId (pass :: Pass) = (OutputableBndr (NameOrRdrName (IdP (GhcPass pass))), OutputableBndr (IdP (GhcPass pass)), OutputableBndr (NameOrRdrName (IdP (NoGhcTc (GhcPass pass)))), OutputableBndr (IdP (NoGhcTc (GhcPass pass))), NoGhcTc (GhcPass pass) ~ NoGhcTc (NoGhcTc (GhcPass pass)), OutputableX (GhcPass pass), OutputableX (NoGhcTc (GhcPass pass)))
- placeHolderNamesTc :: NameSet
- type family NameOrRdrName id where ...
- isExportedId :: Var -> Bool
- isGlobalId :: Var -> Bool
- isLocalId :: Var -> Bool
- type Id = Var
- type TyVar = Var
- data ForallVisFlag
- data Token
- unicodeAnn :: AnnKeywordId -> AnnKeywordId
- getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns)
- getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment]
- getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns)
- getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan]
- type ApiAnns = (Map ApiAnnKey [SrcSpan], Map SrcSpan [Located AnnotationComment])
- data AnnKeywordId
- = AnnAnyclass
- | AnnAs
- | AnnAt
- | AnnBang
- | AnnBackquote
- | AnnBy
- | AnnCase
- | AnnClass
- | AnnClose
- | AnnCloseB
- | AnnCloseBU
- | AnnCloseC
- | AnnCloseQ
- | AnnCloseQU
- | AnnCloseP
- | AnnCloseS
- | AnnColon
- | AnnComma
- | AnnCommaTuple
- | AnnDarrow
- | AnnDarrowU
- | AnnData
- | AnnDcolon
- | AnnDcolonU
- | AnnDefault
- | AnnDeriving
- | AnnDo
- | AnnDot
- | AnnDotdot
- | AnnElse
- | AnnEqual
- | AnnExport
- | AnnFamily
- | AnnForall
- | AnnForallU
- | AnnForeign
- | AnnFunId
- | AnnGroup
- | AnnHeader
- | AnnHiding
- | AnnIf
- | AnnImport
- | AnnIn
- | AnnInfix
- | AnnInstance
- | AnnLam
- | AnnLarrow
- | AnnLarrowU
- | AnnLet
- | AnnMdo
- | AnnMinus
- | AnnModule
- | AnnNewtype
- | AnnName
- | AnnOf
- | AnnOpen
- | AnnOpenB
- | AnnOpenBU
- | AnnOpenC
- | AnnOpenE
- | AnnOpenEQ
- | AnnOpenEQU
- | AnnOpenP
- | AnnOpenPE
- | AnnOpenPTE
- | AnnOpenS
- | AnnPackageName
- | AnnPattern
- | AnnProc
- | AnnQualified
- | AnnRarrow
- | AnnRarrowU
- | AnnRec
- | AnnRole
- | AnnSafe
- | AnnSemi
- | AnnSimpleQuote
- | AnnSignature
- | AnnStatic
- | AnnStock
- | AnnThen
- | AnnThIdSplice
- | AnnThIdTySplice
- | AnnThTyQuote
- | AnnTilde
- | AnnType
- | AnnUnit
- | AnnUsing
- | AnnVal
- | AnnValStr
- | AnnVbar
- | AnnVia
- | AnnWhere
- | Annlarrowtail
- | AnnlarrowtailU
- | Annrarrowtail
- | AnnrarrowtailU
- | AnnLarrowtail
- | AnnLarrowtailU
- | AnnRarrowtail
- | AnnRarrowtailU
- | AnnEofPos
- data AnnotationComment
- data RdrName
- emptyArgDocMap :: ArgDocMap
- emptyDeclDocMap :: DeclDocMap
- concatDocs :: [HsDocString] -> Maybe HsDocString
- appendDocs :: HsDocString -> HsDocString -> HsDocString
- ppr_mbDoc :: Maybe LHsDocString -> SDoc
- hsDocStringToByteString :: HsDocString -> ByteString
- unpackHDS :: HsDocString -> String
- mkHsDocStringUtf8ByteString :: ByteString -> HsDocString
- mkHsDocString :: String -> HsDocString
- data HsDocString
- type LHsDocString = Located HsDocString
- newtype DeclDocMap = DeclDocMap (Map Name HsDocString)
- newtype ArgDocMap = ArgDocMap (Map Name (Map Int HsDocString))
- nameModule :: HasDebugCallStack => Name -> Module
- isExternalName :: Name -> Bool
- nameSrcSpan :: Name -> SrcSpan
- class NamedThing a where
- getOccName :: a -> OccName
- getName :: a -> Name
- data Type
- data TyThing
- type PredType = Type
- type Kind = Type
- type ThetaType = [PredType]
- prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
- gopt :: GeneralFlag -> DynFlags -> Bool
- defaultObjectTarget :: DynFlags -> HscTarget
- data SafeHaskellMode
- data HscTarget
- data GhcMode
- data GhcLink
- data Phase
- pprModule :: Module -> SDoc
- mkModule :: UnitId -> ModuleName -> Module
- mkModuleName :: String -> ModuleName
- moduleNameString :: ModuleName -> String
- ml_hie_file :: ModLocation -> FilePath
- ml_obj_file :: ModLocation -> FilePath
- ml_hs_file :: ModLocation -> Maybe FilePath
- ml_hi_file :: ModLocation -> FilePath
- failed :: SuccessFlag -> Bool
- succeeded :: SuccessFlag -> Bool
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- negateFixity :: Fixity
- defaultFixity :: Fixity
- maxPrecedence :: Int
- data Fixity
- data FixityDirection
- data LexicalFixity
- data SuccessFlag
- data SpliceExplicitFlag
- data Severity
- unRealSrcSpan :: RealLocated a -> a
- getRealSrcSpan :: RealLocated a -> RealSrcSpan
- cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a
- dL :: HasSrcSpan a => a -> Located (SrcSpanLess a)
- isSubspanOf :: SrcSpan -> SrcSpan -> Bool
- spans :: SrcSpan -> (Int, Int) -> Bool
- leftmost_largest :: SrcSpan -> SrcSpan -> Ordering
- leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
- rightmost :: SrcSpan -> SrcSpan -> Ordering
- cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering
- eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool
- addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c
- combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan
- mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e
- noLoc :: HasSrcSpan a => SrcSpanLess a -> a
- unLoc :: HasSrcSpan a => a -> SrcSpanLess a
- srcSpanEnd :: SrcSpan -> SrcLoc
- srcSpanStart :: SrcSpan -> SrcLoc
- srcSpanEndCol :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanStartLine :: RealSrcSpan -> Int
- isGoodSrcSpan :: SrcSpan -> Bool
- mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
- srcLocSpan :: SrcLoc -> SrcSpan
- noSrcSpan :: SrcSpan
- srcLocCol :: RealSrcLoc -> Int
- srcLocLine :: RealSrcLoc -> Int
- srcLocFile :: RealSrcLoc -> FastString
- noSrcLoc :: SrcLoc
- mkSrcLoc :: FastString -> Int -> Int -> SrcLoc
- data RealSrcLoc
- data SrcLoc
- data RealSrcSpan
- data SrcSpan
- data GenLocated l e = L l e
- type Located = GenLocated SrcSpan
- type family SrcSpanLess a
- composeSrcSpan :: HasSrcSpan a => Located (SrcSpanLess a) -> a
- decomposeSrcSpan :: HasSrcSpan a => a -> Located (SrcSpanLess a)
- alwaysQualify :: PrintUnqualified
- data PrintUnqualified
- data Module
- data ModuleName
- data UnitId
- isFunTyCon :: TyCon -> Bool
- data TyCon
- withSignalHandlers :: (ExceptionMonad m, MonadIO m) => m a -> m a
- showGhcException :: GhcException -> ShowS
- data GhcException
- data Name
- data DynFlags = DynFlags {
- ghcMode :: GhcMode
- ghcLink :: GhcLink
- hscTarget :: HscTarget
- ghcNameVersion :: !GhcNameVersion
- fileSettings :: !FileSettings
- targetPlatform :: Platform
- toolSettings :: !ToolSettings
- platformMisc :: !PlatformMisc
- platformConstants :: PlatformConstants
- rawSettings :: [(String, String)]
- integerLibrary :: IntegerLibrary
- llvmConfig :: LlvmConfig
- verbosity :: Int
- optLevel :: Int
- debugLevel :: Int
- simplPhases :: Int
- maxSimplIterations :: Int
- ruleCheck :: Maybe String
- inlineCheck :: Maybe String
- strictnessBefore :: [Int]
- parMakeCount :: Maybe Int
- enableTimeStats :: Bool
- ghcHeapSize :: Maybe Int
- maxRelevantBinds :: Maybe Int
- maxValidHoleFits :: Maybe Int
- maxRefHoleFits :: Maybe Int
- refLevelHoleFits :: Maybe Int
- maxUncoveredPatterns :: Int
- maxPmCheckModels :: Int
- simplTickFactor :: Int
- specConstrThreshold :: Maybe Int
- specConstrCount :: Maybe Int
- specConstrRecursive :: Int
- binBlobThreshold :: Word
- liberateCaseThreshold :: Maybe Int
- floatLamArgs :: Maybe Int
- liftLamsRecArgs :: Maybe Int
- liftLamsNonRecArgs :: Maybe Int
- liftLamsKnown :: Bool
- cmmProcAlignment :: Maybe Int
- historySize :: Int
- importPaths :: [FilePath]
- mainModIs :: Module
- mainFunIs :: Maybe String
- reductionDepth :: IntWithInf
- solverIterations :: IntWithInf
- thisInstalledUnitId :: InstalledUnitId
- thisComponentId_ :: Maybe ComponentId
- thisUnitIdInsts_ :: Maybe [(ModuleName, Module)]
- ways :: [Way]
- buildTag :: String
- splitInfo :: Maybe (String, Int)
- objectDir :: Maybe String
- dylibInstallName :: Maybe String
- hiDir :: Maybe String
- hieDir :: Maybe String
- stubDir :: Maybe String
- dumpDir :: Maybe String
- objectSuf :: String
- hcSuf :: String
- hiSuf :: String
- hieSuf :: String
- canGenerateDynamicToo :: IORef Bool
- dynObjectSuf :: String
- dynHiSuf :: String
- outputFile :: Maybe String
- dynOutputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe FilePath
- dumpPrefixForce :: Maybe FilePath
- ldInputs :: [Option]
- includePaths :: IncludeSpecs
- libraryPaths :: [String]
- frameworkPaths :: [String]
- cmdlineFrameworks :: [String]
- rtsOpts :: Maybe String
- rtsOptsEnabled :: RtsOptsEnabled
- rtsOptsSuggestions :: Bool
- hpcDir :: String
- pluginModNames :: [ModuleName]
- pluginModNameOpts :: [(ModuleName, String)]
- frontendPluginOpts :: [String]
- cachedPlugins :: [LoadedPlugin]
- staticPlugins :: [StaticPlugin]
- hooks :: Hooks
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depIncludeCppDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- packageDBFlags :: [PackageDBFlag]
- ignorePackageFlags :: [IgnorePackageFlag]
- packageFlags :: [PackageFlag]
- pluginPackageFlags :: [PackageFlag]
- trustFlags :: [TrustFlag]
- packageEnv :: Maybe FilePath
- pkgDatabase :: Maybe [(FilePath, [PackageConfig])]
- pkgState :: PackageState
- filesToClean :: IORef FilesToClean
- dirsToClean :: IORef (Map FilePath FilePath)
- nextTempSuffix :: IORef Int
- generatedDumps :: IORef (Set FilePath)
- dumpFlags :: EnumSet DumpFlag
- generalFlags :: EnumSet GeneralFlag
- warningFlags :: EnumSet WarningFlag
- fatalWarningFlags :: EnumSet WarningFlag
- language :: Maybe Language
- safeHaskell :: SafeHaskellMode
- safeInfer :: Bool
- safeInferred :: Bool
- thOnLoc :: SrcSpan
- newDerivOnLoc :: SrcSpan
- overlapInstLoc :: SrcSpan
- incoherentOnLoc :: SrcSpan
- pkgTrustOnLoc :: SrcSpan
- warnSafeOnLoc :: SrcSpan
- warnUnsafeOnLoc :: SrcSpan
- trustworthyOnLoc :: SrcSpan
- extensions :: [OnOff Extension]
- extensionFlags :: EnumSet Extension
- ufCreationThreshold :: Int
- ufUseThreshold :: Int
- ufFunAppDiscount :: Int
- ufDictDiscount :: Int
- ufKeenessFactor :: Float
- ufDearOp :: Int
- ufVeryAggressive :: Bool
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- log_action :: LogAction
- flushOut :: FlushOut
- flushErr :: FlushErr
- ghcVersionFile :: Maybe FilePath
- haddockOptions :: Maybe String
- ghciScripts :: [String]
- pprUserLength :: Int
- pprCols :: Int
- useUnicode :: Bool
- useColor :: OverridingBool
- canUseColor :: Bool
- colScheme :: Scheme
- profAuto :: ProfAuto
- interactivePrint :: Maybe String
- nextWrapperNum :: IORef (ModuleEnv Int)
- sseVersion :: Maybe SseVersion
- bmiVersion :: Maybe BmiVersion
- avx :: Bool
- avx2 :: Bool
- avx512cd :: Bool
- avx512er :: Bool
- avx512f :: Bool
- avx512pf :: Bool
- rtldInfo :: IORef (Maybe LinkerInfo)
- rtccInfo :: IORef (Maybe CompilerInfo)
- maxInlineAllocSize :: Int
- maxInlineMemcpyInsns :: Int
- maxInlineMemsetInsns :: Int
- reverseErrors :: Bool
- maxErrors :: Maybe Int
- initialUnique :: Int
- uniqueIncrement :: Int
- cfgWeightInfo :: CfgWeights
- data GeneralFlag
- = Opt_DumpToFile
- | Opt_D_faststring_stats
- | Opt_D_dump_minimal_imports
- | Opt_DoCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_DoAnnotationLinting
- | Opt_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_NoTypeableBinds
- | Opt_WarnIsError
- | Opt_ShowWarnGroups
- | Opt_HideSourcePaths
- | Opt_PrintExplicitForalls
- | Opt_PrintExplicitKinds
- | Opt_PrintExplicitCoercions
- | Opt_PrintExplicitRuntimeReps
- | Opt_PrintEqualityRelations
- | Opt_PrintAxiomIncomps
- | Opt_PrintUnicodeSyntax
- | Opt_PrintExpandedSynonyms
- | Opt_PrintPotentialInstances
- | Opt_PrintTypecheckerElaboration
- | Opt_CallArity
- | Opt_Exitification
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_LateSpecialise
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_CrossModuleSpecialise
- | Opt_StaticArgumentTransformation
- | Opt_CSE
- | Opt_StgCSE
- | Opt_StgLiftLams
- | Opt_LiberateCase
- | Opt_SpecConstr
- | Opt_SpecConstrKeen
- | Opt_DoLambdaEtaExpansion
- | Opt_IgnoreAsserts
- | Opt_DoEtaReduction
- | Opt_CaseMerge
- | Opt_CaseFolding
- | Opt_UnboxStrictFields
- | Opt_UnboxSmallStrictFields
- | Opt_DictsCheap
- | Opt_EnableRewriteRules
- | Opt_EnableThSpliceWarnings
- | Opt_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmFillUndefWithGarbage
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_CmmElimCommonBlocks
- | Opt_AsmShortcutting
- | Opt_OmitYields
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_CfgBlocklayout
- | Opt_WeightlessBlocklayout
- | Opt_CprAnal
- | Opt_WorkerWrapper
- | Opt_SolveConstantDicts
- | Opt_AlignmentSanitisation
- | Opt_CatchBottoms
- | Opt_NumConstantFolding
- | Opt_SimplPreInlining
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_WriteHie
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_IgnoreOptimChanges
- | Opt_IgnoreHpcChanges
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_NoHsMain
- | Opt_SplitSections
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_HideAllPluginPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_IgnoreDotGhci
- | Opt_GhciSandbox
- | Opt_GhciHistory
- | Opt_GhciLeakCheck
- | Opt_ValidateHie
- | Opt_LocalGhciHistory
- | Opt_NoIt
- | Opt_HelpfulErrors
- | Opt_DeferTypeErrors
- | Opt_DeferTypedHoles
- | Opt_DeferOutOfScopeVariables
- | Opt_PIC
- | Opt_PIE
- | Opt_PICExecutable
- | Opt_ExternalDynamicRefs
- | Opt_SccProfilingOn
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_Hpc
- | Opt_FlatCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCode
- | Opt_ErrorSpans
- | Opt_DeferDiagnostics
- | Opt_DiagnosticsShowCaret
- | Opt_PprCaseAsLet
- | Opt_PprShowTicks
- | Opt_ShowHoleConstraints
- | Opt_ShowValidHoleFits
- | Opt_SortValidHoleFits
- | Opt_SortBySizeHoleFits
- | Opt_SortBySubsumHoleFits
- | Opt_AbstractRefHoleFits
- | Opt_UnclutterValidHoleFits
- | Opt_ShowTypeAppOfHoleFits
- | Opt_ShowTypeAppVarsOfHoleFits
- | Opt_ShowDocsOfHoleFits
- | Opt_ShowTypeOfHoleFits
- | Opt_ShowProvOfHoleFits
- | Opt_ShowMatchesOfHoleFits
- | Opt_ShowLoadedModules
- | Opt_HexWordLiterals
- | Opt_SuppressCoercions
- | Opt_SuppressVarKinds
- | Opt_SuppressModulePrefixes
- | Opt_SuppressTypeApplications
- | Opt_SuppressIdInfo
- | Opt_SuppressUnfoldings
- | Opt_SuppressTypeSignatures
- | Opt_SuppressUniques
- | Opt_SuppressStgExts
- | Opt_SuppressTicks
- | Opt_SuppressTimestamps
- | Opt_AutoLinkPackages
- | Opt_ImplicitImportQualified
- | Opt_KeepHscppFiles
- | Opt_KeepHiDiffs
- | Opt_KeepHcFiles
- | Opt_KeepSFiles
- | Opt_KeepTmpFiles
- | Opt_KeepRawTokenStream
- | Opt_KeepLlvmFiles
- | Opt_KeepHiFiles
- | Opt_KeepOFiles
- | Opt_BuildDynamicToo
- | Opt_DistrustAllPackages
- | Opt_PackageTrust
- | Opt_PluginTrustworthy
- | Opt_G_NoStateHack
- | Opt_G_NoOptCoercion
- gfinally :: ExceptionMonad m => m a -> m b -> m a
- gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a
- gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c
- type ForeignHValue = ForeignRef HValue
- data HValue
- coreModule :: DesugaredMod m => m -> ModGuts
- emptyFilesToClean :: FilesToClean
- isBmi2Enabled :: DynFlags -> Bool
- isBmiEnabled :: DynFlags -> Bool
- isAvx512pfEnabled :: DynFlags -> Bool
- isAvx512fEnabled :: DynFlags -> Bool
- isAvx512erEnabled :: DynFlags -> Bool
- isAvx512cdEnabled :: DynFlags -> Bool
- isAvx2Enabled :: DynFlags -> Bool
- isAvxEnabled :: DynFlags -> Bool
- isSse4_2Enabled :: DynFlags -> Bool
- isSse2Enabled :: DynFlags -> Bool
- isSseEnabled :: DynFlags -> Bool
- setUnsafeGlobalDynFlags :: DynFlags -> IO ()
- makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Located String])
- tARGET_MAX_WORD :: DynFlags -> Integer
- tARGET_MAX_INT :: DynFlags -> Integer
- tARGET_MIN_INT :: DynFlags -> Integer
- mAX_PTR_TAG :: DynFlags -> Int
- tAG_MASK :: DynFlags -> Int
- wordAlignment :: DynFlags -> Alignment
- wORD_SIZE_IN_BITS :: DynFlags -> Int
- bLOCK_SIZE_W :: DynFlags -> Int
- iLDV_STATE_USE :: DynFlags -> Integer
- iLDV_STATE_CREATE :: DynFlags -> Integer
- iLDV_CREATE_MASK :: DynFlags -> Integer
- lDV_SHIFT :: DynFlags -> Int
- dYNAMIC_BY_DEFAULT :: DynFlags -> Bool
- wORDS_BIGENDIAN :: DynFlags -> Bool
- tAG_BITS :: DynFlags -> Int
- bITMAP_BITS_SHIFT :: DynFlags -> Int
- cLONG_LONG_SIZE :: DynFlags -> Int
- cLONG_SIZE :: DynFlags -> Int
- cINT_SIZE :: DynFlags -> Int
- dOUBLE_SIZE :: DynFlags -> Int
- wORD_SIZE :: DynFlags -> Int
- aP_STACK_SPLIM :: DynFlags -> Int
- rESERVED_STACK_WORDS :: DynFlags -> Int
- rESERVED_C_STACK_BYTES :: DynFlags -> Int
- mAX_Real_Long_REG :: DynFlags -> Int
- mAX_Real_XMM_REG :: DynFlags -> Int
- mAX_Real_Double_REG :: DynFlags -> Int
- mAX_Real_Float_REG :: DynFlags -> Int
- mAX_Real_Vanilla_REG :: DynFlags -> Int
- mAX_XMM_REG :: DynFlags -> Int
- mAX_Long_REG :: DynFlags -> Int
- mAX_Double_REG :: DynFlags -> Int
- mAX_Float_REG :: DynFlags -> Int
- mAX_Vanilla_REG :: DynFlags -> Int
- mUT_ARR_PTRS_CARD_BITS :: DynFlags -> Int
- mAX_CHARLIKE :: DynFlags -> Int
- mIN_CHARLIKE :: DynFlags -> Int
- mAX_INTLIKE :: DynFlags -> Int
- mIN_INTLIKE :: DynFlags -> Int
- mIN_PAYLOAD_SIZE :: DynFlags -> Int
- mAX_SPEC_AP_SIZE :: DynFlags -> Int
- mAX_SPEC_SELECTEE_SIZE :: DynFlags -> Int
- oFFSET_StgFunInfoExtraRev_arity :: DynFlags -> Int
- sIZEOF_StgFunInfoExtraRev :: DynFlags -> Int
- oFFSET_StgFunInfoExtraFwd_arity :: DynFlags -> Int
- oFFSET_StgUpdateFrame_updatee :: DynFlags -> Int
- oFFSET_StgStack_stack :: DynFlags -> Int
- oFFSET_StgStack_sp :: DynFlags -> Int
- oFFSET_StgTSO_stackobj :: DynFlags -> Int
- oFFSET_StgTSO_cccs :: DynFlags -> Int
- oFFSET_StgTSO_alloc_limit :: DynFlags -> Int
- oFFSET_StgArrBytes_bytes :: DynFlags -> Int
- sIZEOF_StgArrBytes_NoHdr :: DynFlags -> Int
- oFFSET_StgSmallMutArrPtrs_ptrs :: DynFlags -> Int
- sIZEOF_StgSmallMutArrPtrs_NoHdr :: DynFlags -> Int
- oFFSET_StgMutArrPtrs_size :: DynFlags -> Int
- oFFSET_StgMutArrPtrs_ptrs :: DynFlags -> Int
- sIZEOF_StgMutArrPtrs_NoHdr :: DynFlags -> Int
- sIZEOF_StgUpdateFrame_NoHdr :: DynFlags -> Int
- oFFSET_StgEntCounter_entry_count :: DynFlags -> Int
- oFFSET_StgEntCounter_link :: DynFlags -> Int
- oFFSET_StgEntCounter_registeredp :: DynFlags -> Int
- oFFSET_StgEntCounter_allocd :: DynFlags -> Int
- oFFSET_StgEntCounter_allocs :: DynFlags -> Int
- sIZEOF_StgSMPThunkHeader :: DynFlags -> Int
- oFFSET_StgHeader_ldvw :: DynFlags -> Int
- oFFSET_StgHeader_ccs :: DynFlags -> Int
- oFFSET_CostCentreStack_scc_count :: DynFlags -> Int
- oFFSET_CostCentreStack_mem_alloc :: DynFlags -> Int
- sIZEOF_CostCentreStack :: DynFlags -> Int
- oFFSET_bdescr_flags :: DynFlags -> Int
- oFFSET_bdescr_blocks :: DynFlags -> Int
- oFFSET_bdescr_free :: DynFlags -> Int
- oFFSET_bdescr_start :: DynFlags -> Int
- oFFSET_Capability_r :: DynFlags -> Int
- oFFSET_stgGCFun :: DynFlags -> Int
- oFFSET_stgGCEnter1 :: DynFlags -> Int
- oFFSET_stgEagerBlackholeInfo :: DynFlags -> Int
- oFFSET_StgRegTable_rHpAlloc :: DynFlags -> Int
- oFFSET_StgRegTable_rCurrentNursery :: DynFlags -> Int
- oFFSET_StgRegTable_rCurrentTSO :: DynFlags -> Int
- oFFSET_StgRegTable_rCCCS :: DynFlags -> Int
- oFFSET_StgRegTable_rHpLim :: DynFlags -> Int
- oFFSET_StgRegTable_rHp :: DynFlags -> Int
- oFFSET_StgRegTable_rSpLim :: DynFlags -> Int
- oFFSET_StgRegTable_rSp :: DynFlags -> Int
- oFFSET_StgRegTable_rL1 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rD6 :: DynFlags -> Int
- oFFSET_StgRegTable_rD5 :: DynFlags -> Int
- oFFSET_StgRegTable_rD4 :: DynFlags -> Int
- oFFSET_StgRegTable_rD3 :: DynFlags -> Int
- oFFSET_StgRegTable_rD2 :: DynFlags -> Int
- oFFSET_StgRegTable_rD1 :: DynFlags -> Int
- oFFSET_StgRegTable_rF6 :: DynFlags -> Int
- oFFSET_StgRegTable_rF5 :: DynFlags -> Int
- oFFSET_StgRegTable_rF4 :: DynFlags -> Int
- oFFSET_StgRegTable_rF3 :: DynFlags -> Int
- oFFSET_StgRegTable_rF2 :: DynFlags -> Int
- oFFSET_StgRegTable_rF1 :: DynFlags -> Int
- oFFSET_StgRegTable_rR10 :: DynFlags -> Int
- oFFSET_StgRegTable_rR9 :: DynFlags -> Int
- oFFSET_StgRegTable_rR8 :: DynFlags -> Int
- oFFSET_StgRegTable_rR7 :: DynFlags -> Int
- oFFSET_StgRegTable_rR6 :: DynFlags -> Int
- oFFSET_StgRegTable_rR5 :: DynFlags -> Int
- oFFSET_StgRegTable_rR4 :: DynFlags -> Int
- oFFSET_StgRegTable_rR3 :: DynFlags -> Int
- oFFSET_StgRegTable_rR2 :: DynFlags -> Int
- oFFSET_StgRegTable_rR1 :: DynFlags -> Int
- tICKY_BIN_COUNT :: DynFlags -> Int
- bLOCKS_PER_MBLOCK :: DynFlags -> Int
- bLOCK_SIZE :: DynFlags -> Int
- pROF_HDR_SIZE :: DynFlags -> Int
- sTD_HDR_SIZE :: DynFlags -> Int
- cONTROL_GROUP_CONST_291 :: DynFlags -> Int
- compilerInfo :: DynFlags -> [(String, String)]
- picPOpts :: DynFlags -> [String]
- picCCOpts :: DynFlags -> [String]
- setTmpDir :: FilePath -> DynFlags -> DynFlags
- setFlagsFromEnvFile :: FilePath -> String -> DynP ()
- canonicalizeModuleIfHome :: DynFlags -> Module -> Module
- canonicalizeHomeModule :: DynFlags -> ModuleName -> Module
- setUnitId :: String -> DynFlags -> DynFlags
- unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
- setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
- addWay' :: Way -> DynFlags -> DynFlags
- dynamicGhc :: Bool
- rtsIsProfiled :: Bool
- glasgowExtsFlags :: [Extension]
- warningHierarchies :: [[String]]
- warningGroups :: [(String, [WarningFlag])]
- xFlags :: [FlagSpec Extension]
- supportedLanguagesAndExtensions :: PlatformMini -> [String]
- fLangFlags :: [FlagSpec Extension]
- fFlags :: [FlagSpec GeneralFlag]
- wWarningFlags :: [FlagSpec WarningFlag]
- flagsForCompletion :: Bool -> [String]
- flagsPackage :: [Flag (CmdLineP DynFlags)]
- flagsDynamic :: [Flag (CmdLineP DynFlags)]
- flagsAll :: [Flag (CmdLineP DynFlags)]
- allNonDeprecatedFlags :: [String]
- updateWays :: DynFlags -> DynFlags
- putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- parseDynamicFlagsFull :: MonadIO m => [Flag (CmdLineP DynFlags)] -> Bool -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- updOptLevel :: Int -> DynFlags -> DynFlags
- addPluginModuleName :: String -> DynFlags -> DynFlags
- thisPackage :: DynFlags -> UnitId
- thisUnitIdInsts :: DynFlags -> [(ModuleName, Module)]
- thisComponentId :: DynFlags -> ComponentId
- getVerbFlags :: DynFlags -> [String]
- getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
- unsafeFlagsForInfer :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
- unsafeFlags :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
- safeImplicitImpsReq :: DynFlags -> Bool
- safeDirectImpsReq :: DynFlags -> Bool
- safeImportsOn :: DynFlags -> Bool
- safeInferOn :: DynFlags -> Bool
- safeLanguageOn :: DynFlags -> Bool
- safeHaskellModeEnabled :: DynFlags -> Bool
- safeHaskellOn :: DynFlags -> Bool
- packageTrustOn :: DynFlags -> Bool
- dynFlagDependencies :: DynFlags -> [ModuleName]
- lang_set :: DynFlags -> Maybe Language -> DynFlags
- xopt_set_unlessExplSpec :: Extension -> (DynFlags -> Extension -> DynFlags) -> DynFlags -> DynFlags
- xopt_unset :: DynFlags -> Extension -> DynFlags
- xopt_set :: DynFlags -> Extension -> DynFlags
- xopt :: Extension -> DynFlags -> Bool
- wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
- wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags
- wopt_fatal :: WarningFlag -> DynFlags -> Bool
- wopt_unset :: DynFlags -> WarningFlag -> DynFlags
- wopt_set :: DynFlags -> WarningFlag -> DynFlags
- wopt :: WarningFlag -> DynFlags -> Bool
- gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
- gopt_set :: DynFlags -> GeneralFlag -> DynFlags
- gopt :: GeneralFlag -> DynFlags -> Bool
- dopt_unset :: DynFlags -> DumpFlag -> DynFlags
- dopt_set :: DynFlags -> DumpFlag -> DynFlags
- dopt :: DumpFlag -> DynFlags -> Bool
- hasNoOptCoercion :: DynFlags -> Bool
- hasNoStateHack :: DynFlags -> Bool
- languageExtensions :: Maybe Language -> [Extension]
- defaultFlushErr :: FlushErr
- defaultFlushOut :: FlushOut
- defaultLogActionHPutStrDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
- defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
- defaultLogAction :: LogAction
- defaultFatalMessager :: FatalMessager
- interpreterDynamic :: DynFlags -> Bool
- interpreterProfiled :: DynFlags -> Bool
- interpWays :: [Way]
- defaultWays :: Settings -> [Way]
- defaultDynFlags :: Settings -> LlvmConfig -> DynFlags
- initDynFlags :: DynFlags -> IO DynFlags
- dynamicOutputFile :: DynFlags -> FilePath -> FilePath
- dynamicTooMkDynamicDynFlags :: DynFlags -> DynFlags
- whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
- ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a
- whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
- wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayRTSOnly :: Way -> Bool
- mkBuildTag :: [Way] -> String
- positionIndependent :: DynFlags -> Bool
- defaultObjectTarget :: DynFlags -> HscTarget
- packageFlagsChanged :: DynFlags -> DynFlags -> Bool
- isNoLink :: GhcLink -> Bool
- isOneShot :: GhcMode -> Bool
- targetRetainsAllBindings :: HscTarget -> Bool
- isObjectTarget :: HscTarget -> Bool
- versionedFilePath :: DynFlags -> FilePath
- versionedAppDir :: DynFlags -> MaybeT IO FilePath
- tablesNextToCode :: DynFlags -> Bool
- opt_i :: DynFlags -> [String]
- opt_lc :: DynFlags -> [String]
- opt_lo :: DynFlags -> [String]
- opt_lcc :: DynFlags -> [String]
- opt_windres :: DynFlags -> [String]
- opt_lm :: DynFlags -> [String]
- opt_l :: DynFlags -> [String]
- opt_a :: DynFlags -> [String]
- opt_cxx :: DynFlags -> [String]
- opt_c :: DynFlags -> [String]
- opt_F :: DynFlags -> [String]
- opt_P_signature :: DynFlags -> ([String], Fingerprint)
- opt_P :: DynFlags -> [String]
- opt_L :: DynFlags -> [String]
- pgm_i :: DynFlags -> String
- pgm_lc :: DynFlags -> (String, [Option])
- pgm_lo :: DynFlags -> (String, [Option])
- pgm_ranlib :: DynFlags -> String
- pgm_ar :: DynFlags -> String
- pgm_lcc :: DynFlags -> (String, [Option])
- pgm_libtool :: DynFlags -> String
- pgm_windres :: DynFlags -> String
- pgm_T :: DynFlags -> String
- pgm_dll :: DynFlags -> (String, [Option])
- pgm_lm :: DynFlags -> (String, [Option])
- pgm_l :: DynFlags -> (String, [Option])
- pgm_a :: DynFlags -> (String, [Option])
- pgm_c :: DynFlags -> String
- pgm_F :: DynFlags -> String
- pgm_P :: DynFlags -> (String, [Option])
- pgm_L :: DynFlags -> String
- systemPackageConfig :: DynFlags -> FilePath
- extraGccViaCFlags :: DynFlags -> [String]
- tmpDir :: DynFlags -> String
- topDir :: DynFlags -> FilePath
- ghciUsagePath :: DynFlags -> FilePath
- ghcUsagePath :: DynFlags -> FilePath
- projectVersion :: DynFlags -> String
- programName :: DynFlags -> String
- settings :: DynFlags -> Settings
- backendMaintainsCfg :: DynFlags -> Bool
- flattenIncludes :: IncludeSpecs -> [String]
- addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
- addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
- optimisationFlags :: EnumSet GeneralFlag
- data WarnReason
- = NoReason
- | Reason !WarningFlag
- | ErrReason !(Maybe WarningFlag)
- data IncludeSpecs = IncludeSpecs {
- includePathsQuote :: [String]
- includePathsGlobal :: [String]
- data WarningFlag
- = Opt_WarnDuplicateExports
- | Opt_WarnDuplicateConstraints
- | Opt_WarnRedundantConstraints
- | Opt_WarnHiShadows
- | Opt_WarnImplicitPrelude
- | Opt_WarnIncompletePatterns
- | Opt_WarnIncompleteUniPatterns
- | Opt_WarnIncompletePatternsRecUpd
- | Opt_WarnOverflowedLiterals
- | Opt_WarnEmptyEnumerations
- | Opt_WarnMissingFields
- | Opt_WarnMissingImportList
- | Opt_WarnMissingMethods
- | Opt_WarnMissingSignatures
- | Opt_WarnMissingLocalSignatures
- | Opt_WarnNameShadowing
- | Opt_WarnOverlappingPatterns
- | Opt_WarnTypeDefaults
- | Opt_WarnMonomorphism
- | Opt_WarnUnusedTopBinds
- | Opt_WarnUnusedLocalBinds
- | Opt_WarnUnusedPatternBinds
- | Opt_WarnUnusedImports
- | Opt_WarnUnusedMatches
- | Opt_WarnUnusedTypePatterns
- | Opt_WarnUnusedForalls
- | Opt_WarnUnusedRecordWildcards
- | Opt_WarnRedundantRecordWildcards
- | Opt_WarnWarningsDeprecations
- | Opt_WarnDeprecatedFlags
- | Opt_WarnMissingMonadFailInstances
- | Opt_WarnSemigroup
- | Opt_WarnDodgyExports
- | Opt_WarnDodgyImports
- | Opt_WarnOrphans
- | Opt_WarnAutoOrphans
- | Opt_WarnIdentities
- | Opt_WarnTabs
- | Opt_WarnUnrecognisedPragmas
- | Opt_WarnDodgyForeignImports
- | Opt_WarnUnusedDoBind
- | Opt_WarnWrongDoBind
- | Opt_WarnAlternativeLayoutRuleTransitional
- | Opt_WarnUnsafe
- | Opt_WarnSafe
- | Opt_WarnTrustworthySafe
- | Opt_WarnMissedSpecs
- | Opt_WarnAllMissedSpecs
- | Opt_WarnUnsupportedCallingConventions
- | Opt_WarnUnsupportedLlvmVersion
- | Opt_WarnMissedExtraSharedLib
- | Opt_WarnInlineRuleShadowing
- | Opt_WarnTypedHoles
- | Opt_WarnPartialTypeSignatures
- | Opt_WarnMissingExportedSignatures
- | Opt_WarnUntickedPromotedConstructors
- | Opt_WarnDerivingTypeable
- | Opt_WarnDeferredTypeErrors
- | Opt_WarnDeferredOutOfScopeVariables
- | Opt_WarnNonCanonicalMonadInstances
- | Opt_WarnNonCanonicalMonadFailInstances
- | Opt_WarnNonCanonicalMonoidInstances
- | Opt_WarnMissingPatternSynonymSignatures
- | Opt_WarnUnrecognisedWarningFlags
- | Opt_WarnSimplifiableClassConstraints
- | Opt_WarnCPPUndef
- | Opt_WarnUnbangedStrictPatterns
- | Opt_WarnMissingHomeModules
- | Opt_WarnPartialFields
- | Opt_WarnMissingExportList
- | Opt_WarnInaccessibleCode
- | Opt_WarnStarIsType
- | Opt_WarnStarBinder
- | Opt_WarnImplicitKindVars
- | Opt_WarnSpaceAfterBang
- | Opt_WarnMissingDerivingStrategies
- | Opt_WarnPrepositiveQualifiedModule
- | Opt_WarnUnusedPackages
- | Opt_WarnInferredSafeImports
- | Opt_WarnMissingSafeHaskellMode
- | Opt_WarnCompatUnqualifiedImports
- | Opt_WarnDerivingDefaults
- data Language
- data SafeHaskellMode
- data CfgWeights = CFGWeights {}
- class HasDynFlags (m :: Type -> Type) where
- getDynFlags :: m DynFlags
- class ContainsDynFlags t where
- extractDynFlags :: t -> DynFlags
- data ProfAuto
- data LlvmTarget = LlvmTarget {
- lDataLayout :: String
- lCPU :: String
- lAttributes :: [String]
- data LlvmConfig = LlvmConfig {
- llvmTargets :: [(String, LlvmTarget)]
- llvmPasses :: [(Int, String)]
- data HscTarget
- data GhcMode
- data GhcLink
- data PackageArg
- data ModRenaming = ModRenaming {}
- newtype IgnorePackageFlag = IgnorePackage String
- data TrustFlag
- data PackageFlag = HidePackage String
- data PackageDBFlag
- data DynLibLoader
- data RtsOptsEnabled
- data Way
- type FatalMessager = String -> IO ()
- type LogAction = DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- newtype FlushOut = FlushOut (IO ())
- newtype FlushErr = FlushErr (IO ())
- data FlagSpec flag = FlagSpec {
- flagSpecName :: String
- flagSpecFlag :: flag
- flagSpecAction :: TurnOnFlag -> DynP ()
- flagSpecGhcMode :: GhcFlagMode
- data PkgConfRef
- data LinkerInfo
- data CompilerInfo
- = GCC
- | Clang
- | AppleClang
- | AppleClang51
- | UnknownCC
- data FilesToClean = FilesToClean {
- ftcGhcSession :: !(Set FilePath)
- ftcCurrentModule :: !(Set FilePath)
- sGhcRtsWithLibdw :: Settings -> Bool
- sGhcDebugged :: Settings -> Bool
- sGhcThreaded :: Settings -> Bool
- sLibFFI :: Settings -> Bool
- sLeadingUnderscore :: Settings -> Bool
- sTablesNextToCode :: Settings -> Bool
- sGhcRTSWays :: Settings -> String
- sGhcWithSMP :: Settings -> Bool
- sGhcWithNativeCodeGen :: Settings -> Bool
- sGhcWithInterpreter :: Settings -> Bool
- sIntegerLibraryType :: Settings -> IntegerLibrary
- sIntegerLibrary :: Settings -> String
- sTargetPlatformString :: Settings -> String
- sExtraGccViaCFlags :: Settings -> [String]
- sOpt_i :: Settings -> [String]
- sOpt_lcc :: Settings -> [String]
- sOpt_lc :: Settings -> [String]
- sOpt_lo :: Settings -> [String]
- sOpt_windres :: Settings -> [String]
- sOpt_lm :: Settings -> [String]
- sOpt_l :: Settings -> [String]
- sOpt_a :: Settings -> [String]
- sOpt_cxx :: Settings -> [String]
- sOpt_c :: Settings -> [String]
- sOpt_F :: Settings -> [String]
- sOpt_P_fingerprint :: Settings -> Fingerprint
- sOpt_P :: Settings -> [String]
- sOpt_L :: Settings -> [String]
- sPgm_i :: Settings -> String
- sPgm_lcc :: Settings -> (String, [Option])
- sPgm_lc :: Settings -> (String, [Option])
- sPgm_lo :: Settings -> (String, [Option])
- sPgm_ranlib :: Settings -> String
- sPgm_ar :: Settings -> String
- sPgm_libtool :: Settings -> String
- sPgm_windres :: Settings -> String
- sPgm_T :: Settings -> String
- sPgm_dll :: Settings -> (String, [Option])
- sPgm_lm :: Settings -> (String, [Option])
- sPgm_l :: Settings -> (String, [Option])
- sPgm_a :: Settings -> (String, [Option])
- sPgm_c :: Settings -> String
- sPgm_F :: Settings -> String
- sPgm_P :: Settings -> (String, [Option])
- sPgm_L :: Settings -> String
- sGccSupportsNoPie :: Settings -> Bool
- sLdIsGnuLd :: Settings -> Bool
- sLdSupportsFilelist :: Settings -> Bool
- sLdSupportsBuildId :: Settings -> Bool
- sLdSupportsCompactUnwind :: Settings -> Bool
- sSystemPackageConfig :: Settings -> FilePath
- sTmpDir :: Settings -> String
- sTopDir :: Settings -> FilePath
- sToolDir :: Settings -> Maybe FilePath
- sGhciUsagePath :: Settings -> FilePath
- sGhcUsagePath :: Settings -> FilePath
- sProjectVersion :: Settings -> String
- sProgramName :: Settings -> String
- data Settings = Settings {}
- data PlatformConstants = PlatformConstants {
- pc_CONTROL_GROUP_CONST_291 :: Int
- pc_STD_HDR_SIZE :: Int
- pc_PROF_HDR_SIZE :: Int
- pc_BLOCK_SIZE :: Int
- pc_BLOCKS_PER_MBLOCK :: Int
- pc_TICKY_BIN_COUNT :: Int
- pc_OFFSET_StgRegTable_rR1 :: Int
- pc_OFFSET_StgRegTable_rR2 :: Int
- pc_OFFSET_StgRegTable_rR3 :: Int
- pc_OFFSET_StgRegTable_rR4 :: Int
- pc_OFFSET_StgRegTable_rR5 :: Int
- pc_OFFSET_StgRegTable_rR6 :: Int
- pc_OFFSET_StgRegTable_rR7 :: Int
- pc_OFFSET_StgRegTable_rR8 :: Int
- pc_OFFSET_StgRegTable_rR9 :: Int
- pc_OFFSET_StgRegTable_rR10 :: Int
- pc_OFFSET_StgRegTable_rF1 :: Int
- pc_OFFSET_StgRegTable_rF2 :: Int
- pc_OFFSET_StgRegTable_rF3 :: Int
- pc_OFFSET_StgRegTable_rF4 :: Int
- pc_OFFSET_StgRegTable_rF5 :: Int
- pc_OFFSET_StgRegTable_rF6 :: Int
- pc_OFFSET_StgRegTable_rD1 :: Int
- pc_OFFSET_StgRegTable_rD2 :: Int
- pc_OFFSET_StgRegTable_rD3 :: Int
- pc_OFFSET_StgRegTable_rD4 :: Int
- pc_OFFSET_StgRegTable_rD5 :: Int
- pc_OFFSET_StgRegTable_rD6 :: Int
- pc_OFFSET_StgRegTable_rXMM1 :: Int
- pc_OFFSET_StgRegTable_rXMM2 :: Int
- pc_OFFSET_StgRegTable_rXMM3 :: Int
- pc_OFFSET_StgRegTable_rXMM4 :: Int
- pc_OFFSET_StgRegTable_rXMM5 :: Int
- pc_OFFSET_StgRegTable_rXMM6 :: Int
- pc_OFFSET_StgRegTable_rYMM1 :: Int
- pc_OFFSET_StgRegTable_rYMM2 :: Int
- pc_OFFSET_StgRegTable_rYMM3 :: Int
- pc_OFFSET_StgRegTable_rYMM4 :: Int
- pc_OFFSET_StgRegTable_rYMM5 :: Int
- pc_OFFSET_StgRegTable_rYMM6 :: Int
- pc_OFFSET_StgRegTable_rZMM1 :: Int
- pc_OFFSET_StgRegTable_rZMM2 :: Int
- pc_OFFSET_StgRegTable_rZMM3 :: Int
- pc_OFFSET_StgRegTable_rZMM4 :: Int
- pc_OFFSET_StgRegTable_rZMM5 :: Int
- pc_OFFSET_StgRegTable_rZMM6 :: Int
- pc_OFFSET_StgRegTable_rL1 :: Int
- pc_OFFSET_StgRegTable_rSp :: Int
- pc_OFFSET_StgRegTable_rSpLim :: Int
- pc_OFFSET_StgRegTable_rHp :: Int
- pc_OFFSET_StgRegTable_rHpLim :: Int
- pc_OFFSET_StgRegTable_rCCCS :: Int
- pc_OFFSET_StgRegTable_rCurrentTSO :: Int
- pc_OFFSET_StgRegTable_rCurrentNursery :: Int
- pc_OFFSET_StgRegTable_rHpAlloc :: Int
- pc_OFFSET_stgEagerBlackholeInfo :: Int
- pc_OFFSET_stgGCEnter1 :: Int
- pc_OFFSET_stgGCFun :: Int
- pc_OFFSET_Capability_r :: Int
- pc_OFFSET_bdescr_start :: Int
- pc_OFFSET_bdescr_free :: Int
- pc_OFFSET_bdescr_blocks :: Int
- pc_OFFSET_bdescr_flags :: Int
- pc_SIZEOF_CostCentreStack :: Int
- pc_OFFSET_CostCentreStack_mem_alloc :: Int
- pc_REP_CostCentreStack_mem_alloc :: Int
- pc_OFFSET_CostCentreStack_scc_count :: Int
- pc_REP_CostCentreStack_scc_count :: Int
- pc_OFFSET_StgHeader_ccs :: Int
- pc_OFFSET_StgHeader_ldvw :: Int
- pc_SIZEOF_StgSMPThunkHeader :: Int
- pc_OFFSET_StgEntCounter_allocs :: Int
- pc_REP_StgEntCounter_allocs :: Int
- pc_OFFSET_StgEntCounter_allocd :: Int
- pc_REP_StgEntCounter_allocd :: Int
- pc_OFFSET_StgEntCounter_registeredp :: Int
- pc_OFFSET_StgEntCounter_link :: Int
- pc_OFFSET_StgEntCounter_entry_count :: Int
- pc_SIZEOF_StgUpdateFrame_NoHdr :: Int
- pc_SIZEOF_StgMutArrPtrs_NoHdr :: Int
- pc_OFFSET_StgMutArrPtrs_ptrs :: Int
- pc_OFFSET_StgMutArrPtrs_size :: Int
- pc_SIZEOF_StgSmallMutArrPtrs_NoHdr :: Int
- pc_OFFSET_StgSmallMutArrPtrs_ptrs :: Int
- pc_SIZEOF_StgArrBytes_NoHdr :: Int
- pc_OFFSET_StgArrBytes_bytes :: Int
- pc_OFFSET_StgTSO_alloc_limit :: Int
- pc_OFFSET_StgTSO_cccs :: Int
- pc_OFFSET_StgTSO_stackobj :: Int
- pc_OFFSET_StgStack_sp :: Int
- pc_OFFSET_StgStack_stack :: Int
- pc_OFFSET_StgUpdateFrame_updatee :: Int
- pc_OFFSET_StgFunInfoExtraFwd_arity :: Int
- pc_REP_StgFunInfoExtraFwd_arity :: Int
- pc_SIZEOF_StgFunInfoExtraRev :: Int
- pc_OFFSET_StgFunInfoExtraRev_arity :: Int
- pc_REP_StgFunInfoExtraRev_arity :: Int
- pc_MAX_SPEC_SELECTEE_SIZE :: Int
- pc_MAX_SPEC_AP_SIZE :: Int
- pc_MIN_PAYLOAD_SIZE :: Int
- pc_MIN_INTLIKE :: Int
- pc_MAX_INTLIKE :: Int
- pc_MIN_CHARLIKE :: Int
- pc_MAX_CHARLIKE :: Int
- pc_MUT_ARR_PTRS_CARD_BITS :: Int
- pc_MAX_Vanilla_REG :: Int
- pc_MAX_Float_REG :: Int
- pc_MAX_Double_REG :: Int
- pc_MAX_Long_REG :: Int
- pc_MAX_XMM_REG :: Int
- pc_MAX_Real_Vanilla_REG :: Int
- pc_MAX_Real_Float_REG :: Int
- pc_MAX_Real_Double_REG :: Int
- pc_MAX_Real_XMM_REG :: Int
- pc_MAX_Real_Long_REG :: Int
- pc_RESERVED_C_STACK_BYTES :: Int
- pc_RESERVED_STACK_WORDS :: Int
- pc_AP_STACK_SPLIM :: Int
- pc_WORD_SIZE :: Int
- pc_DOUBLE_SIZE :: Int
- pc_CINT_SIZE :: Int
- pc_CLONG_SIZE :: Int
- pc_CLONG_LONG_SIZE :: Int
- pc_BITMAP_BITS_SHIFT :: Int
- pc_TAG_BITS :: Int
- pc_WORDS_BIGENDIAN :: Bool
- pc_DYNAMIC_BY_DEFAULT :: Bool
- pc_LDV_SHIFT :: Int
- pc_ILDV_CREATE_MASK :: Integer
- pc_ILDV_STATE_CREATE :: Integer
- pc_ILDV_STATE_USE :: Integer
- showOpt :: Option -> String
- data Option
- unsafeGlobalDynFlags :: DynFlags
- useUnicodeSyntax :: DynFlags -> Bool
- useStarIsType :: DynFlags -> Bool
- shouldUseColor :: DynFlags -> Bool
- shouldUseHexWordLiterals :: DynFlags -> Bool
- hasPprDebug :: DynFlags -> Bool
- hasNoDebugOutput :: DynFlags -> Bool
- data DynFlags = DynFlags {
- ghcMode :: GhcMode
- ghcLink :: GhcLink
- hscTarget :: HscTarget
- ghcNameVersion :: !GhcNameVersion
- fileSettings :: !FileSettings
- targetPlatform :: Platform
- toolSettings :: !ToolSettings
- platformMisc :: !PlatformMisc
- platformConstants :: PlatformConstants
- rawSettings :: [(String, String)]
- integerLibrary :: IntegerLibrary
- llvmConfig :: LlvmConfig
- verbosity :: Int
- optLevel :: Int
- debugLevel :: Int
- simplPhases :: Int
- maxSimplIterations :: Int
- ruleCheck :: Maybe String
- inlineCheck :: Maybe String
- strictnessBefore :: [Int]
- parMakeCount :: Maybe Int
- enableTimeStats :: Bool
- ghcHeapSize :: Maybe Int
- maxRelevantBinds :: Maybe Int
- maxValidHoleFits :: Maybe Int
- maxRefHoleFits :: Maybe Int
- refLevelHoleFits :: Maybe Int
- maxUncoveredPatterns :: Int
- maxPmCheckModels :: Int
- simplTickFactor :: Int
- specConstrThreshold :: Maybe Int
- specConstrCount :: Maybe Int
- specConstrRecursive :: Int
- binBlobThreshold :: Word
- liberateCaseThreshold :: Maybe Int
- floatLamArgs :: Maybe Int
- liftLamsRecArgs :: Maybe Int
- liftLamsNonRecArgs :: Maybe Int
- liftLamsKnown :: Bool
- cmmProcAlignment :: Maybe Int
- historySize :: Int
- importPaths :: [FilePath]
- mainModIs :: Module
- mainFunIs :: Maybe String
- reductionDepth :: IntWithInf
- solverIterations :: IntWithInf
- thisInstalledUnitId :: InstalledUnitId
- thisComponentId_ :: Maybe ComponentId
- thisUnitIdInsts_ :: Maybe [(ModuleName, Module)]
- ways :: [Way]
- buildTag :: String
- splitInfo :: Maybe (String, Int)
- objectDir :: Maybe String
- dylibInstallName :: Maybe String
- hiDir :: Maybe String
- hieDir :: Maybe String
- stubDir :: Maybe String
- dumpDir :: Maybe String
- objectSuf :: String
- hcSuf :: String
- hiSuf :: String
- hieSuf :: String
- canGenerateDynamicToo :: IORef Bool
- dynObjectSuf :: String
- dynHiSuf :: String
- outputFile :: Maybe String
- dynOutputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe FilePath
- dumpPrefixForce :: Maybe FilePath
- ldInputs :: [Option]
- includePaths :: IncludeSpecs
- libraryPaths :: [String]
- frameworkPaths :: [String]
- cmdlineFrameworks :: [String]
- rtsOpts :: Maybe String
- rtsOptsEnabled :: RtsOptsEnabled
- rtsOptsSuggestions :: Bool
- hpcDir :: String
- pluginModNames :: [ModuleName]
- pluginModNameOpts :: [(ModuleName, String)]
- frontendPluginOpts :: [String]
- cachedPlugins :: [LoadedPlugin]
- staticPlugins :: [StaticPlugin]
- hooks :: Hooks
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depIncludeCppDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- packageDBFlags :: [PackageDBFlag]
- ignorePackageFlags :: [IgnorePackageFlag]
- packageFlags :: [PackageFlag]
- pluginPackageFlags :: [PackageFlag]
- trustFlags :: [TrustFlag]
- packageEnv :: Maybe FilePath
- pkgDatabase :: Maybe [(FilePath, [PackageConfig])]
- pkgState :: PackageState
- filesToClean :: IORef FilesToClean
- dirsToClean :: IORef (Map FilePath FilePath)
- nextTempSuffix :: IORef Int
- generatedDumps :: IORef (Set FilePath)
- dumpFlags :: EnumSet DumpFlag
- generalFlags :: EnumSet GeneralFlag
- warningFlags :: EnumSet WarningFlag
- fatalWarningFlags :: EnumSet WarningFlag
- language :: Maybe Language
- safeHaskell :: SafeHaskellMode
- safeInfer :: Bool
- safeInferred :: Bool
- thOnLoc :: SrcSpan
- newDerivOnLoc :: SrcSpan
- overlapInstLoc :: SrcSpan
- incoherentOnLoc :: SrcSpan
- pkgTrustOnLoc :: SrcSpan
- warnSafeOnLoc :: SrcSpan
- warnUnsafeOnLoc :: SrcSpan
- trustworthyOnLoc :: SrcSpan
- extensions :: [OnOff Extension]
- extensionFlags :: EnumSet Extension
- ufCreationThreshold :: Int
- ufUseThreshold :: Int
- ufFunAppDiscount :: Int
- ufDictDiscount :: Int
- ufKeenessFactor :: Float
- ufDearOp :: Int
- ufVeryAggressive :: Bool
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- log_action :: LogAction
- flushOut :: FlushOut
- flushErr :: FlushErr
- ghcVersionFile :: Maybe FilePath
- haddockOptions :: Maybe String
- ghciScripts :: [String]
- pprUserLength :: Int
- pprCols :: Int
- useUnicode :: Bool
- useColor :: OverridingBool
- canUseColor :: Bool
- colScheme :: Scheme
- profAuto :: ProfAuto
- interactivePrint :: Maybe String
- nextWrapperNum :: IORef (ModuleEnv Int)
- sseVersion :: Maybe SseVersion
- bmiVersion :: Maybe BmiVersion
- avx :: Bool
- avx2 :: Bool
- avx512cd :: Bool
- avx512er :: Bool
- avx512f :: Bool
- avx512pf :: Bool
- rtldInfo :: IORef (Maybe LinkerInfo)
- rtccInfo :: IORef (Maybe CompilerInfo)
- maxInlineAllocSize :: Int
- maxInlineMemcpyInsns :: Int
- maxInlineMemsetInsns :: Int
- reverseErrors :: Bool
- maxErrors :: Maybe Int
- initialUnique :: Int
- uniqueIncrement :: Int
- cfgWeightInfo :: CfgWeights
- data DumpFlag
- = Opt_D_dump_cmm
- | Opt_D_dump_cmm_from_stg
- | Opt_D_dump_cmm_raw
- | Opt_D_dump_cmm_verbose_by_proc
- | Opt_D_dump_cmm_verbose
- | Opt_D_dump_cmm_cfg
- | Opt_D_dump_cmm_cbe
- | Opt_D_dump_cmm_switch
- | Opt_D_dump_cmm_proc
- | Opt_D_dump_cmm_sp
- | Opt_D_dump_cmm_sink
- | Opt_D_dump_cmm_caf
- | Opt_D_dump_cmm_procmap
- | Opt_D_dump_cmm_split
- | Opt_D_dump_cmm_info
- | Opt_D_dump_cmm_cps
- | Opt_D_dump_cfg_weights
- | Opt_D_dump_asm
- | Opt_D_dump_asm_native
- | Opt_D_dump_asm_liveness
- | Opt_D_dump_asm_regalloc
- | Opt_D_dump_asm_regalloc_stages
- | Opt_D_dump_asm_conflicts
- | Opt_D_dump_asm_stats
- | Opt_D_dump_asm_expanded
- | Opt_D_dump_llvm
- | Opt_D_dump_core_stats
- | Opt_D_dump_deriv
- | Opt_D_dump_ds
- | Opt_D_dump_ds_preopt
- | Opt_D_dump_foreign
- | Opt_D_dump_inlinings
- | Opt_D_dump_rule_firings
- | Opt_D_dump_rule_rewrites
- | Opt_D_dump_simpl_trace
- | Opt_D_dump_occur_anal
- | Opt_D_dump_parsed
- | Opt_D_dump_parsed_ast
- | Opt_D_dump_rn
- | Opt_D_dump_rn_ast
- | Opt_D_dump_simpl
- | Opt_D_dump_simpl_iterations
- | Opt_D_dump_spec
- | Opt_D_dump_prep
- | Opt_D_dump_stg
- | Opt_D_dump_stg_unarised
- | Opt_D_dump_stg_final
- | Opt_D_dump_call_arity
- | Opt_D_dump_exitify
- | Opt_D_dump_stranal
- | Opt_D_dump_str_signatures
- | Opt_D_dump_tc
- | Opt_D_dump_tc_ast
- | Opt_D_dump_types
- | Opt_D_dump_rules
- | Opt_D_dump_cse
- | Opt_D_dump_worker_wrapper
- | Opt_D_dump_rn_trace
- | Opt_D_dump_rn_stats
- | Opt_D_dump_opt_cmm
- | Opt_D_dump_simpl_stats
- | Opt_D_dump_cs_trace
- | Opt_D_dump_tc_trace
- | Opt_D_dump_ec_trace
- | Opt_D_dump_if_trace
- | Opt_D_dump_vt_trace
- | Opt_D_dump_splices
- | Opt_D_th_dec_file
- | Opt_D_dump_BCOs
- | Opt_D_dump_ticked
- | Opt_D_dump_rtti
- | Opt_D_source_stats
- | Opt_D_verbose_stg2stg
- | Opt_D_dump_hi
- | Opt_D_dump_hi_diffs
- | Opt_D_dump_mod_cycles
- | Opt_D_dump_mod_map
- | Opt_D_dump_timings
- | Opt_D_dump_view_pattern_commoning
- | Opt_D_verbose_core2core
- | Opt_D_dump_debug
- | Opt_D_dump_json
- | Opt_D_ppr_debug
- | Opt_D_no_debug_output
- data GeneralFlag
- = Opt_DumpToFile
- | Opt_D_faststring_stats
- | Opt_D_dump_minimal_imports
- | Opt_DoCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_DoAnnotationLinting
- | Opt_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_NoTypeableBinds
- | Opt_WarnIsError
- | Opt_ShowWarnGroups
- | Opt_HideSourcePaths
- | Opt_PrintExplicitForalls
- | Opt_PrintExplicitKinds
- | Opt_PrintExplicitCoercions
- | Opt_PrintExplicitRuntimeReps
- | Opt_PrintEqualityRelations
- | Opt_PrintAxiomIncomps
- | Opt_PrintUnicodeSyntax
- | Opt_PrintExpandedSynonyms
- | Opt_PrintPotentialInstances
- | Opt_PrintTypecheckerElaboration
- | Opt_CallArity
- | Opt_Exitification
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_LateSpecialise
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_CrossModuleSpecialise
- | Opt_StaticArgumentTransformation
- | Opt_CSE
- | Opt_StgCSE
- | Opt_StgLiftLams
- | Opt_LiberateCase
- | Opt_SpecConstr
- | Opt_SpecConstrKeen
- | Opt_DoLambdaEtaExpansion
- | Opt_IgnoreAsserts
- | Opt_DoEtaReduction
- | Opt_CaseMerge
- | Opt_CaseFolding
- | Opt_UnboxStrictFields
- | Opt_UnboxSmallStrictFields
- | Opt_DictsCheap
- | Opt_EnableRewriteRules
- | Opt_EnableThSpliceWarnings
- | Opt_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmFillUndefWithGarbage
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_CmmElimCommonBlocks
- | Opt_AsmShortcutting
- | Opt_OmitYields
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_CfgBlocklayout
- | Opt_WeightlessBlocklayout
- | Opt_CprAnal
- | Opt_WorkerWrapper
- | Opt_SolveConstantDicts
- | Opt_AlignmentSanitisation
- | Opt_CatchBottoms
- | Opt_NumConstantFolding
- | Opt_SimplPreInlining
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_WriteHie
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_IgnoreOptimChanges
- | Opt_IgnoreHpcChanges
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_NoHsMain
- | Opt_SplitSections
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_HideAllPluginPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_IgnoreDotGhci
- | Opt_GhciSandbox
- | Opt_GhciHistory
- | Opt_GhciLeakCheck
- | Opt_ValidateHie
- | Opt_LocalGhciHistory
- | Opt_NoIt
- | Opt_HelpfulErrors
- | Opt_DeferTypeErrors
- | Opt_DeferTypedHoles
- | Opt_DeferOutOfScopeVariables
- | Opt_PIC
- | Opt_PIE
- | Opt_PICExecutable
- | Opt_ExternalDynamicRefs
- | Opt_SccProfilingOn
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_Hpc
- | Opt_FlatCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCode
- | Opt_ErrorSpans
- | Opt_DeferDiagnostics
- | Opt_DiagnosticsShowCaret
- | Opt_PprCaseAsLet
- | Opt_PprShowTicks
- | Opt_ShowHoleConstraints
- | Opt_ShowValidHoleFits
- | Opt_SortValidHoleFits
- | Opt_SortBySizeHoleFits
- | Opt_SortBySubsumHoleFits
- | Opt_AbstractRefHoleFits
- | Opt_UnclutterValidHoleFits
- | Opt_ShowTypeAppOfHoleFits
- | Opt_ShowTypeAppVarsOfHoleFits
- | Opt_ShowDocsOfHoleFits
- | Opt_ShowTypeOfHoleFits
- | Opt_ShowProvOfHoleFits
- | Opt_ShowMatchesOfHoleFits
- | Opt_ShowLoadedModules
- | Opt_HexWordLiterals
- | Opt_SuppressCoercions
- | Opt_SuppressVarKinds
- | Opt_SuppressModulePrefixes
- | Opt_SuppressTypeApplications
- | Opt_SuppressIdInfo
- | Opt_SuppressUnfoldings
- | Opt_SuppressTypeSignatures
- | Opt_SuppressUniques
- | Opt_SuppressStgExts
- | Opt_SuppressTicks
- | Opt_SuppressTimestamps
- | Opt_AutoLinkPackages
- | Opt_ImplicitImportQualified
- | Opt_KeepHscppFiles
- | Opt_KeepHiDiffs
- | Opt_KeepHcFiles
- | Opt_KeepSFiles
- | Opt_KeepTmpFiles
- | Opt_KeepRawTokenStream
- | Opt_KeepLlvmFiles
- | Opt_KeepHiFiles
- | Opt_KeepOFiles
- | Opt_BuildDynamicToo
- | Opt_DistrustAllPackages
- | Opt_PackageTrust
- | Opt_PluginTrustworthy
- | Opt_G_NoStateHack
- | Opt_G_NoOptCoercion
- data FileSettings = FileSettings {}
- data GhcNameVersion = GhcNameVersion {}
- data IntegerLibrary
- data PlatformMisc = PlatformMisc {
- platformMisc_targetPlatformString :: String
- platformMisc_integerLibrary :: String
- platformMisc_integerLibraryType :: IntegerLibrary
- platformMisc_ghcWithInterpreter :: Bool
- platformMisc_ghcWithNativeCodeGen :: Bool
- platformMisc_ghcWithSMP :: Bool
- platformMisc_ghcRTSWays :: String
- platformMisc_tablesNextToCode :: Bool
- platformMisc_leadingUnderscore :: Bool
- platformMisc_libFFI :: Bool
- platformMisc_ghcThreaded :: Bool
- platformMisc_ghcDebugged :: Bool
- platformMisc_ghcRtsWithLibdw :: Bool
- platformMisc_llvmTarget :: String
- initializePlugins :: HscEnv -> DynFlags -> IO DynFlags
- applyPluginsParsedResultAction :: HscEnv -> DynFlags -> ModSummary -> ApiAnns -> ParsedSource -> IO ParsedSource
- module Compat.HieTypes
- module Compat.HieUtils
Documentation
data HieFileResult #
GHC builds up a wealth of information about Haskell source as it compiles it.
.hie
files are a way of persisting some of this information to disk so that
external tools that need to work with haskell source don't need to parse,
typecheck, and rename all over again. These files contain:
a simplified AST
- nodes are annotated with source positions and types
- identifiers are annotated with scope information
- the raw bytes of the initial Haskell source
Besides saving compilation cycles, .hie
files also offer a more stable
interface than the GHC API.
HieFile | |
|
newtype NameCacheUpdater #
A function that atomically updates the name cache given a modifier function. The second result of the modifier function will be the result of the IO action.
NCU | |
|
mkHieFile :: ModSummary -> TcGblEnv -> RenamedSource -> ByteString -> Hsc HieFile #
Construct an HieFile
from the outputs of the typechecker.
mkHieFile' :: ModSummary -> [AvailInfo] -> HieASTs Type -> ByteString -> Hsc HieFile Source #
type RefMap = Map Identifier [(Span, IdentifierDetails Type)] Source #
writeHieFile :: FilePath -> HieFile -> IO () #
Write a HieFile
to the given FilePath
, with a proper header and
symbol tables for Name
s and FastString
s
readHieFile :: NameCacheUpdater -> FilePath -> IO HieFileResult #
dontWriteHieFiles :: DynFlags -> DynFlags Source #
hPutStringBuffer :: Handle -> StringBuffer -> IO () #
getModuleHash :: ModIface -> Fingerprint Source #
getPackageName :: DynFlags -> InstalledUnitId -> Maybe PackageName Source #
setUpTypedHoles :: DynFlags -> DynFlags Source #
data ModLocation #
Module Location
Where a module lives on the file system: the actual locations of the .hs, .hi and .o files, if we have them
Instances
Show ModLocation | |
Defined in Module showsPrec :: Int -> ModLocation -> ShowS # show :: ModLocation -> String # showList :: [ModLocation] -> ShowS # | |
Outputable ModLocation | |
Defined in Module ppr :: ModLocation -> SDoc # pprPrec :: Rational -> ModLocation -> SDoc # |
addBootSuffix :: FilePath -> FilePath #
Add the -boot
suffix to .hs, .hi and .o files
pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> ModLocation Source #
pattern ExposePackage :: String -> PackageArg -> ModRenaming -> PackageFlag Source #
type HasSrcSpan = HasSrcSpan Source #
getLoc :: HasSrcSpan a => a -> SrcSpan Source #
Records what things are "available", i.e. in scope
Instances
Eq AvailInfo | Used when deciding if the interface has changed |
Data AvailInfo | |
Defined in Avail gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AvailInfo -> c AvailInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AvailInfo # toConstr :: AvailInfo -> Constr # dataTypeOf :: AvailInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AvailInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AvailInfo) # gmapT :: (forall b. Data b => b -> b) -> AvailInfo -> AvailInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AvailInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AvailInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> AvailInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AvailInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AvailInfo -> m AvailInfo # | |
Binary AvailInfo | |
Outputable AvailInfo | |
tcg_exports :: TcGblEnv -> [AvailInfo] #
What is exported
module GHC.Hs.Extension
module LinkerTypes
:: String | Haskell module source text (full Unicode is supported) |
-> DynFlags | the flags |
-> FilePath | the filename (for source locations) |
-> (WarningMessages, Either ErrorMessages (Located (HsModule GhcPs))) |
A pure interface to the module parser.
getHistorySpan :: GhcMonad m => History -> m SrcSpan #
getGHCiMonad :: GhcMonad m => m Name #
Get the monad GHCi lifts user statements into.
setGHCiMonad :: GhcMonad m => String -> m () #
Set the monad GHCi lifts user statements into.
Checks that a type (in string form) is an instance of the
GHC.GHCi.GHCiSandboxIO
type class. Sets it to be the GHCi monad if it is,
throws an error otherwise.
moduleTrustReqs :: GhcMonad m => Module -> m (Bool, Set InstalledUnitId) #
Return if a module is trusted and the pkgs it depends on to be trusted.
isModuleTrusted :: GhcMonad m => Module -> m Bool #
Check that a module is safe to import (according to Safe Haskell).
We return True to indicate the import is safe and False otherwise although in the False case an error may be thrown first.
lookupModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module #
Like findModule
, but differs slightly when the module refers to
a source file, and the file has not been loaded via load
. In
this case, findModule
will throw an error (module not loaded),
but lookupModule
will check to see whether the module can also be
found in a package, and if so, that package Module
will be
returned. If not, the usual module-not-found error will be thrown.
findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module #
Takes a ModuleName
and possibly a UnitId
, and consults the
filesystem and package database to find the corresponding Module
,
using the algorithm that is used for an import
declaration.
showRichTokenStream :: [(Located Token, String)] -> String #
Take a rich token stream such as produced from getRichTokenStream
and
return source code almost identical to the original code (except for
insignificant whitespace.)
addSourceToTokens :: RealSrcLoc -> StringBuffer -> [Located Token] -> [(Located Token, String)] #
Given a source location and a StringBuffer corresponding to this location, return a rich token stream with the source associated to the tokens.
getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)] #
Give even more information on the source than getTokenStream
This function allows reconstructing the source completely with
showRichTokenStream
.
getTokenStream :: GhcMonad m => Module -> m [Located Token] #
Return module source as token stream, including comments.
The module must be in the module graph and its source must be available.
Throws a SourceError
on parse error.
pprParenSymName :: NamedThing a => a -> SDoc #
print a NamedThing
, adding parentheses if the name is an operator.
dataConType :: DataCon -> Type #
:: GhcMonad m | |
=> [Module] | visible modules. An orphan instance will be returned if it is visible from at least one module in the list. |
-> Maybe [Module] | modules to load. If this is not specified, we load modules for everything that is in scope unqualified. |
-> m (Messages, Maybe (NameEnv ([ClsInst], [FamInst]))) |
Retrieve all type and family instances in the environment, indexed
by Name
. Each name's lists will contain every instance in which that name
is mentioned in the instance head.
getGRE :: GhcMonad m => m GlobalRdrEnv #
get the GlobalRdrEnv for a session
lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing) #
Looks up a global name: that is, any top-level name in any
visible module. Unlike lookupName
, lookupGlobalName does not use
the interactive context, and therefore does not require a preceding
setContext
.
isDictonaryId :: Id -> Bool #
modInfoModBreaks :: ModuleInfo -> ModBreaks #
modInfoSafe :: ModuleInfo -> SafeHaskellMode #
Retrieve module safe haskell mode
modInfoIface :: ModuleInfo -> Maybe ModIface #
modInfoLookupName :: GhcMonad m => ModuleInfo -> Name -> m (Maybe TyThing) #
mkPrintUnqualifiedForModule :: GhcMonad m => ModuleInfo -> m (Maybe PrintUnqualified) #
modInfoIsExportedName :: ModuleInfo -> Name -> Bool #
modInfoInstances :: ModuleInfo -> [ClsInst] #
Returns the instances defined by the specified module. Warning: currently unimplemented for package modules.
modInfoExportsWithSelectors :: ModuleInfo -> [Name] #
modInfoExports :: ModuleInfo -> [Name] #
modInfoTopLevelScope :: ModuleInfo -> Maybe [Name] #
modInfoTyThings :: ModuleInfo -> [TyThing] #
The list of top-level entities defined in a module
getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) #
Request information about a loaded Module
getPrintUnqual :: GhcMonad m => m PrintUnqualified #
getInsts :: GhcMonad m => m ([ClsInst], [FamInst]) #
Return the instances for the current interactive session.
getBindings :: GhcMonad m => m [TyThing] #
Return the bindings for the current interactive session.
getModuleGraph :: GhcMonad m => m ModuleGraph #
Get the module dependency graph.
compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule #
Like compileToCoreModule, but invokes the simplifier, so as to return simplified and tidied Core.
compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule #
This is the way to get access to the Core bindings corresponding
to a module. compileToCore
parses, typechecks, and
desugars the module, then returns the resulting Core module (consisting of
the module name, type declarations, and function declarations) if
successful.
loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod #
Load a module. Input doesn't need to be desugared.
A module must be loaded before dependent modules can be typechecked. This
always includes generating a ModIface
and, depending on the
hscTarget
, may also include code generation.
This function will always cause recompilation and will always overwrite previous compilation results (potentially files on disk).
desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule #
Desugar a typechecked module.
typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule #
Typecheck and rename a parsed module.
Throws a SourceError
if either fails.
parseModule :: GhcMonad m => ModSummary -> m ParsedModule #
Parse a module.
Throws a SourceError
on parse error.
getModSummary :: GhcMonad m => ModuleName -> m ModSummary #
Return the ModSummary
of a module with the given name.
The module must be part of the module graph (see hsc_mod_graph
and
ModuleGraph
). If this is not the case, this function will throw a
GhcApiError
.
This function ignores boot modules and requires that there is only one non-boot module with the given name.
workingDirectoryChanged :: GhcMonad m => m () #
Inform GHC that the working directory has changed. GHC will flush its cache of module locations, since it may no longer be valid.
Note: Before changing the working directory make sure all threads running in the same session have stopped. If you change the working directory, you should also unload the current program (set targets to empty, followed by load).
guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target #
Attempts to guess what Target a string refers to. This function
implements the --make
/GHCi command-line syntax for filenames:
- if the string looks like a Haskell source filename, then interpret it as such
- if adding a .hs or .lhs suffix yields the name of an existing file, then use that
- otherwise interpret the string as a module name
removeTarget :: GhcMonad m => TargetId -> m () #
Remove a target
getTargets :: GhcMonad m => m [Target] #
Returns the current set of targets
setTargets :: GhcMonad m => [Target] -> m () #
Sets the targets for this session. Each target may be a module name
or a filename. The targets correspond to the set of root modules for
the program/library. Unloading the current program is achieved by
setting the current set of targets to be empty, followed by load
.
parseDynamicFlags :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn]) #
getInteractiveDynFlags :: GhcMonad m => m DynFlags #
Get the DynFlags
used to evaluate interactive expressions.
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () #
Set the DynFlags
used to evaluate interactive expressions.
Note: this cannot be used for changes to packages. Use
setSessionDynFlags
, or setProgramDynFlags
and then copy the
pkgState
into the interactive DynFlags
.
getProgramDynFlags :: GhcMonad m => m DynFlags #
Returns the program DynFlags
.
setLogAction :: GhcMonad m => LogAction -> m () #
Set the action taken when the compiler produces a message. This
can also be accomplished using setProgramDynFlags
, but using
setLogAction
avoids invalidating the cached module graph.
setProgramDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId] #
setSessionDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId] #
Updates both the interactive and program DynFlags in a Session. This also reads the package database (unless it has already been read), and prepares the compilers knowledge about packages. It can be called again to load new packages: just add new package flags to (packageFlags dflags).
Returns a list of new packages that may need to be linked in using
the dynamic linker (see linkPackages
) as a result of new package
flags. If you are not doing linking or doing static linking, you
can ignore the list of packages returned.
initGhcMonad :: GhcMonad m => Maybe FilePath -> m () #
Initialise a GHC session.
If you implement a custom GhcMonad
you must call this function in the
monad run function. It will initialise the session variable and clear all
warnings.
The first argument should point to the directory where GHC's library files
reside. More precisely, this should be the output of ghc --print-libdir
of the version of GHC the module using this API is compiled with. For
portability, you should use the ghc-paths
package, available at
http://hackage.haskell.org/package/ghc-paths.
withCleanupSession :: GhcMonad m => m a -> m a #
:: ExceptionMonad m | |
=> Maybe FilePath | See argument to |
-> GhcT m a | The action to perform. |
-> m a |
Run function for GhcT
monad transformer.
It initialises the GHC session and warnings via initGhcMonad
. Each call
to this function will create a new session which should not be shared among
several threads.
:: Maybe FilePath | See argument to |
-> Ghc a | The action to perform. |
-> IO a |
Run function for the Ghc
monad.
It initialises the GHC session and warnings via initGhcMonad
. Each call
to this function will create a new session which should not be shared among
several threads.
Any errors not handled inside the Ghc
action are propagated as IO
exceptions.
defaultCleanupHandler :: ExceptionMonad m => DynFlags -> m a -> m a #
This function is no longer necessary, cleanup is now done by runGhc/runGhcT.
defaultErrorHandler :: ExceptionMonad m => FatalMessager -> FlushOut -> m a -> m a #
Install some default exception handlers and run the inner computation. Unless you want to handle exceptions yourself, you should wrap this around the top level of your program. The default handlers output the error message(s) to stderr and exit cleanly.
modSummary, parsedSource
parsedSource :: m -> ParsedSource #
Instances
ParsedMod ParsedModule | |
Defined in GHC | |
ParsedMod TypecheckedModule | |
Defined in GHC | |
ParsedMod DesugaredModule | |
Defined in GHC |
class ParsedMod m => TypecheckedMod m where #
renamedSource, typecheckedSource, moduleInfo, tm_internals
renamedSource :: m -> Maybe RenamedSource #
typecheckedSource :: m -> TypecheckedSource #
moduleInfo :: m -> ModuleInfo #
Instances
TypecheckedMod TypecheckedModule | |
Defined in GHC | |
TypecheckedMod DesugaredModule | |
Defined in GHC |
data ParsedModule #
The result of successful parsing.
Instances
Show ParsedModule Source # | |
Defined in Development.IDE.GHC.Orphans showsPrec :: Int -> ParsedModule -> ShowS # show :: ParsedModule -> String # showList :: [ParsedModule] -> ShowS # | |
NFData ParsedModule Source # | |
Defined in Development.IDE.GHC.Orphans rnf :: ParsedModule -> () # | |
ParsedMod ParsedModule | |
Defined in GHC |
data TypecheckedModule #
The result of successful typechecking. It also contains the parser result.
Instances
ParsedMod TypecheckedModule | |
Defined in GHC | |
TypecheckedMod TypecheckedModule | |
Defined in GHC |
data DesugaredModule #
The result of successful desugaring (i.e., translation to core). Also contains all the information of a typechecked module.
Instances
ParsedMod DesugaredModule | |
Defined in GHC | |
TypecheckedMod DesugaredModule | |
Defined in GHC | |
DesugaredMod DesugaredModule | |
Defined in GHC coreModule :: DesugaredModule -> ModGuts # |
type ParsedSource = Located (HsModule GhcPs) #
type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString) #
type TypecheckedSource = LHsBinds GhcTc #
data CoreModule #
A CoreModule consists of just the fields of a ModGuts
that are needed for
the compileToCoreModule
interface.
CoreModule | |
|
Instances
Show CoreModule Source # | |
Defined in Development.IDE.GHC.Orphans showsPrec :: Int -> CoreModule -> ShowS # show :: CoreModule -> String # showList :: [CoreModule] -> ShowS # | |
NFData CoreModule Source # | |
Defined in Development.IDE.GHC.Orphans rnf :: CoreModule -> () # | |
Outputable CoreModule | |
Defined in GHC ppr :: CoreModule -> SDoc # pprPrec :: Rational -> CoreModule -> SDoc # |
data ModuleInfo #
Container for information about a Module
.
cyclicModuleErr :: [ModSummary] -> SDoc #
:: Bool | Drop hi-boot nodes? (see below) |
-> ModuleGraph | |
-> Maybe ModuleName | Root module name. If |
-> [SCC ModSummary] |
Topological sort of the module graph
Calculate SCCs of the module graph, possibly dropping the hi-boot nodes The resulting list of strongly-connected-components is in topologically sorted order, starting with the module(s) at the bottom of the dependency graph (ie compile them first) and ending with the ones at the top.
Drop hi-boot nodes (first boolean arg)?
False
: treat the hi-boot summaries as nodes of the graph, so the graph must be acyclicTrue
: eliminate the hi-boot nodes, and instead pretend the a source-import of Foo is an import of Foo The resulting graph has no hi-boot nodes, but can be cyclic
load :: GhcMonad m => LoadHowMuch -> m SuccessFlag #
Try to load the program. See LoadHowMuch
for the different modes.
This function implements the core of GHC's --make
mode. It preprocesses,
compiles and loads the specified modules, avoiding re-compilation wherever
possible. Depending on the target (see hscTarget
) compiling
and loading may result in files being created on disk.
Calls the defaultWarnErrLogger
after each compiling each module, whether
successful or not.
Throw a SourceError
if errors are encountered before the actual
compilation starts (e.g., during dependency analysis). All other errors
are reported using the defaultWarnErrLogger
.
:: GhcMonad m | |
=> [ModuleName] | excluded modules |
-> Bool | allow duplicate roots |
-> m ModuleGraph |
Perform a dependency analysis starting from the current targets and update the session with the new module graph.
Dependency analysis entails parsing the import
directives and may
therefore require running certain preprocessors.
Note that each ModSummary
in the module graph caches its DynFlags
.
These DynFlags
are determined by the current session DynFlags
and the
OPTIONS
and LANGUAGE
pragmas of the parsed module. Thus if you want
changes to the DynFlags
to take effect you need to call this function
again.
data LoadHowMuch #
Describes which modules of the module graph need to be loaded.
LoadAllTargets | Load all targets and its dependencies. |
LoadUpTo ModuleName | Load only the given module and its dependencies. |
LoadDependenciesOf ModuleName | Load only the dependencies of the given module, but not the module itself. |
moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool #
showModule :: GhcMonad m => ModSummary -> m String #
dynCompileExpr :: GhcMonad m => String -> m Dynamic #
Compile an expression, run it and return the result as a Dynamic.
compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue #
Compile a parsed expression (before renaming), run it, and deliver the resulting HValue.
compileExprRemote :: GhcMonad m => String -> m ForeignHValue #
Compile an expression, run it, and deliver the resulting HValue.
compileExpr :: GhcMonad m => String -> m HValue #
Compile an expression, run it, and deliver the resulting HValue.
parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs) #
Parse an expression, the parsed expression can be further processed and passed to compileParsedExpr.
parseInstanceHead :: GhcMonad m => String -> m Type #
getInstancesForType :: GhcMonad m => Type -> m [ClsInst] #
exprType :: GhcMonad m => TcRnExprMode -> String -> m Type #
Get the type of an expression
Returns the type as described by TcRnExprMode
getDocs :: GhcMonad m => Name -> m (Either GetDocsFailure (Maybe HsDocString, Map Int HsDocString)) #
isDecl :: DynFlags -> String -> Bool #
Returns True
if passed string is a declaration but not a splice.
parseName :: GhcMonad m => String -> m [Name] #
Parses a string as an identifier, and returns the list of Name
s that
the identifier can refer to in the current interactive context.
getRdrNamesInScope :: GhcMonad m => m [RdrName] #
Returns all RdrName
s in scope in the current interactive
context, excluding any that are internally-generated.
getNamesInScope :: GhcMonad m => m [Name] #
Returns all names in scope in the current interactive context
getInfo :: GhcMonad m => Bool -> Name -> m (Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)) #
Looks up an identifier in the current interactive context (for :info) Filter the instances by the ones whose tycons (or clases resp) are in scope (qualified or otherwise). Otherwise we list a whole lot too many! The exact choice of which ones to show, and which to hide, is a judgement call. (see #1581)
moduleIsInterpreted :: GhcMonad m => Module -> m Bool #
Returns True
if the specified module is interpreted, and hence has
its full top-level scope available.
getContext :: GhcMonad m => m [InteractiveImport] #
Get the interactive evaluation context, consisting of a pair of the set of modules from which we take the full top-level scope, and the set of modules from which we take just the exports respectively.
setContext :: GhcMonad m => [InteractiveImport] -> m () #
Set the interactive evaluation context.
(setContext imports) sets the ic_imports field (which in turn
determines what is in scope at the prompt) to imports
, and
constructs the ic_rn_glb_env environment to reflect it.
We retain in scope all the things defined at the prompt, and kept in ic_tythings. (Indeed, they shadow stuff from ic_imports.)
abandonAll :: GhcMonad m => m Bool #
resumeExec :: GhcMonad m => (SrcSpan -> Bool) -> SingleStep -> m ExecResult #
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) #
runParsedDecls :: GhcMonad m => [LHsDecl GhcPs] -> m [Name] #
Like runDeclsWithLocation
, but takes parsed declarations as argument.
Useful when doing preprocessing on the AST before execution, e.g. in GHCi
(see GHCi.UI.runStmt).
runDeclsWithLocation :: GhcMonad m => String -> Int -> String -> m [Name] #
Run some declarations and return any user-visible names that were brought into scope.
execStmt' :: GhcMonad m => GhciLStmt GhcPs -> String -> ExecOptions -> m ExecResult #
Like execStmt
, but takes a parsed statement as argument. Useful when
doing preprocessing on the AST before execution, e.g. in GHCi (see
GHCi.UI.runStmt).
:: GhcMonad m | |
=> String | a statement (bind or expression) |
-> ExecOptions | |
-> m ExecResult |
Run a statement in the current interactive context.
default ExecOptions
getHistoryModule :: History -> Module #
getResumeContext :: GhcMonad m => m [Resume] #
data GetDocsFailure #
Failure modes for getDocs
.
NameHasNoModule Name |
|
NoDocsInIface Module Bool |
|
InteractiveName | The |
Instances
Outputable GetDocsFailure | |
Defined in InteractiveEval ppr :: GetDocsFailure -> SDoc # pprPrec :: Rational -> GetDocsFailure -> SDoc # |
data TcRnExprMode #
How should we infer a type? See Note [TcRnExprMode]
TM_Inst | Instantiate the type fully (:type) |
TM_NoInst | Do not instantiate the type (:type +v) |
TM_Default | Default the type eagerly (:type +d) |
pprFamInst :: FamInst -> SDoc #
Pretty-prints a FamInst
(type/data family instance) with its defining location.
printException :: GhcMonad m => SourceError -> m () #
Print the error message and all warnings. Useful inside exception handlers. Clears warnings after printing.
getSessionDynFlags :: GhcMonad m => m DynFlags #
Grabs the DynFlags from the Session
class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) where #
A monad that has all the features needed by GHC API calls.
In short, a GHC monad
- allows embedding of IO actions,
- can log warnings,
- allows handling of (extensible) exceptions, and
- maintains a current session.
If you do not use Ghc
or GhcT
, make sure to call initGhcMonad
before any call to the GHC API functions can occur.
getSession :: m HscEnv #
setSession :: HscEnv -> m () #
Instances
GhcMonad Ghc | |
Defined in GhcMonad getSession :: Ghc HscEnv # setSession :: HscEnv -> Ghc () # | |
ExceptionMonad m => GhcMonad (GhcT m) | |
Defined in GhcMonad getSession :: GhcT m HscEnv # setSession :: HscEnv -> GhcT m () # |
A minimal implementation of a GhcMonad
. If you need a custom monad,
e.g., to maintain additional state consider wrapping this monad or using
GhcT
.
Instances
Monad Ghc | |
Functor Ghc | |
MonadFix Ghc | |
Applicative Ghc | |
MonadIO Ghc | |
GhcMonad Ghc | |
Defined in GhcMonad getSession :: Ghc HscEnv # setSession :: HscEnv -> Ghc () # | |
HasDynFlags Ghc | |
Defined in GhcMonad getDynFlags :: Ghc DynFlags # | |
ExceptionMonad Ghc | |
data GhcT (m :: Type -> Type) a #
A monad transformer to add GHC specific features to another monad.
Note that the wrapped monad must support IO and handling of exceptions.
Instances
Monad m => Monad (GhcT m) | |
Functor m => Functor (GhcT m) | |
Applicative m => Applicative (GhcT m) | |
MonadIO m => MonadIO (GhcT m) | |
ExceptionMonad m => GhcMonad (GhcT m) | |
Defined in GhcMonad getSession :: GhcT m HscEnv # setSession :: HscEnv -> GhcT m () # | |
MonadIO m => HasDynFlags (GhcT m) | |
Defined in GhcMonad getDynFlags :: GhcT m DynFlags # | |
ExceptionMonad m => ExceptionMonad (GhcT m) | |
type WarnErrLogger = forall (m :: Type -> Type). GhcMonad m => Maybe SourceError -> m () #
A function called to log warnings and errors.
ms_mod_name :: ModSummary -> ModuleName #
mkModuleGraph :: [ModSummary] -> ModuleGraph #
emptyMG :: ModuleGraph #
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary #
Look up a ModSummary in the ModuleGraph
mgModSummaries :: ModuleGraph -> [ModSummary] #
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph #
Map a function f
over all the ModSummaries
.
To preserve invariants f
can't change the isBoot status.
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool #
Determines whether a set of modules requires Template Haskell or Quasi Quotes
Note that if the session's DynFlags
enabled Template Haskell when
depanal
was called, then each module in the returned module graph will
have Template Haskell enabled whether it is actually needed or not.
:: ExceptionMonad m | |
=> (SourceError -> m a) | exception handler |
-> m a | action to perform |
-> m a |
Perform the given action and call the exception handler if the action
throws a SourceError
. See SourceError
for more information.
HscEnv is like Session
, except that some of the fields are immutable.
An HscEnv is used to compile a single module from plain Haskell source
code (after preprocessing) to either C, assembly or C--. It's also used
to store the dynamic linker state to allow for multiple linkers in the
same address space.
Things like the module graph don't change during a single compilation.
Historical note: "hsc" used to be the name of the compiler binary, when there was a separate driver and compiler. To compile a single module, the driver would invoke hsc on the source code... so nowadays we think of hsc as the layer of the compiler that deals with compiling a single module.
A compilation target.
A target may be supplied with the actual text of the module. If so, use this instead of the file contents (this is for use in an IDE where the file hasn't been saved by the user yet).
Target | |
|
TargetModule ModuleName | A module name: search for the file |
TargetFile FilePath (Maybe Phase) | A filename: preprocess & parse it to find the module name. If specified, the Phase indicates how to compile this file (which phase to start from). Nothing indicates the starting phase should be determined from the suffix of the filename. |
data ModIface_ (phase :: ModIfacePhase) #
A ModIface
plus a ModDetails
summarises everything we know
about a compiled module. The ModIface
is the stuff *before* linking,
and can be written out to an interface file. The 'ModDetails is after
linking and can be completely recovered from just the ModIface
.
When we read an interface file, we also construct a ModIface
from it,
except that we explicitly make the mi_decls
and a few other fields empty;
as when reading we consolidate the declarations etc. into a number of indexed
maps and environments in the ExternalPackageState
.
ModIface | |
|
data InteractiveImport #
IIDecl (ImportDecl GhcPs) | Bring the exports of a particular module (filtered by an import decl) into scope |
IIModule ModuleName | Bring into scope the entire top-level envt of of this module, including the things imported into it. |
Instances
Show InteractiveImport Source # | |
Defined in Development.IDE.GHC.Orphans showsPrec :: Int -> InteractiveImport -> ShowS # show :: InteractiveImport -> String # showList :: [InteractiveImport] -> ShowS # | |
Outputable InteractiveImport | |
Defined in HscTypes ppr :: InteractiveImport -> SDoc # pprPrec :: Rational -> InteractiveImport -> SDoc # |
data ModuleGraph #
A ModuleGraph contains all the nodes from the home package (only). There will be a node for each source module, plus a node for each hi-boot module.
The graph is not necessarily stored in topologically-sorted order. Use
topSortModuleGraph
and flattenSCC
to achieve this.
data ModSummary #
A single node in a ModuleGraph
. The nodes of the module graph
are one of:
- A regular Haskell source module
- A hi-boot source module
ModSummary | |
|
Instances
Show ModSummary Source # | |
Defined in Development.IDE.GHC.Orphans showsPrec :: Int -> ModSummary -> ShowS # show :: ModSummary -> String # showList :: [ModSummary] -> ShowS # | |
NFData ModSummary Source # | |
Defined in Development.IDE.GHC.Orphans rnf :: ModSummary -> () # | |
Outputable ModSummary | |
Defined in HscTypes ppr :: ModSummary -> SDoc # pprPrec :: Rational -> ModSummary -> SDoc # |
Haskell Module
All we actually declare here is the top-level structure for a module.
HsModule | |
|
Instances
Data (HsModule GhcPs) | |
Defined in GHC.Hs gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcPs -> c (HsModule GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcPs) # toConstr :: HsModule GhcPs -> Constr # dataTypeOf :: HsModule GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcPs -> HsModule GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) # | |
Data (HsModule GhcRn) | |
Defined in GHC.Hs gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcRn -> c (HsModule GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcRn) # toConstr :: HsModule GhcRn -> Constr # dataTypeOf :: HsModule GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcRn -> HsModule GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) # | |
Data (HsModule GhcTc) | |
Defined in GHC.Hs gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcTc -> c (HsModule GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcTc) # toConstr :: HsModule GhcTc -> Constr # dataTypeOf :: HsModule GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcTc -> HsModule GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) # | |
OutputableBndrId p => Outputable (HsModule (GhcPass p)) | |
hsValBindsImplicits :: forall (idR :: Pass). HsValBindsLR GhcRn (GhcPass idR) -> [(SrcSpan, [Name])] #
lStmtsImplicits :: forall (idR :: Pass) body. [LStmtLR GhcRn (GhcPass idR) (Located (body (GhcPass idR)))] -> [(SrcSpan, [Name])] #
hsDataFamInstBinders :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)]) #
the SrcLoc returned are for the whole declarations, not just the names
getPatSynBinds :: [(RecFlag, LHsBinds id)] -> [PatSynBind id id] #
hsPatSynSelectors :: forall (p :: Pass). HsValBinds (GhcPass p) -> [IdP (GhcPass p)] #
Collects record pattern-synonym selectors only; the pattern synonym names are collected by collectHsValBinders.
hsForeignDeclsBinders :: [LForeignDecl pass] -> [Located (IdP pass)] #
See Note [SrcSpan for binders]
hsLTyClDeclBinders :: forall (p :: Pass). Located (TyClDecl (GhcPass p)) -> ([Located (IdP (GhcPass p))], [LFieldOcc (GhcPass p)]) #
Returns all the binding names of the decl. The first one is guaranteed to be the name of the decl. The first component represents all binding names except record fields; the second represents field occurrences. For record fields mentioned in multiple constructors, the SrcLoc will be from the first occurrence.
Each returned (Located name) has a SrcSpan for the whole declaration. See Note [SrcSpan for binders]
hsTyClForeignBinders :: [TyClGroup GhcRn] -> [LForeignDecl GhcRn] -> [Name] #
hsGroupBinders :: HsGroup GhcRn -> [Name] #
collectStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. StmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] #
collectLStmtBinders :: forall (idL :: Pass) (idR :: Pass) body. LStmtLR (GhcPass idL) (GhcPass idR) body -> [IdP (GhcPass idL)] #
collectStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [StmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] #
collectLStmtsBinders :: forall (idL :: Pass) (idR :: Pass) body. [LStmtLR (GhcPass idL) (GhcPass idR) body] -> [IdP (GhcPass idL)] #
collectMethodBinders :: LHsBindsLR idL idR -> [Located (IdP idL)] #
Used exclusively for the bindings of an instance decl which are all FunBinds
collectHsBindListBinders :: forall (p :: Pass) idR. [LHsBindLR (GhcPass p) idR] -> [IdP (GhcPass p)] #
Same as collectHsBindsBinders, but works over a list of bindings
collectHsBindsBinders :: forall (p :: Pass) idR. LHsBindsLR (GhcPass p) idR -> [IdP (GhcPass p)] #
collectHsBindBinders :: (SrcSpanLess (LPat p) ~ Pat p, HasSrcSpan (LPat p)) => HsBindLR p idR -> [IdP p] #
Collect both Ids and pattern-synonym binders
collectHsValBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #
Collect Id binders only, or Ids + pattern synonyms, respectively
collectHsIdBinders :: forall (idL :: Pass) (idR :: Pass). HsValBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #
Collect Id binders only, or Ids + pattern synonyms, respectively
collectLocalBinders :: forall (idL :: Pass) (idR :: Pass). HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> [IdP (GhcPass idL)] #
isBangedHsBind :: HsBind GhcTc -> Bool #
Is a binding a strict variable or pattern bind (e.g. !x = ...
)?
isUnliftedHsBind :: HsBind GhcTc -> Bool #
Should we treat this as an unlifted bind? This will be true for any bind that binds an unlifted variable, but we must be careful around AbsBinds. See Note [Unlifted id check in isUnliftedHsBind]. For usage information, see Note [Strict binds check] is DsBinds.
mkMatch :: forall (p :: Pass). HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> Located (HsLocalBinds (GhcPass p)) -> LMatch (GhcPass p) (LHsExpr (GhcPass p)) #
mkPrefixFunRhs :: Located id -> HsMatchContext id #
Make a prefix, non-strict function HsMatchContext
mkSimpleGeneratedFunBind :: SrcSpan -> RdrName -> [LPat GhcPs] -> LHsExpr GhcPs -> LHsBind GhcPs #
Convenience function using mkFunBind
.
This is for generated bindings only, do not use for user-written code.
isInfixFunBind :: HsBindLR id1 id2 -> Bool #
mkPatSynBind :: Located RdrName -> HsPatSynDetails (Located RdrName) -> LPat GhcPs -> HsPatSynDir GhcPs -> HsBind GhcPs #
mkTopFunBind :: Origin -> Located Name -> [LMatch GhcRn (LHsExpr GhcRn)] -> HsBind GhcRn #
In Name-land, with empty bind_fvs
mkFunBind :: Origin -> Located RdrName -> [LMatch GhcPs (LHsExpr GhcPs)] -> HsBind GhcPs #
Not infix, with place holders for coercion and free vars
mkHsWrapPatCo :: forall (id :: Pass). TcCoercionN -> Pat (GhcPass id) -> Type -> Pat (GhcPass id) #
mkLHsWrapCo :: forall (id :: Pass). TcCoercionN -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
mkHsWrapCoR :: forall (id :: Pass). TcCoercionR -> HsExpr (GhcPass id) -> HsExpr (GhcPass id) #
mkHsWrapCo :: forall (id :: Pass). TcCoercionN -> HsExpr (GhcPass id) -> HsExpr (GhcPass id) #
mkHsWrap :: forall (id :: Pass). HsWrapper -> HsExpr (GhcPass id) -> HsExpr (GhcPass id) #
Avoid (HsWrap co (HsWrap co' _)). See Note [Detecting forced eta expansion] in DsExpr
typeToLHsType :: Type -> LHsType GhcPs #
Converting a Type to an HsType RdrName This is needed to implement GeneralizedNewtypeDeriving.
Note that we use getRdrName
extensively, which
generates Exact RdrNames rather than strings.
mkClassOpSigs :: [LSig GhcPs] -> [LSig GhcPs] #
Convert TypeSig to ClassOpSig The former is what is parsed, but the latter is what we need in class/instance declarations
mkLHsSigWcType :: LHsType GhcPs -> LHsSigWcType GhcPs #
mkLHsSigType :: LHsType GhcPs -> LHsSigType GhcPs #
Split a list into lists that are small enough to have a corresponding
tuple arity. The sub-lists of the result all have length <= mAX_TUPLE_SIZE
But there may be more than mAX_TUPLE_SIZE
sub-lists
:: ([a] -> a) | "Small" constructor function, of maximum input arity |
-> [a] | Possible "big" list of things to construct from |
-> a | Constructed thing made possible by recursive decomposition |
Lifts a "small" constructor into a "big" constructor by recursive decompositon
mkBigLHsVarTup :: forall (id :: Pass). [IdP (GhcPass id)] -> LHsExpr (GhcPass id) #
The Big equivalents for the source tuple expressions
nlHsAppKindTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsKind (GhcPass p) -> LHsType (GhcPass p) #
nlHsTyConApp :: forall (p :: Pass). IdP (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p) #
nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
nlHsIf :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
Note [Rebindable nlHsIf] nlHsIf should generate if-expressions which are NOT subject to RebindableSyntax, so the first field of HsIf is Nothing. (#12080)
nlWildPatName :: LPat GhcRn #
Wildcard pattern - after renaming
nlWildConPat :: DataCon -> LPat GhcPs #
nlHsVarApps :: forall (id :: Pass). IdP (GhcPass id) -> [IdP (GhcPass id)] -> LHsExpr (GhcPass id) #
nlHsApps :: forall (id :: Pass). IdP (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #
nlHsSyntaxApps :: forall (id :: Pass). SyntaxExpr (GhcPass id) -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #
nlHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
nlHsDataCon :: DataCon -> LHsExpr GhcTc #
NB: Only for LHsExpr **Id**
mkHsStringPrimLit :: forall (p :: Pass). FastString -> HsLit (GhcPass p) #
mkHsQuasiQuote :: RdrName -> SrcSpan -> FastString -> HsSplice GhcPs #
mkTypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs #
mkUntypedSplice :: SpliceDecoration -> LHsExpr GhcPs -> HsSplice GhcPs #
mkHsOpApp :: LHsExpr GhcPs -> IdP GhcPs -> LHsExpr GhcPs -> HsExpr GhcPs #
A useful function for building OpApps
. The operator is always a
variable, and we don't know the fixity yet.
mkRecStmt :: forall (idL :: Pass) bodyR. [LStmtLR (GhcPass idL) GhcPs bodyR] -> StmtLR (GhcPass idL) GhcPs bodyR #
emptyRecStmtId :: StmtLR GhcTc GhcTc bodyR #
emptyRecStmtName :: StmtLR GhcRn GhcRn bodyR #
mkBindStmt :: forall (idL :: Pass) (idR :: Pass) bodyR. XBindStmt (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) ~ NoExtField => LPat (GhcPass idL) -> Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) #
mkBodyStmt :: forall bodyR (idL :: Pass). Located (bodyR GhcPs) -> StmtLR (GhcPass idL) GhcPs (Located (bodyR GhcPs)) #
mkLastStmt :: forall bodyR (idR :: Pass) (idL :: Pass). Located (bodyR (GhcPass idR)) -> StmtLR (GhcPass idL) (GhcPass idR) (Located (bodyR (GhcPass idR))) #
mkGroupByUsingStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkTransformByStmt :: [ExprLStmt GhcPs] -> LHsExpr GhcPs -> LHsExpr GhcPs -> StmtLR GhcPs GhcPs (LHsExpr GhcPs) #
mkHsCmdIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsCmd (GhcPass p) -> LHsCmd (GhcPass p) -> HsCmd (GhcPass p) #
mkHsIf :: forall (p :: Pass). LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) -> HsExpr (GhcPass p) #
mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs #
mkHsIntegral :: IntegralLit -> HsOverLit GhcPs #
mkLHsPar :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
Wrap in parens if (hsExprNeedsParens appPrec) says it needs them So 'f x' becomes '(f x)', but '3' stays as '3'
nlHsTyApps :: forall (id :: Pass). IdP (GhcPass id) -> [Type] -> [LHsExpr (GhcPass id)] -> LHsExpr (GhcPass id) #
mkHsCaseAlt :: forall (p :: Pass) body. LPat (GhcPass p) -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p))) #
A simple case alternative with a single pattern, no binds, no guards; pre-typechecking
mkHsLam :: forall (p :: Pass). XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ NoExtField => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #
mkHsAppType :: forall (id :: Pass). NoGhcTc (GhcPass id) ~ GhcRn => LHsExpr (GhcPass id) -> LHsWcType GhcRn -> LHsExpr (GhcPass id) #
mkHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #
mkMatchGroup :: XMG name (Located (body name)) ~ NoExtField => Origin -> [LMatch name (Located (body name))] -> MatchGroup name (Located (body name)) #
unguardedRHS :: forall body (p :: Pass). SrcSpan -> Located (body (GhcPass p)) -> [LGRHS (GhcPass p) (Located (body (GhcPass p)))] #
unguardedGRHSs :: forall body (p :: Pass). Located (body (GhcPass p)) -> GRHSs (GhcPass p) (Located (body (GhcPass p))) #
mkSimpleMatch :: forall (p :: Pass) body. HsMatchContext (NameOrRdrName (IdP (GhcPass p))) -> [LPat (GhcPass p)] -> Located (body (GhcPass p)) -> LMatch (GhcPass p) (Located (body (GhcPass p))) #
pprStmtInCtxt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => HsStmtContext (IdP (GhcPass idL)) -> StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc #
pprMatchInCtxt :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable (NameOrRdrName (NameOrRdrName (IdP (GhcPass idR)))), Outputable body) => Match (GhcPass idR) body -> SDoc #
matchContextErrString :: Outputable id => HsMatchContext id -> SDoc #
pprStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc #
pprAStmtContext :: (Outputable id, Outputable (NameOrRdrName id)) => HsStmtContext id -> SDoc #
pprMatchContextNoun :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc #
pprMatchContext :: (Outputable (NameOrRdrName id), Outputable id) => HsMatchContext id -> SDoc #
matchSeparator :: HsMatchContext id -> SDoc #
isMonadCompContext :: HsStmtContext id -> Bool #
isMonadFailStmtContext :: HsStmtContext id -> Bool #
Should pattern match failure in a HsStmtContext
be desugared using
MonadFail
?
isComprehensionContext :: HsStmtContext id -> Bool #
isPatSynCtxt :: HsMatchContext id -> Bool #
thTyBrackets :: SDoc -> SDoc #
thBrackets :: SDoc -> SDoc -> SDoc #
pprHsBracket :: forall (p :: Pass). OutputableBndrId p => HsBracket (GhcPass p) -> SDoc #
isTypedBracket :: HsBracket id -> Bool #
ppr_splice :: forall (p :: Pass). OutputableBndrId p => SDoc -> IdP (GhcPass p) -> LHsExpr (GhcPass p) -> SDoc -> SDoc #
ppr_quasi :: OutputableBndr p => p -> p -> FastString -> SDoc #
ppr_splice_decl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SDoc #
pprPendingSplice :: forall (p :: Pass). OutputableBndrId p => SplicePointName -> LHsExpr (GhcPass p) -> SDoc #
isTypedSplice :: HsSplice id -> Bool #
pprQuals :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc #
pprComp :: forall (p :: Pass) body. (OutputableBndrId p, Outputable body) => [LStmt (GhcPass p) body] -> SDoc #
ppr_do_stmts :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => [LStmtLR (GhcPass idL) (GhcPass idR) body] -> SDoc #
pprDo :: forall (p :: Pass) body any. (OutputableBndrId p, Outputable body) => HsStmtContext any -> [LStmt (GhcPass p) body] -> SDoc #
pprBy :: Outputable body => Maybe body -> SDoc #
pprTransStmt :: Outputable body => Maybe body -> body -> TransForm -> SDoc #
pprTransformStmt :: forall (p :: Pass). OutputableBndrId p => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) -> Maybe (LHsExpr (GhcPass p)) -> SDoc #
pprArg :: forall (idL :: Pass). OutputableBndrId idL => ApplicativeArg (GhcPass idL) -> SDoc #
pprStmt :: forall (idL :: Pass) (idR :: Pass) body. (OutputableBndrId idL, OutputableBndrId idR, Outputable body) => StmtLR (GhcPass idL) (GhcPass idR) body -> SDoc #
pp_rhs :: Outputable body => HsMatchContext idL -> body -> SDoc #
pprGRHS :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHS (GhcPass idR) body -> SDoc #
pprGRHSs :: forall (idR :: Pass) body idL. (OutputableBndrId idR, Outputable body) => HsMatchContext idL -> GRHSs (GhcPass idR) body -> SDoc #
pprMatch :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => Match (GhcPass idR) body -> SDoc #
pprMatches :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc #
matchGroupArity :: forall (id :: Pass) body. MatchGroup (GhcPass id) body -> Arity #
isSingletonMatchGroup :: [LMatch id body] -> Bool #
Is there only one RHS in this list of matches?
isEmptyMatchGroup :: MatchGroup id body -> Bool #
isInfixMatch :: Match id body -> Bool #
isQuietHsCmd :: HsCmd id -> Bool #
isAtomicHsExpr :: HsExpr id -> Bool #
parenthesizeHsExpr :: forall (p :: Pass). PprPrec -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #
checks if parenthesizeHsExpr
p e
is true,
and if so, surrounds hsExprNeedsParens
p ee
with an HsPar
. Otherwise, it simply returns e
.
hsExprNeedsParens :: PprPrec -> HsExpr p -> Bool #
returns hsExprNeedsParens
p eTrue
if the expression e
needs
parentheses under precedence p
.
pprParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> HsExpr (GhcPass p) -> SDoc #
pprParendLExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc #
pprDebugParendExpr :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LHsExpr (GhcPass p) -> SDoc #
pprExternalSrcLoc :: (StringLiteral, (Int, Int), (Int, Int)) -> SDoc #
ppr_apps :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> [Either (LHsExpr (GhcPass p)) (LHsWcType (NoGhcTc (GhcPass p)))] -> SDoc #
ppr_infix_expr :: forall (p :: Pass). OutputableBndrId p => HsExpr (GhcPass p) -> Maybe SDoc #
pprBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsLocalBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #
isQuietHsExpr :: HsExpr id -> Bool #
tupArgPresent :: LHsTupArg id -> Bool #
unboundVarOcc :: UnboundVar -> OccName #
mkRnSyntaxExpr :: Name -> SyntaxExpr GhcRn #
Make a 'SyntaxExpr Name' (the "rn" is because this is used in the renamer), missing its HsWrappers.
mkSyntaxExpr :: forall (p :: Pass). HsExpr (GhcPass p) -> SyntaxExpr (GhcPass p) #
Make a 'SyntaxExpr (HsExpr _)', missing its HsWrappers.
noSyntaxExpr :: forall (p :: Pass). SyntaxExpr (GhcPass p) #
noExpr :: forall (p :: Pass). HsExpr (GhcPass p) #
This is used for rebindable-syntax pieces that are too polymorphic for tcSyntaxOp (trS_fmap and the mzip in ParStmt)
type PostTcExpr = HsExpr GhcTc #
Post-Type checking Expression
PostTcExpr is an evidence expression attached to the syntax tree by the type checker (c.f. postTcType).
type PostTcTable = [(Name, PostTcExpr)] #
Post-Type checking Table
We use a PostTcTable where there are a bunch of pieces of evidence, more than is convenient to keep individually.
type CmdSyntaxTable p = [(Name, HsExpr p)] #
Command Syntax Table (for Arrow syntax)
data UnboundVar #
An unbound variable; used for treating out-of-scope variables as expression holes
Either "x", "y" Plain OutOfScope or "_", "_x" A TrueExprHole
Both forms indicate an out-of-scope variable, but the latter indicates that the user expects it to be out of scope, and just wants GHC to report its type
OutOfScope OccName GlobalRdrEnv | An (unqualified) out-of-scope variable, together with the GlobalRdrEnv with respect to which it is unbound |
TrueExprHole OccName | A "true" expression hole (_ or _x) |
Instances
Data UnboundVar | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnboundVar -> c UnboundVar # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnboundVar # toConstr :: UnboundVar -> Constr # dataTypeOf :: UnboundVar -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnboundVar) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnboundVar) # gmapT :: (forall b. Data b => b -> b) -> UnboundVar -> UnboundVar # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnboundVar -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnboundVar -> r # gmapQ :: (forall d. Data d => d -> u) -> UnboundVar -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnboundVar -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnboundVar -> m UnboundVar # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnboundVar -> m UnboundVar # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnboundVar -> m UnboundVar # | |
Outputable UnboundVar | |
Defined in GHC.Hs.Expr ppr :: UnboundVar -> SDoc # pprPrec :: Rational -> UnboundVar -> SDoc # |
data RecordConTc #
Extra data fields for a RecordCon
, added by the type checker
data RecordUpdTc #
Extra data fields for a RecordUpd
, added by the type checker
RecordUpdTc | |
|
Instances
Data RecordUpdTc | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordUpdTc -> c RecordUpdTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecordUpdTc # toConstr :: RecordUpdTc -> Constr # dataTypeOf :: RecordUpdTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecordUpdTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecordUpdTc) # gmapT :: (forall b. Data b => b -> b) -> RecordUpdTc -> RecordUpdTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordUpdTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordUpdTc -> r # gmapQ :: (forall d. Data d => d -> u) -> RecordUpdTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordUpdTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordUpdTc -> m RecordUpdTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordUpdTc -> m RecordUpdTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordUpdTc -> m RecordUpdTc # |
type LHsTupArg id = Located (HsTupArg id) #
Located Haskell Tuple Argument
HsTupArg
is used for tuple sections
(,a,)
is represented by
ExplicitTuple [Missing ty1, Present a, Missing ty3]
Which in turn stands for (x:ty1 y:ty2. (x,a,y))
Haskell Tuple Argument
data HsArrAppType #
Haskell Array Application Type
Instances
Data HsArrAppType | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrAppType -> c HsArrAppType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsArrAppType # toConstr :: HsArrAppType -> Constr # dataTypeOf :: HsArrAppType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsArrAppType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsArrAppType) # gmapT :: (forall b. Data b => b -> b) -> HsArrAppType -> HsArrAppType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrAppType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrAppType -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrAppType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrAppType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrAppType -> m HsArrAppType # |
type LHsCmdTop p = Located (HsCmdTop p) #
Top-level command, introducing a new arrow. This may occur inside a proc (where the stack is empty) or as an argument of a command-forming operator.
Located Haskell Top-level Command
Haskell Top-level Command
Instances
type HsRecordBinds p = HsRecFields p (LHsExpr p) #
Haskell Record Bindings
data MatchGroupTc #
MatchGroupTc | |
|
Instances
Data MatchGroupTc | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroupTc -> c MatchGroupTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MatchGroupTc # toConstr :: MatchGroupTc -> Constr # dataTypeOf :: MatchGroupTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MatchGroupTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MatchGroupTc) # gmapT :: (forall b. Data b => b -> b) -> MatchGroupTc -> MatchGroupTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroupTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroupTc -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroupTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroupTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroupTc -> m MatchGroupTc # |
type LMatch id body = Located (Match id body) #
Located Match
May have AnnKeywordId
: AnnSemi
when in a
list
Match | |
| |
XMatch (XXMatch p body) |
Instances
(OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) | |
(a ~ GhcPass p, ToHie body, ToHie (HsMatchContext (NameOrRdrName (IdP a))), ToHie (PScoped (LPat a)), ToHie (GRHSs a body), Data (Match a body)) => ToHie (LMatch (GhcPass p) body) | |
Guarded Right Hand Side.
GRHS (XCGRHS p body) [GuardLStmt p] body | |
XGRHS (XXGRHS p body) |
type LStmtLR idL idR body = Located (StmtLR idL idR body) #
Located Statement with separate Left and Right id's
type GuardLStmt id = LStmt id (LHsExpr id) #
Guard Located Statement
API Annotations when in qualifier lists or guards
- AnnKeywordId
: AnnVbar
,
AnnComma
,AnnThen
,
AnnBy
,AnnBy
,
AnnGroup
,AnnUsing
LastStmt (XLastStmt idL idR body) body Bool (SyntaxExpr idR) | |
BindStmt (XBindStmt idL idR body) (LPat idL) body (SyntaxExpr idR) (SyntaxExpr idR) | |
ApplicativeStmt (XApplicativeStmt idL idR body) [(SyntaxExpr idR, ApplicativeArg idL)] (Maybe (SyntaxExpr idR)) |
For full details, see Note [ApplicativeDo] in RnExpr |
BodyStmt (XBodyStmt idL idR body) body (SyntaxExpr idR) (SyntaxExpr idR) | |
LetStmt (XLetStmt idL idR body) (LHsLocalBindsLR idL idR) |
|
ParStmt (XParStmt idL idR body) [ParStmtBlock idL idR] (HsExpr idR) (SyntaxExpr idR) | |
TransStmt | |
RecStmt | |
| |
XStmtLR (XXStmtLR idL idR body) |
Instances
(a ~ GhcPass p, ToHie (PScoped (LPat a)), ToHie (LHsExpr a), ToHie (SigContext (LSig a)), ToHie (RScoped (LHsLocalBinds a)), ToHie (RScoped (ApplicativeArg a)), ToHie (Located body), Data (StmtLR a a (Located body)), Data (StmtLR a a (Located (HsExpr a)))) => ToHie (RScoped (LStmt (GhcPass p) (Located body))) | |
(OutputableBndrId pl, OutputableBndrId pr, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) | |
RecStmtTc | |
|
Instances
Data TransForm | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransForm -> c TransForm # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransForm # toConstr :: TransForm -> Constr # dataTypeOf :: TransForm -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TransForm) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransForm) # gmapT :: (forall b. Data b => b -> b) -> TransForm -> TransForm # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransForm -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransForm -> r # gmapQ :: (forall d. Data d => d -> u) -> TransForm -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TransForm -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransForm -> m TransForm # |
data ParStmtBlock idL idR #
Parenthesised Statement Block
ParStmtBlock (XParStmtBlock idL idR) [ExprLStmt idL] [IdP idR] (SyntaxExpr idR) | |
XParStmtBlock (XXParStmtBlock idL idR) |
Instances
(Outputable (StmtLR idL idL (LHsExpr idL)), Outputable (XXParStmtBlock idL idR)) => Outputable (ParStmtBlock idL idR) | |
Defined in GHC.Hs.Expr ppr :: ParStmtBlock idL idR -> SDoc # pprPrec :: Rational -> ParStmtBlock idL idR -> SDoc # |
data ApplicativeArg idL #
Applicative Argument
ApplicativeArgOne | |
| |
ApplicativeArgMany | |
| |
XApplicativeArg (XXApplicativeArg idL) |
Instances
OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) | |
Defined in GHC.Hs.Expr | |
(a ~ GhcPass p, ToHie (PScoped (LPat a)), ToHie (BindContext (LHsBind a)), ToHie (LHsExpr a), ToHie (SigContext (LSig a)), ToHie (RScoped (HsValBindsLR a a)), Data (StmtLR a a (Located (HsExpr a))), Data (HsLocalBinds a)) => ToHie (RScoped (ApplicativeArg (GhcPass p))) | |
Defined in Compat.HieAst toHie :: RScoped (ApplicativeArg (GhcPass p)) -> HieM [HieAST Type] |
data SpliceDecoration #
A splice can appear with various decorations wrapped around it. This data type captures explicitly how it was originally written, for use in the pretty printer.
Instances
newtype ThModFinalizers #
Finalizers produced by a splice with
addModFinalizer
See Note [Delaying modFinalizers in untyped splices] in RnSplice. For how this is used.
ThModFinalizers [ForeignRef (Q ())] |
Instances
Data ThModFinalizers | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ThModFinalizers -> c ThModFinalizers # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ThModFinalizers # toConstr :: ThModFinalizers -> Constr # dataTypeOf :: ThModFinalizers -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ThModFinalizers) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ThModFinalizers) # gmapT :: (forall b. Data b => b -> b) -> ThModFinalizers -> ThModFinalizers # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ThModFinalizers -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ThModFinalizers -> r # gmapQ :: (forall d. Data d => d -> u) -> ThModFinalizers -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ThModFinalizers -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ThModFinalizers -> m ThModFinalizers # |
data DelayedSplice #
Instances
Data DelayedSplice | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DelayedSplice -> c DelayedSplice # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DelayedSplice # toConstr :: DelayedSplice -> Constr # dataTypeOf :: DelayedSplice -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DelayedSplice) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DelayedSplice) # gmapT :: (forall b. Data b => b -> b) -> DelayedSplice -> DelayedSplice # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DelayedSplice -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DelayedSplice -> r # gmapQ :: (forall d. Data d => d -> u) -> DelayedSplice -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DelayedSplice -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DelayedSplice -> m DelayedSplice # |
data HsSplicedThing id #
Haskell Spliced Thing
Values that can result from running a splice.
HsSplicedExpr (HsExpr id) | Haskell Spliced Expression |
HsSplicedTy (HsType id) | Haskell Spliced Type |
HsSplicedPat (Pat id) | Haskell Spliced Pattern |
Instances
OutputableBndrId p => Outputable (HsSplicedThing (GhcPass p)) | |
Defined in GHC.Hs.Expr |
type SplicePointName = Name #
data PendingRnSplice #
Pending Renamer Splice
Instances
Outputable PendingRnSplice | |
Defined in GHC.Hs.Expr ppr :: PendingRnSplice -> SDoc # pprPrec :: Rational -> PendingRnSplice -> SDoc # | |
ToHie PendingRnSplice | |
Defined in Compat.HieAst toHie :: PendingRnSplice -> HieM [HieAST Type] |
data UntypedSpliceFlavour #
Instances
Data UntypedSpliceFlavour | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UntypedSpliceFlavour -> c UntypedSpliceFlavour # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UntypedSpliceFlavour # toConstr :: UntypedSpliceFlavour -> Constr # dataTypeOf :: UntypedSpliceFlavour -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UntypedSpliceFlavour) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UntypedSpliceFlavour) # gmapT :: (forall b. Data b => b -> b) -> UntypedSpliceFlavour -> UntypedSpliceFlavour # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UntypedSpliceFlavour -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UntypedSpliceFlavour -> r # gmapQ :: (forall d. Data d => d -> u) -> UntypedSpliceFlavour -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UntypedSpliceFlavour -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UntypedSpliceFlavour -> m UntypedSpliceFlavour # |
data PendingTcSplice #
Pending Type-checker Splice
Instances
Outputable PendingTcSplice | |
Defined in GHC.Hs.Expr ppr :: PendingTcSplice -> SDoc # pprPrec :: Rational -> PendingTcSplice -> SDoc # | |
ToHie PendingTcSplice | |
Defined in Compat.HieAst toHie :: PendingTcSplice -> HieM [HieAST Type] |
Haskell Bracket
data ArithSeqInfo id #
Arithmetic Sequence Information
From (LHsExpr id) | |
FromThen (LHsExpr id) (LHsExpr id) | |
FromTo (LHsExpr id) (LHsExpr id) | |
FromThenTo (LHsExpr id) (LHsExpr id) (LHsExpr id) |
Instances
OutputableBndrId p => Outputable (ArithSeqInfo (GhcPass p)) | |
Defined in GHC.Hs.Expr | |
ToHie (LHsExpr a) => ToHie (ArithSeqInfo a) | |
Defined in Compat.HieAst toHie :: ArithSeqInfo a -> HieM [HieAST Type] |
data HsMatchContext id #
Haskell Match Context
Context of a pattern match. This is more subtle than it would seem. See Note [Varieties of pattern matches].
FunRhs | A pattern matching on an argument of a function binding |
| |
LambdaExpr | Patterns of a lambda |
CaseAlt | Patterns and guards on a case alternative |
IfAlt | Guards of a multi-way if alternative |
ProcExpr | Patterns of a proc |
PatBindRhs | A pattern binding eg [y] <- e = e |
PatBindGuards | Guards of pattern bindings, e.g., (Just b) | Just _ <- x = e | otherwise = e' |
RecUpd | Record update [used only in DsExpr to tell matchWrapper what sort of runtime error message to generate] |
StmtCtxt (HsStmtContext id) | Pattern of a do-stmt, list comprehension, pattern guard, etc |
ThPatSplice | A Template Haskell pattern splice |
ThPatQuote | A Template Haskell pattern quotation [p| (a,b) |] |
PatSyn | A pattern synonym declaration |
Instances
Functor HsMatchContext | |
Defined in GHC.Hs.Expr fmap :: (a -> b) -> HsMatchContext a -> HsMatchContext b # (<$) :: a -> HsMatchContext b -> HsMatchContext a # | |
Data id => Data (HsMatchContext id) | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsMatchContext id -> c (HsMatchContext id) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext id) # toConstr :: HsMatchContext id -> Constr # dataTypeOf :: HsMatchContext id -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext id)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext id)) # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext id -> HsMatchContext id # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext id -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext id -> r # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext id -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext id -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext id -> m (HsMatchContext id) # | |
OutputableBndr id => Outputable (HsMatchContext id) | |
Defined in GHC.Hs.Expr ppr :: HsMatchContext id -> SDoc # pprPrec :: Rational -> HsMatchContext id -> SDoc # | |
ToHie (Context (Located a)) => ToHie (HsMatchContext a) | |
Defined in Compat.HieAst toHie :: HsMatchContext a -> HieM [HieAST Type] |
data HsStmtContext id #
Haskell Statement Context. It expects to be parameterised with one of
RdrName
, Name
or Id
ListComp | |
MonadComp | |
DoExpr | do { ... } |
MDoExpr | mdo { ... } ie recursive do-expression |
ArrowExpr | do-notation in an arrow-command context |
GhciStmtCtxt | A command-line Stmt in GHCi pat <- rhs |
PatGuard (HsMatchContext id) | Pattern guard for specified thing |
ParStmtCtxt (HsStmtContext id) | A branch of a parallel stmt |
TransStmtCtxt (HsStmtContext id) | A branch of a transform stmt |
Instances
Functor HsStmtContext | |
Defined in GHC.Hs.Expr fmap :: (a -> b) -> HsStmtContext a -> HsStmtContext b # (<$) :: a -> HsStmtContext b -> HsStmtContext a # | |
Data id => Data (HsStmtContext id) | |
Defined in GHC.Hs.Expr gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsStmtContext id -> c (HsStmtContext id) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext id) # toConstr :: HsStmtContext id -> Constr # dataTypeOf :: HsStmtContext id -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext id)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext id)) # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext id -> HsStmtContext id # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext id -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext id -> r # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext id -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext id -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext id -> m (HsStmtContext id) # | |
(Outputable (GhcPass p), Outputable (NameOrRdrName (GhcPass p))) => Outputable (HsStmtContext (GhcPass p)) | |
Defined in GHC.Hs.Expr | |
ToHie (HsMatchContext a) => ToHie (HsStmtContext a) | |
Defined in Compat.HieAst toHie :: HsStmtContext a -> HieM [HieAST Type] |
roleAnnotDeclName :: forall (p :: Pass). RoleAnnotDecl (GhcPass p) -> IdP (GhcPass p) #
annProvenanceName_maybe :: AnnProvenance name -> Maybe name #
docDeclDoc :: DocDecl -> HsDocString #
pprFullRuleName :: Located (SourceText, RuleName) -> SDoc #
collectRuleBndrSigTys :: [RuleBndr pass] -> [LHsSigWcType pass] #
flattenRuleDecls :: [LRuleDecls pass] -> [LRuleDecl pass] #
mapDerivStrategy :: forall p (pass :: Pass). p ~ GhcPass pass => (XViaStrategy p -> XViaStrategy p) -> DerivStrategy p -> DerivStrategy p #
Map over the via
type if dealing with ViaStrategy
. Otherwise,
return the DerivStrategy
unchanged.
foldDerivStrategy :: forall p (pass :: Pass) r. p ~ GhcPass pass => r -> (XViaStrategy p -> r) -> DerivStrategy p -> r #
Eliminate a DerivStrategy
.
derivStrategyName :: DerivStrategy a -> SDoc #
A short description of a DerivStrategy'
.
instDeclDataFamInsts :: forall (p :: Pass). [LInstDecl (GhcPass p)] -> [DataFamInstDecl (GhcPass p)] #
pprHsFamInstLHS :: forall (p :: Pass). OutputableBndrId p => IdP (GhcPass p) -> Maybe [LHsTyVarBndr (GhcPass p)] -> HsTyPats (GhcPass p) -> LexicalFixity -> LHsContext (GhcPass p) -> SDoc #
pprDataFamInstFlavour :: forall (p :: Pass). DataFamInstDecl (GhcPass p) -> SDoc #
pprTyFamInstDecl :: forall (p :: Pass). OutputableBndrId p => TopLevelFlag -> TyFamInstDecl (GhcPass p) -> SDoc #
hsConDeclTheta :: Maybe (LHsContext pass) -> [LHsType pass] #
hsConDeclArgTys :: HsConDeclDetails pass -> [LBangType pass] #
getConArgs :: ConDecl pass -> HsConDeclDetails pass #
newOrDataToFlavour :: NewOrData -> TyConFlavour #
Convert a NewOrData
to a TyConFlavour
standaloneKindSigName :: forall (p :: Pass). StandaloneKindSig (GhcPass p) -> IdP (GhcPass p) #
resultVariableName :: forall (a :: Pass). FamilyResultSig (GhcPass a) -> Maybe (IdP (GhcPass a)) #
Maybe return name of the result type variable
famResultKindSignature :: forall (p :: Pass). FamilyResultSig (GhcPass p) -> Maybe (LHsKind (GhcPass p)) #
familyDeclName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> IdP (GhcPass p) #
familyDeclLName :: forall (p :: Pass). FamilyDecl (GhcPass p) -> Located (IdP (GhcPass p)) #
tyClGroupKindSigs :: [TyClGroup pass] -> [LStandaloneKindSig pass] #
tyClGroupRoleDecls :: [TyClGroup pass] -> [LRoleAnnotDecl pass] #
tyClGroupInstDecls :: [TyClGroup pass] -> [LInstDecl pass] #
tyClGroupTyClDecls :: [TyClGroup pass] -> [LTyClDecl pass] #
hsDeclHasCusk :: TyClDecl GhcRn -> Bool #
Does this declaration have a complete, user-supplied kind signature? See Note [CUSKs: complete user-supplied kind signatures]
tyClDeclTyVars :: TyClDecl pass -> LHsQTyVars pass #
tyFamInstDeclLName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> Located (IdP (GhcPass p)) #
tyFamInstDeclName :: forall (p :: Pass). TyFamInstDecl (GhcPass p) -> IdP (GhcPass p) #
isDataFamilyDecl :: TyClDecl pass -> Bool #
data family declaration
isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool #
closed type family info
isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool #
open type family info
isTypeFamilyDecl :: TyClDecl pass -> Bool #
type family declaration
isFamilyDecl :: TyClDecl pass -> Bool #
type/data family declaration
isClassDecl :: TyClDecl pass -> Bool #
type class
isDataDecl :: TyClDecl pass -> Bool #
True
= argument is a data
/newtype
declaration.
appendGroups :: forall (p :: Pass). HsGroup (GhcPass p) -> HsGroup (GhcPass p) -> HsGroup (GhcPass p) #
hsGroupInstDecls :: HsGroup id -> [LInstDecl id] #
emptyRnGroup :: forall (p :: Pass). HsGroup (GhcPass p) #
emptyRdrGroup :: forall (p :: Pass). HsGroup (GhcPass p) #
A Haskell Declaration
TyClD (XTyClD p) (TyClDecl p) | Type or Class Declaration |
InstD (XInstD p) (InstDecl p) | Instance declaration |
DerivD (XDerivD p) (DerivDecl p) | Deriving declaration |
ValD (XValD p) (HsBind p) | Value declaration |
SigD (XSigD p) (Sig p) | Signature declaration |
KindSigD (XKindSigD p) (StandaloneKindSig p) | Standalone kind signature |
DefD (XDefD p) (DefaultDecl p) | 'default' declaration |
ForD (XForD p) (ForeignDecl p) | Foreign declaration |
WarningD (XWarningD p) (WarnDecls p) | Warning declaration |
AnnD (XAnnD p) (AnnDecl p) | Annotation declaration |
RuleD (XRuleD p) (RuleDecls p) | Rule declaration |
SpliceD (XSpliceD p) (SpliceDecl p) | Splice declaration (Includes quasi-quotes) |
DocD (XDocD p) DocDecl | Documentation comment declaration |
RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p) | Role annotation declaration |
XHsDecl (XXHsDecl p) |
HsGroup | |
| |
XHsGroup (XXHsGroup p) |
type LSpliceDecl pass = Located (SpliceDecl pass) #
Located Splice Declaration
data SpliceDecl p #
Splice Declaration
SpliceDecl (XSpliceDecl p) (Located (HsSplice p)) SpliceExplicitFlag | |
XSpliceDecl (XXSpliceDecl p) |
Instances
OutputableBndrId p => Outputable (SpliceDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LSpliceDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type] |
A type or class declaration.
FamDecl | type/data family T :: *->* |
| |
SynDecl |
|
DataDecl |
|
| |
ClassDecl | |
| |
XTyClDecl (XXTyClDecl pass) |
data DataDeclRn #
DataDeclRn | |
|
Instances
Data DataDeclRn | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataDeclRn -> c DataDeclRn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataDeclRn # toConstr :: DataDeclRn -> Constr # dataTypeOf :: DataDeclRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataDeclRn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataDeclRn) # gmapT :: (forall b. Data b => b -> b) -> DataDeclRn -> DataDeclRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataDeclRn -> r # gmapQ :: (forall d. Data d => d -> u) -> DataDeclRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataDeclRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataDeclRn -> m DataDeclRn # |
Type or Class Group
TyClGroup | |
| |
XTyClGroup (XXTyClGroup pass) |
type LFamilyResultSig pass = Located (FamilyResultSig pass) #
Located type Family Result Signature
data FamilyResultSig pass #
type Family Result Signature
NoSig (XNoSig pass) | |
KindSig (XCKindSig pass) (LHsKind pass) | |
TyVarSig (XTyVarSig pass) (LHsTyVarBndr pass) | |
XFamilyResultSig (XXFamilyResultSig pass) |
Instances
ToHie (RScoped (LFamilyResultSig GhcRn)) | |
Defined in Compat.HieAst toHie :: RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type] |
type LFamilyDecl pass = Located (FamilyDecl pass) #
Located type Family Declaration
data FamilyDecl pass #
type Family Declaration
FamilyDecl | |
| |
XFamilyDecl (XXFamilyDecl pass) |
Instances
OutputableBndrId p => Outputable (FamilyDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LFamilyDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LFamilyDecl GhcRn -> HieM [HieAST Type] |
type LInjectivityAnn pass = Located (InjectivityAnn pass) #
Located Injectivity Annotation
data InjectivityAnn pass #
If the user supplied an injectivity annotation it is represented using InjectivityAnn. At the moment this is a single injectivity condition - see Note [Injectivity annotation]. `Located name` stores the LHS of injectivity condition. `[Located name]` stores the RHS of injectivity condition. Example:
type family Foo a b c = r | r -> a c where ...
This will be represented as "InjectivityAnn r
[a
, c
]"
InjectivityAnn (Located (IdP pass)) [Located (IdP pass)] |
Instances
ToHie (LInjectivityAnn GhcRn) | |
Defined in Compat.HieAst toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type] |
data FamilyInfo pass #
DataFamily | |
OpenTypeFamily | |
ClosedTypeFamily (Maybe [LTyFamInstEqn pass]) |
|
Instances
Outputable (FamilyInfo pass) | |
Defined in GHC.Hs.Decls ppr :: FamilyInfo pass -> SDoc # pprPrec :: Rational -> FamilyInfo pass -> SDoc # | |
ToHie (FamilyInfo GhcRn) | |
Defined in Compat.HieAst toHie :: FamilyInfo GhcRn -> HieM [HieAST Type] |
data HsDataDefn pass #
Haskell Data type Definition
HsDataDefn | Declares a data type or newtype, giving its constructors
|
| |
XHsDataDefn (XXHsDataDefn pass) |
Instances
OutputableBndrId p => Outputable (HsDataDefn (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
HasLoc (HsDataDefn GhcRn) | |
Defined in Compat.HieAst loc :: HsDataDefn GhcRn -> SrcSpan | |
ToHie (HsDataDefn GhcRn) | |
Defined in Compat.HieAst toHie :: HsDataDefn GhcRn -> HieM [HieAST Type] |
type HsDeriving pass #
= Located [LHsDerivingClause pass] | The optional The list of |
Haskell Deriving clause
type LHsDerivingClause pass = Located (HsDerivingClause pass) #
data HsDerivingClause pass #
A single deriving
clause of a data declaration.
HsDerivingClause | |
| |
XHsDerivingClause (XXHsDerivingClause pass) |
Instances
OutputableBndrId p => Outputable (HsDerivingClause (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (HsDeriving GhcRn) | |
Defined in Compat.HieAst toHie :: HsDeriving GhcRn -> HieM [HieAST Type] | |
ToHie (LHsDerivingClause GhcRn) | |
Defined in Compat.HieAst toHie :: LHsDerivingClause GhcRn -> HieM [HieAST Type] |
type LStandaloneKindSig pass = Located (StandaloneKindSig pass) #
Located Standalone Kind Signature
data StandaloneKindSig pass #
StandaloneKindSig (XStandaloneKindSig pass) (Located (IdP pass)) (LHsSigType pass) | |
XStandaloneKindSig (XXStandaloneKindSig pass) |
Instances
OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LStandaloneKindSig GhcRn) | |
Defined in Compat.HieAst toHie :: LStandaloneKindSig GhcRn -> HieM [HieAST Type] | |
ToHie (StandaloneKindSig GhcRn) | |
Defined in Compat.HieAst toHie :: StandaloneKindSig GhcRn -> HieM [HieAST Type] |
Instances
Eq NewOrData | |
Data NewOrData | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewOrData -> c NewOrData # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewOrData # toConstr :: NewOrData -> Constr # dataTypeOf :: NewOrData -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewOrData) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewOrData) # gmapT :: (forall b. Data b => b -> b) -> NewOrData -> NewOrData # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewOrData -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewOrData -> r # gmapQ :: (forall d. Data d => d -> u) -> NewOrData -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NewOrData -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewOrData -> m NewOrData # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewOrData -> m NewOrData # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewOrData -> m NewOrData # | |
Outputable NewOrData | |
= Located (ConDecl pass) | May have |
Located data Constructor Declaration
data T b = forall a. Eq a => MkT a b MkT :: forall b a. Eq a => MkT a b data T b where MkT1 :: Int -> T Int data T = IntMkT
Int | MkT2 data T a where IntMkT
Int :: T Int
AnnKeywordId
s :AnnOpen
,AnnDotdot
,AnnCLose
,AnnEqual
,AnnVbar
,AnnDarrow
,AnnDarrow
,AnnForall
,AnnDot
data Constructor Declaration
ConDeclGADT | |
| |
ConDeclH98 | |
| |
XConDecl (XXConDecl pass) |
type HsConDeclDetails pass = HsConDetails (LBangType pass) (Located [LConDeclField pass]) #
Haskell data Constructor Declaration Details
type LTyFamInstEqn pass #
= Located (TyFamInstEqn pass) | May have |
Located Type Family Instance Equation
type HsTyPats pass = [LHsTypeArg pass] #
Haskell Type Patterns
type TyFamInstEqn pass = FamInstEqn pass (LHsType pass) #
Type Family Instance Equation
type TyFamDefltDecl = TyFamInstDecl #
Type family default declarations.
A convenient synonym for TyFamInstDecl
.
See Note [Type family instance declarations in HsSyn]
.
type LTyFamDefltDecl pass = Located (TyFamDefltDecl pass) #
Located type family default declarations.
type LTyFamInstDecl pass = Located (TyFamInstDecl pass) #
Located Type Family Instance Declaration
newtype TyFamInstDecl pass #
Type Family Instance Declaration
Instances
OutputableBndrId p => Outputable (TyFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LTyFamInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type] |
type LDataFamInstDecl pass = Located (DataFamInstDecl pass) #
Located Data Family Instance Declaration
newtype DataFamInstDecl pass #
Data Family Instance Declaration
DataFamInstDecl | |
|
Instances
OutputableBndrId p => Outputable (DataFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LDataFamInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type] |
type LFamInstEqn pass rhs = Located (FamInstEqn pass rhs) #
Located Family Instance Equation
type FamInstEqn pass rhs #
= HsImplicitBndrs pass (FamEqn pass rhs) | Here, the |
Family Instance Equation
Family Equation
One equation in a type family instance declaration, data family instance declaration, or type family default. See Note [Type family instance declarations in HsSyn] See Note [Family instance declaration binders]
FamEqn | |
| |
XFamEqn (XXFamEqn pass rhs) |
type LClsInstDecl pass = Located (ClsInstDecl pass) #
Located Class Instance Declaration
data ClsInstDecl pass #
Class Instance Declaration
ClsInstDecl | |
| |
XClsInstDecl (XXClsInstDecl pass) |
Instances
OutputableBndrId p => Outputable (ClsInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LClsInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type] |
Instance Declaration
ClsInstD | |
| |
DataFamInstD | |
| |
TyFamInstD | |
| |
XInstDecl (XXInstDecl pass) |
type LDerivDecl pass = Located (DerivDecl pass) #
Located stand-alone 'deriving instance' declaration
Stand-alone 'deriving instance' declaration
DerivDecl | |
| |
XDerivDecl (XXDerivDecl pass) |
Instances
OutputableBndrId p => Outputable (DerivDecl (GhcPass p)) | |
ToHie (LDerivDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDerivDecl GhcRn -> HieM [HieAST Type] |
type LDerivStrategy pass = Located (DerivStrategy pass) #
data DerivStrategy pass #
Which technique the user explicitly requested when deriving an instance.
StockStrategy | GHC's "standard" strategy, which is to implement a
custom instance for the data type. This only works
for certain types that GHC knows about (e.g., |
AnyclassStrategy | -XDeriveAnyClass |
NewtypeStrategy | -XGeneralizedNewtypeDeriving |
ViaStrategy (XViaStrategy pass) | -XDerivingVia |
Instances
OutputableBndrId p => Outputable (DerivStrategy (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (Located (DerivStrategy GhcRn)) | |
Defined in Compat.HieAst |
type LDefaultDecl pass = Located (DefaultDecl pass) #
Located Default Declaration
data DefaultDecl pass #
Default Declaration
DefaultDecl (XCDefaultDecl pass) [LHsType pass] | |
XDefaultDecl (XXDefaultDecl pass) |
Instances
OutputableBndrId p => Outputable (DefaultDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LDefaultDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type] |
type LForeignDecl pass = Located (ForeignDecl pass) #
Located Foreign Declaration
data ForeignDecl pass #
Foreign Declaration
ForeignImport | |
| |
ForeignExport | |
| |
XForeignDecl (XXForeignDecl pass) |
Instances
OutputableBndrId p => Outputable (ForeignDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LForeignDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LForeignDecl GhcRn -> HieM [HieAST Type] |
data ForeignImport #
Instances
Data ForeignImport | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignImport -> c ForeignImport # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignImport # toConstr :: ForeignImport -> Constr # dataTypeOf :: ForeignImport -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignImport) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignImport) # gmapT :: (forall b. Data b => b -> b) -> ForeignImport -> ForeignImport # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignImport -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignImport -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignImport -> m ForeignImport # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport -> m ForeignImport # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport -> m ForeignImport # | |
Outputable ForeignImport | |
Defined in GHC.Hs.Decls ppr :: ForeignImport -> SDoc # pprPrec :: Rational -> ForeignImport -> SDoc # | |
ToHie ForeignImport | |
Defined in Compat.HieAst toHie :: ForeignImport -> HieM [HieAST Type] |
data CImportSpec #
Instances
Data CImportSpec | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CImportSpec -> c CImportSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CImportSpec # toConstr :: CImportSpec -> Constr # dataTypeOf :: CImportSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CImportSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CImportSpec) # gmapT :: (forall b. Data b => b -> b) -> CImportSpec -> CImportSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CImportSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CImportSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> CImportSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CImportSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CImportSpec -> m CImportSpec # |
data ForeignExport #
Instances
Data ForeignExport | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignExport -> c ForeignExport # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForeignExport # toConstr :: ForeignExport -> Constr # dataTypeOf :: ForeignExport -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForeignExport) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForeignExport) # gmapT :: (forall b. Data b => b -> b) -> ForeignExport -> ForeignExport # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignExport -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignExport -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignExport -> m ForeignExport # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport -> m ForeignExport # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport -> m ForeignExport # | |
Outputable ForeignExport | |
Defined in GHC.Hs.Decls ppr :: ForeignExport -> SDoc # pprPrec :: Rational -> ForeignExport -> SDoc # | |
ToHie ForeignExport | |
Defined in Compat.HieAst toHie :: ForeignExport -> HieM [HieAST Type] |
type LRuleDecls pass = Located (RuleDecls pass) #
Located Rule Declarations
Rule Declarations
HsRules | |
| |
XRuleDecls (XXRuleDecls pass) |
Instances
OutputableBndrId p => Outputable (RuleDecls (GhcPass p)) | |
ToHie (LRuleDecls GhcRn) | |
Defined in Compat.HieAst toHie :: LRuleDecls GhcRn -> HieM [HieAST Type] |
Rule Declaration
HsRule | |
| |
XRuleDecl (XXRuleDecl pass) |
Instances
Data HsRuleRn | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRuleRn -> c HsRuleRn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsRuleRn # toConstr :: HsRuleRn -> Constr # dataTypeOf :: HsRuleRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsRuleRn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsRuleRn) # gmapT :: (forall b. Data b => b -> b) -> HsRuleRn -> HsRuleRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRuleRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRuleRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsRuleRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRuleRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRuleRn -> m HsRuleRn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRuleRn -> m HsRuleRn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRuleRn -> m HsRuleRn # |
Rule Binder
RuleBndr (XCRuleBndr pass) (Located (IdP pass)) | |
RuleBndrSig (XRuleBndrSig pass) (Located (IdP pass)) (LHsSigWcType pass) | |
XRuleBndr (XXRuleBndr pass) |
Documentation comment Declaration
DocCommentNext HsDocString | |
DocCommentPrev HsDocString | |
DocCommentNamed String HsDocString | |
DocGroup Int HsDocString |
Instances
Data DocDecl | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DocDecl -> c DocDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DocDecl # toConstr :: DocDecl -> Constr # dataTypeOf :: DocDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DocDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DocDecl) # gmapT :: (forall b. Data b => b -> b) -> DocDecl -> DocDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DocDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DocDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> DocDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DocDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DocDecl -> m DocDecl # | |
Outputable DocDecl | |
type LWarnDecls pass = Located (WarnDecls pass) #
Located Warning Declarations
Warning pragma Declarations
Warnings | |
| |
XWarnDecls (XXWarnDecls pass) |
Instances
OutputableBndr (IdP (GhcPass p)) => Outputable (WarnDecls (GhcPass p)) | |
ToHie (LWarnDecls GhcRn) | |
Defined in Compat.HieAst toHie :: LWarnDecls GhcRn -> HieM [HieAST Type] |
Warning pragma Declaration
Warning (XWarning pass) [Located (IdP pass)] WarningTxt | |
XWarnDecl (XXWarnDecl pass) |
Annotation Declaration
HsAnnotation (XHsAnnotation pass) SourceText (AnnProvenance (IdP pass)) (Located (HsExpr pass)) | |
XAnnDecl (XXAnnDecl pass) |
data AnnProvenance name #
Annotation Provenance
ValueAnnProvenance (Located name) | |
TypeAnnProvenance (Located name) | |
ModuleAnnProvenance |
Instances
Functor AnnProvenance | |
Defined in GHC.Hs.Decls fmap :: (a -> b) -> AnnProvenance a -> AnnProvenance b # (<$) :: a -> AnnProvenance b -> AnnProvenance a # | |
Foldable AnnProvenance | |
Defined in GHC.Hs.Decls fold :: Monoid m => AnnProvenance m -> m # foldMap :: Monoid m => (a -> m) -> AnnProvenance a -> m # foldMap' :: Monoid m => (a -> m) -> AnnProvenance a -> m # foldr :: (a -> b -> b) -> b -> AnnProvenance a -> b # foldr' :: (a -> b -> b) -> b -> AnnProvenance a -> b # foldl :: (b -> a -> b) -> b -> AnnProvenance a -> b # foldl' :: (b -> a -> b) -> b -> AnnProvenance a -> b # foldr1 :: (a -> a -> a) -> AnnProvenance a -> a # foldl1 :: (a -> a -> a) -> AnnProvenance a -> a # toList :: AnnProvenance a -> [a] # null :: AnnProvenance a -> Bool # length :: AnnProvenance a -> Int # elem :: Eq a => a -> AnnProvenance a -> Bool # maximum :: Ord a => AnnProvenance a -> a # minimum :: Ord a => AnnProvenance a -> a # sum :: Num a => AnnProvenance a -> a # product :: Num a => AnnProvenance a -> a # | |
Traversable AnnProvenance | |
Defined in GHC.Hs.Decls traverse :: Applicative f => (a -> f b) -> AnnProvenance a -> f (AnnProvenance b) # sequenceA :: Applicative f => AnnProvenance (f a) -> f (AnnProvenance a) # mapM :: Monad m => (a -> m b) -> AnnProvenance a -> m (AnnProvenance b) # sequence :: Monad m => AnnProvenance (m a) -> m (AnnProvenance a) # | |
Data pass => Data (AnnProvenance pass) | |
Defined in GHC.Hs.Decls gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnProvenance pass -> c (AnnProvenance pass) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance pass) # toConstr :: AnnProvenance pass -> Constr # dataTypeOf :: AnnProvenance pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance pass)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance pass)) # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance pass -> AnnProvenance pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance pass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance pass -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance pass -> m (AnnProvenance pass) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance pass -> m (AnnProvenance pass) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance pass -> m (AnnProvenance pass) # | |
ToHie (Context (Located a)) => ToHie (AnnProvenance a) | |
Defined in Compat.HieAst toHie :: AnnProvenance a -> HieM [HieAST Type] |
type LRoleAnnotDecl pass = Located (RoleAnnotDecl pass) #
Located Role Annotation Declaration
data RoleAnnotDecl pass #
Role Annotation Declaration
RoleAnnotDecl (XCRoleAnnotDecl pass) (Located (IdP pass)) [Located (Maybe Role)] | |
XRoleAnnotDecl (XXRoleAnnotDecl pass) |
Instances
OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
ToHie (LRoleAnnotDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type] |
parenthesizePat :: forall (p :: Pass). PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p) #
checks if parenthesizePat
p pat
is true, and
if so, surrounds patNeedsParens
p patpat
with a ParPat
. Otherwise, it simply returns pat
.
patNeedsParens :: PprPrec -> Pat p -> Bool #
returns patNeedsParens
p patTrue
if the pattern pat
needs
parentheses under precedence p
.
isIrrefutableHsPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> Bool #
mkCharLitPat :: forall (p :: Pass). SourceText -> Char -> OutPat (GhcPass p) #
mkPrefixConPat :: forall (p :: Pass). DataCon -> [OutPat (GhcPass p)] -> [Type] -> OutPat (GhcPass p) #
pprConArgs :: forall (p :: Pass). OutputableBndrId p => HsConPatDetails (GhcPass p) -> SDoc #
pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc #
hsRecUpdFieldOcc :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> LFieldOcc GhcTc #
hsRecUpdFieldId :: HsRecField' (AmbiguousFieldOcc GhcTc) arg -> Located Id #
hsRecUpdFieldRdr :: forall (p :: Pass). HsRecUpdField (GhcPass p) -> Located RdrName #
hsRecFieldId :: HsRecField GhcTc arg -> Located Id #
hsRecFieldSel :: HsRecField pass arg -> Located (XCFieldOcc pass) #
hsRecFieldsArgs :: HsRecFields p arg -> [arg] #
hsRecFields :: HsRecFields p arg -> [XCFieldOcc p] #
hsConPatArgs :: HsConPatDetails p -> [LPat p] #
type HsConPatDetails p = HsConDetails (LPat p) (HsRecFields p (LPat p)) #
Haskell Constructor Pattern Details
data HsRecFields p arg #
Haskell Record Fields
HsRecFields is used only for patterns and expressions (not data type declarations)
HsRecFields | |
|
Instances
Functor (HsRecFields p) | |
Defined in GHC.Hs.Pat fmap :: (a -> b) -> HsRecFields p a -> HsRecFields p b # (<$) :: a -> HsRecFields p b -> HsRecFields p a # | |
Foldable (HsRecFields p) | |
Defined in GHC.Hs.Pat fold :: Monoid m => HsRecFields p m -> m # foldMap :: Monoid m => (a -> m) -> HsRecFields p a -> m # foldMap' :: Monoid m => (a -> m) -> HsRecFields p a -> m # foldr :: (a -> b -> b) -> b -> HsRecFields p a -> b # foldr' :: (a -> b -> b) -> b -> HsRecFields p a -> b # foldl :: (b -> a -> b) -> b -> HsRecFields p a -> b # foldl' :: (b -> a -> b) -> b -> HsRecFields p a -> b # foldr1 :: (a -> a -> a) -> HsRecFields p a -> a # foldl1 :: (a -> a -> a) -> HsRecFields p a -> a # toList :: HsRecFields p a -> [a] # null :: HsRecFields p a -> Bool # length :: HsRecFields p a -> Int # elem :: Eq a => a -> HsRecFields p a -> Bool # maximum :: Ord a => HsRecFields p a -> a # minimum :: Ord a => HsRecFields p a -> a # sum :: Num a => HsRecFields p a -> a # product :: Num a => HsRecFields p a -> a # | |
Traversable (HsRecFields p) | |
Defined in GHC.Hs.Pat traverse :: Applicative f => (a -> f b) -> HsRecFields p a -> f (HsRecFields p b) # sequenceA :: Applicative f => HsRecFields p (f a) -> f (HsRecFields p a) # mapM :: Monad m => (a -> m b) -> HsRecFields p a -> m (HsRecFields p b) # sequence :: Monad m => HsRecFields p (m a) -> m (HsRecFields p a) # | |
ToHie (RContext (LHsRecField a arg)) => ToHie (RContext (HsRecFields a arg)) | |
Defined in Compat.HieAst toHie :: RContext (HsRecFields a arg) -> HieM [HieAST Type] | |
Outputable arg => Outputable (HsRecFields p arg) | |
Defined in GHC.Hs.Pat ppr :: HsRecFields p arg -> SDoc # pprPrec :: Rational -> HsRecFields p arg -> SDoc # |
type LHsRecField' p arg = Located (HsRecField' p arg) #
Located Haskell Record Field
type LHsRecField p arg = Located (HsRecField p arg) #
Located Haskell Record Field
type LHsRecUpdField p = Located (HsRecUpdField p) #
Located Haskell Record Update Field
type HsRecField p arg = HsRecField' (FieldOcc p) arg #
Haskell Record Field
type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p) #
Haskell Record Update Field
data HsRecField' id arg #
Haskell Record Field
For details on above see note [Api annotations] in ApiAnnotation
HsRecField | |
|
Instances
Functor (HsRecField' id) | |
Defined in GHC.Hs.Pat fmap :: (a -> b) -> HsRecField' id a -> HsRecField' id b # (<$) :: a -> HsRecField' id b -> HsRecField' id a # | |
Foldable (HsRecField' id) | |
Defined in GHC.Hs.Pat fold :: Monoid m => HsRecField' id m -> m # foldMap :: Monoid m => (a -> m) -> HsRecField' id a -> m # foldMap' :: Monoid m => (a -> m) -> HsRecField' id a -> m # foldr :: (a -> b -> b) -> b -> HsRecField' id a -> b # foldr' :: (a -> b -> b) -> b -> HsRecField' id a -> b # foldl :: (b -> a -> b) -> b -> HsRecField' id a -> b # foldl' :: (b -> a -> b) -> b -> HsRecField' id a -> b # foldr1 :: (a -> a -> a) -> HsRecField' id a -> a # foldl1 :: (a -> a -> a) -> HsRecField' id a -> a # toList :: HsRecField' id a -> [a] # null :: HsRecField' id a -> Bool # length :: HsRecField' id a -> Int # elem :: Eq a => a -> HsRecField' id a -> Bool # maximum :: Ord a => HsRecField' id a -> a # minimum :: Ord a => HsRecField' id a -> a # sum :: Num a => HsRecField' id a -> a # product :: Num a => HsRecField' id a -> a # | |
Traversable (HsRecField' id) | |
Defined in GHC.Hs.Pat traverse :: Applicative f => (a -> f b) -> HsRecField' id a -> f (HsRecField' id b) # sequenceA :: Applicative f => HsRecField' id (f a) -> f (HsRecField' id a) # mapM :: Monad m => (a -> m b) -> HsRecField' id a -> m (HsRecField' id b) # sequence :: Monad m => HsRecField' id (m a) -> m (HsRecField' id a) # | |
(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data label, Data arg) => ToHie (RContext (LHsRecField' label arg)) | |
Defined in Compat.HieAst toHie :: RContext (LHsRecField' label arg) -> HieM [HieAST Type] | |
(Data id, Data arg) => Data (HsRecField' id arg) | |
Defined in GHC.Hs.Pat gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecField' id arg -> c (HsRecField' id arg) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecField' id arg) # toConstr :: HsRecField' id arg -> Constr # dataTypeOf :: HsRecField' id arg -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecField' id arg)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecField' id arg)) # gmapT :: (forall b. Data b => b -> b) -> HsRecField' id arg -> HsRecField' id arg # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecField' id arg -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecField' id arg -> r # gmapQ :: (forall d. Data d => d -> u) -> HsRecField' id arg -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecField' id arg -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) # | |
(Outputable p, Outputable arg) => Outputable (HsRecField' p arg) | |
Defined in GHC.Hs.Pat ppr :: HsRecField' p arg -> SDoc # pprPrec :: Rational -> HsRecField' p arg -> SDoc # |
pprMinimalSig :: OutputableBndr name => LBooleanFormula (Located name) -> SDoc #
pprTcSpecPrags :: TcSpecPrags -> SDoc #
pprSpec :: OutputableBndr id => id -> SDoc -> InlinePragma -> SDoc #
pprVarSig :: OutputableBndr id => [id] -> SDoc -> SDoc #
pragSrcBrackets :: SourceText -> String -> SDoc -> SDoc #
Using SourceText in case the pragma was spelled differently or used mixed case
pragBrackets :: SDoc -> SDoc #
isCompleteMatchSig :: LSig name -> Bool #
isSCCFunSig :: LSig name -> Bool #
isMinimalLSig :: LSig name -> Bool #
isInlineLSig :: LSig name -> Bool #
isPragLSig :: LSig name -> Bool #
isSpecInstLSig :: LSig name -> Bool #
isSpecLSig :: LSig name -> Bool #
isTypeLSig :: LSig name -> Bool #
isFixityLSig :: LSig name -> Bool #
isDefaultMethod :: TcSpecPrags -> Bool #
hasSpecPrags :: TcSpecPrags -> Bool #
isEmptyIPBindsTc :: HsIPBinds GhcTc -> Bool #
ppr_monobind :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => HsBindLR (GhcPass idL) (GhcPass idR) -> SDoc #
plusHsValBinds :: forall (a :: Pass). HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) -> HsValBinds (GhcPass a) #
isEmptyLHsBinds :: LHsBindsLR idL idR -> Bool #
emptyLHsBinds :: LHsBindsLR idL idR #
emptyValBindsOut :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #
emptyValBindsIn :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) #
isEmptyValBinds :: forall (a :: Pass) (b :: Pass). HsValBindsLR (GhcPass a) (GhcPass b) -> Bool #
eqEmptyLocalBinds :: HsLocalBindsLR a b -> Bool #
isEmptyLocalBindsPR :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) -> Bool #
isEmptyLocalBindsTc :: forall (a :: Pass). HsLocalBindsLR (GhcPass a) GhcTc -> Bool #
emptyLocalBinds :: forall (a :: Pass) (b :: Pass). HsLocalBindsLR (GhcPass a) (GhcPass b) #
pprDeclList :: [SDoc] -> SDoc #
pprLHsBindsForUser :: forall (idL :: Pass) (idR :: Pass) (id2 :: Pass). (OutputableBndrId idL, OutputableBndrId idR, OutputableBndrId id2) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> [LSig (GhcPass id2)] -> [SDoc] #
pprLHsBinds :: forall (idL :: Pass) (idR :: Pass). (OutputableBndrId idL, OutputableBndrId idR) => LHsBindsLR (GhcPass idL) (GhcPass idR) -> SDoc #
type HsLocalBinds id = HsLocalBindsLR id id #
Haskell Local Bindings
type LHsLocalBinds id = Located (HsLocalBinds id) #
Located Haskell local bindings
data HsLocalBindsLR idL idR #
Haskell Local Bindings with separate Left and Right identifier types
Bindings in a 'let' expression or a 'where' clause
HsValBinds (XHsValBinds idL idR) (HsValBindsLR idL idR) | Haskell Value Bindings |
HsIPBinds (XHsIPBinds idL idR) (HsIPBinds idR) | Haskell Implicit Parameter Bindings |
EmptyLocalBinds (XEmptyLocalBinds idL idR) | Empty Local Bindings |
XHsLocalBindsLR (XXHsLocalBindsLR idL idR) |
Instances
(ToHie (LHsExpr a), ToHie (PScoped (LPat a)), ToHie (BindContext (LHsBind a)), ToHie (SigContext (LSig a)), ToHie (RScoped (HsValBindsLR a a)), Data (HsLocalBinds a)) => ToHie (RScoped (LHsLocalBinds a)) | |
Defined in Compat.HieAst toHie :: RScoped (LHsLocalBinds a) -> HieM [HieAST Type] | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) | |
Defined in GHC.Hs.Binds |
type LHsLocalBindsLR idL idR = Located (HsLocalBindsLR idL idR) #
type HsValBinds id = HsValBindsLR id id #
Haskell Value Bindings
data HsValBindsLR idL idR #
Haskell Value bindings with separate Left and Right identifier types (not implicit parameters) Used for both top level and nested bindings May contain pattern synonym bindings
ValBinds (XValBinds idL idR) (LHsBindsLR idL idR) [LSig idR] | Value Bindings In Before renaming RHS; idR is always RdrName Not dependency analysed Recursive by default |
XValBindsLR (XXValBindsLR idL idR) | Value Bindings Out After renaming RHS; idR can be Name or Id Dependency analysed, later bindings in the list may depend on earlier ones. |
Instances
(ToHie (BindContext (LHsBind a)), ToHie (SigContext (LSig a)), ToHie (RScoped (XXValBindsLR a a))) => ToHie (RScoped (HsValBindsLR a a)) | |
Defined in Compat.HieAst toHie :: RScoped (HsValBindsLR a a) -> HieM [HieAST Type] | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsValBindsLR (GhcPass pl) (GhcPass pr)) | |
Defined in GHC.Hs.Binds |
data NHsValBindsLR idL #
Instances
ToHie (RScoped (NHsValBindsLR GhcRn)) | |
Defined in Compat.HieAst toHie :: RScoped (NHsValBindsLR GhcRn) -> HieM [HieAST Type] | |
ToHie (RScoped (NHsValBindsLR GhcTc)) | |
Defined in Compat.HieAst toHie :: RScoped (NHsValBindsLR GhcTc) -> HieM [HieAST Type] |
type LHsBinds id = LHsBindsLR id id #
Located Haskell Bindings
type LHsBindsLR idL idR = Bag (LHsBindLR idL idR) #
Located Haskell Bindings with separate Left and Right identifier types
type LHsBindLR idL idR = Located (HsBindLR idL idR) #
Located Haskell Binding with separate Left and Right identifier types
Haskell Binding with separate Left and Right id's
FunBind | Function-like Binding FunBind is used for both functions Reason 1: Special case for type inference: see Reason 2: Instance decls can only have FunBinds, which is convenient. If you change this, you'll need to change e.g. rnMethodBinds But note that the form Strict bindings have their strictness recorded in the |
| |
PatBind | Pattern Binding The pattern is never a simple variable; That case is done by FunBind. See Note [FunBind vs PatBind] for details about the relationship between FunBind and PatBind. |
VarBind | Variable Binding Dictionary binding and suchlike. All VarBinds are introduced by the type checker |
AbsBinds | Abstraction Bindings |
| |
PatSynBind (XPatSynBind idL idR) (PatSynBind idL idR) |
|
XHsBindsLR (XXHsBindsLR idL idR) |
Instances
HasType (LHsBind GhcRn) | |
Defined in Compat.HieAst getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type] | |
HasType (LHsBind GhcTc) | |
Defined in Compat.HieAst getTypeNode :: LHsBind GhcTc -> HieM [HieAST Type] | |
(ToHie (Context (Located (IdP a))), ToHie (MatchGroup a (LHsExpr a)), ToHie (PScoped (LPat a)), ToHie (GRHSs a (LHsExpr a)), ToHie (LHsExpr a), ToHie (Located (PatSynBind a a)), HasType (LHsBind a), ModifyState (IdP a), Data (HsBind a)) => ToHie (BindContext (LHsBind a)) | |
Defined in Compat.HieAst | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) | |
data NPatBindTc #
NPatBindTc | |
|
Instances
Data NPatBindTc | |
Defined in GHC.Hs.Binds gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NPatBindTc -> c NPatBindTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NPatBindTc # toConstr :: NPatBindTc -> Constr # dataTypeOf :: NPatBindTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NPatBindTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NPatBindTc) # gmapT :: (forall b. Data b => b -> b) -> NPatBindTc -> NPatBindTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NPatBindTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NPatBindTc -> r # gmapQ :: (forall d. Data d => d -> u) -> NPatBindTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NPatBindTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NPatBindTc -> m NPatBindTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NPatBindTc -> m NPatBindTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NPatBindTc -> m NPatBindTc # |
Abtraction Bindings Export
ABE | |
XABExport (XXABExport p) |
data PatSynBind idL idR #
AnnKeywordId
:AnnPattern
,AnnEqual
,AnnLarrow
AnnWhere
,AnnOpen
'{'
,AnnClose
'}'
,
Pattern Synonym binding
PSB | |
XPatSynBind (XXPatSynBind idL idR) |
Instances
(ToHie (Context (Located (IdP a))), ToHie (PScoped (LPat a)), ToHie (HsPatSynDir a)) => ToHie (Located (PatSynBind a a)) | |
Defined in Compat.HieAst toHie :: Located (PatSynBind a a) -> HieM [HieAST Type] | |
(OutputableBndrId l, OutputableBndrId r, Outputable (XXPatSynBind (GhcPass l) (GhcPass r))) => Outputable (PatSynBind (GhcPass l) (GhcPass r)) | |
Defined in GHC.Hs.Binds |
Haskell Implicit Parameter Bindings
IPBinds (XIPBinds id) [LIPBind id] | |
XHsIPBinds (XXHsIPBinds id) |
type LIPBind id = Located (IPBind id) #
Located Implicit Parameter Binding
May have AnnKeywordId
: AnnSemi
when in a
list
Implicit parameter bindings.
These bindings start off as (Left "x") in the parser and stay that way until after type-checking when they are replaced with (Right d), where "d" is the name of the dictionary holding the evidence for the implicit parameter.
Signatures and pragmas
TypeSig (XTypeSig pass) [Located (IdP pass)] (LHsSigWcType pass) | An ordinary type signature f :: Num a => a -> a After renaming, this list of Names contains the named
wildcards brought into scope by this signature. For a signature
|
PatSynSig (XPatSynSig pass) [Located (IdP pass)] (LHsSigType pass) | A pattern synonym type signature pattern Single :: () => (Show a) => a -> [a] |
ClassOpSig (XClassOpSig pass) Bool [Located (IdP pass)] (LHsSigType pass) | A signature for a class method False: ordinary class-method signature True: generic-default class method signature e.g. class C a where op :: a -> a -- Ordinary default op :: Eq a => a -> a -- Generic default No wildcards allowed here |
IdSig (XIdSig pass) Id | A type signature in generated code, notably the code generated for record selectors. We simply record the desired Id itself, replete with its name, type and IdDetails. Otherwise it's just like a type signature: there should be an accompanying binding |
FixSig (XFixSig pass) (FixitySig pass) | An ordinary fixity declaration infixl 8 *** |
InlineSig (XInlineSig pass) (Located (IdP pass)) InlinePragma | An inline pragma {#- INLINE f #-} |
SpecSig (XSpecSig pass) (Located (IdP pass)) [LHsSigType pass] InlinePragma | A specialisation pragma {-# SPECIALISE f :: Int -> Int #-} |
SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass) | A specialisation pragma for instance declarations only {-# SPECIALISE instance Eq [Int] #-} (Class tys); should be a specialisation of the current instance declaration |
MinimalSig (XMinimalSig pass) SourceText (LBooleanFormula (Located (IdP pass))) | A minimal complete definition pragma {-# MINIMAL a | (b, c | (d | e)) #-} |
SCCFunSig (XSCCFunSig pass) SourceText (Located (IdP pass)) (Maybe (Located StringLiteral)) | A "set cost centre" pragma for declarations {-# SCC funName #-} or {-# SCC funName "cost_centre_name" #-} |
CompleteMatchSig (XCompleteMatchSig pass) SourceText (Located [Located (IdP pass)]) (Maybe (Located (IdP pass))) | A complete match pragma {-# COMPLETE C, D [:: T] #-} Used to inform the pattern match checker about additional complete matchings which, for example, arise from pattern synonym definitions. |
XSig (XXSig pass) |
Instances
OutputableBndrId p => Outputable (Sig (GhcPass p)) | |
ToHie (SigContext (LSig GhcRn)) | |
ToHie (SigContext (LSig GhcTc)) | |
type LFixitySig pass = Located (FixitySig pass) #
Located Fixity Signature
Fixity Signature
FixitySig (XFixitySig pass) [Located (IdP pass)] Fixity | |
XFixitySig (XXFixitySig pass) |
Instances
OutputableBndrId p => Outputable (FixitySig (GhcPass p)) | |
ToHie (LFixitySig GhcRn) | |
Defined in Compat.HieAst toHie :: LFixitySig GhcRn -> HieM [HieAST Type] |
data TcSpecPrags #
Type checker Specialisation Pragmas
TcSpecPrags
conveys SPECIALISE
pragmas from the type checker to the desugarer
IsDefaultMethod | Super-specialised: a default method should be macro-expanded at every call site |
SpecPrags [LTcSpecPrag] |
Instances
Data TcSpecPrags | |
Defined in GHC.Hs.Binds gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrags -> c TcSpecPrags # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrags # toConstr :: TcSpecPrags -> Constr # dataTypeOf :: TcSpecPrags -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrags) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrags) # gmapT :: (forall b. Data b => b -> b) -> TcSpecPrags -> TcSpecPrags # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrags -> r # gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrags -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrags -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrags -> m TcSpecPrags # |
type LTcSpecPrag = Located TcSpecPrag #
Located Type checker Specification Pragmas
data TcSpecPrag #
Type checker Specification Pragma
SpecPrag Id HsWrapper InlinePragma | The Id to be specialised, a wrapper that specialises the polymorphic function, and inlining spec for the specialised function |
Instances
Data TcSpecPrag | |
Defined in GHC.Hs.Binds gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcSpecPrag -> c TcSpecPrag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcSpecPrag # toConstr :: TcSpecPrag -> Constr # dataTypeOf :: TcSpecPrag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcSpecPrag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcSpecPrag) # gmapT :: (forall b. Data b => b -> b) -> TcSpecPrag -> TcSpecPrag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcSpecPrag -> r # gmapQ :: (forall d. Data d => d -> u) -> TcSpecPrag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TcSpecPrag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcSpecPrag -> m TcSpecPrag # | |
Outputable TcSpecPrag | |
Defined in GHC.Hs.Binds ppr :: TcSpecPrag -> SDoc # pprPrec :: Rational -> TcSpecPrag -> SDoc # |
type HsPatSynDetails arg = HsConDetails arg [RecordPatSynField arg] #
Haskell Pattern Synonym Details
data RecordPatSynField a #
Record Pattern Synonym Field
Instances
data HsPatSynDir id #
Haskell Pattern Synonym Direction
Instances
ToHie (MatchGroup a (LHsExpr a)) => ToHie (HsPatSynDir a) | |
Defined in Compat.HieAst toHie :: HsPatSynDir a -> HieM [HieAST Type] |
pprInstanceHdr :: ClsInst -> SDoc #
pprInstance :: ClsInst -> SDoc #
instanceDFunId :: ClsInst -> DFunId #
A type-class instance. Note that there is some tricky laziness at work here. See Note [ClsInst laziness and the rough-match fields] for more details.
Instances
Data ClsInst | |
Defined in InstEnv gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInst -> c ClsInst # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClsInst # toConstr :: ClsInst -> Constr # dataTypeOf :: ClsInst -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClsInst) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClsInst) # gmapT :: (forall b. Data b => b -> b) -> ClsInst -> ClsInst # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInst -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInst -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInst -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInst -> m ClsInst # | |
NamedThing ClsInst | |
Outputable ClsInst | |
Instances
NamedThing FamInst | |
Defined in FamInstEnv | |
Outputable FamInst | |
type BreakIndex = Int #
Breakpoint index
All the information about the breakpoints for a module
ModBreaks | |
|
parenthesizeHsContext :: forall (p :: Pass). PprPrec -> LHsContext (GhcPass p) -> LHsContext (GhcPass p) #
checks if parenthesizeHsContext
p ctxtctxt
is a single constraint
c
such that
is true, and if so, surrounds hsTypeNeedsParens
p cc
with an HsParTy
to form a parenthesized ctxt
. Otherwise, it simply
returns ctxt
unchanged.
parenthesizeHsType :: forall (p :: Pass). PprPrec -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
checks if parenthesizeHsType
p ty
is
true, and if so, surrounds hsTypeNeedsParens
p tyty
with an HsParTy
. Otherwise, it simply
returns ty
.
hsTypeNeedsParens :: PprPrec -> HsType pass -> Bool #
returns hsTypeNeedsParens
p tTrue
if the type t
needs parentheses
under precedence p
.
pprConDeclFields :: forall (p :: Pass). OutputableBndrId p => [LConDeclField (GhcPass p)] -> SDoc #
pprLHsContext :: forall (p :: Pass). OutputableBndrId p => LHsContext (GhcPass p) -> SDoc #
pprHsExplicitForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> Maybe [LHsTyVarBndr (GhcPass p)] -> SDoc #
Version of pprHsForAll
or pprHsForAllExtra
that will always print
forall.
when passed Just []
. Prints nothing if passed Nothing
pprHsForAllExtra :: forall (p :: Pass). OutputableBndrId p => Maybe SrcSpan -> ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc #
Version of pprHsForAll
that can also print an extra-constraints
wildcard, e.g. _ => a -> Bool
or (Show a, _) => a -> String
. This
underscore will be printed when the 'Maybe SrcSpan' argument is a Just
containing the location of the extra-constraints wildcard. A special
function for this is needed, as the extra-constraints wildcard is removed
from the actual context and type, and stored in a separate field, thus just
printing the type will not print the extra-constraints wildcard.
pprHsForAll :: forall (p :: Pass). OutputableBndrId p => ForallVisFlag -> [LHsTyVarBndr (GhcPass p)] -> LHsContext (GhcPass p) -> SDoc #
Prints a forall; When passed an empty list, prints forall .
/forall ->
only when -dppr-debug
is enabled.
pprAnonWildCard :: SDoc #
rdrNameAmbiguousFieldOcc :: forall (p :: Pass). AmbiguousFieldOcc (GhcPass p) -> RdrName #
getLHsInstDeclClass_maybe :: forall (p :: Pass). LHsSigType (GhcPass p) -> Maybe (Located (IdP (GhcPass p))) #
getLHsInstDeclHead :: forall (p :: Pass). LHsSigType (GhcPass p) -> LHsType (GhcPass p) #
splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], LHsContext GhcRn, LHsType GhcRn) #
Decompose a type class instance type (of the form
forall tvs. context => instance_head
) into its constituent parts.
Note that this function looks through parentheses, so it will work on types
such as (forall tvs. ...)
. The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsQualTy :: LHsType pass -> (LHsContext pass, LHsType pass) #
Decompose a type of the form context => body
into its constituent parts.
Note that this function looks through parentheses, so it will work on types
such as (context => ...)
. The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsForAllTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass) #
Decompose a type of the form forall tvs. body
into its constituent
parts. Note that only invisible forall
s
(i.e., forall a.
, with a dot) are split apart; visible forall
s
(i.e., forall a ->
, with an arrow) are left untouched.
This function is used to split apart certain types, such as instance
declaration types, which disallow visible forall
s. For instance, if GHC
split apart the forall
in instance forall a -> Show (Blah a)
, then that
declaration would mistakenly be accepted!
Note that this function looks through parentheses, so it will work on types
such as (forall a. ...)
. The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsSigmaTyInvis :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass) #
Decompose a sigma type (of the form forall tvs. context => body
)
into its constituent parts. Note that only invisible forall
s
(i.e., forall a.
, with a dot) are split apart; visible forall
s
(i.e., forall a ->
, with an arrow) are left untouched.
This function is used to split apart certain types, such as instance
declaration types, which disallow visible forall
s. For instance, if GHC
split apart the forall
in instance forall a -> Show (Blah a)
, then that
declaration would mistakenly be accepted!
Note that this function looks through parentheses, so it will work on types
such as (forall a. ...)
. The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
splitLHsPatSynTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, [LHsTyVarBndr pass], LHsContext pass, LHsType pass) #
Decompose a pattern synonym type signature into its constituent parts.
Note that this function looks through parentheses, so it will work on types
such as (forall a. ...)
. The downside to this is that it is not
generally possible to take the returned types and reconstruct the original
type (parentheses and all) from them.
numVisibleArgs :: [HsArg tm ty] -> Arity #
hsTyGetAppHead_maybe :: forall (p :: Pass). LHsType (GhcPass p) -> Maybe (Located (IdP (GhcPass p))) #
mkHsAppKindTy :: forall (p :: Pass). XAppKindTy (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
mkHsAppTys :: forall (p :: Pass). LHsType (GhcPass p) -> [LHsType (GhcPass p)] -> LHsType (GhcPass p) #
mkHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #
mkHsOpTy :: forall (p :: Pass). LHsType (GhcPass p) -> Located (IdP (GhcPass p)) -> LHsType (GhcPass p) -> HsType (GhcPass p) #
isLHsForAllTy :: LHsType p -> Bool #
ignoreParens :: LHsType pass -> LHsType pass #
hsTyKindSig :: LHsType pass -> Maybe (LHsKind pass) #
Get the kind signature of a type, ignoring parentheses:
hsTyKindSig `Maybe ` = Nothing hsTyKindSig `Maybe :: Type -> Type ` = Just `Type -> Type` hsTyKindSig `Maybe :: ((Type -> Type))` = Just `Type -> Type`
This is used to extract the result kind of type synonyms with a CUSK:
type S = (F :: res_kind) ^^^^^^^^
hsLTyVarBndrsToTypes :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [LHsType (GhcPass p)] #
Convert a LHsTyVarBndrs to a list of types. Works on *type* variable only, no kind vars.
hsLTyVarBndrToType :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> LHsType (GhcPass p) #
Convert a LHsTyVarBndr to an equivalent LHsType.
hsLTyVarLocNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [Located (IdP (GhcPass p))] #
hsLTyVarLocName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> Located (IdP (GhcPass p)) #
hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name] #
hsExplicitLTyVarNames :: forall (p :: Pass). LHsQTyVars (GhcPass p) -> [IdP (GhcPass p)] #
hsLTyVarNames :: forall (p :: Pass). [LHsTyVarBndr (GhcPass p)] -> [IdP (GhcPass p)] #
hsLTyVarName :: forall (p :: Pass). LHsTyVarBndr (GhcPass p) -> IdP (GhcPass p) #
hsTyVarName :: forall (p :: Pass). HsTyVarBndr (GhcPass p) -> IdP (GhcPass p) #
hsScopedTvs :: LHsSigType GhcRn -> [Name] #
hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name] #
hsConDetailsArgs :: HsConDetails (LHsType a) (Located [LConDeclField a]) -> [LHsType a] #
hsTvbAllKinded :: LHsQTyVars pass -> Bool #
Do all type variables in this LHsQTyVars
come with kind annotations?
isHsKindedTyVar :: HsTyVarBndr pass -> Bool #
Does this HsTyVarBndr
come with an explicit kind annotation?
hsIPNameFS :: HsIPName -> FastString #
mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing #
mkEmptyImplicitBndrs :: thing -> HsImplicitBndrs GhcRn thing #
mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing #
mkHsImplicitBndrs :: thing -> HsImplicitBndrs GhcPs thing #
dropWildCards :: LHsSigWcType pass -> LHsSigType pass #
hsSigWcType :: LHsSigWcType pass -> LHsType pass #
hsImplicitBody :: forall (p :: Pass) thing. HsImplicitBndrs (GhcPass p) thing -> thing #
isEmptyLHsQTvs :: LHsQTyVars GhcRn -> Bool #
hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr pass] #
mkHsQTvs :: [LHsTyVarBndr GhcPs] -> LHsQTyVars GhcPs #
noLHsContext :: LHsContext pass #
getBangStrictness :: LHsType a -> HsSrcBang #
getBangType :: LHsType a -> LHsType a #
type BangType pass = HsType pass #
Bang Type
In the parser, strictness and packedness annotations bind more tightly
than docstrings. This means that when consuming a BangType
(and looking
for HsBangTy
) we must be ready to peer behind a potential layer of
HsDocTy
. See #15206 for motivation and getBangType
for an example.
type LHsContext pass #
= Located (HsContext pass) |
|
Located Haskell Context
= Located (HsType pass) | May have |
Located Haskell Type
type LHsTyVarBndr pass = Located (HsTyVarBndr pass) #
Located Haskell Type Variable Binder
data LHsQTyVars pass #
Located Haskell Quantified Type Variables
HsQTvs | |
| |
XLHsQTyVars (XXLHsQTyVars pass) |
Instances
OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) | |
Defined in GHC.Hs.Types | |
HasLoc (LHsQTyVars GhcRn) | |
Defined in Compat.HieAst loc :: LHsQTyVars GhcRn -> SrcSpan | |
ToHie (TScoped (LHsQTyVars GhcRn)) | |
Defined in Compat.HieAst toHie :: TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type] |
data HsImplicitBndrs pass thing #
Haskell Implicit Binders
HsIB | |
XHsImplicitBndrs (XXHsImplicitBndrs pass thing) |
Instances
(HasLoc thing, ToHie (TScoped thing)) => ToHie (TScoped (HsImplicitBndrs GhcRn thing)) | |
Defined in Compat.HieAst toHie :: TScoped (HsImplicitBndrs GhcRn thing) -> HieM [HieAST Type] | |
ToHie (TScoped (LHsSigWcType GhcTc)) | Dummy instances - never called |
Defined in Compat.HieAst toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] | |
Outputable thing => Outputable (HsImplicitBndrs (GhcPass p) thing) | |
Defined in GHC.Hs.Types | |
HasLoc thing => HasLoc (HsImplicitBndrs a thing) | |
Defined in Compat.HieAst loc :: HsImplicitBndrs a thing -> SrcSpan |
data HsWildCardBndrs pass thing #
Haskell Wildcard Binders
HsWC | |
XHsWildCardBndrs (XXHsWildCardBndrs pass thing) |
Instances
(HasLoc thing, ToHie (TScoped thing)) => ToHie (TScoped (HsWildCardBndrs GhcRn thing)) | |
Defined in Compat.HieAst toHie :: TScoped (HsWildCardBndrs GhcRn thing) -> HieM [HieAST Type] | |
ToHie (TScoped (LHsWcType GhcTc)) | |
ToHie (TScoped (LHsSigWcType GhcTc)) | Dummy instances - never called |
Defined in Compat.HieAst toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] | |
Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) | |
Defined in GHC.Hs.Types | |
HasLoc thing => HasLoc (HsWildCardBndrs a thing) | |
Defined in Compat.HieAst loc :: HsWildCardBndrs a thing -> SrcSpan |
type LHsSigType pass = HsImplicitBndrs pass (LHsType pass) #
Located Haskell Signature Type
type LHsWcType pass = HsWildCardBndrs pass (LHsType pass) #
Located Haskell Wildcard Type
type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass) #
Located Haskell Signature Wildcard Type
These names are used early on to store the names of implicit parameters. They completely disappear after type-checking.
Instances
Eq HsIPName | |
Data HsIPName | |
Defined in GHC.Hs.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPName -> c HsIPName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsIPName # toConstr :: HsIPName -> Constr # dataTypeOf :: HsIPName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsIPName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName) # gmapT :: (forall b. Data b => b -> b) -> HsIPName -> HsIPName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r # gmapQ :: (forall d. Data d => d -> u) -> HsIPName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # | |
Outputable HsIPName | |
OutputableBndr HsIPName | |
Defined in GHC.Hs.Types pprBndr :: BindingSite -> HsIPName -> SDoc # pprPrefixOcc :: HsIPName -> SDoc # pprInfixOcc :: HsIPName -> SDoc # bndrIsJoin_maybe :: HsIPName -> Maybe Int # | |
ToHie (Located HsIPName) | |
data HsTyVarBndr pass #
Haskell Type Variable Binder
UserTyVar (XUserTyVar pass) (Located (IdP pass)) | |
KindedTyVar (XKindedTyVar pass) (Located (IdP pass)) (LHsKind pass) | |
XTyVarBndr (XXTyVarBndr pass) |
Instances
NamedThing (HsTyVarBndr GhcRn) | |
Defined in GHC.Hs.Types getOccName :: HsTyVarBndr GhcRn -> OccName # getName :: HsTyVarBndr GhcRn -> Name # | |
OutputableBndrId p => Outputable (HsTyVarBndr (GhcPass p)) | |
Defined in GHC.Hs.Types | |
ToHie (TVScoped (LHsTyVarBndr GhcRn)) | |
Defined in Compat.HieAst toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type] |
Haskell Type
Instances
OutputableBndrId p => Outputable (HsType (GhcPass p)) | |
ToHie (LHsContext GhcRn) | |
Defined in Compat.HieAst toHie :: LHsContext GhcRn -> HieM [HieAST Type] | |
ToHie (LHsType GhcRn) | |
ToHie (TScoped (LHsType GhcRn)) | |
ToHie (TScoped (LHsWcType GhcTc)) | |
ToHie (TScoped (LHsSigWcType GhcTc)) | Dummy instances - never called |
Defined in Compat.HieAst toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] |
data NewHsTypeX #
Instances
Data NewHsTypeX |
|
Defined in GHC.Hs.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewHsTypeX -> c NewHsTypeX # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewHsTypeX # toConstr :: NewHsTypeX -> Constr # dataTypeOf :: NewHsTypeX -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewHsTypeX) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewHsTypeX) # gmapT :: (forall b. Data b => b -> b) -> NewHsTypeX -> NewHsTypeX # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewHsTypeX -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewHsTypeX -> r # gmapQ :: (forall d. Data d => d -> u) -> NewHsTypeX -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NewHsTypeX -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewHsTypeX -> m NewHsTypeX # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewHsTypeX -> m NewHsTypeX # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewHsTypeX -> m NewHsTypeX # | |
Outputable NewHsTypeX | |
Defined in GHC.Hs.Types ppr :: NewHsTypeX -> SDoc # pprPrec :: Rational -> NewHsTypeX -> SDoc # |
Haskell Type Literal
Instances
Data HsTyLit | |
Defined in GHC.Hs.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit -> c HsTyLit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTyLit # toConstr :: HsTyLit -> Constr # dataTypeOf :: HsTyLit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTyLit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTyLit) # gmapT :: (forall b. Data b => b -> b) -> HsTyLit -> HsTyLit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit # | |
Outputable HsTyLit | |
data HsTupleSort #
Haskell Tuple Sort
Instances
Data HsTupleSort | |
Defined in GHC.Hs.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTupleSort # toConstr :: HsTupleSort -> Constr # dataTypeOf :: HsTupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTupleSort) # gmapT :: (forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # |
type LConDeclField pass #
= Located (ConDeclField pass) | May have |
Located Constructor Declaration Field
data ConDeclField pass #
Constructor Declaration Field
ConDeclField | |
| |
XConDeclField (XXConDeclField pass) |
Instances
OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) | |
Defined in GHC.Hs.Types | |
ToHie (LConDeclField GhcRn) | |
Defined in Compat.HieAst toHie :: LConDeclField GhcRn -> HieM [HieAST Type] | |
ToHie (Located [LConDeclField GhcRn]) | |
Defined in Compat.HieAst |
data HsConDetails arg rec #
Haskell Constructor Details
Instances
(Data arg, Data rec) => Data (HsConDetails arg rec) | |
Defined in GHC.Hs.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDetails arg rec -> c (HsConDetails arg rec) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDetails arg rec) # toConstr :: HsConDetails arg rec -> Constr # dataTypeOf :: HsConDetails arg rec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDetails arg rec)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDetails arg rec)) # gmapT :: (forall b. Data b => b -> b) -> HsConDetails arg rec -> HsConDetails arg rec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails arg rec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails arg rec -> r # gmapQ :: (forall d. Data d => d -> u) -> HsConDetails arg rec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDetails arg rec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) # | |
(Outputable arg, Outputable rec) => Outputable (HsConDetails arg rec) | |
Defined in GHC.Hs.Types ppr :: HsConDetails arg rec -> SDoc # pprPrec :: Rational -> HsConDetails arg rec -> SDoc # | |
(ToHie arg, ToHie rec) => ToHie (HsConDetails arg rec) | |
Defined in Compat.HieAst toHie :: HsConDetails arg rec -> HieM [HieAST Type] |
Instances
(Outputable tm, Outputable ty) => Outputable (HsArg tm ty) | |
(HasLoc tm, HasLoc ty) => HasLoc (HsArg tm ty) | |
Defined in Compat.HieAst | |
(ToHie tm, ToHie ty) => ToHie (HsArg tm ty) | |
Defined in Compat.HieAst |
type LHsTypeArg p = HsArg (LHsType p) (LHsKind p) #
Field Occurrence
Represents an *occurrence* of an unambiguous field. We store
both the RdrName
the user originally wrote, and after the
renamer, the selector function.
FieldOcc | |
| |
XFieldOcc (XXFieldOcc pass) |
Instances
Eq (XCFieldOcc (GhcPass p)) => Eq (FieldOcc (GhcPass p)) | |
Ord (XCFieldOcc (GhcPass p)) => Ord (FieldOcc (GhcPass p)) | |
Defined in GHC.Hs.Types compare :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Ordering # (<) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # (<=) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # (>) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # (>=) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool # max :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) # min :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) # | |
Outputable (FieldOcc pass) | |
ToHie (RFContext (LFieldOcc GhcRn)) | |
ToHie (RFContext (LFieldOcc GhcTc)) | |
data AmbiguousFieldOcc pass #
Ambiguous Field Occurrence
Represents an *occurrence* of a field that is potentially
ambiguous after the renamer, with the ambiguity resolved by the
typechecker. We always store the RdrName
that the user
originally wrote, and store the selector function after the renamer
(for unambiguous occurrences) or the typechecker (for ambiguous
occurrences).
See Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat and Note [Disambiguating record fields] in TcExpr. See Note [Located RdrNames] in GHC.Hs.Expr
Unambiguous (XUnambiguous pass) (Located RdrName) | |
Ambiguous (XAmbiguous pass) (Located RdrName) | |
XAmbiguousFieldOcc (XXAmbiguousFieldOcc pass) |
Instances
Outputable (AmbiguousFieldOcc (GhcPass p)) | |
Defined in GHC.Hs.Types | |
OutputableBndr (AmbiguousFieldOcc (GhcPass p)) | |
Defined in GHC.Hs.Types pprBndr :: BindingSite -> AmbiguousFieldOcc (GhcPass p) -> SDoc # pprPrefixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc # pprInfixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc # bndrIsJoin_maybe :: AmbiguousFieldOcc (GhcPass p) -> Maybe Int # | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) | |
Defined in Compat.HieAst | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) | |
Defined in Compat.HieAst |
data ExecOptions #
ExecOptions | |
|
data ExecResult #
Resume | |
|
isBottomingId :: Var -> Bool #
Returns true if an application to n args would diverge
isDeadBinder :: Id -> Bool #
isImplicitId :: Id -> Bool #
isImplicitId
tells whether an Id
s info is implied by other
declarations, so we don't need to put its signature in an interface
file, even if it's mentioned in some other interface unfolding.
Get from either the worker or the wrapper Id
to the DataCon
. Currently used only in the desugarer.
INVARIANT: idDataCon (dataConWrapId d) = d
: remember, dataConWrapId
can return either the wrapper or the worker
isDataConWorkId :: Id -> Bool #
isPrimOpId :: Id -> Bool #
isClassOpId_maybe :: Id -> Maybe Class #
isRecordSelector :: Id -> Bool #
recordSelectorTyCon :: Id -> RecSelParent #
isVanillaDataCon :: DataCon -> Bool #
Vanilla DataCon
s are those that are nice boring Haskell 98 constructors
dataConUserType :: DataCon -> Type #
The user-declared type of the data constructor in the nice-to-read form:
T :: forall a b. a -> b -> T [a]
rather than:
T :: forall a c. forall b. (c~[a]) => a -> b -> T c
The type variables are quantified in the order that the user wrote them.
See Note [DataCon user type variable binders]
.
NB: If the constructor is part of a data instance, the result type mentions the family tycon, not the internal one.
dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type) #
The "signature" of the DataCon
returns, in order:
1) The result of dataConUnivAndExTyCoVars
,
2) All the ThetaType
s relating to the DataCon
(coercion, dictionary,
implicit parameter - whatever), including dependent GADT equalities.
Dependent GADT equalities are *also* listed in return value (1), so be
careful!
3) The type arguments to the constructor
4) The original result type of the DataCon
dataConSrcBangs :: DataCon -> [HsSrcBang] #
Strictness/unpack annotations, from user; or, for imported
DataCons, from the interface file
The list is in one-to-one correspondence with the arity of the DataCon
dataConIsInfix :: DataCon -> Bool #
Should the DataCon
be presented infix?
isMarkedStrict :: StrictnessMark -> Bool #
Haskell Source Bang
Bangs on data constructor arguments as the user wrote them in the source code.
(HsSrcBang _ SrcUnpack SrcLazy)
and
(HsSrcBang _ SrcUnpack NoSrcStrict)
(without StrictData) makes no sense, we
emit a warning (in checkValidDataCon) and treat it like
(HsSrcBang _ NoSrcUnpack SrcLazy)
Instances
Data HsSrcBang | |
Defined in DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSrcBang # toConstr :: HsSrcBang -> Constr # dataTypeOf :: HsSrcBang -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang) # gmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSrcBang -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSrcBang -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # | |
Outputable HsSrcBang | |
data HsImplBang #
Haskell Implementation Bang
Bangs of data constructor arguments as generated by the compiler after consulting HsSrcBang, flags, etc.
HsLazy | Lazy field, or one with an unlifted type |
HsStrict | Strict but not unpacked field |
HsUnpack (Maybe Coercion) | Strict and unpacked field co :: arg-ty ~ product-ty HsBang |
Instances
Data HsImplBang | |
Defined in DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplBang -> c HsImplBang # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsImplBang # toConstr :: HsImplBang -> Constr # dataTypeOf :: HsImplBang -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsImplBang) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang) # gmapT :: (forall b. Data b => b -> b) -> HsImplBang -> HsImplBang # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r # gmapQ :: (forall d. Data d => d -> u) -> HsImplBang -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplBang -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang # | |
Outputable HsImplBang | |
Defined in DataCon ppr :: HsImplBang -> SDoc # pprPrec :: Rational -> HsImplBang -> SDoc # |
data SrcStrictness #
Source Strictness
What strictness annotation the user wrote
SrcLazy | Lazy, ie '~' |
SrcStrict | Strict, ie |
NoSrcStrict | no strictness annotation |
Instances
Eq SrcStrictness | |
Defined in DataCon (==) :: SrcStrictness -> SrcStrictness -> Bool # (/=) :: SrcStrictness -> SrcStrictness -> Bool # | |
Data SrcStrictness | |
Defined in DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcStrictness # toConstr :: SrcStrictness -> Constr # dataTypeOf :: SrcStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcStrictness) # gmapT :: (forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness # | |
Binary SrcStrictness | |
Defined in DataCon put_ :: BinHandle -> SrcStrictness -> IO () # put :: BinHandle -> SrcStrictness -> IO (Bin SrcStrictness) # get :: BinHandle -> IO SrcStrictness # | |
Outputable SrcStrictness | |
Defined in DataCon ppr :: SrcStrictness -> SDoc # pprPrec :: Rational -> SrcStrictness -> SDoc # |
data SrcUnpackedness #
Source Unpackedness
What unpackedness the user requested
SrcUnpack | |
SrcNoUnpack | |
NoSrcUnpack | no unpack pragma |
Instances
data StrictnessMark #
Instances
Outputable StrictnessMark | |
Defined in DataCon ppr :: StrictnessMark -> SDoc # pprPrec :: Rational -> StrictnessMark -> SDoc # |
hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool #
returns hsOverLitNeedsParens
p olTrue
if an overloaded literal
ol
needs to be parenthesized under precedence p
.
hsLitNeedsParens :: PprPrec -> HsLit x -> Bool #
returns hsLitNeedsParens
p lTrue
if a literal l
needs
to be parenthesized under precedence p
.
pmPprHsLit :: forall (x :: Pass). HsLit (GhcPass x) -> SDoc #
pmPprHsLit pretty prints literals and is used when pretty printing pattern match warnings. All are printed the same (i.e., without hashes if they are primitive and not wrapped in constructors if they are boxed). This happens mainly for too reasons: * We do not want to expose their internal representation * The warnings become too messy
pp_st_suffix :: SourceText -> SDoc -> SDoc -> SDoc #
convertLit :: ConvertIdX a b => HsLit a -> HsLit b #
Convert a literal from one index type to another, updating the annotations
according to the relevant Convertable
instance
overLitType :: HsOverLit GhcTc -> Type #
Haskell Literal
HsChar (XHsChar x) Char | Character |
HsCharPrim (XHsCharPrim x) Char | Unboxed character |
HsString (XHsString x) FastString | String |
HsStringPrim (XHsStringPrim x) ByteString | Packed bytes |
HsInt (XHsInt x) IntegralLit | Genuinely an Int; arises from
|
HsIntPrim (XHsIntPrim x) Integer | literal |
HsWordPrim (XHsWordPrim x) Integer | literal |
HsInt64Prim (XHsInt64Prim x) Integer | literal |
HsWord64Prim (XHsWord64Prim x) Integer | literal |
HsInteger (XHsInteger x) Integer Type | Genuinely an integer; arises only from TRANSLATION (overloaded literals are done with HsOverLit) |
HsRat (XHsRat x) FractionalLit Type | Genuinely a rational; arises only from TRANSLATION (overloaded literals are done with HsOverLit) |
HsFloatPrim (XHsFloatPrim x) FractionalLit | Unboxed Float |
HsDoublePrim (XHsDoublePrim x) FractionalLit | Unboxed Double |
XLit (XXLit x) |
Haskell Overloaded Literal
OverLit | |
| |
XOverLit (XXOverLit p) |
Instances
Eq (XXOverLit p) => Eq (HsOverLit p) | |
Ord (XXOverLit p) => Ord (HsOverLit p) | |
OutputableBndrId p => Outputable (HsOverLit (GhcPass p)) | |
OverLitTc | |
|
Instances
Data OverLitTc | |
Defined in GHC.Hs.Lit gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverLitTc -> c OverLitTc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitTc # toConstr :: OverLitTc -> Constr # dataTypeOf :: OverLitTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitTc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitTc) # gmapT :: (forall b. Data b => b -> b) -> OverLitTc -> OverLitTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitTc -> r # gmapQ :: (forall d. Data d => d -> u) -> OverLitTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc # |
data OverLitVal #
Overloaded Literal Value
HsIntegral !IntegralLit | Integer-looking literals; |
HsFractional !FractionalLit | Frac-looking literals |
HsIsString !SourceText !FastString | String-looking literals |
Instances
Eq OverLitVal | |
Defined in GHC.Hs.Lit (==) :: OverLitVal -> OverLitVal -> Bool # (/=) :: OverLitVal -> OverLitVal -> Bool # | |
Data OverLitVal | |
Defined in GHC.Hs.Lit gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverLitVal -> c OverLitVal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitVal # toConstr :: OverLitVal -> Constr # dataTypeOf :: OverLitVal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitVal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitVal) # gmapT :: (forall b. Data b => b -> b) -> OverLitVal -> OverLitVal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitVal -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitVal -> r # gmapQ :: (forall d. Data d => d -> u) -> OverLitVal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitVal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitVal -> m OverLitVal # | |
Ord OverLitVal | |
Defined in GHC.Hs.Lit compare :: OverLitVal -> OverLitVal -> Ordering # (<) :: OverLitVal -> OverLitVal -> Bool # (<=) :: OverLitVal -> OverLitVal -> Bool # (>) :: OverLitVal -> OverLitVal -> Bool # (>=) :: OverLitVal -> OverLitVal -> Bool # max :: OverLitVal -> OverLitVal -> OverLitVal # min :: OverLitVal -> OverLitVal -> OverLitVal # | |
Outputable OverLitVal | |
Defined in GHC.Hs.Lit ppr :: OverLitVal -> SDoc # pprPrec :: Rational -> OverLitVal -> SDoc # |
splitForAllTys :: Type -> ([TyCoVar], Type) #
Take a ForAllTy apart, returning the list of tycovars and the result type. This always succeeds, even if it returns only an empty list. Note that the result type returned may have free variables that were bound by a forall.
funResultTy :: Type -> Type #
Extract the function result type and panic if that is not possible
pprTypeApp :: TyCon -> [Type] -> SDoc #
pprForAll :: [TyCoVarBinder] -> SDoc #
pprThetaArrowTy :: ThetaType -> SDoc #
pprParendType :: Type -> SDoc #
alphaTyVars :: [TyVar] #
tyConClass_maybe :: TyCon -> Maybe Class #
If this TyCon
is that for a class instance, return the class it is for.
Otherwise returns Nothing
isClassTyCon :: TyCon -> Bool #
Is this TyCon
that for a class instance?
synTyConRhs_maybe :: TyCon -> Maybe Type #
Extract the information pertaining to the right hand side of a type synonym
(type
) declaration.
synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type) #
Extract the TyVar
s bound by a vanilla type synonym
and the corresponding (unsubstituted) right hand side.
tyConDataCons :: TyCon -> [DataCon] #
As tyConDataCons_maybe
, but returns the empty list of constructors if no
constructors could be found
isOpenTypeFamilyTyCon :: TyCon -> Bool #
Is this an open type family TyCon?
isTypeFamilyTyCon :: TyCon -> Bool #
Is this a synonym TyCon
that can have may have further instances appear?
isOpenFamilyTyCon :: TyCon -> Bool #
Is this a TyCon
, synonym or otherwise, that defines a family with
instances?
isFamilyTyCon :: TyCon -> Bool #
Is this a TyCon
, synonym or otherwise, that defines a family?
isTypeSynonymTyCon :: TyCon -> Bool #
Is this a TyCon
representing a regular H98 type synonym (type
)?
isNewTyCon :: TyCon -> Bool #
Is this TyCon
that for a newtype
isPrimTyCon :: TyCon -> Bool #
Does this TyCon
represent something that cannot be defined in Haskell?
pprFundeps :: Outputable a => [FunDep a] -> SDoc #
classSCTheta :: Class -> [PredType] #
classMethods :: Class -> [Id] #
Instances
Eq Class | |
Data Class | |
Defined in Class gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Class -> c Class # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Class # dataTypeOf :: Class -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Class) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Class) # gmapT :: (forall b. Data b => b -> b) -> Class -> Class # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Class -> r # gmapQ :: (forall d. Data d => d -> u) -> Class -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Class -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Class -> m Class # | |
NamedThing Class | |
Uniquable Class | |
Outputable Class | |
dataConTyCon :: DataCon -> TyCon #
The type constructor that we are building via this data constructor
dataConFieldLabels :: DataCon -> [FieldLabel] #
The labels for the fields of this particular DataCon
A data constructor
Instances
Eq DataCon | |
Data DataCon | |
Defined in DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataCon -> c DataCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataCon # toConstr :: DataCon -> Constr # dataTypeOf :: DataCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DataCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataCon) # gmapT :: (forall b. Data b => b -> b) -> DataCon -> DataCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r # gmapQ :: (forall d. Data d => d -> u) -> DataCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon # | |
NamedThing DataCon | |
Uniquable DataCon | |
Outputable DataCon | |
OutputableBndr DataCon | |
Defined in DataCon pprBndr :: BindingSite -> DataCon -> SDoc # pprPrefixOcc :: DataCon -> SDoc # pprInfixOcc :: DataCon -> SDoc # bndrIsJoin_maybe :: DataCon -> Maybe Int # |
pprSpliceDecl :: forall (p :: Pass). OutputableBndrId p => HsSplice (GhcPass p) -> SpliceExplicitFlag -> SDoc #
pprPatBind :: forall (bndr :: Pass) (p :: Pass) body. (OutputableBndrId bndr, OutputableBndrId p, Outputable body) => LPat (GhcPass bndr) -> GRHSs (GhcPass p) body -> SDoc #
pprFunBind :: forall (idR :: Pass) body. (OutputableBndrId idR, Outputable body) => MatchGroup (GhcPass idR) body -> SDoc #
A Haskell expression.
HsVar (XVar p) (Located (IdP p)) | Variable |
HsUnboundVar (XUnboundVar p) UnboundVar | Unbound variable; also used for "holes" (_ or _x). Turned from HsVar to HsUnboundVar by the renamer, when it finds an out-of-scope variable or hole. Turned into HsVar by type checker, to support deferred type errors. |
HsConLikeOut (XConLikeOut p) ConLike | After typechecker only; must be different HsVar for pretty printing |
HsRecFld (XRecFld p) (AmbiguousFieldOcc p) | Variable pointing to record selector Not in use after typechecking |
HsOverLabel (XOverLabel p) (Maybe (IdP p)) FastString | Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels)
|
HsIPVar (XIPVar p) HsIPName | Implicit parameter (not in use after typechecking) |
HsOverLit (XOverLitE p) (HsOverLit p) | Overloaded literals |
HsLit (XLitE p) (HsLit p) | Simple (non-overloaded) literals |
HsLam (XLam p) (MatchGroup p (LHsExpr p)) | Lambda abstraction. Currently always a single match |
HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p)) | Lambda-case |
HsApp (XApp p) (LHsExpr p) (LHsExpr p) | Application |
HsAppType (XAppTypeE p) (LHsExpr p) (LHsWcType (NoGhcTc p)) | Visible type application Explicit type argument; e.g f @Int x y NB: Has wildcards, but no implicit quantification |
OpApp (XOpApp p) (LHsExpr p) (LHsExpr p) (LHsExpr p) | Operator applications: NB Bracketed ops such as (+) come out as Vars. |
NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p) | Negation operator. Contains the negated expression and the name
of |
HsPar (XPar p) (LHsExpr p) | Parenthesised expr; see Note [Parens in HsSyn] |
SectionL (XSectionL p) (LHsExpr p) (LHsExpr p) | |
SectionR (XSectionR p) (LHsExpr p) (LHsExpr p) | |
ExplicitTuple (XExplicitTuple p) [LHsTupArg p] Boxity | Used for explicit tuples and sections thereof |
ExplicitSum (XExplicitSum p) ConTag Arity (LHsExpr p) | Used for unboxed sum types
There will be multiple |
HsCase (XCase p) (LHsExpr p) (MatchGroup p (LHsExpr p)) |
|
HsIf (XIf p) (Maybe (SyntaxExpr p)) (LHsExpr p) (LHsExpr p) (LHsExpr p) | |
HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)] | Multi-way if |
HsLet (XLet p) (LHsLocalBinds p) (LHsExpr p) | let(rec)
|
HsDo (XDo p) (HsStmtContext Name) (Located [ExprLStmt p]) | |
ExplicitList (XExplicitList p) (Maybe (SyntaxExpr p)) [LHsExpr p] | Syntactic list: [a,b,c,...]
|
RecordCon | Record construction
|
| |
RecordUpd | Record update
|
| |
ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p)) | Expression with an explicit type signature. |
ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) (ArithSeqInfo p) | Arithmetic sequence
|
HsSCC (XSCC p) SourceText StringLiteral (LHsExpr p) | |
HsCoreAnn (XCoreAnn p) SourceText StringLiteral (LHsExpr p) |
|
HsBracket (XBracket p) (HsBracket p) | |
HsRnBracketOut (XRnBracketOut p) (HsBracket GhcRn) [PendingRnSplice] | |
HsTcBracketOut (XTcBracketOut p) (HsBracket GhcRn) [PendingTcSplice] | |
HsSpliceE (XSpliceE p) (HsSplice p) | |
HsProc (XProc p) (LPat p) (LHsCmdTop p) |
|
HsStatic (XStatic p) (LHsExpr p) | |
HsTick (XTick p) (Tickish (IdP p)) (LHsExpr p) | |
HsBinTick (XBinTick p) Int Int (LHsExpr p) | |
HsTickPragma (XTickPragma p) SourceText (StringLiteral, (Int, Int), (Int, Int)) ((SourceText, SourceText), (SourceText, SourceText)) (LHsExpr p) | |
HsWrap (XWrap p) HsWrapper (HsExpr p) | |
XExpr (XXExpr p) |
Instances
p ~ GhcPs => DisambInfixOp (HsExpr p) | |
p ~ GhcPs => DisambECP (HsExpr p) | |
Defined in RdrHsSyn ecpFromCmd' :: LHsCmd GhcPs -> PV (Located (HsExpr p)) # ecpFromExp' :: LHsExpr GhcPs -> PV (Located (HsExpr p)) # mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located (HsExpr p)) -> PV (Located (HsExpr p)) # mkHsLetPV :: SrcSpan -> LHsLocalBinds GhcPs -> Located (HsExpr p) -> PV (Located (HsExpr p)) # superInfixOp :: (DisambInfixOp (InfixOp (HsExpr p)) => PV (Located (HsExpr p))) -> PV (Located (HsExpr p)) # mkHsOpAppPV :: SrcSpan -> Located (HsExpr p) -> Located (InfixOp (HsExpr p)) -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> MatchGroup GhcPs (Located (HsExpr p)) -> PV (Located (HsExpr p)) # superFunArg :: (DisambECP (FunArg (HsExpr p)) => PV (Located (HsExpr p))) -> PV (Located (HsExpr p)) # mkHsAppPV :: SrcSpan -> Located (HsExpr p) -> Located (FunArg (HsExpr p)) -> PV (Located (HsExpr p)) # mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> Located (HsExpr p) -> Bool -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkHsDoPV :: SrcSpan -> Located [LStmt GhcPs (Located (HsExpr p))] -> PV (Located (HsExpr p)) # mkHsParPV :: SrcSpan -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkHsVarPV :: Located RdrName -> PV (Located (HsExpr p)) # mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsExpr p)) # mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (HsExpr p)) # mkHsWildCardPV :: SrcSpan -> PV (Located (HsExpr p)) # mkHsTySigPV :: SrcSpan -> Located (HsExpr p) -> LHsType GhcPs -> PV (Located (HsExpr p)) # mkHsExplicitListPV :: SrcSpan -> [Located (HsExpr p)] -> PV (Located (HsExpr p)) # mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (HsExpr p)) # mkHsRecordPV :: SrcSpan -> SrcSpan -> Located (HsExpr p) -> ([LHsRecField GhcPs (Located (HsExpr p))], Maybe SrcSpan) -> PV (Located (HsExpr p)) # mkHsNegAppPV :: SrcSpan -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkHsSectionR_PV :: SrcSpan -> Located (InfixOp (HsExpr p)) -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkHsAsPatPV :: SrcSpan -> Located RdrName -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkHsLazyPatPV :: SrcSpan -> Located (HsExpr p) -> PV (Located (HsExpr p)) # mkSumOrTuplePV :: SrcSpan -> Boxity -> SumOrTuple (HsExpr p) -> PV (Located (HsExpr p)) # | |
OutputableBndrId p => Outputable (HsExpr (GhcPass p)) | |
HasType (LHsExpr GhcRn) | |
Defined in Compat.HieAst getTypeNode :: LHsExpr GhcRn -> HieM [HieAST Type] | |
HasType (LHsExpr GhcTc) | This instance tries to construct
Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive. See #16233 |
Defined in Compat.HieAst getTypeNode :: LHsExpr GhcTc -> HieM [HieAST Type] | |
(a ~ GhcPass p, ToHie (Context (Located (IdP a))), HasType (LHsExpr a), ToHie (PScoped (LPat a)), ToHie (MatchGroup a (LHsExpr a)), ToHie (LGRHS a (LHsExpr a)), ToHie (RContext (HsRecordBinds a)), ToHie (RFContext (Located (AmbiguousFieldOcc a))), ToHie (ArithSeqInfo a), ToHie (LHsCmdTop a), ToHie (RScoped (GuardLStmt a)), ToHie (RScoped (LHsLocalBinds a)), ToHie (TScoped (LHsWcType (NoGhcTc a))), ToHie (TScoped (LHsSigWcType (NoGhcTc a))), Data (HsExpr a), Data (HsSplice a), Data (HsTupArg a), Data (AmbiguousFieldOcc a), HasRealDataConName a) => ToHie (LHsExpr (GhcPass p)) | |
type FunArg (HsExpr p) | |
type InfixOp (HsExpr p) | |
type Body (HsExpr p) | |
Haskell Command (e.g. a "statement" in an Arrow proc block)
HsCmdArrApp (XCmdArrApp id) (LHsExpr id) (LHsExpr id) HsArrAppType Bool | |
HsCmdArrForm (XCmdArrForm id) (LHsExpr id) LexicalFixity (Maybe Fixity) [LHsCmdTop id] |
|
HsCmdApp (XCmdApp id) (LHsCmd id) (LHsExpr id) | |
HsCmdLam (XCmdLam id) (MatchGroup id (LHsCmd id)) | |
HsCmdPar (XCmdPar id) (LHsCmd id) |
|
HsCmdCase (XCmdCase id) (LHsExpr id) (MatchGroup id (LHsCmd id)) |
|
HsCmdIf (XCmdIf id) (Maybe (SyntaxExpr id)) (LHsExpr id) (LHsCmd id) (LHsCmd id) | |
HsCmdLet (XCmdLet id) (LHsLocalBinds id) (LHsCmd id) |
|
HsCmdDo (XCmdDo id) (Located [CmdLStmt id]) | |
HsCmdWrap (XCmdWrap id) HsWrapper (HsCmd id) | |
XCmd (XXCmd id) |
Instances
Haskell Splice
HsTypedSplice (XTypedSplice id) SpliceDecoration (IdP id) (LHsExpr id) | |
HsUntypedSplice (XUntypedSplice id) SpliceDecoration (IdP id) (LHsExpr id) | |
HsQuasiQuote (XQuasiQuote id) (IdP id) (IdP id) SrcSpan FastString | |
HsSpliced (XSpliced id) ThModFinalizers (HsSplicedThing id) | |
HsSplicedT DelayedSplice | |
XSplice (XXSplice id) |
Instances
OutputableBndrId p => Outputable (HsSplice (GhcPass p)) | |
(ToHie (LHsExpr a), Data (HsSplice a)) => ToHie (Located (HsSplice a)) | |
data MatchGroup p body #
MG | |
XMatchGroup (XXMatchGroup p body) |
Instances
ToHie (LMatch a body) => ToHie (MatchGroup a body) | |
Defined in Compat.HieAst toHie :: MatchGroup a body -> HieM [HieAST Type] |
Guarded Right-Hand Sides
GRHSs are used both for pattern bindings and for Matches
GRHSs | |
| |
XGRHSs (XXGRHSs p body) |
Instances
(ToHie body, ToHie (LGRHS a body), ToHie (RScoped (LHsLocalBinds a))) => ToHie (GRHSs a body) | |
Defined in Compat.HieAst |
data SyntaxExpr p #
Syntax Expression
SyntaxExpr is like PostTcExpr
, but it's filled in a little earlier,
by the renamer. It's used for rebindable syntax.
E.g. (>>=)
is filled in before the renamer by the appropriate Name
for
(>>=)
, and then instantiated by the type checker with its type args
etc
This should desugar to
syn_res_wrap $ syn_expr (syn_arg_wraps[0] arg0) (syn_arg_wraps[1] arg1) ...
where the actual arguments come from elsewhere in the AST.
This could be defined using GhcPass p
and such, but it's
harder to get it all to work out that way. (noSyntaxExpr
is hard to
write, for example.)
SyntaxExpr | |
|
Instances
OutputableBndrId p => Outputable (SyntaxExpr (GhcPass p)) | |
Defined in GHC.Hs.Expr |
= Located (HsExpr p) | May have |
Located Haskell Expression
pprImpExp :: (HasOccName name, OutputableBndr name) => name -> SDoc #
replaceLWrappedName :: LIEWrappedName name1 -> name2 -> LIEWrappedName name2 #
replaceWrappedName :: IEWrappedName name1 -> name2 -> IEWrappedName name2 #
ieLWrappedName :: LIEWrappedName name -> Located name #
lieWrappedName :: LIEWrappedName name -> name #
ieWrappedName :: IEWrappedName name -> name #
simpleImportDecl :: forall (p :: Pass). ModuleName -> ImportDecl (GhcPass p) #
isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool #
Convenience function to answer the question if an import decl. is qualified.
importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle #
type LImportDecl pass #
= Located (ImportDecl pass) | When in a list this may have |
Located Import Declaration
data ImportDeclQualifiedStyle #
If/how an import is qualified
.
QualifiedPre |
|
QualifiedPost |
|
NotQualified | Not qualified. |
Instances
data ImportDecl pass #
Import Declaration
A single Haskell import
declaration.
ImportDecl | |
| |
XImportDecl (XXImportDecl pass) |
Instances
NFData (ImportDecl GhcPs) Source # | |
Defined in Development.IDE.GHC.Orphans rnf :: ImportDecl GhcPs -> () # | |
OutputableBndrId p => Outputable (ImportDecl (GhcPass p)) | |
Defined in GHC.Hs.ImpExp | |
ToHie (LImportDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LImportDecl GhcRn -> HieM [HieAST Type] |
data IEWrappedName name #
A name in an import or export specification which may have adornments. Used primarily for accurate pretty printing of ParsedSource, and API Annotation placement.
Instances
Eq name => Eq (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp (==) :: IEWrappedName name -> IEWrappedName name -> Bool # (/=) :: IEWrappedName name -> IEWrappedName name -> Bool # | |
Data name => Data (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName name -> c (IEWrappedName name) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName name) # toConstr :: IEWrappedName name -> Constr # dataTypeOf :: IEWrappedName name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName name)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName name)) # gmapT :: (forall b. Data b => b -> b) -> IEWrappedName name -> IEWrappedName name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName name -> r # gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName name -> m (IEWrappedName name) # | |
HasOccName name => HasOccName (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp occName :: IEWrappedName name -> OccName # | |
OutputableBndr name => Outputable (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp ppr :: IEWrappedName name -> SDoc # pprPrec :: Rational -> IEWrappedName name -> SDoc # | |
OutputableBndr name => OutputableBndr (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp pprBndr :: BindingSite -> IEWrappedName name -> SDoc # pprPrefixOcc :: IEWrappedName name -> SDoc # pprInfixOcc :: IEWrappedName name -> SDoc # bndrIsJoin_maybe :: IEWrappedName name -> Maybe Int # | |
ToHie (IEContext (LIEWrappedName Name)) | |
Defined in Compat.HieAst toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type] |
type LIEWrappedName name = Located (IEWrappedName name) #
Located name with possible adornment
- AnnKeywordId
s : AnnType
,
AnnPattern
Imported or exported entity.
IEVar (XIEVar pass) (LIEWrappedName (IdP pass)) | Imported or Exported Variable |
IEThingAbs (XIEThingAbs pass) (LIEWrappedName (IdP pass)) | Imported or exported Thing with Absent list The thing is a Class/Type (can't tell)
- |
IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass)) | Imported or exported Thing with All imported or exported The thing is a ClassType and the All refers to methodsconstructors |
IEThingWith (XIEThingWith pass) (LIEWrappedName (IdP pass)) IEWildcard [LIEWrappedName (IdP pass)] [Located (FieldLbl (IdP pass))] | Imported or exported Thing With given imported or exported The thing is a Class/Type and the imported or exported things are
methods/constructors and record fields; see Note [IEThingWith]
- |
IEModuleContents (XIEModuleContents pass) (Located ModuleName) | Imported or exported module contents (Export Only) |
IEGroup (XIEGroup pass) Int HsDocString | Doc section heading |
IEDoc (XIEDoc pass) HsDocString | Some documentation |
IEDocNamed (XIEDocNamed pass) String | Reference to named doc |
XIE (XXIE pass) |
data IEWildcard #
Imported or Exported Wildcard
Instances
Eq IEWildcard | |
Defined in GHC.Hs.ImpExp (==) :: IEWildcard -> IEWildcard -> Bool # (/=) :: IEWildcard -> IEWildcard -> Bool # | |
Data IEWildcard | |
Defined in GHC.Hs.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWildcard -> c IEWildcard # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IEWildcard # toConstr :: IEWildcard -> Constr # dataTypeOf :: IEWildcard -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IEWildcard) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IEWildcard) # gmapT :: (forall b. Data b => b -> b) -> IEWildcard -> IEWildcard # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWildcard -> r # gmapQ :: (forall d. Data d => d -> u) -> IEWildcard -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWildcard -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWildcard -> m IEWildcard # |
Pattern
WildPat (XWildPat p) | Wildcard Pattern The sole reason for a type on a WildPat is to support hsPatType :: Pat Id -> Type |
VarPat (XVarPat p) (Located (IdP p)) | Variable Pattern |
LazyPat (XLazyPat p) (LPat p) | Lazy Pattern
^ - |
AsPat (XAsPat p) (Located (IdP p)) (LPat p) | As pattern
^ - |
ParPat (XParPat p) (LPat p) | Parenthesised pattern
See Note [Parens in HsSyn] in GHC.Hs.Expr
^ - |
BangPat (XBangPat p) (LPat p) | Bang pattern
^ - |
ListPat (XListPat p) [LPat p] | Syntactic List
|
TuplePat (XTuplePat p) [LPat p] Boxity | Tuple sub-patterns
|
SumPat (XSumPat p) (LPat p) ConTag Arity | Anonymous sum pattern
|
ConPatIn (Located (IdP p)) (HsConPatDetails p) | Constructor Pattern In |
ConPatOut | Constructor Pattern Out |
ViewPat (XViewPat p) (LHsExpr p) (LPat p) | View Pattern |
SplicePat (XSplicePat p) (HsSplice p) | Splice Pattern (Includes quasi-quotes) |
LitPat (XLitPat p) (HsLit p) | Literal Pattern Used for *non-overloaded* literal patterns: Int, Int, Char, String, etc. |
NPat (XNPat p) (Located (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p) | Natural Pattern |
NPlusKPat (XNPlusKPat p) (Located (IdP p)) (Located (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p) | n+k pattern |
SigPat (XSigPat p) (LPat p) (LHsSigWcType (NoGhcTc p)) | Pattern with a type signature |
CoPat (XCoPat p) HsWrapper (Pat p) Type | Coercion Pattern |
XPat (XXPat p) | Trees that Grow extension point for new constructors |
Instances
OutputableBndrId p => Outputable (Pat (GhcPass p)) | |
HasType (Located (Pat GhcRn)) | |
Defined in Compat.HieAst | |
HasType (Located (Pat GhcTc)) | |
Defined in Compat.HieAst | |
(a ~ GhcPass p, ToHie (Context (Located (IdP a))), ToHie (RContext (HsRecFields a (PScoped (LPat a)))), ToHie (LHsExpr a), ToHie (TScoped (LHsSigWcType a)), ProtectSig a, ToHie (TScoped (ProtectedSig a)), HasType (LPat a), Data (HsSplice a)) => ToHie (PScoped (Located (Pat (GhcPass p)))) | |
Used when constructing a term with an unused extension point.
data NoExtField #
A placeholder type for TTG extension points that are not currently unused to represent any particular value.
This should not be confused with NoExtCon
, which are found in unused
extension constructors and therefore should never be inhabited. In
contrast, NoExtField
is used in extension points (e.g., as the field of
some constructor), so it must have an inhabitant to construct AST passes
that manipulate fields with that extension point as their type.
Instances
Eq NoExtField | |
Defined in GHC.Hs.Extension (==) :: NoExtField -> NoExtField -> Bool # (/=) :: NoExtField -> NoExtField -> Bool # | |
Data NoExtField | |
Defined in GHC.Hs.Extension gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtField -> c NoExtField # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtField # toConstr :: NoExtField -> Constr # dataTypeOf :: NoExtField -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtField) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtField) # gmapT :: (forall b. Data b => b -> b) -> NoExtField -> NoExtField # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtField -> r # gmapQ :: (forall d. Data d => d -> u) -> NoExtField -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtField -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtField -> m NoExtField # | |
Ord NoExtField | |
Defined in GHC.Hs.Extension compare :: NoExtField -> NoExtField -> Ordering # (<) :: NoExtField -> NoExtField -> Bool # (<=) :: NoExtField -> NoExtField -> Bool # (>) :: NoExtField -> NoExtField -> Bool # (>=) :: NoExtField -> NoExtField -> Bool # max :: NoExtField -> NoExtField -> NoExtField # min :: NoExtField -> NoExtField -> NoExtField # | |
Outputable NoExtField | |
Defined in GHC.Hs.Extension ppr :: NoExtField -> SDoc # pprPrec :: Rational -> NoExtField -> SDoc # | |
ToHie (TScoped NoExtField) | |
Defined in Compat.HieAst toHie :: TScoped NoExtField -> HieM [HieAST Type] | |
ToHie (Context (Located NoExtField)) | |
Defined in Compat.HieAst toHie :: Context (Located NoExtField) -> HieM [HieAST Type] |
Used in TTG extension constructors that have yet to be extended with
anything. If an extension constructor has NoExtCon
as its field, it is
not intended to ever be constructed anywhere, and any function that consumes
the extension constructor can eliminate it by way of noExtCon
.
This should not be confused with NoExtField
, which are found in unused
extension points (not constructors) and therefore can be inhabited.
Instances
Eq NoExtCon | |
Data NoExtCon | |
Defined in GHC.Hs.Extension gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NoExtCon -> c NoExtCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NoExtCon # toConstr :: NoExtCon -> Constr # dataTypeOf :: NoExtCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NoExtCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NoExtCon) # gmapT :: (forall b. Data b => b -> b) -> NoExtCon -> NoExtCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NoExtCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NoExtCon -> r # gmapQ :: (forall d. Data d => d -> u) -> NoExtCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NoExtCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NoExtCon -> m NoExtCon # | |
Ord NoExtCon | |
Defined in GHC.Hs.Extension | |
Outputable NoExtCon | |
Used as a data type index for the hsSyn AST
Instances
Instances
Data Pass | |
Defined in GHC.Hs.Extension gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pass -> c Pass # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pass # dataTypeOf :: Pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pass) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass) # gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQ :: (forall d. Data d => d -> u) -> Pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # |
type GhcTc = GhcPass 'Typechecked #
type family XRec p (f :: Type -> Type) = (r :: Type) | r -> p f #
Maps the "normal" id type for a given pass
type family NoGhcTc p where ... #
Marks that a field uses the GhcRn variant even when the pass parameter is GhcTc. Useful for storing HsTypes in GHC.Hs.Exprs, say, because HsType GhcTc should never occur.
NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass) | |
NoGhcTc other = other |
type family NoGhcTcPass (p :: Pass) :: Pass where ... #
NoGhcTcPass 'Typechecked = 'Renamed | |
NoGhcTcPass other = other |
type family XHsValBinds x x' #
Instances
type XHsValBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XHsIPBinds x x' #
Instances
type XHsIPBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XEmptyLocalBinds x x' #
Instances
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XXHsLocalBindsLR x x' #
Instances
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type ForallXHsLocalBindsLR (c :: Type -> Constraint) x x' = (c (XHsValBinds x x'), c (XHsIPBinds x x'), c (XEmptyLocalBinds x x'), c (XXHsLocalBindsLR x x')) #
Instances
type XValBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XXValBindsLR x x' #
Instances
type XXValBindsLR (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type ForallXValBindsLR (c :: Type -> Constraint) x x' = (c (XValBinds x x'), c (XXValBindsLR x x')) #
Instances
type XFunBind (GhcPass pL) GhcTc | |
Defined in GHC.Hs.Binds | |
type XFunBind (GhcPass pL) GhcRn | |
Defined in GHC.Hs.Binds | |
type XFunBind (GhcPass pL) GhcPs | |
Defined in GHC.Hs.Binds |
Instances
type XPatBind GhcPs (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type XPatBind GhcRn (GhcPass pR) | |
Defined in GHC.Hs.Binds | |
type XPatBind GhcTc (GhcPass pR) | |
Defined in GHC.Hs.Binds |
Instances
type XVarBind (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
Instances
type XAbsBinds (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XPatSynBind x x' #
Instances
type XPatSynBind (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type family XXHsBindsLR x x' #
Instances
type XXHsBindsLR (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Binds |
type ForallXHsBindsLR (c :: Type -> Constraint) x x' = (c (XFunBind x x'), c (XPatBind x x'), c (XVarBind x x'), c (XAbsBinds x x'), c (XPatSynBind x x'), c (XXHsBindsLR x x')) #
Instances
type XABE (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XXABExport x #
Instances
type XXABExport (GhcPass p) | |
Defined in GHC.Hs.Binds |
type ForallXABExport (c :: Type -> Constraint) x = (c (XABE x), c (XXABExport x)) #
type family XXPatSynBind x x' #
Instances
type XXPatSynBind (GhcPass idL) (GhcPass idR) | |
Defined in GHC.Hs.Binds |
type ForallXPatSynBind (c :: Type -> Constraint) x x' = (c (XPSB x x'), c (XXPatSynBind x x')) #
Instances
type XIPBinds GhcPs | |
Defined in GHC.Hs.Binds | |
type XIPBinds GhcRn | |
Defined in GHC.Hs.Binds | |
type XIPBinds GhcTc | |
Defined in GHC.Hs.Binds |
type family XXHsIPBinds x #
Instances
type XXHsIPBinds (GhcPass p) | |
Defined in GHC.Hs.Binds |
type ForallXHsIPBinds (c :: Type -> Constraint) x = (c (XIPBinds x), c (XXHsIPBinds x)) #
Instances
type XCIPBind (GhcPass p) | |
Defined in GHC.Hs.Binds |
type ForallXIPBind (c :: Type -> Constraint) x = (c (XCIPBind x), c (XXIPBind x)) #
Instances
type XTypeSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XPatSynSig x #
Instances
type XPatSynSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XClassOpSig x #
Instances
type XClassOpSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
Instances
type XIdSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
Instances
type XFixSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XInlineSig x #
Instances
type XInlineSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
Instances
type XSpecSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XSpecInstSig x #
Instances
type XSpecInstSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XMinimalSig x #
Instances
type XMinimalSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XSCCFunSig x #
Instances
type XSCCFunSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XCompleteMatchSig x #
Instances
type XCompleteMatchSig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type ForallXSig (c :: Type -> Constraint) x = (c (XTypeSig x), c (XPatSynSig x), c (XClassOpSig x), c (XIdSig x), c (XFixSig x), c (XInlineSig x), c (XSpecSig x), c (XSpecInstSig x), c (XMinimalSig x), c (XSCCFunSig x), c (XCompleteMatchSig x), c (XXSig x)) #
type family XFixitySig x #
Instances
type XFixitySig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type family XXFixitySig x #
Instances
type XXFixitySig (GhcPass p) | |
Defined in GHC.Hs.Binds |
type ForallXFixitySig (c :: Type -> Constraint) x = (c (XFixitySig x), c (XXFixitySig x)) #
type family XStandaloneKindSig x #
Instances
type XStandaloneKindSig (GhcPass p) | |
Defined in GHC.Hs.Decls |
type family XXStandaloneKindSig x #
Instances
type XXStandaloneKindSig (GhcPass p) | |
Defined in GHC.Hs.Decls |
Instances
type XTyClD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XDerivD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XValD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XSigD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XKindSigD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XDefD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XForD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XWarningD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XAnnD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XRuleD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XSpliceD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XDocD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XRoleAnnotD x #
Instances
type XRoleAnnotD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXHsDecl (c :: Type -> Constraint) x = (c (XTyClD x), c (XInstD x), c (XDerivD x), c (XValD x), c (XSigD x), c (XKindSigD x), c (XDefD x), c (XForD x), c (XWarningD x), c (XAnnD x), c (XRuleD x), c (XSpliceD x), c (XDocD x), c (XRoleAnnotD x), c (XXHsDecl x)) #
Instances
type XCHsGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXHsGroup (c :: Type -> Constraint) x = (c (XCHsGroup x), c (XXHsGroup x)) #
type family XSpliceDecl x #
Instances
type XSpliceDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXSpliceDecl x #
Instances
type XXSpliceDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXSpliceDecl (c :: Type -> Constraint) x = (c (XSpliceDecl x), c (XXSpliceDecl x)) #
Instances
type XFamDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XSynDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XSynDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XSynDecl GhcTc | |
Defined in GHC.Hs.Decls |
Instances
type XDataDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XDataDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XDataDecl GhcTc | |
Defined in GHC.Hs.Decls |
type family XClassDecl x #
Instances
type XClassDecl GhcPs | |
Defined in GHC.Hs.Decls | |
type XClassDecl GhcRn | |
Defined in GHC.Hs.Decls | |
type XClassDecl GhcTc | |
Defined in GHC.Hs.Decls |
type family XXTyClDecl x #
Instances
type XXTyClDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXTyClDecl (c :: Type -> Constraint) x = (c (XFamDecl x), c (XSynDecl x), c (XDataDecl x), c (XClassDecl x), c (XXTyClDecl x)) #
type family XCTyClGroup x #
Instances
type XCTyClGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXTyClGroup x #
Instances
type XXTyClGroup (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXTyClGroup (c :: Type -> Constraint) x = (c (XCTyClGroup x), c (XXTyClGroup x)) #
Instances
type XNoSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XCKindSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
Instances
type XTyVarSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXFamilyResultSig x #
Instances
type XXFamilyResultSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXFamilyResultSig (c :: Type -> Constraint) x = (c (XNoSig x), c (XCKindSig x), c (XTyVarSig x), c (XXFamilyResultSig x)) #
type family XCFamilyDecl x #
Instances
type XCFamilyDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXFamilyDecl x #
Instances
type XXFamilyDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXFamilyDecl (c :: Type -> Constraint) x = (c (XCFamilyDecl x), c (XXFamilyDecl x)) #
type family XCHsDataDefn x #
Instances
type XCHsDataDefn (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXHsDataDefn x #
Instances
type XXHsDataDefn (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXHsDataDefn (c :: Type -> Constraint) x = (c (XCHsDataDefn x), c (XXHsDataDefn x)) #
type family XCHsDerivingClause x #
Instances
type XCHsDerivingClause (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXHsDerivingClause x #
Instances
type XXHsDerivingClause (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXHsDerivingClause (c :: Type -> Constraint) x = (c (XCHsDerivingClause x), c (XXHsDerivingClause x)) #
type family XConDeclGADT x #
Instances
type XConDeclGADT (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XConDeclH98 x #
Instances
type XConDeclH98 (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXConDecl (c :: Type -> Constraint) x = (c (XConDeclGADT x), c (XConDeclH98 x), c (XXConDecl x)) #
Instances
type XCFamEqn (GhcPass _1) r | |
Defined in GHC.Hs.Decls |
type ForallXFamEqn (c :: Type -> Constraint) x r = (c (XCFamEqn x r), c (XXFamEqn x r)) #
type family XCClsInstDecl x #
Instances
type XCClsInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXClsInstDecl x #
Instances
type XXClsInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXClsInstDecl (c :: Type -> Constraint) x = (c (XCClsInstDecl x), c (XXClsInstDecl x)) #
Instances
type XClsInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XDataFamInstD x #
Instances
type XDataFamInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XTyFamInstD x #
Instances
type XTyFamInstD (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXInstDecl x #
Instances
type XXInstDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXInstDecl (c :: Type -> Constraint) x = (c (XClsInstD x), c (XDataFamInstD x), c (XTyFamInstD x), c (XXInstDecl x)) #
type family XCDerivDecl x #
Instances
type XCDerivDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXDerivDecl x #
Instances
type XXDerivDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXDerivDecl (c :: Type -> Constraint) x = (c (XCDerivDecl x), c (XXDerivDecl x)) #
type family XViaStrategy x #
Instances
type XViaStrategy GhcPs | |
Defined in GHC.Hs.Decls | |
type XViaStrategy GhcRn | |
Defined in GHC.Hs.Decls | |
type XViaStrategy GhcTc | |
Defined in GHC.Hs.Decls |
type family XCDefaultDecl x #
Instances
type XCDefaultDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXDefaultDecl x #
Instances
type XXDefaultDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXDefaultDecl (c :: Type -> Constraint) x = (c (XCDefaultDecl x), c (XXDefaultDecl x)) #
type family XForeignImport x #
Instances
type XForeignImport GhcPs | |
Defined in GHC.Hs.Decls | |
type XForeignImport GhcRn | |
Defined in GHC.Hs.Decls | |
type XForeignImport GhcTc | |
Defined in GHC.Hs.Decls |
type family XForeignExport x #
Instances
type XForeignExport GhcPs | |
Defined in GHC.Hs.Decls | |
type XForeignExport GhcRn | |
Defined in GHC.Hs.Decls | |
type XForeignExport GhcTc | |
Defined in GHC.Hs.Decls |
type family XXForeignDecl x #
Instances
type XXForeignDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXForeignDecl (c :: Type -> Constraint) x = (c (XForeignImport x), c (XForeignExport x), c (XXForeignDecl x)) #
type family XCRuleDecls x #
Instances
type XCRuleDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXRuleDecls x #
Instances
type XXRuleDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXRuleDecls (c :: Type -> Constraint) x = (c (XCRuleDecls x), c (XXRuleDecls x)) #
Instances
type XHsRule GhcPs | |
Defined in GHC.Hs.Decls | |
type XHsRule GhcRn | |
Defined in GHC.Hs.Decls | |
type XHsRule GhcTc | |
Defined in GHC.Hs.Decls |
type family XXRuleDecl x #
Instances
type XXRuleDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXRuleDecl (c :: Type -> Constraint) x = (c (XHsRule x), c (XXRuleDecl x)) #
type family XCRuleBndr x #
Instances
type XCRuleBndr (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XRuleBndrSig x #
Instances
type XRuleBndrSig (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXRuleBndr x #
Instances
type XXRuleBndr (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXRuleBndr (c :: Type -> Constraint) x = (c (XCRuleBndr x), c (XRuleBndrSig x), c (XXRuleBndr x)) #
Instances
type XWarnings (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXWarnDecls x #
Instances
type XXWarnDecls (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXWarnDecls (c :: Type -> Constraint) x = (c (XWarnings x), c (XXWarnDecls x)) #
Instances
type XWarning (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXWarnDecl x #
Instances
type XXWarnDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXWarnDecl (c :: Type -> Constraint) x = (c (XWarning x), c (XXWarnDecl x)) #
type family XHsAnnotation x #
Instances
type XHsAnnotation (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXAnnDecl (c :: Type -> Constraint) x = (c (XHsAnnotation x), c (XXAnnDecl x)) #
type family XCRoleAnnotDecl x #
Instances
type XCRoleAnnotDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type family XXRoleAnnotDecl x #
Instances
type XXRoleAnnotDecl (GhcPass _1) | |
Defined in GHC.Hs.Decls |
type ForallXRoleAnnotDecl (c :: Type -> Constraint) x = (c (XCRoleAnnotDecl x), c (XXRoleAnnotDecl x)) #
Instances
type XVar (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XUnboundVar x #
Instances
type XUnboundVar (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XConLikeOut x #
Instances
type XConLikeOut (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XRecFld (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XOverLabel x #
Instances
type XOverLabel (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XIPVar (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XOverLitE (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XLitE (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XLam (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XLamCase (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XApp (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XAppTypeE (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XOpApp GhcPs | |
Defined in GHC.Hs.Expr | |
type XOpApp GhcRn | |
Defined in GHC.Hs.Expr | |
type XOpApp GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XNegApp (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XPar (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XSectionL (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XSectionR (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XExplicitTuple x #
Instances
type XExplicitTuple (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XExplicitSum x #
Instances
type XExplicitSum GhcPs | |
Defined in GHC.Hs.Expr | |
type XExplicitSum GhcRn | |
Defined in GHC.Hs.Expr | |
type XExplicitSum GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XCase (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XIf (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XMultiIf GhcPs | |
Defined in GHC.Hs.Expr | |
type XMultiIf GhcRn | |
Defined in GHC.Hs.Expr | |
type XMultiIf GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XLet (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XDo GhcPs | |
Defined in GHC.Hs.Expr | |
type XDo GhcRn | |
Defined in GHC.Hs.Expr | |
type XDo GhcTc | |
Defined in GHC.Hs.Expr |
type family XExplicitList x #
Instances
type XExplicitList GhcPs | |
Defined in GHC.Hs.Expr | |
type XExplicitList GhcRn | |
Defined in GHC.Hs.Expr | |
type XExplicitList GhcTc | |
Defined in GHC.Hs.Expr |
type family XRecordCon x #
Instances
type XRecordCon GhcPs | |
Defined in GHC.Hs.Expr | |
type XRecordCon GhcRn | |
Defined in GHC.Hs.Expr | |
type XRecordCon GhcTc | |
Defined in GHC.Hs.Expr |
type family XRecordUpd x #
Instances
type XRecordUpd GhcPs | |
Defined in GHC.Hs.Expr | |
type XRecordUpd GhcRn | |
Defined in GHC.Hs.Expr | |
type XRecordUpd GhcTc | |
Defined in GHC.Hs.Expr |
type family XExprWithTySig x #
Instances
type XExprWithTySig (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XArithSeq GhcPs | |
Defined in GHC.Hs.Expr | |
type XArithSeq GhcRn | |
Defined in GHC.Hs.Expr | |
type XArithSeq GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XSCC (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCoreAnn (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XBracket (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XRnBracketOut x #
Instances
type XRnBracketOut (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XTcBracketOut x #
Instances
type XTcBracketOut (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XSpliceE (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XProc (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XStatic GhcPs | |
Defined in GHC.Hs.Expr | |
type XStatic GhcRn | |
Defined in GHC.Hs.Expr | |
type XStatic GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XTick (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XBinTick (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XTickPragma x #
Instances
type XTickPragma (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XWrap (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type ForallXExpr (c :: Type -> Constraint) x = (c (XVar x), c (XUnboundVar x), c (XConLikeOut x), c (XRecFld x), c (XOverLabel x), c (XIPVar x), c (XOverLitE x), c (XLitE x), c (XLam x), c (XLamCase x), c (XApp x), c (XAppTypeE x), c (XOpApp x), c (XNegApp x), c (XPar x), c (XSectionL x), c (XSectionR x), c (XExplicitTuple x), c (XExplicitSum x), c (XCase x), c (XIf x), c (XMultiIf x), c (XLet x), c (XDo x), c (XExplicitList x), c (XRecordCon x), c (XRecordUpd x), c (XExprWithTySig x), c (XArithSeq x), c (XSCC x), c (XCoreAnn x), c (XBracket x), c (XRnBracketOut x), c (XTcBracketOut x), c (XSpliceE x), c (XProc x), c (XStatic x), c (XTick x), c (XBinTick x), c (XTickPragma x), c (XWrap x), c (XXExpr x)) #
type family XUnambiguous x #
Instances
type XUnambiguous GhcPs | |
Defined in GHC.Hs.Types | |
type XUnambiguous GhcRn | |
Defined in GHC.Hs.Types | |
type XUnambiguous GhcTc | |
Defined in GHC.Hs.Types |
type family XAmbiguous x #
Instances
type XAmbiguous GhcPs | |
Defined in GHC.Hs.Types | |
type XAmbiguous GhcRn | |
Defined in GHC.Hs.Types | |
type XAmbiguous GhcTc | |
Defined in GHC.Hs.Types |
type family XXAmbiguousFieldOcc x #
Instances
type XXAmbiguousFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Types |
type ForallXAmbiguousFieldOcc (c :: Type -> Constraint) x = (c (XUnambiguous x), c (XAmbiguous x), c (XXAmbiguousFieldOcc x)) #
Instances
type XPresent (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XMissing GhcPs | |
Defined in GHC.Hs.Expr | |
type XMissing GhcRn | |
Defined in GHC.Hs.Expr | |
type XMissing GhcTc | |
Defined in GHC.Hs.Expr |
type ForallXTupArg (c :: Type -> Constraint) x = (c (XPresent x), c (XMissing x), c (XXTupArg x)) #
type family XTypedSplice x #
Instances
type XTypedSplice (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XUntypedSplice x #
Instances
type XUntypedSplice (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XQuasiQuote x #
Instances
type XQuasiQuote (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XSpliced (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type ForallXSplice (c :: Type -> Constraint) x = (c (XTypedSplice x), c (XUntypedSplice x), c (XQuasiQuote x), c (XSpliced x), c (XXSplice x)) #
Instances
type XExpBr (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XPatBr (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XDecBrL (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XDecBrG (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XTypBr (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XVarBr (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XTExpBr (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type ForallXBracket (c :: Type -> Constraint) x = (c (XExpBr x), c (XPatBr x), c (XDecBrL x), c (XDecBrG x), c (XTypBr x), c (XVarBr x), c (XTExpBr x), c (XXBracket x)) #
Instances
type XCmdTop GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdTop GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdTop GhcTc | |
Defined in GHC.Hs.Expr |
type ForallXCmdTop (c :: Type -> Constraint) x = (c (XCmdTop x), c (XXCmdTop x)) #
Instances
type XMG GhcPs b | |
Defined in GHC.Hs.Expr | |
type XMG GhcRn b | |
Defined in GHC.Hs.Expr | |
type XMG GhcTc b | |
Defined in GHC.Hs.Expr |
type family XXMatchGroup x b #
Instances
type XXMatchGroup (GhcPass _1) b | |
Defined in GHC.Hs.Expr |
type ForallXMatchGroup (c :: Type -> Constraint) x b = (c (XMG x b), c (XXMatchGroup x b)) #
Instances
type XCMatch (GhcPass _1) b | |
Defined in GHC.Hs.Expr |
type ForallXMatch (c :: Type -> Constraint) x b = (c (XCMatch x b), c (XXMatch x b)) #
Instances
type XCGRHSs (GhcPass _1) b | |
Defined in GHC.Hs.Expr |
type ForallXGRHSs (c :: Type -> Constraint) x b = (c (XCGRHSs x b), c (XXGRHSs x b)) #
Instances
type XCGRHS (GhcPass _1) b | |
Defined in GHC.Hs.Expr |
type ForallXGRHS (c :: Type -> Constraint) x b = (c (XCGRHS x b), c (XXGRHS x b)) #
type family XLastStmt x x' b #
Instances
type XLastStmt (GhcPass _1) (GhcPass _2) b | |
Defined in GHC.Hs.Expr |
type family XBindStmt x x' b #
Instances
type XBindStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
type XBindStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XBindStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr |
type family XApplicativeStmt x x' b #
Instances
type XApplicativeStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
type XApplicativeStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XApplicativeStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr |
type family XBodyStmt x x' b #
Instances
type XBodyStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
type XBodyStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XBodyStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr |
Instances
type XLetStmt (GhcPass _1) (GhcPass _2) b | |
Defined in GHC.Hs.Expr |
Instances
type XParStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
type XParStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XParStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr |
type family XTransStmt x x' b #
Instances
type XTransStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr | |
type XTransStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XTransStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr |
Instances
type XRecStmt (GhcPass _1) GhcRn b | |
Defined in GHC.Hs.Expr | |
type XRecStmt (GhcPass _1) GhcPs b | |
Defined in GHC.Hs.Expr | |
type XRecStmt (GhcPass _1) GhcTc b | |
Defined in GHC.Hs.Expr |
type ForallXStmtLR (c :: Type -> Constraint) x x' b = (c (XLastStmt x x' b), c (XBindStmt x x' b), c (XApplicativeStmt x x' b), c (XBodyStmt x x' b), c (XLetStmt x x' b), c (XParStmt x x' b), c (XTransStmt x x' b), c (XRecStmt x x' b), c (XXStmtLR x x' b)) #
type family XCmdArrApp x #
Instances
type XCmdArrApp GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdArrApp GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdArrApp GhcTc | |
Defined in GHC.Hs.Expr |
type family XCmdArrForm x #
Instances
type XCmdArrForm (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdApp (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdLam (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdPar (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdCase (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdIf (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdLet (GhcPass _1) | |
Defined in GHC.Hs.Expr |
Instances
type XCmdDo GhcPs | |
Defined in GHC.Hs.Expr | |
type XCmdDo GhcRn | |
Defined in GHC.Hs.Expr | |
type XCmdDo GhcTc | |
Defined in GHC.Hs.Expr |
Instances
type XCmdWrap (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type ForallXCmd (c :: Type -> Constraint) x = (c (XCmdArrApp x), c (XCmdArrForm x), c (XCmdApp x), c (XCmdLam x), c (XCmdPar x), c (XCmdCase x), c (XCmdIf x), c (XCmdLet x), c (XCmdDo x), c (XCmdWrap x), c (XXCmd x)) #
type family XParStmtBlock x x' #
Instances
type XParStmtBlock (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Expr |
type family XXParStmtBlock x x' #
Instances
type XXParStmtBlock (GhcPass pL) (GhcPass pR) | |
Defined in GHC.Hs.Expr |
type ForallXParStmtBlock (c :: Type -> Constraint) x x' = (c (XParStmtBlock x x'), c (XXParStmtBlock x x')) #
type family XApplicativeArgOne x #
Instances
type XApplicativeArgOne (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XApplicativeArgMany x #
Instances
type XApplicativeArgMany (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type family XXApplicativeArg x #
Instances
type XXApplicativeArg (GhcPass _1) | |
Defined in GHC.Hs.Expr |
type ForallXApplicativeArg (c :: Type -> Constraint) x = (c (XApplicativeArgOne x), c (XApplicativeArgMany x), c (XXApplicativeArg x)) #
Instances
type XHsChar (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsCharPrim x #
Instances
type XHsCharPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XHsString (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsStringPrim x #
Instances
type XHsStringPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XHsInt (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsIntPrim x #
Instances
type XHsIntPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsWordPrim x #
Instances
type XHsWordPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsInt64Prim x #
Instances
type XHsInt64Prim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsWord64Prim x #
Instances
type XHsWord64Prim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsInteger x #
Instances
type XHsInteger (GhcPass _1) | |
Defined in GHC.Hs.Lit |
Instances
type XHsRat (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsFloatPrim x #
Instances
type XHsFloatPrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type family XHsDoublePrim x #
Instances
type XHsDoublePrim (GhcPass _1) | |
Defined in GHC.Hs.Lit |
type ForallXHsLit (c :: Type -> Constraint) x = (c (XHsChar x), c (XHsCharPrim x), c (XHsDoublePrim x), c (XHsFloatPrim x), c (XHsInt x), c (XHsInt64Prim x), c (XHsIntPrim x), c (XHsInteger x), c (XHsRat x), c (XHsString x), c (XHsStringPrim x), c (XHsWord64Prim x), c (XHsWordPrim x), c (XXLit x)) #
Helper to apply a constraint to all extension points. It has one entry per extension point type family.
Instances
type XOverLit GhcPs | |
Defined in GHC.Hs.Lit | |
type XOverLit GhcRn | |
Defined in GHC.Hs.Lit | |
type XOverLit GhcTc | |
Defined in GHC.Hs.Lit |
type ForallXOverLit (c :: Type -> Constraint) x = (c (XOverLit x), c (XXOverLit x)) #
Instances
type XWildPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XWildPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XWildPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XVarPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XLazyPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XAsPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XParPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XBangPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XListPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XListPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XListPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XTuplePat GhcPs | |
Defined in GHC.Hs.Pat | |
type XTuplePat GhcRn | |
Defined in GHC.Hs.Pat | |
type XTuplePat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XSumPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XSumPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XSumPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XViewPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XViewPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XViewPat GhcTc | |
Defined in GHC.Hs.Pat |
type family XSplicePat x #
Instances
type XSplicePat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XLitPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
Instances
type XNPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XNPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XNPat GhcTc | |
Defined in GHC.Hs.Pat |
type family XNPlusKPat x #
Instances
type XNPlusKPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XNPlusKPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XNPlusKPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XSigPat GhcPs | |
Defined in GHC.Hs.Pat | |
type XSigPat GhcRn | |
Defined in GHC.Hs.Pat | |
type XSigPat GhcTc | |
Defined in GHC.Hs.Pat |
Instances
type XCoPat (GhcPass _1) | |
Defined in GHC.Hs.Pat |
type ForallXPat (c :: Type -> Constraint) x = (c (XWildPat x), c (XVarPat x), c (XLazyPat x), c (XAsPat x), c (XParPat x), c (XBangPat x), c (XListPat x), c (XTuplePat x), c (XSumPat x), c (XViewPat x), c (XSplicePat x), c (XLitPat x), c (XNPat x), c (XNPlusKPat x), c (XSigPat x), c (XCoPat x), c (XXPat x)) #
Instances
type XHsQTvs GhcPs | |
Defined in GHC.Hs.Types | |
type XHsQTvs GhcRn | |
Defined in GHC.Hs.Types | |
type XHsQTvs GhcTc | |
Defined in GHC.Hs.Types |
type family XXLHsQTyVars x #
Instances
type XXLHsQTyVars (GhcPass _1) | |
Defined in GHC.Hs.Types |
type ForallXLHsQTyVars (c :: Type -> Constraint) x = (c (XHsQTvs x), c (XXLHsQTyVars x)) #
Instances
type XHsIB GhcPs _1 | |
Defined in GHC.Hs.Types | |
type XHsIB GhcRn _1 | |
Defined in GHC.Hs.Types | |
type XHsIB GhcTc _1 | |
Defined in GHC.Hs.Types |
type family XXHsImplicitBndrs x b #
Instances
type XXHsImplicitBndrs (GhcPass _1) _2 | |
Defined in GHC.Hs.Types |
type ForallXHsImplicitBndrs (c :: Type -> Constraint) x b = (c (XHsIB x b), c (XXHsImplicitBndrs x b)) #
Instances
type XHsWC GhcPs b | |
Defined in GHC.Hs.Types | |
type XHsWC GhcRn b | |
Defined in GHC.Hs.Types | |
type XHsWC GhcTc b | |
Defined in GHC.Hs.Types |
type family XXHsWildCardBndrs x b #
Instances
type XXHsWildCardBndrs (GhcPass _1) b | |
Defined in GHC.Hs.Types |
type ForallXHsWildCardBndrs (c :: Type -> Constraint) x b = (c (XHsWC x b), c (XXHsWildCardBndrs x b)) #
Instances
type XForAllTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XQualTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XTyVar (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XAppTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
type family XAppKindTy x #
Instances
type XAppKindTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XFunTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XListTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XTupleTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XSumTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XOpTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XParTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XIParamTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XStarTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XKindSig (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XSpliceTy GhcPs | |
Defined in GHC.Hs.Types | |
type XSpliceTy GhcRn | |
Defined in GHC.Hs.Types | |
type XSpliceTy GhcTc | |
Defined in GHC.Hs.Types |
Instances
type XDocTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XBangTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XRecTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
type family XExplicitListTy x #
Instances
type XExplicitListTy GhcPs | |
Defined in GHC.Hs.Types | |
type XExplicitListTy GhcRn | |
Defined in GHC.Hs.Types | |
type XExplicitListTy GhcTc | |
Defined in GHC.Hs.Types |
type family XExplicitTupleTy x #
Instances
type XExplicitTupleTy GhcPs | |
Defined in GHC.Hs.Types | |
type XExplicitTupleTy GhcRn | |
Defined in GHC.Hs.Types | |
type XExplicitTupleTy GhcTc | |
Defined in GHC.Hs.Types |
Instances
type XTyLit (GhcPass _1) | |
Defined in GHC.Hs.Types |
type family XWildCardTy x #
Instances
type XWildCardTy (GhcPass _1) | |
Defined in GHC.Hs.Types |
Instances
type XXType (GhcPass _1) | |
Defined in GHC.Hs.Types |
type ForallXType (c :: Type -> Constraint) x = (c (XForAllTy x), c (XQualTy x), c (XTyVar x), c (XAppTy x), c (XAppKindTy x), c (XFunTy x), c (XListTy x), c (XTupleTy x), c (XSumTy x), c (XOpTy x), c (XParTy x), c (XIParamTy x), c (XStarTy x), c (XKindSig x), c (XSpliceTy x), c (XDocTy x), c (XBangTy x), c (XRecTy x), c (XExplicitListTy x), c (XExplicitTupleTy x), c (XTyLit x), c (XWildCardTy x), c (XXType x)) #
Helper to apply a constraint to all extension points. It has one entry per extension point type family.
type family XUserTyVar x #
Instances
type XUserTyVar (GhcPass _1) | |
Defined in GHC.Hs.Types |
type family XKindedTyVar x #
Instances
type XKindedTyVar (GhcPass _1) | |
Defined in GHC.Hs.Types |
type family XXTyVarBndr x #
Instances
type XXTyVarBndr (GhcPass _1) | |
Defined in GHC.Hs.Types |
type ForallXTyVarBndr (c :: Type -> Constraint) x = (c (XUserTyVar x), c (XKindedTyVar x), c (XXTyVarBndr x)) #
type family XConDeclField x #
Instances
type XConDeclField (GhcPass _1) | |
Defined in GHC.Hs.Types |
type family XXConDeclField x #
Instances
type XXConDeclField (GhcPass _1) | |
Defined in GHC.Hs.Types |
type ForallXConDeclField (c :: Type -> Constraint) x = (c (XConDeclField x), c (XXConDeclField x)) #
type family XCFieldOcc x #
Instances
type XCFieldOcc GhcPs | |
Defined in GHC.Hs.Types | |
type XCFieldOcc GhcRn | |
Defined in GHC.Hs.Types | |
type XCFieldOcc GhcTc | |
Defined in GHC.Hs.Types |
type family XXFieldOcc x #
Instances
type XXFieldOcc (GhcPass _1) | |
Defined in GHC.Hs.Types |
type ForallXFieldOcc (c :: Type -> Constraint) x = (c (XCFieldOcc x), c (XXFieldOcc x)) #
type family XCImportDecl x #
Instances
type XCImportDecl (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XXImportDecl x #
Instances
type XXImportDecl (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type ForallXImportDecl (c :: Type -> Constraint) x = (c (XCImportDecl x), c (XXImportDecl x)) #
Instances
type XIEVar (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEThingAbs x #
Instances
type XIEThingAbs (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEThingAll x #
Instances
type XIEThingAll (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEThingWith x #
Instances
type XIEThingWith (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEModuleContents x #
Instances
type XIEModuleContents (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XIEGroup (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
Instances
type XIEDoc (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type family XIEDocNamed x #
Instances
type XIEDocNamed (GhcPass _1) | |
Defined in GHC.Hs.ImpExp |
type ForallXIE (c :: Type -> Constraint) x = (c (XIEVar x), c (XIEThingAbs x), c (XIEThingAll x), c (XIEThingWith x), c (XIEModuleContents x), c (XIEGroup x), c (XIEDoc x), c (XIEDocNamed x), c (XXIE x)) #
class Convertable a b | a -> b where #
Conversion of annotations from one type index to another. This is required
where the AST is converted from one pass to another, and the extension values
need to be brought along if possible. So for example a SourceText
is
converted via id
, but needs a type signature to keep the type checker
happy.
Instances
Convertable a a | |
Defined in GHC.Hs.Extension |
type ConvertIdX a b = (XHsDoublePrim a ~ XHsDoublePrim b, XHsFloatPrim a ~ XHsFloatPrim b, XHsRat a ~ XHsRat b, XHsInteger a ~ XHsInteger b, XHsWord64Prim a ~ XHsWord64Prim b, XHsInt64Prim a ~ XHsInt64Prim b, XHsWordPrim a ~ XHsWordPrim b, XHsIntPrim a ~ XHsIntPrim b, XHsInt a ~ XHsInt b, XHsStringPrim a ~ XHsStringPrim b, XHsString a ~ XHsString b, XHsCharPrim a ~ XHsCharPrim b, XHsChar a ~ XHsChar b, XXLit a ~ XXLit b) #
A constraint capturing all the extension points that can be converted via
instance Convertable a a
type OutputableX p = (Outputable (XIPBinds p), Outputable (XViaStrategy p), Outputable (XViaStrategy GhcRn)) #
Provide a summary constraint that gives all am Outputable constraint to extension points needing one
type OutputableBndrId (pass :: Pass) = (OutputableBndr (NameOrRdrName (IdP (GhcPass pass))), OutputableBndr (IdP (GhcPass pass)), OutputableBndr (NameOrRdrName (IdP (NoGhcTc (GhcPass pass)))), OutputableBndr (IdP (NoGhcTc (GhcPass pass))), NoGhcTc (GhcPass pass) ~ NoGhcTc (NoGhcTc (GhcPass pass)), OutputableX (GhcPass pass), OutputableX (NoGhcTc (GhcPass pass))) #
Constraint type to bundle up the requirement for OutputableBndr
on both
the p
and the NameOrRdrName
type for it
type family NameOrRdrName id where ... #
Follow the id
, but never beyond Name. This is used in a HsMatchContext
,
for printing messages related to a Match
isExportedId :: Var -> Bool #
isExportedIdVar
means "don't throw this away"
isGlobalId :: Var -> Bool #
data ForallVisFlag #
Is a forall
invisible (e.g., forall a b. {...}
, with a dot) or visible
(e.g., forall a b -> {...}
, with an arrow)?
ForallVis | A visible |
ForallInvis | An invisible |
Instances
unicodeAnn :: AnnKeywordId -> AnnKeywordId #
Convert a normal annotation into its unicode equivalent one
getAndRemoveAnnotationComments :: ApiAnns -> SrcSpan -> ([Located AnnotationComment], ApiAnns) #
Retrieve the comments allocated to the current SrcSpan
, and
remove them from the annotations
getAnnotationComments :: ApiAnns -> SrcSpan -> [Located AnnotationComment] #
getAndRemoveAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> ([SrcSpan], ApiAnns) #
getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> [SrcSpan] #
data AnnKeywordId #
API Annotations exist so that tools can perform source to source conversions of Haskell code. They are used to keep track of the various syntactic keywords that are not captured in the existing AST.
The annotations, together with original source comments are made
available in the
field of pm_annotations
.
Comments are only retained if ParsedModule
is set in
Opt_KeepRawTokenStream
before parsing.DynFlags
The wiki page describing this feature is https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations
Note: in general the names of these are taken from the corresponding token, unless otherwise noted See note [Api annotations] above for details of the usage
Instances
data AnnotationComment #
AnnDocCommentNext String | something beginning '-- |' |
AnnDocCommentPrev String | something beginning '-- ^' |
AnnDocCommentNamed String | something beginning '-- $' |
AnnDocSection Int String | a section heading |
AnnDocOptions String | doc options (prune, ignore-exports, etc) |
AnnLineComment String | comment starting by "--" |
AnnBlockComment String | comment in {- -} |
Instances
Reader Name
Do not use the data constructors of RdrName directly: prefer the family
of functions that creates them, such as mkRdrUnqual
- Note: A Located RdrName will only have API Annotations if it is a compound one, e.g.
`bar` ( ~ )
AnnKeywordId
:AnnType
,AnnOpen
'('
or'['
or'[:'
,AnnClose
')'
or']'
or':]'
,,AnnBackquote
'`'
,AnnVal
AnnTilde
,
Unqual OccName | Unqualified name Used for ordinary, unqualified occurrences, e.g. |
Qual ModuleName OccName | Qualified name A qualified name written by the user in
source code. The module isn't necessarily
the module where the thing is defined;
just the one from which it is imported.
Examples are |
Instances
Eq RdrName | |
Data RdrName | |
Defined in RdrName gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RdrName -> c RdrName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RdrName # toConstr :: RdrName -> Constr # dataTypeOf :: RdrName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RdrName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RdrName) # gmapT :: (forall b. Data b => b -> b) -> RdrName -> RdrName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RdrName -> r # gmapQ :: (forall d. Data d => d -> u) -> RdrName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RdrName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RdrName -> m RdrName # | |
Ord RdrName | |
DisambInfixOp RdrName | |
HasOccName RdrName | |
Outputable RdrName | |
OutputableBndr RdrName | |
Defined in RdrName pprBndr :: BindingSite -> RdrName -> SDoc # pprPrefixOcc :: RdrName -> SDoc # pprInfixOcc :: RdrName -> SDoc # bndrIsJoin_maybe :: RdrName -> Maybe Int # |
concatDocs :: [HsDocString] -> Maybe HsDocString #
Concat docstrings with two newlines in between.
Empty docstrings are skipped.
If all inputs are empty, Nothing
is returned.
appendDocs :: HsDocString -> HsDocString -> HsDocString #
Join two docstrings.
Non-empty docstrings are joined with two newlines in between, resulting in separate paragraphs.
ppr_mbDoc :: Maybe LHsDocString -> SDoc #
hsDocStringToByteString :: HsDocString -> ByteString #
Return the contents of a HsDocString
as a UTF8-encoded ByteString
.
unpackHDS :: HsDocString -> String #
mkHsDocStringUtf8ByteString :: ByteString -> HsDocString #
Create a HsDocString
from a UTF8-encoded ByteString
.
mkHsDocString :: String -> HsDocString #
data HsDocString #
Haskell Documentation String
Internally this is a UTF8-Encoded ByteString
.
Instances
type LHsDocString = Located HsDocString #
Located Haskell Documentation String
newtype DeclDocMap #
Docs for declarations: functions, data types, instances, methods etc.
Instances
Binary DeclDocMap | |
Defined in GHC.Hs.Doc put_ :: BinHandle -> DeclDocMap -> IO () # put :: BinHandle -> DeclDocMap -> IO (Bin DeclDocMap) # get :: BinHandle -> IO DeclDocMap # | |
Outputable DeclDocMap | |
Defined in GHC.Hs.Doc ppr :: DeclDocMap -> SDoc # pprPrec :: Rational -> DeclDocMap -> SDoc # |
Docs for arguments. E.g. function arguments, method arguments.
nameModule :: HasDebugCallStack => Name -> Module #
isExternalName :: Name -> Bool #
nameSrcSpan :: Name -> SrcSpan #
class NamedThing a where #
A class allowing convenient access to the Name
of various datatypes
Instances
NamedThing HoleFitCandidate | |
Defined in TcHoleFitTypes getOccName :: HoleFitCandidate -> OccName # getName :: HoleFitCandidate -> Name # | |
NamedThing ClsInst | |
NamedThing FamInst | |
Defined in FamInstEnv | |
NamedThing IfaceDecl | |
NamedThing IfaceClassOp | |
Defined in IfaceSyn getOccName :: IfaceClassOp -> OccName # getName :: IfaceClassOp -> Name # | |
NamedThing IfaceConDecl | |
Defined in IfaceSyn getOccName :: IfaceConDecl -> OccName # getName :: IfaceConDecl -> Name # | |
NamedThing Class | |
NamedThing ConLike | |
NamedThing DataCon | |
NamedThing PatSyn | |
NamedThing TyThing | |
NamedThing Var | |
NamedThing TyCon | |
NamedThing Name | |
NamedThing (HsTyVarBndr GhcRn) | |
Defined in GHC.Hs.Types getOccName :: HsTyVarBndr GhcRn -> OccName # getName :: HsTyVarBndr GhcRn -> Name # | |
NamedThing (CoAxiom br) | |
NamedThing e => NamedThing (Located e) | |
NamedThing tv => NamedThing (VarBndr tv flag) | |
Instances
Data Type | |
Defined in TyCoRep gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # dataTypeOf :: Type -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) # gmapT :: (forall b. Data b => b -> b) -> Type -> Type # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # | |
NFData Type Source # | |
Defined in Development.IDE.GHC.Orphans | |
Outputable Type | |
Eq (DeBruijn Type) | |
ToHie (TScoped Type) | |
Defined in Compat.HieAst |
A type of the form p
of constraint kind represents a value whose type is
the Haskell predicate p
, where a predicate is what occurs before
the =>
in a Haskell type.
We use PredType
as documentation to mark those types that we guarantee to
have this kind.
It can be expanded into its representation, but:
- The type checker must treat it as opaque
- The rest of the compiler treats it as transparent
Consider these examples:
f :: (Eq a) => a -> Int g :: (?x :: Int -> Int) => a -> Int h :: (r\l) => {r} => {l::Int | r}
Here the Eq a
and ?x :: Int -> Int
and rl
are all called "predicates"
prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a #
gopt :: GeneralFlag -> DynFlags -> Bool #
Test whether a GeneralFlag
is set
data SafeHaskellMode #
The various Safe Haskell modes
Sf_None | inferred unsafe |
Sf_Unsafe | declared and checked |
Sf_Trustworthy | declared and checked |
Sf_Safe | declared and checked |
Sf_SafeInferred | inferred as safe |
Sf_Ignore |
|
Instances
Eq SafeHaskellMode | |
Defined in DynFlags (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
Show SafeHaskellMode | |
Defined in DynFlags showsPrec :: Int -> SafeHaskellMode -> ShowS # show :: SafeHaskellMode -> String # showList :: [SafeHaskellMode] -> ShowS # | |
NFData SafeHaskellMode Source # | |
Defined in Development.IDE.GHC.Orphans rnf :: SafeHaskellMode -> () # | |
Outputable SafeHaskellMode | |
Defined in DynFlags ppr :: SafeHaskellMode -> SDoc # pprPrec :: Rational -> SafeHaskellMode -> SDoc # |
The target code type of the compilation (if any).
Whenever you change the target, also make sure to set ghcLink
to
something sensible.
HscNothing
can be used to avoid generating any output, however, note
that:
- If a program uses Template Haskell the typechecker may need to run code from an imported module. To facilitate this, code generation is enabled for modules imported by modules that use template haskell. See Note [-fno-code mode].
HscC | Generate C code. |
HscAsm | Generate assembly using the native code generator. |
HscLlvm | Generate assembly using the llvm code generator. |
HscInterpreted | Generate bytecode. (Requires |
HscNothing | Don't generate any code. See notes above. |
The GhcMode
tells us whether we're doing multi-module
compilation (controlled via the GHC API) or one-shot
(single-module) compilation. This makes a difference primarily to
the Finder: in one-shot mode we look for interface files for
imported modules, but in multi-module mode we look for source files
in order to check whether they need to be recompiled.
CompManager |
|
OneShot | ghc -c Foo.hs |
MkDepend |
|
What to do in the link step, if there is one.
NoLink | Don't link at all |
LinkBinary | Link object code into a binary |
LinkInMemory | Use the in-memory dynamic linker (works for both bytecode and object code). |
LinkDynLib | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms) |
LinkStaticLib | Link objects into a static lib |
mkModule :: UnitId -> ModuleName -> Module #
mkModuleName :: String -> ModuleName #
moduleNameString :: ModuleName -> String #
ml_hie_file :: ModLocation -> FilePath #
ml_obj_file :: ModLocation -> FilePath #
ml_hs_file :: ModLocation -> Maybe FilePath #
ml_hi_file :: ModLocation -> FilePath #
failed :: SuccessFlag -> Bool #
succeeded :: SuccessFlag -> Bool #
negateFixity :: Fixity #
defaultFixity :: Fixity #
maxPrecedence :: Int #
Instances
Eq Fixity | |
Data Fixity | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity # toConstr :: Fixity -> Constr # dataTypeOf :: Fixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) # gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # | |
Outputable Fixity | |
data FixityDirection #
Instances
Eq FixityDirection | |
Defined in BasicTypes (==) :: FixityDirection -> FixityDirection -> Bool # (/=) :: FixityDirection -> FixityDirection -> Bool # | |
Data FixityDirection | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixityDirection -> c FixityDirection # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FixityDirection # toConstr :: FixityDirection -> Constr # dataTypeOf :: FixityDirection -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FixityDirection) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FixityDirection) # gmapT :: (forall b. Data b => b -> b) -> FixityDirection -> FixityDirection # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixityDirection -> r # gmapQ :: (forall d. Data d => d -> u) -> FixityDirection -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixityDirection -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixityDirection -> m FixityDirection # | |
Outputable FixityDirection | |
Defined in BasicTypes ppr :: FixityDirection -> SDoc # pprPrec :: Rational -> FixityDirection -> SDoc # |
data LexicalFixity #
Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.
Instances
Eq LexicalFixity | |
Defined in BasicTypes (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Data LexicalFixity | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFixity # toConstr :: LexicalFixity -> Constr # dataTypeOf :: LexicalFixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFixity) # gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # | |
Outputable LexicalFixity | |
Defined in BasicTypes ppr :: LexicalFixity -> SDoc # pprPrec :: Rational -> LexicalFixity -> SDoc # |
data SuccessFlag #
Instances
Outputable SuccessFlag | |
Defined in BasicTypes ppr :: SuccessFlag -> SDoc # pprPrec :: Rational -> SuccessFlag -> SDoc # |
data SpliceExplicitFlag #
ExplicitSplice | = $(f x y) |
ImplicitSplice | = f x y, i.e. a naked top level expression |
Instances
Data SpliceExplicitFlag | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceExplicitFlag -> c SpliceExplicitFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag # toConstr :: SpliceExplicitFlag -> Constr # dataTypeOf :: SpliceExplicitFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpliceExplicitFlag) # gmapT :: (forall b. Data b => b -> b) -> SpliceExplicitFlag -> SpliceExplicitFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag # |
SevOutput | |
SevFatal | |
SevInteractive | |
SevDump | Log message intended for compiler developers No filelinecolumn stuff |
SevInfo | Log messages intended for end users. No filelinecolumn stuff. |
SevWarning | |
SevError | SevWarning and SevError are used for warnings and errors o The message has a filelinecolumn heading, plus "warning:" or "error:", added by mkLocMessags o Output is intended for end users |
unRealSrcSpan :: RealLocated a -> a #
getRealSrcSpan :: RealLocated a -> RealSrcSpan #
cL :: HasSrcSpan a => SrcSpan -> SrcSpanLess a -> a #
An abbreviated form of composeSrcSpan,
mainly to replace the hardcoded L
dL :: HasSrcSpan a => a -> Located (SrcSpanLess a) #
An abbreviated form of decomposeSrcSpan, mainly to be used in ViewPatterns
Determines whether a span is enclosed by another one
spans :: SrcSpan -> (Int, Int) -> Bool #
Determines whether a span encloses a given line and column index
cmpLocated :: (HasSrcSpan a, Ord (SrcSpanLess a)) => a -> a -> Ordering #
Tests the ordering of the two located things
eqLocated :: (HasSrcSpan a, Eq (SrcSpanLess a)) => a -> a -> Bool #
Tests whether the two located things are equal
addCLoc :: (HasSrcSpan a, HasSrcSpan b, HasSrcSpan c) => a -> b -> SrcSpanLess c -> c #
Combine locations from two Located
things and add them to a third thing
combineLocs :: (HasSrcSpan a, HasSrcSpan b) => a -> b -> SrcSpan #
mkGeneralLocated :: HasSrcSpan e => String -> SrcSpanLess e -> e #
noLoc :: HasSrcSpan a => SrcSpanLess a -> a #
unLoc :: HasSrcSpan a => a -> SrcSpanLess a #
srcSpanEnd :: SrcSpan -> SrcLoc #
srcSpanStart :: SrcSpan -> SrcLoc #
srcSpanEndCol :: RealSrcSpan -> Int #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanEndLine :: RealSrcSpan -> Int #
srcSpanStartLine :: RealSrcSpan -> Int #
isGoodSrcSpan :: SrcSpan -> Bool #
Test if a SrcSpan
is "good", i.e. has precise location information
srcLocSpan :: SrcLoc -> SrcSpan #
Create a SrcSpan
corresponding to a single point
srcLocCol :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc
srcLocLine :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc
srcLocFile :: RealSrcLoc -> FastString #
Gives the filename of the RealSrcLoc
data RealSrcLoc #
Real Source Location
Represents a single point within a file
Instances
Eq RealSrcLoc | |
Defined in SrcLoc (==) :: RealSrcLoc -> RealSrcLoc -> Bool # (/=) :: RealSrcLoc -> RealSrcLoc -> Bool # | |
Ord RealSrcLoc | |
Defined in SrcLoc compare :: RealSrcLoc -> RealSrcLoc -> Ordering # (<) :: RealSrcLoc -> RealSrcLoc -> Bool # (<=) :: RealSrcLoc -> RealSrcLoc -> Bool # (>) :: RealSrcLoc -> RealSrcLoc -> Bool # (>=) :: RealSrcLoc -> RealSrcLoc -> Bool # max :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # min :: RealSrcLoc -> RealSrcLoc -> RealSrcLoc # | |
Show RealSrcLoc | |
Defined in SrcLoc showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
Outputable RealSrcLoc | |
Defined in SrcLoc ppr :: RealSrcLoc -> SDoc # pprPrec :: Rational -> RealSrcLoc -> SDoc # |
data RealSrcSpan #
A RealSrcSpan
delimits a portion of a text file. It could be represented
by a pair of (line,column) coordinates, but in fact we optimise
slightly by using more compact representations for single-line and
zero-length spans, both of which are quite common.
The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.
Real Source Span
Instances
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.
Instances
Eq SrcSpan | |
Data SrcSpan | |
Defined in SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan # toConstr :: SrcSpan -> Constr # dataTypeOf :: SrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) # gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # | |
Ord SrcSpan | |
Show SrcSpan | |
NFData SrcSpan | |
ToJson SrcSpan | |
Outputable SrcSpan | |
NamedThing e => NamedThing (Located e) | |
HasSrcSpan (Located a) | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
HasLoc (Located a) | |
Defined in Compat.HieAst | |
HasType (LHsBind GhcRn) | |
Defined in Compat.HieAst getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type] | |
HasType (LHsBind GhcTc) | |
Defined in Compat.HieAst getTypeNode :: LHsBind GhcTc -> HieM [HieAST Type] | |
HasType (LHsExpr GhcRn) | |
Defined in Compat.HieAst getTypeNode :: LHsExpr GhcRn -> HieM [HieAST Type] | |
HasType (LHsExpr GhcTc) | This instance tries to construct
Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive. See #16233 |
Defined in Compat.HieAst getTypeNode :: LHsExpr GhcTc -> HieM [HieAST Type] | |
HasType (Located (Pat GhcRn)) | |
Defined in Compat.HieAst | |
HasType (Located (Pat GhcTc)) | |
Defined in Compat.HieAst | |
(a ~ GhcPass p, ToHie (LHsExpr a), Data (HsTupArg a)) => ToHie (LHsTupArg (GhcPass p)) | |
(a ~ GhcPass p, ToHie (PScoped (LPat a)), ToHie (BindContext (LHsBind a)), ToHie (LHsExpr a), ToHie (MatchGroup a (LHsCmd a)), ToHie (SigContext (LSig a)), ToHie (RScoped (HsValBindsLR a a)), Data (HsCmd a), Data (HsCmdTop a), Data (StmtLR a a (Located (HsCmd a))), Data (HsLocalBinds a), Data (StmtLR a a (Located (HsExpr a)))) => ToHie (LHsCmd (GhcPass p)) | |
(ToHie (LHsCmd a), Data (HsCmdTop a)) => ToHie (LHsCmdTop a) | |
Defined in Compat.HieAst | |
ToHie (LSpliceDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LTyClDecl GhcRn) | |
ToHie (LFamilyDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LFamilyDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInjectivityAnn GhcRn) | |
Defined in Compat.HieAst toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type] | |
ToHie (HsDeriving GhcRn) | |
Defined in Compat.HieAst toHie :: HsDeriving GhcRn -> HieM [HieAST Type] | |
ToHie (LHsDerivingClause GhcRn) | |
Defined in Compat.HieAst toHie :: LHsDerivingClause GhcRn -> HieM [HieAST Type] | |
ToHie (LStandaloneKindSig GhcRn) | |
Defined in Compat.HieAst toHie :: LStandaloneKindSig GhcRn -> HieM [HieAST Type] | |
ToHie (LConDecl GhcRn) | |
ToHie (LTyFamInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDataFamInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LClsInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInstDecl GhcRn) | |
ToHie (LDerivDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDerivDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDefaultDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LForeignDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LForeignDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecls GhcRn) | |
Defined in Compat.HieAst toHie :: LRuleDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecl GhcRn) | |
ToHie (LWarnDecls GhcRn) | |
Defined in Compat.HieAst toHie :: LWarnDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LWarnDecl GhcRn) | |
ToHie (LAnnDecl GhcRn) | |
ToHie (LRoleAnnotDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LFixitySig GhcRn) | |
Defined in Compat.HieAst toHie :: LFixitySig GhcRn -> HieM [HieAST Type] | |
ToHie (LHsContext GhcRn) | |
Defined in Compat.HieAst toHie :: LHsContext GhcRn -> HieM [HieAST Type] | |
ToHie (LHsType GhcRn) | |
ToHie (LConDeclField GhcRn) | |
Defined in Compat.HieAst toHie :: LConDeclField GhcRn -> HieM [HieAST Type] | |
(a ~ GhcPass p, ToHie (Context (Located (IdP a))), HasType (LHsExpr a), ToHie (PScoped (LPat a)), ToHie (MatchGroup a (LHsExpr a)), ToHie (LGRHS a (LHsExpr a)), ToHie (RContext (HsRecordBinds a)), ToHie (RFContext (Located (AmbiguousFieldOcc a))), ToHie (ArithSeqInfo a), ToHie (LHsCmdTop a), ToHie (RScoped (GuardLStmt a)), ToHie (RScoped (LHsLocalBinds a)), ToHie (TScoped (LHsWcType (NoGhcTc a))), ToHie (TScoped (LHsSigWcType (NoGhcTc a))), Data (HsExpr a), Data (HsSplice a), Data (HsTupArg a), Data (AmbiguousFieldOcc a), HasRealDataConName a) => ToHie (LHsExpr (GhcPass p)) | |
ToHie (LImportDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LImportDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LBooleanFormula (Located Name)) | |
Defined in Compat.HieAst | |
ToHie (Located [LConDeclField GhcRn]) | |
Defined in Compat.HieAst | |
ToHie (Located (DerivStrategy GhcRn)) | |
Defined in Compat.HieAst | |
(ToHie (Context (Located (IdP a))), ToHie (PScoped (LPat a)), ToHie (HsPatSynDir a)) => ToHie (Located (PatSynBind a a)) | |
Defined in Compat.HieAst toHie :: Located (PatSynBind a a) -> HieM [HieAST Type] | |
ToHie (Located HsIPName) | |
ToHie (Located (FunDep (Located Name))) | |
(ToHie (LHsExpr a), Data (HsSplice a)) => ToHie (Located (HsSplice a)) | |
ToHie (Located OverlapMode) | |
Defined in Compat.HieAst toHie :: Located OverlapMode -> HieM [HieAST Type] | |
(a ~ GhcPass p, ToHie (Context (Located (IdP a))), ToHie (RContext (HsRecFields a (PScoped (LPat a)))), ToHie (LHsExpr a), ToHie (TScoped (LHsSigWcType a)), ProtectSig a, ToHie (TScoped (ProtectedSig a)), HasType (LPat a), Data (HsSplice a)) => ToHie (PScoped (Located (Pat (GhcPass p)))) | |
ToHie (TScoped (LHsType GhcRn)) | |
ToHie (TScoped (LHsWcType GhcTc)) | |
ToHie (TScoped (LHsSigWcType GhcTc)) | Dummy instances - never called |
Defined in Compat.HieAst toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] | |
ToHie (Context (Located NoExtField)) | |
Defined in Compat.HieAst toHie :: Context (Located NoExtField) -> HieM [HieAST Type] | |
ToHie (Context (Located Var)) | |
ToHie (Context (Located Name)) | |
(ToHie (Context (Located (IdP a))), ToHie (MatchGroup a (LHsExpr a)), ToHie (PScoped (LPat a)), ToHie (GRHSs a (LHsExpr a)), ToHie (LHsExpr a), ToHie (Located (PatSynBind a a)), HasType (LHsBind a), ModifyState (IdP a), Data (HsBind a)) => ToHie (BindContext (LHsBind a)) | |
Defined in Compat.HieAst | |
(a ~ GhcPass p, ToHie (PScoped (LPat a)), ToHie (LHsExpr a), ToHie (SigContext (LSig a)), ToHie (RScoped (LHsLocalBinds a)), ToHie (RScoped (ApplicativeArg a)), ToHie (Located body), Data (StmtLR a a (Located body)), Data (StmtLR a a (Located (HsExpr a)))) => ToHie (RScoped (LStmt (GhcPass p) (Located body))) | |
ToHie (RScoped (LFamilyResultSig GhcRn)) | |
Defined in Compat.HieAst toHie :: RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type] | |
ToHie (RScoped (LRuleBndr GhcRn)) | |
(ToHie (LHsExpr a), ToHie (PScoped (LPat a)), ToHie (BindContext (LHsBind a)), ToHie (SigContext (LSig a)), ToHie (RScoped (HsValBindsLR a a)), Data (HsLocalBinds a)) => ToHie (RScoped (LHsLocalBinds a)) | |
Defined in Compat.HieAst toHie :: RScoped (LHsLocalBinds a) -> HieM [HieAST Type] | |
ToHie (SigContext (LSig GhcRn)) | |
ToHie (SigContext (LSig GhcTc)) | |
(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data label, Data arg) => ToHie (RContext (LHsRecField' label arg)) | |
Defined in Compat.HieAst toHie :: RContext (LHsRecField' label arg) -> HieM [HieAST Type] | |
ToHie (RFContext (LFieldOcc GhcRn)) | |
ToHie (RFContext (LFieldOcc GhcTc)) | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) | |
Defined in Compat.HieAst | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) | |
Defined in Compat.HieAst | |
ToHie (IEContext (LIEWrappedName Name)) | |
Defined in Compat.HieAst toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type] | |
ToHie (IEContext (LIE GhcRn)) | |
ToHie (IEContext (Located (FieldLbl Name))) | |
ToHie (IEContext (Located ModuleName)) | |
Defined in Compat.HieAst toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type] | |
ToHie (TVScoped (LHsTyVarBndr GhcRn)) | |
Defined in Compat.HieAst toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type] | |
Outputable a => Show (GenLocated SrcSpan a) Source # | |
Defined in Development.IDE.GHC.Orphans | |
(a ~ GhcPass p, ToHie body, ToHie (HsMatchContext (NameOrRdrName (IdP a))), ToHie (PScoped (LPat a)), ToHie (GRHSs a body), Data (Match a body)) => ToHie (LMatch (GhcPass p) body) | |
(ToHie (Located body), ToHie (RScoped (GuardLStmt a)), Data (GRHS a (Located body))) => ToHie (LGRHS a (Located body)) | |
data GenLocated l e #
We attach SrcSpans to lots of things, so let's have a datatype for it.
L l e |
Instances
Functor (GenLocated l) | |
Defined in SrcLoc fmap :: (a -> b) -> GenLocated l a -> GenLocated l b # (<$) :: a -> GenLocated l b -> GenLocated l a # | |
Foldable (GenLocated l) | |
Defined in SrcLoc fold :: Monoid m => GenLocated l m -> m # foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m # foldMap' :: Monoid m => (a -> m) -> GenLocated l a -> m # foldr :: (a -> b -> b) -> b -> GenLocated l a -> b # foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b # foldl :: (b -> a -> b) -> b -> GenLocated l a -> b # foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b # foldr1 :: (a -> a -> a) -> GenLocated l a -> a # foldl1 :: (a -> a -> a) -> GenLocated l a -> a # toList :: GenLocated l a -> [a] # null :: GenLocated l a -> Bool # length :: GenLocated l a -> Int # elem :: Eq a => a -> GenLocated l a -> Bool # maximum :: Ord a => GenLocated l a -> a # minimum :: Ord a => GenLocated l a -> a # sum :: Num a => GenLocated l a -> a # product :: Num a => GenLocated l a -> a # | |
Traversable (GenLocated l) | |
Defined in SrcLoc traverse :: Applicative f => (a -> f b) -> GenLocated l a -> f (GenLocated l b) # sequenceA :: Applicative f => GenLocated l (f a) -> f (GenLocated l a) # mapM :: Monad m => (a -> m b) -> GenLocated l a -> m (GenLocated l b) # sequence :: Monad m => GenLocated l (m a) -> m (GenLocated l a) # | |
NamedThing e => NamedThing (Located e) | |
HasSrcSpan (Located a) | |
Defined in SrcLoc composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
HasLoc (Located a) | |
Defined in Compat.HieAst | |
HasType (LHsBind GhcRn) | |
Defined in Compat.HieAst getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type] | |
HasType (LHsBind GhcTc) | |
Defined in Compat.HieAst getTypeNode :: LHsBind GhcTc -> HieM [HieAST Type] | |
HasType (LHsExpr GhcRn) | |
Defined in Compat.HieAst getTypeNode :: LHsExpr GhcRn -> HieM [HieAST Type] | |
HasType (LHsExpr GhcTc) | This instance tries to construct
Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive. See #16233 |
Defined in Compat.HieAst getTypeNode :: LHsExpr GhcTc -> HieM [HieAST Type] | |
HasType (Located (Pat GhcRn)) | |
Defined in Compat.HieAst | |
HasType (Located (Pat GhcTc)) | |
Defined in Compat.HieAst | |
(a ~ GhcPass p, ToHie (LHsExpr a), Data (HsTupArg a)) => ToHie (LHsTupArg (GhcPass p)) | |
(a ~ GhcPass p, ToHie (PScoped (LPat a)), ToHie (BindContext (LHsBind a)), ToHie (LHsExpr a), ToHie (MatchGroup a (LHsCmd a)), ToHie (SigContext (LSig a)), ToHie (RScoped (HsValBindsLR a a)), Data (HsCmd a), Data (HsCmdTop a), Data (StmtLR a a (Located (HsCmd a))), Data (HsLocalBinds a), Data (StmtLR a a (Located (HsExpr a)))) => ToHie (LHsCmd (GhcPass p)) | |
(ToHie (LHsCmd a), Data (HsCmdTop a)) => ToHie (LHsCmdTop a) | |
Defined in Compat.HieAst | |
ToHie (LSpliceDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LTyClDecl GhcRn) | |
ToHie (LFamilyDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LFamilyDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInjectivityAnn GhcRn) | |
Defined in Compat.HieAst toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type] | |
ToHie (HsDeriving GhcRn) | |
Defined in Compat.HieAst toHie :: HsDeriving GhcRn -> HieM [HieAST Type] | |
ToHie (LHsDerivingClause GhcRn) | |
Defined in Compat.HieAst toHie :: LHsDerivingClause GhcRn -> HieM [HieAST Type] | |
ToHie (LStandaloneKindSig GhcRn) | |
Defined in Compat.HieAst toHie :: LStandaloneKindSig GhcRn -> HieM [HieAST Type] | |
ToHie (LConDecl GhcRn) | |
ToHie (LTyFamInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDataFamInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LClsInstDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInstDecl GhcRn) | |
ToHie (LDerivDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDerivDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDefaultDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LForeignDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LForeignDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecls GhcRn) | |
Defined in Compat.HieAst toHie :: LRuleDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecl GhcRn) | |
ToHie (LWarnDecls GhcRn) | |
Defined in Compat.HieAst toHie :: LWarnDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LWarnDecl GhcRn) | |
ToHie (LAnnDecl GhcRn) | |
ToHie (LRoleAnnotDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LFixitySig GhcRn) | |
Defined in Compat.HieAst toHie :: LFixitySig GhcRn -> HieM [HieAST Type] | |
ToHie (LHsContext GhcRn) | |
Defined in Compat.HieAst toHie :: LHsContext GhcRn -> HieM [HieAST Type] | |
ToHie (LHsType GhcRn) | |
ToHie (LConDeclField GhcRn) | |
Defined in Compat.HieAst toHie :: LConDeclField GhcRn -> HieM [HieAST Type] | |
(a ~ GhcPass p, ToHie (Context (Located (IdP a))), HasType (LHsExpr a), ToHie (PScoped (LPat a)), ToHie (MatchGroup a (LHsExpr a)), ToHie (LGRHS a (LHsExpr a)), ToHie (RContext (HsRecordBinds a)), ToHie (RFContext (Located (AmbiguousFieldOcc a))), ToHie (ArithSeqInfo a), ToHie (LHsCmdTop a), ToHie (RScoped (GuardLStmt a)), ToHie (RScoped (LHsLocalBinds a)), ToHie (TScoped (LHsWcType (NoGhcTc a))), ToHie (TScoped (LHsSigWcType (NoGhcTc a))), Data (HsExpr a), Data (HsSplice a), Data (HsTupArg a), Data (AmbiguousFieldOcc a), HasRealDataConName a) => ToHie (LHsExpr (GhcPass p)) | |
ToHie (LImportDecl GhcRn) | |
Defined in Compat.HieAst toHie :: LImportDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LBooleanFormula (Located Name)) | |
Defined in Compat.HieAst | |
ToHie (Located [LConDeclField GhcRn]) | |
Defined in Compat.HieAst | |
ToHie (Located (DerivStrategy GhcRn)) | |
Defined in Compat.HieAst | |
(ToHie (Context (Located (IdP a))), ToHie (PScoped (LPat a)), ToHie (HsPatSynDir a)) => ToHie (Located (PatSynBind a a)) | |
Defined in Compat.HieAst toHie :: Located (PatSynBind a a) -> HieM [HieAST Type] | |
ToHie (Located HsIPName) | |
ToHie (Located (FunDep (Located Name))) | |
(ToHie (LHsExpr a), Data (HsSplice a)) => ToHie (Located (HsSplice a)) | |
ToHie (Located OverlapMode) | |
Defined in Compat.HieAst toHie :: Located OverlapMode -> HieM [HieAST Type] | |
(a ~ GhcPass p, ToHie (Context (Located (IdP a))), ToHie (RContext (HsRecFields a (PScoped (LPat a)))), ToHie (LHsExpr a), ToHie (TScoped (LHsSigWcType a)), ProtectSig a, ToHie (TScoped (ProtectedSig a)), HasType (LPat a), Data (HsSplice a)) => ToHie (PScoped (Located (Pat (GhcPass p)))) | |
ToHie (TScoped (LHsType GhcRn)) | |
ToHie (TScoped (LHsWcType GhcTc)) | |
ToHie (TScoped (LHsSigWcType GhcTc)) | Dummy instances - never called |
Defined in Compat.HieAst toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] | |
ToHie (Context (Located NoExtField)) | |
Defined in Compat.HieAst toHie :: Context (Located NoExtField) -> HieM [HieAST Type] | |
ToHie (Context (Located Var)) | |
ToHie (Context (Located Name)) | |
(ToHie (Context (Located (IdP a))), ToHie (MatchGroup a (LHsExpr a)), ToHie (PScoped (LPat a)), ToHie (GRHSs a (LHsExpr a)), ToHie (LHsExpr a), ToHie (Located (PatSynBind a a)), HasType (LHsBind a), ModifyState (IdP a), Data (HsBind a)) => ToHie (BindContext (LHsBind a)) | |
Defined in Compat.HieAst | |
(a ~ GhcPass p, ToHie (PScoped (LPat a)), ToHie (LHsExpr a), ToHie (SigContext (LSig a)), ToHie (RScoped (LHsLocalBinds a)), ToHie (RScoped (ApplicativeArg a)), ToHie (Located body), Data (StmtLR a a (Located body)), Data (StmtLR a a (Located (HsExpr a)))) => ToHie (RScoped (LStmt (GhcPass p) (Located body))) | |
ToHie (RScoped (LFamilyResultSig GhcRn)) | |
Defined in Compat.HieAst toHie :: RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type] | |
ToHie (RScoped (LRuleBndr GhcRn)) | |
(ToHie (LHsExpr a), ToHie (PScoped (LPat a)), ToHie (BindContext (LHsBind a)), ToHie (SigContext (LSig a)), ToHie (RScoped (HsValBindsLR a a)), Data (HsLocalBinds a)) => ToHie (RScoped (LHsLocalBinds a)) | |
Defined in Compat.HieAst toHie :: RScoped (LHsLocalBinds a) -> HieM [HieAST Type] | |
ToHie (SigContext (LSig GhcRn)) | |
ToHie (SigContext (LSig GhcTc)) | |
(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data label, Data arg) => ToHie (RContext (LHsRecField' label arg)) | |
Defined in Compat.HieAst toHie :: RContext (LHsRecField' label arg) -> HieM [HieAST Type] | |
ToHie (RFContext (LFieldOcc GhcRn)) | |
ToHie (RFContext (LFieldOcc GhcTc)) | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) | |
Defined in Compat.HieAst | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) | |
Defined in Compat.HieAst | |
ToHie (IEContext (LIEWrappedName Name)) | |
Defined in Compat.HieAst toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type] | |
ToHie (IEContext (LIE GhcRn)) | |
ToHie (IEContext (Located (FieldLbl Name))) | |
ToHie (IEContext (Located ModuleName)) | |
Defined in Compat.HieAst toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type] | |
ToHie (TVScoped (LHsTyVarBndr GhcRn)) | |
Defined in Compat.HieAst toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type] | |
(Eq l, Eq e) => Eq (GenLocated l e) | |
Defined in SrcLoc (==) :: GenLocated l e -> GenLocated l e -> Bool # (/=) :: GenLocated l e -> GenLocated l e -> Bool # | |
(Data l, Data e) => Data (GenLocated l e) | |
Defined in SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenLocated l e -> c (GenLocated l e) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenLocated l e) # toConstr :: GenLocated l e -> Constr # dataTypeOf :: GenLocated l e -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenLocated l e)) # dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (GenLocated l e)) # gmapT :: (forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r # gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) # | |
(Ord l, Ord e) => Ord (GenLocated l e) | |
Defined in SrcLoc compare :: GenLocated l e -> GenLocated l e -> Ordering # (<) :: GenLocated l e -> GenLocated l e -> Bool # (<=) :: GenLocated l e -> GenLocated l e -> Bool # (>) :: GenLocated l e -> GenLocated l e -> Bool # (>=) :: GenLocated l e -> GenLocated l e -> Bool # max :: GenLocated l e -> GenLocated l e -> GenLocated l e # min :: GenLocated l e -> GenLocated l e -> GenLocated l e # | |
Outputable a => Show (GenLocated SrcSpan a) Source # | |
Defined in Development.IDE.GHC.Orphans | |
(NFData l, NFData e) => NFData (GenLocated l e) Source # | |
Defined in Development.IDE.GHC.Orphans rnf :: GenLocated l e -> () # | |
(Outputable l, Outputable e) => Outputable (GenLocated l e) | |
Defined in SrcLoc ppr :: GenLocated l e -> SDoc # pprPrec :: Rational -> GenLocated l e -> SDoc # | |
(a ~ GhcPass p, ToHie body, ToHie (HsMatchContext (NameOrRdrName (IdP a))), ToHie (PScoped (LPat a)), ToHie (GRHSs a body), Data (Match a body)) => ToHie (LMatch (GhcPass p) body) | |
(ToHie (Located body), ToHie (RScoped (GuardLStmt a)), Data (GRHS a (Located body))) => ToHie (LGRHS a (Located body)) | |
type SrcSpanLess (GenLocated l e) | |
Defined in SrcLoc |
type Located = GenLocated SrcSpan #
type family SrcSpanLess a #
Determines the type of undecorated syntactic entities
For most syntactic entities E
, where source location spans are
introduced by a wrapper construtor of the same syntactic entity,
we have `SrcSpanLess E = E`.
However, some syntactic entities have a different type compared to
a syntactic entity `e :: E` may have the type `Located E` when
decorated by wrapping it with `L sp e` for a source span sp
.
Instances
type SrcSpanLess Name | |
Defined in Name | |
type SrcSpanLess (GenLocated l e) | |
Defined in SrcLoc |
composeSrcSpan :: HasSrcSpan a => Located (SrcSpanLess a) -> a #
Composes a SrcSpan
decoration with an undecorated syntactic
entity to form its decorated variant
decomposeSrcSpan :: HasSrcSpan a => a -> Located (SrcSpanLess a) #
Decomposes a decorated syntactic entity into its SrcSpan
decoration and its undecorated variant
data PrintUnqualified #
When printing code that contains original names, we need to map the
original names back to something the user understands. This is the
purpose of the triple of functions that gets passed around
when rendering SDoc
.
A Module is a pair of a UnitId
and a ModuleName
.
Module variables (i.e. H
) which can be instantiated to a
specific module at some later point in time are represented
with moduleUnitId
set to holeUnitId
(this allows us to
avoid having to make moduleUnitId
a partial operation.)
Instances
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List
.
Instances
A unit identifier identifies a (possibly partially) instantiated
library. It is primarily used as part of Module
, which in turn
is used in Name
, which is used to give names to entities when
typechecking.
There are two possible forms for a UnitId
. It can be a
DefiniteUnitId
, in which case we just have a string that uniquely
identifies some fully compiled, installed library we have on disk.
However, when we are typechecking a library with missing holes,
we may need to instantiate a library on the fly (in which case
we don't have any on-disk representation.) In that case, you
have an IndefiniteUnitId
, which explicitly records the
instantiation, so that we can substitute over it.
Instances
isFunTyCon :: TyCon -> Bool #
TyCons represent type constructors. Type constructors are introduced by things such as:
1) Data declarations: data Foo = ...
creates the Foo
type constructor of
kind *
2) Type synonyms: type Foo = ...
creates the Foo
type constructor
3) Newtypes: newtype Foo a = MkFoo ...
creates the Foo
type constructor
of kind * -> *
4) Class declarations: class Foo where
creates the Foo
type constructor
of kind *
This data type also encodes a number of primitive, built in type constructors such as those for function and tuple types.
Instances
Eq TyCon | |
Data TyCon | |
Defined in TyCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCon -> c TyCon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCon # dataTypeOf :: TyCon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyCon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCon) # gmapT :: (forall b. Data b => b -> b) -> TyCon -> TyCon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCon -> r # gmapQ :: (forall d. Data d => d -> u) -> TyCon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCon -> m TyCon # | |
NamedThing TyCon | |
Uniquable TyCon | |
Outputable TyCon | |
withSignalHandlers :: (ExceptionMonad m, MonadIO m) => m a -> m a #
Temporarily install standard signal handlers for catching ^C, which just throw an exception in the current thread.
showGhcException :: GhcException -> ShowS #
Append a description of the given exception to this string.
Note that this uses unsafeGlobalDynFlags
, which may have some
uninitialized fields if invoked before initGhcMonad
has been called.
If the error message to be printed includes a pretty-printer document
which forces one of these fields this call may bottom.
data GhcException #
GHC's own exception type error messages all take the form:
location: error
If the location is on the command line, or in GHC itself, then location="ghc". All of the error types below correspond to a location of "ghc", except for ProgramError (where the string is assumed to contain a location already, so we don't print one).
Signal Int | Some other fatal signal (SIGHUP,SIGTERM) |
UsageError String | Prints the short usage msg after the error |
CmdLineError String | A problem with the command line arguments, but don't print usage. |
Panic String | The |
PprPanic String SDoc | |
Sorry String | The user tickled something that's known not to work yet, but we're not counting it as a bug. |
PprSorry String SDoc | |
InstallationError String | An installation problem. |
ProgramError String | An error in the user's code, probably. |
PprProgramError String SDoc |
Instances
Show GhcException | |
Defined in Panic showsPrec :: Int -> GhcException -> ShowS # show :: GhcException -> String # showList :: [GhcException] -> ShowS # | |
Exception GhcException | |
Defined in Panic |
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
Eq Name | |
Data Name | |
Defined in Name gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Ord Name | Caution: This instance is implemented via See |
NFData Name | |
NamedThing Name | |
HasOccName Name | |
Binary Name | Assumes that the |
Uniquable Name | |
HasSrcSpan Name | |
Defined in Name composeSrcSpan :: Located (SrcSpanLess Name) -> Name # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) # | |
Outputable Name | |
OutputableBndr Name | |
Defined in Name pprBndr :: BindingSite -> Name -> SDoc # pprPrefixOcc :: Name -> SDoc # pprInfixOcc :: Name -> SDoc # bndrIsJoin_maybe :: Name -> Maybe Int # | |
ModifyState Name | |
Defined in Compat.HieAst addSubstitution :: Name -> Name -> HieState -> HieState | |
ToHie (LBooleanFormula (Located Name)) | |
Defined in Compat.HieAst | |
ToHie (Located (FunDep (Located Name))) | |
ToHie (Context (Located Name)) | |
ToHie (IEContext (LIEWrappedName Name)) | |
Defined in Compat.HieAst toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type] | |
ToHie (IEContext (Located (FieldLbl Name))) | |
type SrcSpanLess Name | |
Defined in Name |
Contains not only a collection of GeneralFlag
s but also a plethora of
information relating to the compilation of a single file or GHC session
DynFlags | |
|
data GeneralFlag #
Enumerates the simple on-or-off dynamic flags
Instances
Enum GeneralFlag | |
Defined in DynFlags succ :: GeneralFlag -> GeneralFlag # pred :: GeneralFlag -> GeneralFlag # toEnum :: Int -> GeneralFlag # fromEnum :: GeneralFlag -> Int # enumFrom :: GeneralFlag -> [GeneralFlag] # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] # | |
Eq GeneralFlag | |
Defined in DynFlags (==) :: GeneralFlag -> GeneralFlag -> Bool # (/=) :: GeneralFlag -> GeneralFlag -> Bool # | |
Show GeneralFlag | |
Defined in DynFlags showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # |
gfinally :: ExceptionMonad m => m a -> m b -> m a #
gcatch :: (ExceptionMonad m, Exception e) => m a -> (e -> m a) -> m a #
gbracket :: ExceptionMonad m => m a -> (a -> m b) -> (a -> m c) -> m c #
type ForeignHValue = ForeignRef HValue #
coreModule :: DesugaredMod m => m -> ModGuts #
emptyFilesToClean :: FilesToClean #
An empty FilesToClean
isBmi2Enabled :: DynFlags -> Bool #
isBmiEnabled :: DynFlags -> Bool #
isAvx512pfEnabled :: DynFlags -> Bool #
isAvx512fEnabled :: DynFlags -> Bool #
isAvx512erEnabled :: DynFlags -> Bool #
isAvx512cdEnabled :: DynFlags -> Bool #
isAvx2Enabled :: DynFlags -> Bool #
isAvxEnabled :: DynFlags -> Bool #
isSse4_2Enabled :: DynFlags -> Bool #
isSse2Enabled :: DynFlags -> Bool #
isSseEnabled :: DynFlags -> Bool #
setUnsafeGlobalDynFlags :: DynFlags -> IO () #
tARGET_MAX_WORD :: DynFlags -> Integer #
tARGET_MAX_INT :: DynFlags -> Integer #
tARGET_MIN_INT :: DynFlags -> Integer #
mAX_PTR_TAG :: DynFlags -> Int #
wordAlignment :: DynFlags -> Alignment #
wORD_SIZE_IN_BITS :: DynFlags -> Int #
bLOCK_SIZE_W :: DynFlags -> Int #
iLDV_STATE_USE :: DynFlags -> Integer #
iLDV_STATE_CREATE :: DynFlags -> Integer #
iLDV_CREATE_MASK :: DynFlags -> Integer #
dYNAMIC_BY_DEFAULT :: DynFlags -> Bool #
wORDS_BIGENDIAN :: DynFlags -> Bool #
bITMAP_BITS_SHIFT :: DynFlags -> Int #
cLONG_LONG_SIZE :: DynFlags -> Int #
cLONG_SIZE :: DynFlags -> Int #
dOUBLE_SIZE :: DynFlags -> Int #
aP_STACK_SPLIM :: DynFlags -> Int #
rESERVED_STACK_WORDS :: DynFlags -> Int #
rESERVED_C_STACK_BYTES :: DynFlags -> Int #
mAX_Real_Long_REG :: DynFlags -> Int #
mAX_Real_XMM_REG :: DynFlags -> Int #
mAX_Real_Double_REG :: DynFlags -> Int #
mAX_Real_Float_REG :: DynFlags -> Int #
mAX_Real_Vanilla_REG :: DynFlags -> Int #
mAX_XMM_REG :: DynFlags -> Int #
mAX_Long_REG :: DynFlags -> Int #
mAX_Double_REG :: DynFlags -> Int #
mAX_Float_REG :: DynFlags -> Int #
mAX_Vanilla_REG :: DynFlags -> Int #
mUT_ARR_PTRS_CARD_BITS :: DynFlags -> Int #
mAX_CHARLIKE :: DynFlags -> Int #
mIN_CHARLIKE :: DynFlags -> Int #
mAX_INTLIKE :: DynFlags -> Int #
mIN_INTLIKE :: DynFlags -> Int #
mIN_PAYLOAD_SIZE :: DynFlags -> Int #
mAX_SPEC_AP_SIZE :: DynFlags -> Int #
mAX_SPEC_SELECTEE_SIZE :: DynFlags -> Int #
oFFSET_StgStack_stack :: DynFlags -> Int #
oFFSET_StgStack_sp :: DynFlags -> Int #
oFFSET_StgTSO_stackobj :: DynFlags -> Int #
oFFSET_StgTSO_cccs :: DynFlags -> Int #
oFFSET_StgArrBytes_bytes :: DynFlags -> Int #
sIZEOF_StgArrBytes_NoHdr :: DynFlags -> Int #
sIZEOF_StgSMPThunkHeader :: DynFlags -> Int #
oFFSET_StgHeader_ldvw :: DynFlags -> Int #
oFFSET_StgHeader_ccs :: DynFlags -> Int #
sIZEOF_CostCentreStack :: DynFlags -> Int #
oFFSET_bdescr_flags :: DynFlags -> Int #
oFFSET_bdescr_blocks :: DynFlags -> Int #
oFFSET_bdescr_free :: DynFlags -> Int #
oFFSET_bdescr_start :: DynFlags -> Int #
oFFSET_Capability_r :: DynFlags -> Int #
oFFSET_stgGCFun :: DynFlags -> Int #
oFFSET_stgGCEnter1 :: DynFlags -> Int #
oFFSET_StgRegTable_rCCCS :: DynFlags -> Int #
oFFSET_StgRegTable_rHp :: DynFlags -> Int #
oFFSET_StgRegTable_rSp :: DynFlags -> Int #
oFFSET_StgRegTable_rL1 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM6 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM5 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM4 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM3 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM2 :: DynFlags -> Int #
oFFSET_StgRegTable_rZMM1 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM6 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM5 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM4 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM3 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM2 :: DynFlags -> Int #
oFFSET_StgRegTable_rYMM1 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM6 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM5 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM4 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM3 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM2 :: DynFlags -> Int #
oFFSET_StgRegTable_rXMM1 :: DynFlags -> Int #
oFFSET_StgRegTable_rD6 :: DynFlags -> Int #
oFFSET_StgRegTable_rD5 :: DynFlags -> Int #
oFFSET_StgRegTable_rD4 :: DynFlags -> Int #
oFFSET_StgRegTable_rD3 :: DynFlags -> Int #
oFFSET_StgRegTable_rD2 :: DynFlags -> Int #
oFFSET_StgRegTable_rD1 :: DynFlags -> Int #
oFFSET_StgRegTable_rF6 :: DynFlags -> Int #
oFFSET_StgRegTable_rF5 :: DynFlags -> Int #
oFFSET_StgRegTable_rF4 :: DynFlags -> Int #
oFFSET_StgRegTable_rF3 :: DynFlags -> Int #
oFFSET_StgRegTable_rF2 :: DynFlags -> Int #
oFFSET_StgRegTable_rF1 :: DynFlags -> Int #
oFFSET_StgRegTable_rR10 :: DynFlags -> Int #
oFFSET_StgRegTable_rR9 :: DynFlags -> Int #
oFFSET_StgRegTable_rR8 :: DynFlags -> Int #
oFFSET_StgRegTable_rR7 :: DynFlags -> Int #
oFFSET_StgRegTable_rR6 :: DynFlags -> Int #
oFFSET_StgRegTable_rR5 :: DynFlags -> Int #
oFFSET_StgRegTable_rR4 :: DynFlags -> Int #
oFFSET_StgRegTable_rR3 :: DynFlags -> Int #
oFFSET_StgRegTable_rR2 :: DynFlags -> Int #
oFFSET_StgRegTable_rR1 :: DynFlags -> Int #
tICKY_BIN_COUNT :: DynFlags -> Int #
bLOCKS_PER_MBLOCK :: DynFlags -> Int #
bLOCK_SIZE :: DynFlags -> Int #
pROF_HDR_SIZE :: DynFlags -> Int #
sTD_HDR_SIZE :: DynFlags -> Int #
cONTROL_GROUP_CONST_291 :: DynFlags -> Int #
compilerInfo :: DynFlags -> [(String, String)] #
setFlagsFromEnvFile :: FilePath -> String -> DynP () #
canonicalizeModuleIfHome :: DynFlags -> Module -> Module #
canonicalizeHomeModule :: DynFlags -> ModuleName -> Module #
Given a ModuleName
of a signature in the home library, find
out how it is instantiated. E.g., the canonical form of
A in p[A=q[]:A]
is q[]:A
.
unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags #
setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags #
dynamicGhc :: Bool #
rtsIsProfiled :: Bool #
Was the runtime system built with profiling enabled?
glasgowExtsFlags :: [Extension] #
warningHierarchies :: [[String]] #
Warning group hierarchies, where there is an explicit inclusion relation.
Each inner list is a hierarchy of warning groups, ordered from smallest to largest, where each group is a superset of the one before it.
Separating this from warningGroups
allows for multiple
hierarchies with no inherent relation to be defined.
The special-case Weverything group is not included.
warningGroups :: [(String, [WarningFlag])] #
Warning groups.
As all warnings are in the Weverything set, it is ignored when displaying to the user which group a warning is in.
fLangFlags :: [FlagSpec Extension] #
These -f<blah>
flags can all be reversed with -fno-<blah>
fFlags :: [FlagSpec GeneralFlag] #
These -f<blah>
flags can all be reversed with -fno-<blah>
wWarningFlags :: [FlagSpec WarningFlag] #
These -W<blah>
flags can all be reversed with -Wno-<blah>
flagsForCompletion :: Bool -> [String] #
Make a list of flags for shell completion. Filter all available flags into two groups, for interactive GHC vs all other.
flagsPackage :: [Flag (CmdLineP DynFlags)] #
flagsDynamic :: [Flag (CmdLineP DynFlags)] #
allNonDeprecatedFlags :: [String] #
All dynamic flags option strings without the deprecated ones. These are the user facing strings for enabling and disabling options.
updateWays :: DynFlags -> DynFlags #
putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO () #
Write an error or warning to the LogOutput
.
:: MonadIO m | |
=> [Flag (CmdLineP DynFlags)] | valid flags to match against |
-> Bool | are the arguments from the command line? |
-> DynFlags | current dynamic flags |
-> [Located String] | arguments to parse |
-> m (DynFlags, [Located String], [Warn]) |
Parses the dynamically set flags for GHC. This is the most general form of the dynamic flag parser that the other methods simply wrap. It allows saying which flags are valid flags and indicating if we are parsing arguments from the command line or from a file pragma.
:: MonadIO m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Warn]) | Updated |
Like parseDynamicFlagsCmdLine
but does not allow the package flags
(-package, -hide-package, -ignore-package, -hide-all-packages, -package-db).
Used to parse flags set in a modules pragma.
:: MonadIO m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Warn]) | Updated |
Parse dynamic flags from a list of command line arguments. Returns
the parsed DynFlags
, the left-over arguments, and a list of warnings.
Throws a UsageError
if errors occurred during parsing (such as unknown
flags or missing arguments).
updOptLevel :: Int -> DynFlags -> DynFlags #
Sets the DynFlags
to be appropriate to the optimisation level
addPluginModuleName :: String -> DynFlags -> DynFlags #
thisPackage :: DynFlags -> UnitId #
thisUnitIdInsts :: DynFlags -> [(ModuleName, Module)] #
thisComponentId :: DynFlags -> ComponentId #
getVerbFlags :: DynFlags -> [String] #
Gets the verbosity flag for the current verbosity level. This is fed to
other tools, so GHC-specific verbosity flags like -ddump-most
are not included
:: DynFlags |
|
-> (DynFlags -> [a]) | Relevant record accessor: one of the |
-> [a] | Correctly ordered extracted options |
Retrieve the options corresponding to a particular opt_*
field in the correct order
unsafeFlagsForInfer :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)] #
A list of unsafe flags under Safe Haskell. Tuple elements are: * name of the flag * function to get srcspan that enabled the flag * function to test if the flag is on * function to turn the flag off
unsafeFlags :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)] #
A list of unsafe flags under Safe Haskell. Tuple elements are: * name of the flag * function to get srcspan that enabled the flag * function to test if the flag is on * function to turn the flag off
safeImplicitImpsReq :: DynFlags -> Bool #
Are all implicit imports required to be safe for this Safe Haskell mode? Implicit imports are things in the prelude. e.g System.IO when print is used.
safeDirectImpsReq :: DynFlags -> Bool #
Are all direct imports required to be safe for this Safe Haskell mode? Direct imports are when the code explicitly imports a module
safeImportsOn :: DynFlags -> Bool #
Test if Safe Imports are on in some form
safeInferOn :: DynFlags -> Bool #
Is the Safe Haskell safe inference mode active
safeLanguageOn :: DynFlags -> Bool #
Is the Safe Haskell safe language in use
safeHaskellModeEnabled :: DynFlags -> Bool #
safeHaskellOn :: DynFlags -> Bool #
Is Safe Haskell on in some way (including inference mode)
packageTrustOn :: DynFlags -> Bool #
Is the -fpackage-trust mode on
dynFlagDependencies :: DynFlags -> [ModuleName] #
Some modules have dependencies on others through the DynFlags rather than textual imports
xopt_set_unlessExplSpec :: Extension -> (DynFlags -> Extension -> DynFlags) -> DynFlags -> DynFlags #
Set or unset a Extension
, unless it has been explicitly
set or unset before.
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags #
Mark a WarningFlag
as not fatal
wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags #
Mark a WarningFlag
as fatal (do not set the flag)
wopt_fatal :: WarningFlag -> DynFlags -> Bool #
Test whether a WarningFlag
is set as fatal
wopt_unset :: DynFlags -> WarningFlag -> DynFlags #
Unset a WarningFlag
wopt_set :: DynFlags -> WarningFlag -> DynFlags #
Set a WarningFlag
wopt :: WarningFlag -> DynFlags -> Bool #
Test whether a WarningFlag
is set
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags #
Unset a GeneralFlag
gopt_set :: DynFlags -> GeneralFlag -> DynFlags #
Set a GeneralFlag
gopt :: GeneralFlag -> DynFlags -> Bool #
Test whether a GeneralFlag
is set
hasNoOptCoercion :: DynFlags -> Bool #
hasNoStateHack :: DynFlags -> Bool #
languageExtensions :: Maybe Language -> [Extension] #
The language extensions implied by the various language variants.
When updating this be sure to update the flag documentation in
docsusers-guideglasgow_exts.rst
.
defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO () #
Like defaultLogActionHPutStrDoc
but appends an extra newline.
interpreterDynamic :: DynFlags -> Bool #
interpreterProfiled :: DynFlags -> Bool #
interpWays :: [Way] #
defaultWays :: Settings -> [Way] #
defaultDynFlags :: Settings -> LlvmConfig -> DynFlags #
initDynFlags :: DynFlags -> IO DynFlags #
dynamicOutputFile :: DynFlags -> FilePath -> FilePath #
Compute the path of the dynamic object corresponding to an object file.
whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m () #
ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a #
whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m () #
wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] #
wayGeneralFlags :: Platform -> Way -> [GeneralFlag] #
wayRTSOnly :: Way -> Bool #
mkBuildTag :: [Way] -> String #
positionIndependent :: DynFlags -> Bool #
Are we building with -fPIE
or -fPIC
enabled?
packageFlagsChanged :: DynFlags -> DynFlags -> Bool #
targetRetainsAllBindings :: HscTarget -> Bool #
Does this target retain *all* top-level bindings for a module, rather than just the exported bindings, in the TypeEnv and compiled code (if any)? In interpreted mode we do this, so that GHCi can call functions inside a module. In HscNothing mode we also do it, so that Haddock can get access to the GlobalRdrEnv for a module after typechecking it.
isObjectTarget :: HscTarget -> Bool #
Will this target result in an object file on the disk?
versionedFilePath :: DynFlags -> FilePath #
versionedAppDir :: DynFlags -> MaybeT IO FilePath #
The directory for this version of ghc in the user's app directory
(typically something like ~.ghcx86_64-linux-7.6.3
)
tablesNextToCode :: DynFlags -> Bool #
opt_windres :: DynFlags -> [String] #
opt_P_signature :: DynFlags -> ([String], Fingerprint) #
pgm_ranlib :: DynFlags -> String #
pgm_libtool :: DynFlags -> String #
pgm_windres :: DynFlags -> String #
systemPackageConfig :: DynFlags -> FilePath #
extraGccViaCFlags :: DynFlags -> [String] #
ghciUsagePath :: DynFlags -> FilePath #
ghcUsagePath :: DynFlags -> FilePath #
projectVersion :: DynFlags -> String #
programName :: DynFlags -> String #
backendMaintainsCfg :: DynFlags -> Bool #
flattenIncludes :: IncludeSpecs -> [String] #
Concatenate and flatten the list of global and quoted includes returning just a flat list of paths.
addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs #
Append to the list of includes a path that shall be included using `-iquote` when the C compiler is called. These paths only apply when quoted includes are used. e.g. #include "foo.h"
addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs #
Append to the list of includes a path that shall be included using `-I` when the C compiler is called. These paths override system search paths.
data WarnReason #
Used when outputting warnings: if a reason is given, it is displayed. If a warning isn't controlled by a flag, this is made explicit at the point of use.
NoReason | |
Reason !WarningFlag | Warning was enabled with the flag |
ErrReason !(Maybe WarningFlag) | Warning was made an error because of -Werror or -Werror=WarningFlag |
Instances
Show WarnReason | |
Defined in DynFlags showsPrec :: Int -> WarnReason -> ShowS # show :: WarnReason -> String # showList :: [WarnReason] -> ShowS # | |
ToJson WarnReason | |
Defined in DynFlags json :: WarnReason -> JsonDoc # | |
Outputable WarnReason | |
Defined in DynFlags ppr :: WarnReason -> SDoc # pprPrec :: Rational -> WarnReason -> SDoc # |
data IncludeSpecs #
Used to differentiate the scope an include needs to apply to. We have to split the include paths to avoid accidentally forcing recursive includes since -I overrides the system search paths. See #14312.
Instances
Show IncludeSpecs | |
Defined in DynFlags showsPrec :: Int -> IncludeSpecs -> ShowS # show :: IncludeSpecs -> String # showList :: [IncludeSpecs] -> ShowS # |
data WarningFlag #
Instances
Enum WarningFlag | |
Defined in DynFlags succ :: WarningFlag -> WarningFlag # pred :: WarningFlag -> WarningFlag # toEnum :: Int -> WarningFlag # fromEnum :: WarningFlag -> Int # enumFrom :: WarningFlag -> [WarningFlag] # enumFromThen :: WarningFlag -> WarningFlag -> [WarningFlag] # enumFromTo :: WarningFlag -> WarningFlag -> [WarningFlag] # enumFromThenTo :: WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag] # | |
Eq WarningFlag | |
Defined in DynFlags (==) :: WarningFlag -> WarningFlag -> Bool # (/=) :: WarningFlag -> WarningFlag -> Bool # | |
Show WarningFlag | |
Defined in DynFlags showsPrec :: Int -> WarningFlag -> ShowS # show :: WarningFlag -> String # showList :: [WarningFlag] -> ShowS # |
Instances
Enum Language | |
Eq Language | |
Show Language | |
Outputable Language | |
data SafeHaskellMode #
The various Safe Haskell modes
Sf_None | inferred unsafe |
Sf_Unsafe | declared and checked |
Sf_Trustworthy | declared and checked |
Sf_Safe | declared and checked |
Sf_SafeInferred | inferred as safe |
Sf_Ignore |
|
Instances
Eq SafeHaskellMode | |
Defined in DynFlags (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
Show SafeHaskellMode | |
Defined in DynFlags showsPrec :: Int -> SafeHaskellMode -> ShowS # show :: SafeHaskellMode -> String # showList :: [SafeHaskellMode] -> ShowS # | |
NFData SafeHaskellMode Source # | |
Defined in Development.IDE.GHC.Orphans rnf :: SafeHaskellMode -> () # | |
Outputable SafeHaskellMode | |
Defined in DynFlags ppr :: SafeHaskellMode -> SDoc # pprPrec :: Rational -> SafeHaskellMode -> SDoc # |
data CfgWeights #
Edge weights to use when generating a CFG from CMM
CFGWeights | |
|
class HasDynFlags (m :: Type -> Type) where #
getDynFlags :: m DynFlags #
Instances
HasDynFlags Ghc | |
Defined in GhcMonad getDynFlags :: Ghc DynFlags # | |
HasDynFlags CompPipeline | |
Defined in PipelineMonad | |
HasDynFlags Hsc | |
Defined in HscTypes getDynFlags :: Hsc DynFlags # | |
HasDynFlags LlvmM | |
Defined in LlvmCodeGen.Base | |
HasDynFlags CoreM | |
Defined in CoreMonad | |
(Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) | |
Defined in DynFlags getDynFlags :: MaybeT m DynFlags # | |
MonadIO m => HasDynFlags (GhcT m) | |
Defined in GhcMonad getDynFlags :: GhcT m DynFlags # | |
ContainsDynFlags env => HasDynFlags (IOEnv env) | |
Defined in IOEnv getDynFlags :: IOEnv env DynFlags # | |
(Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) | |
Defined in DynFlags getDynFlags :: WriterT a m DynFlags # | |
(Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) | |
Defined in DynFlags getDynFlags :: ReaderT a m DynFlags # | |
(Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) | |
Defined in DynFlags getDynFlags :: ExceptT e m DynFlags # |
class ContainsDynFlags t where #
extractDynFlags :: t -> DynFlags #
Instances
ContainsDynFlags (Env gbl lcl) | |
Defined in TcRnTypes extractDynFlags :: Env gbl lcl -> DynFlags # |
NoProfAuto | no SCC annotations added |
ProfAutoAll | top-level and nested functions are annotated |
ProfAutoTop | top-level functions annotated only |
ProfAutoExports | exported functions annotated only |
ProfAutoCalls | annotate call-sites |
Instances
Enum ProfAuto | |
Eq ProfAuto | |
data LlvmTarget #
LlvmTarget | |
|
data LlvmConfig #
See Note [LLVM Configuration] in SysTools.
LlvmConfig | |
|
The target code type of the compilation (if any).
Whenever you change the target, also make sure to set ghcLink
to
something sensible.
HscNothing
can be used to avoid generating any output, however, note
that:
- If a program uses Template Haskell the typechecker may need to run code from an imported module. To facilitate this, code generation is enabled for modules imported by modules that use template haskell. See Note [-fno-code mode].
HscC | Generate C code. |
HscAsm | Generate assembly using the native code generator. |
HscLlvm | Generate assembly using the llvm code generator. |
HscInterpreted | Generate bytecode. (Requires |
HscNothing | Don't generate any code. See notes above. |
The GhcMode
tells us whether we're doing multi-module
compilation (controlled via the GHC API) or one-shot
(single-module) compilation. This makes a difference primarily to
the Finder: in one-shot mode we look for interface files for
imported modules, but in multi-module mode we look for source files
in order to check whether they need to be recompiled.
CompManager |
|
OneShot | ghc -c Foo.hs |
MkDepend |
|
What to do in the link step, if there is one.
NoLink | Don't link at all |
LinkBinary | Link object code into a binary |
LinkInMemory | Use the in-memory dynamic linker (works for both bytecode and object code). |
LinkDynLib | Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms) |
LinkStaticLib | Link objects into a static lib |
data PackageArg #
We accept flags which make packages visible, but how they select the package varies; this data type reflects what selection criterion is used.
PackageArg String |
|
UnitIdArg UnitId |
|
Instances
Eq PackageArg | |
Defined in DynFlags (==) :: PackageArg -> PackageArg -> Bool # (/=) :: PackageArg -> PackageArg -> Bool # | |
Show PackageArg | |
Defined in DynFlags showsPrec :: Int -> PackageArg -> ShowS # show :: PackageArg -> String # showList :: [PackageArg] -> ShowS # | |
Outputable PackageArg | |
Defined in DynFlags ppr :: PackageArg -> SDoc # pprPrec :: Rational -> PackageArg -> SDoc # |
data ModRenaming #
Represents the renaming that may be associated with an exposed
package, e.g. the rns
part of -package "foo (rns)"
.
Here are some example parsings of the package flags (where
a string literal is punned to be a ModuleName
:
ModRenaming | |
|
Instances
Eq ModRenaming | |
Defined in DynFlags (==) :: ModRenaming -> ModRenaming -> Bool # (/=) :: ModRenaming -> ModRenaming -> Bool # | |
Outputable ModRenaming | |
Defined in DynFlags ppr :: ModRenaming -> SDoc # pprPrec :: Rational -> ModRenaming -> SDoc # |
newtype IgnorePackageFlag #
Flags for manipulating the set of non-broken packages.
IgnorePackage String | -ignore-package |
Instances
Eq IgnorePackageFlag | |
Defined in DynFlags (==) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # (/=) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # |
Flags for manipulating package trust.
TrustPackage String | -trust |
DistrustPackage String | -distrust |
data PackageFlag #
Flags for manipulating packages visibility.
HidePackage String | -hide-package |
Instances
Eq PackageFlag | |
Defined in DynFlags (==) :: PackageFlag -> PackageFlag -> Bool # (/=) :: PackageFlag -> PackageFlag -> Bool # | |
Show PackageFlag Source # | |
Defined in Development.IDE.GHC.Orphans showsPrec :: Int -> PackageFlag -> ShowS # show :: PackageFlag -> String # showList :: [PackageFlag] -> ShowS # | |
Outputable PackageFlag | |
Defined in DynFlags ppr :: PackageFlag -> SDoc # pprPrec :: Rational -> PackageFlag -> SDoc # |
data PackageDBFlag #
Instances
Eq PackageDBFlag | |
Defined in DynFlags (==) :: PackageDBFlag -> PackageDBFlag -> Bool # (/=) :: PackageDBFlag -> PackageDBFlag -> Bool # |
data DynLibLoader #
Instances
Eq DynLibLoader | |
Defined in DynFlags (==) :: DynLibLoader -> DynLibLoader -> Bool # (/=) :: DynLibLoader -> DynLibLoader -> Bool # |
data RtsOptsEnabled #
Instances
Show RtsOptsEnabled | |
Defined in DynFlags showsPrec :: Int -> RtsOptsEnabled -> ShowS # show :: RtsOptsEnabled -> String # showList :: [RtsOptsEnabled] -> ShowS # |
type FatalMessager = String -> IO () #
FlagSpec | |
|
data PkgConfRef #
Instances
Eq PkgConfRef | |
Defined in DynFlags (==) :: PkgConfRef -> PkgConfRef -> Bool # (/=) :: PkgConfRef -> PkgConfRef -> Bool # |
data LinkerInfo #
GnuLD [Option] | |
GnuGold [Option] | |
LlvmLLD [Option] | |
DarwinLD [Option] | |
SolarisLD [Option] | |
AixLD [Option] | |
UnknownLD |
Instances
Eq LinkerInfo | |
Defined in DynFlags (==) :: LinkerInfo -> LinkerInfo -> Bool # (/=) :: LinkerInfo -> LinkerInfo -> Bool # |
data CompilerInfo #
Instances
Eq CompilerInfo | |
Defined in DynFlags (==) :: CompilerInfo -> CompilerInfo -> Bool # (/=) :: CompilerInfo -> CompilerInfo -> Bool # |
data FilesToClean #
A collection of files that must be deleted before ghc exits.
The current collection
is stored in an IORef in DynFlags, filesToClean
.
FilesToClean | |
|
sGhcRtsWithLibdw :: Settings -> Bool #
sGhcDebugged :: Settings -> Bool #
sGhcThreaded :: Settings -> Bool #
sLeadingUnderscore :: Settings -> Bool #
sTablesNextToCode :: Settings -> Bool #
sGhcRTSWays :: Settings -> String #
sGhcWithSMP :: Settings -> Bool #
sGhcWithNativeCodeGen :: Settings -> Bool #
sGhcWithInterpreter :: Settings -> Bool #
sIntegerLibrary :: Settings -> String #
sTargetPlatformString :: Settings -> String #
sExtraGccViaCFlags :: Settings -> [String] #
sOpt_windres :: Settings -> [String] #
sPgm_ranlib :: Settings -> String #
sPgm_libtool :: Settings -> String #
sPgm_windres :: Settings -> String #
sGccSupportsNoPie :: Settings -> Bool #
sLdIsGnuLd :: Settings -> Bool #
sLdSupportsFilelist :: Settings -> Bool #
sLdSupportsBuildId :: Settings -> Bool #
sGhciUsagePath :: Settings -> FilePath #
sGhcUsagePath :: Settings -> FilePath #
sProjectVersion :: Settings -> String #
sProgramName :: Settings -> String #
data PlatformConstants #
Instances
Read PlatformConstants | |
Defined in PlatformConstants |
When invoking external tools as part of the compilation pipeline, we pass these a sequence of options on the command-line. Rather than just using a list of Strings, we use a type that allows us to distinguish between filepaths and 'other stuff'. The reason for this is that this type gives us a handle on transforming filenames, and filenames only, to whatever format they're expected to be on a particular platform.
useUnicodeSyntax :: DynFlags -> Bool #
An internal helper to check whether to use unicode syntax for output.
Note: You should very likely be using unicodeSyntax
instead
of this function.
useStarIsType :: DynFlags -> Bool #
shouldUseColor :: DynFlags -> Bool #
hasPprDebug :: DynFlags -> Bool #
hasNoDebugOutput :: DynFlags -> Bool #
Contains not only a collection of GeneralFlag
s but also a plethora of
information relating to the compilation of a single file or GHC session
DynFlags | |
|
Instances
Enum DumpFlag | |
Eq DumpFlag | |
Show DumpFlag | |
data GeneralFlag #
Enumerates the simple on-or-off dynamic flags
Instances
Enum GeneralFlag | |
Defined in DynFlags succ :: GeneralFlag -> GeneralFlag # pred :: GeneralFlag -> GeneralFlag # toEnum :: Int -> GeneralFlag # fromEnum :: GeneralFlag -> Int # enumFrom :: GeneralFlag -> [GeneralFlag] # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] # | |
Eq GeneralFlag | |
Defined in DynFlags (==) :: GeneralFlag -> GeneralFlag -> Bool # (/=) :: GeneralFlag -> GeneralFlag -> Bool # | |
Show GeneralFlag | |
Defined in DynFlags showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # |
data FileSettings #
Paths to various files and directories used by GHC, including those that provide more settings.
data GhcNameVersion #
Settings for what GHC this is.
data IntegerLibrary #
Instances
Eq IntegerLibrary | |
Defined in GHC.Platform (==) :: IntegerLibrary -> IntegerLibrary -> Bool # (/=) :: IntegerLibrary -> IntegerLibrary -> Bool # | |
Read IntegerLibrary | |
Defined in GHC.Platform readsPrec :: Int -> ReadS IntegerLibrary # readList :: ReadS [IntegerLibrary] # | |
Show IntegerLibrary | |
Defined in GHC.Platform showsPrec :: Int -> IntegerLibrary -> ShowS # show :: IntegerLibrary -> String # showList :: [IntegerLibrary] -> ShowS # |
data PlatformMisc #
Platform-specific settings formerly hard-coded in Config.hs.
These should probably be all be triaged whether they can be computed from
other settings or belong in another another place (like Platform
above).
PlatformMisc | |
|
initializePlugins :: HscEnv -> DynFlags -> IO DynFlags #
Loads the plugins specified in the pluginModNames field of the dynamic flags. Should be called after command line arguments are parsed, but before actual compilation starts. Idempotent operation. Should be re-called if pluginModNames or pluginModNameOpts changes.
applyPluginsParsedResultAction :: HscEnv -> DynFlags -> ModSummary -> ApiAnns -> ParsedSource -> IO ParsedSource Source #
module Compat.HieTypes
module Compat.HieUtils