Safe Haskell | None |
---|---|
Language | Haskell2010 |
Development.IDE.GHC.Compat.Core
Contents
- Session
- Linear Haskell
- Interface Files
- Fixity
- ModSummary
- HomeModInfo
- ModGuts
- ModDetails
- HsExpr,
- Var
- Specs
- SourceText
- Name
- Ways
- AvailInfo
- TcGblEnv
- Parsing and LExer types
- Compilation Main
- Typecheck utils
- Source Locations
- Finder
- Module and Package
- Linker
- Hooks
- HPT
- Driver-Make
- GHCi
- ModLocation
- DataCon
- Role
- Panic
- Other
- Util Module re-exports
- Syntax re-exports
Description
Compat Core module that handles the GHC module hierarchy re-organisation by re-exporting everything we care about.
This module provides no other compat mechanisms, except for simple backward-compatible pattern synonyms.
Synopsis
- data DynFlags
- extensions :: DynFlags -> [OnOff Extension]
- extensionFlags :: DynFlags -> EnumSet Extension
- targetPlatform :: DynFlags -> Platform
- packageFlags :: DynFlags -> [PackageFlag]
- generalFlags :: DynFlags -> EnumSet GeneralFlag
- warningFlags :: DynFlags -> EnumSet WarningFlag
- topDir :: DynFlags -> FilePath
- hiDir :: DynFlags -> Maybe String
- tmpDir :: DynFlags -> String
- importPaths :: DynFlags -> [FilePath]
- useColor :: DynFlags -> OverridingBool
- canUseColor :: DynFlags -> Bool
- useUnicode :: DynFlags -> Bool
- objectDir :: DynFlags -> Maybe String
- flagsForCompletion :: Bool -> [String]
- setImportPaths :: [FilePath] -> DynFlags -> DynFlags
- outputFile :: DynFlags -> Maybe String
- pluginModNames :: DynFlags -> [ModuleName]
- refLevelHoleFits :: DynFlags -> Maybe Int
- maxRefHoleFits :: DynFlags -> Maybe Int
- maxValidHoleFits :: DynFlags -> Maybe Int
- setOutputFile :: FilePath -> DynFlags -> DynFlags
- type CommandLineOption = String
- staticPlugins :: DynFlags -> [StaticPlugin]
- sPgm_F :: Settings -> String
- settings :: DynFlags -> Settings
- gopt :: GeneralFlag -> DynFlags -> Bool
- gopt_set :: DynFlags -> GeneralFlag -> DynFlags
- gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
- wopt :: WarningFlag -> DynFlags -> Bool
- wopt_set :: DynFlags -> WarningFlag -> DynFlags
- xFlags :: [FlagSpec Extension]
- xopt :: Extension -> DynFlags -> Bool
- xopt_unset :: DynFlags -> Extension -> DynFlags
- xopt_set :: DynFlags -> Extension -> DynFlags
- data FlagSpec flag = FlagSpec {
- flagSpecName :: String
- flagSpecFlag :: flag
- flagSpecAction :: TurnOnFlag -> DynP ()
- flagSpecGhcMode :: GhcFlagMode
- 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 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 PackageFlag
- data PackageArg
- data ModRenaming = ModRenaming {}
- pattern ExposePackage :: String -> PackageArg -> ModRenaming -> PackageFlag
- parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- data WarnReason
- = NoReason
- | Reason !WarningFlag
- | ErrReason !(Maybe WarningFlag)
- wWarningFlags :: [FlagSpec WarningFlag]
- updOptLevel :: Int -> DynFlags -> DynFlags
- setUnsafeGlobalDynFlags :: DynFlags -> IO ()
- type Scaled a = a
- unrestricted :: a -> Scaled a
- scaledThing :: Scaled a -> a
- type IfaceExport = AvailInfo
- data IfaceTyCon = IfaceTyCon {}
- 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 HscSource
- data WhereFrom
- loadInterface :: SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr MsgDoc ModIface)
- data SourceModified
- loadModuleInterface :: SDoc -> Module -> TcM ModIface
- data RecompileRequired
- mkPartialIface :: HscEnv -> ModDetails -> ModGuts -> PartialModIface
- mkFullIface :: HscEnv -> PartialModIface -> IO ModIface
- checkOldIface :: HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> IO (RecompileRequired, Maybe ModIface)
- pattern IsBoot :: IsBootInterface
- pattern NotBoot :: IsBootInterface
- data LexicalFixity
- 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 HomeModInfo = HomeModInfo {
- hm_iface :: !ModIface
- hm_details :: !ModDetails
- hm_linkable :: !(Maybe Linkable)
- data ModGuts = ModGuts {
- mg_module :: !Module
- mg_hsc_src :: HscSource
- mg_loc :: SrcSpan
- mg_exports :: ![AvailInfo]
- mg_deps :: !Dependencies
- mg_usages :: ![Usage]
- mg_used_th :: !Bool
- mg_rdr_env :: !GlobalRdrEnv
- mg_fix_env :: !FixityEnv
- mg_tcs :: ![TyCon]
- mg_insts :: ![ClsInst]
- mg_fam_insts :: ![FamInst]
- mg_patsyns :: ![PatSyn]
- mg_rules :: ![CoreRule]
- mg_binds :: !CoreProgram
- mg_foreign :: !ForeignStubs
- mg_foreign_files :: ![(ForeignSrcLang, FilePath)]
- mg_warns :: !Warnings
- mg_anns :: [Annotation]
- mg_complete_sigs :: [CompleteMatch]
- mg_hpc_info :: !HpcInfo
- mg_modBreaks :: !(Maybe ModBreaks)
- mg_inst_env :: InstEnv
- mg_fam_inst_env :: FamInstEnv
- mg_safe_haskell :: SafeHaskellMode
- mg_trust_pkg :: Bool
- mg_doc_hdr :: !(Maybe HsDocString)
- mg_decl_docs :: !DeclDocMap
- mg_arg_docs :: !ArgDocMap
- data CgGuts = CgGuts {
- cg_module :: !Module
- cg_tycons :: [TyCon]
- cg_binds :: CoreProgram
- cg_foreign :: !ForeignStubs
- cg_foreign_files :: ![(ForeignSrcLang, FilePath)]
- cg_dep_pkgs :: ![InstalledUnitId]
- cg_hpc_info :: !HpcInfo
- cg_modBreaks :: !(Maybe ModBreaks)
- cg_spt_entries :: [SptEntry]
- data ModDetails = ModDetails {
- md_exports :: [AvailInfo]
- md_types :: !TypeEnv
- md_insts :: ![ClsInst]
- md_fam_insts :: ![FamInst]
- md_rules :: ![CoreRule]
- md_anns :: ![Annotation]
- md_complete_sigs :: [CompleteMatch]
- pattern HsLet :: XLet p -> SrcSpanLess (LHsLocalBinds p) -> LHsExpr p -> HsExpr p
- pattern LetStmt :: XLetStmt idL idR body -> SrcSpanLess (LHsLocalBindsLR idL idR) -> StmtLR idL idR body
- data Type
- pattern FunTy :: Type -> Type -> Type
- pattern ConPatIn :: Located (IdP p) -> HsConPatDetails p -> Pat p
- splitForAllTyCoVars :: Type -> ([TyCoVar], Type)
- mkVisFunTys :: [Scaled Type] -> Type -> Type
- mkInfForAllTys :: [TyVar] -> Type -> Type
- data ImpDeclSpec = ImpDeclSpec {
- is_mod :: ModuleName
- is_as :: ModuleName
- is_qual :: Bool
- is_dloc :: SrcSpan
- data ImportSpec = ImpSpec {}
- data SourceText
- rationalFromFractionalLit :: FractionalLit -> Rational
- tyThingParent_maybe :: TyThing -> Maybe TyThing
- data Way
- wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
- data AvailInfo
- pattern AvailName :: Name -> AvailInfo
- pattern AvailFL :: FieldLabel -> AvailInfo
- pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> AvailInfo
- availName :: AvailInfo -> Name
- availNames :: AvailInfo -> [Name]
- availNamesWithSelectors :: AvailInfo -> [Name]
- availsToNameSet :: [AvailInfo] -> NameSet
- data TcGblEnv = TcGblEnv {
- tcg_mod :: Module
- tcg_semantic_mod :: Module
- tcg_src :: HscSource
- tcg_rdr_env :: GlobalRdrEnv
- tcg_default :: Maybe [Type]
- tcg_fix_env :: FixityEnv
- tcg_field_env :: RecFieldEnv
- tcg_type_env :: TypeEnv
- tcg_type_env_var :: TcRef TypeEnv
- tcg_inst_env :: !InstEnv
- tcg_fam_inst_env :: !FamInstEnv
- tcg_ann_env :: AnnEnv
- tcg_exports :: [AvailInfo]
- tcg_imports :: ImportAvails
- tcg_dus :: DefUses
- tcg_used_gres :: TcRef [GlobalRdrElt]
- tcg_keep :: TcRef NameSet
- tcg_th_used :: TcRef Bool
- tcg_th_splice_used :: TcRef Bool
- tcg_th_top_level_locs :: TcRef (Set RealSrcSpan)
- tcg_dfun_n :: TcRef OccSet
- tcg_merged :: [(Module, Fingerprint)]
- tcg_rn_exports :: Maybe [(Located (IE GhcRn), Avails)]
- tcg_rn_imports :: [LImportDecl GhcRn]
- tcg_rn_decls :: Maybe (HsGroup GhcRn)
- tcg_dependent_files :: TcRef [FilePath]
- tcg_th_topdecls :: TcRef [LHsDecl GhcPs]
- tcg_th_foreign_files :: TcRef [(ForeignSrcLang, FilePath)]
- tcg_th_topnames :: TcRef NameSet
- tcg_th_modfinalizers :: TcRef [(TcLclEnv, ThModFinalizers)]
- tcg_th_coreplugins :: TcRef [String]
- tcg_th_state :: TcRef (Map TypeRep Dynamic)
- tcg_th_remote_state :: TcRef (Maybe (ForeignRef (IORef QState)))
- tcg_ev_binds :: Bag EvBind
- tcg_tr_module :: Maybe Id
- tcg_binds :: LHsBinds GhcTc
- tcg_sigs :: NameSet
- tcg_imp_specs :: [LTcSpecPrag]
- tcg_warns :: Warnings
- tcg_anns :: [Annotation]
- tcg_tcs :: [TyCon]
- tcg_insts :: [ClsInst]
- tcg_fam_insts :: [FamInst]
- tcg_rules :: [LRuleDecl GhcTc]
- tcg_fords :: [LForeignDecl GhcTc]
- tcg_patsyns :: [PatSyn]
- tcg_doc_hdr :: Maybe LHsDocString
- tcg_hpc :: !AnyHpcUsage
- tcg_self_boot :: SelfBootInfo
- tcg_main :: Maybe Name
- tcg_safeInfer :: TcRef (Bool, WarningMessages)
- tcg_tc_plugins :: [TcPluginSolver]
- tcg_hf_plugins :: [HoleFitPlugin]
- tcg_top_loc :: RealSrcSpan
- tcg_static_wc :: TcRef WantedConstraints
- tcg_complete_matches :: [CompleteMatch]
- tcg_cc_st :: TcRef CostCentreState
- 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
- type ParsedSource = Located (HsModule GhcPs)
- type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString)
- data HscEnv
- runGhc :: Maybe FilePath -> Ghc a -> IO a
- unGhc :: Ghc a -> Session -> IO a
- data Session = Session !(IORef HscEnv)
- modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()
- getSession :: GhcMonad m => m HscEnv
- setSessionDynFlags :: GhcMonad m => DynFlags -> m [InstalledUnitId]
- getSessionDynFlags :: GhcMonad m => m DynFlags
- class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type)
- data Ghc a
- runHsc :: HscEnv -> Hsc a -> IO a
- compileFile :: HscEnv -> Phase -> (FilePath, Maybe Phase) -> IO FilePath
- data Phase
- hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts
- hscGenHardCode :: HscEnv -> CgGuts -> ModLocation -> FilePath -> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)])
- hscInteractive :: HscEnv -> CgGuts -> ModLocation -> IO (Maybe FilePath, CompiledByteCode, [SptEntry])
- hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts
- hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff)
- makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
- tcSplitForAllTyVars :: Type -> ([TyVar], Type)
- tcSplitForAllTyVarBinder_maybe :: Type -> Maybe (TyVarBinder, Type)
- typecheckIface :: ModIface -> IfG ModDetails
- mkIfaceTc :: HscEnv -> SafeHaskellMode -> ModDetails -> TcGblEnv -> IO ModIface
- data ImportedModsVal = ImportedModsVal {}
- importedByUser :: [ImportedBy] -> [ImportedModsVal]
- type TypecheckedSource = LHsBinds GhcTc
- type HasSrcSpan = HasSrcSpan
- type Located = GenLocated SrcSpan
- unLoc :: HasSrcSpan a => a -> SrcSpanLess a
- getLoc :: HasSrcSpan a => a -> SrcSpan
- getLocA :: HasSrcSpan a => a -> SrcSpan
- locA :: a -> a
- noLocA :: a -> LocatedAn an a
- type LocatedAn a = Located
- type AnnListItem = SrcSpan
- type NameAnn = SrcSpan
- type RealLocated = GenLocated RealSrcSpan
- data GenLocated l e = L l e
- data SrcSpan = UnhelpfulSpan !FastString
- data RealSrcSpan
- pattern RealSrcSpan :: RealSrcSpan -> Maybe BufSpan -> SrcSpan
- data RealSrcLoc
- pattern RealSrcLoc :: RealSrcLoc -> Maybe BufPos -> SrcLoc
- data SrcLoc = UnhelpfulLoc FastString
- type BufSpan = ()
- leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering
- containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool
- mkGeneralSrcSpan :: FastString -> SrcSpan
- mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan
- mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc
- getRealSrcSpan :: RealLocated a -> RealSrcSpan
- realSrcLocSpan :: RealSrcLoc -> RealSrcSpan
- realSrcSpanStart :: RealSrcSpan -> RealSrcLoc
- realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc
- isSubspanOfA :: LocatedAn la a -> LocatedAn lb b -> Bool
- isSubspanOf :: SrcSpan -> SrcSpan -> Bool
- wiredInSrcSpan :: SrcSpan
- mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan
- srcSpanStart :: SrcSpan -> SrcLoc
- srcSpanStartLine :: RealSrcSpan -> Int
- srcSpanStartCol :: RealSrcSpan -> Int
- srcSpanEnd :: SrcSpan -> SrcLoc
- srcSpanEndLine :: RealSrcSpan -> Int
- srcSpanEndCol :: RealSrcSpan -> Int
- srcSpanFile :: RealSrcSpan -> FastString
- srcLocCol :: RealSrcLoc -> Int
- srcLocFile :: RealSrcLoc -> FastString
- srcLocLine :: RealSrcLoc -> Int
- noSrcSpan :: SrcSpan
- noSrcLoc :: SrcLoc
- noLoc :: HasSrcSpan a => SrcSpanLess a -> a
- data FindResult
- = Found ModLocation Module
- | NoPackage UnitId
- | FoundMultiple [(Module, ModuleOrigin)]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe UnitId
- fr_mods_hidden :: [UnitId]
- fr_pkgs_hidden :: [UnitId]
- fr_unusables :: [(UnitId, UnusablePackageReason)]
- fr_suggestions :: [ModuleSuggestion]
- mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
- addBootSuffixLocnOut :: ModLocation -> ModLocation
- findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
- data InstalledFindResult
- data ModuleOrigin
- newtype PackageName = PackageName FastString
- data Unlinked
- data Linkable = LM {}
- unload :: HscEnv -> [Linkable] -> IO ()
- initDynLinker :: HscEnv -> IO ()
- data Hooks
- runMetaHook :: Hooks -> Maybe (MetaHook TcM)
- type MetaHook (f :: Type -> Type) = MetaRequest -> LHsExpr GhcTc -> f MetaResult
- data MetaRequest
- = MetaE (LHsExpr GhcPs -> MetaResult)
- | MetaP (LPat GhcPs -> MetaResult)
- | MetaT (LHsType GhcPs -> MetaResult)
- | MetaD ([LHsDecl GhcPs] -> MetaResult)
- | MetaAW (Serialized -> MetaResult)
- metaRequestE :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsExpr GhcPs)
- metaRequestP :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LPat GhcPs)
- metaRequestT :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsType GhcPs)
- metaRequestD :: Functor f => MetaHook f -> LHsExpr GhcTc -> f [LHsDecl GhcPs]
- metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized
- addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
- addListToHpt :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
- data Target = Target {}
- data TargetId
- mkModuleGraph :: [ModSummary] -> ModuleGraph
- initObjLinker :: HscEnv -> IO ()
- loadDLL :: HscEnv -> String -> IO (Maybe String)
- data InteractiveImport
- getContext :: GhcMonad m => m [InteractiveImport]
- setContext :: GhcMonad m => [InteractiveImport] -> m ()
- parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs)
- runDecls :: GhcMonad m => String -> m [Name]
- data Warn = Warn {}
- data ModLocation
- pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> ModLocation
- ml_hs_file :: ModLocation -> Maybe FilePath
- ml_obj_file :: ModLocation -> FilePath
- ml_hi_file :: ModLocation -> FilePath
- ml_hie_file :: ModLocation -> FilePath
- dataConExTyCoVars :: DataCon -> [TyCoVar]
- data Role
- type PlainGhcException = PlainGhcException
- panic :: String -> a
- data CoreModule = CoreModule {
- cm_module :: !Module
- cm_types :: !TypeEnv
- cm_binds :: CoreProgram
- cm_safe :: SafeHaskellMode
- data SafeHaskellMode
- pattern GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt
- gre_name :: GlobalRdrElt -> Name
- gre_imp :: GlobalRdrElt -> [ImportSpec]
- gre_lcl :: GlobalRdrElt -> Bool
- gre_par :: GlobalRdrElt -> Parent
- isKindLevel :: TypeOrKind -> Bool
- isTypeLevel :: TypeOrKind -> Bool
- mkIntWithInf :: Int -> IntWithInf
- treatZeroAsInf :: Int -> IntWithInf
- intGtLimit :: Int -> IntWithInf -> Bool
- infinity :: IntWithInf
- integralFractionalLit :: Bool -> Integer -> FractionalLit
- negateFractionalLit :: FractionalLit -> FractionalLit
- mkFractionalLit :: Real a => a -> FractionalLit
- negateIntegralLit :: IntegralLit -> IntegralLit
- mkIntegralLit :: Integral a => a -> IntegralLit
- isEarlyActive :: Activation -> Bool
- isAlwaysActive :: Activation -> Bool
- isNeverActive :: Activation -> Bool
- competesWith :: Activation -> Activation -> Bool
- isActiveIn :: PhaseNum -> Activation -> Bool
- isActive :: CompilerPhase -> Activation -> Bool
- pprInlineDebug :: InlinePragma -> SDoc
- pprInline :: InlinePragma -> SDoc
- setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
- setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma
- inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo
- inlinePragmaActivation :: InlinePragma -> Activation
- inlinePragmaSat :: InlinePragma -> Maybe Arity
- isAnyInlinePragma :: InlinePragma -> Bool
- isInlinablePragma :: InlinePragma -> Bool
- isInlinePragma :: InlinePragma -> Bool
- isDefaultInlinePragma :: InlinePragma -> Bool
- dfunInlinePragma :: InlinePragma
- inlinePragmaSpec :: InlinePragma -> InlineSpec
- neverInlinePragma :: InlinePragma
- alwaysInlinePragma :: InlinePragma
- defaultInlinePragma :: InlinePragma
- noUserInlineSpec :: InlineSpec -> Bool
- isFunLike :: RuleMatchInfo -> Bool
- isConLike :: RuleMatchInfo -> Bool
- activeDuringFinal :: Activation
- activeAfterInitial :: Activation
- pprWithSourceText :: SourceText -> SDoc -> SDoc
- failed :: SuccessFlag -> Bool
- succeeded :: SuccessFlag -> Bool
- successIf :: Bool -> SuccessFlag
- zapFragileOcc :: OccInfo -> OccInfo
- isOneOcc :: OccInfo -> Bool
- isDeadOcc :: OccInfo -> Bool
- isStrongLoopBreaker :: OccInfo -> Bool
- isWeakLoopBreaker :: OccInfo -> Bool
- weakLoopBreaker :: OccInfo
- strongLoopBreaker :: OccInfo
- isAlwaysTailCalled :: OccInfo -> Bool
- zapOccTailCallInfo :: OccInfo -> OccInfo
- tailCallInfo :: OccInfo -> TailCallInfo
- notOneBranch :: OneBranch
- oneBranch :: OneBranch
- notInsideLam :: InsideLam
- insideLam :: InsideLam
- seqOccInfo :: OccInfo -> ()
- isManyOccs :: OccInfo -> Bool
- noOccInfo :: OccInfo
- pprAlternative :: (a -> SDoc) -> a -> ConTag -> Arity -> SDoc
- sumParens :: SDoc -> SDoc
- tupleParens :: TupleSort -> SDoc -> SDoc
- boxityTupleSort :: Boxity -> TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- maybeParen :: PprPrec -> PprPrec -> SDoc -> SDoc
- appPrec :: PprPrec
- opPrec :: PprPrec
- funPrec :: PprPrec
- sigPrec :: PprPrec
- topPrec :: PprPrec
- hasOverlappingFlag :: OverlapMode -> Bool
- hasOverlappableFlag :: OverlapMode -> Bool
- hasIncoherentFlag :: OverlapMode -> Bool
- setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
- isGenerated :: Origin -> Bool
- boolToRecFlag :: Bool -> RecFlag
- isNonRec :: RecFlag -> Bool
- isRec :: RecFlag -> Bool
- isBoxed :: Boxity -> Bool
- isTopLevel :: TopLevelFlag -> Bool
- isNotTopLevel :: TopLevelFlag -> Bool
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- funTyFixity :: Fixity
- negateFixity :: Fixity
- defaultFixity :: Fixity
- minPrecedence :: Int
- maxPrecedence :: Int
- pprRuleName :: RuleName -> SDoc
- pprWarningTxtForMsg :: WarningTxt -> SDoc
- initialVersion :: Version
- bumpVersion :: Version -> Version
- isPromoted :: PromotionFlag -> Bool
- unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b
- isSwapped :: SwapFlag -> Bool
- flipSwap :: SwapFlag -> SwapFlag
- bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- hasNoOneShotInfo :: OneShotInfo -> Bool
- isOneShotInfo :: OneShotInfo -> Bool
- noOneShotInfo :: OneShotInfo
- alignmentOf :: Int -> Alignment
- mkAlignment :: Int -> Alignment
- fIRST_TAG :: ConTag
- pickLR :: LeftOrRight -> (a, a) -> a
- data LeftOrRight
- type Arity = Int
- type RepArity = Int
- type JoinArity = Int
- type ConTag = Int
- type ConTagZ = Int
- data Alignment
- data OneShotInfo
- data SwapFlag
- data PromotionFlag
- data FunctionOrData
- = IsFunction
- | IsData
- data StringLiteral = StringLiteral {
- sl_st :: SourceText
- sl_fs :: FastString
- data WarningTxt
- type RuleName = FastString
- data Fixity = Fixity SourceText Int FixityDirection
- data FixityDirection
- data LexicalFixity
- data TopLevelFlag
- data Boxity
- data RecFlag
- data Origin
- data OverlapFlag = OverlapFlag {}
- data OverlapMode
- newtype PprPrec = PprPrec Int
- data TupleSort
- data EP a = EP {}
- data OccInfo
- = ManyOccs {
- occ_tail :: !TailCallInfo
- | IAmDead
- | OneOcc { }
- | IAmALoopBreaker {
- occ_rules_only :: !RulesOnly
- occ_tail :: !TailCallInfo
- = ManyOccs {
- type InterestingCxt = Bool
- type InsideLam = Bool
- type OneBranch = Bool
- data TailCallInfo
- data DefMethSpec ty
- data SuccessFlag
- data SourceText
- type PhaseNum = Int
- data CompilerPhase
- data Activation
- data RuleMatchInfo
- data InlinePragma = InlinePragma {}
- data InlineSpec
- data IntegralLit = IL {}
- data FractionalLit = FL {}
- data IntWithInf
- data SpliceExplicitFlag
- data TypeOrKind
- module Class
- coercionKind :: Coercion -> Pair Type
- module Predicate
- module ConLike
- module CoreUtils
- buildSynTyCon :: Name -> [KnotTied TyConBinder] -> Kind -> [Role] -> KnotTied Type -> TyCon
- buildAlgTyCon :: Name -> [TyVar] -> [Role] -> Maybe CType -> ThetaType -> AlgTyConRhs -> Bool -> AlgTyConFlav -> TyCon
- splitDataProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type])
- promoteDataCon :: DataCon -> TyCon
- dataConUserTyVarsArePermuted :: DataCon -> Bool
- dataConCannotMatch :: [Type] -> DataCon -> Bool
- classDataCon :: Class -> DataCon
- specialPromotedDc :: DataCon -> Bool
- isVanillaDataCon :: DataCon -> Bool
- isUnboxedTupleCon :: DataCon -> Bool
- isTupleDataCon :: DataCon -> Bool
- dataConIdentity :: DataCon -> ByteString
- dataConRepArgTys :: DataCon -> [Type]
- dataConOrigArgTys :: DataCon -> [Type]
- dataConInstArgTys :: DataCon -> [Type] -> [Type]
- dataConUserType :: DataCon -> Type
- dataConOrigResTy :: DataCon -> Type
- dataConInstSig :: DataCon -> [Type] -> ([TyCoVar], ThetaType, [Type])
- dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type)
- dataConBoxer :: DataCon -> Maybe DataConBoxer
- dataConImplBangs :: DataCon -> [HsImplBang]
- dataConRepStrictness :: DataCon -> [StrictnessMark]
- isNullaryRepDataCon :: DataCon -> Bool
- isNullarySrcDataCon :: DataCon -> Bool
- dataConRepArity :: DataCon -> Arity
- dataConSrcBangs :: DataCon -> [HsSrcBang]
- dataConFieldType_maybe :: DataCon -> FieldLabelString -> Maybe (FieldLabel, Type)
- dataConFieldType :: DataCon -> FieldLabelString -> Type
- dataConImplicitTyThings :: DataCon -> [TyThing]
- dataConWrapId :: DataCon -> Id
- dataConWrapId_maybe :: DataCon -> Maybe Id
- dataConWorkId :: DataCon -> Id
- dataConTheta :: DataCon -> ThetaType
- dataConEqSpec :: DataCon -> [EqSpec]
- dataConUnivAndExTyCoVars :: DataCon -> [TyCoVar]
- dataConUnivTyVars :: DataCon -> [TyVar]
- dataConIsInfix :: DataCon -> Bool
- dataConRepType :: DataCon -> Type
- dataConOrigTyCon :: DataCon -> TyCon
- dataConTagZ :: DataCon -> ConTagZ
- dataConTag :: DataCon -> ConTag
- mkDataCon :: Name -> Bool -> TyConRepName -> [HsSrcBang] -> [FieldLabel] -> [TyVar] -> [TyCoVar] -> [TyVarBinder] -> [EqSpec] -> KnotTied ThetaType -> [KnotTied Type] -> KnotTied Type -> RuntimeRepInfo -> KnotTied TyCon -> ConTag -> ThetaType -> Id -> DataConRep -> DataCon
- isMarkedStrict :: StrictnessMark -> Bool
- isSrcUnpacked :: SrcUnpackedness -> Bool
- isSrcStrict :: SrcStrictness -> Bool
- isBanged :: HsImplBang -> Bool
- eqHsBang :: HsImplBang -> HsImplBang -> Bool
- filterEqSpec :: [EqSpec] -> [TyVar] -> [TyVar]
- substEqSpec :: TCvSubst -> EqSpec -> EqSpec
- eqSpecPreds :: [EqSpec] -> ThetaType
- eqSpecPair :: EqSpec -> (TyVar, Type)
- eqSpecType :: EqSpec -> Type
- eqSpecTyVar :: EqSpec -> TyVar
- mkEqSpec :: TyVar -> Type -> EqSpec
- data HsSrcBang = HsSrcBang SourceText SrcUnpackedness SrcStrictness
- data HsImplBang
- data SrcStrictness
- data SrcUnpackedness
- data StrictnessMark
- dataConName :: DataCon -> Name
- dataConTyCon :: DataCon -> TyCon
- dataConUserTyVars :: DataCon -> [TyVar]
- dataConUserTyVarBinders :: DataCon -> [TyVarBinder]
- dataConSourceArity :: DataCon -> Arity
- dataConFieldLabels :: DataCon -> [FieldLabel]
- dataConInstOrigArgTys :: DataCon -> [Type] -> [Type]
- dataConStupidTheta :: DataCon -> ThetaType
- dataConFullSig :: DataCon -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, [Type], Type)
- isUnboxedSumCon :: DataCon -> Bool
- data DataCon
- data DataConRep
- = NoDataConRep
- | DCR {
- dcr_wrap_id :: Id
- dcr_boxer :: DataConBoxer
- dcr_arg_tys :: [Type]
- dcr_stricts :: [StrictnessMark]
- dcr_bangs :: [HsImplBang]
- data EqSpec
- type FieldLabelString = FastString
- type FieldLabel = FieldLbl Name
- data FieldLbl a = FieldLabel {
- flLabel :: FieldLabelString
- flIsOverloaded :: Bool
- flSelector :: a
- fIRST_TAG :: ConTag
- type ConTag = Int
- module DsExpr
- class Functor f => Applicative (f :: Type -> Type) where
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- pprRuntimeTrace :: String -> SDoc -> CoreExpr -> DsM CoreExpr
- dsWhenNoErrs :: DsM a -> (a -> CoreExpr) -> DsM CoreExpr
- dsNoLevPolyExpr :: CoreExpr -> SDoc -> DsM ()
- dsNoLevPoly :: Type -> SDoc -> DsM ()
- discardWarningsDs :: DsM a -> DsM a
- dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a
- dsLookupMetaEnv :: Name -> DsM (Maybe DsMetaVal)
- dsGetCompleteMatches :: TyCon -> DsM [CompleteMatch]
- dsGetMetaEnv :: DsM (NameEnv DsMetaVal)
- dsGetFamInstEnvs :: DsM FamInstEnvs
- dsLookupConLike :: Name -> DsM ConLike
- dsLookupDataCon :: Name -> DsM DataCon
- dsLookupTyCon :: Name -> DsM TyCon
- dsLookupGlobalId :: Name -> DsM Id
- dsLookupGlobal :: Name -> DsM TyThing
- mkPrintUnqualifiedDs :: DsM PrintUnqualified
- askNoErrsDs :: DsM a -> DsM (a, Bool)
- failDs :: DsM a
- failWithDs :: SDoc -> DsM a
- errDsCoreExpr :: SDoc -> DsM CoreExpr
- errDs :: SDoc -> DsM ()
- warnIfSetDs :: WarningFlag -> SDoc -> DsM ()
- warnDs :: WarnReason -> SDoc -> DsM ()
- putSrcSpanDs :: SrcSpan -> DsM a -> DsM a
- getSrcSpanDs :: DsM SrcSpan
- updPmDelta :: Delta -> DsM a -> DsM a
- getPmDelta :: DsM Delta
- getGhcModeDs :: DsM GhcMode
- newSysLocalsDs :: [Type] -> DsM [Id]
- newSysLocalsDsNoLP :: [Type] -> DsM [Id]
- newFailLocalDs :: Type -> DsM Id
- newSysLocalDs :: Type -> DsM Id
- newSysLocalDsNoLP :: Type -> DsM Id
- newPredVarDs :: PredType -> DsM Var
- duplicateLocalDs :: Id -> DsM Id
- newUniqueId :: Id -> Type -> DsM Id
- initTcDsForSolver :: TcM a -> DsM (Messages, Maybe a)
- initDsWithModGuts :: HscEnv -> ModGuts -> DsM a -> IO (Messages, Maybe a)
- initDs :: HscEnv -> TcGblEnv -> DsM a -> IO (Messages, Maybe a)
- initDsTc :: DsM a -> TcM a
- fixDs :: (a -> DsM a) -> DsM a
- orFail :: CanItFail -> CanItFail -> CanItFail
- idDsWrapper :: DsWrapper
- data DsMatchContext = DsMatchContext (HsMatchContext Name) SrcSpan
- data EquationInfo = EqnInfo {}
- type DsWrapper = CoreExpr -> CoreExpr
- data MatchResult = MatchResult CanItFail (CoreExpr -> DsM CoreExpr)
- data CanItFail
- type DsWarning = (SrcSpan, SDoc)
- newUniqueSupply :: TcRnIf gbl lcl UniqSupply
- newUnique :: TcRnIf gbl lcl Unique
- whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- xoptM :: Extension -> TcRnIf gbl lcl Bool
- type DsM = TcRnIf DsGblEnv DsLclEnv
- type DsMetaEnv = NameEnv DsMetaVal
- data DsMetaVal
- data UniqSupply
- traceCmd :: DynFlags -> String -> String -> IO a -> IO a
- isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag)
- prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
- logOutput :: DynFlags -> PprStyle -> MsgDoc -> IO ()
- printOutputForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO ()
- printInfoForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO ()
- putMsg :: DynFlags -> MsgDoc -> IO ()
- debugTraceMsg :: DynFlags -> Int -> MsgDoc -> IO ()
- withTimingSilentD :: (MonadIO m, HasDynFlags m) => SDoc -> (a -> ()) -> m a -> m a
- withTimingSilent :: MonadIO m => DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- withTimingD :: (MonadIO m, HasDynFlags m) => SDoc -> (a -> ()) -> m a -> m a
- withTiming :: MonadIO m => DynFlags -> SDoc -> (a -> ()) -> m a -> m a
- showPass :: DynFlags -> String -> IO ()
- compilationProgressMsg :: DynFlags -> String -> IO ()
- fatalErrorMsg'' :: FatalMessager -> String -> IO ()
- fatalErrorMsg :: DynFlags -> MsgDoc -> IO ()
- warningMsg :: DynFlags -> MsgDoc -> IO ()
- errorMsg :: DynFlags -> MsgDoc -> IO ()
- dumpSDocWithStyle :: PprStyle -> DynFlags -> DumpFlag -> String -> SDoc -> IO ()
- dumpSDocForUser :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO ()
- mkDumpDoc :: String -> SDoc -> SDoc
- dumpIfSet_dyn_printer :: PrintUnqualified -> DynFlags -> DumpFlag -> SDoc -> IO ()
- dumpIfSet_dyn :: DynFlags -> DumpFlag -> String -> SDoc -> IO ()
- dumpIfSet :: DynFlags -> Bool -> String -> SDoc -> IO ()
- doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO ()
- doIfSet :: Bool -> IO () -> IO ()
- ghcExit :: DynFlags -> Int -> IO ()
- pprLocErrMsg :: ErrMsg -> SDoc
- pprErrMsgBagWithLoc :: Bag ErrMsg -> [SDoc]
- formatErrDoc :: DynFlags -> ErrDoc -> SDoc
- printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO ()
- warningsToMessages :: DynFlags -> WarningMessages -> Messages
- errorsFound :: DynFlags -> Messages -> Bool
- isEmptyMessages :: Messages -> Bool
- emptyMessages :: Messages
- mkPlainWarnMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
- mkLongWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg
- mkPlainErrMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg
- mkErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg
- mkLongErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg
- mkErrDoc :: DynFlags -> SrcSpan -> PrintUnqualified -> ErrDoc -> ErrMsg
- makeIntoWarning :: WarnReason -> ErrMsg -> ErrMsg
- pprMessageBag :: Bag MsgDoc -> SDoc
- errDoc :: [MsgDoc] -> [MsgDoc] -> [MsgDoc] -> ErrDoc
- unionMessages :: Messages -> Messages -> Messages
- orValid :: Validity -> Validity -> Validity
- getInvalids :: [Validity] -> [MsgDoc]
- allValid :: [Validity] -> Validity
- andValid :: Validity -> Validity -> Validity
- isValid :: Validity -> Bool
- data Validity
- type Messages = (WarningMessages, ErrorMessages)
- type WarningMessages = Bag WarnMsg
- type ErrorMessages = Bag ErrMsg
- data ErrMsg
- data ErrDoc
- type WarnMsg = ErrMsg
- mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc
- mkLocMessageAnn :: Maybe String -> Severity -> SrcSpan -> MsgDoc -> MsgDoc
- getCaretDiagnostic :: Severity -> SrcSpan -> IO MsgDoc
- dumpSDoc :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO ()
- data Severity
- type MsgDoc = SDoc
- module FamInst
- module FamInstEnv
- optionsErrorMsgs :: DynFlags -> [String] -> [Located String] -> FilePath -> Messages
- checkProcessArgsResult :: MonadIO m => DynFlags -> [Located String] -> m ()
- getOptions :: DynFlags -> StringBuffer -> FilePath -> [Located String]
- getOptionsFromFile :: DynFlags -> FilePath -> IO [Located String]
- mkPrelImports :: ModuleName -> SrcSpan -> Bool -> [LImportDecl GhcPs] -> [LImportDecl GhcPs]
- module Id
- module InstEnv
- module IfaceSyn
- unitModuleSet :: Module -> ModuleSet
- unionModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- delModuleSet :: ModuleSet -> Module -> ModuleSet
- minusModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- intersectModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
- elemModuleSet :: Module -> ModuleSet -> Bool
- moduleSetElts :: ModuleSet -> [Module]
- emptyModuleSet :: ModuleSet
- extendModuleSetList :: ModuleSet -> [Module] -> ModuleSet
- extendModuleSet :: ModuleSet -> Module -> ModuleSet
- mkModuleSet :: [Module] -> ModuleSet
- isEmptyModuleEnv :: ModuleEnv a -> Bool
- unitModuleEnv :: Module -> a -> ModuleEnv a
- moduleEnvToList :: ModuleEnv a -> [(Module, a)]
- moduleEnvElts :: ModuleEnv a -> [a]
- moduleEnvKeys :: ModuleEnv a -> [Module]
- emptyModuleEnv :: ModuleEnv a
- mkModuleEnv :: [(Module, a)] -> ModuleEnv a
- mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b
- lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a
- lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a
- plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a
- delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a
- delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a
- plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a
- extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a
- extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a
- extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a
- extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a
- elemModuleEnv :: Module -> ModuleEnv a -> Bool
- filterModuleEnv :: (Module -> a -> Bool) -> ModuleEnv a -> ModuleEnv a
- wiredInUnitIds :: [UnitId]
- isHoleModule :: Module -> Bool
- isInteractiveModule :: Module -> Bool
- mainUnitId :: UnitId
- interactiveUnitId :: UnitId
- thisGhcUnitId :: UnitId
- thUnitId :: UnitId
- rtsUnitId :: UnitId
- baseUnitId :: UnitId
- integerUnitId :: UnitId
- primUnitId :: UnitId
- parseModSubst :: ReadP [(ModuleName, Module)]
- parseModuleId :: ReadP Module
- parseComponentId :: ReadP ComponentId
- parseUnitId :: ReadP UnitId
- parseModuleName :: ReadP ModuleName
- generalizeIndefModule :: IndefModule -> IndefModule
- generalizeIndefUnitId :: IndefUnitId -> IndefUnitId
- splitUnitIdInsts :: UnitId -> (InstalledUnitId, Maybe IndefUnitId)
- splitModuleInsts :: Module -> (InstalledModule, Maybe IndefModule)
- renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId
- renameHoleModule' :: PackageConfigMap -> ShHoleSubst -> Module -> Module
- renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId
- renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module
- stringToUnitId :: String -> UnitId
- fsToUnitId :: FastString -> UnitId
- newSimpleUnitId :: ComponentId -> UnitId
- stableUnitIdCmp :: UnitId -> UnitId -> Ordering
- newUnitId :: ComponentId -> [(ModuleName, Module)] -> UnitId
- hashUnitId :: ComponentId -> [(ModuleName, Module)] -> FastString
- unitIdIsDefinite :: UnitId -> Bool
- unitIdFreeHoles :: UnitId -> UniqDSet ModuleName
- delInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> InstalledModuleEnv a
- filterInstalledModuleEnv :: (InstalledModule -> a -> Bool) -> InstalledModuleEnv a -> InstalledModuleEnv a
- extendInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> a -> InstalledModuleEnv a
- lookupInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> Maybe a
- emptyInstalledModuleEnv :: InstalledModuleEnv a
- installedUnitIdEq :: InstalledUnitId -> UnitId -> Bool
- installedModuleEq :: InstalledModule -> Module -> Bool
- stringToInstalledUnitId :: String -> InstalledUnitId
- componentIdToInstalledUnitId :: ComponentId -> InstalledUnitId
- fsToInstalledUnitId :: FastString -> InstalledUnitId
- installedUnitIdString :: InstalledUnitId -> String
- toInstalledUnitId :: UnitId -> InstalledUnitId
- indefModuleToModule :: DynFlags -> IndefModule -> Module
- indefUnitIdToUnitId :: DynFlags -> IndefUnitId -> UnitId
- newIndefUnitId :: ComponentId -> [(ModuleName, Module)] -> IndefUnitId
- unitIdKey :: UnitId -> Unique
- unitIdFS :: UnitId -> FastString
- pprModule :: Module -> SDoc
- mkModule :: UnitId -> ModuleName -> Module
- stableModuleCmp :: Module -> Module -> Ordering
- mkHoleModule :: ModuleName -> Module
- moduleIsDefinite :: Module -> Bool
- moduleFreeHoles :: Module -> UniqDSet ModuleName
- moduleNameColons :: ModuleName -> String
- moduleNameSlashes :: ModuleName -> String
- mkModuleNameFS :: FastString -> ModuleName
- mkModuleName :: String -> ModuleName
- moduleStableString :: Module -> String
- moduleNameString :: ModuleName -> String
- moduleNameFS :: ModuleName -> FastString
- pprModuleName :: ModuleName -> SDoc
- stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
- addBootSuffixLocn :: ModLocation -> ModLocation
- addBootSuffix_maybe :: Bool -> FilePath -> FilePath
- addBootSuffix :: FilePath -> FilePath
- class ContainsModule t where
- extractModule :: t -> Module
- class HasModule (m :: Type -> Type) where
- data IndefUnitId = IndefUnitId {}
- data IndefModule = IndefModule {}
- data InstalledModule = InstalledModule {}
- newtype DefUnitId = DefUnitId {}
- data InstalledModuleEnv elt
- type ShHoleSubst = ModuleNameEnv Module
- data ModuleEnv elt
- type ModuleSet = Set NDModule
- type ModuleNameEnv elt = UniqFM elt
- type DModuleNameEnv elt = UniqDFM elt
- unitIdString :: UnitId -> String
- data Module = Module !UnitId !ModuleName
- data ModuleName
- pattern IndefiniteUnitId :: !IndefUnitId -> UnitId
- pattern DefiniteUnitId :: !DefUnitId -> UnitId
- newtype InstalledUnitId = InstalledUnitId {}
- newtype ComponentId = ComponentId FastString
- pprPrefixName :: NamedThing a => a -> SDoc
- pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc
- getOccFS :: NamedThing a => a -> FastString
- getOccString :: NamedThing a => a -> String
- getSrcSpan :: NamedThing a => a -> SrcSpan
- getSrcLoc :: NamedThing a => a -> SrcLoc
- nameStableString :: Name -> String
- pprNameDefnLoc :: Name -> SDoc
- pprDefinedAt :: Name -> SDoc
- pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
- pprNameUnqualified :: Name -> SDoc
- stableNameCmp :: Name -> Name -> Ordering
- localiseName :: Name -> Name
- tidyNameOcc :: Name -> OccName -> Name
- setNameLoc :: Name -> SrcSpan -> Name
- setNameUnique :: Name -> Unique -> Name
- mkFCallName :: Unique -> String -> Name
- mkSysTvName :: Unique -> FastString -> Name
- mkSystemVarName :: Unique -> FastString -> Name
- mkSystemNameAt :: Unique -> OccName -> SrcSpan -> Name
- mkSystemName :: Unique -> OccName -> Name
- mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name
- mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name
- mkDerivedInternalName :: (OccName -> OccName) -> Unique -> Name -> Name
- mkClonedInternalName :: Unique -> Name -> Name
- mkInternalName :: Unique -> OccName -> SrcSpan -> Name
- isSystemName :: Name -> Bool
- isVarName :: Name -> Bool
- isValName :: Name -> Bool
- isDataConName :: Name -> Bool
- isTyConName :: Name -> Bool
- isTyVarName :: Name -> Bool
- nameIsFromExternalPackage :: UnitId -> Name -> Bool
- nameIsHomePackageImport :: Module -> Name -> Bool
- nameIsHomePackage :: Module -> Name -> Bool
- nameIsLocalOrFrom :: Module -> Name -> Bool
- nameModule_maybe :: Name -> Maybe Module
- nameModule :: HasDebugCallStack => Name -> Module
- isHoleName :: Name -> Bool
- isInternalName :: Name -> Bool
- isExternalName :: Name -> Bool
- isBuiltInSyntax :: Name -> Bool
- wiredInNameTyThing_maybe :: Name -> Maybe TyThing
- isWiredInName :: Name -> Bool
- nameSrcSpan :: Name -> SrcSpan
- nameSrcLoc :: Name -> SrcLoc
- nameNameSpace :: Name -> NameSpace
- nameOccName :: Name -> OccName
- nameUnique :: Name -> Unique
- data BuiltInSyntax
- class NamedThing a where
- getOccName :: a -> OccName
- getName :: a -> Name
- tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName)
- avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv
- initTidyOccEnv :: [OccName] -> TidyOccEnv
- emptyTidyOccEnv :: TidyOccEnv
- mkMethodOcc :: OccName -> OccName
- mkDataCOcc :: OccName -> OccSet -> OccName
- mkDataTOcc :: OccName -> OccSet -> OccName
- mkDFunOcc :: String -> Bool -> OccSet -> OccName
- mkInstTyTcOcc :: String -> OccSet -> OccName
- mkLocalOcc :: Unique -> OccName -> OccName
- mkSuperDictSelOcc :: Int -> OccName -> OccName
- mkSuperDictAuxOcc :: Int -> OccName -> OccName
- mkDataConWorkerOcc :: OccName -> OccName
- mkRecFldSelOcc :: String -> OccName
- mkGen1R :: OccName -> OccName
- mkGenR :: OccName -> OccName
- mkTyConRepOcc :: OccName -> OccName
- mkMaxTagOcc :: OccName -> OccName
- mkTag2ConOcc :: OccName -> OccName
- mkCon2TagOcc :: OccName -> OccName
- mkEqPredCoOcc :: OccName -> OccName
- mkInstTyCoOcc :: OccName -> OccName
- mkNewTyCoOcc :: OccName -> OccName
- mkClassDataConOcc :: OccName -> OccName
- mkRepEqOcc :: OccName -> OccName
- mkForeignExportOcc :: OccName -> OccName
- mkSpecOcc :: OccName -> OccName
- mkIPOcc :: OccName -> OccName
- mkDictOcc :: OccName -> OccName
- mkClassOpAuxOcc :: OccName -> OccName
- mkDefaultMethodOcc :: OccName -> OccName
- mkBuilderOcc :: OccName -> OccName
- mkMatcherOcc :: OccName -> OccName
- mkWorkerOcc :: OccName -> OccName
- mkDataConWrapperOcc :: OccName -> OccName
- isTypeableBindOcc :: OccName -> Bool
- isDefaultMethodOcc :: OccName -> Bool
- isDerivedOccName :: OccName -> Bool
- startsWithUnderscore :: OccName -> Bool
- parenSymOcc :: OccName -> SDoc -> SDoc
- isSymOcc :: OccName -> Bool
- isDataSymOcc :: OccName -> Bool
- isDataOcc :: OccName -> Bool
- isValOcc :: OccName -> Bool
- isTcOcc :: OccName -> Bool
- isTvOcc :: OccName -> Bool
- isVarOcc :: OccName -> Bool
- setOccNameSpace :: NameSpace -> OccName -> OccName
- occNameString :: OccName -> String
- filterOccSet :: (OccName -> Bool) -> OccSet -> OccSet
- intersectsOccSet :: OccSet -> OccSet -> Bool
- intersectOccSet :: OccSet -> OccSet -> OccSet
- isEmptyOccSet :: OccSet -> Bool
- elemOccSet :: OccName -> OccSet -> Bool
- minusOccSet :: OccSet -> OccSet -> OccSet
- unionManyOccSets :: [OccSet] -> OccSet
- unionOccSets :: OccSet -> OccSet -> OccSet
- extendOccSetList :: OccSet -> [OccName] -> OccSet
- extendOccSet :: OccSet -> OccName -> OccSet
- mkOccSet :: [OccName] -> OccSet
- unitOccSet :: OccName -> OccSet
- emptyOccSet :: OccSet
- pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc
- alterOccEnv :: (Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt
- filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt
- delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a
- delFromOccEnv :: OccEnv a -> OccName -> OccEnv a
- mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a
- mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b
- extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
- extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a
- plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a
- plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a
- occEnvElts :: OccEnv a -> [a]
- foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b
- elemOccEnv :: OccName -> OccEnv a -> Bool
- mkOccEnv :: [(OccName, a)] -> OccEnv a
- lookupOccEnv :: OccEnv a -> OccName -> Maybe a
- extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a
- extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a
- unitOccEnv :: OccName -> a -> OccEnv a
- emptyOccEnv :: OccEnv a
- nameSpacesRelated :: NameSpace -> NameSpace -> Bool
- demoteOccName :: OccName -> Maybe OccName
- mkClsOccFS :: FastString -> OccName
- mkClsOcc :: String -> OccName
- mkTcOccFS :: FastString -> OccName
- mkTcOcc :: String -> OccName
- mkTyVarOccFS :: FastString -> OccName
- mkTyVarOcc :: String -> OccName
- mkDataOccFS :: FastString -> OccName
- mkDataOcc :: String -> OccName
- mkVarOccFS :: FastString -> OccName
- mkVarOcc :: String -> OccName
- mkOccNameFS :: NameSpace -> FastString -> OccName
- mkOccName :: NameSpace -> String -> OccName
- pprOccName :: OccName -> SDoc
- pprNameSpaceBrief :: NameSpace -> SDoc
- pprNonVarNameSpace :: NameSpace -> SDoc
- pprNameSpace :: NameSpace -> SDoc
- isValNameSpace :: NameSpace -> Bool
- isVarNameSpace :: NameSpace -> Bool
- isTvNameSpace :: NameSpace -> Bool
- isTcClsNameSpace :: NameSpace -> Bool
- isDataConNameSpace :: NameSpace -> Bool
- tvName :: NameSpace
- srcDataName :: NameSpace
- dataName :: NameSpace
- tcClsName :: NameSpace
- clsName :: NameSpace
- tcName :: NameSpace
- data NameSpace
- class HasOccName name where
- data OccEnv a
- type OccSet = UniqSet OccName
- type TidyOccEnv = UniqFM Int
- mkFsEnv :: [(FastString, a)] -> FastStringEnv a
- lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a
- extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a
- emptyFsEnv :: FastStringEnv a
- type FastStringEnv a = UniqFM a
- data OccName
- data Name
- module NameCache
- module NameEnv
- module NameSet
- module PatSyn
- pprTypeForUser :: Type -> SDoc
- pprTyThing :: ShowSub -> TyThing -> SDoc
- pprTyThingInContextLoc :: TyThing -> SDoc
- pprTyThingInContext :: ShowSub -> TyThing -> SDoc
- pprTyThingHdr :: TyThing -> SDoc
- pprTyThingLoc :: TyThing -> SDoc
- module PrelInfo
- pretendNameIsInScope :: Name -> Bool
- interactiveClassKeys :: [Unique]
- interactiveClassNames :: [Name]
- derivableClassKeys :: [Unique]
- standardClassKeys :: [Unique]
- fractionalClassKeys :: [Unique]
- numericClassKeys :: [Unique]
- wordToNaturalIdKey :: Unique
- naturalSDataConKey :: Unique
- mkNaturalIdKey :: Unique
- timesNaturalIdKey :: Unique
- minusNaturalIdKey :: Unique
- plusNaturalIdKey :: Unique
- naturalToIntegerIdKey :: Unique
- naturalFromIntegerIdKey :: Unique
- makeStaticKey :: Unique
- fromStaticPtrClassOpKey :: Unique
- pushCallStackKey :: Unique
- emptyCallStackKey :: Unique
- mconcatClassOpKey :: Unique
- mappendClassOpKey :: Unique
- memptyClassOpKey :: Unique
- sappendClassOpKey :: Unique
- coercibleSCSelIdKey :: Unique
- heqSCSelIdKey :: Unique
- eqSCSelIdKey :: Unique
- bitIntegerIdKey :: Unique
- toDynIdKey :: Unique
- starArrStarArrStarKindRepKey :: Unique
- starArrStarKindRepKey :: Unique
- starKindRepKey :: Unique
- tr'PtrRepLiftedKey :: Unique
- trRuntimeRepKey :: Unique
- trTYPE'PtrRepLiftedKey :: Unique
- trTYPEKey :: Unique
- mkTrFunKey :: Unique
- typeRepIdKey :: Unique
- typeSymbolTypeRepKey :: Unique
- typeNatTypeRepKey :: Unique
- mkTrAppKey :: Unique
- mkTrConKey :: Unique
- mkTrTypeKey :: Unique
- mkTyConKey :: Unique
- proxyHashKey :: Unique
- toListClassOpKey :: Unique
- fromListNClassOpKey :: Unique
- fromListClassOpKey :: Unique
- isListClassKey :: Unique
- ghciStepIoMClassOpKey :: Unique
- mzipIdKey :: Unique
- liftMIdKey :: Unique
- guardMIdKey :: Unique
- toRationalClassOpKey :: Unique
- toIntegerClassOpKey :: Unique
- realToFracIdKey :: Unique
- fromIntegralIdKey :: Unique
- toAnnotationWrapperIdKey :: Unique
- fromStringClassOpKey :: Unique
- loopAIdKey :: Unique
- choiceAIdKey :: Unique
- appAIdKey :: Unique
- firstAIdKey :: Unique
- composeAIdKey :: Unique
- arrAIdKey :: Unique
- failMClassOpKey :: Unique
- mfixIdKey :: Unique
- returnMClassOpKey :: Unique
- fmapClassOpKey :: Unique
- thenMClassOpKey :: Unique
- bindMClassOpKey :: Unique
- negateClassOpKey :: Unique
- geClassOpKey :: Unique
- eqClassOpKey :: Unique
- enumFromThenToClassOpKey :: Unique
- enumFromToClassOpKey :: Unique
- enumFromThenClassOpKey :: Unique
- enumFromClassOpKey :: Unique
- fromRationalClassOpKey :: Unique
- minusClassOpKey :: Unique
- fromIntegerClassOpKey :: Unique
- unboundKey :: Unique
- coerceKey :: Unique
- magicDictKey :: Unique
- undefinedKey :: Unique
- checkDotnetResNameIdKey :: Unique
- unmarshalStringIdKey :: Unique
- marshalStringIdKey :: Unique
- marshalObjectIdKey :: Unique
- unmarshalObjectIdKey :: Unique
- rationalToDoubleIdKey :: Unique
- rationalToFloatIdKey :: Unique
- noinlineIdKey :: Unique
- coercionTokenIdKey :: Unique
- dollarIdKey :: Unique
- groupWithIdKey :: Unique
- mapIdKey :: Unique
- inlineIdKey :: Unique
- breakpointCondIdKey :: Unique
- breakpointIdKey :: Unique
- traceKey :: Unique
- runRWKey :: Unique
- oneShotKey :: Unique
- assertErrorIdKey :: Unique
- lazyIdKey :: Unique
- thenIOIdKey :: Unique
- runMainKey :: Unique
- rootMainKey :: Unique
- decodeDoubleIntegerIdKey :: Unique
- int64ToIntegerIdKey :: Unique
- word64ToIntegerIdKey :: Unique
- wordToIntegerIdKey :: Unique
- shiftRIntegerIdKey :: Unique
- shiftLIntegerIdKey :: Unique
- complementIntegerIdKey :: Unique
- xorIntegerIdKey :: Unique
- orIntegerIdKey :: Unique
- andIntegerIdKey :: Unique
- lcmIntegerIdKey :: Unique
- gcdIntegerIdKey :: Unique
- encodeDoubleIntegerIdKey :: Unique
- encodeFloatIntegerIdKey :: Unique
- doubleFromIntegerIdKey :: Unique
- floatFromIntegerIdKey :: Unique
- quotRemIntegerIdKey :: Unique
- divModIntegerIdKey :: Unique
- modIntegerIdKey :: Unique
- divIntegerIdKey :: Unique
- remIntegerIdKey :: Unique
- quotIntegerIdKey :: Unique
- compareIntegerIdKey :: Unique
- geIntegerPrimIdKey :: Unique
- ltIntegerPrimIdKey :: Unique
- gtIntegerPrimIdKey :: Unique
- leIntegerPrimIdKey :: Unique
- signumIntegerIdKey :: Unique
- absIntegerIdKey :: Unique
- neqIntegerPrimIdKey :: Unique
- eqIntegerPrimIdKey :: Unique
- negateIntegerIdKey :: Unique
- minusIntegerIdKey :: Unique
- timesIntegerIdKey :: Unique
- plusIntegerIdKey :: Unique
- integerToInt64IdKey :: Unique
- integerToWord64IdKey :: Unique
- integerToIntIdKey :: Unique
- integerToWordIdKey :: Unique
- smallIntegerIdKey :: Unique
- mkIntegerIdKey :: Unique
- assertIdKey :: Unique
- otherwiseIdKey :: Unique
- sndIdKey :: Unique
- fstIdKey :: Unique
- voidArgIdKey :: Unique
- nullAddrIdKey :: Unique
- failIOIdKey :: Unique
- printIdKey :: Unique
- newStablePtrIdKey :: Unique
- returnIOIdKey :: Unique
- bindIOIdKey :: Unique
- zipIdKey :: Unique
- filterIdKey :: Unique
- concatIdKey :: Unique
- unsafeCoerceIdKey :: Unique
- absentSumFieldErrorIdKey :: Unique
- modIntIdKey :: Unique
- divIntIdKey :: Unique
- typeErrorIdKey :: Unique
- voidPrimIdKey :: Unique
- unpackCStringIdKey :: Unique
- unpackCStringFoldrIdKey :: Unique
- unpackCStringAppendIdKey :: Unique
- unpackCStringUtf8IdKey :: Unique
- recConErrorIdKey :: Unique
- realWorldPrimIdKey :: Unique
- patErrorIdKey :: Unique
- runtimeErrorIdKey :: Unique
- nonExhaustiveGuardsErrorIdKey :: Unique
- noMethodBindingErrorIdKey :: Unique
- eqStringIdKey :: Unique
- seqIdKey :: Unique
- recSelErrorIdKey :: Unique
- foldrIdKey :: Unique
- errorIdKey :: Unique
- buildIdKey :: Unique
- appendIdKey :: Unique
- augmentIdKey :: Unique
- absentErrorIdKey :: Unique
- wildCardKey :: Unique
- typeLitNatDataConKey :: Unique
- typeLitSymbolDataConKey :: Unique
- kindRepTypeLitDDataConKey :: Unique
- kindRepTypeLitSDataConKey :: Unique
- kindRepTYPEDataConKey :: Unique
- kindRepFunDataConKey :: Unique
- kindRepAppDataConKey :: Unique
- kindRepVarDataConKey :: Unique
- kindRepTyConAppDataConKey :: Unique
- vecElemDataConKeys :: [Unique]
- vecCountDataConKeys :: [Unique]
- unliftedRepDataConKeys :: [Unique]
- unliftedSimpleRepDataConKeys :: [Unique]
- liftedRepDataConKey :: Unique
- runtimeRepSimpleDataConKeys :: [Unique]
- sumRepDataConKey :: Unique
- tupleRepDataConKey :: Unique
- vecRepDataConKey :: Unique
- metaSelDataConKey :: Unique
- metaConsDataConKey :: Unique
- metaDataDataConKey :: Unique
- decidedUnpackDataConKey :: Unique
- decidedStrictDataConKey :: Unique
- decidedLazyDataConKey :: Unique
- noSourceStrictnessDataConKey :: Unique
- sourceStrictDataConKey :: Unique
- sourceLazyDataConKey :: Unique
- noSourceUnpackednessDataConKey :: Unique
- sourceNoUnpackDataConKey :: Unique
- sourceUnpackDataConKey :: Unique
- notAssociativeDataConKey :: Unique
- rightAssociativeDataConKey :: Unique
- leftAssociativeDataConKey :: Unique
- infixIDataConKey :: Unique
- prefixIDataConKey :: Unique
- typeErrorShowTypeDataConKey :: Unique
- typeErrorVAppendDataConKey :: Unique
- typeErrorAppendDataConKey :: Unique
- typeErrorTextDataConKey :: Unique
- typeLitSortTyConKey :: Unique
- kindRepTyConKey :: Unique
- trGhcPrimModuleKey :: Unique
- trNameDDataConKey :: Unique
- trNameSDataConKey :: Unique
- trNameTyConKey :: Unique
- trModuleDataConKey :: Unique
- trModuleTyConKey :: Unique
- trTyConDataConKey :: Unique
- trTyConTyConKey :: Unique
- srcLocDataConKey :: Unique
- fingerprintDataConKey :: Unique
- staticPtrInfoDataConKey :: Unique
- staticPtrDataConKey :: Unique
- coercibleDataConKey :: Unique
- ordGTDataConKey :: Unique
- ordEQDataConKey :: Unique
- ordLTDataConKey :: Unique
- rightDataConKey :: Unique
- leftDataConKey :: Unique
- genUnitDataConKey :: Unique
- inrDataConKey :: Unique
- inlDataConKey :: Unique
- crossDataConKey :: Unique
- heqDataConKey :: Unique
- integerDataConKey :: Unique
- ioDataConKey :: Unique
- wordDataConKey :: Unique
- trueDataConKey :: Unique
- stableNameDataConKey :: Unique
- word8DataConKey :: Unique
- ratioDataConKey :: Unique
- nilDataConKey :: Unique
- eqDataConKey :: Unique
- justDataConKey :: Unique
- nothingDataConKey :: Unique
- integerSDataConKey :: Unique
- intDataConKey :: Unique
- floatDataConKey :: Unique
- falseDataConKey :: Unique
- doubleDataConKey :: Unique
- consDataConKey :: Unique
- charDataConKey :: Unique
- doubleX8PrimTyConKey :: Unique
- floatX16PrimTyConKey :: Unique
- doubleX4PrimTyConKey :: Unique
- floatX8PrimTyConKey :: Unique
- doubleX2PrimTyConKey :: Unique
- floatX4PrimTyConKey :: Unique
- word64X8PrimTyConKey :: Unique
- word32X16PrimTyConKey :: Unique
- word16X32PrimTyConKey :: Unique
- word8X64PrimTyConKey :: Unique
- word64X4PrimTyConKey :: Unique
- word32X8PrimTyConKey :: Unique
- word16X16PrimTyConKey :: Unique
- word8X32PrimTyConKey :: Unique
- word64X2PrimTyConKey :: Unique
- word32X4PrimTyConKey :: Unique
- word16X8PrimTyConKey :: Unique
- word8X16PrimTyConKey :: Unique
- int64X8PrimTyConKey :: Unique
- int32X16PrimTyConKey :: Unique
- int16X32PrimTyConKey :: Unique
- int8X64PrimTyConKey :: Unique
- int64X4PrimTyConKey :: Unique
- int32X8PrimTyConKey :: Unique
- int16X16PrimTyConKey :: Unique
- int8X32PrimTyConKey :: Unique
- int64X2PrimTyConKey :: Unique
- int32X4PrimTyConKey :: Unique
- int16X8PrimTyConKey :: Unique
- int8X16PrimTyConKey :: Unique
- typeSymbolAppendFamNameKey :: Unique
- someTypeRepDataConKey :: Unique
- someTypeRepTyConKey :: Unique
- typeRepTyConKey :: Unique
- callStackTyConKey :: Unique
- staticPtrInfoTyConKey :: Unique
- staticPtrTyConKey :: Unique
- smallMutableArrayPrimTyConKey :: Unique
- smallArrayPrimTyConKey :: Unique
- anyTyConKey :: Unique
- specTyConKey :: Unique
- proxyPrimTyConKey :: Unique
- coercibleTyConKey :: Unique
- ntTyConKey :: Unique
- errorMessageTypeErrorFamKey :: Unique
- typeNatLogTyFamNameKey :: Unique
- typeNatModTyFamNameKey :: Unique
- typeNatDivTyFamNameKey :: Unique
- typeNatCmpTyFamNameKey :: Unique
- typeSymbolCmpTyFamNameKey :: Unique
- typeNatSubTyFamNameKey :: Unique
- typeNatLeqTyFamNameKey :: Unique
- typeNatExpTyFamNameKey :: Unique
- typeNatMulTyFamNameKey :: Unique
- typeNatAddTyFamNameKey :: Unique
- typeSymbolKindConNameKey :: Unique
- typeNatKindConNameKey :: Unique
- uWordTyConKey :: Unique
- uIntTyConKey :: Unique
- uFloatTyConKey :: Unique
- uDoubleTyConKey :: Unique
- uCharTyConKey :: Unique
- uAddrTyConKey :: Unique
- uRecTyConKey :: Unique
- rep1TyConKey :: Unique
- repTyConKey :: Unique
- noSelTyConKey :: Unique
- s1TyConKey :: Unique
- c1TyConKey :: Unique
- d1TyConKey :: Unique
- rec0TyConKey :: Unique
- sTyConKey :: Unique
- cTyConKey :: Unique
- dTyConKey :: Unique
- rTyConKey :: Unique
- compTyConKey :: Unique
- prodTyConKey :: Unique
- sumTyConKey :: Unique
- m1TyConKey :: Unique
- k1TyConKey :: Unique
- rec1TyConKey :: Unique
- par1TyConKey :: Unique
- u1TyConKey :: Unique
- v1TyConKey :: Unique
- opaqueTyConKey :: Unique
- unknown3TyConKey :: Unique
- unknown2TyConKey :: Unique
- unknown1TyConKey :: Unique
- unknownTyConKey :: Unique
- frontendPluginTyConKey :: Unique
- pluginTyConKey :: Unique
- vecElemTyConKey :: Unique
- vecCountTyConKey :: Unique
- runtimeRepTyConKey :: Unique
- constraintKindTyConKey :: Unique
- tYPETyConKey :: Unique
- eitherTyConKey :: Unique
- objectTyConKey :: Unique
- compactPrimTyConKey :: Unique
- tVarPrimTyConKey :: Unique
- funPtrTyConKey :: Unique
- ptrTyConKey :: Unique
- bcoPrimTyConKey :: Unique
- threadIdPrimTyConKey :: Unique
- typeConKey :: Unique
- boxityConKey :: Unique
- kindConKey :: Unique
- anyBoxConKey :: Unique
- unliftedConKey :: Unique
- liftedConKey :: Unique
- word64TyConKey :: Unique
- word64PrimTyConKey :: Unique
- word32TyConKey :: Unique
- word32PrimTyConKey :: Unique
- word16TyConKey :: Unique
- word16PrimTyConKey :: Unique
- word8TyConKey :: Unique
- word8PrimTyConKey :: Unique
- wordTyConKey :: Unique
- wordPrimTyConKey :: Unique
- voidPrimTyConKey :: Unique
- ioTyConKey :: Unique
- mutVarPrimTyConKey :: Unique
- eqPhantPrimTyConKey :: Unique
- eqReprPrimTyConKey :: Unique
- eqPrimTyConKey :: Unique
- stableNameTyConKey :: Unique
- stableNamePrimTyConKey :: Unique
- statePrimTyConKey :: Unique
- mutableArrayArrayPrimTyConKey :: Unique
- arrayArrayPrimTyConKey :: Unique
- heqTyConKey :: Unique
- eqTyConKey :: Unique
- stablePtrTyConKey :: Unique
- stablePtrPrimTyConKey :: Unique
- realWorldTyConKey :: Unique
- rationalTyConKey :: Unique
- ratioTyConKey :: Unique
- mVarPrimTyConKey :: Unique
- orderingTyConKey :: Unique
- mutableByteArrayPrimTyConKey :: Unique
- mutableArrayPrimTyConKey :: Unique
- weakPrimTyConKey :: Unique
- maybeTyConKey :: Unique
- foreignObjPrimTyConKey :: Unique
- listTyConKey :: Unique
- naturalTyConKey :: Unique
- integerTyConKey :: Unique
- int64TyConKey :: Unique
- int64PrimTyConKey :: Unique
- int32TyConKey :: Unique
- int32PrimTyConKey :: Unique
- int16TyConKey :: Unique
- int16PrimTyConKey :: Unique
- int8TyConKey :: Unique
- int8PrimTyConKey :: Unique
- intTyConKey :: Unique
- intPrimTyConKey :: Unique
- funTyConKey :: Unique
- floatTyConKey :: Unique
- floatPrimTyConKey :: Unique
- doubleTyConKey :: Unique
- doublePrimTyConKey :: Unique
- charTyConKey :: Unique
- charPrimTyConKey :: Unique
- byteArrayPrimTyConKey :: Unique
- boolTyConKey :: Unique
- arrayPrimTyConKey :: Unique
- addrPrimTyConKey :: Unique
- hasFieldClassNameKey :: Unique
- ipClassKey :: Unique
- monoidClassKey :: Unique
- semigroupClassKey :: Unique
- isLabelClassNameKey :: Unique
- ghciIoClassKey :: Unique
- knownSymbolClassNameKey :: Unique
- knownNatClassNameKey :: Unique
- selectorClassKey :: Unique
- constructorClassKey :: Unique
- datatypeClassKey :: Unique
- gen1ClassKey :: Unique
- genClassKey :: Unique
- traversableClassKey :: Unique
- foldableClassKey :: Unique
- applicativeClassKey :: Unique
- isStringClassKey :: Unique
- randomGenClassKey :: Unique
- randomClassKey :: Unique
- monadPlusClassKey :: Unique
- monadFailClassKey :: Unique
- monadFixClassKey :: Unique
- typeable7ClassKey :: Unique
- typeable6ClassKey :: Unique
- typeable5ClassKey :: Unique
- typeable4ClassKey :: Unique
- typeable3ClassKey :: Unique
- typeable2ClassKey :: Unique
- typeable1ClassKey :: Unique
- typeableClassKey :: Unique
- ixClassKey :: Unique
- showClassKey :: Unique
- realFracClassKey :: Unique
- realFloatClassKey :: Unique
- realClassKey :: Unique
- readClassKey :: Unique
- ordClassKey :: Unique
- numClassKey :: Unique
- functorClassKey :: Unique
- dataClassKey :: Unique
- monadClassKey :: Unique
- integralClassKey :: Unique
- fractionalClassKey :: Unique
- floatingClassKey :: Unique
- eqClassKey :: Unique
- enumClassKey :: Unique
- boundedClassKey :: Unique
- mk_known_key_name :: NameSpace -> Module -> FastString -> Unique -> Name
- dcQual :: Module -> FastString -> Unique -> Name
- clsQual :: Module -> FastString -> Unique -> Name
- tcQual :: Module -> FastString -> Unique -> Name
- varQual :: Module -> FastString -> Unique -> Name
- fingerprintDataConName :: Name
- fromStaticPtrName :: Name
- staticPtrDataConName :: Name
- staticPtrTyConName :: Name
- staticPtrInfoDataConName :: Name
- staticPtrInfoTyConName :: Name
- makeStaticName :: Name
- frontendPluginTyConName :: Name
- pluginTyConName :: Name
- pLUGINS :: Module
- srcLocDataConName :: Name
- pushCallStackName :: Name
- emptyCallStackName :: Name
- callStackTyConName :: Name
- hasFieldClassName :: Name
- ipClassName :: Name
- isLabelClassName :: Name
- knownSymbolClassName :: Name
- knownNatClassName :: Name
- isStringClassName :: Name
- randomGenClassName :: Name
- randomClassName :: Name
- monadPlusClassName :: Name
- toAnnotationWrapperName :: Name
- mzipName :: Name
- liftMName :: Name
- guardMName :: Name
- loopAName :: Name
- choiceAName :: Name
- appAName :: Name
- firstAName :: Name
- composeAName :: Name
- arrAName :: Name
- mfixName :: Name
- monadFixClassName :: Name
- newStablePtrName :: Name
- stablePtrTyConName :: Name
- funPtrTyConName :: Name
- ptrTyConName :: Name
- word64TyConName :: Name
- word32TyConName :: Name
- word16TyConName :: Name
- int64TyConName :: Name
- int32TyConName :: Name
- int16TyConName :: Name
- int8TyConName :: Name
- failIOName :: Name
- returnIOName :: Name
- bindIOName :: Name
- thenIOName :: Name
- ioDataConName :: Name
- ioTyConName :: Name
- ghciStepIoMName :: Name
- ghciIoClassName :: Name
- genericClassNames :: [Name]
- selectorClassName :: Name
- constructorClassName :: Name
- datatypeClassName :: Name
- gen1ClassName :: Name
- genClassName :: Name
- readClassName :: Name
- showClassName :: Name
- toListName :: Name
- fromListNName :: Name
- fromListName :: Name
- isListClassName :: Name
- zipName :: Name
- filterName :: Name
- concatName :: Name
- boundedClassName :: Name
- enumFromThenToName :: Name
- enumFromThenName :: Name
- enumFromToName :: Name
- enumFromName :: Name
- enumClassName :: Name
- traceName :: Name
- assertErrorName :: Name
- dataClassName :: Name
- toDynName :: Name
- typeErrorShowTypeDataConName :: Name
- typeErrorVAppendDataConName :: Name
- typeErrorAppendDataConName :: Name
- typeErrorTextDataConName :: Name
- errorMessageTypeErrorFamName :: Name
- starArrStarArrStarKindRepName :: Name
- starArrStarKindRepName :: Name
- starKindRepName :: Name
- trGhcPrimModuleName :: Name
- typeSymbolTypeRepName :: Name
- typeNatTypeRepName :: Name
- mkTrFunName :: Name
- mkTrAppName :: Name
- mkTrConName :: Name
- mkTrTypeName :: Name
- typeRepIdName :: Name
- someTypeRepDataConName :: Name
- someTypeRepTyConName :: Name
- typeRepTyConName :: Name
- typeableClassName :: Name
- typeLitNatDataConName :: Name
- typeLitSymbolDataConName :: Name
- typeLitSortTyConName :: Name
- kindRepTypeLitDDataConName :: Name
- kindRepTypeLitSDataConName :: Name
- kindRepTYPEDataConName :: Name
- kindRepFunDataConName :: Name
- kindRepAppDataConName :: Name
- kindRepVarDataConName :: Name
- kindRepTyConAppDataConName :: Name
- kindRepTyConName :: Name
- trTyConDataConName :: Name
- trTyConTyConName :: Name
- trNameDDataConName :: Name
- trNameSDataConName :: Name
- trNameTyConName :: Name
- trModuleDataConName :: Name
- trModuleTyConName :: Name
- ixClassName :: Name
- rationalToDoubleName :: Name
- rationalToFloatName :: Name
- realFloatClassName :: Name
- floatingClassName :: Name
- realToFracName :: Name
- fromIntegralName :: Name
- toRationalName :: Name
- toIntegerName :: Name
- fromRationalName :: Name
- fractionalClassName :: Name
- realFracClassName :: Name
- integralClassName :: Name
- realClassName :: Name
- ratioDataConName :: Name
- ratioTyConName :: Name
- rationalTyConName :: Name
- wordToNaturalName :: Name
- mkNaturalName :: Name
- timesNaturalName :: Name
- minusNaturalName :: Name
- plusNaturalName :: Name
- naturalToIntegerName :: Name
- naturalFromIntegerName :: Name
- naturalSDataConName :: Name
- naturalTyConName :: Name
- bitIntegerName :: Name
- shiftRIntegerName :: Name
- shiftLIntegerName :: Name
- complementIntegerName :: Name
- xorIntegerName :: Name
- orIntegerName :: Name
- andIntegerName :: Name
- lcmIntegerName :: Name
- gcdIntegerName :: Name
- decodeDoubleIntegerName :: Name
- encodeDoubleIntegerName :: Name
- encodeFloatIntegerName :: Name
- doubleFromIntegerName :: Name
- floatFromIntegerName :: Name
- modIntegerName :: Name
- divIntegerName :: Name
- remIntegerName :: Name
- quotIntegerName :: Name
- divModIntegerName :: Name
- quotRemIntegerName :: Name
- compareIntegerName :: Name
- geIntegerPrimName :: Name
- ltIntegerPrimName :: Name
- gtIntegerPrimName :: Name
- leIntegerPrimName :: Name
- signumIntegerName :: Name
- absIntegerName :: Name
- neqIntegerPrimName :: Name
- eqIntegerPrimName :: Name
- negateIntegerName :: Name
- minusIntegerName :: Name
- integerToIntName :: Name
- integerToWordName :: Name
- wordToIntegerName :: Name
- smallIntegerName :: Name
- timesIntegerName :: Name
- plusIntegerName :: Name
- int64ToIntegerName :: Name
- word64ToIntegerName :: Name
- integerToInt64Name :: Name
- integerToWord64Name :: Name
- mkIntegerName :: Name
- integerSDataConName :: Name
- integerTyConName :: Name
- negateName :: Name
- minusName :: Name
- fromIntegerName :: Name
- numClassName :: Name
- sndName :: Name
- fstName :: Name
- fromStringName :: Name
- opaqueTyConName :: Name
- breakpointCondName :: Name
- breakpointName :: Name
- assertName :: Name
- appendName :: Name
- mapName :: Name
- augmentName :: Name
- buildName :: Name
- foldrName :: Name
- otherwiseIdName :: Name
- dollarName :: Name
- groupWithName :: Name
- alternativeClassKey :: Unique
- thenAClassOpKey :: Unique
- pureAClassOpKey :: Unique
- apAClassOpKey :: Unique
- joinMIdKey :: Unique
- alternativeClassName :: Name
- joinMName :: Name
- mconcatName :: Name
- mappendName :: Name
- memptyName :: Name
- monoidClassName :: Name
- sappendName :: Name
- semigroupClassName :: Name
- traversableClassName :: Name
- foldableClassName :: Name
- thenAName :: Name
- pureAName :: Name
- apAName :: Name
- applicativeClassName :: Name
- failMName :: Name
- monadFailClassName :: Name
- returnMName :: Name
- bindMName :: Name
- thenMName :: Name
- monadClassName :: Name
- fmapName :: Name
- functorClassName :: Name
- geName :: Name
- ordClassName :: Name
- eqName :: Name
- eqClassName :: Name
- inlineIdName :: Name
- eqStringName :: Name
- unpackCStringUtf8Name :: Name
- unpackCStringFoldrName :: Name
- unpackCStringName :: Name
- modIntName :: Name
- divIntName :: Name
- metaSelDataConName :: Name
- metaConsDataConName :: Name
- metaDataDataConName :: Name
- decidedUnpackDataConName :: Name
- decidedStrictDataConName :: Name
- decidedLazyDataConName :: Name
- noSourceStrictnessDataConName :: Name
- sourceStrictDataConName :: Name
- sourceLazyDataConName :: Name
- noSourceUnpackednessDataConName :: Name
- sourceNoUnpackDataConName :: Name
- sourceUnpackDataConName :: Name
- notAssociativeDataConName :: Name
- rightAssociativeDataConName :: Name
- leftAssociativeDataConName :: Name
- infixIDataConName :: Name
- prefixIDataConName :: Name
- uWordTyConName :: Name
- uIntTyConName :: Name
- uFloatTyConName :: Name
- uDoubleTyConName :: Name
- uCharTyConName :: Name
- uAddrTyConName :: Name
- uRecTyConName :: Name
- rep1TyConName :: Name
- repTyConName :: Name
- noSelTyConName :: Name
- s1TyConName :: Name
- c1TyConName :: Name
- d1TyConName :: Name
- rec0TyConName :: Name
- sTyConName :: Name
- cTyConName :: Name
- dTyConName :: Name
- rTyConName :: Name
- compTyConName :: Name
- prodTyConName :: Name
- sumTyConName :: Name
- m1TyConName :: Name
- k1TyConName :: Name
- rec1TyConName :: Name
- par1TyConName :: Name
- u1TyConName :: Name
- v1TyConName :: Name
- rightDataConName :: Name
- leftDataConName :: Name
- eitherTyConName :: Name
- specTyConName :: Name
- ordGTDataConName :: Name
- ordEQDataConName :: Name
- ordLTDataConName :: Name
- orderingTyConName :: Name
- runRWName :: Name
- runMainIOName :: Name
- wildCardName :: Name
- dataQual_RDR :: Module -> FastString -> RdrName
- clsQual_RDR :: Module -> FastString -> RdrName
- tcQual_RDR :: Module -> FastString -> RdrName
- varQual_RDR :: Module -> FastString -> RdrName
- mappend_RDR :: RdrName
- mempty_RDR :: RdrName
- traverse_RDR :: RdrName
- all_RDR :: RdrName
- null_RDR :: RdrName
- foldMap_RDR :: RdrName
- foldable_foldr_RDR :: RdrName
- liftA2_RDR :: RdrName
- ap_RDR :: RdrName
- pure_RDR :: RdrName
- replace_RDR :: RdrName
- fmap_RDR :: RdrName
- uWordHash_RDR :: RdrName
- uIntHash_RDR :: RdrName
- uFloatHash_RDR :: RdrName
- uDoubleHash_RDR :: RdrName
- uCharHash_RDR :: RdrName
- uAddrHash_RDR :: RdrName
- uWordDataCon_RDR :: RdrName
- uIntDataCon_RDR :: RdrName
- uFloatDataCon_RDR :: RdrName
- uDoubleDataCon_RDR :: RdrName
- uCharDataCon_RDR :: RdrName
- uAddrDataCon_RDR :: RdrName
- notAssocDataCon_RDR :: RdrName
- rightAssocDataCon_RDR :: RdrName
- leftAssocDataCon_RDR :: RdrName
- infixDataCon_RDR :: RdrName
- prefixDataCon_RDR :: RdrName
- conIsRecord_RDR :: RdrName
- conFixity_RDR :: RdrName
- conName_RDR :: RdrName
- selName_RDR :: RdrName
- isNewtypeName_RDR :: RdrName
- packageName_RDR :: RdrName
- moduleName_RDR :: RdrName
- datatypeName_RDR :: RdrName
- to1_RDR :: RdrName
- to_RDR :: RdrName
- from1_RDR :: RdrName
- from_RDR :: RdrName
- unComp1_RDR :: RdrName
- unK1_RDR :: RdrName
- unRec1_RDR :: RdrName
- unPar1_RDR :: RdrName
- comp1DataCon_RDR :: RdrName
- prodDataCon_RDR :: RdrName
- r1DataCon_RDR :: RdrName
- l1DataCon_RDR :: RdrName
- m1DataCon_RDR :: RdrName
- k1DataCon_RDR :: RdrName
- rec1DataCon_RDR :: RdrName
- par1DataCon_RDR :: RdrName
- u1DataCon_RDR :: RdrName
- error_RDR :: RdrName
- undefined_RDR :: RdrName
- showParen_RDR :: RdrName
- showCommaSpace_RDR :: RdrName
- showSpace_RDR :: RdrName
- showString_RDR :: RdrName
- shows_RDR :: RdrName
- showsPrec_RDR :: RdrName
- pfail_RDR :: RdrName
- prec_RDR :: RdrName
- reset_RDR :: RdrName
- alt_RDR :: RdrName
- step_RDR :: RdrName
- symbol_RDR :: RdrName
- ident_RDR :: RdrName
- punc_RDR :: RdrName
- readSymField_RDR :: RdrName
- readFieldHash_RDR :: RdrName
- readField_RDR :: RdrName
- expectP_RDR :: RdrName
- lexP_RDR :: RdrName
- choose_RDR :: RdrName
- parens_RDR :: RdrName
- readPrec_RDR :: RdrName
- readListPrecDefault_RDR :: RdrName
- readListPrec_RDR :: RdrName
- readListDefault_RDR :: RdrName
- readList_RDR :: RdrName
- unsafeRangeSize_RDR :: RdrName
- unsafeIndex_RDR :: RdrName
- index_RDR :: RdrName
- inRange_RDR :: RdrName
- range_RDR :: RdrName
- maxBound_RDR :: RdrName
- minBound_RDR :: RdrName
- pred_RDR :: RdrName
- succ_RDR :: RdrName
- getTag_RDR :: RdrName
- not_RDR :: RdrName
- and_RDR :: RdrName
- compose_RDR :: RdrName
- toList_RDR :: RdrName
- fromListN_RDR :: RdrName
- fromList_RDR :: RdrName
- fromString_RDR :: RdrName
- stringTy_RDR :: RdrName
- fromIntegral_RDR :: RdrName
- toRational_RDR :: RdrName
- toInteger_RDR :: RdrName
- plus_RDR :: RdrName
- times_RDR :: RdrName
- minus_RDR :: RdrName
- fromRational_RDR :: RdrName
- fromInteger_RDR :: RdrName
- returnIO_RDR :: RdrName
- bindIO_RDR :: RdrName
- newStablePtr_RDR :: RdrName
- unpackCStringUtf8_RDR :: RdrName
- unpackCStringFoldr_RDR :: RdrName
- unpackCString_RDR :: RdrName
- eqString_RDR :: RdrName
- ioDataCon_RDR :: RdrName
- timesInteger_RDR :: RdrName
- plusInteger_RDR :: RdrName
- ratioDataCon_RDR :: RdrName
- enumFromThenTo_RDR :: RdrName
- enumFromThen_RDR :: RdrName
- enumFromTo_RDR :: RdrName
- enumFrom_RDR :: RdrName
- toEnum_RDR :: RdrName
- fromEnum_RDR :: RdrName
- right_RDR :: RdrName
- left_RDR :: RdrName
- failM_RDR :: RdrName
- bindM_RDR :: RdrName
- returnM_RDR :: RdrName
- build_RDR :: RdrName
- foldr_RDR :: RdrName
- append_RDR :: RdrName
- map_RDR :: RdrName
- monadClass_RDR :: RdrName
- enumClass_RDR :: RdrName
- ordClass_RDR :: RdrName
- numClass_RDR :: RdrName
- eqClass_RDR :: RdrName
- gtTag_RDR :: RdrName
- eqTag_RDR :: RdrName
- ltTag_RDR :: RdrName
- compare_RDR :: RdrName
- gt_RDR :: RdrName
- lt_RDR :: RdrName
- le_RDR :: RdrName
- ge_RDR :: RdrName
- eq_RDR :: RdrName
- main_RDR_Unqual :: RdrName
- mkMainModule_ :: ModuleName -> Module
- mkMainModule :: FastString -> Module
- mkThisGhcModule_ :: ModuleName -> Module
- mkThisGhcModule :: FastString -> Module
- mkBaseModule_ :: ModuleName -> Module
- mkBaseModule :: FastString -> Module
- mkIntegerModule :: FastString -> Module
- mkPrimModule :: FastString -> Module
- dATA_ARRAY_PARALLEL_PRIM_NAME :: ModuleName
- dATA_ARRAY_PARALLEL_NAME :: ModuleName
- mAIN_NAME :: ModuleName
- pRELUDE_NAME :: ModuleName
- mkInteractiveModule :: Int -> Module
- rOOT_MAIN :: Module
- gHC_RECORDS :: Module
- gHC_OVER_LABELS :: Module
- gHC_FINGERPRINT_TYPE :: Module
- gHC_STATICPTR_INTERNAL :: Module
- gHC_STATICPTR :: Module
- gHC_STACK_TYPES :: Module
- gHC_STACK :: Module
- gHC_SRCLOC :: Module
- dEBUG_TRACE :: Module
- dATA_COERCE :: Module
- dATA_TYPE_EQUALITY :: Module
- gHC_TYPENATS :: Module
- gHC_TYPELITS :: Module
- gHC_GENERICS :: Module
- cONTROL_EXCEPTION_BASE :: Module
- gHC_EXTS :: Module
- rANDOM :: Module
- gHC_DESUGAR :: Module
- cONTROL_APPLICATIVE :: Module
- aRROW :: Module
- mONAD_FAIL :: Module
- mONAD_ZIP :: Module
- mONAD_FIX :: Module
- mONAD :: Module
- gHC_WORD :: Module
- gHC_INT :: Module
- lEX :: Module
- rEAD_PREC :: Module
- gENERICS :: Module
- tYPEABLE_INTERNAL :: Module
- tYPEABLE :: Module
- dYNAMIC :: Module
- sYSTEM_IO :: Module
- gHC_TOP_HANDLER :: Module
- gHC_FLOAT :: Module
- gHC_REAL :: Module
- gHC_ERR :: Module
- gHC_PTR :: Module
- gHC_STABLE :: Module
- gHC_IX :: Module
- gHC_ST :: Module
- gHC_IO_Exception :: Module
- gHC_IO :: Module
- gHC_CONC :: Module
- dATA_TRAVERSABLE :: Module
- dATA_FOLDABLE :: Module
- dATA_STRING :: Module
- dATA_LIST :: Module
- dATA_EITHER :: Module
- dATA_TUPLE :: Module
- gHC_TUPLE :: Module
- gHC_LIST :: Module
- gHC_NATURAL :: Module
- gHC_INTEGER_TYPE :: Module
- gHC_MAYBE :: Module
- gHC_NUM :: Module
- gHC_READ :: Module
- gHC_SHOW :: Module
- gHC_GHCI_HELPERS :: Module
- gHC_GHCI :: Module
- gHC_ENUM :: Module
- gHC_BASE :: Module
- gHC_PRIMOPWRAPPERS :: Module
- gHC_CLASSES :: Module
- gHC_CSTRING :: Module
- gHC_MAGIC :: Module
- gHC_TYPES :: Module
- gHC_PRIM :: Module
- pRELUDE :: Module
- genericTyConNames :: [Name]
- basicKnownKeyNames :: [Name]
- isUnboundName :: Name -> Bool
- mkUnboundName :: OccName -> Name
- itName :: Unique -> SrcSpan -> Name
- allNameStrings :: [String]
- mAIN :: Module
- liftedTypeKindTyConKey :: Unique
- hasKey :: Uniquable a => a -> Unique -> Bool
- class Uniquable a where
- starInfo :: Bool -> RdrName -> SDoc
- pprNameProvenance :: GlobalRdrElt -> SDoc
- isExplicitItem :: ImpItemSpec -> Bool
- importSpecModule :: ImportSpec -> ModuleName
- importSpecLoc :: ImportSpec -> SrcSpan
- qualSpecOK :: ModuleName -> ImportSpec -> Bool
- unQualSpecOK :: ImportSpec -> Bool
- bestImport :: [ImportSpec] -> ImportSpec
- shadowNames :: GlobalRdrEnv -> [Name] -> GlobalRdrEnv
- extendGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrElt -> GlobalRdrEnv
- transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv
- mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv
- plusGlobalRdrEnv :: GlobalRdrEnv -> GlobalRdrEnv -> GlobalRdrEnv
- pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)]
- pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt]
- unQualOK :: GlobalRdrElt -> Bool
- greLabel :: GlobalRdrElt -> Maybe FieldLabelString
- isOverloadedRecFldGRE :: GlobalRdrElt -> Bool
- isRecFldGRE :: GlobalRdrElt -> Bool
- isLocalGRE :: GlobalRdrElt -> Bool
- getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]]
- lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt
- lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt
- lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt
- lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt]
- greOccName :: GlobalRdrElt -> OccName
- lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt]
- pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc
- globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt]
- emptyGlobalRdrEnv :: GlobalRdrEnv
- availFromGRE :: GlobalRdrElt -> AvailInfo
- gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo]
- greParent_maybe :: GlobalRdrElt -> Maybe Name
- greSrcSpan :: GlobalRdrElt -> SrcSpan
- greRdrNames :: GlobalRdrElt -> [RdrName]
- greQualModName :: GlobalRdrElt -> ModuleName
- gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt]
- localGREsFromAvail :: AvailInfo -> [GlobalRdrElt]
- gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
- delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv
- inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool
- localRdrEnvElts :: LocalRdrEnv -> [Name]
- elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool
- lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name
- lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
- extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
- extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv
- emptyLocalRdrEnv :: LocalRdrEnv
- isExact_maybe :: RdrName -> Maybe Name
- isExact :: RdrName -> Bool
- isOrig_maybe :: RdrName -> Maybe (Module, OccName)
- isOrig :: RdrName -> Bool
- isQual_maybe :: RdrName -> Maybe (ModuleName, OccName)
- isQual :: RdrName -> Bool
- isUnqual :: RdrName -> Bool
- isSrcRdrName :: RdrName -> Bool
- isRdrTc :: RdrName -> Bool
- isRdrTyVar :: RdrName -> Bool
- isRdrDataCon :: RdrName -> Bool
- nameRdrName :: Name -> RdrName
- getRdrName :: NamedThing thing => thing -> RdrName
- mkQual :: NameSpace -> (FastString, FastString) -> RdrName
- mkVarUnqual :: FastString -> RdrName
- mkUnqual :: NameSpace -> FastString -> RdrName
- mkOrig :: Module -> OccName -> RdrName
- mkRdrQual :: ModuleName -> OccName -> RdrName
- mkRdrUnqual :: OccName -> RdrName
- demoteRdrName :: RdrName -> Maybe RdrName
- rdrNameSpace :: RdrName -> NameSpace
- rdrNameOcc :: RdrName -> OccName
- data RdrName
- data LocalRdrEnv
- type GlobalRdrEnv = OccEnv [GlobalRdrElt]
- data GlobalRdrElt
- data Parent
- data ImportSpec = ImpSpec {}
- data ImpDeclSpec = ImpDeclSpec {
- is_mod :: ModuleName
- is_as :: ModuleName
- is_qual :: Bool
- is_dloc :: SrcSpan
- data ImpItemSpec
- module RnSplice
- module RnNames
- module TcEnv
- wrapIP :: Type -> CoercionR
- unwrapIP :: Type -> CoercionR
- pprHsWrapper :: HsWrapper -> (Bool -> SDoc) -> SDoc
- evVarsOfTerm :: EvTerm -> VarSet
- findNeededEvVars :: EvBindMap -> VarSet -> VarSet
- evTermCoercion :: EvTerm -> TcCoercion
- evTermCoercion_maybe :: EvTerm -> Maybe TcCoercion
- isEmptyTcEvBinds :: TcEvBinds -> Bool
- emptyTcEvBinds :: TcEvBinds
- mkEvScSelectors :: Class -> [TcType] -> [(TcPredType, EvExpr)]
- mkEvCast :: EvExpr -> TcCoercion -> EvTerm
- evTypeable :: Type -> EvTypeable -> EvTerm
- evSelector :: Id -> [Type] -> [EvExpr] -> EvExpr
- evDataConApp :: DataCon -> [Type] -> [EvExpr] -> EvTerm
- evDFunApp :: DFunId -> [Type] -> [EvExpr] -> EvTerm
- evCast :: EvExpr -> TcCoercion -> EvTerm
- evCoercion :: TcCoercion -> EvTerm
- evId :: EvId -> EvExpr
- mkGivenEvBind :: EvVar -> EvTerm -> EvBind
- mkWantedEvBind :: EvVar -> EvTerm -> EvBind
- evBindVar :: EvBind -> EvVar
- filterEvBindMap :: (EvBind -> Bool) -> EvBindMap -> EvBindMap
- foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a
- evBindMapBinds :: EvBindMap -> Bag EvBind
- lookupEvBind :: EvBindMap -> EvVar -> Maybe EvBind
- isEmptyEvBindMap :: EvBindMap -> Bool
- extendEvBinds :: EvBindMap -> EvBind -> EvBindMap
- emptyEvBindMap :: EvBindMap
- isCoEvBindsVar :: EvBindsVar -> Bool
- collectHsWrapBinders :: HsWrapper -> ([Var], HsWrapper)
- isErasableHsWrapper :: HsWrapper -> Bool
- isIdHsWrapper :: HsWrapper -> Bool
- idHsWrapper :: HsWrapper
- mkWpLet :: TcEvBinds -> HsWrapper
- mkWpLams :: [Var] -> HsWrapper
- mkWpTyLams :: [TyVar] -> HsWrapper
- mkWpEvVarApps :: [EvVar] -> HsWrapper
- mkWpEvApps :: [EvTerm] -> HsWrapper
- mkWpTyApps :: [Type] -> HsWrapper
- mkWpCastN :: TcCoercionN -> HsWrapper
- mkWpCastR :: TcCoercionR -> HsWrapper
- mkWpFun :: HsWrapper -> HsWrapper -> TcType -> TcType -> SDoc -> HsWrapper
- maybeTcSubCo :: EqRel -> TcCoercion -> TcCoercion
- tcCoToMCo :: TcCoercion -> TcMCoercion
- isTcReflexiveCo :: TcCoercion -> Bool
- isTcGReflMCo :: TcMCoercion -> Bool
- isTcReflCo :: TcCoercion -> Bool
- coVarsOfTcCo :: TcCoercion -> TcTyCoVarSet
- tcCoercionRole :: TcCoercion -> Role
- tcCoercionKind :: TcCoercion -> Pair TcType
- mkTcCoVarCo :: CoVar -> TcCoercion
- mkTcKindCo :: TcCoercion -> TcCoercionN
- mkTcPhantomCo :: TcCoercionN -> TcType -> TcType -> TcCoercionP
- mkTcCoherenceRightCo :: Role -> TcType -> TcCoercionN -> TcCoercion -> TcCoercion
- mkTcCoherenceLeftCo :: Role -> TcType -> TcCoercionN -> TcCoercion -> TcCoercion
- mkTcGReflLeftCo :: Role -> TcType -> TcCoercionN -> TcCoercion
- mkTcGReflRightCo :: Role -> TcType -> TcCoercionN -> TcCoercion
- mkTcAxiomRuleCo :: CoAxiomRule -> [TcCoercion] -> TcCoercionR
- tcDowngradeRole :: Role -> Role -> TcCoercion -> TcCoercion
- mkTcSubCo :: TcCoercionN -> TcCoercionR
- mkTcLRCo :: LeftOrRight -> TcCoercion -> TcCoercion
- mkTcNthCo :: Role -> Int -> TcCoercion -> TcCoercion
- mkTcForAllCos :: [(TyVar, TcCoercionN)] -> TcCoercion -> TcCoercion
- mkTcForAllCo :: TyVar -> TcCoercionN -> TcCoercion -> TcCoercion
- mkTcUnbranchedAxInstCo :: CoAxiom Unbranched -> [TcType] -> [TcCoercion] -> TcCoercionR
- mkTcAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [TcType] -> [TcCoercion] -> TcCoercion
- mkTcFunCo :: Role -> TcCoercion -> TcCoercion -> TcCoercion
- mkTcAppCo :: TcCoercion -> TcCoercionN -> TcCoercion
- mkTcTyConAppCo :: Role -> TyCon -> [TcCoercion] -> TcCoercion
- mkTcRepReflCo :: TcType -> TcCoercionR
- mkTcNomReflCo :: TcType -> TcCoercionN
- mkTcTransCo :: TcCoercion -> TcCoercion -> TcCoercion
- mkTcSymCo :: TcCoercion -> TcCoercion
- mkTcReflCo :: Role -> TcType -> TcCoercion
- type TcCoercion = Coercion
- type TcCoercionN = CoercionN
- type TcCoercionR = CoercionR
- type TcCoercionP = CoercionP
- type TcMCoercion = MCoercion
- data HsWrapper
- data TcEvBinds
- = TcEvBinds EvBindsVar
- | EvBinds (Bag EvBind)
- data EvBindsVar
- newtype EvBindMap = EvBindMap {}
- data EvBind = EvBind {}
- data EvTerm
- type EvExpr = CoreExpr
- data EvTypeable
- data EvCallStack
- data CoercionHole
- data Role
- pickLR :: LeftOrRight -> (a, a) -> a
- data LeftOrRight
- isNextArgVisible :: TcType -> Bool
- isNextTyConArgVisible :: TyCon -> [Type] -> Bool
- tcTyConVisibilities :: TyCon -> [Bool]
- sizeTypes :: [Type] -> TypeSize
- sizeType :: Type -> TypeSize
- isFunPtrTy :: Type -> Bool
- isFFIPrimResultTy :: DynFlags -> Type -> Validity
- isFFIPrimArgumentTy :: DynFlags -> Type -> Validity
- isFFILabelTy :: Type -> Validity
- isFFIDynTy :: Type -> Type -> Validity
- isFFIExportResultTy :: Type -> Validity
- isFFIImportResultTy :: DynFlags -> Type -> Validity
- isFFIExternalTy :: Type -> Validity
- isFFIArgumentTy :: DynFlags -> Safety -> Type -> Validity
- isFFITy :: Type -> Bool
- tcSplitIOType_maybe :: Type -> Maybe (TyCon, Type)
- deNoteType :: Type -> Type
- isAlmostFunctionFree :: TcType -> Bool
- isRigidTy :: TcType -> Bool
- isTyVarHead :: TcTyVar -> TcType -> Bool
- isCallStackPred :: Class -> [Type] -> Maybe FastString
- isCallStackTy :: Type -> Bool
- isStringTy :: Type -> Bool
- isFloatingTy :: Type -> Bool
- isCharTy :: Type -> Bool
- isUnitTy :: Type -> Bool
- isBoolTy :: Type -> Bool
- isWordTy :: Type -> Bool
- isIntTy :: Type -> Bool
- isIntegerTy :: Type -> Bool
- isDoubleTy :: Type -> Bool
- isFloatTy :: Type -> Bool
- isOverloadedTy :: Type -> Bool
- isRhoExpTy :: ExpType -> Bool
- isRhoTy :: TcType -> Bool
- isSigmaTy :: TcType -> Bool
- isInsolubleOccursCheck :: EqRel -> TcTyVar -> TcType -> Bool
- isImprovementPred :: PredType -> Bool
- immSuperClasses :: Class -> [Type] -> [PredType]
- transSuperClasses :: PredType -> [PredType]
- mkMinimalBySCs :: (a -> PredType) -> [a] -> [a]
- pickCapturedPreds :: TyVarSet -> TcThetaType -> TcThetaType
- boxEqPred :: EqRel -> Type -> Type -> Maybe (Class, [Type])
- pickQuantifiablePreds :: TyVarSet -> TcThetaType -> TcThetaType
- evVarPred :: EvVar -> PredType
- hasTyVarHead :: Type -> Bool
- checkValidClsArgs :: Bool -> Class -> [KindOrType] -> Bool
- isTyVarClassPred :: PredType -> Bool
- pickyEqType :: TcType -> TcType -> Bool
- tcEqTypeVis :: TcType -> TcType -> Bool
- tcEqTypeNoKindCheck :: TcType -> TcType -> Bool
- tcEqType :: HasDebugCallStack => TcType -> TcType -> Bool
- tcEqKind :: HasDebugCallStack => TcKind -> TcKind -> Bool
- tcSplitMethodTy :: Type -> ([TyVar], PredType, Type)
- tcSplitDFunHead :: Type -> (Class, [Type])
- tcSplitDFunTy :: Type -> ([TyVar], [Type], Class, [Type])
- tcIsTyVarTy :: Type -> Bool
- tcGetTyVar :: String -> Type -> TyVar
- tcGetTyVar_maybe :: Type -> Maybe TyVar
- tcGetCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN)
- tcRepGetNumAppTys :: Type -> Arity
- tcSplitAppTys :: Type -> (Type, [Type])
- tcSplitAppTy :: Type -> (Type, Type)
- tcSplitAppTy_maybe :: Type -> Maybe (Type, Type)
- tcFunResultTyN :: HasDebugCallStack => Arity -> Type -> Type
- tcFunResultTy :: Type -> Type
- tcFunArgTy :: Type -> Type
- tcSplitFunTysN :: Arity -> TcRhoType -> Either Arity ([TcSigmaType], TcSigmaType)
- tcSplitFunTy_maybe :: Type -> Maybe (Type, Type)
- tcSplitFunTys :: Type -> ([Type], Type)
- tcSplitTyConApp :: Type -> (TyCon, [Type])
- tcTyConAppArgs :: Type -> [Type]
- tcTyConAppTyCon_maybe :: Type -> Maybe TyCon
- tcTyConAppTyCon :: Type -> TyCon
- tcDeepSplitSigmaTy_maybe :: TcSigmaType -> Maybe ([TcType], [TyVar], ThetaType, TcSigmaType)
- tcSplitNestedSigmaTys :: Type -> ([TyVar], ThetaType, Type)
- tcSplitSigmaTy :: Type -> ([TyVar], ThetaType, Type)
- tcSplitPhiTy :: Type -> (ThetaType, Type)
- tcSplitPredFunTy_maybe :: Type -> Maybe (PredType, Type)
- tcIsForAllTy :: Type -> Bool
- tcSplitForAllVarBndrs :: Type -> ([TyVarBinder], Type)
- tcSplitForAllTysSameVis :: ArgFlag -> Type -> ([TyVar], Type)
- tcSplitForAllTys :: Type -> ([TyVar], Type)
- tcSplitForAllTy_maybe :: Type -> Maybe (TyVarBinder, Type)
- tcSplitPiTy_maybe :: Type -> Maybe (TyBinder, Type)
- tcSplitPiTys :: Type -> ([TyBinder], Type)
- mkTcCastTy :: Type -> Coercion -> Type
- mkTcAppTy :: Type -> Type -> Type
- mkTcAppTys :: Type -> [Type] -> Type
- getDFunTyKey :: Type -> OccName
- mkPhiTy :: [PredType] -> Type -> Type
- mkSpecSigmaTy :: [TyVar] -> [PredType] -> Type -> Type
- mkInfSigmaTy :: [TyCoVar] -> [PredType] -> Type -> Type
- mkSigmaTy :: [TyCoVarBinder] -> [PredType] -> Type -> Type
- findDupTyVarTvs :: [(Name, TcTyVar)] -> [(Name, Name)]
- mkTyVarNamePairs :: [TyVar] -> [(Name, TyVar)]
- isRuntimeUnkSkol :: TyVar -> Bool
- isIndirect :: MetaDetails -> Bool
- isFlexi :: MetaDetails -> Bool
- isTyVarTyVar :: Var -> Bool
- setMetaTyVarTcLevel :: TcTyVar -> TcLevel -> TcTyVar
- metaTyVarRef :: TyVar -> IORef MetaDetails
- metaTyVarTcLevel_maybe :: TcTyVar -> Maybe TcLevel
- metaTyVarTcLevel :: TcTyVar -> TcLevel
- metaTyVarInfo :: TcTyVar -> MetaInfo
- isMetaTyVarTy :: TcType -> Bool
- isAmbiguousTyVar :: TcTyVar -> Bool
- isMetaTyVar :: TcTyVar -> Bool
- isOverlappableTyVar :: TcTyVar -> Bool
- isSkolemTyVar :: TcTyVar -> Bool
- isFlattenTyVar :: TcTyVar -> Bool
- isFskTyVar :: TcTyVar -> Bool
- isFmvTyVar :: TcTyVar -> Bool
- isTyConableTyVar :: TcTyVar -> Bool
- isImmutableTyVar :: TyVar -> Bool
- isFloatedTouchableMetaTyVar :: TcLevel -> TcTyVar -> Bool
- isTouchableMetaTyVar :: TcLevel -> TcTyVar -> Bool
- tcIsTcTyVar :: TcTyVar -> Bool
- anyRewritableTyVar :: Bool -> EqRel -> (EqRel -> TcTyVar -> Bool) -> TcType -> Bool
- isTyFamFree :: Type -> Bool
- tcTyConAppTyFamInstsAndVis :: TyCon -> [Type] -> [(Bool, TyCon, [Type])]
- tcTyFamInstsAndVis :: Type -> [(Bool, TyCon, [Type])]
- tcTyFamInsts :: Type -> [(TyCon, [Type])]
- promoteSkolemsX :: TcLevel -> TCvSubst -> [TcTyVar] -> (TCvSubst, [TcTyVar])
- promoteSkolemX :: TcLevel -> TCvSubst -> TcTyVar -> (TCvSubst, TcTyVar)
- promoteSkolem :: TcLevel -> TcTyVar -> TcTyVar
- tcTypeLevel :: TcType -> TcLevel
- tcTyVarLevel :: TcTyVar -> TcLevel
- sameDepthAs :: TcLevel -> TcLevel -> Bool
- strictlyDeeperThan :: TcLevel -> TcLevel -> Bool
- pushTcLevel :: TcLevel -> TcLevel
- isTopTcLevel :: TcLevel -> Bool
- topTcLevel :: TcLevel
- maxTcLevel :: TcLevel -> TcLevel -> TcLevel
- superSkolemTv :: TcTyVarDetails
- mkSynFunTys :: [SyntaxOpType] -> ExpType -> SyntaxOpType
- synKnownType :: TcType -> SyntaxOpType
- mkCheckExpType :: TcType -> ExpType
- type TcCoVar = CoVar
- type TcType = Type
- type TcTyCoVar = Var
- type TcTyVarBinder = TyVarBinder
- type TcTyCon = TyCon
- type TcPredType = PredType
- type TcThetaType = ThetaType
- type TcSigmaType = TcType
- type TcRhoType = TcType
- type TcTauType = TcType
- type TcKind = Kind
- type TcTyVarSet = TyVarSet
- type TcTyCoVarSet = TyCoVarSet
- type TcDTyVarSet = DTyVarSet
- type TcDTyCoVarSet = DTyCoVarSet
- data ExpType
- = Check TcType
- | Infer !InferResult
- data InferResult = IR {}
- type ExpSigmaType = ExpType
- type ExpRhoType = ExpType
- data SyntaxOpType
- data MetaInfo
- = TauTv
- | TyVarTv
- | FlatMetaTv
- | FlatSkolTv
- newtype TcLevel = TcLevel Int
- type TypeSize = IntWithInf
- orphNamesOfCoCon :: forall (br :: BranchFlag). CoAxiom br -> NameSet
- orphNamesOfCo :: Coercion -> NameSet
- orphNamesOfTypes :: [Type] -> NameSet
- orphNamesOfType :: Type -> NameSet
- hasIPPred :: PredType -> Bool
- isIPPred :: PredType -> Bool
- isEqPrimPred :: PredType -> Bool
- isEqPred :: PredType -> Bool
- isClassPred :: PredType -> Bool
- isEqPredClass :: Class -> Bool
- mkClassPred :: Class -> [Type] -> PredType
- classifiesTypeWithValues :: Kind -> Bool
- isKindLevPoly :: Kind -> Bool
- tcTypeKind :: HasDebugCallStack => Type -> Kind
- nonDetCmpTypes :: [Type] -> [Type] -> Ordering
- nonDetCmpType :: Type -> Type -> Ordering
- eqTypes :: [Type] -> [Type] -> Bool
- eqTypeX :: RnEnv2 -> Type -> Type -> Bool
- isPrimitiveType :: Type -> Bool
- isUnboxedTupleType :: Type -> Bool
- isUnliftedType :: HasDebugCallStack => Type -> Bool
- closeOverKindsDSet :: DTyVarSet -> DTyVarSet
- closeOverKinds :: TyVarSet -> TyVarSet
- isTauTy :: Type -> Bool
- mkSpecForAllTys :: [TyVar] -> Type -> Type
- mkInvForAllTys :: [TyVar] -> Type -> Type
- mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type
- mkInvForAllTy :: TyVar -> Type -> Type
- mkTyCoInvForAllTy :: TyCoVar -> Type -> Type
- nextRole :: Type -> Role
- tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type])
- mkTyConApp :: TyCon -> [Type] -> Type
- tcRepSplitAppTy_maybe :: Type -> Maybe (Type, Type)
- mkAppTys :: Type -> [Type] -> Type
- isTyVarTy :: Type -> Bool
- getTyVar :: String -> Type -> TyVar
- isRuntimeRepVar :: TyVar -> Bool
- isUnliftedTypeKind :: Kind -> Bool
- substTyVarBndr :: HasCallStack => TCvSubst -> TyVar -> (TCvSubst, TyVar)
- substCoUnchecked :: TCvSubst -> Coercion -> Coercion
- lookupTyVar :: TCvSubst -> TyVar -> Maybe Type
- substThetaUnchecked :: TCvSubst -> ThetaType -> ThetaType
- substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType
- substTysUnchecked :: TCvSubst -> [Type] -> [Type]
- substTys :: HasCallStack => TCvSubst -> [Type] -> [Type]
- substTyUnchecked :: TCvSubst -> Type -> Type
- substTy :: HasCallStack => TCvSubst -> Type -> Type
- substTyAddInScope :: TCvSubst -> Type -> Type
- substTyWithCoVars :: [CoVar] -> [Coercion] -> Type -> Type
- substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion
- substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type
- substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type
- zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv
- zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv
- mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst
- zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst
- unionTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst
- extendTvSubstAndInScope :: TCvSubst -> TyVar -> Type -> TCvSubst
- extendTvSubst :: TCvSubst -> TyVar -> Type -> TCvSubst
- extendTCvSubst :: TCvSubst -> TyCoVar -> Type -> TCvSubst
- extendTCvInScopeSet :: TCvSubst -> VarSet -> TCvSubst
- extendTCvInScopeList :: TCvSubst -> [Var] -> TCvSubst
- extendTCvInScope :: TCvSubst -> Var -> TCvSubst
- setTvSubstEnv :: TCvSubst -> TvSubstEnv -> TCvSubst
- notElemTCvSubst :: Var -> TCvSubst -> Bool
- isInScope :: Var -> TCvSubst -> Bool
- getTCvInScope :: TCvSubst -> InScopeSet
- getTvSubstEnv :: TCvSubst -> TvSubstEnv
- mkTvSubst :: InScopeSet -> TvSubstEnv -> TCvSubst
- mkTCvSubst :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> TCvSubst
- mkEmptyTCvSubst :: InScopeSet -> TCvSubst
- emptyTCvSubst :: TCvSubst
- data TCvSubst = TCvSubst InScopeSet TvSubstEnv CvSubstEnv
- type TvSubstEnv = TyVarEnv Type
- pprTypeApp :: TyCon -> [Type] -> SDoc
- pprTCvBndr :: TyCoVarBinder -> SDoc
- pprTCvBndrs :: [TyCoVarBinder] -> SDoc
- pprSigmaType :: Type -> SDoc
- pprThetaArrowTy :: ThetaType -> SDoc
- pprParendTheta :: ThetaType -> SDoc
- pprTheta :: ThetaType -> SDoc
- pprClassPred :: Class -> [Type] -> SDoc
- pprParendKind :: Kind -> SDoc
- pprParendType :: Type -> SDoc
- scopedSort :: [TyCoVar] -> [TyCoVar]
- noFreeVarsOfType :: Type -> Bool
- tyCoFVsOfTypes :: [Type] -> FV
- tyCoFVsOfType :: Type -> FV
- exactTyCoVarsOfTypes :: [Type] -> TyVarSet
- exactTyCoVarsOfType :: Type -> TyCoVarSet
- tyCoVarsOfTypesList :: [Type] -> [TyCoVar]
- tyCoVarsOfTypesDSet :: [Type] -> DTyCoVarSet
- tyCoVarsOfTypeList :: Type -> [TyCoVar]
- tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet
- tyCoVarsOfTypes :: [Type] -> TyCoVarSet
- tyCoVarsOfType :: Type -> TyCoVarSet
- mkTyConTy :: TyCon -> Type
- mkForAllTys :: [TyCoVarBinder] -> Type -> Type
- mkInvisFunTys :: [Type] -> Type -> Type
- mkInvisFunTy :: Type -> Type -> Type
- mkVisFunTy :: Type -> Type -> Type
- mkTyCoVarTys :: [TyCoVar] -> [Type]
- mkTyCoVarTy :: TyCoVar -> Type
- mkTyVarTys :: [TyVar] -> [Type]
- mkTyVarTy :: TyVar -> Type
- isVisibleBinder :: TyCoBinder -> Bool
- isInvisibleBinder :: TyCoBinder -> Bool
- tyThingCategory :: TyThing -> String
- pprTyThingCategory :: TyThing -> SDoc
- type KnotTied ty = ty
- isPredTy :: HasDebugCallStack => Type -> Bool
- mkAppTy :: Type -> Type -> Type
- eqType :: Type -> Type -> Bool
- coreView :: Type -> Maybe Type
- tcView :: Type -> Maybe Type
- isLiftedTypeKind :: Kind -> Bool
- isTauTyCon :: TyCon -> Bool
- type TcTyVar = Var
- data ForallVisFlag
- liftedTypeKind :: Kind
- constraintKind :: Kind
- pprType :: Type -> SDoc
- pprKind :: Kind -> SDoc
- mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type
- data Type
- data TyCoBinder
- type PredType = Type
- type Kind = Type
- type ThetaType = [PredType]
- data ArgFlag
- data AnonArgFlag
- pprTcTyVarDetails :: TcTyVarDetails -> SDoc
- vanillaSkolemTv :: TcTyVarDetails
- data MetaDetails
- data TcTyVarDetails
- module TcRnTypes
- module TcRnDriver
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- getCCIndexM :: ContainsCostCentreState gbl => FastString -> TcRnIf gbl lcl CostCentreIndex
- setImplicitEnvM :: TypeEnv -> IfL a -> IfL a
- forkM :: SDoc -> IfL a -> IfL a
- forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a)
- failIfM :: MsgDoc -> IfL a
- getIfModule :: IfL Module
- initIfaceLclWithSubst :: Module -> SDoc -> Bool -> NameShape -> IfL a -> IfM lcl a
- initIfaceLcl :: Module -> SDoc -> Bool -> IfL a -> IfM lcl a
- initIfaceCheck :: SDoc -> HscEnv -> IfG a -> IO a
- initIfaceLoad :: HscEnv -> IfG a -> IO a
- initIfaceTcRn :: IfG a -> TcRn a
- mkIfLclEnv :: Module -> SDoc -> Bool -> IfLclEnv
- setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a
- getLocalRdrEnv :: RnM LocalRdrEnv
- fixSafeInstances :: SafeHaskellMode -> [ClsInst] -> [ClsInst]
- finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode
- recordUnsafeInfer :: WarningMessages -> TcM ()
- addModFinalizersWithLclEnv :: ThModFinalizers -> TcM ()
- setStage :: ThStage -> TcM a -> TcRn a
- getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, ThLevel, ThStage))
- getStage :: TcM ThStage
- keepAlive :: Name -> TcRn ()
- getTopLevelSpliceLocs :: TcM (Set RealSrcSpan)
- recordTopLevelSpliceLoc :: SrcSpan -> TcM ()
- recordThSpliceUse :: TcM ()
- recordThUse :: TcM ()
- emitNamedWildCardHoleConstraints :: [(Name, TcTyVar)] -> TcM ()
- emitAnonWildCardHoleConstraint :: TcTyVar -> TcM ()
- traceTcConstraints :: String -> TcM ()
- setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a
- getLclTypeEnv :: TcM TcTypeEnv
- isTouchableTcM :: TcTyVar -> TcM Bool
- setTcLevel :: TcLevel -> TcM a -> TcM a
- getTcLevel :: TcM TcLevel
- pushTcLevelsM :: Int -> TcM a -> TcM (a, TcLevel)
- pushTcLevelM :: TcM a -> TcM (TcLevel, a)
- pushTcLevelM_ :: TcM a -> TcM a
- pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a)
- discardConstraints :: TcM a -> TcM a
- emitInsoluble :: Ct -> TcM ()
- emitImplications :: Bag Implication -> TcM ()
- emitImplication :: Implication -> TcM ()
- emitSimples :: Cts -> TcM ()
- emitSimple :: Ct -> TcM ()
- emitConstraints :: WantedConstraints -> TcM ()
- emitStaticConstraints :: WantedConstraints -> TcM ()
- setConstraintVar :: TcRef WantedConstraints -> TcM a -> TcM a
- getConstraintVar :: TcM (TcRef WantedConstraints)
- chooseUniqueOccTc :: (OccSet -> OccName) -> TcM OccName
- addTcEvBind :: EvBindsVar -> EvBind -> TcM ()
- setTcEvBindsMap :: EvBindsVar -> EvBindMap -> TcM ()
- getTcEvBindsMap :: EvBindsVar -> TcM EvBindMap
- getTcEvTyCoVars :: EvBindsVar -> TcM TyCoVarSet
- cloneEvBindsVar :: EvBindsVar -> TcM EvBindsVar
- newNoTcEvBinds :: TcM EvBindsVar
- newTcEvBinds :: TcM EvBindsVar
- addTopEvBinds :: Bag EvBind -> TcM a -> TcM a
- debugTc :: TcM () -> TcM ()
- mkErrInfo :: TidyEnv -> [ErrCtxt] -> TcM SDoc
- add_warn :: WarnReason -> MsgDoc -> MsgDoc -> TcRn ()
- addWarnAt :: WarnReason -> SrcSpan -> MsgDoc -> TcRn ()
- addWarn :: WarnReason -> MsgDoc -> TcRn ()
- addWarnTcM :: WarnReason -> (TidyEnv, MsgDoc) -> TcM ()
- addWarnTc :: WarnReason -> MsgDoc -> TcM ()
- warnTcM :: WarnReason -> Bool -> (TidyEnv, MsgDoc) -> TcM ()
- warnTc :: WarnReason -> Bool -> MsgDoc -> TcM ()
- warnIf :: Bool -> MsgDoc -> TcRn ()
- warnIfFlag :: WarningFlag -> Bool -> MsgDoc -> TcRn ()
- failIfTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM ()
- failIfTc :: Bool -> MsgDoc -> TcM ()
- checkTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM ()
- checkTc :: Bool -> MsgDoc -> TcM ()
- failWithTcM :: (TidyEnv, MsgDoc) -> TcM a
- failWithTc :: MsgDoc -> TcM a
- mkErrTc :: MsgDoc -> TcM ErrMsg
- mkErrTcM :: (TidyEnv, MsgDoc) -> TcM ErrMsg
- addErrTcM :: (TidyEnv, MsgDoc) -> TcM ()
- addErrsTc :: [MsgDoc] -> TcM ()
- addErrTc :: MsgDoc -> TcM ()
- tryTcDiscardingErrs :: TcM r -> TcM r -> TcM r
- discardErrs :: TcRn a -> TcRn a
- tryTc :: TcRn a -> TcRn (Maybe a, Messages)
- foldAndRecoverM :: (b -> a -> TcRn b) -> b -> [a] -> TcRn b
- mapAndReportM :: (a -> TcRn b) -> [a] -> TcRn [b]
- mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b]
- recoverM :: TcRn r -> TcRn r -> TcRn r
- attemptM :: TcRn r -> TcRn (Maybe r)
- captureConstraints :: TcM a -> TcM (a, WantedConstraints)
- tryCaptureConstraints :: TcM a -> TcM (Maybe a, WantedConstraints)
- askNoErrs :: TcRn a -> TcRn (a, Bool)
- setCtLocM :: CtLoc -> TcM a -> TcM a
- getCtLocM :: CtOrigin -> Maybe TypeOrKind -> TcM CtLoc
- popErrCtxt :: TcM a -> TcM a
- updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> TcM a -> TcM a
- addLandmarkErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a
- addLandmarkErrCtxt :: MsgDoc -> TcM a -> TcM a
- addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a
- addErrCtxt :: MsgDoc -> TcM a -> TcM a
- setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a
- getErrCtxt :: TcM [ErrCtxt]
- failIfErrsM :: TcRn ()
- ifErrsM :: TcRn r -> TcRn r -> TcRn r
- whenNoErrs :: TcM () -> TcM ()
- checkNoErrs :: TcM r -> TcM r
- reportWarning :: WarnReason -> ErrMsg -> TcRn ()
- reportError :: ErrMsg -> TcRn ()
- reportErrors :: [ErrMsg] -> TcM ()
- addLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ()
- mkErrDocAt :: SrcSpan -> ErrDoc -> TcRn ErrMsg
- mkLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ErrMsg
- discardWarnings :: TcRn a -> TcRn a
- addMessages :: Messages -> TcRn ()
- checkErr :: Bool -> MsgDoc -> TcRn ()
- addErrs :: [(SrcSpan, MsgDoc)] -> TcRn ()
- addErrAt :: SrcSpan -> MsgDoc -> TcRn ()
- failAt :: SrcSpan -> MsgDoc -> TcRn a
- failWith :: MsgDoc -> TcRn a
- addErr :: MsgDoc -> TcRn ()
- setErrsVar :: TcRef Messages -> TcRn a -> TcRn a
- getErrsVar :: TcRn (TcRef Messages)
- wrapLocM_ :: HasSrcSpan a => (SrcSpanLess a -> TcM ()) -> a -> TcM ()
- wrapLocSndM :: (HasSrcSpan a, HasSrcSpan c) => (SrcSpanLess a -> TcM (b, SrcSpanLess c)) -> a -> TcM (b, c)
- wrapLocFstM :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> TcM (SrcSpanLess b, c)) -> a -> TcM (b, c)
- wrapLocM :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> TcM (SrcSpanLess b)) -> a -> TcM b
- addLocM :: HasSrcSpan a => (SrcSpanLess a -> TcM b) -> a -> TcM b
- setSrcSpan :: SrcSpan -> TcRn a -> TcRn a
- getSrcSpanM :: TcRn SrcSpan
- addDependentFiles :: [FilePath] -> TcRn ()
- getDeclaredDefaultTys :: TcRn (Maybe [Type])
- getRecFieldEnv :: TcRn RecFieldEnv
- extendFixityEnv :: [(Name, FixItem)] -> RnM a -> RnM a
- getFixityEnv :: TcRn FixityEnv
- getImports :: TcRn ImportAvails
- getRdrEnvs :: TcRn (GlobalRdrEnv, LocalRdrEnv)
- getGlobalRdrEnv :: TcRn GlobalRdrEnv
- tcSelfBootInfo :: TcRn SelfBootInfo
- tcIsHsig :: TcRn Bool
- tcIsHsBootOrSig :: TcRn Bool
- getInteractivePrintName :: TcRn Name
- getGHCiMonad :: TcRn Name
- getIsGHCi :: TcRn Bool
- traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n ()
- traceHiDiffs :: SDoc -> TcRnIf m n ()
- traceIf :: SDoc -> TcRnIf m n ()
- printForUserTcRn :: SDoc -> TcRn ()
- getPrintUnqualified :: DynFlags -> TcRn PrintUnqualified
- traceTcRnWithStyle :: PprStyle -> DynFlags -> DumpFlag -> SDoc -> TcRn ()
- traceTcRnForUser :: DumpFlag -> SDoc -> TcRn ()
- traceTcRn :: DumpFlag -> SDoc -> TcRn ()
- traceOptTcRn :: DumpFlag -> SDoc -> TcRn ()
- traceRn :: String -> SDoc -> TcRn ()
- traceTc :: String -> SDoc -> TcRn ()
- updTcRef :: TcRef a -> (a -> a) -> TcRnIf gbl lcl ()
- writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl ()
- readTcRef :: TcRef a -> TcRnIf gbl lcl a
- newTcRef :: a -> TcRnIf gbl lcl (TcRef a)
- newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId]
- newSysLocalId :: FastString -> TcType -> TcRnIf gbl lcl TcId
- newSysName :: OccName -> TcRnIf gbl lcl Name
- newNameAt :: OccName -> SrcSpan -> TcM Name
- newName :: OccName -> TcM Name
- cloneLocalName :: Name -> TcM Name
- newUniqueSupply :: TcRnIf gbl lcl UniqSupply
- newUnique :: TcRnIf gbl lcl Unique
- escapeArrowScope :: TcM a -> TcM a
- newArrowScope :: TcM a -> TcM a
- withException :: TcRnIf gbl lcl (MaybeErr MsgDoc a) -> TcRnIf gbl lcl a
- getEpsAndHpt :: TcRnIf gbl lcl (ExternalPackageState, HomePackageTable)
- getHpt :: TcRnIf gbl lcl HomePackageTable
- updateEps_ :: (ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl ()
- updateEps :: (ExternalPackageState -> (ExternalPackageState, a)) -> TcRnIf gbl lcl a
- getEps :: TcRnIf gbl lcl ExternalPackageState
- getEpsVar :: TcRnIf gbl lcl (TcRef ExternalPackageState)
- withDoDynamicToo :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- getGhcMode :: TcRnIf gbl lcl GhcMode
- unlessXOptM :: Extension -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- whenXOptM :: Extension -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- whenWOptM :: WarningFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- whenDOptM :: DumpFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- unsetXOptM :: Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- setXOptM :: Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- woptM :: WarningFlag -> TcRnIf gbl lcl Bool
- goptM :: GeneralFlag -> TcRnIf gbl lcl Bool
- doptM :: DumpFlag -> TcRnIf gbl lcl Bool
- xoptM :: Extension -> TcRnIf gbl lcl Bool
- setEnvs :: (gbl', lcl') -> TcRnIf gbl' lcl' a -> TcRnIf gbl lcl a
- getEnvs :: TcRnIf gbl lcl (gbl, lcl)
- setLclEnv :: lcl' -> TcRnIf gbl lcl' a -> TcRnIf gbl lcl a
- updLclEnv :: (lcl -> lcl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- getLclEnv :: TcRnIf gbl lcl lcl
- setGblEnv :: gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- updGblEnv :: (gbl -> gbl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- getGblEnv :: TcRnIf gbl lcl gbl
- updTopEnv :: (HscEnv -> HscEnv) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- getTopEnv :: TcRnIf gbl lcl HscEnv
- discardResult :: TcM a -> TcM ()
- initTcRnIf :: Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a
- initTcInteractive :: HscEnv -> TcM a -> IO (Messages, Maybe a)
- initTcWithGbl :: HscEnv -> TcGblEnv -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r)
- initTc :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r)
- class ContainsCostCentreState e where
- getRoleAnnots :: [Name] -> RoleAnnotEnv -> [LRoleAnnotDecl GhcRn]
- lookupRoleAnnot :: RoleAnnotEnv -> Name -> Maybe (LRoleAnnotDecl GhcRn)
- emptyRoleAnnotEnv :: RoleAnnotEnv
- mkRoleAnnotEnv :: [LRoleAnnotDecl GhcRn] -> RoleAnnotEnv
- getEvBindsTcPluginM :: TcPluginM EvBindsVar
- unsafeTcPluginTcM :: TcM a -> TcPluginM a
- runTcPluginM :: TcPluginM a -> EvBindsVar -> TcM a
- hasCompleteSig :: TcSigFun -> Name -> Bool
- isPartialSig :: TcIdSigInst -> Bool
- plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails
- emptyImportAvails :: ImportAvails
- modDepsElts :: ModuleNameEnv (ModuleName, IsBootInterface) -> [(ModuleName, IsBootInterface)]
- mkModDeps :: [(ModuleName, IsBootInterface)] -> ModuleNameEnv (ModuleName, IsBootInterface)
- pprPECategory :: PromotionErr -> SDoc
- pprTcTyThingCategory :: TcTyThing -> SDoc
- thLevel :: ThStage -> ThLevel
- outerLevel :: ThLevel
- impLevel :: ThLevel
- topSpliceStage :: ThStage
- topAnnStage :: ThStage
- topStage :: ThStage
- removeBindingShadowing :: HasOccName a => [a] -> [a]
- pushErrCtxtSameOrigin :: ErrCtxt -> CtLoc -> CtLoc
- pushErrCtxt :: CtOrigin -> ErrCtxt -> CtLoc -> CtLoc
- tcVisibleOrphanMods :: TcGblEnv -> ModuleSet
- data NameShape = NameShape {
- ns_mod_name :: ModuleName
- ns_exports :: [AvailInfo]
- ns_map :: OccEnv Name
- type TcRnIf a b = IOEnv (Env a b)
- type TcRn = TcRnIf TcGblEnv TcLclEnv
- type IfM lcl = TcRnIf IfGblEnv lcl
- type IfG = IfM ()
- type IfL = IfM IfLclEnv
- type DsM = TcRnIf DsGblEnv DsLclEnv
- type RnM = TcRn
- type TcM = TcRn
- data Env gbl lcl = Env {}
- data IfGblEnv = IfGblEnv {}
- data IfLclEnv = IfLclEnv {}
- data DsGblEnv = DsGblEnv {}
- data DsLclEnv = DsLclEnv {}
- type DsMetaEnv = NameEnv DsMetaVal
- data DsMetaVal
- data FrontendResult = FrontendTypecheck TcGblEnv
- data TcGblEnv = TcGblEnv {
- tcg_mod :: Module
- tcg_semantic_mod :: Module
- tcg_src :: HscSource
- tcg_rdr_env :: GlobalRdrEnv
- tcg_default :: Maybe [Type]
- tcg_fix_env :: FixityEnv
- tcg_field_env :: RecFieldEnv
- tcg_type_env :: TypeEnv
- tcg_type_env_var :: TcRef TypeEnv
- tcg_inst_env :: !InstEnv
- tcg_fam_inst_env :: !FamInstEnv
- tcg_ann_env :: AnnEnv
- tcg_exports :: [AvailInfo]
- tcg_imports :: ImportAvails
- tcg_dus :: DefUses
- tcg_used_gres :: TcRef [GlobalRdrElt]
- tcg_keep :: TcRef NameSet
- tcg_th_used :: TcRef Bool
- tcg_th_splice_used :: TcRef Bool
- tcg_th_top_level_locs :: TcRef (Set RealSrcSpan)
- tcg_dfun_n :: TcRef OccSet
- tcg_merged :: [(Module, Fingerprint)]
- tcg_rn_exports :: Maybe [(Located (IE GhcRn), Avails)]
- tcg_rn_imports :: [LImportDecl GhcRn]
- tcg_rn_decls :: Maybe (HsGroup GhcRn)
- tcg_dependent_files :: TcRef [FilePath]
- tcg_th_topdecls :: TcRef [LHsDecl GhcPs]
- tcg_th_foreign_files :: TcRef [(ForeignSrcLang, FilePath)]
- tcg_th_topnames :: TcRef NameSet
- tcg_th_modfinalizers :: TcRef [(TcLclEnv, ThModFinalizers)]
- tcg_th_coreplugins :: TcRef [String]
- tcg_th_state :: TcRef (Map TypeRep Dynamic)
- tcg_th_remote_state :: TcRef (Maybe (ForeignRef (IORef QState)))
- tcg_ev_binds :: Bag EvBind
- tcg_tr_module :: Maybe Id
- tcg_binds :: LHsBinds GhcTc
- tcg_sigs :: NameSet
- tcg_imp_specs :: [LTcSpecPrag]
- tcg_warns :: Warnings
- tcg_anns :: [Annotation]
- tcg_tcs :: [TyCon]
- tcg_insts :: [ClsInst]
- tcg_fam_insts :: [FamInst]
- tcg_rules :: [LRuleDecl GhcTc]
- tcg_fords :: [LForeignDecl GhcTc]
- tcg_patsyns :: [PatSyn]
- tcg_doc_hdr :: Maybe LHsDocString
- tcg_hpc :: !AnyHpcUsage
- tcg_self_boot :: SelfBootInfo
- tcg_main :: Maybe Name
- tcg_safeInfer :: TcRef (Bool, WarningMessages)
- tcg_tc_plugins :: [TcPluginSolver]
- tcg_hf_plugins :: [HoleFitPlugin]
- tcg_top_loc :: RealSrcSpan
- tcg_static_wc :: TcRef WantedConstraints
- tcg_complete_matches :: [CompleteMatch]
- tcg_cc_st :: TcRef CostCentreState
- type RecFieldEnv = NameEnv [FieldLabel]
- data SelfBootInfo
- = NoSelfBoot
- | SelfBoot {
- sb_mds :: ModDetails
- sb_tcs :: NameSet
- type ErrCtxt = (Bool, TidyEnv -> TcM (TidyEnv, MsgDoc))
- type TcTypeEnv = NameEnv TcTyThing
- type TcRef a = IORef a
- type TcId = Id
- type TcIdSet = IdSet
- type TcBinderStack = [TcBinder]
- data TcBinder
- data SpliceType
- data ThStage
- = Splice SpliceType
- | RunSplice (TcRef [ForeignRef (Q ())])
- | Comp
- | Brack ThStage PendingStuff
- data PendingStuff
- type ThLevel = Int
- data ArrowCtxt
- data TcTyThing
- = AGlobal TyThing
- | ATcId {
- tct_id :: TcId
- tct_info :: IdBindingInfo
- | ATyVar Name TcTyVar
- | ATcTyCon TyCon
- | APromotionErr PromotionErr
- data PromotionErr
- data IdBindingInfo
- data IsGroupClosed = IsGroupClosed (NameEnv RhsNames) ClosedTypeId
- type RhsNames = NameSet
- type ClosedTypeId = Bool
- data ImportAvails = ImportAvails {}
- data WhereFrom
- type TcSigFun = Name -> Maybe TcSigInfo
- data TcSigInfo
- data TcIdSigInfo
- = CompleteSig { }
- | PartialSig { }
- data TcIdSigInst = TISI {
- sig_inst_sig :: TcIdSigInfo
- sig_inst_skols :: [(Name, TcTyVar)]
- sig_inst_theta :: TcThetaType
- sig_inst_tau :: TcSigmaType
- sig_inst_wcs :: [(Name, TcTyVar)]
- sig_inst_wcx :: Maybe TcType
- data TcPatSynInfo = TPSI {}
- type TcPluginSolver = [Ct] -> [Ct] -> [Ct] -> TcPluginM TcPluginResult
- data TcPluginM a
- data TcPlugin = TcPlugin {
- tcPluginInit :: TcPluginM s
- tcPluginSolve :: s -> TcPluginSolver
- tcPluginStop :: s -> TcPluginM ()
- data TcPluginResult
- = TcPluginContradiction [Ct]
- | TcPluginOk [(EvTerm, Ct)] [Ct]
- type RoleAnnotEnv = NameEnv (LRoleAnnotDecl GhcRn)
- holeOcc :: Hole -> OccName
- data Hole
- extendCompleteMatchMap :: CompleteMatchMap -> [CompleteMatch] -> CompleteMatchMap
- mkCompleteMatchMap :: [CompleteMatch] -> CompleteMatchMap
- data CompleteMatch = CompleteMatch {}
- type CompleteMatchMap = UniqFM [CompleteMatch]
- setLclEnvTcLevel :: TcLclEnv -> TcLevel -> TcLclEnv
- getLclEnvTcLevel :: TcLclEnv -> TcLevel
- setLclEnvLoc :: TcLclEnv -> RealSrcSpan -> TcLclEnv
- getLclEnvLoc :: TcLclEnv -> RealSrcSpan
- data TcLclEnv = TcLclEnv {
- tcl_loc :: RealSrcSpan
- tcl_ctxt :: [ErrCtxt]
- tcl_tclvl :: TcLevel
- tcl_th_ctxt :: ThStage
- tcl_th_bndrs :: ThBindEnv
- tcl_arrow_ctxt :: ArrowCtxt
- tcl_rdr :: LocalRdrEnv
- tcl_env :: TcTypeEnv
- tcl_bndrs :: TcBinderStack
- tcl_lie :: TcRef WantedConstraints
- tcl_errs :: TcRef Messages
- updEnv :: (env -> env') -> IOEnv env' a -> IOEnv env a
- setEnv :: env' -> IOEnv env' a -> IOEnv env a
- getEnv :: IOEnv env env
- atomicUpdMutVar' :: IORef a -> (a -> (a, b)) -> IOEnv env b
- atomicUpdMutVar :: IORef a -> (a -> (a, b)) -> IOEnv env b
- updMutVar :: IORef a -> (a -> a) -> IOEnv env ()
- readMutVar :: IORef a -> IOEnv env a
- writeMutVar :: IORef a -> a -> IOEnv env ()
- newMutVar :: a -> IOEnv env (IORef a)
- uninterruptibleMaskM_ :: IOEnv env a -> IOEnv env a
- unsafeInterleaveM :: IOEnv env a -> IOEnv env a
- tryMostM :: IOEnv env r -> IOEnv env (Either SomeException r)
- tryAllM :: IOEnv env r -> IOEnv env (Either SomeException r)
- tryM :: IOEnv env r -> IOEnv env (Either IOEnvFailure r)
- fixM :: (a -> IOEnv env a) -> IOEnv env a
- runIOEnv :: env -> IOEnv env a -> IO a
- failWithM :: String -> IOEnv env a
- failM :: IOEnv env a
- data IOEnv env a
- data IOEnvFailure = IOEnvFailure
- filterOutM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- unlessM :: Monad m => m Bool -> m () -> m ()
- whenM :: Monad m => m Bool -> m () -> m ()
- maybeMapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b)
- foldlM_ :: (Monad m, Foldable t) => (a -> b -> m a) -> a -> t b -> m ()
- orM :: Monad m => m Bool -> m Bool -> m Bool
- fmapEitherM :: Monad m => (a -> m b) -> (c -> m d) -> Either a c -> m (Either b d)
- fmapMaybeM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b)
- mapSndM :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)]
- mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
- mapAndUnzip5M :: Monad m => (a -> m (b, c, d, e, f)) -> [a] -> m ([b], [c], [d], [e], [f])
- mapAndUnzip4M :: Monad m => (a -> m (b, c, d, e)) -> [a] -> m ([b], [c], [d], [e])
- mapAndUnzip3M :: Monad m => (a -> m (b, c, d)) -> [a] -> m ([b], [c], [d])
- zipWithAndUnzipM :: Monad m => (a -> b -> m (c, d)) -> [a] -> [b] -> m ([c], [d])
- zipWith4M :: Monad m => (a -> b -> c -> d -> m e) -> [a] -> [b] -> [c] -> [d] -> m [e]
- zipWith3M_ :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m ()
- zipWith3M :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d]
- data ForeignSrcLang
- module TidyPgm
- module TyCon
- module TysPrim
- module TysWiredIn
- tyConAppNeedsKindSig :: Bool -> TyCon -> Int -> Bool
- classifiesTypeWithValues :: Kind -> Bool
- isKindLevPoly :: Kind -> Bool
- isConstraintKindCon :: TyCon -> Bool
- setJoinResTy :: Int -> Type -> Type -> Type
- modifyJoinResTy :: Int -> (Type -> Type) -> Type -> Type
- splitVisVarsOfTypes :: [Type] -> Pair TyCoVarSet
- splitVisVarsOfType :: Type -> Pair TyCoVarSet
- synTyConResKind :: TyCon -> Kind
- tyConsOfType :: Type -> UniqSet TyCon
- occCheckExpand :: [Var] -> Type -> Maybe Type
- resultIsLevPoly :: Type -> Bool
- isTypeLevPoly :: Type -> Bool
- tcReturnsConstraintKind :: Kind -> Bool
- tcIsRuntimeTypeKind :: Kind -> Bool
- tcIsLiftedTypeKind :: Kind -> Bool
- tcIsConstraintKind :: Kind -> Bool
- tcTypeKind :: HasDebugCallStack => Type -> Kind
- typeKind :: HasDebugCallStack => Type -> Kind
- nonDetCmpTc :: TyCon -> TyCon -> Ordering
- nonDetCmpTypesX :: RnEnv2 -> [Type] -> [Type] -> Ordering
- nonDetCmpTypeX :: RnEnv2 -> Type -> Type -> Ordering
- nonDetCmpTypes :: [Type] -> [Type] -> Ordering
- nonDetCmpType :: Type -> Type -> Ordering
- eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2
- eqTypes :: [Type] -> [Type] -> Bool
- eqTypeX :: RnEnv2 -> Type -> Type -> Bool
- seqTypes :: [Type] -> ()
- seqType :: Type -> ()
- isValidJoinPointType :: JoinArity -> Type -> Bool
- isPrimitiveType :: Type -> Bool
- isStrictType :: HasDebugCallStack => Type -> Bool
- isDataFamilyAppType :: Type -> Bool
- isAlgType :: Type -> Bool
- isUnboxedSumType :: Type -> Bool
- isUnboxedTupleType :: Type -> Bool
- getRuntimeRep :: HasDebugCallStack => Type -> Type
- getRuntimeRep_maybe :: HasDebugCallStack => Type -> Maybe Type
- dropRuntimeRepArgs :: [Type] -> [Type]
- isRuntimeRepKindedTy :: Type -> Bool
- mightBeUnliftedType :: Type -> Bool
- isUnliftedType :: HasDebugCallStack => Type -> Bool
- isLiftedType_maybe :: HasDebugCallStack => Type -> Maybe Bool
- isCoVarType :: Type -> Bool
- isFamFreeTy :: Type -> Bool
- coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type
- mkFamilyTyConApp :: TyCon -> [Type] -> Type
- closeOverKindsDSet :: DTyVarSet -> DTyVarSet
- closeOverKindsList :: [TyVar] -> [TyVar]
- closeOverKindsFV :: [TyVar] -> FV
- closeOverKinds :: TyVarSet -> TyVarSet
- binderRelevantType_maybe :: TyCoBinder -> Maybe Type
- tyBinderType :: TyBinder -> Type
- tyCoBinderType :: TyCoBinder -> Type
- tyCoBinderVar_maybe :: TyCoBinder -> Maybe TyCoVar
- isAnonTyCoBinder :: TyCoBinder -> Bool
- mkAnonBinder :: AnonArgFlag -> Type -> TyCoBinder
- isTauTy :: Type -> Bool
- appTyArgFlags :: Type -> [Type] -> [ArgFlag]
- tyConArgFlags :: TyCon -> [Type] -> [ArgFlag]
- partitionInvisibles :: [(a, ArgFlag)] -> ([a], [a])
- filterOutInferredTypes :: TyCon -> [Type] -> [Type]
- filterOutInvisibleTypes :: TyCon -> [Type] -> [Type]
- splitPiTysInvisibleN :: Int -> Type -> ([TyCoBinder], Type)
- splitPiTysInvisible :: Type -> ([TyCoBinder], Type)
- invisibleTyBndrCount :: Type -> Int
- splitForAllVarBndrs :: Type -> ([TyCoVarBinder], Type)
- splitPiTys :: Type -> ([TyCoBinder], Type)
- splitPiTy :: Type -> (TyCoBinder, Type)
- splitPiTy_maybe :: Type -> Maybe (TyCoBinder, Type)
- splitForAllTy_co_maybe :: Type -> Maybe (TyCoVar, Type)
- splitForAllTy_ty_maybe :: Type -> Maybe (TyCoVar, Type)
- splitForAllTy_maybe :: Type -> Maybe (TyCoVar, Type)
- dropForAlls :: Type -> Type
- splitForAllTy :: Type -> (TyCoVar, Type)
- isFunTy :: Type -> Bool
- isPiTy :: Type -> Bool
- isForAllTy_co :: Type -> Bool
- isForAllTy_ty :: Type -> Bool
- isForAllTy :: Type -> Bool
- splitForAllTysSameVis :: ArgFlag -> Type -> ([TyCoVar], Type)
- splitForAllTys :: Type -> ([TyCoVar], Type)
- mkTyConBindersPreferAnon :: [TyVar] -> TyCoVarSet -> [TyConBinder]
- mkLamTypes :: [Var] -> Type -> Type
- mkLamType :: Var -> Type -> Type
- mkVisForAllTys :: [TyVar] -> Type -> Type
- mkSpecForAllTys :: [TyVar] -> Type -> Type
- mkSpecForAllTy :: TyVar -> Type -> Type
- mkInvForAllTys :: [TyVar] -> Type -> Type
- mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type
- mkInvForAllTy :: TyVar -> Type -> Type
- mkTyCoInvForAllTy :: TyCoVar -> Type -> Type
- stripCoercionTy :: Type -> Coercion
- isCoercionTy_maybe :: Type -> Maybe Coercion
- mkCoercionTy :: Coercion -> Type
- discardCast :: Type -> Type
- tyConBindersTyCoBinders :: [TyConBinder] -> [TyCoBinder]
- splitCastTy_maybe :: Type -> Maybe (Type, Coercion)
- newTyConInstRhs :: TyCon -> [Type] -> Type
- nextRole :: Type -> Role
- splitListTyConApp_maybe :: Type -> Maybe Type
- repSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type])
- tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type])
- splitTyConApp :: Type -> (TyCon, [Type])
- tyConAppArgN :: Int -> Type -> Type
- tyConAppArgs :: Type -> [Type]
- tyConAppArgs_maybe :: Type -> Maybe [Type]
- tyConAppTyCon :: Type -> TyCon
- tyConAppTyCon_maybe :: Type -> Maybe TyCon
- tyConAppTyConPicky_maybe :: Type -> Maybe TyCon
- mkTyConApp :: TyCon -> [Type] -> Type
- applyTysX :: [TyVar] -> Type -> [Type] -> Type
- piResultTys :: HasDebugCallStack => Type -> [Type] -> Type
- funArgTy :: Type -> Type
- funResultTy :: Type -> Type
- splitFunTys :: Type -> ([Type], Type)
- splitFunTy_maybe :: Type -> Maybe (Type, Type)
- splitFunTy :: Type -> (Type, Type)
- pprUserTypeErrorTy :: Type -> SDoc
- userTypeError_maybe :: Type -> Maybe Type
- isLitTy :: Type -> Maybe TyLit
- isStrLitTy :: Type -> Maybe FastString
- mkStrLitTy :: FastString -> Type
- isNumLitTy :: Type -> Maybe Integer
- mkNumLitTy :: Integer -> Type
- repSplitAppTys :: HasDebugCallStack => Type -> (Type, [Type])
- splitAppTys :: Type -> (Type, [Type])
- splitAppTy :: Type -> (Type, Type)
- tcRepSplitAppTy_maybe :: Type -> Maybe (Type, Type)
- repSplitAppTy_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type)
- splitAppTy_maybe :: Type -> Maybe (Type, Type)
- mkAppTys :: Type -> [Type] -> Type
- repGetTyVar_maybe :: Type -> Maybe TyVar
- getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN)
- getTyVar_maybe :: Type -> Maybe TyVar
- isTyVarTy :: Type -> Bool
- getTyVar :: String -> Type -> TyVar
- mapCoercion :: Monad m => TyCoMapper env m -> env -> Coercion -> m Coercion
- mapType :: Monad m => TyCoMapper env m -> env -> Type -> m Type
- isRuntimeRepVar :: TyVar -> Bool
- isUnliftedRuntimeRep :: Type -> Bool
- isUnliftedTypeKind :: Kind -> Bool
- isLiftedRuntimeRep :: Type -> Bool
- kindRep_maybe :: HasDebugCallStack => Kind -> Maybe Type
- kindRep :: HasDebugCallStack => Kind -> Type
- expandTypeSynonyms :: Type -> Type
- data TyCoMapper env (m :: Type -> Type) = TyCoMapper {}
- cloneTyVarBndrs :: TCvSubst -> [TyVar] -> UniqSupply -> (TCvSubst, [TyVar])
- cloneTyVarBndr :: TCvSubst -> TyVar -> Unique -> (TCvSubst, TyVar)
- substVarBndrs :: HasCallStack => TCvSubst -> [TyCoVar] -> (TCvSubst, [TyCoVar])
- substVarBndr :: HasCallStack => TCvSubst -> TyCoVar -> (TCvSubst, TyCoVar)
- substTyVarBndrs :: HasCallStack => TCvSubst -> [TyVar] -> (TCvSubst, [TyVar])
- substTyVarBndr :: HasCallStack => TCvSubst -> TyVar -> (TCvSubst, TyVar)
- substCoUnchecked :: TCvSubst -> Coercion -> Coercion
- lookupTyVar :: TCvSubst -> TyVar -> Maybe Type
- substTyVars :: TCvSubst -> [TyVar] -> [Type]
- substTyVar :: TCvSubst -> TyVar -> Type
- substThetaUnchecked :: TCvSubst -> ThetaType -> ThetaType
- substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType
- substTysUnchecked :: TCvSubst -> [Type] -> [Type]
- substTys :: HasCallStack => TCvSubst -> [Type] -> [Type]
- substTyUnchecked :: TCvSubst -> Type -> Type
- substTy :: HasCallStack => TCvSubst -> Type -> Type
- substTyAddInScope :: TCvSubst -> Type -> Type
- substTysWith :: [TyVar] -> [Type] -> [Type] -> [Type]
- substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion
- substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type
- substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type
- zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv
- zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv
- mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst
- zipTCvSubst :: HasDebugCallStack => [TyCoVar] -> [Type] -> TCvSubst
- zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst
- unionTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst
- extendTCvSubstList :: TCvSubst -> [Var] -> [Type] -> TCvSubst
- extendTvSubstList :: TCvSubst -> [Var] -> [Type] -> TCvSubst
- extendTvSubstAndInScope :: TCvSubst -> TyVar -> Type -> TCvSubst
- extendCvSubst :: TCvSubst -> CoVar -> Coercion -> TCvSubst
- extendTvSubstWithClone :: TCvSubst -> TyVar -> TyVar -> TCvSubst
- extendTvSubstBinderAndInScope :: TCvSubst -> TyCoBinder -> Type -> TCvSubst
- extendTvSubst :: TCvSubst -> TyVar -> Type -> TCvSubst
- extendTCvSubstWithClone :: TCvSubst -> TyCoVar -> TyCoVar -> TCvSubst
- extendTCvSubst :: TCvSubst -> TyCoVar -> Type -> TCvSubst
- extendTCvInScopeSet :: TCvSubst -> VarSet -> TCvSubst
- extendTCvInScopeList :: TCvSubst -> [Var] -> TCvSubst
- extendTCvInScope :: TCvSubst -> Var -> TCvSubst
- zapTCvSubst :: TCvSubst -> TCvSubst
- setTvSubstEnv :: TCvSubst -> TvSubstEnv -> TCvSubst
- notElemTCvSubst :: Var -> TCvSubst -> Bool
- isInScope :: Var -> TCvSubst -> Bool
- getTCvSubstRangeFVs :: TCvSubst -> VarSet
- getTCvInScope :: TCvSubst -> InScopeSet
- getTvSubstEnv :: TCvSubst -> TvSubstEnv
- mkTCvSubst :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> TCvSubst
- isEmptyTCvSubst :: TCvSubst -> Bool
- mkEmptyTCvSubst :: InScopeSet -> TCvSubst
- emptyTCvSubst :: TCvSubst
- composeTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst
- composeTCvSubstEnv :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv)
- emptyTvSubstEnv :: TvSubstEnv
- data TCvSubst = TCvSubst InScopeSet TvSubstEnv CvSubstEnv
- type TvSubstEnv = TyVarEnv Type
- tidyKind :: TidyEnv -> Kind -> Kind
- tidyOpenKind :: TidyEnv -> Kind -> (TidyEnv, Kind)
- tidyTopType :: Type -> Type
- tidyOpenType :: TidyEnv -> Type -> (TidyEnv, Type)
- tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type])
- tidyType :: TidyEnv -> Type -> Type
- tidyTypes :: TidyEnv -> [Type] -> [Type]
- tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar
- tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar)
- tidyOpenTyCoVars :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar])
- tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv
- tidyTyCoVarBinders :: TidyEnv -> [VarBndr TyCoVar vis] -> (TidyEnv, [VarBndr TyCoVar vis])
- tidyTyCoVarBinder :: TidyEnv -> VarBndr TyCoVar vis -> (TidyEnv, VarBndr TyCoVar vis)
- tidyVarBndr :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar)
- tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar])
- tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar]
- tyCoVarsOfTypeWellScoped :: Type -> [TyVar]
- scopedSort :: [TyCoVar] -> [TyCoVar]
- noFreeVarsOfType :: Type -> Bool
- coVarsOfTypes :: [Type] -> TyCoVarSet
- coVarsOfType :: Type -> CoVarSet
- tyCoFVsVarBndr :: Var -> FV -> FV
- tyCoFVsVarBndrs :: [Var] -> FV -> FV
- tyCoFVsBndr :: TyCoVarBinder -> FV -> FV
- tyCoFVsOfType :: Type -> FV
- tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet
- tyCoVarsOfTypes :: [Type] -> TyCoVarSet
- tyCoVarsOfType :: Type -> TyCoVarSet
- funTyCon :: TyCon
- typeSize :: Type -> Int
- mkTyConTy :: TyCon -> Type
- mkPiTys :: [TyCoBinder] -> Type -> Type
- mkPiTy :: TyCoBinder -> Type -> Type
- mkForAllTys :: [TyCoVarBinder] -> Type -> Type
- mkInvisFunTys :: [Type] -> Type -> Type
- mkInvisFunTy :: Type -> Type -> Type
- mkVisFunTy :: Type -> Type -> Type
- mkTyVarTys :: [TyVar] -> [Type]
- mkTyVarTy :: TyVar -> Type
- isNamedBinder :: TyCoBinder -> Bool
- isVisibleBinder :: TyCoBinder -> Bool
- isInvisibleBinder :: TyCoBinder -> Bool
- type KindOrType = Type
- type KnotTied ty = ty
- isPredTy :: HasDebugCallStack => Type -> Bool
- isCoercionTy :: Type -> Bool
- mkAppTy :: Type -> Type -> Type
- mkCastTy :: Type -> Coercion -> Type
- piResultTy :: HasDebugCallStack => Type -> Type -> Type
- eqType :: Type -> Type -> Bool
- coreView :: Type -> Maybe Type
- tcView :: Type -> Maybe Type
- isRuntimeRepTy :: Type -> Bool
- isLiftedTypeKind :: Kind -> Bool
- splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type])
- partitionInvisibleTypes :: TyCon -> [Type] -> ([Type], [Type])
- isTyVar :: Var -> Bool
- tyVarKind :: TyVar -> Kind
- mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder]
- mkTyCoVarBinders :: ArgFlag -> [TyCoVar] -> [TyCoVarBinder]
- mkTyCoVarBinder :: ArgFlag -> TyCoVar -> TyCoVarBinder
- binderType :: VarBndr TyCoVar argf -> Type
- binderArgFlag :: VarBndr tv argf -> argf
- binderVars :: [VarBndr tv argf] -> [tv]
- binderVar :: VarBndr tv argf -> tv
- sameVis :: ArgFlag -> ArgFlag -> Bool
- isInvisibleArgFlag :: ArgFlag -> Bool
- isVisibleArgFlag :: ArgFlag -> Bool
- type TyVar = Var
- type TyCoVar = Id
- data ForallVisFlag
- type TyCoVarBinder = VarBndr TyCoVar ArgFlag
- type TyVarBinder = VarBndr TyVar ArgFlag
- liftedTypeKind :: Kind
- mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type
- data Type
- data TyThing
- data TyCoBinder
- type PredType = Type
- type Kind = Type
- type ThetaType = [PredType]
- data ArgFlag
- data AnonArgFlag
- data Var
- module Unify
- module UniqFM
- module UniqSupply
- setTyVarUnique :: TyVar -> Unique -> TyVar
- setVarUnique :: Var -> Unique -> Var
- data Var
- 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)
- | 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
- 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 HsSrcBang = HsSrcBang SourceText SrcUnpackedness SrcStrictness
- data HsImplBang
- data SrcStrictness
- data SrcUnpackedness
- 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
- 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)]
- | 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 ...
- data ForallVisFlag
- 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))
- data Fixity
- data SpliceExplicitFlag
- module ExtractDocs
- module Parser
- module Lexer
Session
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
extensions :: DynFlags -> [OnOff Extension] #
extensionFlags :: DynFlags -> EnumSet Extension #
targetPlatform :: DynFlags -> Platform #
packageFlags :: DynFlags -> [PackageFlag] #
The -package
and -hide-package
flags from the command-line.
In *reverse* order that they're specified on the command line.
generalFlags :: DynFlags -> EnumSet GeneralFlag #
warningFlags :: DynFlags -> EnumSet WarningFlag #
importPaths :: DynFlags -> [FilePath] #
useColor :: DynFlags -> OverridingBool #
canUseColor :: DynFlags -> Bool #
useUnicode :: DynFlags -> Bool #
flagsForCompletion :: Bool -> [String] #
Make a list of flags for shell completion. Filter all available flags into two groups, for interactive GHC vs all other.
outputFile :: DynFlags -> Maybe String #
pluginModNames :: DynFlags -> [ModuleName] #
refLevelHoleFits :: DynFlags -> Maybe Int #
Maximum level of refinement for refinement hole fits in typed hole error messages
maxRefHoleFits :: DynFlags -> Maybe Int #
Maximum number of refinement hole fits to show in typed hole error messages
maxValidHoleFits :: DynFlags -> Maybe Int #
Maximum number of hole fits to show in typed hole error messages
type CommandLineOption = String #
Command line options gathered from the -PModule.Name:stuff syntax are given to you as this type
staticPlugins :: DynFlags -> [StaticPlugin] #
staic plugins which do not need dynamic loading. These plugins are intended to be added by GHC API users directly to this list.
To add dynamically loaded plugins through the GHC API see
addPluginModuleName
instead.
gopt :: GeneralFlag -> DynFlags -> Bool #
Test whether a GeneralFlag
is set
gopt_set :: DynFlags -> GeneralFlag -> DynFlags #
Set a GeneralFlag
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags #
Unset a GeneralFlag
wopt :: WarningFlag -> DynFlags -> Bool #
Test whether a WarningFlag
is set
wopt_set :: DynFlags -> WarningFlag -> DynFlags #
Set a WarningFlag
Constructors
FlagSpec | |
Fields
|
data WarningFlag #
Constructors
Instances
Enum WarningFlag | |
Defined in DynFlags Methods 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 | |
Show WarningFlag | |
Defined in DynFlags Methods showsPrec :: Int -> WarningFlag -> ShowS # show :: WarningFlag -> String # showList :: [WarningFlag] -> ShowS # |
data GeneralFlag #
Enumerates the simple on-or-off dynamic flags
Constructors
Instances
Enum GeneralFlag | |
Defined in DynFlags Methods 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 | |
Show GeneralFlag | |
Defined in DynFlags Methods showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # |
data PackageFlag #
Flags for manipulating packages visibility.
Instances
Eq PackageFlag | |
Defined in DynFlags | |
Show PackageFlag Source # | |
Defined in Development.IDE.GHC.Orphans Methods showsPrec :: Int -> PackageFlag -> ShowS # show :: PackageFlag -> String # showList :: [PackageFlag] -> ShowS # | |
Outputable PackageFlag | |
Defined in DynFlags |
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.
Constructors
PackageArg String |
|
UnitIdArg UnitId |
|
Instances
Eq PackageArg | |
Defined in DynFlags | |
Show PackageArg | |
Defined in DynFlags Methods showsPrec :: Int -> PackageArg -> ShowS # show :: PackageArg -> String # showList :: [PackageArg] -> ShowS # | |
Outputable PackageArg | |
Defined in DynFlags |
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
:
Constructors
ModRenaming | |
Fields
|
Instances
Eq ModRenaming | |
Defined in DynFlags | |
Outputable ModRenaming | |
Defined in DynFlags |
pattern ExposePackage :: String -> PackageArg -> ModRenaming -> PackageFlag Source #
Arguments
:: 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).
Arguments
:: 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.
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.
Constructors
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 Methods showsPrec :: Int -> WarnReason -> ShowS # show :: WarnReason -> String # showList :: [WarnReason] -> ShowS # | |
ToJson WarnReason | |
Defined in DynFlags Methods json :: WarnReason -> JsonDoc # | |
Outputable WarnReason | |
Defined in DynFlags |
wWarningFlags :: [FlagSpec WarningFlag] #
These -W<blah>
flags can all be reversed with -Wno-<blah>
updOptLevel :: Int -> DynFlags -> DynFlags #
Sets the DynFlags
to be appropriate to the optimisation level
setUnsafeGlobalDynFlags :: DynFlags -> IO () #
Linear Haskell
unrestricted :: a -> Scaled a Source #
scaledThing :: Scaled a -> a Source #
Interface Files
type IfaceExport = AvailInfo #
The original names declared of a certain module that are exported
data IfaceTyCon #
Constructors
IfaceTyCon | |
Fields |
Instances
Eq IfaceTyCon | |
Defined in IfaceType | |
NFData IfaceTyCon | |
Defined in IfaceType Methods rnf :: IfaceTyCon -> () # | |
Binary IfaceTyCon | |
Defined in IfaceType Methods put_ :: BinHandle -> IfaceTyCon -> IO () # put :: BinHandle -> IfaceTyCon -> IO (Bin IfaceTyCon) # get :: BinHandle -> IO IfaceTyCon # | |
Outputable IfaceTyCon | |
Defined in IfaceType |
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
.
Constructors
ModIface | |
Fields
|
Constructors
HsSrcFile | |
HsBootFile | |
HsigFile |
Instances
Eq HscSource | |
Ord HscSource | |
Show HscSource | |
Binary HscSource | |
Constructors
ImportByUser IsBootInterface | |
ImportBySystem | |
ImportByPlugin |
data SourceModified #
Indicates whether a given module's source has been modified since it was last compiled.
Constructors
SourceModified | the source has been modified |
SourceUnmodified | the source has not been modified. Compilation may or may not be necessary, depending on whether any dependencies have changed since we last compiled. |
SourceUnmodifiedAndStable | the source has not been modified, and furthermore all of its (transitive) dependencies are up to date; it definitely does not need to be recompiled. This is important for two reasons: (a) we can omit the version check in checkOldIface, and (b) if the module used TH splices we don't need to force recompilation. |
Instances
Eq SourceModified Source # | |
Defined in Development.IDE.GHC.Orphans Methods (==) :: SourceModified -> SourceModified -> Bool # (/=) :: SourceModified -> SourceModified -> Bool # | |
Show SourceModified Source # | |
Defined in Development.IDE.GHC.Orphans Methods showsPrec :: Int -> SourceModified -> ShowS # show :: SourceModified -> String # showList :: [SourceModified] -> ShowS # | |
NFData SourceModified Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: SourceModified -> () # |
loadModuleInterface :: SDoc -> Module -> TcM ModIface #
Load interface directly for a fully qualified Module
. (This is a fairly
rare operation, but in particular it is used to load orphan modules
in order to pull their instances into the global package table and to
handle some operations in GHCi).
data RecompileRequired #
Constructors
UpToDate | everything is up to date, recompilation is not required |
MustCompile | The .hs file has been touched, or the .o/.hi file does not exist |
RecompBecause String | The .o/.hi files are up to date, but something else has changed to force recompilation; the String says what (one-line summary) |
Instances
Eq RecompileRequired | |
Defined in MkIface Methods (==) :: RecompileRequired -> RecompileRequired -> Bool # (/=) :: RecompileRequired -> RecompileRequired -> Bool # | |
Semigroup RecompileRequired | |
Defined in MkIface Methods (<>) :: RecompileRequired -> RecompileRequired -> RecompileRequired # sconcat :: NonEmpty RecompileRequired -> RecompileRequired # stimes :: Integral b => b -> RecompileRequired -> RecompileRequired # | |
Monoid RecompileRequired | |
Defined in MkIface Methods mappend :: RecompileRequired -> RecompileRequired -> RecompileRequired # mconcat :: [RecompileRequired] -> RecompileRequired # |
mkPartialIface :: HscEnv -> ModDetails -> ModGuts -> PartialModIface #
mkFullIface :: HscEnv -> PartialModIface -> IO ModIface #
Fully instantiate a interface Adds fingerprints and potentially code generator produced information.
checkOldIface :: HscEnv -> ModSummary -> SourceModified -> Maybe ModIface -> IO (RecompileRequired, Maybe ModIface) #
Top level function to check if the version of an old interface file is equivalent to the current source file the user asked us to compile. If the same, we can avoid recompilation. We return a tuple where the first element is a bool saying if we should recompile the object file and the second is maybe the interface file, where Nothing means to rebuild the interface file and not use the existing one.
pattern IsBoot :: IsBootInterface Source #
pattern NotBoot :: IsBootInterface Source #
Fixity
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 Methods (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Data LexicalFixity | |
Defined in BasicTypes Methods 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 |
ModSummary
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
Constructors
ModSummary | |
Fields
|
Instances
Show ModSummary Source # | |
Defined in Development.IDE.GHC.Orphans Methods showsPrec :: Int -> ModSummary -> ShowS # show :: ModSummary -> String # showList :: [ModSummary] -> ShowS # | |
NFData ModSummary Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: ModSummary -> () # | |
Outputable ModSummary | |
Defined in HscTypes |
HomeModInfo
data HomeModInfo #
Information about modules in the package being compiled
Constructors
HomeModInfo | |
Fields
|
ModGuts
A ModGuts is carried through the compiler, accumulating stuff as it goes
There is only one ModGuts at any time, the one for the module
being compiled right now. Once it is compiled, a ModIface
and
ModDetails
are extracted and the ModGuts is discarded.
Constructors
ModGuts | |
Fields
|
A restricted form of ModGuts
for code generation purposes
Constructors
CgGuts | |
Fields
|
ModDetails
data ModDetails #
The ModDetails
is essentially a cache for information in the ModIface
for home modules only. Information relating to packages will be loaded into
global environments in ExternalPackageState
.
Constructors
ModDetails | |
Fields
|
Instances
Show ModDetails Source # | |
Defined in Development.IDE.GHC.Orphans Methods showsPrec :: Int -> ModDetails -> ShowS # show :: ModDetails -> String # showList :: [ModDetails] -> ShowS # | |
NFData ModDetails Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: ModDetails -> () # |
HsExpr,
pattern HsLet :: XLet p -> SrcSpanLess (LHsLocalBinds p) -> LHsExpr p -> HsExpr p Source #
pattern LetStmt :: XLetStmt idL idR body -> SrcSpanLess (LHsLocalBindsLR idL idR) -> StmtLR idL idR body Source #
Var
Constructors
TyVarTy Var | Vanilla type or kind variable (*never* a coercion variable) |
AppTy Type Type | Type application to something other than a 1) Function: must not be a 2) Argument type |
TyConApp TyCon [KindOrType] | Application of a 1) Type constructor being applied to. 2) Type arguments. Might not have enough type arguments here to saturate the constructor. Even type synonyms are not necessarily saturated; for example unsaturated type synonyms can appear as the right hand side of a type synonym. |
ForAllTy !TyCoVarBinder Type | A Π type. |
LitTy TyLit | Type literals are similar to type constructors. |
CastTy Type KindCoercion | A kind cast. The coercion is always nominal. INVARIANT: The cast is never refl. INVARIANT: The Type is not a CastTy (use TransCo instead) See Note Respecting definitional equality and (EQ3) |
CoercionTy Coercion | Injection of a Coercion into a type This should only ever be used in the RHS of an AppTy, in the list of a TyConApp, when applying a promoted GADT data constructor |
Instances
Data Type | |
Defined in TyCoRep Methods 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 |
Specs
data ImpDeclSpec #
Import Declaration Specification
Describes a particular import declaration and is
shared among all the Provenance
s for that decl
Constructors
ImpDeclSpec | |
Fields
|
Instances
Eq ImpDeclSpec | |
Defined in RdrName | |
Data ImpDeclSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpDeclSpec # toConstr :: ImpDeclSpec -> Constr # dataTypeOf :: ImpDeclSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpDeclSpec) # gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImpDeclSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # | |
Ord ImpDeclSpec | |
Defined in RdrName Methods compare :: ImpDeclSpec -> ImpDeclSpec -> Ordering # (<) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (<=) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (>) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (>=) :: ImpDeclSpec -> ImpDeclSpec -> Bool # max :: ImpDeclSpec -> ImpDeclSpec -> ImpDeclSpec # min :: ImpDeclSpec -> ImpDeclSpec -> ImpDeclSpec # |
data ImportSpec #
Import Specification
The ImportSpec
of something says how it came to be imported
It's quite elaborate so that we can give accurate unused-name warnings.
Constructors
ImpSpec | |
Fields
|
Instances
Eq ImportSpec | |
Defined in RdrName | |
Data ImportSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportSpec -> c ImportSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSpec # toConstr :: ImportSpec -> Constr # dataTypeOf :: ImportSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec) # gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # | |
Ord ImportSpec | |
Defined in RdrName Methods compare :: ImportSpec -> ImportSpec -> Ordering # (<) :: ImportSpec -> ImportSpec -> Bool # (<=) :: ImportSpec -> ImportSpec -> Bool # (>) :: ImportSpec -> ImportSpec -> Bool # (>=) :: ImportSpec -> ImportSpec -> Bool # max :: ImportSpec -> ImportSpec -> ImportSpec # min :: ImportSpec -> ImportSpec -> ImportSpec # | |
Outputable ImportSpec | |
Defined in RdrName |
SourceText
data SourceText #
Constructors
SourceText String | |
NoSourceText | For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item. |
Instances
Eq SourceText | |
Defined in BasicTypes | |
Data SourceText | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceText -> c SourceText # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceText # toConstr :: SourceText -> Constr # dataTypeOf :: SourceText -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceText) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText) # gmapT :: (forall b. Data b => b -> b) -> SourceText -> SourceText # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceText -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceText -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # | |
Show SourceText | |
Defined in BasicTypes Methods showsPrec :: Int -> SourceText -> ShowS # show :: SourceText -> String # showList :: [SourceText] -> ShowS # | |
Outputable SourceText | |
Defined in BasicTypes | |
Annotate (SourceText, FastString) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater Methods markAST :: SrcSpan -> (SourceText, FastString) -> Annotated () # |
Name
tyThingParent_maybe :: TyThing -> Maybe TyThing #
tyThingParent_maybe x returns (Just p) when pprTyThingInContext should print a declaration for p (albeit with some "..." in it) when asked to show x It returns the *immediate* parent. So a datacon returns its tycon but the tycon could be the associated type of a class, so it in turn might have a parent.
Ways
wayGeneralFlags :: Platform -> Way -> [GeneralFlag] #
wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] #
AvailInfo
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 Methods 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 | |
pattern AvailFL :: FieldLabel -> AvailInfo Source #
availName :: AvailInfo -> Name #
Just the main name made available, i.e. not the available pieces
of type or class brought into scope by the GenAvailInfo
availNames :: AvailInfo -> [Name] #
All names made available by the availability information (excluding overloaded selectors)
availNamesWithSelectors :: AvailInfo -> [Name] #
All names made available by the availability information (including overloaded selectors)
availsToNameSet :: [AvailInfo] -> NameSet #
TcGblEnv
TcGblEnv
describes the top-level of the module at the
point at which the typechecker is finished work.
It is this structure that is handed on to the desugarer
For state that needs to be updated during the typechecking
phase and returned at end, use a TcRef
(= IORef
).
Constructors
TcGblEnv | |
Fields
|
Instances
ContainsCostCentreState TcGblEnv | |
Defined in TcRnMonad Methods extractCostCentreState :: TcGblEnv -> TcRef CostCentreState # | |
ContainsModule TcGblEnv | |
Defined in TcRnTypes Methods extractModule :: TcGblEnv -> Module # |
Parsing and LExer types
Haskell Module
All we actually declare here is the top-level structure for a module.
Constructors
HsModule | |
Fields
|
Instances
HasDecls ParsedSource | |
Defined in Language.Haskell.GHC.ExactPrint.Transform Methods hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] # replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource # | |
Data (HsModule GhcPs) | |
Defined in GHC.Hs Methods 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 Methods 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 Methods 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) # | |
Show (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans | |
NFData (HsModule a) Source # | |
Defined in Development.IDE.GHC.Orphans | |
NFData (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: Annotated ParsedSource -> () # | |
OutputableBndrId p => Outputable (HsModule (GhcPass p)) | |
Annotate (HsModule GhcPs) | |
type ParsedSource = Located (HsModule GhcPs) #
type RenamedSource = (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString) #
Compilation Main
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.
Arguments
:: 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.
The Session is a handle to the complete state of a compilation session. A compilation session consists of a set of modules constituting the current program or library, the context for interactive evaluation, and various caches.
modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () #
Set the current session to the result of applying the current session to the argument.
getSession :: GhcMonad m => m HscEnv #
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.
getSessionDynFlags :: GhcMonad m => m DynFlags #
Grabs the DynFlags from the Session
class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad (m :: Type -> Type) #
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.
Minimal complete definition
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
.
Constructors
Unlit HscSource | |
Cpp HscSource | |
HsPp HscSource | |
Hsc HscSource | |
Ccxx | |
Cc | |
Cobjc | |
Cobjcxx | |
HCc | |
As Bool | |
LlvmOpt | |
LlvmLlc | |
LlvmMangle | |
CmmCpp | |
Cmm | |
MergeForeign | |
StopLn |
hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts #
Convert a typechecked module to Core
Arguments
:: HscEnv | |
-> CgGuts | |
-> ModLocation | |
-> FilePath | |
-> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)]) |
|
Compile to hard-code.
hscInteractive :: HscEnv -> CgGuts -> ModLocation -> IO (Maybe FilePath, CompiledByteCode, [SptEntry]) #
hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) #
Rename and typecheck a module, additionally returning the renamed syntax
makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails #
Make a ModDetails
from the results of typechecking. Used when
typechecking only, as opposed to full compilation.
Typecheck utils
typecheckIface :: ModIface -> IfG ModDetails #
mkIfaceTc :: HscEnv -> SafeHaskellMode -> ModDetails -> TcGblEnv -> IO ModIface #
Make an interface from the results of typechecking only. Useful
for non-optimising compilation, or where we aren't generating any
object code at all (HscNothing
).
data ImportedModsVal #
Constructors
ImportedModsVal | |
Fields
|
importedByUser :: [ImportedBy] -> [ImportedModsVal] #
type TypecheckedSource = LHsBinds GhcTc #
Source Locations
type HasSrcSpan = HasSrcSpan Source #
type Located = GenLocated SrcSpan #
unLoc :: HasSrcSpan a => a -> SrcSpanLess a #
getLoc :: HasSrcSpan a => a -> SrcSpan Source #
getLocA :: HasSrcSpan a => a -> SrcSpan Source #
type AnnListItem = SrcSpan Source #
type RealLocated = GenLocated RealSrcSpan #
data GenLocated l e #
We attach SrcSpans to lots of things, so let's have a datatype for it.
Constructors
L l e |
Instances
HasDecls ParsedSource | |
Defined in Language.Haskell.GHC.ExactPrint.Transform Methods hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] # replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource # | |
Functor (GenLocated l) | |
Defined in SrcLoc Methods fmap :: (a -> b) -> GenLocated l a -> GenLocated l b # (<$) :: a -> GenLocated l b -> GenLocated l a # | |
Show (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans | |
Foldable (GenLocated l) | |
Defined in SrcLoc Methods 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 Methods 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) # | |
NFData (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: Annotated ParsedSource -> () # | |
NamedThing e => NamedThing (Located e) | |
HasSrcSpan (Located a) | |
Defined in SrcLoc Methods composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
Annotate [ExprLStmt GhcPs] | Used for declarations that need to be aligned together, e.g. in a do or let .. in statement/expr |
Annotate [LHsDerivingClause GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate [LHsType GhcPs] | |
Annotate [LHsSigType GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate [LConDeclField GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate [LIE GhcPs] | |
Annotate body => Annotate [Located (Match GhcPs (Located body))] | |
Annotate [Located (StmtLR GhcPs GhcPs (LHsCmd GhcPs))] | |
Annotate (TyFamInstEqn GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsRecUpdField GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (FunDep (Located RdrName)) | |
Annotate name => Annotate (BooleanFormula (Located name)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
(Data ast, Annotate ast) => Annotate (Located ast) | |
HasDecls (LHsExpr GhcPs) | |
HasLoc (Located a) | |
Defined in Compat.HieAst | |
HasType (LHsBind GhcRn) | |
Defined in Compat.HieAst Methods getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type] | |
HasType (LHsBind GhcTc) | |
Defined in Compat.HieAst Methods getTypeNode :: LHsBind GhcTc -> HieM [HieAST Type] | |
HasType (LHsExpr GhcRn) | |
Defined in Compat.HieAst Methods 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 Methods 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 Methods toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LTyClDecl GhcRn) | |
ToHie (LFamilyDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LFamilyDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInjectivityAnn GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type] | |
ToHie (HsDeriving GhcRn) | |
Defined in Compat.HieAst Methods toHie :: HsDeriving GhcRn -> HieM [HieAST Type] | |
ToHie (LHsDerivingClause GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LHsDerivingClause GhcRn -> HieM [HieAST Type] | |
ToHie (LStandaloneKindSig GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LStandaloneKindSig GhcRn -> HieM [HieAST Type] | |
ToHie (LConDecl GhcRn) | |
ToHie (LTyFamInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDataFamInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LClsInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInstDecl GhcRn) | |
ToHie (LDerivDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDerivDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDefaultDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LForeignDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LForeignDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecls GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LRuleDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecl GhcRn) | |
ToHie (LWarnDecls GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LWarnDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LWarnDecl GhcRn) | |
ToHie (LAnnDecl GhcRn) | |
ToHie (LRoleAnnotDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LFixitySig GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LFixitySig GhcRn -> HieM [HieAST Type] | |
ToHie (LHsContext GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LHsContext GhcRn -> HieM [HieAST Type] | |
ToHie (LHsType GhcRn) | |
ToHie (LConDeclField GhcRn) | |
Defined in Compat.HieAst Methods 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 Methods 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 Methods 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 Methods 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 Methods toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] | |
ToHie (Context (Located NoExtField)) | |
Defined in Compat.HieAst Methods 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 Methods 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 Methods 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 Methods 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 Methods toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type] | |
ToHie (IEContext (LIE GhcRn)) | |
ToHie (IEContext (Located (FieldLbl Name))) | |
ToHie (IEContext (Located ModuleName)) | |
Defined in Compat.HieAst Methods toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type] | |
ToHie (TVScoped (LHsTyVarBndr GhcRn)) | |
Defined in Compat.HieAst Methods toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type] | |
(Eq l, Eq e) => Eq (GenLocated l e) | |
Defined in SrcLoc Methods (==) :: 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 Methods 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 Methods 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 Methods rnf :: GenLocated l e -> () # | |
(Outputable l, Outputable e) => Outputable (GenLocated l e) | |
Defined in SrcLoc | |
Annotate body => Annotate (Match GhcPs (Located body)) | |
Annotate body => Annotate (GRHS GhcPs (Located body)) | |
Annotate body => Annotate (Stmt GhcPs (Located body)) | |
Annotate (HsRecField GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsRecField GhcPs (Located (Pat GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate arg => Annotate (HsImplicitBndrs GhcPs (Located arg)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
HasDecls (LMatch GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform | |
HasDecls (LStmt GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform | |
(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 |
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.
Constructors
UnhelpfulSpan !FastString |
Instances
Eq SrcSpan | |
Data SrcSpan | |
Defined in SrcLoc Methods 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 | |
HasDecls ParsedSource | |
Defined in Language.Haskell.GHC.ExactPrint.Transform Methods hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] # replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource # | |
ASTElement NameAnn RdrName Source # | |
p ~ GhcPs => ASTElement AnnListItem (HsDecl p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
p ~ GhcPs => ASTElement AnnListItem (HsType p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
p ~ GhcPs => ASTElement AnnListItem (HsExpr p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
p ~ GhcPs => ASTElement AnnListItem (ImportDecl p) Source # | |
Defined in Development.IDE.GHC.ExactPrint Methods parseAST :: Parser (LocatedAn AnnListItem (ImportDecl p)) Source # maybeParensAST :: LocatedAn AnnListItem (ImportDecl p) -> LocatedAn AnnListItem (ImportDecl p) Source # graft :: Data a => SrcSpan -> LocatedAn AnnListItem (ImportDecl p) -> Graft (Either String) a Source # | |
p ~ GhcPs => ASTElement AnnListItem (Pat p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
Show (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans | |
NFData (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: Annotated ParsedSource -> () # | |
NamedThing e => NamedThing (Located e) | |
HasSrcSpan (Located a) | |
Defined in SrcLoc Methods composeSrcSpan :: Located (SrcSpanLess (Located a)) -> Located a # decomposeSrcSpan :: Located a -> Located (SrcSpanLess (Located a)) # | |
Annotate [ExprLStmt GhcPs] | Used for declarations that need to be aligned together, e.g. in a do or let .. in statement/expr |
Annotate [LHsDerivingClause GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate [LHsType GhcPs] | |
Annotate [LHsSigType GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate [LConDeclField GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate [LIE GhcPs] | |
Annotate body => Annotate [Located (Match GhcPs (Located body))] | |
Annotate [Located (StmtLR GhcPs GhcPs (LHsCmd GhcPs))] | |
Annotate (TyFamInstEqn GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsRecUpdField GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (FunDep (Located RdrName)) | |
Annotate name => Annotate (BooleanFormula (Located name)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
(Data ast, Annotate ast) => Annotate (Located ast) | |
HasDecls (LHsExpr GhcPs) | |
HasLoc (Located a) | |
Defined in Compat.HieAst | |
HasType (LHsBind GhcRn) | |
Defined in Compat.HieAst Methods getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type] | |
HasType (LHsBind GhcTc) | |
Defined in Compat.HieAst Methods getTypeNode :: LHsBind GhcTc -> HieM [HieAST Type] | |
HasType (LHsExpr GhcRn) | |
Defined in Compat.HieAst Methods 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 Methods 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 Methods toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LTyClDecl GhcRn) | |
ToHie (LFamilyDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LFamilyDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInjectivityAnn GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type] | |
ToHie (HsDeriving GhcRn) | |
Defined in Compat.HieAst Methods toHie :: HsDeriving GhcRn -> HieM [HieAST Type] | |
ToHie (LHsDerivingClause GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LHsDerivingClause GhcRn -> HieM [HieAST Type] | |
ToHie (LStandaloneKindSig GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LStandaloneKindSig GhcRn -> HieM [HieAST Type] | |
ToHie (LConDecl GhcRn) | |
ToHie (LTyFamInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDataFamInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LClsInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LInstDecl GhcRn) | |
ToHie (LDerivDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDerivDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LDefaultDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LForeignDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LForeignDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecls GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LRuleDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LRuleDecl GhcRn) | |
ToHie (LWarnDecls GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LWarnDecls GhcRn -> HieM [HieAST Type] | |
ToHie (LWarnDecl GhcRn) | |
ToHie (LAnnDecl GhcRn) | |
ToHie (LRoleAnnotDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type] | |
ToHie (LFixitySig GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LFixitySig GhcRn -> HieM [HieAST Type] | |
ToHie (LHsContext GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LHsContext GhcRn -> HieM [HieAST Type] | |
ToHie (LHsType GhcRn) | |
ToHie (LConDeclField GhcRn) | |
Defined in Compat.HieAst Methods 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 Methods 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 Methods 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 Methods 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 Methods toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] | |
ToHie (Context (Located NoExtField)) | |
Defined in Compat.HieAst Methods 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 Methods 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 Methods 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 Methods 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 Methods toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type] | |
ToHie (IEContext (LIE GhcRn)) | |
ToHie (IEContext (Located (FieldLbl Name))) | |
ToHie (IEContext (Located ModuleName)) | |
Defined in Compat.HieAst Methods toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type] | |
ToHie (TVScoped (LHsTyVarBndr GhcRn)) | |
Defined in Compat.HieAst Methods toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type] | |
Outputable a => Show (GenLocated SrcSpan a) Source # | |
Defined in Development.IDE.GHC.Orphans | |
Annotate body => Annotate (Match GhcPs (Located body)) | |
Annotate body => Annotate (GRHS GhcPs (Located body)) | |
Annotate body => Annotate (Stmt GhcPs (Located body)) | |
Annotate (HsRecField GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsRecField GhcPs (Located (Pat GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate arg => Annotate (HsImplicitBndrs GhcPs (Located arg)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
HasDecls (LMatch GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform | |
HasDecls (LStmt GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform | |
(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 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
pattern RealSrcSpan :: RealSrcSpan -> Maybe BufSpan -> SrcSpan Source #
data RealSrcLoc #
Real Source Location
Represents a single point within a file
Instances
Eq RealSrcLoc | |
Defined in SrcLoc | |
Ord RealSrcLoc | |
Defined in SrcLoc Methods 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 Methods showsPrec :: Int -> RealSrcLoc -> ShowS # show :: RealSrcLoc -> String # showList :: [RealSrcLoc] -> ShowS # | |
Outputable RealSrcLoc | |
Defined in SrcLoc |
pattern RealSrcLoc :: RealSrcLoc -> Maybe BufPos -> SrcLoc Source #
Source Location
Constructors
UnhelpfulLoc FastString |
containsSpan :: RealSrcSpan -> RealSrcSpan -> Bool #
Tests whether the first span "contains" the other span, meaning that it covers at least as much source code. True where spans are equal.
mkGeneralSrcSpan :: FastString -> SrcSpan #
Create a "bad" SrcSpan
that has not location information
mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #
Create a SrcSpan
between two points in a file
mkRealSrcLoc :: FastString -> Int -> Int -> RealSrcLoc #
getRealSrcSpan :: RealLocated a -> RealSrcSpan Source #
realSrcLocSpan :: RealSrcLoc -> RealSrcSpan #
realSrcSpanEnd :: RealSrcSpan -> RealSrcLoc #
Arguments
:: SrcSpan | The span that may be enclosed by the other |
-> SrcSpan | The span it may be enclosed by |
-> Bool |
Determines whether a span is enclosed by another one
Built-in "bad" SrcSpan
s for common sources of location uncertainty
srcSpanStart :: SrcSpan -> SrcLoc #
srcSpanStartLine :: RealSrcSpan -> Int #
srcSpanStartCol :: RealSrcSpan -> Int #
srcSpanEnd :: SrcSpan -> SrcLoc #
srcSpanEndLine :: RealSrcSpan -> Int #
srcSpanEndCol :: RealSrcSpan -> Int #
srcSpanFile :: RealSrcSpan -> FastString #
srcLocCol :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc
srcLocFile :: RealSrcLoc -> FastString #
Gives the filename of the RealSrcLoc
srcLocLine :: RealSrcLoc -> Int #
Raises an error when used on a "bad" SrcLoc
noLoc :: HasSrcSpan a => SrcSpanLess a -> a #
Finder
data FindResult #
The result of searching for an imported module.
NB: FindResult manages both user source-import lookups
(which can result in Module
) as well as direct imports
for interfaces (which always result in InstalledModule
).
Constructors
Found ModLocation Module | The module was found |
NoPackage UnitId | The requested package was not found |
FoundMultiple [(Module, ModuleOrigin)] | _Error_: both in multiple packages |
NotFound | Not found |
Fields
|
mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation #
addBootSuffixLocnOut :: ModLocation -> ModLocation Source #
Add the -boot
suffix to all output file paths associated with the
module, not including the input file itself
findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) #
data InstalledFindResult #
Module and Package
data ModuleOrigin #
Package state is all stored in DynFlags
, including the details of
all packages, which packages are exposed, and which modules they
provide.
The package state is computed by initPackages
, and kept in DynFlags.
It is influenced by various package flags:
-package pkg
and-package-id pkg
causepkg
to become exposed. If-hide-all-packages
was not specified, these commands also cause all other packages with the same name to become hidden.-hide-package pkg
causespkg
to become hidden.- (there are a few more flags, check below for their semantics)
The package state has the following properties.
- Let
exposedPackages
be the set of packages thus exposed. LetdepExposedPackages
be the transitive closure fromexposedPackages
of their dependencies. - When searching for a module from a preload import declaration,
only the exposed modules in
exposedPackages
are valid. - When searching for a module from an implicit import, all modules
from
depExposedPackages
are valid. - When linking in a compilation manager mode, we link in packages the
program depends on (the compiler knows this list by the
time it gets to the link step). Also, we link in all packages
which were mentioned with preload
-package
flags on the command-line, or are a transitive dependency of same, or are "base"/"rts". The reason for this is that we might need packages which don't contain any Haskell modules, and therefore won't be discovered by the normal mechanism of dependency tracking.
Given a module name, there may be multiple ways it came into scope, possibly simultaneously. This data type tracks all the possible ways it could have come into scope. Warning: don't use the record functions, they're partial!
Constructors
ModHidden | Module is hidden, and thus never will be available for import. (But maybe the user didn't realize), so we'll still keep track of these modules.) |
ModUnusable UnusablePackageReason | Module is unavailable because the package is unusable. |
ModOrigin | Module is public, and could have come from some places. |
Fields
|
Instances
Semigroup ModuleOrigin | |
Defined in Packages Methods (<>) :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin # sconcat :: NonEmpty ModuleOrigin -> ModuleOrigin # stimes :: Integral b => b -> ModuleOrigin -> ModuleOrigin # | |
Monoid ModuleOrigin | |
Defined in Packages Methods mempty :: ModuleOrigin # mappend :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin # mconcat :: [ModuleOrigin] -> ModuleOrigin # | |
Outputable ModuleOrigin | |
Defined in Packages |
newtype PackageName #
Constructors
PackageName FastString |
Instances
Eq PackageName | |
Defined in PackageConfig | |
Ord PackageName | |
Defined in PackageConfig Methods compare :: PackageName -> PackageName -> Ordering # (<) :: PackageName -> PackageName -> Bool # (<=) :: PackageName -> PackageName -> Bool # (>) :: PackageName -> PackageName -> Bool # (>=) :: PackageName -> PackageName -> Bool # max :: PackageName -> PackageName -> PackageName # min :: PackageName -> PackageName -> PackageName # | |
Show PackageName Source # | |
Defined in Development.IDE.GHC.Orphans Methods showsPrec :: Int -> PackageName -> ShowS # show :: PackageName -> String # showList :: [PackageName] -> ShowS # | |
Uniquable PackageName | |
Defined in PackageConfig Methods getUnique :: PackageName -> Unique # | |
Outputable PackageName | |
Defined in PackageConfig | |
BinaryStringRep PackageName | |
Defined in PackageConfig |
Linker
Objects which have yet to be linked by the compiler
Constructors
DotO FilePath | An object file (.o) |
DotA FilePath | Static archive file (.a) |
DotDLL FilePath | Dynamically linked library file (.so, .dll, .dylib) |
BCOs CompiledByteCode [SptEntry] | A byte-code object, lives only in memory. Also carries some static pointer table entries which should be loaded along with the BCOs. See Note [Grant plan for static forms] in StaticPtrTable. |
Information we can use to dynamically link modules into the compiler
Constructors
LM | |
Fields
|
initDynLinker :: HscEnv -> IO () Source #
Hooks
type MetaHook (f :: Type -> Type) = MetaRequest -> LHsExpr GhcTc -> f MetaResult #
data MetaRequest #
The supported metaprogramming result types
Constructors
MetaE (LHsExpr GhcPs -> MetaResult) | |
MetaP (LPat GhcPs -> MetaResult) | |
MetaT (LHsType GhcPs -> MetaResult) | |
MetaD ([LHsDecl GhcPs] -> MetaResult) | |
MetaAW (Serialized -> MetaResult) |
metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized #
HPT
addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable #
addListToHpt :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable #
Driver-Make
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).
Constructors
Target | |
Fields
|
Constructors
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. |
mkModuleGraph :: [ModSummary] -> ModuleGraph #
GHCi
initObjLinker :: HscEnv -> IO () Source #
data InteractiveImport #
Constructors
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 Methods showsPrec :: Int -> InteractiveImport -> ShowS # show :: InteractiveImport -> String # showList :: [InteractiveImport] -> ShowS # | |
Outputable InteractiveImport | |
Defined in HscTypes |
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.)
parseImportDecl :: GhcMonad m => String -> m (ImportDecl GhcPs) #
A command-line warning message and the reason it arose
Constructors
Warn | |
Fields
|
ModLocation
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 Methods showsPrec :: Int -> ModLocation -> ShowS # show :: ModLocation -> String # showList :: [ModLocation] -> ShowS # | |
Outputable ModLocation | |
Defined in Module |
pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> ModLocation Source #
ml_hs_file :: ModLocation -> Maybe FilePath #
ml_obj_file :: ModLocation -> FilePath #
ml_hi_file :: ModLocation -> FilePath #
ml_hie_file :: ModLocation -> FilePath Source #
DataCon
dataConExTyCoVars :: DataCon -> [TyCoVar] Source #
Role
Constructors
Nominal | |
Representational | |
Phantom |
Instances
Eq Role | |
Data Role | |
Defined in CoAxiom Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role # dataTypeOf :: Role -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Role) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) # gmapT :: (forall b. Data b => b -> b) -> Role -> Role # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # | |
Ord Role | |
Binary Role | |
Outputable Role | |
Annotate (Maybe Role) | |
Panic
Other
data CoreModule #
A CoreModule consists of just the fields of a ModGuts
that are needed for
the compileToCoreModule
interface.
Constructors
CoreModule | |
Fields
|
Instances
Show CoreModule Source # | |
Defined in Development.IDE.GHC.Orphans Methods showsPrec :: Int -> CoreModule -> ShowS # show :: CoreModule -> String # showList :: [CoreModule] -> ShowS # | |
NFData CoreModule Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: CoreModule -> () # | |
Outputable CoreModule | |
Defined in GHC |
data SafeHaskellMode #
The various Safe Haskell modes
Constructors
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 Methods (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
Show SafeHaskellMode | |
Defined in DynFlags Methods showsPrec :: Int -> SafeHaskellMode -> ShowS # show :: SafeHaskellMode -> String # showList :: [SafeHaskellMode] -> ShowS # | |
NFData SafeHaskellMode Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: SafeHaskellMode -> () # | |
Outputable SafeHaskellMode | |
Defined in DynFlags |
pattern GRE :: Name -> Parent -> Bool -> [ImportSpec] -> GlobalRdrElt Source #
gre_name :: GlobalRdrElt -> Name Source #
gre_imp :: GlobalRdrElt -> [ImportSpec] Source #
gre_lcl :: GlobalRdrElt -> Bool Source #
gre_par :: GlobalRdrElt -> Parent Source #
Util Module re-exports
isKindLevel :: TypeOrKind -> Bool #
isTypeLevel :: TypeOrKind -> Bool #
mkIntWithInf :: Int -> IntWithInf #
Inject any integer into an IntWithInf
treatZeroAsInf :: Int -> IntWithInf #
Turn a positive number into an IntWithInf
, where 0 represents infinity
intGtLimit :: Int -> IntWithInf -> Bool #
infinity :: IntWithInf #
A representation of infinity
integralFractionalLit :: Bool -> Integer -> FractionalLit #
mkFractionalLit :: Real a => a -> FractionalLit #
mkIntegralLit :: Integral a => a -> IntegralLit #
isEarlyActive :: Activation -> Bool #
isAlwaysActive :: Activation -> Bool #
isNeverActive :: Activation -> Bool #
competesWith :: Activation -> Activation -> Bool #
isActiveIn :: PhaseNum -> Activation -> Bool #
isActive :: CompilerPhase -> Activation -> Bool #
pprInlineDebug :: InlinePragma -> SDoc #
pprInline :: InlinePragma -> SDoc #
inlinePragmaSat :: InlinePragma -> Maybe Arity #
isAnyInlinePragma :: InlinePragma -> Bool #
isInlinablePragma :: InlinePragma -> Bool #
isInlinePragma :: InlinePragma -> Bool #
noUserInlineSpec :: InlineSpec -> Bool #
isFunLike :: RuleMatchInfo -> Bool #
isConLike :: RuleMatchInfo -> Bool #
pprWithSourceText :: SourceText -> SDoc -> SDoc #
Special combinator for showing string literals.
failed :: SuccessFlag -> Bool #
succeeded :: SuccessFlag -> Bool #
successIf :: Bool -> SuccessFlag #
zapFragileOcc :: OccInfo -> OccInfo #
isStrongLoopBreaker :: OccInfo -> Bool #
isWeakLoopBreaker :: OccInfo -> Bool #
isAlwaysTailCalled :: OccInfo -> Bool #
zapOccTailCallInfo :: OccInfo -> OccInfo #
tailCallInfo :: OccInfo -> TailCallInfo #
seqOccInfo :: OccInfo -> () #
isManyOccs :: OccInfo -> Bool #
Arguments
:: (a -> SDoc) | The pretty printing function to use |
-> a | The things to be pretty printed |
-> ConTag | Alternative (one-based) |
-> Arity | Arity |
-> SDoc |
|
Pretty print an alternative in an unboxed sum e.g. "| a | |".
tupleParens :: TupleSort -> SDoc -> SDoc #
boxityTupleSort :: Boxity -> TupleSort #
tupleSortBoxity :: TupleSort -> Boxity #
hasOverlappingFlag :: OverlapMode -> Bool #
hasOverlappableFlag :: OverlapMode -> Bool #
hasIncoherentFlag :: OverlapMode -> Bool #
isGenerated :: Origin -> Bool #
boolToRecFlag :: Bool -> RecFlag #
isTopLevel :: TopLevelFlag -> Bool #
isNotTopLevel :: TopLevelFlag -> Bool #
funTyFixity :: Fixity #
negateFixity :: Fixity #
defaultFixity :: Fixity #
minPrecedence :: Int #
maxPrecedence :: Int #
pprRuleName :: RuleName -> SDoc #
pprWarningTxtForMsg :: WarningTxt -> SDoc #
bumpVersion :: Version -> Version #
isPromoted :: PromotionFlag -> Bool #
bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo #
worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo #
hasNoOneShotInfo :: OneShotInfo -> Bool #
isOneShotInfo :: OneShotInfo -> Bool #
noOneShotInfo :: OneShotInfo #
It is always safe to assume that an Id
has no lambda-bound variable information
alignmentOf :: Int -> Alignment #
mkAlignment :: Int -> Alignment #
pickLR :: LeftOrRight -> (a, a) -> a #
data LeftOrRight #
Instances
Eq LeftOrRight | |
Defined in BasicTypes | |
Data LeftOrRight | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight # toConstr :: LeftOrRight -> Constr # dataTypeOf :: LeftOrRight -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) # gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # | |
Outputable LeftOrRight | |
Defined in BasicTypes |
The number of value arguments that can be applied to a value before it does "real work". So: fib 100 has arity 0 x -> fib x has arity 1 See also Note [Definition of arity] in CoreArity
The number of arguments that a join point takes. Unlike the arity of a function, this is a purely syntactic property and is fixed when the join point is created (or converted from a value). Both type and value arguments are counted.
Constructor Tag
Type of the tags associated with each constructor possibility or superclass selector
A power-of-two alignment
Instances
Eq Alignment | |
Ord Alignment | |
Outputable Alignment | |
data OneShotInfo #
If the Id
is a lambda-bound variable then it may have lambda-bound
variable info. Sometimes we know whether the lambda binding this variable
is a "one-shot" lambda; that is, whether it is applied at most once.
This information may be useful in optimisation, as computations may safely be floated inside such a lambda without risk of duplicating work.
Constructors
NoOneShotInfo | No information |
OneShotLam | The lambda is applied at most once. |
Instances
Eq OneShotInfo | |
Defined in BasicTypes | |
Outputable OneShotInfo | |
Defined in BasicTypes |
Constructors
NotSwapped | |
IsSwapped |
data PromotionFlag #
Is a TyCon a promoted data constructor or just a normal type constructor?
Constructors
NotPromoted | |
IsPromoted |
Instances
Eq PromotionFlag | |
Defined in BasicTypes Methods (==) :: PromotionFlag -> PromotionFlag -> Bool # (/=) :: PromotionFlag -> PromotionFlag -> Bool # | |
Data PromotionFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PromotionFlag # toConstr :: PromotionFlag -> Constr # dataTypeOf :: PromotionFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PromotionFlag) # gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # |
data FunctionOrData #
Constructors
IsFunction | |
IsData |
Instances
data StringLiteral #
A String Literal in the source, including its original raw format for use by source to source manipulation tools.
Constructors
StringLiteral | |
Fields
|
Instances
Eq StringLiteral | |
Defined in BasicTypes Methods (==) :: StringLiteral -> StringLiteral -> Bool # (/=) :: StringLiteral -> StringLiteral -> Bool # | |
Data StringLiteral | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StringLiteral -> c StringLiteral # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StringLiteral # toConstr :: StringLiteral -> Constr # dataTypeOf :: StringLiteral -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StringLiteral) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StringLiteral) # gmapT :: (forall b. Data b => b -> b) -> StringLiteral -> StringLiteral # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StringLiteral -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StringLiteral -> r # gmapQ :: (forall d. Data d => d -> u) -> StringLiteral -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StringLiteral -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLiteral -> m StringLiteral # | |
Outputable StringLiteral | |
Defined in BasicTypes | |
Annotate StringLiteral | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater Methods markAST :: SrcSpan -> StringLiteral -> Annotated () # |
data WarningTxt #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
Constructors
WarningTxt (Located SourceText) [Located StringLiteral] | |
DeprecatedTxt (Located SourceText) [Located StringLiteral] |
Instances
Eq WarningTxt | |
Defined in BasicTypes | |
Data WarningTxt | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarningTxt -> c WarningTxt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WarningTxt # toConstr :: WarningTxt -> Constr # dataTypeOf :: WarningTxt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WarningTxt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningTxt) # gmapT :: (forall b. Data b => b -> b) -> WarningTxt -> WarningTxt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt -> r # gmapQ :: (forall d. Data d => d -> u) -> WarningTxt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarningTxt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt # | |
Outputable WarningTxt | |
Defined in BasicTypes | |
Annotate WarningTxt | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater Methods markAST :: SrcSpan -> WarningTxt -> Annotated () # |
type RuleName = FastString #
Constructors
Fixity SourceText Int FixityDirection |
Instances
Eq Fixity | |
Data Fixity | |
Defined in BasicTypes Methods 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 Methods (==) :: FixityDirection -> FixityDirection -> Bool # (/=) :: FixityDirection -> FixityDirection -> Bool # | |
Data FixityDirection | |
Defined in BasicTypes Methods 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 |
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 Methods (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Data LexicalFixity | |
Defined in BasicTypes Methods 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 |
data TopLevelFlag #
Constructors
TopLevel | |
NotTopLevel |
Instances
Outputable TopLevelFlag | |
Defined in BasicTypes |
Instances
Eq Boxity | |
Data Boxity | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boxity -> c Boxity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boxity # toConstr :: Boxity -> Constr # dataTypeOf :: Boxity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Boxity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity) # gmapT :: (forall b. Data b => b -> b) -> Boxity -> Boxity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQ :: (forall d. Data d => d -> u) -> Boxity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # | |
Outputable Boxity | |
Recursivity Flag
Constructors
Recursive | |
NonRecursive |
Instances
Eq RecFlag | |
Data RecFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecFlag -> c RecFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFlag # toConstr :: RecFlag -> Constr # dataTypeOf :: RecFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag) # gmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> RecFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # | |
Outputable RecFlag | |
Constructors
FromSource | |
Generated |
Instances
Eq Origin | |
Data Origin | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Origin -> c Origin # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Origin # toConstr :: Origin -> Constr # dataTypeOf :: Origin -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Origin) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin) # gmapT :: (forall b. Data b => b -> b) -> Origin -> Origin # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQ :: (forall d. Data d => d -> u) -> Origin -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Origin -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # | |
Outputable Origin | |
data OverlapFlag #
The semantics allowed for overlapping instances for a particular
instance. See Note [Safe Haskell isSafeOverlap] (in hs
) for a
explanation of the isSafeOverlap
field.
AnnKeywordId
:AnnOpen
'{-# OVERLAPPABLE'
or'{-# OVERLAPPING'
or'{-# OVERLAPS'
or'{-# INCOHERENT'
,AnnClose
`#-}`
,
Constructors
OverlapFlag | |
Fields |
Instances
Eq OverlapFlag | |
Defined in BasicTypes | |
Data OverlapFlag | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapFlag # toConstr :: OverlapFlag -> Constr # dataTypeOf :: OverlapFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapFlag) # gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # | |
Outputable OverlapFlag | |
Defined in BasicTypes |
data OverlapMode #
Constructors
NoOverlap SourceText | This instance must not overlap another |
Overlappable SourceText | Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve Example: constraint (Foo [Int]) instance Foo [Int] instance {--} Foo [a] Since the second instance has the Overlappable flag, the first instance will be chosen (otherwise its ambiguous which to choose) |
Overlapping SourceText | Silently ignore any more general instances that may be used to solve the constraint. Example: constraint (Foo [Int]) instance {--} Foo [Int] instance Foo [a] Since the first instance has the Overlapping flag, the second---more general---instance will be ignored (otherwise it is ambiguous which to choose) |
Overlaps SourceText | Equivalent to having both |
Incoherent SourceText | Behave like Overlappable and Overlapping, and in addition pick an an arbitrary one if there are multiple matching candidates, and don't worry about later instantiation Example: constraint (Foo [b])
instance {-# INCOHERENT -} Foo [Int]
instance Foo [a]
Without the Incoherent flag, we'd complain that
instantiating |
Instances
Eq OverlapMode | |
Defined in BasicTypes | |
Data OverlapMode | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapMode -> c OverlapMode # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapMode # toConstr :: OverlapMode -> Constr # dataTypeOf :: OverlapMode -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapMode) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapMode) # gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapMode -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapMode -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # | |
Outputable OverlapMode | |
Defined in BasicTypes | |
Annotate OverlapMode | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater Methods markAST :: SrcSpan -> OverlapMode -> Annotated () # | |
ToHie (Located OverlapMode) | |
Defined in Compat.HieAst Methods toHie :: Located OverlapMode -> HieM [HieAST Type] |
Constructors
BoxedTuple | |
UnboxedTuple | |
ConstraintTuple |
Instances
Eq TupleSort | |
Data TupleSort | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TupleSort -> c TupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TupleSort # toConstr :: TupleSort -> Constr # dataTypeOf :: TupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort) # gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> TupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # | |
Outputable TupleSort | |
identifier Occurrence Information
Constructors
ManyOccs | There are many occurrences, or unknown occurrences |
Fields
| |
IAmDead | Marks unused variables. Sometimes useful for lambda and case-bound variables. |
OneOcc | Occurs exactly once (per branch), not inside a rule |
Fields
| |
IAmALoopBreaker | This identifier breaks a loop of mutually recursive functions. The field marks whether it is only a loop breaker due to a reference in a rule |
Fields
|
type InterestingCxt = Bool #
Interesting Context
data TailCallInfo #
Constructors
AlwaysTailCalled JoinArity | |
NoTailCallInfo |
Instances
Eq TailCallInfo | |
Defined in BasicTypes | |
Outputable TailCallInfo | |
Defined in BasicTypes |
data DefMethSpec ty #
Default Method Specification
Instances
Binary (DefMethSpec IfaceType) | |
Outputable (DefMethSpec ty) | |
Defined in BasicTypes |
data SuccessFlag #
Instances
Outputable SuccessFlag | |
Defined in BasicTypes |
data SourceText #
Constructors
SourceText String | |
NoSourceText | For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item. |
Instances
Eq SourceText | |
Defined in BasicTypes | |
Data SourceText | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceText -> c SourceText # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceText # toConstr :: SourceText -> Constr # dataTypeOf :: SourceText -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceText) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText) # gmapT :: (forall b. Data b => b -> b) -> SourceText -> SourceText # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceText -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceText -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # | |
Show SourceText | |
Defined in BasicTypes Methods showsPrec :: Int -> SourceText -> ShowS # show :: SourceText -> String # showList :: [SourceText] -> ShowS # | |
Outputable SourceText | |
Defined in BasicTypes | |
Annotate (SourceText, FastString) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater Methods markAST :: SrcSpan -> (SourceText, FastString) -> Annotated () # |
data CompilerPhase #
Constructors
Phase PhaseNum | |
InitialPhase |
Instances
Outputable CompilerPhase | |
Defined in BasicTypes |
data Activation #
Constructors
NeverActive | |
AlwaysActive | |
ActiveBefore SourceText PhaseNum | |
ActiveAfter SourceText PhaseNum |
Instances
Eq Activation | |
Defined in BasicTypes | |
Data Activation | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Activation -> c Activation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Activation # toConstr :: Activation -> Constr # dataTypeOf :: Activation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Activation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation) # gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQ :: (forall d. Data d => d -> u) -> Activation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # | |
Outputable Activation | |
Defined in BasicTypes |
data RuleMatchInfo #
Rule Match Information
Instances
Eq RuleMatchInfo | |
Defined in BasicTypes Methods (==) :: RuleMatchInfo -> RuleMatchInfo -> Bool # (/=) :: RuleMatchInfo -> RuleMatchInfo -> Bool # | |
Data RuleMatchInfo | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleMatchInfo -> c RuleMatchInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleMatchInfo # toConstr :: RuleMatchInfo -> Constr # dataTypeOf :: RuleMatchInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RuleMatchInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleMatchInfo) # gmapT :: (forall b. Data b => b -> b) -> RuleMatchInfo -> RuleMatchInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatchInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleMatchInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleMatchInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatchInfo -> m RuleMatchInfo # | |
Show RuleMatchInfo | |
Defined in BasicTypes Methods showsPrec :: Int -> RuleMatchInfo -> ShowS # show :: RuleMatchInfo -> String # showList :: [RuleMatchInfo] -> ShowS # | |
Outputable RuleMatchInfo | |
Defined in BasicTypes |
data InlinePragma #
Constructors
InlinePragma | |
Fields
|
Instances
Eq InlinePragma | |
Defined in BasicTypes | |
Data InlinePragma | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlinePragma -> c InlinePragma # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlinePragma # toConstr :: InlinePragma -> Constr # dataTypeOf :: InlinePragma -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlinePragma) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlinePragma) # gmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQ :: (forall d. Data d => d -> u) -> InlinePragma -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # | |
Outputable InlinePragma | |
Defined in BasicTypes |
data InlineSpec #
Inline Specification
Constructors
Inline | |
Inlinable | |
NoInline | |
NoUserInline |
Instances
Eq InlineSpec | |
Defined in BasicTypes | |
Data InlineSpec | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlineSpec -> c InlineSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlineSpec # toConstr :: InlineSpec -> Constr # dataTypeOf :: InlineSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlineSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec) # gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> InlineSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # | |
Show InlineSpec | |
Defined in BasicTypes Methods showsPrec :: Int -> InlineSpec -> ShowS # show :: InlineSpec -> String # showList :: [InlineSpec] -> ShowS # | |
Outputable InlineSpec | |
Defined in BasicTypes |
data IntegralLit #
Integral Literal
Used (instead of Integer) to represent negative zegative zero which is required for NegativeLiterals extension to correctly parse `-0::Double` as negative zero. See also #13211.
Instances
Eq IntegralLit | |
Defined in BasicTypes | |
Data IntegralLit | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntegralLit -> c IntegralLit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntegralLit # toConstr :: IntegralLit -> Constr # dataTypeOf :: IntegralLit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntegralLit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntegralLit) # gmapT :: (forall b. Data b => b -> b) -> IntegralLit -> IntegralLit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntegralLit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntegralLit -> r # gmapQ :: (forall d. Data d => d -> u) -> IntegralLit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntegralLit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntegralLit -> m IntegralLit # | |
Ord IntegralLit | |
Defined in BasicTypes Methods compare :: IntegralLit -> IntegralLit -> Ordering # (<) :: IntegralLit -> IntegralLit -> Bool # (<=) :: IntegralLit -> IntegralLit -> Bool # (>) :: IntegralLit -> IntegralLit -> Bool # (>=) :: IntegralLit -> IntegralLit -> Bool # max :: IntegralLit -> IntegralLit -> IntegralLit # min :: IntegralLit -> IntegralLit -> IntegralLit # | |
Show IntegralLit | |
Defined in BasicTypes Methods showsPrec :: Int -> IntegralLit -> ShowS # show :: IntegralLit -> String # showList :: [IntegralLit] -> ShowS # | |
Outputable IntegralLit | |
Defined in BasicTypes |
data FractionalLit #
Fractional Literal
Used (instead of Rational) to represent exactly the floating point literal that we encountered in the user's source program. This allows us to pretty-print exactly what the user wrote, which is important e.g. for floating point numbers that can't represented as Doubles (we used to via Double for pretty-printing). See also #2245.
Instances
data IntWithInf #
An integer or infinity
Instances
Eq IntWithInf | |
Defined in BasicTypes | |
Num IntWithInf | |
Defined in BasicTypes Methods (+) :: IntWithInf -> IntWithInf -> IntWithInf # (-) :: IntWithInf -> IntWithInf -> IntWithInf # (*) :: IntWithInf -> IntWithInf -> IntWithInf # negate :: IntWithInf -> IntWithInf # abs :: IntWithInf -> IntWithInf # signum :: IntWithInf -> IntWithInf # fromInteger :: Integer -> IntWithInf # | |
Ord IntWithInf | |
Defined in BasicTypes Methods compare :: IntWithInf -> IntWithInf -> Ordering # (<) :: IntWithInf -> IntWithInf -> Bool # (<=) :: IntWithInf -> IntWithInf -> Bool # (>) :: IntWithInf -> IntWithInf -> Bool # (>=) :: IntWithInf -> IntWithInf -> Bool # max :: IntWithInf -> IntWithInf -> IntWithInf # min :: IntWithInf -> IntWithInf -> IntWithInf # | |
Outputable IntWithInf | |
Defined in BasicTypes |
data SpliceExplicitFlag #
Constructors
ExplicitSplice | = $(f x y) |
ImplicitSplice | = f x y, i.e. a naked top level expression |
Instances
Data SpliceExplicitFlag | |
Defined in BasicTypes Methods 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 # |
data TypeOrKind #
Flag to see whether we're type-checking terms or kind-checking types
Instances
Eq TypeOrKind | |
Defined in BasicTypes | |
Outputable TypeOrKind | |
Defined in BasicTypes |
module Class
coercionKind :: Coercion -> Pair Type #
If it is the case that
c :: (t1 ~ t2)
i.e. the kind of c
relates t1
and t2
, then coercionKind c = Pair t1 t2
.
module Predicate
module ConLike
module CoreUtils
Extract the type constructor, type argument, data constructor and it's representation argument types from a type if it is a product type.
Precisely, we return Just
for any type that is all of:
- Concrete (i.e. constructors visible)
- Single-constructor
- Not existentially quantified
Whether the type is a data
type or a newtype
promoteDataCon :: DataCon -> TyCon #
dataConUserTyVarsArePermuted :: DataCon -> Bool #
Were the type variables of the data con written in a different order than the regular order (universal tyvars followed by existential tyvars)?
This is not a cheap test, so we minimize its use in GHC as much as possible.
Currently, its only call site in the GHC codebase is in mkDataConRep
in
MkId, and so dataConUserTyVarsArePermuted
is only called at most once
during a data constructor's lifetime.
dataConCannotMatch :: [Type] -> DataCon -> Bool #
classDataCon :: Class -> DataCon #
specialPromotedDc :: DataCon -> Bool #
Should this DataCon be allowed in a type even without -XDataKinds? Currently, only Lifted & Unlifted
isVanillaDataCon :: DataCon -> Bool #
Vanilla DataCon
s are those that are nice boring Haskell 98 constructors
isUnboxedTupleCon :: DataCon -> Bool #
isTupleDataCon :: DataCon -> Bool #
dataConIdentity :: DataCon -> ByteString #
The string package:module.name
identifying a constructor, which is attached
to its info table and used by the GHCi debugger and the heap profiler
dataConRepArgTys :: DataCon -> [Type] #
Returns the arg types of the worker, including *all* non-dependent evidence, after any flattening has been done and without substituting for any type variables
dataConOrigArgTys :: DataCon -> [Type] #
Returns the argument types of the wrapper, excluding all dictionary arguments and without substituting for any type variables
Arguments
:: DataCon | A datacon with no existentials or equality constraints However, it can have a dcTheta (notably it can be a class dictionary, with superclasses) |
-> [Type] | Instantiated at these types |
-> [Type] |
Finds the instantiated types of the arguments required to construct a
DataCon
representation
NB: these INCLUDE any dictionary args
but EXCLUDE the data-declaration context, which is discarded
It's all post-flattening etc; this is a representation type
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.
dataConOrigResTy :: DataCon -> Type #
dataConInstSig :: DataCon -> [Type] -> ([TyCoVar], ThetaType, [Type]) #
Instantiate the universal tyvars of a data con, returning ( instantiated existentials , instantiated constraints including dependent GADT equalities which are *also* listed in the instantiated existentials , instantiated args)
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
dataConBoxer :: DataCon -> Maybe DataConBoxer #
dataConImplBangs :: DataCon -> [HsImplBang] #
dataConRepStrictness :: DataCon -> [StrictnessMark] #
Give the demands on the arguments of a Core constructor application (Con dc args)
isNullaryRepDataCon :: DataCon -> Bool #
Return whether there are any argument types for this DataCon
s runtime representation type
See Note [DataCon arities]
isNullarySrcDataCon :: DataCon -> Bool #
Return whether there are any argument types for this DataCon
s original source type
See Note [DataCon arities]
dataConRepArity :: DataCon -> Arity #
Gives the number of actual fields in the representation of the data constructor. This may be more than appear in the source code; the extra ones are the existentially quantified dictionaries
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
dataConFieldType_maybe :: DataCon -> FieldLabelString -> Maybe (FieldLabel, Type) #
dataConFieldType :: DataCon -> FieldLabelString -> Type #
Extract the type for any given labelled field of the DataCon
dataConImplicitTyThings :: DataCon -> [TyThing] #
Find all the Id
s implicitly brought into scope by the data constructor. Currently,
the union of the dataConWorkId
and the dataConWrapId
dataConWrapId :: DataCon -> Id #
Returns an Id which looks like the Haskell-source constructor by using
the wrapper if it exists (see dataConWrapId_maybe
) and failing over to
the worker (see dataConWorkId
)
dataConWrapId_maybe :: DataCon -> Maybe Id #
Get the Id of the DataCon
wrapper: a function that wraps the "actual"
constructor so it has the type visible in the source program: c.f.
dataConWorkId
.
Returns Nothing if there is no wrapper, which occurs for an algebraic data
constructor and also for a newtype (whose constructor is inlined
compulsorily)
dataConWorkId :: DataCon -> Id #
dataConTheta :: DataCon -> ThetaType #
The *full* constraints on the constructor type, including dependent GADT equalities.
dataConEqSpec :: DataCon -> [EqSpec] #
Equalities derived from the result type of the data constructor, as written by the programmer in any GADT declaration. This includes *all* GADT-like equalities, including those written in by hand by the programmer.
dataConUnivAndExTyCoVars :: DataCon -> [TyCoVar] #
Both the universal and existential type/coercion variables of the constructor
dataConUnivTyVars :: DataCon -> [TyVar] #
The universally-quantified type variables of the constructor
dataConIsInfix :: DataCon -> Bool #
Should the DataCon
be presented infix?
dataConRepType :: DataCon -> Type #
The representation type of the data constructor, i.e. the sort type that will represent values of this type at runtime
dataConOrigTyCon :: DataCon -> TyCon #
The original type constructor used in the definition of this data constructor. In case of a data family instance, that will be the family type constructor.
dataConTagZ :: DataCon -> ConTagZ #
dataConTag :: DataCon -> ConTag #
The tag used for ordering DataCon
s
Arguments
:: Name | |
-> Bool | Is the constructor declared infix? |
-> TyConRepName | TyConRepName for the promoted TyCon |
-> [HsSrcBang] | Strictness/unpack annotations, from user |
-> [FieldLabel] | Field labels for the constructor, if it is a record, otherwise empty |
-> [TyVar] | Universals. |
-> [TyCoVar] | Existentials. |
-> [TyVarBinder] | User-written |
-> [EqSpec] | GADT equalities |
-> KnotTied ThetaType | Theta-type occurring before the arguments proper |
-> [KnotTied Type] | Original argument types |
-> KnotTied Type | Original result type |
-> RuntimeRepInfo | See comments on |
-> KnotTied TyCon | Representation type constructor |
-> ConTag | Constructor tag |
-> ThetaType | The "stupid theta", context of the data
declaration e.g. |
-> Id | Worker Id |
-> DataConRep | Representation |
-> DataCon |
Build a new data constructor
isMarkedStrict :: StrictnessMark -> Bool #
isSrcUnpacked :: SrcUnpackedness -> Bool #
isSrcStrict :: SrcStrictness -> Bool #
isBanged :: HsImplBang -> Bool #
eqHsBang :: HsImplBang -> HsImplBang -> Bool #
Compare strictness annotations
substEqSpec :: TCvSubst -> EqSpec -> EqSpec #
Substitute in an EqSpec
. Precondition: if the LHS of the EqSpec
is mapped in the substitution, it is mapped to a type variable, not
a full type.
eqSpecPreds :: [EqSpec] -> ThetaType #
eqSpecPair :: EqSpec -> (TyVar, Type) #
eqSpecType :: EqSpec -> Type #
eqSpecTyVar :: EqSpec -> TyVar #
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)
Constructors
HsSrcBang SourceText SrcUnpackedness SrcStrictness |
Instances
Data HsSrcBang | |
Defined in DataCon Methods 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.
Constructors
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 Methods 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 |
data SrcStrictness #
Source Strictness
What strictness annotation the user wrote
Constructors
SrcLazy | Lazy, ie '~' |
SrcStrict | Strict, ie |
NoSrcStrict | no strictness annotation |
Instances
Eq SrcStrictness | |
Defined in DataCon Methods (==) :: SrcStrictness -> SrcStrictness -> Bool # (/=) :: SrcStrictness -> SrcStrictness -> Bool # | |
Data SrcStrictness | |
Defined in DataCon Methods 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 Methods put_ :: BinHandle -> SrcStrictness -> IO () # put :: BinHandle -> SrcStrictness -> IO (Bin SrcStrictness) # get :: BinHandle -> IO SrcStrictness # | |
Outputable SrcStrictness | |
Defined in DataCon |
data SrcUnpackedness #
Source Unpackedness
What unpackedness the user requested
Constructors
SrcUnpack | |
SrcNoUnpack | |
NoSrcUnpack | no unpack pragma |
Instances
Eq SrcUnpackedness | |
Defined in DataCon Methods (==) :: SrcUnpackedness -> SrcUnpackedness -> Bool # (/=) :: SrcUnpackedness -> SrcUnpackedness -> Bool # | |
Data SrcUnpackedness | |
Defined in DataCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcUnpackedness # toConstr :: SrcUnpackedness -> Constr # dataTypeOf :: SrcUnpackedness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcUnpackedness) # gmapT :: (forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcUnpackedness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # | |
Binary SrcUnpackedness | |
Defined in DataCon Methods put_ :: BinHandle -> SrcUnpackedness -> IO () # put :: BinHandle -> SrcUnpackedness -> IO (Bin SrcUnpackedness) # get :: BinHandle -> IO SrcUnpackedness # | |
Outputable SrcUnpackedness | |
Defined in DataCon |
data StrictnessMark #
Constructors
MarkedStrict | |
NotMarkedStrict |
Instances
Outputable StrictnessMark | |
Defined in DataCon |
dataConTyCon :: DataCon -> TyCon #
The type constructor that we are building via this data constructor
dataConUserTyVars :: DataCon -> [TyVar] #
The type variables of the constructor, in the order the user wrote them
dataConUserTyVarBinders :: DataCon -> [TyVarBinder] #
TyCoVarBinder
s for the type variables of the constructor, in the order the
user wrote them
dataConSourceArity :: DataCon -> Arity #
Source-level arity of the data constructor
dataConFieldLabels :: DataCon -> [FieldLabel] #
The labels for the fields of this particular DataCon
dataConInstOrigArgTys :: DataCon -> [Type] -> [Type] #
Returns just the instantiated value argument types of a DataCon
,
(excluding dictionary args)
dataConStupidTheta :: DataCon -> ThetaType #
The "stupid theta" of the DataCon
, such as data Eq a
in:
data Eq a => T a = ...
dataConFullSig :: DataCon -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, [Type], Type) #
The "full signature" of the DataCon
returns, in order:
1) The result of dataConUnivTyVars
2) The result of dataConExTyCoVars
3) The non-dependent GADT equalities. Dependent GADT equalities are implied by coercion variables in return value (2).
4) The other constraints of the data constructor type, excluding GADT equalities
5) The original argument types to the DataCon
(i.e. before
any change of the representation of the type)
6) The original result type of the DataCon
isUnboxedSumCon :: DataCon -> Bool #
A data constructor
Instances
Eq DataCon | |
Data DataCon | |
Defined in DataCon Methods 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 Methods pprBndr :: BindingSite -> DataCon -> SDoc # pprPrefixOcc :: DataCon -> SDoc # pprInfixOcc :: DataCon -> SDoc # bndrIsJoin_maybe :: DataCon -> Maybe Int # |
data DataConRep #
Data Constructor Representation See Note [Data constructor workers and wrappers]
Constructors
NoDataConRep | |
DCR | |
Fields
|
An EqSpec
is a tyvar/type pair representing an equality made in
rejigging a GADT constructor
type FieldLabelString = FastString #
Field labels are just represented as strings; they are not necessarily unique (even within a module)
type FieldLabel = FieldLbl Name #
Fields in an algebraic record type
Constructors
FieldLabel | |
Fields
|
Instances
Functor FieldLbl | |
Foldable FieldLbl | |
Defined in FieldLabel Methods fold :: Monoid m => FieldLbl m -> m # foldMap :: Monoid m => (a -> m) -> FieldLbl a -> m # foldMap' :: Monoid m => (a -> m) -> FieldLbl a -> m # foldr :: (a -> b -> b) -> b -> FieldLbl a -> b # foldr' :: (a -> b -> b) -> b -> FieldLbl a -> b # foldl :: (b -> a -> b) -> b -> FieldLbl a -> b # foldl' :: (b -> a -> b) -> b -> FieldLbl a -> b # foldr1 :: (a -> a -> a) -> FieldLbl a -> a # foldl1 :: (a -> a -> a) -> FieldLbl a -> a # elem :: Eq a => a -> FieldLbl a -> Bool # maximum :: Ord a => FieldLbl a -> a # minimum :: Ord a => FieldLbl a -> a # | |
Traversable FieldLbl | |
Eq a => Eq (FieldLbl a) | |
Data a => Data (FieldLbl a) | |
Defined in FieldLabel Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLbl a -> c (FieldLbl a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLbl a) # toConstr :: FieldLbl a -> Constr # dataTypeOf :: FieldLbl a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLbl a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLbl a)) # gmapT :: (forall b. Data b => b -> b) -> FieldLbl a -> FieldLbl a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldLbl a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLbl a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) # | |
Binary a => Binary (FieldLbl a) | |
Outputable a => Outputable (FieldLbl a) | |
ToHie (IEContext (Located (FieldLbl Name))) | |
Constructor Tag
Type of the tags associated with each constructor possibility or superclass selector
module DsExpr
class Functor f => Applicative (f :: Type -> Type) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*>
or liftA2
. If it defines both, then they must behave
the same as their default definitions:
(<*>
) =liftA2
id
liftA2
f x y = f<$>
x<*>
y
Further, any definition must satisfy the following:
- Identity
pure
id
<*>
v = v- Composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- Homomorphism
pure
f<*>
pure
x =pure
(f x)- Interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2
p (liftA2
q u v) =liftA2
f u .liftA2
g v
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Methods
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
Using ApplicativeDo
: 'fs
' can be understood as
the <*>
asdo
expression
do f <- fs a <- as pure (f a)
liftA2 :: (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of <*>
and fmap
.
Using ApplicativeDo
: '
' can be understood
as the liftA2
f as bsdo
expression
do a <- as b <- bs pure (f a b)
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
'as
' can be understood as the *>
bsdo
expression
do as bs
This is a tad complicated for our ApplicativeDo
extension
which will give it a Monad
constraint. For an Applicative
constraint we write it of the form
do _ <- as b <- bs pure b
(<*) :: f a -> f b -> f a infixl 4 #
Sequence actions, discarding the value of the second argument.
Using ApplicativeDo
: 'as
' can be understood as
the <*
bsdo
expression
do a <- as bs pure a
Instances
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) #
The mapAndUnzipM
function maps its first argument over a list, returning
the result as a pair of lists. This function is mainly used with complicated
data structures or a state monad.
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an
Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.
Inject a trace message into the compiled program. Whereas pprTrace prints out information *while compiling*, pprRuntimeTrace captures that information and causes it to be printed *at runtime* using Debug.Trace.trace.
pprRuntimeTrace hdr doc expr
will produce an expression that looks like
trace (hdr + doc) expr
When using this to debug a module that Debug.Trace depends on, it is necessary to import {--} Debug.Trace () in that module. We could avoid this inconvenience by wiring in Debug.Trace.trace, but that doesn't seem worth the effort and maintenance cost.
dsWhenNoErrs :: DsM a -> (a -> CoreExpr) -> DsM CoreExpr #
Runs the thing_inside. If there are no errors, then returns the expr given. Otherwise, returns unitExpr. This is useful for doing a bunch of levity polymorphism checks and then avoiding making a core App. (If we make a core App on a levity polymorphic argument, detecting how to handle the let/app invariant might call isUnliftedType, which panics on a levity polymorphic type.) See #12709 for an example of why this machinery is necessary.
dsNoLevPolyExpr :: CoreExpr -> SDoc -> DsM () #
Check an expression for levity polymorphism, failing if it is levity polymorphic.
dsNoLevPoly :: Type -> SDoc -> DsM () #
Fail with an error message if the type is levity polymorphic.
discardWarningsDs :: DsM a -> DsM a #
dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a #
dsGetCompleteMatches :: TyCon -> DsM [CompleteMatch] #
The COMPLETE
pragmas provided by the user for a given TyCon
.
dsGetMetaEnv :: DsM (NameEnv DsMetaVal) #
dsLookupConLike :: Name -> DsM ConLike #
dsLookupDataCon :: Name -> DsM DataCon #
dsLookupTyCon :: Name -> DsM TyCon #
dsLookupGlobalId :: Name -> DsM Id #
dsLookupGlobal :: Name -> DsM TyThing #
askNoErrsDs :: DsM a -> DsM (a, Bool) #
failWithDs :: SDoc -> DsM a #
errDsCoreExpr :: SDoc -> DsM CoreExpr #
Issue an error, but return the expression for (), so that we can continue reporting errors.
warnIfSetDs :: WarningFlag -> SDoc -> DsM () #
Emit a warning only if the correct WarnReason is set in the DynFlags
warnDs :: WarnReason -> SDoc -> DsM () #
Emit a warning for the current source location NB: Warns whether or not -Wxyz is set
putSrcSpanDs :: SrcSpan -> DsM a -> DsM a #
getSrcSpanDs :: DsM SrcSpan #
updPmDelta :: Delta -> DsM a -> DsM a #
Set the pattern match oracle state within the scope of the given action.
See dsl_delta
.
getPmDelta :: DsM Delta #
Get the current pattern match oracle state. See dsl_delta
.
getGhcModeDs :: DsM GhcMode #
newSysLocalsDs :: [Type] -> DsM [Id] #
newSysLocalsDsNoLP :: [Type] -> DsM [Id] #
newFailLocalDs :: Type -> DsM Id #
newSysLocalDs :: Type -> DsM Id #
newSysLocalDsNoLP :: Type -> DsM Id #
newPredVarDs :: PredType -> DsM Var #
duplicateLocalDs :: Id -> DsM Id #
data DsMatchContext #
Constructors
DsMatchContext (HsMatchContext Name) SrcSpan |
Instances
Outputable DsMatchContext | |
Defined in DsMonad |
data MatchResult #
Constructors
MatchResult CanItFail (CoreExpr -> DsM CoreExpr) |
newUniqueSupply :: TcRnIf gbl lcl UniqSupply #
whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #
unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #
unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #
data UniqSupply #
Unique Supply
A value of type UniqSupply
is unique, and it can
supply one distinct Unique
. Also, from the supply, one can
also manufacture an arbitrary number of further UniqueSupply
values,
which will be distinct from the first and from all others.
isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag) #
Checks if given WarnMsg
is a fatal warning.
prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a #
printOutputForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO () #
printInfoForUser :: DynFlags -> PrintUnqualified -> MsgDoc -> IO () #
Arguments
:: (MonadIO m, HasDynFlags m) | |
=> SDoc | The name of the phase |
-> (a -> ()) | A function to force the result
(often either |
-> m a | The body of the phase to be timed |
-> m a |
Same as withTiming
, but doesn't print timings in the
console (when given -vN
, N >= 2
or -ddump-timings
)
and gets the DynFlags from the given Monad.
See Note [withTiming] for more.
Arguments
:: MonadIO m | |
=> DynFlags | DynFlags |
-> SDoc | The name of the phase |
-> (a -> ()) | A function to force the result
(often either |
-> m a | The body of the phase to be timed |
-> m a |
Same as withTiming
, but doesn't print timings in the
console (when given -vN
, N >= 2
or -ddump-timings
).
See Note [withTiming] for more.
Arguments
:: (MonadIO m, HasDynFlags m) | |
=> SDoc | The name of the phase |
-> (a -> ()) | A function to force the result
(often either |
-> m a | The body of the phase to be timed |
-> m a |
Like withTiming but get DynFlags from the Monad.
Arguments
:: MonadIO m | |
=> DynFlags | DynFlags |
-> SDoc | The name of the phase |
-> (a -> ()) | A function to force the result
(often either |
-> m a | The body of the phase to be timed |
-> m a |
Time a compilation phase.
When timings are enabled (e.g. with the -v2
flag), the allocations
and CPU time used by the phase will be reported to stderr. Consider
a typical usage:
withTiming getDynFlags (text "simplify") force PrintTimings pass
.
When timings are enabled the following costs are included in the
produced accounting,
- The cost of executing
pass
to a resultr
in WHNF - The cost of evaluating
force r
to WHNF (e.g.()
)
The choice of the force
function depends upon the amount of forcing
desired; the goal here is to ensure that the cost of evaluating the result
is, to the greatest extent possible, included in the accounting provided by
withTiming
. Often the pass already sufficiently forces its result during
construction; in this case const ()
is a reasonable choice.
In other cases, it is necessary to evaluate the result to normal form, in
which case something like Control.DeepSeq.rnf
is appropriate.
To avoid adversely affecting compiler performance when timings are not requested, the result is only forced when timings are enabled.
See Note [withTiming] for more.
compilationProgressMsg :: DynFlags -> String -> IO () #
fatalErrorMsg'' :: FatalMessager -> String -> IO () #
fatalErrorMsg :: DynFlags -> MsgDoc -> IO () #
warningMsg :: DynFlags -> MsgDoc -> IO () #
dumpSDocWithStyle :: PprStyle -> DynFlags -> DumpFlag -> String -> SDoc -> IO () #
Write out a dump. If --dump-to-file is set then this goes to a file. otherwise emit to stdout.
When hdr
is empty, we print in a more compact format (no separators and
blank lines)
The DumpFlag
is used only to choose the filename to use if --dump-to-file
is used; it is not used to decide whether to dump the output
dumpSDocForUser :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO () #
A wrapper around dumpSDocWithStyle
which uses PprUser
style.
dumpIfSet_dyn_printer :: PrintUnqualified -> DynFlags -> DumpFlag -> SDoc -> IO () #
a wrapper around dumpSDoc
.
First check whether the dump flag is set
Do nothing if it is unset
Unlike dumpIfSet_dyn
,
has a printer argument but no header argument
dumpIfSet_dyn :: DynFlags -> DumpFlag -> String -> SDoc -> IO () #
a wrapper around dumpSDoc
.
First check whether the dump flag is set
Do nothing if it is unset
doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO () #
pprLocErrMsg :: ErrMsg -> SDoc #
pprErrMsgBagWithLoc :: Bag ErrMsg -> [SDoc] #
formatErrDoc :: DynFlags -> ErrDoc -> SDoc #
warningsToMessages :: DynFlags -> WarningMessages -> Messages #
errorsFound :: DynFlags -> Messages -> Bool #
isEmptyMessages :: Messages -> Bool #
mkPlainWarnMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg #
Variant that doesn't care about qualified/unqualified names
mkLongWarnMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg #
A long (multi-line) error message
mkPlainErrMsg :: DynFlags -> SrcSpan -> MsgDoc -> ErrMsg #
Variant that doesn't care about qualified/unqualified names
mkErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> ErrMsg #
A short (one-line) error message
mkLongErrMsg :: DynFlags -> SrcSpan -> PrintUnqualified -> MsgDoc -> MsgDoc -> ErrMsg #
A long (multi-line) error message
makeIntoWarning :: WarnReason -> ErrMsg -> ErrMsg #
pprMessageBag :: Bag MsgDoc -> SDoc #
unionMessages :: Messages -> Messages -> Messages #
getInvalids :: [Validity] -> [MsgDoc] #
type Messages = (WarningMessages, ErrorMessages) #
type WarningMessages = Bag WarnMsg #
type ErrorMessages = Bag ErrMsg #
Categorise error msgs by their importance. This is so each section can be rendered visually distinct. See Note [Error report] for where these come from.
mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc #
Make an unannotated error message with location info.
Arguments
:: Maybe String | optional annotation |
-> Severity | severity |
-> SrcSpan | location |
-> MsgDoc | message |
-> MsgDoc |
Make a possibly annotated error message with location info.
dumpSDoc :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO () #
A wrapper around dumpSDocWithStyle
which uses PprDump
style.
Constructors
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 |
module FamInst
module FamInstEnv
checkProcessArgsResult :: MonadIO m => DynFlags -> [Located String] -> m () #
Complain about non-dynamic flags in OPTIONS pragmas.
Throws a SourceError
if the input list is non-empty claiming that the
input flags are unknown.
Arguments
:: DynFlags | |
-> StringBuffer | Input Buffer |
-> FilePath | Source filename. Used for location info. |
-> [Located String] | Parsed options. |
Parse OPTIONS and LANGUAGE pragmas of the source file.
Throws a SourceError
if flag parsing fails (including unsupported flags.)
Parse OPTIONS and LANGUAGE pragmas of the source file.
Throws a SourceError
if flag parsing fails (including unsupported flags.)
mkPrelImports :: ModuleName -> SrcSpan -> Bool -> [LImportDecl GhcPs] -> [LImportDecl GhcPs] #
module Id
module InstEnv
module IfaceSyn
unitModuleSet :: Module -> ModuleSet #
unionModuleSet :: ModuleSet -> ModuleSet -> ModuleSet #
delModuleSet :: ModuleSet -> Module -> ModuleSet #
minusModuleSet :: ModuleSet -> ModuleSet -> ModuleSet #
intersectModuleSet :: ModuleSet -> ModuleSet -> ModuleSet #
elemModuleSet :: Module -> ModuleSet -> Bool #
moduleSetElts :: ModuleSet -> [Module] #
extendModuleSetList :: ModuleSet -> [Module] -> ModuleSet #
extendModuleSet :: ModuleSet -> Module -> ModuleSet #
mkModuleSet :: [Module] -> ModuleSet #
isEmptyModuleEnv :: ModuleEnv a -> Bool #
unitModuleEnv :: Module -> a -> ModuleEnv a #
moduleEnvToList :: ModuleEnv a -> [(Module, a)] #
moduleEnvElts :: ModuleEnv a -> [a] #
moduleEnvKeys :: ModuleEnv a -> [Module] #
emptyModuleEnv :: ModuleEnv a #
mkModuleEnv :: [(Module, a)] -> ModuleEnv a #
mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b #
lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a #
lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a #
plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a #
delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a #
delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a #
plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a #
extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a #
extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a #
extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a #
extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a #
elemModuleEnv :: Module -> ModuleEnv a -> Bool #
wiredInUnitIds :: [UnitId] #
isHoleModule :: Module -> Bool #
isInteractiveModule :: Module -> Bool #
mainUnitId :: UnitId #
This is the package Id for the current program. It is the default package Id if you don't specify a package name. We don't add this prefix to symbol names, since there can be only one main package per program.
thisGhcUnitId :: UnitId #
baseUnitId :: UnitId #
integerUnitId :: UnitId #
primUnitId :: UnitId #
parseModSubst :: ReadP [(ModuleName, Module)] #
parseUnitId :: ReadP UnitId #
splitUnitIdInsts :: UnitId -> (InstalledUnitId, Maybe IndefUnitId) #
See splitModuleInsts
.
splitModuleInsts :: Module -> (InstalledModule, Maybe IndefModule) #
Given a possibly on-the-fly instantiated module, split it into
a Module
that we definitely can find on-disk, as well as an
instantiation if we need to instantiate it on the fly. If the
instantiation is Nothing
no on-the-fly renaming is needed.
renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId #
Like 'renameHoleUnitId, but requires only PackageConfigMap
so it can be used by Packages.
renameHoleModule' :: PackageConfigMap -> ShHoleSubst -> Module -> Module #
Like renameHoleModule
, but requires only PackageConfigMap
so it can be used by Packages.
renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId #
renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module #
stringToUnitId :: String -> UnitId #
fsToUnitId :: FastString -> UnitId #
Create a new simple unit identifier from a FastString
. Internally,
this is primarily used to specify wired-in unit identifiers.
newSimpleUnitId :: ComponentId -> UnitId #
Create a new simple unit identifier (no holes) from a ComponentId
.
stableUnitIdCmp :: UnitId -> UnitId -> Ordering #
Compares package ids lexically, rather than by their Unique
s
newUnitId :: ComponentId -> [(ModuleName, Module)] -> UnitId #
Create a new, un-hashed unit identifier.
hashUnitId :: ComponentId -> [(ModuleName, Module)] -> FastString #
Generate a uniquely identifying FastString
for a unit
identifier. This is a one-way function. You can rely on one special
property: if a unit identifier is in most general form, its FastString
coincides with its ComponentId
. This hash is completely internal
to GHC and is not used for symbol names or file paths.
unitIdIsDefinite :: UnitId -> Bool #
A UnitId
is definite if it has no free holes.
unitIdFreeHoles :: UnitId -> UniqDSet ModuleName #
Retrieve the set of free holes of a UnitId
.
filterInstalledModuleEnv :: (InstalledModule -> a -> Bool) -> InstalledModuleEnv a -> InstalledModuleEnv a #
extendInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> a -> InstalledModuleEnv a #
lookupInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> Maybe a #
installedUnitIdEq :: InstalledUnitId -> UnitId -> Bool #
Test if a UnitId
corresponds to a given InstalledUnitId
,
modulo instantiation.
installedModuleEq :: InstalledModule -> Module -> Bool #
Test if a Module
corresponds to a given InstalledModule
,
modulo instantiation.
toInstalledUnitId :: UnitId -> InstalledUnitId #
Lossy conversion to the on-disk InstalledUnitId
for a component.
indefModuleToModule :: DynFlags -> IndefModule -> Module #
Injects an IndefModule
to Module
(see also
indefUnitIdToUnitId
.
indefUnitIdToUnitId :: DynFlags -> IndefUnitId -> UnitId #
Injects an IndefUnitId
(indefinite library which
was on-the-fly instantiated) to a UnitId
(either
an indefinite or definite library).
newIndefUnitId :: ComponentId -> [(ModuleName, Module)] -> IndefUnitId #
Create a new IndefUnitId
given an explicit module substitution.
unitIdFS :: UnitId -> FastString #
mkModule :: UnitId -> ModuleName -> Module #
stableModuleCmp :: Module -> Module -> Ordering #
This gives a stable ordering, as opposed to the Ord instance which
gives an ordering based on the Unique
s of the components, which may
not be stable from run to run of the compiler.
mkHoleModule :: ModuleName -> Module #
Create a module variable at some ModuleName
.
See Note [Representation of module/name variables]
moduleIsDefinite :: Module -> Bool #
A Module
is definite if it has no free holes.
moduleFreeHoles :: Module -> UniqDSet ModuleName #
Calculate the free holes of a Module
. If this set is non-empty,
this module was defined in an indefinite library that had required
signatures.
If a module has free holes, that means that substitutions can operate on it; if it has no free holes, substituting over a module has no effect.
moduleNameColons :: ModuleName -> String #
Returns the string version of the module name, with dots replaced by colons.
moduleNameSlashes :: ModuleName -> String #
Returns the string version of the module name, with dots replaced by slashes.
mkModuleNameFS :: FastString -> ModuleName #
mkModuleName :: String -> ModuleName #
moduleStableString :: Module -> String #
Get a string representation of a Module
that's unique and stable
across recompilations.
eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal"
moduleNameString :: ModuleName -> String #
moduleNameFS :: ModuleName -> FastString #
pprModuleName :: ModuleName -> SDoc #
stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering #
Compares module names lexically, rather than by their Unique
s
addBootSuffixLocn :: ModLocation -> ModLocation #
Add the -boot
suffix to all file paths associated with the module
addBootSuffix_maybe :: Bool -> FilePath -> FilePath #
Add the -boot
suffix if the Bool
argument is True
addBootSuffix :: FilePath -> FilePath #
Add the -boot
suffix to .hs, .hi and .o files
class ContainsModule t where #
Methods
extractModule :: t -> Module #
Instances
ContainsModule DsGblEnv | |
Defined in TcRnTypes Methods extractModule :: DsGblEnv -> Module # | |
ContainsModule TcGblEnv | |
Defined in TcRnTypes Methods extractModule :: TcGblEnv -> Module # | |
ContainsModule gbl => ContainsModule (Env gbl lcl) | |
Defined in TcRnTypes Methods extractModule :: Env gbl lcl -> Module # |
data IndefUnitId #
A unit identifier which identifies an indefinite
library (with holes) that has been *on-the-fly* instantiated
with a substitution indefUnitIdInsts
. In fact, an indefinite
unit identifier could have no holes, but we haven't gotten
around to compiling the actual library yet.
An indefinite unit identifier pretty-prints to something like
p[H=H,A=aimpl:A>]
(p
is the ComponentId
, and the
brackets enclose the module substitution).
Constructors
IndefUnitId | |
Fields
|
Instances
Eq IndefUnitId | |
Defined in Module | |
Ord IndefUnitId | |
Defined in Module Methods compare :: IndefUnitId -> IndefUnitId -> Ordering # (<) :: IndefUnitId -> IndefUnitId -> Bool # (<=) :: IndefUnitId -> IndefUnitId -> Bool # (>) :: IndefUnitId -> IndefUnitId -> Bool # (>=) :: IndefUnitId -> IndefUnitId -> Bool # max :: IndefUnitId -> IndefUnitId -> IndefUnitId # min :: IndefUnitId -> IndefUnitId -> IndefUnitId # | |
Binary IndefUnitId | |
Defined in Module Methods put_ :: BinHandle -> IndefUnitId -> IO () # put :: BinHandle -> IndefUnitId -> IO (Bin IndefUnitId) # get :: BinHandle -> IO IndefUnitId # | |
Outputable IndefUnitId | |
Defined in Module |
data IndefModule #
Constructors
IndefModule | |
Fields |
Instances
Eq IndefModule | |
Defined in Module | |
Ord IndefModule | |
Defined in Module Methods compare :: IndefModule -> IndefModule -> Ordering # (<) :: IndefModule -> IndefModule -> Bool # (<=) :: IndefModule -> IndefModule -> Bool # (>) :: IndefModule -> IndefModule -> Bool # (>=) :: IndefModule -> IndefModule -> Bool # max :: IndefModule -> IndefModule -> IndefModule # min :: IndefModule -> IndefModule -> IndefModule # | |
Outputable IndefModule | |
Defined in Module |
data InstalledModule #
A InstalledModule
is a Module
which contains a InstalledUnitId
.
Constructors
InstalledModule | |
Fields |
Instances
Eq InstalledModule | |
Defined in Module Methods (==) :: InstalledModule -> InstalledModule -> Bool # (/=) :: InstalledModule -> InstalledModule -> Bool # | |
Ord InstalledModule | |
Defined in Module Methods compare :: InstalledModule -> InstalledModule -> Ordering # (<) :: InstalledModule -> InstalledModule -> Bool # (<=) :: InstalledModule -> InstalledModule -> Bool # (>) :: InstalledModule -> InstalledModule -> Bool # (>=) :: InstalledModule -> InstalledModule -> Bool # max :: InstalledModule -> InstalledModule -> InstalledModule # min :: InstalledModule -> InstalledModule -> InstalledModule # | |
Outputable InstalledModule | |
Defined in Module |
A DefUnitId
is an InstalledUnitId
with the invariant that
it only refers to a definite library; i.e., one we have generated
code for.
Constructors
DefUnitId | |
Fields |
Instances
Eq DefUnitId | |
Ord DefUnitId | |
Binary DefUnitId | |
Outputable DefUnitId | |
data InstalledModuleEnv elt #
A map keyed off of InstalledModule
type ShHoleSubst = ModuleNameEnv Module #
Substitution on module variables, mapping module names to module identifiers.
type ModuleNameEnv elt = UniqFM elt #
A map keyed off of ModuleName
s (actually, their Unique
s)
type DModuleNameEnv elt = UniqDFM elt #
A map keyed off of ModuleName
s (actually, their Unique
s)
Has deterministic folds and can be deterministically converted to a list
unitIdString :: UnitId -> String #
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.)
Constructors
Module !UnitId !ModuleName |
Instances
data ModuleName #
A ModuleName is essentially a simple string, e.g. Data.List
.
Instances
pattern IndefiniteUnitId :: !IndefUnitId -> UnitId #
pattern DefiniteUnitId :: !DefUnitId -> UnitId #
newtype InstalledUnitId #
An installed unit identifier identifies a library which has
been installed to the package database. These strings are
provided to us via the -this-unit-id
flag. The library
in question may be definite or indefinite; if it is indefinite,
none of the holes have been filled (we never install partially
instantiated libraries.) Put another way, an installed unit id
is either fully instantiated, or not instantiated at all.
Installed unit identifiers look something like p+af23SAj2dZ219
,
or maybe just p
if they don't use Backpack.
Constructors
InstalledUnitId | |
Fields
|
Instances
newtype ComponentId #
A ComponentId
consists of the package name, package version, component
ID, the transitive dependencies of the component, and other information to
uniquely identify the source code and build configuration of a component.
This used to be known as an InstalledPackageId
, but a package can contain
multiple components and a ComponentId
uniquely identifies a component
within a package. When a package only has one component, the ComponentId
coincides with the InstalledPackageId
Constructors
ComponentId FastString |
Instances
pprPrefixName :: NamedThing a => a -> SDoc #
pprInfixName :: (Outputable a, NamedThing a) => a -> SDoc #
getOccFS :: NamedThing a => a -> FastString #
getOccString :: NamedThing a => a -> String #
getSrcSpan :: NamedThing a => a -> SrcSpan #
getSrcLoc :: NamedThing a => a -> SrcLoc #
nameStableString :: Name -> String #
Get a string representation of a Name
that's unique and stable
across recompilations. Used for deterministic generation of binds for
derived instances.
eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String"
pprNameDefnLoc :: Name -> SDoc #
pprDefinedAt :: Name -> SDoc #
pprNameUnqualified :: Name -> SDoc #
Print the string of Name unqualifiedly directly.
stableNameCmp :: Name -> Name -> Ordering #
Compare Names lexicographically This only works for Names that originate in the source code or have been tidied.
localiseName :: Name -> Name #
Make the Name
into an internal name, regardless of what it was to begin with
tidyNameOcc :: Name -> OccName -> Name #
setNameLoc :: Name -> SrcSpan -> Name #
setNameUnique :: Name -> Unique -> Name #
mkFCallName :: Unique -> String -> Name #
Make a name for a foreign call
mkSysTvName :: Unique -> FastString -> Name #
mkSystemVarName :: Unique -> FastString -> Name #
mkSystemName :: Unique -> OccName -> Name #
Create a name brought into being by the compiler
mkWiredInName :: Module -> OccName -> Unique -> TyThing -> BuiltInSyntax -> Name #
Create a name which is actually defined by the compiler itself
mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name #
Create a name which definitely originates in the given module
mkClonedInternalName :: Unique -> Name -> Name #
isSystemName :: Name -> Bool #
isDataConName :: Name -> Bool #
isTyConName :: Name -> Bool #
isTyVarName :: Name -> Bool #
nameIsFromExternalPackage :: UnitId -> Name -> Bool #
Returns True if the Name comes from some other package: neither this package nor the interactive package.
nameIsHomePackageImport :: Module -> Name -> Bool #
nameIsHomePackage :: Module -> Name -> Bool #
nameIsLocalOrFrom :: Module -> Name -> Bool #
Returns True if the name is
(a) Internal
(b) External but from the specified module
(c) External but from the interactive
package
The key idea is that False means: the entity is defined in some other module you can find the details (type, fixity, instances) in some interface file those details will be stored in the EPT or HPT
True means: the entity is defined in this module or earlier in the GHCi session you can find details (type, fixity, instances) in the TcGblEnv or TcLclEnv
The isInteractiveModule part is because successive interactions of a GHCi session
each give rise to a fresh module (Ghci1, Ghci2, etc), but they all come
from the magic interactive
package; and all the details are kept in the
TcLclEnv, TcGblEnv, NOT in the HPT or EPT.
See Note [The interactive package] in HscTypes
nameModule_maybe :: Name -> Maybe Module #
nameModule :: HasDebugCallStack => Name -> Module #
isHoleName :: Name -> Bool #
isInternalName :: Name -> Bool #
isExternalName :: Name -> Bool #
isBuiltInSyntax :: Name -> Bool #
isWiredInName :: Name -> Bool #
nameSrcSpan :: Name -> SrcSpan #
nameSrcLoc :: Name -> SrcLoc #
nameNameSpace :: Name -> NameSpace #
nameOccName :: Name -> OccName #
nameUnique :: Name -> Unique #
data BuiltInSyntax #
BuiltInSyntax is for things like (:)
, []
and tuples,
which have special syntactic forms. They aren't in scope
as such.
Constructors
BuiltInSyntax | |
UserSyntax |
class NamedThing a where #
A class allowing convenient access to the Name
of various datatypes
Minimal complete definition
Instances
NamedThing HoleFitCandidate | |
Defined in TcHoleFitTypes | |
NamedThing ClsInst | |
NamedThing FamInst | |
Defined in FamInstEnv | |
NamedThing IfaceDecl | |
NamedThing IfaceClassOp | |
Defined in IfaceSyn | |
NamedThing IfaceConDecl | |
Defined in IfaceSyn | |
NamedThing Class | |
NamedThing ConLike | |
NamedThing DataCon | |
NamedThing PatSyn | |
NamedThing TyThing | |
NamedThing Var | |
NamedThing TyCon | |
NamedThing Name | |
NamedThing (HsTyVarBndr GhcRn) | |
Defined in GHC.Hs.Types | |
NamedThing (CoAxiom br) | |
NamedThing e => NamedThing (Located e) | |
NamedThing tv => NamedThing (VarBndr tv flag) | |
tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) #
avoidClashesOccEnv :: TidyOccEnv -> [OccName] -> TidyOccEnv #
initTidyOccEnv :: [OccName] -> TidyOccEnv #
mkMethodOcc :: OccName -> OccName #
Derive a name for the representation type constructor of a
data
/newtype
instance.
mkSuperDictAuxOcc :: Int -> OccName -> OccName #
mkDataConWorkerOcc :: OccName -> OccName #
mkRecFldSelOcc :: String -> OccName #
mkTyConRepOcc :: OccName -> OccName #
mkMaxTagOcc :: OccName -> OccName #
mkTag2ConOcc :: OccName -> OccName #
mkCon2TagOcc :: OccName -> OccName #
mkEqPredCoOcc :: OccName -> OccName #
mkInstTyCoOcc :: OccName -> OccName #
mkNewTyCoOcc :: OccName -> OccName #
mkClassDataConOcc :: OccName -> OccName #
mkRepEqOcc :: OccName -> OccName #
mkForeignExportOcc :: OccName -> OccName #
mkClassOpAuxOcc :: OccName -> OccName #
mkDefaultMethodOcc :: OccName -> OccName #
mkBuilderOcc :: OccName -> OccName #
mkMatcherOcc :: OccName -> OccName #
mkWorkerOcc :: OccName -> OccName #
mkDataConWrapperOcc :: OccName -> OccName #
isTypeableBindOcc :: OccName -> Bool #
Is an OccName
one of a Typeable TyCon
or Module
binding?
This is needed as these bindings are renamed differently.
See Note [Grand plan for Typeable] in TcTypeable.
isDefaultMethodOcc :: OccName -> Bool #
isDerivedOccName :: OccName -> Bool #
Test for definitions internally generated by GHC. This predicte is used to suppress printing of internal definitions in some debug prints
startsWithUnderscore :: OccName -> Bool #
Haskell 98 encourages compilers to suppress warnings about unsed
names in a pattern if they start with _
: this implements that test
parenSymOcc :: OccName -> SDoc -> SDoc #
Wrap parens around an operator
Test if the OccName
is that for any operator (whether
it is a data constructor or variable or whatever)
isDataSymOcc :: OccName -> Bool #
Test if the OccName
is a data constructor that starts with
a symbol (e.g. :
, or []
)
Value OccNames
s are those that are either in
the variable or data constructor namespaces
setOccNameSpace :: NameSpace -> OccName -> OccName #
occNameString :: OccName -> String #
intersectsOccSet :: OccSet -> OccSet -> Bool #
intersectOccSet :: OccSet -> OccSet -> OccSet #
isEmptyOccSet :: OccSet -> Bool #
elemOccSet :: OccName -> OccSet -> Bool #
minusOccSet :: OccSet -> OccSet -> OccSet #
unionManyOccSets :: [OccSet] -> OccSet #
unionOccSets :: OccSet -> OccSet -> OccSet #
extendOccSetList :: OccSet -> [OccName] -> OccSet #
extendOccSet :: OccSet -> OccName -> OccSet #
unitOccSet :: OccName -> OccSet #
emptyOccSet :: OccSet #
filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt #
delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a #
delFromOccEnv :: OccEnv a -> OccName -> OccEnv a #
mkOccEnv_C :: (a -> a -> a) -> [(OccName, a)] -> OccEnv a #
extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b #
extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a #
plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a #
plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a #
occEnvElts :: OccEnv a -> [a] #
foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #
elemOccEnv :: OccName -> OccEnv a -> Bool #
lookupOccEnv :: OccEnv a -> OccName -> Maybe a #
extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #
extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a #
unitOccEnv :: OccName -> a -> OccEnv a #
emptyOccEnv :: OccEnv a #
nameSpacesRelated :: NameSpace -> NameSpace -> Bool #
demoteOccName :: OccName -> Maybe OccName #
mkClsOccFS :: FastString -> OccName #
mkTcOccFS :: FastString -> OccName #
mkTyVarOccFS :: FastString -> OccName #
mkTyVarOcc :: String -> OccName #
mkDataOccFS :: FastString -> OccName #
mkVarOccFS :: FastString -> OccName #
mkOccNameFS :: NameSpace -> FastString -> OccName #
pprOccName :: OccName -> SDoc #
pprNameSpaceBrief :: NameSpace -> SDoc #
pprNonVarNameSpace :: NameSpace -> SDoc #
pprNameSpace :: NameSpace -> SDoc #
isValNameSpace :: NameSpace -> Bool #
isVarNameSpace :: NameSpace -> Bool #
isTvNameSpace :: NameSpace -> Bool #
isTcClsNameSpace :: NameSpace -> Bool #
isDataConNameSpace :: NameSpace -> Bool #
Instances
Eq NameSpace | |
Ord NameSpace | |
Binary NameSpace | |
class HasOccName name where #
Other names in the compiler add additional information to an OccName. This class provides a consistent way to access the underlying OccName.
Instances
HasOccName HoleFitCandidate | |
Defined in TcHoleFitTypes Methods occName :: HoleFitCandidate -> OccName # | |
HasOccName TcBinder | |
HasOccName IfaceDecl | |
HasOccName IfaceClassOp | |
Defined in IfaceSyn Methods occName :: IfaceClassOp -> OccName # | |
HasOccName IfaceConDecl | |
Defined in IfaceSyn Methods occName :: IfaceConDecl -> OccName # | |
HasOccName RdrName | |
HasOccName Var | |
HasOccName OccName | |
HasOccName Name | |
HasOccName name => HasOccName (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods occName :: IEWrappedName name -> OccName # |
Instances
Data a => Data (OccEnv a) | |
Defined in OccName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccEnv a -> c (OccEnv a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (OccEnv a) # toConstr :: OccEnv a -> Constr # dataTypeOf :: OccEnv a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (OccEnv a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OccEnv a)) # gmapT :: (forall b. Data b => b -> b) -> OccEnv a -> OccEnv a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccEnv a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccEnv a -> r # gmapQ :: (forall d. Data d => d -> u) -> OccEnv a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OccEnv a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccEnv a -> m (OccEnv a) # | |
Outputable a => Outputable (OccEnv a) | |
type TidyOccEnv = UniqFM Int #
mkFsEnv :: [(FastString, a)] -> FastStringEnv a #
lookupFsEnv :: FastStringEnv a -> FastString -> Maybe a #
extendFsEnv :: FastStringEnv a -> FastString -> a -> FastStringEnv a #
emptyFsEnv :: FastStringEnv a #
type FastStringEnv a = UniqFM a #
A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in UniqDFM for explanation why it's not deterministic and why it matters. Use DFastStringEnv if the set eventually gets converted into a list or folded over in a way where the order changes the generated code.
Occurrence Name
In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"
Instances
Eq OccName | |
Data OccName | |
Defined in OccName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccName -> c OccName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OccName # toConstr :: OccName -> Constr # dataTypeOf :: OccName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OccName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OccName) # gmapT :: (forall b. Data b => b -> b) -> OccName -> OccName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r # gmapQ :: (forall d. Data d => d -> u) -> OccName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OccName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName # | |
Ord OccName | |
Show OccName Source # | |
Hashable OccName Source # | |
Defined in Development.IDE.GHC.Orphans | |
NFData OccName | |
HasOccName OccName | |
Binary OccName | |
Uniquable OccName | |
Outputable OccName | |
OutputableBndr OccName | |
Defined in OccName Methods pprBndr :: BindingSite -> OccName -> SDoc # pprPrefixOcc :: OccName -> SDoc # pprInfixOcc :: OccName -> SDoc # bndrIsJoin_maybe :: OccName -> Maybe Int # |
A unique, unambiguous name for something, containing information about where that thing originated.
Instances
Eq Name | |
Data Name | |
Defined in Name Methods 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 Methods composeSrcSpan :: Located (SrcSpanLess Name) -> Name # decomposeSrcSpan :: Name -> Located (SrcSpanLess Name) # | |
Outputable Name | |
OutputableBndr Name | |
Defined in Name Methods pprBndr :: BindingSite -> Name -> SDoc # pprPrefixOcc :: Name -> SDoc # pprInfixOcc :: Name -> SDoc # bndrIsJoin_maybe :: Name -> Maybe Int # | |
ModifyState Name | |
Defined in Compat.HieAst Methods 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 Methods toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type] | |
ToHie (IEContext (Located (FieldLbl Name))) | |
type SrcSpanLess Name | |
Defined in Name |
module NameCache
module NameEnv
module NameSet
module PatSyn
pprTypeForUser :: Type -> SDoc #
pprTyThingInContextLoc :: TyThing -> SDoc #
Like pprTyThingInContext
, but adds the defining location.
pprTyThingInContext :: ShowSub -> TyThing -> SDoc #
Pretty-prints a TyThing
in context: that is, if the entity
is a data constructor, record selector, or class method, then
the entity's parent declaration is pretty-printed with irrelevant
parts omitted.
pprTyThingHdr :: TyThing -> SDoc #
Pretty-prints the TyThing
header. For functions and data constructors
the function is equivalent to pprTyThing
but for type constructors
and classes it prints only the header part of the declaration.
pprTyThingLoc :: TyThing -> SDoc #
Pretty-prints a TyThing
with its defining location.
module PrelInfo
pretendNameIsInScope :: Name -> Bool #
interactiveClassKeys :: [Unique] #
interactiveClassNames :: [Name] #
derivableClassKeys :: [Unique] #
standardClassKeys :: [Unique] #
fractionalClassKeys :: [Unique] #
numericClassKeys :: [Unique] #
makeStaticKey :: Unique #
heqSCSelIdKey :: Unique #
eqSCSelIdKey :: Unique #
toDynIdKey :: Unique #
mkTrFunKey :: Unique #
typeRepIdKey :: Unique #
mkTrAppKey :: Unique #
mkTrConKey :: Unique #
mkTrTypeKey :: Unique #
mkTyConKey :: Unique #
proxyHashKey :: Unique #
liftMIdKey :: Unique #
guardMIdKey :: Unique #
loopAIdKey :: Unique #
choiceAIdKey :: Unique #
firstAIdKey :: Unique #
composeAIdKey :: Unique #
geClassOpKey :: Unique #
eqClassOpKey :: Unique #
unboundKey :: Unique #
magicDictKey :: Unique #
undefinedKey :: Unique #
noinlineIdKey :: Unique #
dollarIdKey :: Unique #
inlineIdKey :: Unique #
oneShotKey :: Unique #
thenIOIdKey :: Unique #
runMainKey :: Unique #
rootMainKey :: Unique #
assertIdKey :: Unique #
voidArgIdKey :: Unique #
nullAddrIdKey :: Unique #
failIOIdKey :: Unique #
printIdKey :: Unique #
returnIOIdKey :: Unique #
bindIOIdKey :: Unique #
filterIdKey :: Unique #
concatIdKey :: Unique #
modIntIdKey :: Unique #
divIntIdKey :: Unique #
voidPrimIdKey :: Unique #
patErrorIdKey :: Unique #
eqStringIdKey :: Unique #
foldrIdKey :: Unique #
errorIdKey :: Unique #
buildIdKey :: Unique #
appendIdKey :: Unique #
augmentIdKey :: Unique #
wildCardKey :: Unique #
vecElemDataConKeys :: [Unique] #
vecCountDataConKeys :: [Unique] #
inrDataConKey :: Unique #
inlDataConKey :: Unique #
heqDataConKey :: Unique #
ioDataConKey :: Unique #
nilDataConKey :: Unique #
eqDataConKey :: Unique #
intDataConKey :: Unique #
anyTyConKey :: Unique #
specTyConKey :: Unique #
ntTyConKey :: Unique #
uWordTyConKey :: Unique #
uIntTyConKey :: Unique #
uCharTyConKey :: Unique #
uAddrTyConKey :: Unique #
uRecTyConKey :: Unique #
rep1TyConKey :: Unique #
repTyConKey :: Unique #
noSelTyConKey :: Unique #
s1TyConKey :: Unique #
c1TyConKey :: Unique #
d1TyConKey :: Unique #
rec0TyConKey :: Unique #
compTyConKey :: Unique #
prodTyConKey :: Unique #
sumTyConKey :: Unique #
m1TyConKey :: Unique #
k1TyConKey :: Unique #
rec1TyConKey :: Unique #
par1TyConKey :: Unique #
u1TyConKey :: Unique #
v1TyConKey :: Unique #
tYPETyConKey :: Unique #
ptrTyConKey :: Unique #
typeConKey :: Unique #
boxityConKey :: Unique #
kindConKey :: Unique #
anyBoxConKey :: Unique #
liftedConKey :: Unique #
word8TyConKey :: Unique #
wordTyConKey :: Unique #
ioTyConKey :: Unique #
heqTyConKey :: Unique #
eqTyConKey :: Unique #
ratioTyConKey :: Unique #
maybeTyConKey :: Unique #
listTyConKey :: Unique #
int64TyConKey :: Unique #
int32TyConKey :: Unique #
int16TyConKey :: Unique #
int8TyConKey :: Unique #
intTyConKey :: Unique #
funTyConKey :: Unique #
floatTyConKey :: Unique #
charTyConKey :: Unique #
boolTyConKey :: Unique #
ipClassKey :: Unique #
gen1ClassKey :: Unique #
genClassKey :: Unique #
ixClassKey :: Unique #
showClassKey :: Unique #
realClassKey :: Unique #
readClassKey :: Unique #
ordClassKey :: Unique #
numClassKey :: Unique #
dataClassKey :: Unique #
monadClassKey :: Unique #
eqClassKey :: Unique #
enumClassKey :: Unique #
mk_known_key_name :: NameSpace -> Module -> FastString -> Unique -> Name #
makeStaticName :: Name #
pluginTyConName :: Name #
ipClassName :: Name #
randomClassName :: Name #
guardMName :: Name #
choiceAName :: Name #
firstAName :: Name #
composeAName :: Name #
funPtrTyConName :: Name #
ptrTyConName :: Name #
word64TyConName :: Name #
word32TyConName :: Name #
word16TyConName :: Name #
int64TyConName :: Name #
int32TyConName :: Name #
int16TyConName :: Name #
int8TyConName :: Name #
failIOName :: Name #
returnIOName :: Name #
bindIOName :: Name #
thenIOName :: Name #
ioDataConName :: Name #
ioTyConName :: Name #
ghciStepIoMName :: Name #
ghciIoClassName :: Name #
genericClassNames :: [Name] #
gen1ClassName :: Name #
genClassName :: Name #
readClassName :: Name #
showClassName :: Name #
toListName :: Name #
fromListNName :: Name #
fromListName :: Name #
isListClassName :: Name #
filterName :: Name #
concatName :: Name #
enumFromToName :: Name #
enumFromName :: Name #
enumClassName :: Name #
assertErrorName :: Name #
dataClassName :: Name #
starKindRepName :: Name #
mkTrFunName :: Name #
mkTrAppName :: Name #
mkTrConName :: Name #
mkTrTypeName :: Name #
typeRepIdName :: Name #
trNameTyConName :: Name #
ixClassName :: Name #
realToFracName :: Name #
toRationalName :: Name #
toIntegerName :: Name #
realClassName :: Name #
ratioTyConName :: Name #
mkNaturalName :: Name #
plusNaturalName :: Name #
bitIntegerName :: Name #
xorIntegerName :: Name #
orIntegerName :: Name #
andIntegerName :: Name #
lcmIntegerName :: Name #
gcdIntegerName :: Name #
modIntegerName :: Name #
divIntegerName :: Name #
remIntegerName :: Name #
quotIntegerName :: Name #
absIntegerName :: Name #
plusIntegerName :: Name #
mkIntegerName :: Name #
negateName :: Name #
fromIntegerName :: Name #
numClassName :: Name #
fromStringName :: Name #
opaqueTyConName :: Name #
breakpointName :: Name #
assertName :: Name #
appendName :: Name #
augmentName :: Name #
otherwiseIdName :: Name #
dollarName :: Name #
groupWithName :: Name #
apAClassOpKey :: Unique #
joinMIdKey :: Unique #
mconcatName :: Name #
mappendName :: Name #
memptyName :: Name #
monoidClassName :: Name #
sappendName :: Name #
returnMName :: Name #
monadClassName :: Name #
ordClassName :: Name #
eqClassName :: Name #
inlineIdName :: Name #
eqStringName :: Name #
modIntName :: Name #
divIntName :: Name #
uWordTyConName :: Name #
uIntTyConName :: Name #
uFloatTyConName :: Name #
uCharTyConName :: Name #
uAddrTyConName :: Name #
uRecTyConName :: Name #
rep1TyConName :: Name #
repTyConName :: Name #
noSelTyConName :: Name #
s1TyConName :: Name #
c1TyConName :: Name #
d1TyConName :: Name #
rec0TyConName :: Name #
sTyConName :: Name #
cTyConName :: Name #
dTyConName :: Name #
rTyConName :: Name #
compTyConName :: Name #
prodTyConName :: Name #
sumTyConName :: Name #
m1TyConName :: Name #
k1TyConName :: Name #
rec1TyConName :: Name #
par1TyConName :: Name #
u1TyConName :: Name #
v1TyConName :: Name #
leftDataConName :: Name #
eitherTyConName :: Name #
specTyConName :: Name #
runMainIOName :: Name #
wildCardName :: Name #
dataQual_RDR :: Module -> FastString -> RdrName #
clsQual_RDR :: Module -> FastString -> RdrName #
tcQual_RDR :: Module -> FastString -> RdrName #
varQual_RDR :: Module -> FastString -> RdrName #
mappend_RDR :: RdrName #
mempty_RDR :: RdrName #
traverse_RDR :: RdrName #
foldMap_RDR :: RdrName #
liftA2_RDR :: RdrName #
replace_RDR :: RdrName #
uIntHash_RDR :: RdrName #
conName_RDR :: RdrName #
selName_RDR :: RdrName #
unComp1_RDR :: RdrName #
unRec1_RDR :: RdrName #
unPar1_RDR :: RdrName #
symbol_RDR :: RdrName #
expectP_RDR :: RdrName #
choose_RDR :: RdrName #
parens_RDR :: RdrName #
readPrec_RDR :: RdrName #
readList_RDR :: RdrName #
inRange_RDR :: RdrName #
maxBound_RDR :: RdrName #
minBound_RDR :: RdrName #
getTag_RDR :: RdrName #
compose_RDR :: RdrName #
toList_RDR :: RdrName #
fromList_RDR :: RdrName #
stringTy_RDR :: RdrName #
returnIO_RDR :: RdrName #
bindIO_RDR :: RdrName #
eqString_RDR :: RdrName #
enumFrom_RDR :: RdrName #
toEnum_RDR :: RdrName #
fromEnum_RDR :: RdrName #
returnM_RDR :: RdrName #
append_RDR :: RdrName #
ordClass_RDR :: RdrName #
numClass_RDR :: RdrName #
eqClass_RDR :: RdrName #
compare_RDR :: RdrName #
mkMainModule_ :: ModuleName -> Module #
mkMainModule :: FastString -> Module #
mkThisGhcModule_ :: ModuleName -> Module #
mkThisGhcModule :: FastString -> Module #
mkBaseModule_ :: ModuleName -> Module #
mkBaseModule :: FastString -> Module #
mkIntegerModule :: FastString -> Module #
mkPrimModule :: FastString -> Module #
mAIN_NAME :: ModuleName #
mkInteractiveModule :: Int -> Module #
gHC_RECORDS :: Module #
gHC_STATICPTR :: Module #
gHC_SRCLOC :: Module #
dEBUG_TRACE :: Module #
dATA_COERCE :: Module #
gHC_TYPENATS :: Module #
gHC_TYPELITS :: Module #
gHC_GENERICS :: Module #
gHC_DESUGAR :: Module #
mONAD_FAIL :: Module #
gHC_STABLE :: Module #
dATA_FOLDABLE :: Module #
dATA_STRING :: Module #
dATA_EITHER :: Module #
dATA_TUPLE :: Module #
gHC_NATURAL :: Module #
gHC_CLASSES :: Module #
gHC_CSTRING :: Module #
genericTyConNames :: [Name] #
basicKnownKeyNames :: [Name] #
isUnboundName :: Name -> Bool #
mkUnboundName :: OccName -> Name #
allNameStrings :: [String] #
Class of things that we can obtain a Unique
from
Instances
starInfo :: Bool -> RdrName -> SDoc #
Display info about the treatment of *
under NoStarIsType.
With StarIsType, three properties of *
hold:
(a) it is not an infix operator (b) it is always in scope (c) it is a synonym for Data.Kind.Type
However, the user might not know that he's working on a module with NoStarIsType and write code that still assumes (a), (b), and (c), which actually do not hold in that module.
Violation of (a) shows up in the parser. For instance, in the following
examples, we have *
not applied to enough arguments:
data A :: * data F :: * -> *
Violation of (b) or (c) show up in the renamer and the typechecker respectively. For instance:
type K = Either * Bool
This will parse differently depending on whether StarIsType is enabled, but it will parse nonetheless. With NoStarIsType it is parsed as a type operator, thus we have ((*) Either Bool). Now there are two cases to consider:
- There is no definition of (*) in scope. In this case the renamer will fail to look it up. This is a violation of assumption (b).
- There is a definition of the (*) type operator in scope (for example coming from GHC.TypeNats). In this case the user will get a kind mismatch error. This is a violation of assumption (c).
The user might unknowingly be working on a module with NoStarIsType
or use *
as Type
out of habit. So it is important to give a
hint whenever an assumption about *
is violated. Unfortunately, it is
somewhat difficult to deal with (c), so we limit ourselves to (a) and (b).
starInfo
generates an appropriate hint to the user depending on the
extensions enabled in the module and the name that triggered the error.
That is, if we have NoStarIsType and the error is related to *
or its
Unicode variant, the resulting SDoc will contain a helpful suggestion.
Otherwise it is empty.
pprNameProvenance :: GlobalRdrElt -> SDoc #
Print out one place where the name was define/imported (With -dppr-debug, print them all)
isExplicitItem :: ImpItemSpec -> Bool #
importSpecLoc :: ImportSpec -> SrcSpan #
qualSpecOK :: ModuleName -> ImportSpec -> Bool #
Is in scope qualified with the given module?
unQualSpecOK :: ImportSpec -> Bool #
Is in scope unqualified?
bestImport :: [ImportSpec] -> ImportSpec #
shadowNames :: GlobalRdrEnv -> [Name] -> GlobalRdrEnv #
transformGREs :: (GlobalRdrElt -> GlobalRdrElt) -> [OccName] -> GlobalRdrEnv -> GlobalRdrEnv #
Apply a transformation function to the GREs for these OccNames
mkGlobalRdrEnv :: [GlobalRdrElt] -> GlobalRdrEnv #
pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt, GlobalRdrElt)] #
Pick GREs that are in scope *both* qualified *and* unqualified Return each GRE that is, as a pair (qual_gre, unqual_gre) These two GREs are the original GRE with imports filtered to express how it is in scope qualified an unqualified respectively
Used only for the 'module M' item in export list; see RnNames.exports_from_avail
pickGREs :: RdrName -> [GlobalRdrElt] -> [GlobalRdrElt] #
Takes a list of GREs which have the right OccName x
Pick those GREs that are in scope
* Qualified, as x
if want_qual is Qual M _
* Unqualified, as x
if want_unqual is Unqual _
Return each such GRE, with its ImportSpecs filtered, to reflect how it is in scope qualified or unqualified respectively. See Note [GRE filtering]
unQualOK :: GlobalRdrElt -> Bool #
Test if an unqualified version of this thing would be in scope
isOverloadedRecFldGRE :: GlobalRdrElt -> Bool #
Is this a record field defined with DuplicateRecordFields? (See Note [Parents for record fields])
isRecFldGRE :: GlobalRdrElt -> Bool #
isLocalGRE :: GlobalRdrElt -> Bool #
getGRE_NameQualifier_maybes :: GlobalRdrEnv -> Name -> [Maybe [ModuleName]] #
lookupGRE_Name_OccName :: GlobalRdrEnv -> Name -> OccName -> Maybe GlobalRdrElt #
Look for precisely this Name
in the environment, but with an OccName
that might differ from that of the Name
. See lookupGRE_FieldLabel
and
Note [Parents for record fields].
lookupGRE_FieldLabel :: GlobalRdrEnv -> FieldLabel -> Maybe GlobalRdrElt #
Look for a particular record field selector in the environment, where the selector name and field label may be different: the GlobalRdrEnv is keyed on the label. See Note [Parents for record fields] for why this happens.
lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt #
lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] #
greOccName :: GlobalRdrElt -> OccName #
lookupGlobalRdrEnv :: GlobalRdrEnv -> OccName -> [GlobalRdrElt] #
pprGlobalRdrEnv :: Bool -> GlobalRdrEnv -> SDoc #
globalRdrEnvElts :: GlobalRdrEnv -> [GlobalRdrElt] #
availFromGRE :: GlobalRdrElt -> AvailInfo #
gresToAvailInfo :: [GlobalRdrElt] -> [AvailInfo] #
Takes a list of distinct GREs and folds them
into AvailInfos. This is more efficient than mapping each individual
GRE to an AvailInfo and the folding using plusAvail
but needs the
uniqueness assumption.
greParent_maybe :: GlobalRdrElt -> Maybe Name #
greSrcSpan :: GlobalRdrElt -> SrcSpan #
greRdrNames :: GlobalRdrElt -> [RdrName] #
gresFromAvail :: (Name -> Maybe ImportSpec) -> AvailInfo -> [GlobalRdrElt] #
localGREsFromAvail :: AvailInfo -> [GlobalRdrElt] #
gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt] #
make a GlobalRdrEnv
where all the elements point to the same
Provenance (useful for "hiding" imports, or imports with no details).
delLocalRdrEnvList :: LocalRdrEnv -> [OccName] -> LocalRdrEnv #
inLocalRdrEnvScope :: Name -> LocalRdrEnv -> Bool #
localRdrEnvElts :: LocalRdrEnv -> [Name] #
elemLocalRdrEnv :: RdrName -> LocalRdrEnv -> Bool #
lookupLocalRdrOcc :: LocalRdrEnv -> OccName -> Maybe Name #
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name #
extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv #
extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv #
isExact_maybe :: RdrName -> Maybe Name #
isQual_maybe :: RdrName -> Maybe (ModuleName, OccName) #
isSrcRdrName :: RdrName -> Bool #
isRdrTyVar :: RdrName -> Bool #
isRdrDataCon :: RdrName -> Bool #
nameRdrName :: Name -> RdrName #
getRdrName :: NamedThing thing => thing -> RdrName #
mkQual :: NameSpace -> (FastString, FastString) -> RdrName #
Make a qualified RdrName
in the given namespace and where the ModuleName
and
the OccName
are taken from the first and second elements of the tuple respectively
mkVarUnqual :: FastString -> RdrName #
mkUnqual :: NameSpace -> FastString -> RdrName #
mkRdrQual :: ModuleName -> OccName -> RdrName #
mkRdrUnqual :: OccName -> RdrName #
demoteRdrName :: RdrName -> Maybe RdrName #
rdrNameSpace :: RdrName -> NameSpace #
rdrNameOcc :: RdrName -> OccName #
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
,
Constructors
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 |
Orig Module OccName | Original name An original name; the module is the defining module.
This is used when GHC generates code that will be fed
into the renamer (e.g. from deriving clauses), but where
we want to say "Use Prelude.map dammit". One of these
can be created with |
Exact Name | Exact name We know exactly the
Such a |
Instances
Eq RdrName | |
Data RdrName | |
Defined in RdrName Methods 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 Methods pprBndr :: BindingSite -> RdrName -> SDoc # pprPrefixOcc :: RdrName -> SDoc # pprInfixOcc :: RdrName -> SDoc # bndrIsJoin_maybe :: RdrName -> Maybe Int # | |
Annotate RdrName | |
ASTElement NameAnn RdrName Source # | |
Annotate (FunDep (Located RdrName)) | |
Annotate (IEWrappedName RdrName) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater |
data LocalRdrEnv #
Local Reader Environment
This environment is used to store local bindings
(let
, where
, lambda, case
).
It is keyed by OccName, because we never use it for qualified names
We keep the current mapping, *and* the set of all Names in scope
Reason: see Note [Splicing Exact names] in RnEnv
Instances
Outputable LocalRdrEnv | |
Defined in RdrName |
type GlobalRdrEnv = OccEnv [GlobalRdrElt] #
Global Reader Environment
Keyed by OccName
; when looking up a qualified name
we look up the OccName
part, and then check the Provenance
to see if the appropriate qualification is valid. This
saves routinely doubling the size of the env by adding both
qualified and unqualified names to the domain.
The list in the codomain is required because there may be name clashes These only get reported on lookup, not on construction
INVARIANT 1: All the members of the list have distinct
gre_name
fields; that is, no duplicate Names
INVARIANT 2: Imported provenance => Name is an ExternalName However LocalDefs can have an InternalName. This happens only when type-checking a [d| ... |] Template Haskell quotation; see this note in RnNames Note [Top-level Names in Template Haskell decl quotes]
INVARIANT 3: If the GlobalRdrEnv maps [occ -> gre], then greOccName gre = occ
NB: greOccName gre is usually the same as nameOccName (gre_name gre), but not always in the case of record seectors; see greOccName
data GlobalRdrElt #
Global Reader Element
An element of the GlobalRdrEnv
Instances
Eq GlobalRdrElt | |
Defined in RdrName | |
Data GlobalRdrElt | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalRdrElt -> c GlobalRdrElt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalRdrElt # toConstr :: GlobalRdrElt -> Constr # dataTypeOf :: GlobalRdrElt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GlobalRdrElt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalRdrElt) # gmapT :: (forall b. Data b => b -> b) -> GlobalRdrElt -> GlobalRdrElt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalRdrElt -> r # gmapQ :: (forall d. Data d => d -> u) -> GlobalRdrElt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalRdrElt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalRdrElt -> m GlobalRdrElt # | |
Outputable GlobalRdrElt | |
Defined in RdrName |
The children of a Name are the things that are abbreviated by the ".." notation in export lists. See Note [Parents]
Constructors
NoParent | |
ParentIs | |
FldParent | See Note [Parents for record fields] |
Fields
|
Instances
Eq Parent | |
Data Parent | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parent -> c Parent # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parent # toConstr :: Parent -> Constr # dataTypeOf :: Parent -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Parent) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parent) # gmapT :: (forall b. Data b => b -> b) -> Parent -> Parent # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parent -> r # gmapQ :: (forall d. Data d => d -> u) -> Parent -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Parent -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parent -> m Parent # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parent -> m Parent # | |
Outputable Parent | |
data ImportSpec #
Import Specification
The ImportSpec
of something says how it came to be imported
It's quite elaborate so that we can give accurate unused-name warnings.
Constructors
ImpSpec | |
Fields
|
Instances
Eq ImportSpec | |
Defined in RdrName | |
Data ImportSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportSpec -> c ImportSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportSpec # toConstr :: ImportSpec -> Constr # dataTypeOf :: ImportSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportSpec) # gmapT :: (forall b. Data b => b -> b) -> ImportSpec -> ImportSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportSpec -> m ImportSpec # | |
Ord ImportSpec | |
Defined in RdrName Methods compare :: ImportSpec -> ImportSpec -> Ordering # (<) :: ImportSpec -> ImportSpec -> Bool # (<=) :: ImportSpec -> ImportSpec -> Bool # (>) :: ImportSpec -> ImportSpec -> Bool # (>=) :: ImportSpec -> ImportSpec -> Bool # max :: ImportSpec -> ImportSpec -> ImportSpec # min :: ImportSpec -> ImportSpec -> ImportSpec # | |
Outputable ImportSpec | |
Defined in RdrName |
data ImpDeclSpec #
Import Declaration Specification
Describes a particular import declaration and is
shared among all the Provenance
s for that decl
Constructors
ImpDeclSpec | |
Fields
|
Instances
Eq ImpDeclSpec | |
Defined in RdrName | |
Data ImpDeclSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpDeclSpec -> c ImpDeclSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpDeclSpec # toConstr :: ImpDeclSpec -> Constr # dataTypeOf :: ImpDeclSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpDeclSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpDeclSpec) # gmapT :: (forall b. Data b => b -> b) -> ImpDeclSpec -> ImpDeclSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpDeclSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImpDeclSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpDeclSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpDeclSpec -> m ImpDeclSpec # | |
Ord ImpDeclSpec | |
Defined in RdrName Methods compare :: ImpDeclSpec -> ImpDeclSpec -> Ordering # (<) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (<=) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (>) :: ImpDeclSpec -> ImpDeclSpec -> Bool # (>=) :: ImpDeclSpec -> ImpDeclSpec -> Bool # max :: ImpDeclSpec -> ImpDeclSpec -> ImpDeclSpec # min :: ImpDeclSpec -> ImpDeclSpec -> ImpDeclSpec # |
data ImpItemSpec #
Import Item Specification
Describes import info a particular Name
Constructors
ImpAll | The import had no import list, or had a hiding list |
ImpSome | The import had an import list.
The import C( T(..) ) Here the constructors of |
Fields
|
Instances
Eq ImpItemSpec | |
Defined in RdrName | |
Data ImpItemSpec | |
Defined in RdrName Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImpItemSpec -> c ImpItemSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImpItemSpec # toConstr :: ImpItemSpec -> Constr # dataTypeOf :: ImpItemSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImpItemSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImpItemSpec) # gmapT :: (forall b. Data b => b -> b) -> ImpItemSpec -> ImpItemSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImpItemSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> ImpItemSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImpItemSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImpItemSpec -> m ImpItemSpec # | |
Ord ImpItemSpec | |
Defined in RdrName Methods compare :: ImpItemSpec -> ImpItemSpec -> Ordering # (<) :: ImpItemSpec -> ImpItemSpec -> Bool # (<=) :: ImpItemSpec -> ImpItemSpec -> Bool # (>) :: ImpItemSpec -> ImpItemSpec -> Bool # (>=) :: ImpItemSpec -> ImpItemSpec -> Bool # max :: ImpItemSpec -> ImpItemSpec -> ImpItemSpec # min :: ImpItemSpec -> ImpItemSpec -> ImpItemSpec # |
module RnSplice
module RnNames
module TcEnv
unwrapIP :: Type -> CoercionR #
Create a Coercion
that unwraps an implicit-parameter or
overloaded-label dictionary to expose the underlying value. We
expect the Type
to have the form `IP sym ty` or `IsLabel sym ty`,
and return a Coercion
`co :: IP sym ty ~ ty` or
`co :: IsLabel sym ty ~ Proxy# sym -> ty`. See also
Note [Type-checking overloaded labels] in TcExpr.
evVarsOfTerm :: EvTerm -> VarSet #
findNeededEvVars :: EvBindMap -> VarSet -> VarSet #
evTermCoercion :: EvTerm -> TcCoercion #
isEmptyTcEvBinds :: TcEvBinds -> Bool #
mkEvScSelectors :: Class -> [TcType] -> [(TcPredType, EvExpr)] #
mkEvCast :: EvExpr -> TcCoercion -> EvTerm #
evTypeable :: Type -> EvTypeable -> EvTerm #
evCast :: EvExpr -> TcCoercion -> EvTerm #
d |> co
evCoercion :: TcCoercion -> EvTerm #
mkGivenEvBind :: EvVar -> EvTerm -> EvBind #
mkWantedEvBind :: EvVar -> EvTerm -> EvBind #
foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a #
evBindMapBinds :: EvBindMap -> Bag EvBind #
isEmptyEvBindMap :: EvBindMap -> Bool #
extendEvBinds :: EvBindMap -> EvBind -> EvBindMap #
isCoEvBindsVar :: EvBindsVar -> Bool #
collectHsWrapBinders :: HsWrapper -> ([Var], HsWrapper) #
isErasableHsWrapper :: HsWrapper -> Bool #
Is the wrapper erasable, i.e., will not affect runtime semantics?
isIdHsWrapper :: HsWrapper -> Bool #
mkWpTyLams :: [TyVar] -> HsWrapper #
mkWpEvVarApps :: [EvVar] -> HsWrapper #
mkWpEvApps :: [EvTerm] -> HsWrapper #
mkWpTyApps :: [Type] -> HsWrapper #
mkWpCastN :: TcCoercionN -> HsWrapper #
mkWpCastR :: TcCoercionR -> HsWrapper #
maybeTcSubCo :: EqRel -> TcCoercion -> TcCoercion #
If the EqRel is ReprEq, makes a SubCo; otherwise, does nothing. Note that the input coercion should always be nominal.
tcCoToMCo :: TcCoercion -> TcMCoercion #
isTcReflexiveCo :: TcCoercion -> Bool #
This version does a slow check, calculating the related types and seeing if they are equal.
isTcGReflMCo :: TcMCoercion -> Bool #
isTcReflCo :: TcCoercion -> Bool #
coVarsOfTcCo :: TcCoercion -> TcTyCoVarSet #
tcCoercionRole :: TcCoercion -> Role #
tcCoercionKind :: TcCoercion -> Pair TcType #
mkTcCoVarCo :: CoVar -> TcCoercion #
mkTcKindCo :: TcCoercion -> TcCoercionN #
mkTcPhantomCo :: TcCoercionN -> TcType -> TcType -> TcCoercionP #
mkTcCoherenceRightCo :: Role -> TcType -> TcCoercionN -> TcCoercion -> TcCoercion #
mkTcCoherenceLeftCo :: Role -> TcType -> TcCoercionN -> TcCoercion -> TcCoercion #
mkTcGReflLeftCo :: Role -> TcType -> TcCoercionN -> TcCoercion #
mkTcGReflRightCo :: Role -> TcType -> TcCoercionN -> TcCoercion #
mkTcAxiomRuleCo :: CoAxiomRule -> [TcCoercion] -> TcCoercionR #
tcDowngradeRole :: Role -> Role -> TcCoercion -> TcCoercion #
mkTcSubCo :: TcCoercionN -> TcCoercionR #
mkTcLRCo :: LeftOrRight -> TcCoercion -> TcCoercion #
mkTcNthCo :: Role -> Int -> TcCoercion -> TcCoercion #
mkTcForAllCos :: [(TyVar, TcCoercionN)] -> TcCoercion -> TcCoercion #
mkTcForAllCo :: TyVar -> TcCoercionN -> TcCoercion -> TcCoercion #
mkTcUnbranchedAxInstCo :: CoAxiom Unbranched -> [TcType] -> [TcCoercion] -> TcCoercionR #
mkTcAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [TcType] -> [TcCoercion] -> TcCoercion #
mkTcFunCo :: Role -> TcCoercion -> TcCoercion -> TcCoercion #
mkTcAppCo :: TcCoercion -> TcCoercionN -> TcCoercion #
mkTcTyConAppCo :: Role -> TyCon -> [TcCoercion] -> TcCoercion #
mkTcRepReflCo :: TcType -> TcCoercionR #
mkTcNomReflCo :: TcType -> TcCoercionN #
mkTcTransCo :: TcCoercion -> TcCoercion -> TcCoercion #
mkTcSymCo :: TcCoercion -> TcCoercion #
mkTcReflCo :: Role -> TcType -> TcCoercion #
type TcCoercion = Coercion #
type TcCoercionN = CoercionN #
type TcCoercionR = CoercionR #
type TcCoercionP = CoercionP #
type TcMCoercion = MCoercion #
Constructors
WpHole | |
WpCompose HsWrapper HsWrapper | |
WpFun HsWrapper HsWrapper TcType SDoc | |
WpCast TcCoercionR | |
WpEvLam EvVar | |
WpEvApp EvTerm | |
WpTyLam TyVar | |
WpTyApp KindOrType | |
WpLet TcEvBinds |
Instances
Data HsWrapper | |
Defined in TcEvidence Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWrapper -> c HsWrapper # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsWrapper # toConstr :: HsWrapper -> Constr # dataTypeOf :: HsWrapper -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsWrapper) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsWrapper) # gmapT :: (forall b. Data b => b -> b) -> HsWrapper -> HsWrapper # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r # gmapQ :: (forall d. Data d => d -> u) -> HsWrapper -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWrapper -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper # | |
Outputable HsWrapper | |
Constructors
TcEvBinds EvBindsVar | |
EvBinds (Bag EvBind) |
Instances
Data TcEvBinds | |
Defined in TcEvidence Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcEvBinds -> c TcEvBinds # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcEvBinds # toConstr :: TcEvBinds -> Constr # dataTypeOf :: TcEvBinds -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TcEvBinds) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcEvBinds) # gmapT :: (forall b. Data b => b -> b) -> TcEvBinds -> TcEvBinds # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r # gmapQ :: (forall d. Data d => d -> u) -> TcEvBinds -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TcEvBinds -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds # | |
Outputable TcEvBinds | |
data EvBindsVar #
Constructors
EvBindsVar | |
CoEvBindsVar | |
Instances
Uniquable EvBindsVar | |
Defined in TcEvidence Methods getUnique :: EvBindsVar -> Unique # | |
Outputable EvBindsVar | |
Defined in TcEvidence |
Constructors
EvBindMap | |
Fields |
Constructors
EvExpr EvExpr | |
EvTypeable Type EvTypeable | |
EvFun | |
Instances
Data EvTerm | |
Defined in TcEvidence Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTerm -> c EvTerm # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTerm # toConstr :: EvTerm -> Constr # dataTypeOf :: EvTerm -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvTerm) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm) # gmapT :: (forall b. Data b => b -> b) -> EvTerm -> EvTerm # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r # gmapQ :: (forall d. Data d => d -> u) -> EvTerm -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTerm -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm # | |
Outputable EvTerm | |
data EvTypeable #
Instructions on how to make a Typeable
dictionary.
See Note [Typeable evidence terms]
Constructors
EvTypeableTyCon TyCon [EvTerm] | Dictionary for |
EvTypeableTyApp EvTerm EvTerm | Dictionary for |
EvTypeableTrFun EvTerm EvTerm | Dictionary for |
EvTypeableTyLit EvTerm | Dictionary for a type literal,
e.g. |
Instances
Data EvTypeable | |
Defined in TcEvidence Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTypeable -> c EvTypeable # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTypeable # toConstr :: EvTypeable -> Constr # dataTypeOf :: EvTypeable -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvTypeable) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTypeable) # gmapT :: (forall b. Data b => b -> b) -> EvTypeable -> EvTypeable # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r # gmapQ :: (forall d. Data d => d -> u) -> EvTypeable -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTypeable -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable # | |
Outputable EvTypeable | |
Defined in TcEvidence |
data EvCallStack #
Evidence for CallStack
implicit parameters.
Constructors
EvCsEmpty | |
EvCsPushCall Name RealSrcSpan EvExpr |
|
Instances
Data EvCallStack | |
Defined in TcEvidence Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvCallStack -> c EvCallStack # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvCallStack # toConstr :: EvCallStack -> Constr # dataTypeOf :: EvCallStack -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EvCallStack) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvCallStack) # gmapT :: (forall b. Data b => b -> b) -> EvCallStack -> EvCallStack # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r # gmapQ :: (forall d. Data d => d -> u) -> EvCallStack -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EvCallStack -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack # | |
Outputable EvCallStack | |
Defined in TcEvidence |
data CoercionHole #
A coercion to be filled in by the type-checker. See Note [Coercion holes]
Instances
Data CoercionHole | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoercionHole -> c CoercionHole # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoercionHole # toConstr :: CoercionHole -> Constr # dataTypeOf :: CoercionHole -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoercionHole) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoercionHole) # gmapT :: (forall b. Data b => b -> b) -> CoercionHole -> CoercionHole # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r # gmapQ :: (forall d. Data d => d -> u) -> CoercionHole -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CoercionHole -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole # | |
Outputable CoercionHole | |
Defined in TyCoRep |
Constructors
Nominal | |
Representational | |
Phantom |
Instances
Eq Role | |
Data Role | |
Defined in CoAxiom Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role # dataTypeOf :: Role -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Role) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) # gmapT :: (forall b. Data b => b -> b) -> Role -> Role # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r # gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role # | |
Ord Role | |
Binary Role | |
Outputable Role | |
Annotate (Maybe Role) | |
pickLR :: LeftOrRight -> (a, a) -> a #
data LeftOrRight #
Instances
Eq LeftOrRight | |
Defined in BasicTypes | |
Data LeftOrRight | |
Defined in BasicTypes Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight # toConstr :: LeftOrRight -> Constr # dataTypeOf :: LeftOrRight -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) # gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # | |
Outputable LeftOrRight | |
Defined in BasicTypes |
isNextArgVisible :: TcType -> Bool #
Should this type be applied to a visible argument?
isNextTyConArgVisible :: TyCon -> [Type] -> Bool #
If the tycon is applied to the types, is the next argument visible?
tcTyConVisibilities :: TyCon -> [Bool] #
For every arg a tycon can take, the returned list says True if the argument is taken visibly, and False otherwise. Ends with an infinite tail of Trues to allow for oversaturation.
isFunPtrTy :: Type -> Bool #
isFFIPrimResultTy :: DynFlags -> Type -> Validity #
isFFIPrimArgumentTy :: DynFlags -> Type -> Validity #
isFFILabelTy :: Type -> Validity #
isFFIDynTy :: Type -> Type -> Validity #
isFFIExportResultTy :: Type -> Validity #
isFFIImportResultTy :: DynFlags -> Type -> Validity #
isFFIExternalTy :: Type -> Validity #
deNoteType :: Type -> Type #
isAlmostFunctionFree :: TcType -> Bool #
Is this type *almost function-free*? See Note [Almost function-free] in TcRnTypes
isTyVarHead :: TcTyVar -> TcType -> Bool #
Does the given tyvar appear at the head of a chain of applications (a t1 ... tn)
isCallStackPred :: Class -> [Type] -> Maybe FastString #
Is a PredType
a CallStack
implicit parameter?
If so, return the name of the parameter.
isCallStackTy :: Type -> Bool #
Is a type a CallStack
?
isStringTy :: Type -> Bool #
Is a type String
?
isFloatingTy :: Type -> Bool #
Does a type represent a floating-point number?
isIntegerTy :: Type -> Bool #
isDoubleTy :: Type -> Bool #
isOverloadedTy :: Type -> Bool #
isInsolubleOccursCheck :: EqRel -> TcTyVar -> TcType -> Bool #
Is the equality a ~r ...a.... definitely insoluble or not? a ~r Maybe a -- Definitely insoluble a ~N ...(F a)... -- Not definitely insoluble -- Perhaps (F a) reduces to Int a ~R ...(N a)... -- Not definitely insoluble -- Perhaps newtype N a = MkN Int See Note [Occurs check error] in TcCanonical for the motivation for this function.
isImprovementPred :: PredType -> Bool #
immSuperClasses :: Class -> [Type] -> [PredType] #
transSuperClasses :: PredType -> [PredType] #
mkMinimalBySCs :: (a -> PredType) -> [a] -> [a] #
pickCapturedPreds :: TyVarSet -> TcThetaType -> TcThetaType #
pickQuantifiablePreds :: TyVarSet -> TcThetaType -> TcThetaType #
When inferring types, should we quantify over a given predicate? Generally true of classes; generally false of equality constraints. Equality constraints that mention quantified type variables and implicit variables complicate the story. See Notes [Inheriting implicit parameters] and [Quantifying over equality constraints]
hasTyVarHead :: Type -> Bool #
checkValidClsArgs :: Bool -> Class -> [KindOrType] -> Bool #
isTyVarClassPred :: PredType -> Bool #
pickyEqType :: TcType -> TcType -> Bool #
Like pickyEqTypeVis
, but returns a Bool for convenience
tcEqTypeVis :: TcType -> TcType -> Bool #
Like tcEqType
, but returns True if the visible part of the types
are equal, even if they are really unequal (in the invisible bits)
tcEqTypeNoKindCheck :: TcType -> TcType -> Bool #
Just like tcEqType
, but will return True for types of different kinds
as long as their non-coercion structure is identical.
tcSplitDFunHead :: Type -> (Class, [Type]) #
tcIsTyVarTy :: Type -> Bool #
tcGetTyVar :: String -> Type -> TyVar #
tcGetTyVar_maybe :: Type -> Maybe TyVar #
tcGetCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN) #
If the type is a tyvar, possibly under a cast, returns it, along with the coercion. Thus, the co is :: kind tv ~N kind type
tcRepGetNumAppTys :: Type -> Arity #
Returns the number of arguments in the given type, without looking through synonyms. This is used only for error reporting. We don't look through synonyms because of #11313.
tcSplitAppTys :: Type -> (Type, [Type]) #
tcSplitAppTy :: Type -> (Type, Type) #
tcFunResultTyN :: HasDebugCallStack => Arity -> Type -> Type #
Strips off n *visible* arguments and returns the resulting type
tcFunResultTy :: Type -> Type #
tcFunArgTy :: Type -> Type #
tcSplitFunTysN :: Arity -> TcRhoType -> Either Arity ([TcSigmaType], TcSigmaType) #
Split off exactly the specified number argument types
Returns
(Left m) if there are m
missing arrows in the type
(Right (tys,res)) if the type looks like t1 -> ... -> tn -> res
tcSplitFunTys :: Type -> ([Type], Type) #
tcSplitTyConApp :: Type -> (TyCon, [Type]) #
tcTyConAppArgs :: Type -> [Type] #
tcTyConAppTyCon_maybe :: Type -> Maybe TyCon #
Like tcRepSplitTyConApp_maybe
, but only returns the TyCon
.
tcTyConAppTyCon :: Type -> TyCon #
tcDeepSplitSigmaTy_maybe :: TcSigmaType -> Maybe ([TcType], [TyVar], ThetaType, TcSigmaType) #
tcSplitNestedSigmaTys :: Type -> ([TyVar], ThetaType, Type) #
Split a sigma type into its parts, going underneath as many ForAllTy
s
as possible. For example, given this type synonym:
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
if you called tcSplitSigmaTy
on this type:
forall s t a b. Each s t a b => Traversal s t a b
then it would return ([s,t,a,b], [Each s t a b], Traversal s t a b)
. But
if you instead called tcSplitNestedSigmaTys
on the type, it would return
([s,t,a,b,f], [Each s t a b, Applicative f], (a -> f b) -> s -> f t)
.
tcSplitPhiTy :: Type -> (ThetaType, Type) #
tcIsForAllTy :: Type -> Bool #
Is this a ForAllTy with a named binder?
tcSplitForAllVarBndrs :: Type -> ([TyVarBinder], Type) #
Like tcSplitForAllTys
, but splits off only named binders.
tcSplitForAllTysSameVis :: ArgFlag -> Type -> ([TyVar], Type) #
Like tcSplitForAllTys
, but only splits a ForAllTy
if
is sameVis
argf supplied_argfTrue
, where argf
is the visibility
of the ForAllTy
's binder and supplied_argf
is the visibility provided
as an argument to this function.
tcSplitForAllTys :: Type -> ([TyVar], Type) #
Like tcSplitPiTys
, but splits off only named binders,
returning just the tycovars.
tcSplitForAllTy_maybe :: Type -> Maybe (TyVarBinder, Type) #
tcSplitPiTy_maybe :: Type -> Maybe (TyBinder, Type) #
Splits a type into a TyBinder and a body, if possible. Panics otherwise
tcSplitPiTys :: Type -> ([TyBinder], Type) #
Splits a forall type into a list of TyBinder
s and the inner type.
Always succeeds, even if it returns an empty list.
mkTcCastTy :: Type -> Coercion -> Type #
mkTcAppTys :: Type -> [Type] -> Type #
getDFunTyKey :: Type -> OccName #
mkSpecSigmaTy :: [TyVar] -> [PredType] -> Type -> Type #
Make a sigma ty where all type variables are "specified". That is, they can be used with visible type application
mkInfSigmaTy :: [TyCoVar] -> [PredType] -> Type -> Type #
Make a sigma ty where all type variables are Inferred
. That is,
they cannot be used with visible type application.
mkTyVarNamePairs :: [TyVar] -> [(Name, TyVar)] #
isRuntimeUnkSkol :: TyVar -> Bool #
isIndirect :: MetaDetails -> Bool #
isFlexi :: MetaDetails -> Bool #
isTyVarTyVar :: Var -> Bool #
setMetaTyVarTcLevel :: TcTyVar -> TcLevel -> TcTyVar #
metaTyVarRef :: TyVar -> IORef MetaDetails #
metaTyVarTcLevel :: TcTyVar -> TcLevel #
metaTyVarInfo :: TcTyVar -> MetaInfo #
isMetaTyVarTy :: TcType -> Bool #
isAmbiguousTyVar :: TcTyVar -> Bool #
isMetaTyVar :: TcTyVar -> Bool #
isOverlappableTyVar :: TcTyVar -> Bool #
isSkolemTyVar :: TcTyVar -> Bool #
isFlattenTyVar :: TcTyVar -> Bool #
True of both given and wanted flatten-skolems (fmv and fsk)
isFskTyVar :: TcTyVar -> Bool #
isFmvTyVar :: TcTyVar -> Bool #
isTyConableTyVar :: TcTyVar -> Bool #
isImmutableTyVar :: TyVar -> Bool #
isFloatedTouchableMetaTyVar :: TcLevel -> TcTyVar -> Bool #
isTouchableMetaTyVar :: TcLevel -> TcTyVar -> Bool #
tcIsTcTyVar :: TcTyVar -> Bool #
isTyFamFree :: Type -> Bool #
Check that a type does not contain any type family applications.
tcTyConAppTyFamInstsAndVis :: TyCon -> [Type] -> [(Bool, TyCon, [Type])] #
In an application of a TyCon
to some arguments, find the outermost
occurrences of type family applications within the arguments. This function
will not consider the TyCon
itself when checking for type family
applications.
See tcTyFamInstsAndVis
for more details on how this works (as this
function is called inside of tcTyFamInstsAndVis
).
tcTyFamInstsAndVis :: Type -> [(Bool, TyCon, [Type])] #
Like tcTyFamInsts
, except that the output records whether the
type family and its arguments occur as an invisible argument in
some type application. This information is useful because it helps GHC know
when to turn on -fprint-explicit-kinds
during error reporting so that
users can actually see the type family being mentioned.
As an example, consider:
class C a data T (a :: k) type family F a :: k instance C (T @(F Int) (F Bool))
There are two occurrences of the type family F
in that C
instance, so
will return:tcTyFamInstsAndVis
(C (T @(F Int) (F Bool)))
[ (True
, F, [Int]) , (False
, F, [Bool]) ]
F Int
is paired with True
since it appears as an invisible argument
to C
, whereas F Bool
is paired with False
since it appears an a
visible argument to C
.
See also Note [Kind arguments in error messages]
in TcErrors.
tcTyFamInsts :: Type -> [(TyCon, [Type])] #
Finds outermost type-family applications occurring in a type, after expanding synonyms. In the list (F, tys) that is returned we guarantee that tys matches F's arity. For example, given type family F a :: * -> * (arity 1) calling tcTyFamInsts on (Maybe (F Int Bool) will return (F, [Int]), not (F, [Int,Bool])
This is important for its use in deciding termination of type instances (see #11581). E.g. type instance G [Int] = ...(F Int type)... we don't need to take type into account when asking if the calls on the RHS are smaller than the LHS
promoteSkolemX :: TcLevel -> TCvSubst -> TcTyVar -> (TCvSubst, TcTyVar) #
Change the TcLevel in a skolem, extending a substitution
promoteSkolem :: TcLevel -> TcTyVar -> TcTyVar #
tcTypeLevel :: TcType -> TcLevel #
tcTyVarLevel :: TcTyVar -> TcLevel #
sameDepthAs :: TcLevel -> TcLevel -> Bool #
strictlyDeeperThan :: TcLevel -> TcLevel -> Bool #
pushTcLevel :: TcLevel -> TcLevel #
isTopTcLevel :: TcLevel -> Bool #
topTcLevel :: TcLevel #
maxTcLevel :: TcLevel -> TcLevel -> TcLevel #
mkSynFunTys :: [SyntaxOpType] -> ExpType -> SyntaxOpType #
Like mkFunTys
but for SyntaxOpType
synKnownType :: TcType -> SyntaxOpType #
Like SynType
but accepts a regular TcType
mkCheckExpType :: TcType -> ExpType #
Make an ExpType
suitable for checking.
type TcTyVarBinder = TyVarBinder #
type TcPredType = PredType #
type TcThetaType = ThetaType #
type TcSigmaType = TcType #
type TcTyVarSet = TyVarSet #
type TcTyCoVarSet = TyCoVarSet #
type TcDTyVarSet = DTyVarSet #
type TcDTyCoVarSet = DTyCoVarSet #
An expected type to check against during type-checking. See Note [ExpType] in TcMType, where you'll also find manipulators.
Constructors
Check TcType | |
Infer !InferResult |
type ExpSigmaType = ExpType #
type ExpRhoType = ExpType #
data SyntaxOpType #
What to expect for an argument to a rebindable-syntax operator.
Quite like Type
, but allows for holes to be filled in by tcSyntaxOp.
The callback called from tcSyntaxOp gets a list of types; the meaning
of these types is determined by a left-to-right depth-first traversal
of the SyntaxOpType
tree. So if you pass in
SynAny `SynFun` (SynList `SynFun` SynType Int) `SynFun` SynAny
you'll get three types back: one for the first SynAny
, the element
type of the list, and one for the last SynAny
. You don't get anything
for the SynType
, because you've said positively that it should be an
Int, and so it shall be.
This is defined here to avoid defining it in TcExpr.hs-boot.
Constructors
SynAny | Any type |
SynRho | A rho type, deeply skolemised or instantiated as appropriate |
SynList | A list type. You get back the element type of the list |
SynFun SyntaxOpType SyntaxOpType infixr 0 | A function. |
SynType ExpType | A known type. |
Constructors
TauTv | |
TyVarTv | |
FlatMetaTv | |
FlatSkolTv |
type TypeSize = IntWithInf #
orphNamesOfCoCon :: forall (br :: BranchFlag). CoAxiom br -> NameSet #
orphNamesOfCo :: Coercion -> NameSet #
orphNamesOfTypes :: [Type] -> NameSet #
orphNamesOfType :: Type -> NameSet #
isEqPrimPred :: PredType -> Bool #
isClassPred :: PredType -> Bool #
isEqPredClass :: Class -> Bool #
mkClassPred :: Class -> [Type] -> PredType #
classifiesTypeWithValues :: Kind -> Bool #
Does this classify a type allowed to have values? Responds True to things like *, #, TYPE Lifted, TYPE v, Constraint.
True of any sub-kind of OpenTypeKind
isKindLevPoly :: Kind -> Bool #
Tests whether the given kind (which should look like TYPE x
)
is something other than a constructor tree (that is, constructors at every node).
E.g. True of TYPE k, TYPE (F Int)
False of TYPE 'LiftedRep
tcTypeKind :: HasDebugCallStack => Type -> Kind #
nonDetCmpTypes :: [Type] -> [Type] -> Ordering #
nonDetCmpType :: Type -> Type -> Ordering #
eqTypes :: [Type] -> [Type] -> Bool #
Type equality on lists of types, looking through type synonyms but not newtypes.
eqTypeX :: RnEnv2 -> Type -> Type -> Bool #
Compare types with respect to a (presumably) non-empty RnEnv2
.
isPrimitiveType :: Type -> Bool #
Returns true of types that are opaque to Haskell.
isUnboxedTupleType :: Type -> Bool #
isUnliftedType :: HasDebugCallStack => Type -> Bool #
See Type for what an unlifted type is.
Panics on levity polymorphic types; See mightBeUnliftedType
for
a more approximate predicate that behaves better in the presence of
levity polymorphism.
closeOverKindsDSet :: DTyVarSet -> DTyVarSet #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministic set.
closeOverKinds :: TyVarSet -> TyVarSet #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a non-deterministic set.
mkSpecForAllTys :: [TyVar] -> Type -> Type #
Like mkForAllTys
, but assumes all variables are dependent and
Specified
, a common case
mkInvForAllTys :: [TyVar] -> Type -> Type #
Like mkTyCoInvForAllTys
, but tvs should be a list of tyvar
mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type #
Like mkForAllTys
, but assumes all variables are dependent and
Inferred
, a common case
mkInvForAllTy :: TyVar -> Type -> Type #
Like mkTyCoInvForAllTy
, but tv should be a tyvar
tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) #
Split a type constructor application into its type constructor and
applied types. Note that this may fail in the case of a FunTy
with an
argument of unknown kind FunTy
(e.g. FunTy (a :: k) Int
. since the kind
of a
isn't of the form TYPE rep
). Consequently, you may need to zonk your
type before using this function.
If you only need the TyCon
, consider using tcTyConAppTyCon_maybe
.
mkTyConApp :: TyCon -> [Type] -> Type #
tcRepSplitAppTy_maybe :: Type -> Maybe (Type, Type) #
Does the AppTy split as in tcSplitAppTy_maybe
, but assumes that
any coreView stuff is already done. Refuses to look through (c => t)
getTyVar :: String -> Type -> TyVar #
Attempts to obtain the type variable underlying a Type
, and panics with the
given message if this is not a type variable type. See also getTyVar_maybe
isRuntimeRepVar :: TyVar -> Bool #
Is a tyvar of type RuntimeRep
?
isUnliftedTypeKind :: Kind -> Bool #
Returns True if the kind classifies unlifted types and False otherwise. Note that this returns False for levity-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.
substTyVarBndr :: HasCallStack => TCvSubst -> TyVar -> (TCvSubst, TyVar) #
substCoUnchecked :: TCvSubst -> Coercion -> Coercion #
Substitute within a Coercion
disabling sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substThetaUnchecked :: TCvSubst -> ThetaType -> ThetaType #
Substitute within a ThetaType
disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substThetaUnchecked to
substTheta and remove this function. Please don't use in new code.
substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType #
Substitute within a ThetaType
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTysUnchecked :: TCvSubst -> [Type] -> [Type] #
Substitute within several Type
s disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTysUnchecked to
substTys and remove this function. Please don't use in new code.
substTys :: HasCallStack => TCvSubst -> [Type] -> [Type] #
Substitute within several Type
s
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTyUnchecked :: TCvSubst -> Type -> Type #
Substitute within a Type
disabling the sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substTy :: HasCallStack => TCvSubst -> Type -> Type #
Substitute within a Type
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTyAddInScope :: TCvSubst -> Type -> Type #
Substitute within a Type
after adding the free variables of the type
to the in-scope set. This is useful for the case when the free variables
aren't already in the in-scope set or easily available.
See also Note [The substitution invariant].
substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion #
Coercion substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type #
Type substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type #
Type substitution, see zipTvSubst
zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv #
zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv #
mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst #
Generates the in-scope set for the TCvSubst
from the types in the
incoming environment. No CoVars, please!
zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst #
Generates the in-scope set for the TCvSubst
from the types in the incoming
environment. No CoVars, please!
unionTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst #
extendTCvInScopeSet :: TCvSubst -> VarSet -> TCvSubst #
extendTCvInScopeList :: TCvSubst -> [Var] -> TCvSubst #
extendTCvInScope :: TCvSubst -> Var -> TCvSubst #
setTvSubstEnv :: TCvSubst -> TvSubstEnv -> TCvSubst #
notElemTCvSubst :: Var -> TCvSubst -> Bool #
getTCvInScope :: TCvSubst -> InScopeSet #
getTvSubstEnv :: TCvSubst -> TvSubstEnv #
mkTvSubst :: InScopeSet -> TvSubstEnv -> TCvSubst #
Make a TCvSubst with specified tyvar subst and empty covar subst
mkTCvSubst :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> TCvSubst #
mkEmptyTCvSubst :: InScopeSet -> TCvSubst #
Type & coercion substitution
The following invariants must hold of a TCvSubst
:
- The in-scope set is needed only to guide the generation of fresh uniques
- In particular, the kind of the type variables in the in-scope set is not relevant
- The substitution is only applied ONCE! This is because in general such application will not reach a fixed point.
Constructors
TCvSubst InScopeSet TvSubstEnv CvSubstEnv |
pprTypeApp :: TyCon -> [Type] -> SDoc #
pprTCvBndr :: TyCoVarBinder -> SDoc #
pprTCvBndrs :: [TyCoVarBinder] -> SDoc #
pprSigmaType :: Type -> SDoc #
pprThetaArrowTy :: ThetaType -> SDoc #
pprParendTheta :: ThetaType -> SDoc #
pprClassPred :: Class -> [Type] -> SDoc #
pprParendKind :: Kind -> SDoc #
pprParendType :: Type -> SDoc #
scopedSort :: [TyCoVar] -> [TyCoVar] #
Do a topological sort on a list of tyvars, so that binders occur before occurrences E.g. given [ a::k, k::*, b::k ] it'll return a well-scoped list [ k::*, a::k, b::k ]
This is a deterministic sorting operation (that is, doesn't depend on Uniques).
It is also meant to be stable: that is, variables should not be reordered unnecessarily. This is specified in Note [ScopedSort] See also Note [Ordering of implicit variables] in RnTypes
noFreeVarsOfType :: Type -> Bool #
Returns True if this type has no free variables. Should be the same as isEmptyVarSet . tyCoVarsOfType, but faster in the non-forall case.
tyCoFVsOfTypes :: [Type] -> FV #
tyCoFVsOfType :: Type -> FV #
The worker for tyCoFVsOfType
and tyCoFVsOfTypeList
.
The previous implementation used unionVarSet
which is O(n+m) and can
make the function quadratic.
It's exported, so that it can be composed with
other functions that compute free variables.
See Note [FV naming conventions] in FV.
Eta-expanded because that makes it run faster (apparently) See Note [FV eta expansion] in FV for explanation.
exactTyCoVarsOfTypes :: [Type] -> TyVarSet #
exactTyCoVarsOfType :: Type -> TyCoVarSet #
tyCoVarsOfTypesList :: [Type] -> [TyCoVar] #
Returns free variables of types, including kind variables as a deterministically ordered list. For type synonyms it does not expand the synonym.
tyCoVarsOfTypesDSet :: [Type] -> DTyCoVarSet #
Returns free variables of types, including kind variables as a deterministic set. For type synonyms it does not expand the synonym.
tyCoVarsOfTypeList :: Type -> [TyCoVar] #
tyCoFVsOfType
that returns free variables of a type in deterministic
order. For explanation of why using VarSet
is not deterministic see
Note [Deterministic FV] in FV.
tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet #
tyCoFVsOfType
that returns free variables of a type in a deterministic
set. For explanation of why using VarSet
is not deterministic see
Note [Deterministic FV] in FV.
tyCoVarsOfTypes :: [Type] -> TyCoVarSet #
tyCoVarsOfType :: Type -> TyCoVarSet #
Create the plain type constructor type which has been applied to no type arguments at all.
mkForAllTys :: [TyCoVarBinder] -> Type -> Type #
Wraps foralls over the type using the provided TyCoVar
s from left to right
mkInvisFunTys :: [Type] -> Type -> Type #
Make nested arrow types
mkInvisFunTy :: Type -> Type -> Type infixr 3 #
mkVisFunTy :: Type -> Type -> Type infixr 3 #
mkTyCoVarTys :: [TyCoVar] -> [Type] #
mkTyCoVarTy :: TyCoVar -> Type #
mkTyVarTys :: [TyVar] -> [Type] #
isVisibleBinder :: TyCoBinder -> Bool #
Does this binder bind a visible argument?
isInvisibleBinder :: TyCoBinder -> Bool #
Does this binder bind an invisible argument?
tyThingCategory :: TyThing -> String #
pprTyThingCategory :: TyThing -> SDoc #
A type labeled KnotTied
might have knot-tied tycons in it. See
Note [Type checking recursive type and class declarations] in
TcTyClsDecls
isPredTy :: HasDebugCallStack => Type -> Bool #
eqType :: Type -> Type -> Bool #
Type equality on source types. Does not look through newtypes
or
PredType
s, but it does look through type synonyms.
This first checks that the kinds of the types are equal and then
checks whether the types are equal, ignoring casts and coercions.
(The kind check is a recursive call, but since all kinds have type
Type
, there is no need to check the types of kinds.)
See also Note [Non-trivial definitional equality] in TyCoRep.
coreView :: Type -> Maybe Type #
This function Strips off the top layer only of a type synonym
application (if any) its underlying representation type.
Returns Nothing if there is nothing to look through.
This function considers Constraint
to be a synonym of TYPE LiftedRep
.
By being non-recursive and inlined, this case analysis gets efficiently joined onto the case analysis that the caller is already doing
tcView :: Type -> Maybe Type #
Gives the typechecker view of a type. This unwraps synonyms but
leaves Constraint
alone. c.f. coreView, which turns Constraint into
TYPE LiftedRep. Returns Nothing if no unwrapping happens.
See also Note [coreView vs tcView]
isLiftedTypeKind :: Kind -> Bool #
This version considers Constraint to be the same as *. Returns True if the argument is equivalent to Type/Constraint and False otherwise. See Note [Kind Constraint and kind Type]
isTauTyCon :: TyCon -> 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)?
Constructors
ForallVis | A visible |
ForallInvis | An invisible |
Instances
liftedTypeKind :: Kind #
constraintKind :: Kind #
mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type #
Like mkTyCoForAllTy
, but does not check the occurrence of the binder
See Note [Unused coercion variable in ForAllTy]
Instances
Data Type | |
Defined in TyCoRep Methods 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 |
data TyCoBinder #
A TyCoBinder
represents an argument to a function. TyCoBinders can be
dependent (Named
) or nondependent (Anon
). They may also be visible or
not. See Note [TyCoBinders]
Instances
Data TyCoBinder | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCoBinder # toConstr :: TyCoBinder -> Constr # dataTypeOf :: TyCoBinder -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyCoBinder) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCoBinder) # gmapT :: (forall b. Data b => b -> b) -> TyCoBinder -> TyCoBinder # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r # gmapQ :: (forall d. Data d => d -> u) -> TyCoBinder -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # | |
Outputable TyCoBinder | |
Defined in TyCoRep |
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"
Argument Flag
Is something required to appear in source Haskell (Required
),
permitted by request (Specified
) (visible type application), or
prohibited entirely from appearing in source Haskell (Inferred
)?
See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep
Instances
Eq ArgFlag | |
Data ArgFlag | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArgFlag -> c ArgFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArgFlag # toConstr :: ArgFlag -> Constr # dataTypeOf :: ArgFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArgFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgFlag) # gmapT :: (forall b. Data b => b -> b) -> ArgFlag -> ArgFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> ArgFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArgFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # | |
Ord ArgFlag | |
Binary ArgFlag | |
Outputable ArgFlag | |
Outputable tv => Outputable (VarBndr tv ArgFlag) | |
data AnonArgFlag #
The non-dependent version of ArgFlag
.
Constructors
VisArg | Used for |
InvisArg | Used for |
Instances
Eq AnonArgFlag | |
Defined in Var | |
Data AnonArgFlag | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnonArgFlag -> c AnonArgFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnonArgFlag # toConstr :: AnonArgFlag -> Constr # dataTypeOf :: AnonArgFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnonArgFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnonArgFlag) # gmapT :: (forall b. Data b => b -> b) -> AnonArgFlag -> AnonArgFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnonArgFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnonArgFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> AnonArgFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnonArgFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # | |
Ord AnonArgFlag | |
Defined in Var Methods compare :: AnonArgFlag -> AnonArgFlag -> Ordering # (<) :: AnonArgFlag -> AnonArgFlag -> Bool # (<=) :: AnonArgFlag -> AnonArgFlag -> Bool # (>) :: AnonArgFlag -> AnonArgFlag -> Bool # (>=) :: AnonArgFlag -> AnonArgFlag -> Bool # max :: AnonArgFlag -> AnonArgFlag -> AnonArgFlag # min :: AnonArgFlag -> AnonArgFlag -> AnonArgFlag # | |
Binary AnonArgFlag | |
Defined in Var Methods put_ :: BinHandle -> AnonArgFlag -> IO () # put :: BinHandle -> AnonArgFlag -> IO (Bin AnonArgFlag) # get :: BinHandle -> IO AnonArgFlag # | |
Outputable AnonArgFlag | |
Defined in Var |
pprTcTyVarDetails :: TcTyVarDetails -> SDoc #
data MetaDetails #
Instances
Outputable MetaDetails | |
Defined in TcType |
data TcTyVarDetails #
Constructors
SkolemTv TcLevel Bool | |
RuntimeUnk | |
MetaTv | |
Instances
Outputable TcTyVarDetails | |
Defined in TcType |
module TcRnTypes
module TcRnDriver
mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) #
The mapAndUnzipM
function maps its first argument over a list, returning
the result as a pair of lists. This function is mainly used with complicated
data structures or a state monad.
foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.
getCCIndexM :: ContainsCostCentreState gbl => FastString -> TcRnIf gbl lcl CostCentreIndex #
Get the next cost centre index associated with a given name.
setImplicitEnvM :: TypeEnv -> IfL a -> IfL a #
getIfModule :: IfL Module #
initIfaceLoad :: HscEnv -> IfG a -> IO a #
initIfaceTcRn :: IfG a -> TcRn a #
setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a #
fixSafeInstances :: SafeHaskellMode -> [ClsInst] -> [ClsInst] #
Switch instances to safe instances if we're in Safe mode.
finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode #
Figure out the final correct safe haskell mode
recordUnsafeInfer :: WarningMessages -> TcM () #
Mark that safe inference has failed See Note [Safe Haskell Overlapping Instances Implementation] although this is used for more than just that failure case.
addModFinalizersWithLclEnv :: ThModFinalizers -> TcM () #
Adds the given modFinalizers to the global environment and set them to use the current local environment.
getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, ThLevel, ThStage)) #
recordTopLevelSpliceLoc :: SrcSpan -> TcM () #
When generating an out-of-scope error message for a variable matching a binding in a later inter-splice group, the typechecker uses the splice locations to provide details in the message about the scope of that binding.
recordThSpliceUse :: TcM () #
recordThUse :: TcM () #
emitNamedWildCardHoleConstraints :: [(Name, TcTyVar)] -> TcM () #
emitAnonWildCardHoleConstraint :: TcTyVar -> TcM () #
traceTcConstraints :: String -> TcM () #
setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a #
isTouchableTcM :: TcTyVar -> TcM Bool #
setTcLevel :: TcLevel -> TcM a -> TcM a #
getTcLevel :: TcM TcLevel #
pushTcLevelM :: TcM a -> TcM (TcLevel, a) #
pushTcLevelM_ :: TcM a -> TcM a #
pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) #
The name says it all. The returned TcLevel is the *inner* TcLevel.
discardConstraints :: TcM a -> TcM a #
Throw out any constraints emitted by the thing_inside
emitInsoluble :: Ct -> TcM () #
emitImplications :: Bag Implication -> TcM () #
emitImplication :: Implication -> TcM () #
emitSimples :: Cts -> TcM () #
emitSimple :: Ct -> TcM () #
emitConstraints :: WantedConstraints -> TcM () #
emitStaticConstraints :: WantedConstraints -> TcM () #
setConstraintVar :: TcRef WantedConstraints -> TcM a -> TcM a #
addTcEvBind :: EvBindsVar -> EvBind -> TcM () #
setTcEvBindsMap :: EvBindsVar -> EvBindMap -> TcM () #
getTcEvBindsMap :: EvBindsVar -> TcM EvBindMap #
getTcEvTyCoVars :: EvBindsVar -> TcM TyCoVarSet #
cloneEvBindsVar :: EvBindsVar -> TcM EvBindsVar #
newNoTcEvBinds :: TcM EvBindsVar #
Creates an EvBindsVar incapable of holding any bindings. It still tracks covar usages (see comments on ebv_tcvs in TcEvidence), thus must be made monadically
add_warn :: WarnReason -> MsgDoc -> MsgDoc -> TcRn () #
Display a warning, with an optional flag, for the current source location.
addWarnAt :: WarnReason -> SrcSpan -> MsgDoc -> TcRn () #
Display a warning for a given source location.
addWarn :: WarnReason -> MsgDoc -> TcRn () #
Display a warning for the current source location.
addWarnTcM :: WarnReason -> (TidyEnv, MsgDoc) -> TcM () #
Display a warning in a given context.
addWarnTc :: WarnReason -> MsgDoc -> TcM () #
Display a warning in the current context.
warnTcM :: WarnReason -> Bool -> (TidyEnv, MsgDoc) -> TcM () #
Display a warning if a condition is met.
warnIfFlag :: WarningFlag -> Bool -> MsgDoc -> TcRn () #
Display a warning if a condition is met, and the warning is enabled
failWithTcM :: (TidyEnv, MsgDoc) -> TcM a #
failWithTc :: MsgDoc -> TcM a #
tryTcDiscardingErrs :: TcM r -> TcM r -> TcM r #
discardErrs :: TcRn a -> TcRn a #
foldAndRecoverM :: (b -> a -> TcRn b) -> b -> [a] -> TcRn b #
The accumulator is not updated if the action fails
mapAndReportM :: (a -> TcRn b) -> [a] -> TcRn [b] #
Apply the function to all elements on the input list If all succeed, return the list of results Othewise fail, propagating all errors
mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b] #
Drop elements of the input that fail, so the result list can be shorter than the argument list
captureConstraints :: TcM a -> TcM (a, WantedConstraints) #
tryCaptureConstraints :: TcM a -> TcM (Maybe a, WantedConstraints) #
popErrCtxt :: TcM a -> TcM a #
addLandmarkErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a #
Variant of addLandmarkErrCtxt
that allows for monadic operations
and tidying.
addLandmarkErrCtxt :: MsgDoc -> TcM a -> TcM a #
Add a fixed landmark message to the error context. A landmark message is always sure to be reported, even if there is a lot of context. It also doesn't count toward the maximum number of contexts reported.
addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a #
Add a message to the error context. This message may do tidying.
addErrCtxt :: MsgDoc -> TcM a -> TcM a #
Add a fixed message to the error context. This message should not do any tidying.
setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a #
getErrCtxt :: TcM [ErrCtxt] #
failIfErrsM :: TcRn () #
whenNoErrs :: TcM () -> TcM () #
checkNoErrs :: TcM r -> TcM r #
reportWarning :: WarnReason -> ErrMsg -> TcRn () #
reportError :: ErrMsg -> TcRn () #
reportErrors :: [ErrMsg] -> TcM () #
discardWarnings :: TcRn a -> TcRn a #
addMessages :: Messages -> TcRn () #
getErrsVar :: TcRn (TcRef Messages) #
wrapLocM_ :: HasSrcSpan a => (SrcSpanLess a -> TcM ()) -> a -> TcM () #
wrapLocSndM :: (HasSrcSpan a, HasSrcSpan c) => (SrcSpanLess a -> TcM (b, SrcSpanLess c)) -> a -> TcM (b, c) #
wrapLocFstM :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> TcM (SrcSpanLess b, c)) -> a -> TcM (b, c) #
wrapLocM :: (HasSrcSpan a, HasSrcSpan b) => (SrcSpanLess a -> TcM (SrcSpanLess b)) -> a -> TcM b #
addLocM :: HasSrcSpan a => (SrcSpanLess a -> TcM b) -> a -> TcM b #
setSrcSpan :: SrcSpan -> TcRn a -> TcRn a #
getSrcSpanM :: TcRn SrcSpan #
addDependentFiles :: [FilePath] -> TcRn () #
getDeclaredDefaultTys :: TcRn (Maybe [Type]) #
getRdrEnvs :: TcRn (GlobalRdrEnv, LocalRdrEnv) #
tcIsHsBootOrSig :: TcRn Bool #
getGHCiMonad :: TcRn Name #
traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () #
traceHiDiffs :: SDoc -> TcRnIf m n () #
printForUserTcRn :: SDoc -> TcRn () #
Like logInfoTcRn, but for user consumption
traceTcRnWithStyle :: PprStyle -> DynFlags -> DumpFlag -> SDoc -> TcRn () #
Unconditionally dump some trace output
The DumpFlag is used only to set the output filename for --dump-to-file, not to decide whether or not to output That part is done by the caller
traceTcRnForUser :: DumpFlag -> SDoc -> TcRn () #
A wrapper around traceTcRnWithStyle
which uses PprUser
style.
traceTcRn :: DumpFlag -> SDoc -> TcRn () #
A wrapper around traceTcRnWithStyle
which uses PprDump
style.
traceOptTcRn :: DumpFlag -> SDoc -> TcRn () #
writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl () #
newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId] #
newSysLocalId :: FastString -> TcType -> TcRnIf gbl lcl TcId #
newSysName :: OccName -> TcRnIf gbl lcl Name #
cloneLocalName :: Name -> TcM Name #
newUniqueSupply :: TcRnIf gbl lcl UniqSupply #
escapeArrowScope :: TcM a -> TcM a #
newArrowScope :: TcM a -> TcM a #
withException :: TcRnIf gbl lcl (MaybeErr MsgDoc a) -> TcRnIf gbl lcl a #
A convenient wrapper for taking a MaybeErr MsgDoc a
and throwing
an exception if it is an error.
getEpsAndHpt :: TcRnIf gbl lcl (ExternalPackageState, HomePackageTable) #
getHpt :: TcRnIf gbl lcl HomePackageTable #
updateEps_ :: (ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl () #
Update the external package state.
This is an atomic operation and forces evaluation of the modified EPS in order to avoid space leaks.
updateEps :: (ExternalPackageState -> (ExternalPackageState, a)) -> TcRnIf gbl lcl a #
Update the external package state. Returns the second result of the modifier function.
This is an atomic operation and forces evaluation of the modified EPS in order to avoid space leaks.
getEps :: TcRnIf gbl lcl ExternalPackageState #
getEpsVar :: TcRnIf gbl lcl (TcRef ExternalPackageState) #
withDoDynamicToo :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a #
getGhcMode :: TcRnIf gbl lcl GhcMode #
unlessXOptM :: Extension -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #
whenWOptM :: WarningFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #
whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () #
unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #
unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #
unsetXOptM :: Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a #
woptM :: WarningFlag -> TcRnIf gbl lcl Bool #
goptM :: GeneralFlag -> TcRnIf gbl lcl Bool #
discardResult :: TcM a -> TcM () #
initTcWithGbl :: HscEnv -> TcGblEnv -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r) #
Run a TcM
action in the context of an existing GblEnv
.
initTc :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r) #
Setup the initial typechecking environment
class ContainsCostCentreState e where #
Environments which track CostCentreState
Methods
extractCostCentreState :: e -> TcRef CostCentreState #
Instances
ContainsCostCentreState DsGblEnv | |
Defined in TcRnMonad Methods extractCostCentreState :: DsGblEnv -> TcRef CostCentreState # | |
ContainsCostCentreState TcGblEnv | |
Defined in TcRnMonad Methods extractCostCentreState :: TcGblEnv -> TcRef CostCentreState # |
getRoleAnnots :: [Name] -> RoleAnnotEnv -> [LRoleAnnotDecl GhcRn] #
lookupRoleAnnot :: RoleAnnotEnv -> Name -> Maybe (LRoleAnnotDecl GhcRn) #
mkRoleAnnotEnv :: [LRoleAnnotDecl GhcRn] -> RoleAnnotEnv #
getEvBindsTcPluginM :: TcPluginM EvBindsVar #
Access the EvBindsVar
carried by the TcPluginM
during
constraint solving. Returns Nothing
if invoked during
tcPluginInit
or tcPluginStop
.
unsafeTcPluginTcM :: TcM a -> TcPluginM a #
runTcPluginM :: TcPluginM a -> EvBindsVar -> TcM a #
hasCompleteSig :: TcSigFun -> Name -> Bool #
No signature or a partial signature
isPartialSig :: TcIdSigInst -> Bool #
plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails #
Union two ImportAvails
This function is a key part of Import handling, basically for each import we create a separate ImportAvails structure and then union them all together with this function.
modDepsElts :: ModuleNameEnv (ModuleName, IsBootInterface) -> [(ModuleName, IsBootInterface)] #
mkModDeps :: [(ModuleName, IsBootInterface)] -> ModuleNameEnv (ModuleName, IsBootInterface) #
pprPECategory :: PromotionErr -> SDoc #
pprTcTyThingCategory :: TcTyThing -> SDoc #
outerLevel :: ThLevel #
topAnnStage :: ThStage #
removeBindingShadowing :: HasOccName a => [a] -> [a] #
pushErrCtxtSameOrigin :: ErrCtxt -> CtLoc -> CtLoc #
A NameShape
is a substitution on Name
s that can be used
to refine the identities of a hole while we are renaming interfaces
(see RnModIface
). Specifically, a NameShape
for
ns_module_name
A
, defines a mapping from {A.T}
(for some OccName
T
) to some arbitrary other Name
.
The most intruiging thing about a NameShape
, however, is
how it's constructed. A NameShape
is *implied* by the
exported AvailInfo
s of the implementor of an interface:
if an implementor of signature H
exports M.T
, you implicitly
define a substitution from {H.T}
to M.T
. So a NameShape
is computed from the list of AvailInfo
s that are exported
by the implementation of a module, or successively merged
together by the export lists of signatures which are joining
together.
It's not the most obvious way to go about doing this, but it does seem to work!
NB: Can't boot this and put it in NameShape because then we start pulling in too many DynFlags things.
Constructors
NameShape | |
Fields
|
Instances
ContainsDynFlags (Env gbl lcl) | |
Defined in TcRnTypes Methods extractDynFlags :: Env gbl lcl -> DynFlags # | |
ContainsModule gbl => ContainsModule (Env gbl lcl) | |
Defined in TcRnTypes Methods extractModule :: Env gbl lcl -> Module # |
Constructors
DsGblEnv | |
Fields |
Instances
ContainsCostCentreState DsGblEnv | |
Defined in TcRnMonad Methods extractCostCentreState :: DsGblEnv -> TcRef CostCentreState # | |
ContainsModule DsGblEnv | |
Defined in TcRnTypes Methods extractModule :: DsGblEnv -> Module # |
data FrontendResult #
FrontendResult
describes the result of running the
frontend of a Haskell module. Usually, you'll get
a FrontendTypecheck
, since running the frontend involves
typechecking a program, but for an hs-boot merge you'll
just get a ModIface, since no actual typechecking occurred.
This data type really should be in HscTypes, but it needs to have a TcGblEnv which is only defined here.
Constructors
FrontendTypecheck TcGblEnv |
TcGblEnv
describes the top-level of the module at the
point at which the typechecker is finished work.
It is this structure that is handed on to the desugarer
For state that needs to be updated during the typechecking
phase and returned at end, use a TcRef
(= IORef
).
Constructors
TcGblEnv | |
Fields
|
Instances
ContainsCostCentreState TcGblEnv | |
Defined in TcRnMonad Methods extractCostCentreState :: TcGblEnv -> TcRef CostCentreState # | |
ContainsModule TcGblEnv | |
Defined in TcRnTypes Methods extractModule :: TcGblEnv -> Module # |
type RecFieldEnv = NameEnv [FieldLabel] #
data SelfBootInfo #
Constructors
NoSelfBoot | |
SelfBoot | |
Fields
|
type TcBinderStack = [TcBinder] #
Constructors
TcIdBndr TcId TopLevelFlag | |
TcIdBndr_ExpType Name ExpType TopLevelFlag | |
TcTvBndr Name TyVar |
data SpliceType #
Constructors
Splice SpliceType | |
RunSplice (TcRef [ForeignRef (Q ())]) | |
Comp | |
Brack ThStage PendingStuff |
data PendingStuff #
Constructors
RnPendingUntyped (TcRef [PendingRnSplice]) | |
RnPendingTyped | |
TcPending (TcRef [PendingTcSplice]) (TcRef WantedConstraints) |
Constructors
NoArrowCtxt | |
ArrowCtxt LocalRdrEnv (TcRef WantedConstraints) |
A typecheckable thing available in a local context. Could be
AGlobal
TyThing
, but also lexically scoped variables, etc.
See TcEnv
for how to retrieve a TyThing
given a Name
.
Constructors
AGlobal TyThing | |
ATcId | |
Fields
| |
ATyVar Name TcTyVar | |
ATcTyCon TyCon | |
APromotionErr PromotionErr |
data PromotionErr #
Constructors
TyConPE | |
ClassPE | |
FamDataConPE | |
ConstrainedDataConPE PredType | |
PatSynPE | |
RecDataConPE | |
NoDataKindsTC | |
NoDataKindsDC |
Instances
Outputable PromotionErr | |
Defined in TcRnTypes |
data IdBindingInfo #
IdBindingInfo describes how an Id is bound.
It is used for the following purposes: a) for static forms in TcExpr.checkClosedInStaticForm and b) to figure out when a nested binding can be generalised, in TcBinds.decideGeneralisationPlan.
Constructors
NotLetBound | |
ClosedLet | |
NonClosedLet RhsNames ClosedTypeId |
Instances
Outputable IdBindingInfo | |
Defined in TcRnTypes |
data IsGroupClosed #
IsGroupClosed describes a group of mutually-recursive bindings
Constructors
IsGroupClosed (NameEnv RhsNames) ClosedTypeId |
type ClosedTypeId = Bool #
data ImportAvails #
ImportAvails
summarises what was imported from where, irrespective of
whether the imported things are actually used or not. It is used:
- when processing the export list,
- when constructing usage info for the interface file,
- to identify the list of directly imported modules for initialisation purposes and for optimised overlap checking of family instances,
- when figuring out what things are really unused
Constructors
ImportAvails | |
Fields
|
Constructors
ImportByUser IsBootInterface | |
ImportBySystem | |
ImportByPlugin |
Constructors
TcIdSig TcIdSigInfo | |
TcPatSynSig TcPatSynInfo |
data TcIdSigInfo #
Constructors
CompleteSig | |
PartialSig | |
Fields
|
Instances
Outputable TcIdSigInfo | |
Defined in TcRnTypes |
data TcIdSigInst #
Constructors
TISI | |
Fields
|
Instances
Outputable TcIdSigInst | |
Defined in TcRnTypes |
data TcPatSynInfo #
Constructors
TPSI | |
Fields
|
Instances
Outputable TcPatSynInfo | |
Defined in TcRnTypes |
type TcPluginSolver = [Ct] -> [Ct] -> [Ct] -> TcPluginM TcPluginResult #
Constructors
TcPlugin | |
Fields
|
data TcPluginResult #
Constructors
TcPluginContradiction [Ct] | The plugin found a contradiction. The returned constraints are removed from the inert set, and recorded as insoluble. |
TcPluginOk [(EvTerm, Ct)] [Ct] | The first field is for constraints that were solved. These are removed from the inert set, and the evidence for them is recorded. The second field contains new work, that should be processed by the constraint solver. |
type RoleAnnotEnv = NameEnv (LRoleAnnotDecl GhcRn) #
An expression or type hole
Constructors
ExprHole UnboundVar | Either an out-of-scope variable or a "true" hole in an expression (TypedHoles) |
TypeHole OccName | A hole in a type (PartialTypeSignatures) |
data CompleteMatch #
A list of conlikes which represents a complete pattern match.
These arise from COMPLETE
signatures.
Constructors
CompleteMatch | |
Fields
|
Instances
Outputable CompleteMatch | |
Defined in HscTypes |
type CompleteMatchMap = UniqFM [CompleteMatch] #
A map keyed by the completeMatchTyCon
.
setLclEnvTcLevel :: TcLclEnv -> TcLevel -> TcLclEnv #
getLclEnvTcLevel :: TcLclEnv -> TcLevel #
setLclEnvLoc :: TcLclEnv -> RealSrcSpan -> TcLclEnv #
getLclEnvLoc :: TcLclEnv -> RealSrcSpan #
Constructors
TcLclEnv | |
Fields
|
updEnv :: (env -> env') -> IOEnv env' a -> IOEnv env a #
Perform a computation with an altered environment
atomicUpdMutVar' :: IORef a -> (a -> (a, b)) -> IOEnv env b #
Strict variant of atomicUpdMutVar
.
atomicUpdMutVar :: IORef a -> (a -> (a, b)) -> IOEnv env b #
Atomically update the reference. Does not force the evaluation of the
new variable contents. For strict update, use atomicUpdMutVar'
.
readMutVar :: IORef a -> IOEnv env a #
writeMutVar :: IORef a -> a -> IOEnv env () #
uninterruptibleMaskM_ :: IOEnv env a -> IOEnv env a #
unsafeInterleaveM :: IOEnv env a -> IOEnv env a #
Instances
Monad (IOEnv m) | |
Functor (IOEnv env) | |
MonadFail (IOEnv m) | |
Applicative (IOEnv m) | |
MonadPlus (IOEnv env) | |
MonadIO (IOEnv env) | |
Alternative (IOEnv env) | |
ContainsDynFlags env => HasDynFlags (IOEnv env) | |
Defined in IOEnv Methods getDynFlags :: IOEnv env DynFlags # | |
ContainsModule env => HasModule (IOEnv env) | |
ExceptionMonad (IOEnv a) | |
data IOEnvFailure #
Constructors
IOEnvFailure |
Instances
Show IOEnvFailure | |
Defined in IOEnv Methods showsPrec :: Int -> IOEnvFailure -> ShowS # show :: IOEnvFailure -> String # showList :: [IOEnvFailure] -> ShowS # | |
Exception IOEnvFailure | |
Defined in IOEnv Methods toException :: IOEnvFailure -> SomeException # fromException :: SomeException -> Maybe IOEnvFailure # displayException :: IOEnvFailure -> String # |
filterOutM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
Like filterM
, only it reverses the sense of the test.
unlessM :: Monad m => m Bool -> m () -> m () #
Monadic version of unless
, taking the condition in the monad
whenM :: Monad m => m Bool -> m () -> m () #
Monadic version of when
, taking the condition in the monad
maybeMapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #
Monadic version of fmap specialised for Maybe
foldlM_ :: (Monad m, Foldable t) => (a -> b -> m a) -> a -> t b -> m () #
Monadic version of foldl that discards its result
fmapEitherM :: Monad m => (a -> m b) -> (c -> m d) -> Either a c -> m (Either b d) #
Monadic version of fmap
fmapMaybeM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #
Monadic version of fmap
Arguments
:: Monad m | |
=> (acc -> x -> m (acc, y)) | combining function |
-> acc | initial state |
-> [x] | inputs |
-> m (acc, [y]) | final state, outputs |
Monadic version of mapAccumL
mapAndUnzip5M :: Monad m => (a -> m (b, c, d, e, f)) -> [a] -> m ([b], [c], [d], [e], [f]) #
mapAndUnzip4M :: Monad m => (a -> m (b, c, d, e)) -> [a] -> m ([b], [c], [d], [e]) #
mapAndUnzip3M :: Monad m => (a -> m (b, c, d)) -> [a] -> m ([b], [c], [d]) #
mapAndUnzipM for triples
zipWithAndUnzipM :: Monad m => (a -> b -> m (c, d)) -> [a] -> [b] -> m ([c], [d]) #
zipWith3M_ :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m () #
data ForeignSrcLang #
Foreign formats supported by GHC via TH
Constructors
LangC | C |
LangCxx | C++ |
LangObjc | Objective C |
LangObjcxx | Objective C++ |
LangAsm | Assembly language (.s) |
RawObject | Object (.o) |
Instances
module TidyPgm
module TyCon
module TysPrim
module TysWiredIn
Arguments
:: Bool | Should specified binders count towards injective positions in the kind of the TyCon? (If you're using visible kind applications, then you want True here. |
-> TyCon | |
-> Int | The number of args the |
-> Bool | Does |
Does a TyCon
(that is applied to some number of arguments) need to be
ascribed with an explicit kind signature to resolve ambiguity if rendered as
a source-syntax type?
(See Note [When does a tycon application need an explicit kind signature?]
for a full explanation of what this function checks for.)
classifiesTypeWithValues :: Kind -> Bool #
Does this classify a type allowed to have values? Responds True to things like *, #, TYPE Lifted, TYPE v, Constraint.
True of any sub-kind of OpenTypeKind
isKindLevPoly :: Kind -> Bool #
Tests whether the given kind (which should look like TYPE x
)
is something other than a constructor tree (that is, constructors at every node).
E.g. True of TYPE k, TYPE (F Int)
False of TYPE 'LiftedRep
isConstraintKindCon :: TyCon -> Bool #
splitVisVarsOfTypes :: [Type] -> Pair TyCoVarSet #
splitVisVarsOfType :: Type -> Pair TyCoVarSet #
Retrieve the free variables in this type, splitting them based on whether they are used visibly or invisibly. Invisible ones come first.
synTyConResKind :: TyCon -> Kind #
tyConsOfType :: Type -> UniqSet TyCon #
All type constructors occurring in the type; looking through type synonyms, but not newtypes. When it finds a Class, it returns the class TyCon.
resultIsLevPoly :: Type -> Bool #
Looking past all pi-types, is the end result potentially levity polymorphic? Example: True for (forall r (a :: TYPE r). String -> a) Example: False for (forall r1 r2 (a :: TYPE r1) (b :: TYPE r2). a -> b -> Type)
isTypeLevPoly :: Type -> Bool #
Returns True if a type is levity polymorphic. Should be the same as (isKindLevPoly . typeKind) but much faster. Precondition: The type has kind (TYPE blah)
tcReturnsConstraintKind :: Kind -> Bool #
tcIsRuntimeTypeKind :: Kind -> Bool #
Is this kind equivalent to TYPE r
(for some unknown r)?
This considers Constraint
to be distinct from *
.
tcIsLiftedTypeKind :: Kind -> Bool #
Is this kind equivalent to *
?
This considers Constraint
to be distinct from *
. For a version that
treats them as the same type, see isLiftedTypeKind
.
tcIsConstraintKind :: Kind -> Bool #
tcTypeKind :: HasDebugCallStack => Type -> Kind #
typeKind :: HasDebugCallStack => Type -> Kind #
nonDetCmpTc :: TyCon -> TyCon -> Ordering #
nonDetCmpTypes :: [Type] -> [Type] -> Ordering #
nonDetCmpType :: Type -> Type -> Ordering #
eqTypes :: [Type] -> [Type] -> Bool #
Type equality on lists of types, looking through type synonyms but not newtypes.
eqTypeX :: RnEnv2 -> Type -> Type -> Bool #
Compare types with respect to a (presumably) non-empty RnEnv2
.
isValidJoinPointType :: JoinArity -> Type -> Bool #
Determine whether a type could be the type of a join point of given total
arity, according to the polymorphism rule. A join point cannot be polymorphic
in its return type, since given
join j a
b x y z = e1 in e2,
the types of e1 and e2 must be the same, and a and b are not in scope for e2.
(See Note [The polymorphism rule of join points] in CoreSyn.) Returns False
also if the type simply doesn't have enough arguments.
Note that we need to know how many arguments (type *and* value) the putative join point takes; for instance, if j :: forall a. a -> Int then j could be a binary join point returning an Int, but it could *not* be a unary join point returning a -> Int.
TODO: See Note [Excess polymorphism and join points]
isPrimitiveType :: Type -> Bool #
Returns true of types that are opaque to Haskell.
isStrictType :: HasDebugCallStack => Type -> Bool #
Computes whether an argument (or let right hand side) should
be computed strictly or lazily, based only on its type.
Currently, it's just isUnliftedType
. Panics on levity-polymorphic types.
isDataFamilyAppType :: Type -> Bool #
Check whether a type is a data family type
See Type for what an algebraic type is. Should only be applied to types, as opposed to e.g. partially saturated type constructors
isUnboxedSumType :: Type -> Bool #
isUnboxedTupleType :: Type -> Bool #
getRuntimeRep :: HasDebugCallStack => Type -> Type #
Extract the RuntimeRep classifier of a type. For instance,
getRuntimeRep_maybe Int = LiftedRep
. Panics if this is not possible.
getRuntimeRep_maybe :: HasDebugCallStack => Type -> Maybe Type #
Extract the RuntimeRep classifier of a type. For instance,
getRuntimeRep_maybe Int = LiftedRep
. Returns Nothing
if this is not
possible.
dropRuntimeRepArgs :: [Type] -> [Type] #
Drops prefix of RuntimeRep constructors in TyConApp
s. Useful for e.g.
dropping 'LiftedRep arguments of unboxed tuple TyCon applications:
isRuntimeRepKindedTy :: Type -> Bool #
Is this a type of kind RuntimeRep? (e.g. LiftedRep)
mightBeUnliftedType :: Type -> Bool #
isUnliftedType :: HasDebugCallStack => Type -> Bool #
See Type for what an unlifted type is.
Panics on levity polymorphic types; See mightBeUnliftedType
for
a more approximate predicate that behaves better in the presence of
levity polymorphism.
isLiftedType_maybe :: HasDebugCallStack => Type -> Maybe Bool #
Returns Just True if this type is surely lifted, Just False if it is surely unlifted, Nothing if we can't be sure (i.e., it is levity polymorphic), and panics if the kind does not have the shape TYPE r.
isCoVarType :: Type -> Bool #
isFamFreeTy :: Type -> Bool #
coAxNthLHS :: forall (br :: BranchFlag). CoAxiom br -> Int -> Type #
Get the type on the LHS of a coercion induced by a type/data family instance.
mkFamilyTyConApp :: TyCon -> [Type] -> Type #
Given a family instance TyCon and its arg types, return the corresponding family type. E.g:
data family T a data instance T (Maybe b) = MkT b
Where the instance tycon is :RTL, so:
mkFamilyTyConApp :RTL Int = T (Maybe Int)
closeOverKindsDSet :: DTyVarSet -> DTyVarSet #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministic set.
closeOverKindsList :: [TyVar] -> [TyVar] #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a deterministically ordered list.
closeOverKindsFV :: [TyVar] -> FV #
Given a list of tyvars returns a deterministic FV computation that returns the given tyvars with the kind variables free in the kinds of the given tyvars.
closeOverKinds :: TyVarSet -> TyVarSet #
Add the kind variables free in the kinds of the tyvars in the given set. Returns a non-deterministic set.
binderRelevantType_maybe :: TyCoBinder -> Maybe Type #
Extract a relevant type, if there is one.
tyBinderType :: TyBinder -> Type #
tyCoBinderType :: TyCoBinder -> Type #
isAnonTyCoBinder :: TyCoBinder -> Bool #
Does this binder bind a variable that is not erased? Returns
True
for anonymous binders.
mkAnonBinder :: AnonArgFlag -> Type -> TyCoBinder #
Make an anonymous binder
appTyArgFlags :: Type -> [Type] -> [ArgFlag] #
Given a Type
and a list of argument types to which the Type
is
applied, determine each argument's visibility
(Inferred
, Specified
, or Required
).
Most of the time, the arguments will be Required
, but not always. Consider
f :: forall a. a -> Type
. In f Type Bool
, the first argument (Type
) is
Specified
and the second argument (Bool
) is Required
. It is precisely
this sort of higher-rank situation in which appTyArgFlags
comes in handy,
since f Type Bool
would be represented in Core using AppTy
s.
(See also #15792).
tyConArgFlags :: TyCon -> [Type] -> [ArgFlag] #
Given a TyCon
and a list of argument types to which the TyCon
is
applied, determine each argument's visibility
(Inferred
, Specified
, or Required
).
Wrinkle: consider the following scenario:
T :: forall k. k -> k tyConArgFlags T [forall m. m -> m -> m, S, R, Q]
After substituting, we get
T (forall m. m -> m -> m) :: (forall m. m -> m -> m) -> forall n. n -> n -> n
Thus, the first argument is invisible, S
is visible, R
is invisible again,
and Q
is visible.
partitionInvisibles :: [(a, ArgFlag)] -> ([a], [a]) #
Given a list of things paired with their visibilities, partition the things into (invisible things, visible things).
filterOutInferredTypes :: TyCon -> [Type] -> [Type] #
filterOutInvisibleTypes :: TyCon -> [Type] -> [Type] #
splitPiTysInvisibleN :: Int -> Type -> ([TyCoBinder], Type) #
splitPiTysInvisible :: Type -> ([TyCoBinder], Type) #
invisibleTyBndrCount :: Type -> Int #
splitForAllVarBndrs :: Type -> ([TyCoVarBinder], Type) #
Like splitPiTys
but split off only named binders
and returns TyCoVarBinders rather than TyCoBinders
splitPiTys :: Type -> ([TyCoBinder], Type) #
Split off all TyCoBinders to a type, splitting both proper foralls and functions
splitPiTy :: Type -> (TyCoBinder, Type) #
Takes a forall type apart, or panics
splitPiTy_maybe :: Type -> Maybe (TyCoBinder, Type) #
Attempts to take a forall type apart; works with proper foralls and functions
splitForAllTy_co_maybe :: Type -> Maybe (TyCoVar, Type) #
Like splitForAllTy_maybe, but only returns Just if it is a covar binder.
splitForAllTy_ty_maybe :: Type -> Maybe (TyCoVar, Type) #
Like splitForAllTy_maybe, but only returns Just if it is a tyvar binder.
splitForAllTy_maybe :: Type -> Maybe (TyCoVar, Type) #
Attempts to take a forall type apart, but only if it's a proper forall, with a named binder
dropForAlls :: Type -> Type #
Drops all ForAllTys
splitForAllTy :: Type -> (TyCoVar, Type) #
Take a forall type apart, or panics if that is not possible.
isForAllTy_co :: Type -> Bool #
Like isForAllTy
, but returns True only if it is a covar binder
isForAllTy_ty :: Type -> Bool #
Like isForAllTy
, but returns True only if it is a tyvar binder
isForAllTy :: Type -> Bool #
Checks whether this is a proper forall (with a named binder)
splitForAllTysSameVis :: ArgFlag -> Type -> ([TyCoVar], Type) #
Like splitForAllTys
, but only splits a ForAllTy
if
is sameVis
argf supplied_argfTrue
, where argf
is the visibility
of the ForAllTy
's binder and supplied_argf
is the visibility provided
as an argument to this function.
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.
Arguments
:: [TyVar] | binders |
-> TyCoVarSet | free variables of result |
-> [TyConBinder] |
Given a list of type-level vars and the free vars of a result kind, makes TyCoBinders, preferring anonymous binders if the variable is, in fact, not dependent. e.g. mkTyConBindersPreferAnon (k:*),(b:k),(c:k) We want (k:*) Named, (b:k) Anon, (c:k) Anon
All non-coercion binders are visible.
mkLamType :: Var -> Type -> Type #
Makes a (->)
type or an implicit forall type, depending
on whether it is given a type variable or a term variable.
This is used, for example, when producing the type of a lambda.
Always uses Inferred binders.
mkVisForAllTys :: [TyVar] -> Type -> Type #
Like mkForAllTys, but assumes all variables are dependent and visible
mkSpecForAllTys :: [TyVar] -> Type -> Type #
Like mkForAllTys
, but assumes all variables are dependent and
Specified
, a common case
mkSpecForAllTy :: TyVar -> Type -> Type #
Like mkForAllTy
, but assumes the variable is dependent and Specified
,
a common case
mkInvForAllTys :: [TyVar] -> Type -> Type #
Like mkTyCoInvForAllTys
, but tvs should be a list of tyvar
mkTyCoInvForAllTys :: [TyCoVar] -> Type -> Type #
Like mkForAllTys
, but assumes all variables are dependent and
Inferred
, a common case
mkInvForAllTy :: TyVar -> Type -> Type #
Like mkTyCoInvForAllTy
, but tv should be a tyvar
stripCoercionTy :: Type -> Coercion #
isCoercionTy_maybe :: Type -> Maybe Coercion #
mkCoercionTy :: Coercion -> Type #
discardCast :: Type -> Type #
Drop the cast on a type, if any. If there is no cast, just return the original type. This is rarely what you want. The CastTy data constructor (in TyCoRep) has the invariant that another CastTy is not inside. See the data constructor for a full description of this invariant. Since CastTy cannot be nested, the result of discardCast cannot be a CastTy.
tyConBindersTyCoBinders :: [TyConBinder] -> [TyCoBinder] #
newTyConInstRhs :: TyCon -> [Type] -> Type #
Unwrap one layer
of newtype on a type constructor and its
arguments, using an eta-reduced version of the newtype
if possible.
This requires tys to have at least newTyConInstArity tycon
elements.
splitListTyConApp_maybe :: Type -> Maybe Type #
Attempts to tease a list type apart and gives the type of the elements if successful (looks through type synonyms)
repSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #
Like splitTyConApp_maybe
, but doesn't look through synonyms. This
assumes the synonyms have already been dealt with.
Moreover, for a FunTy, it only succeeds if the argument types have enough info to extract the runtime-rep arguments that the funTyCon requires. This will usually be true; but may be temporarily false during canonicalization: see Note [FunTy and decomposing tycon applications] in TcCanonical
tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) #
Split a type constructor application into its type constructor and
applied types. Note that this may fail in the case of a FunTy
with an
argument of unknown kind FunTy
(e.g. FunTy (a :: k) Int
. since the kind
of a
isn't of the form TYPE rep
). Consequently, you may need to zonk your
type before using this function.
If you only need the TyCon
, consider using tcTyConAppTyCon_maybe
.
splitTyConApp :: Type -> (TyCon, [Type]) #
Attempts to tease a type apart into a type constructor and the application
of a number of arguments to that constructor. Panics if that is not possible.
See also splitTyConApp_maybe
tyConAppArgN :: Int -> Type -> Type #
tyConAppArgs :: Type -> [Type] #
tyConAppArgs_maybe :: Type -> Maybe [Type] #
The same as snd . splitTyConApp
tyConAppTyCon :: Type -> TyCon #
tyConAppTyCon_maybe :: Type -> Maybe TyCon #
The same as fst . splitTyConApp
tyConAppTyConPicky_maybe :: Type -> Maybe TyCon #
Retrieve the tycon heading this type, if there is one. Does not look through synonyms.
mkTyConApp :: TyCon -> [Type] -> Type #
piResultTys :: HasDebugCallStack => Type -> [Type] -> Type #
(piResultTys f_ty [ty1, .., tyn]) gives the type of (f ty1 .. tyn)
where f :: f_ty
piResultTys
is interesting because:
1. f_ty
may have more for-alls than there are args
2. Less obviously, it may have fewer for-alls
For case 2. think of:
piResultTys (forall a.a) [forall b.b, Int]
This really can happen, but only (I think) in situations involving
undefined. For example:
undefined :: forall a. a
Term: undefined (forall b. b->b)
Int
This term should have type (Int -> Int), but notice that
there are more type args than foralls in undefined
s type.
Just like piResultTys
but for a single argument
Try not to iterate piResultTy
, because it's inefficient to substitute
one variable at a time; instead use 'piResultTys"
Extract the function argument type and panic if that is not possible
funResultTy :: Type -> Type #
Extract the function result type and panic if that is not possible
splitFunTys :: Type -> ([Type], Type) #
splitFunTy_maybe :: Type -> Maybe (Type, Type) #
Attempts to extract the argument and result types from a type
splitFunTy :: Type -> (Type, Type) #
Attempts to extract the argument and result types from a type, and
panics if that is not possible. See also splitFunTy_maybe
pprUserTypeErrorTy :: Type -> SDoc #
Render a type corresponding to a user type error into a SDoc.
userTypeError_maybe :: Type -> Maybe Type #
Is this type a custom user error? If so, give us the kind and the error message.
isStrLitTy :: Type -> Maybe FastString #
Is this a symbol literal. We also look through type synonyms.
mkStrLitTy :: FastString -> Type #
isNumLitTy :: Type -> Maybe Integer #
Is this a numeric literal. We also look through type synonyms.
mkNumLitTy :: Integer -> Type #
repSplitAppTys :: HasDebugCallStack => Type -> (Type, [Type]) #
Like splitAppTys
, but doesn't look through type synonyms
splitAppTys :: Type -> (Type, [Type]) #
Recursively splits a type as far as is possible, leaving a residual type being applied to and the type arguments applied to it. Never fails, even if that means returning an empty list of type applications.
splitAppTy :: Type -> (Type, Type) #
Attempts to take a type application apart, as in splitAppTy_maybe
,
and panics if this is not possible
tcRepSplitAppTy_maybe :: Type -> Maybe (Type, Type) #
Does the AppTy split as in tcSplitAppTy_maybe
, but assumes that
any coreView stuff is already done. Refuses to look through (c => t)
repSplitAppTy_maybe :: HasDebugCallStack => Type -> Maybe (Type, Type) #
Does the AppTy split as in splitAppTy_maybe
, but assumes that
any Core view stuff is already done
splitAppTy_maybe :: Type -> Maybe (Type, Type) #
Attempt to take a type application apart, whether it is a function, type constructor, or plain type application. Note that type family applications are NEVER unsaturated by this!
repGetTyVar_maybe :: Type -> Maybe TyVar #
Attempts to obtain the type variable underlying a Type
, without
any expansion
getCastedTyVar_maybe :: Type -> Maybe (TyVar, CoercionN) #
If the type is a tyvar, possibly under a cast, returns it, along with the coercion. Thus, the co is :: kind tv ~N kind ty
getTyVar :: String -> Type -> TyVar #
Attempts to obtain the type variable underlying a Type
, and panics with the
given message if this is not a type variable type. See also getTyVar_maybe
mapCoercion :: Monad m => TyCoMapper env m -> env -> Coercion -> m Coercion #
isRuntimeRepVar :: TyVar -> Bool #
Is a tyvar of type RuntimeRep
?
isUnliftedRuntimeRep :: Type -> Bool #
isUnliftedTypeKind :: Kind -> Bool #
Returns True if the kind classifies unlifted types and False otherwise. Note that this returns False for levity-polymorphic kinds, which may be specialized to a kind that classifies unlifted types.
isLiftedRuntimeRep :: Type -> Bool #
kindRep_maybe :: HasDebugCallStack => Kind -> Maybe Type #
Given a kind (TYPE rr), extract its RuntimeRep classifier rr.
For example, kindRep_maybe * = Just LiftedRep
Returns Nothing
if the kind is not of form (TYPE rr)
Treats * and Constraint as the same
kindRep :: HasDebugCallStack => Kind -> Type #
Extract the RuntimeRep classifier of a type from its kind. For example,
kindRep * = LiftedRep
; Panics if this is not possible.
Treats * and Constraint as the same
expandTypeSynonyms :: Type -> Type #
Expand out all type synonyms. Actually, it'd suffice to expand out just the ones that discard type variables (e.g. type Funny a = Int) But we don't know which those are currently, so we just expand all.
expandTypeSynonyms
only expands out type synonyms mentioned in the type,
not in the kinds of any TyCon or TyVar mentioned in the type.
Keep this synchronized with synonymTyConsOfType
data TyCoMapper env (m :: Type -> Type) #
This describes how a "map" operation over a type/coercion should behave
Constructors
TyCoMapper | |
Fields
|
cloneTyVarBndrs :: TCvSubst -> [TyVar] -> UniqSupply -> (TCvSubst, [TyVar]) #
substVarBndrs :: HasCallStack => TCvSubst -> [TyCoVar] -> (TCvSubst, [TyCoVar]) #
substVarBndr :: HasCallStack => TCvSubst -> TyCoVar -> (TCvSubst, TyCoVar) #
substTyVarBndrs :: HasCallStack => TCvSubst -> [TyVar] -> (TCvSubst, [TyVar]) #
substTyVarBndr :: HasCallStack => TCvSubst -> TyVar -> (TCvSubst, TyVar) #
substCoUnchecked :: TCvSubst -> Coercion -> Coercion #
Substitute within a Coercion
disabling sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substTyVars :: TCvSubst -> [TyVar] -> [Type] #
substTyVar :: TCvSubst -> TyVar -> Type #
substThetaUnchecked :: TCvSubst -> ThetaType -> ThetaType #
Substitute within a ThetaType
disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substThetaUnchecked to
substTheta and remove this function. Please don't use in new code.
substTheta :: HasCallStack => TCvSubst -> ThetaType -> ThetaType #
Substitute within a ThetaType
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTysUnchecked :: TCvSubst -> [Type] -> [Type] #
Substitute within several Type
s disabling the sanity checks.
The problems that the sanity checks in substTys catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTysUnchecked to
substTys and remove this function. Please don't use in new code.
substTys :: HasCallStack => TCvSubst -> [Type] -> [Type] #
Substitute within several Type
s
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTyUnchecked :: TCvSubst -> Type -> Type #
Substitute within a Type
disabling the sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substTy :: HasCallStack => TCvSubst -> Type -> Type #
Substitute within a Type
The substitution has to satisfy the invariants described in
Note [The substitution invariant].
substTyAddInScope :: TCvSubst -> Type -> Type #
Substitute within a Type
after adding the free variables of the type
to the in-scope set. This is useful for the case when the free variables
aren't already in the in-scope set or easily available.
See also Note [The substitution invariant].
substTysWith :: [TyVar] -> [Type] -> [Type] -> [Type] #
Type substitution, see zipTvSubst
substCoWithUnchecked :: [TyVar] -> [Type] -> Coercion -> Coercion #
Coercion substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substCo catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substCoUnchecked to
substCo and remove this function. Please don't use in new code.
substTyWithUnchecked :: [TyVar] -> [Type] -> Type -> Type #
Type substitution, see zipTvSubst
. Disables sanity checks.
The problems that the sanity checks in substTy catch are described in
Note [The substitution invariant].
The goal of #11371 is to migrate all the calls of substTyUnchecked to
substTy and remove this function. Please don't use in new code.
substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type #
Type substitution, see zipTvSubst
zipCoEnv :: HasDebugCallStack => [CoVar] -> [Coercion] -> CvSubstEnv #
zipTyEnv :: HasDebugCallStack => [TyVar] -> [Type] -> TvSubstEnv #
mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst #
Generates the in-scope set for the TCvSubst
from the types in the
incoming environment. No CoVars, please!
zipTCvSubst :: HasDebugCallStack => [TyCoVar] -> [Type] -> TCvSubst #
zipTvSubst :: HasDebugCallStack => [TyVar] -> [Type] -> TCvSubst #
Generates the in-scope set for the TCvSubst
from the types in the incoming
environment. No CoVars, please!
unionTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst #
extendTvSubstBinderAndInScope :: TCvSubst -> TyCoBinder -> Type -> TCvSubst #
extendTCvInScopeSet :: TCvSubst -> VarSet -> TCvSubst #
extendTCvInScopeList :: TCvSubst -> [Var] -> TCvSubst #
extendTCvInScope :: TCvSubst -> Var -> TCvSubst #
zapTCvSubst :: TCvSubst -> TCvSubst #
setTvSubstEnv :: TCvSubst -> TvSubstEnv -> TCvSubst #
notElemTCvSubst :: Var -> TCvSubst -> Bool #
getTCvSubstRangeFVs :: TCvSubst -> VarSet #
Returns the free variables of the types in the range of a substitution as a non-deterministic set.
getTCvInScope :: TCvSubst -> InScopeSet #
getTvSubstEnv :: TCvSubst -> TvSubstEnv #
mkTCvSubst :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> TCvSubst #
isEmptyTCvSubst :: TCvSubst -> Bool #
mkEmptyTCvSubst :: InScopeSet -> TCvSubst #
composeTCvSubst :: TCvSubst -> TCvSubst -> TCvSubst #
Composes two substitutions, applying the second one provided first, like in function composition.
composeTCvSubstEnv :: InScopeSet -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) -> (TvSubstEnv, CvSubstEnv) #
(compose env1 env2)(x)
is env1(env2(x))
; i.e. apply env2
then env1
.
It assumes that both are idempotent.
Typically, env1
is the refinement to a base substitution env2
Type & coercion substitution
The following invariants must hold of a TCvSubst
:
- The in-scope set is needed only to guide the generation of fresh uniques
- In particular, the kind of the type variables in the in-scope set is not relevant
- The substitution is only applied ONCE! This is because in general such application will not reach a fixed point.
Constructors
TCvSubst InScopeSet TvSubstEnv CvSubstEnv |
tidyTopType :: Type -> Type #
Calls tidyType
on a top-level type (i.e. with an empty tidying environment)
tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type]) #
Grabs the free type variables, tidies them
and then uses tidyType
to work over the type itself
tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar #
tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) #
Treat a new TyCoVar
as a binder, and give it a fresh tidy name
using the environment if one has not already been allocated. See
also tidyVarBndr
tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv #
Add the free TyVar
s to the env in tidy form,
so that we can tidy the type they are free in
tidyVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) #
This tidies up a type for printing in an error message, or in an interface file.
It doesn't change the uniques at all, just the print names.
tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar] #
Get the free vars of types in scoped order
tyCoVarsOfTypeWellScoped :: Type -> [TyVar] #
Get the free vars of a type in scoped order
scopedSort :: [TyCoVar] -> [TyCoVar] #
Do a topological sort on a list of tyvars, so that binders occur before occurrences E.g. given [ a::k, k::*, b::k ] it'll return a well-scoped list [ k::*, a::k, b::k ]
This is a deterministic sorting operation (that is, doesn't depend on Uniques).
It is also meant to be stable: that is, variables should not be reordered unnecessarily. This is specified in Note [ScopedSort] See also Note [Ordering of implicit variables] in RnTypes
noFreeVarsOfType :: Type -> Bool #
Returns True if this type has no free variables. Should be the same as isEmptyVarSet . tyCoVarsOfType, but faster in the non-forall case.
coVarsOfTypes :: [Type] -> TyCoVarSet #
coVarsOfType :: Type -> CoVarSet #
tyCoFVsVarBndr :: Var -> FV -> FV #
tyCoFVsVarBndrs :: [Var] -> FV -> FV #
tyCoFVsBndr :: TyCoVarBinder -> FV -> FV #
tyCoFVsOfType :: Type -> FV #
The worker for tyCoFVsOfType
and tyCoFVsOfTypeList
.
The previous implementation used unionVarSet
which is O(n+m) and can
make the function quadratic.
It's exported, so that it can be composed with
other functions that compute free variables.
See Note [FV naming conventions] in FV.
Eta-expanded because that makes it run faster (apparently) See Note [FV eta expansion] in FV for explanation.
tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet #
tyCoFVsOfType
that returns free variables of a type in a deterministic
set. For explanation of why using VarSet
is not deterministic see
Note [Deterministic FV] in FV.
tyCoVarsOfTypes :: [Type] -> TyCoVarSet #
tyCoVarsOfType :: Type -> TyCoVarSet #
The (->)
type constructor.
(->) :: forall (rep1 :: RuntimeRep) (rep2 :: RuntimeRep). TYPE rep1 -> TYPE rep2 -> *
Create the plain type constructor type which has been applied to no type arguments at all.
mkPiTys :: [TyCoBinder] -> Type -> Type #
mkPiTy :: TyCoBinder -> Type -> Type #
mkForAllTys :: [TyCoVarBinder] -> Type -> Type #
Wraps foralls over the type using the provided TyCoVar
s from left to right
mkInvisFunTys :: [Type] -> Type -> Type #
Make nested arrow types
mkInvisFunTy :: Type -> Type -> Type infixr 3 #
mkVisFunTy :: Type -> Type -> Type infixr 3 #
mkTyVarTys :: [TyVar] -> [Type] #
isNamedBinder :: TyCoBinder -> Bool #
isVisibleBinder :: TyCoBinder -> Bool #
Does this binder bind a visible argument?
isInvisibleBinder :: TyCoBinder -> Bool #
Does this binder bind an invisible argument?
type KindOrType = Type #
The key representation of types within the compiler
A type labeled KnotTied
might have knot-tied tycons in it. See
Note [Type checking recursive type and class declarations] in
TcTyClsDecls
isPredTy :: HasDebugCallStack => Type -> Bool #
isCoercionTy :: Type -> Bool #
mkCastTy :: Type -> Coercion -> Type #
Make a CastTy
. The Coercion must be nominal. Checks the
Coercion for reflexivity, dropping it if it's reflexive.
See Note [Respecting definitional equality] in TyCoRep
piResultTy :: HasDebugCallStack => Type -> Type -> Type #
eqType :: Type -> Type -> Bool #
Type equality on source types. Does not look through newtypes
or
PredType
s, but it does look through type synonyms.
This first checks that the kinds of the types are equal and then
checks whether the types are equal, ignoring casts and coercions.
(The kind check is a recursive call, but since all kinds have type
Type
, there is no need to check the types of kinds.)
See also Note [Non-trivial definitional equality] in TyCoRep.
coreView :: Type -> Maybe Type #
This function Strips off the top layer only of a type synonym
application (if any) its underlying representation type.
Returns Nothing if there is nothing to look through.
This function considers Constraint
to be a synonym of TYPE LiftedRep
.
By being non-recursive and inlined, this case analysis gets efficiently joined onto the case analysis that the caller is already doing
tcView :: Type -> Maybe Type #
Gives the typechecker view of a type. This unwraps synonyms but
leaves Constraint
alone. c.f. coreView, which turns Constraint into
TYPE LiftedRep. Returns Nothing if no unwrapping happens.
See also Note [coreView vs tcView]
isRuntimeRepTy :: Type -> Bool #
Is this the type RuntimeRep
?
isLiftedTypeKind :: Kind -> Bool #
This version considers Constraint to be the same as *. Returns True if the argument is equivalent to Type/Constraint and False otherwise. See Note [Kind Constraint and kind Type]
splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #
Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor
Is this a type-level (i.e., computationally irrelevant, thus erasable)
variable? Satisfies isTyVar = not . isId
.
mkTyVarBinders :: ArgFlag -> [TyVar] -> [TyVarBinder] #
Make many named binders Input vars should be type variables
mkTyCoVarBinders :: ArgFlag -> [TyCoVar] -> [TyCoVarBinder] #
Make many named binders
mkTyCoVarBinder :: ArgFlag -> TyCoVar -> TyCoVarBinder #
Make a named binder
binderType :: VarBndr TyCoVar argf -> Type #
binderArgFlag :: VarBndr tv argf -> argf #
binderVars :: [VarBndr tv argf] -> [tv] #
isInvisibleArgFlag :: ArgFlag -> Bool #
Does this ArgFlag
classify an argument that is not written in Haskell?
isVisibleArgFlag :: ArgFlag -> Bool #
Does this ArgFlag
classify an argument that is written in Haskell?
data ForallVisFlag #
Is a forall
invisible (e.g., forall a b. {...}
, with a dot) or visible
(e.g., forall a b -> {...}
, with an arrow)?
Constructors
ForallVis | A visible |
ForallInvis | An invisible |
Instances
type TyCoVarBinder = VarBndr TyCoVar ArgFlag #
Variable Binder
A TyCoVarBinder
is the binder of a ForAllTy
It's convenient to define this synonym here rather its natural
home in TyCoRep, because it's used in DataCon.hs-boot
A TyVarBinder
is a binder with only TyVar
type TyVarBinder = VarBndr TyVar ArgFlag #
liftedTypeKind :: Kind #
mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type #
Like mkTyCoForAllTy
, but does not check the occurrence of the binder
See Note [Unused coercion variable in ForAllTy]
Instances
Data Type | |
Defined in TyCoRep Methods 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 |
data TyCoBinder #
A TyCoBinder
represents an argument to a function. TyCoBinders can be
dependent (Named
) or nondependent (Anon
). They may also be visible or
not. See Note [TyCoBinders]
Instances
Data TyCoBinder | |
Defined in TyCoRep Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyCoBinder # toConstr :: TyCoBinder -> Constr # dataTypeOf :: TyCoBinder -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyCoBinder) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCoBinder) # gmapT :: (forall b. Data b => b -> b) -> TyCoBinder -> TyCoBinder # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r # gmapQ :: (forall d. Data d => d -> u) -> TyCoBinder -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder # | |
Outputable TyCoBinder | |
Defined in TyCoRep |
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"
Argument Flag
Is something required to appear in source Haskell (Required
),
permitted by request (Specified
) (visible type application), or
prohibited entirely from appearing in source Haskell (Inferred
)?
See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep
Instances
Eq ArgFlag | |
Data ArgFlag | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArgFlag -> c ArgFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArgFlag # toConstr :: ArgFlag -> Constr # dataTypeOf :: ArgFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArgFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgFlag) # gmapT :: (forall b. Data b => b -> b) -> ArgFlag -> ArgFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArgFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> ArgFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArgFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgFlag -> m ArgFlag # | |
Ord ArgFlag | |
Binary ArgFlag | |
Outputable ArgFlag | |
Outputable tv => Outputable (VarBndr tv ArgFlag) | |
data AnonArgFlag #
The non-dependent version of ArgFlag
.
Constructors
VisArg | Used for |
InvisArg | Used for |
Instances
Eq AnonArgFlag | |
Defined in Var | |
Data AnonArgFlag | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnonArgFlag -> c AnonArgFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnonArgFlag # toConstr :: AnonArgFlag -> Constr # dataTypeOf :: AnonArgFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnonArgFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnonArgFlag) # gmapT :: (forall b. Data b => b -> b) -> AnonArgFlag -> AnonArgFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnonArgFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnonArgFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> AnonArgFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnonArgFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnonArgFlag -> m AnonArgFlag # | |
Ord AnonArgFlag | |
Defined in Var Methods compare :: AnonArgFlag -> AnonArgFlag -> Ordering # (<) :: AnonArgFlag -> AnonArgFlag -> Bool # (<=) :: AnonArgFlag -> AnonArgFlag -> Bool # (>) :: AnonArgFlag -> AnonArgFlag -> Bool # (>=) :: AnonArgFlag -> AnonArgFlag -> Bool # max :: AnonArgFlag -> AnonArgFlag -> AnonArgFlag # min :: AnonArgFlag -> AnonArgFlag -> AnonArgFlag # | |
Binary AnonArgFlag | |
Defined in Var Methods put_ :: BinHandle -> AnonArgFlag -> IO () # put :: BinHandle -> AnonArgFlag -> IO (Bin AnonArgFlag) # get :: BinHandle -> IO AnonArgFlag # | |
Outputable AnonArgFlag | |
Defined in Var |
Variable
Essentially a typed Name
, that may also contain some additional information
about the Var
and its use sites.
Instances
Eq Var | |
Data Var | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var # dataTypeOf :: Var -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Var) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) # gmapT :: (forall b. Data b => b -> b) -> Var -> Var # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # | |
Ord Var | |
NamedThing Var | |
HasOccName Var | |
Uniquable Var | |
Outputable Var | |
ModifyState Id | |
Defined in Compat.HieAst Methods addSubstitution :: Id -> Id -> HieState -> HieState | |
Eq (DeBruijn CoreExpr) | |
Eq (DeBruijn CoreAlt) | |
ToHie (Context (Located Var)) | |
module Unify
module UniqFM
module UniqSupply
setTyVarUnique :: TyVar -> Unique -> TyVar #
setVarUnique :: Var -> Unique -> Var #
Variable
Essentially a typed Name
, that may also contain some additional information
about the Var
and its use sites.
Instances
Eq Var | |
Data Var | |
Defined in Var Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var # dataTypeOf :: Var -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Var) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) # gmapT :: (forall b. Data b => b -> b) -> Var -> Var # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # | |
Ord Var | |
NamedThing Var | |
HasOccName Var | |
Uniquable Var | |
Outputable Var | |
ModifyState Id | |
Defined in Compat.HieAst Methods addSubstitution :: Id -> Id -> HieState -> HieState | |
Eq (DeBruijn CoreExpr) | |
Eq (DeBruijn CoreAlt) | |
ToHie (Context (Located Var)) | |
Syntax re-exports
Haskell Module
All we actually declare here is the top-level structure for a module.
Constructors
HsModule | |
Fields
|
Instances
HasDecls ParsedSource | |
Defined in Language.Haskell.GHC.ExactPrint.Transform Methods hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] # replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource # | |
Data (HsModule GhcPs) | |
Defined in GHC.Hs Methods 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 Methods 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 Methods 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) # | |
Show (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans | |
NFData (HsModule a) Source # | |
Defined in Development.IDE.GHC.Orphans | |
NFData (Annotated ParsedSource) Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: Annotated ParsedSource -> () # | |
OutputableBndrId p => Outputable (HsModule (GhcPass p)) | |
Annotate (HsModule GhcPs) | |
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
Arguments
:: ([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
Constructors
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 Methods 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 |
data RecordConTc #
Extra data fields for a RecordCon
, added by the type checker
Constructors
RecordConTc | |
Fields |
data RecordUpdTc #
Extra data fields for a RecordUpd
, added by the type checker
Constructors
RecordUpdTc | |
Fields
|
Instances
Data RecordUpdTc | |
Defined in GHC.Hs.Expr Methods 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
Constructors
Present (XPresent id) (LHsExpr id) | The argument |
Missing (XMissing id) | The argument is missing, but this is its type |
XTupArg (XXTupArg id) | Note [Trees that Grow] extension point |
data HsArrAppType #
Haskell Array Application Type
Constructors
HsHigherOrderApp | |
HsFirstOrderApp |
Instances
Data HsArrAppType | |
Defined in GHC.Hs.Expr Methods 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
OutputableBndrId p => Outputable (HsCmdTop (GhcPass p)) | |
Annotate (HsCmdTop GhcPs) | |
(ToHie (LHsCmd a), Data (HsCmdTop a)) => ToHie (LHsCmdTop a) | |
Defined in Compat.HieAst |
type HsRecordBinds p = HsRecFields p (LHsExpr p) #
Haskell Record Bindings
data MatchGroupTc #
Constructors
MatchGroupTc | |
Fields
|
Instances
Data MatchGroupTc | |
Defined in GHC.Hs.Expr Methods 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
Constructors
Match | |
Fields
| |
XMatch (XXMatch p body) |
Instances
Annotate body => Annotate [Located (Match GhcPs (Located body))] | |
(OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) | |
Annotate body => Annotate (Match GhcPs (Located body)) | |
HasDecls (LMatch GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform | |
(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.
Constructors
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
Constructors
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) | |
ParStmt (XParStmt idL idR body) [ParStmtBlock idL idR] (HsExpr idR) (SyntaxExpr idR) | |
TransStmt | |
RecStmt | |
Fields
| |
XStmtLR (XXStmtLR idL idR body) |
Instances
Annotate [ExprLStmt GhcPs] | Used for declarations that need to be aligned together, e.g. in a do or let .. in statement/expr |
Annotate [Located (StmtLR GhcPs GhcPs (LHsCmd GhcPs))] | |
(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))) | |
Annotate body => Annotate (Stmt GhcPs (Located body)) | |
HasDecls (LStmt GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform | |
(OutputableBndrId pl, OutputableBndrId pr, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) | |
Constructors
RecStmtTc | |
Fields
|
Instances
Data TransForm | |
Defined in GHC.Hs.Expr Methods 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
Constructors
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 | |
Annotate (ParStmtBlock GhcPs GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater |
data ApplicativeArg idL #
Applicative Argument
Constructors
ApplicativeArgOne | |
Fields
| |
ApplicativeArgMany | |
Fields
| |
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 Methods 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.
Constructors
ThModFinalizers [ForeignRef (Q ())] |
Instances
Data ThModFinalizers | |
Defined in GHC.Hs.Expr Methods 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 Methods 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.
Constructors
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
Constructors
PendingRnSplice UntypedSpliceFlavour SplicePointName (LHsExpr GhcRn) |
Instances
Outputable PendingRnSplice | |
Defined in GHC.Hs.Expr | |
ToHie PendingRnSplice | |
Defined in Compat.HieAst Methods toHie :: PendingRnSplice -> HieM [HieAST Type] |
data UntypedSpliceFlavour #
Instances
Data UntypedSpliceFlavour | |
Defined in GHC.Hs.Expr Methods 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
Constructors
PendingTcSplice SplicePointName (LHsExpr GhcTc) |
Instances
Outputable PendingTcSplice | |
Defined in GHC.Hs.Expr | |
ToHie PendingTcSplice | |
Defined in Compat.HieAst Methods toHie :: PendingTcSplice -> HieM [HieAST Type] |
Haskell Bracket
data ArithSeqInfo id #
Arithmetic Sequence Information
Constructors
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 Methods 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].
Constructors
FunRhs | A pattern matching on an argument of a function binding |
Fields
| |
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 Methods fmap :: (a -> b) -> HsMatchContext a -> HsMatchContext b # (<$) :: a -> HsMatchContext b -> HsMatchContext a # | |
Data id => Data (HsMatchContext id) | |
Defined in GHC.Hs.Expr Methods 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 | |
ToHie (Context (Located a)) => ToHie (HsMatchContext a) | |
Defined in Compat.HieAst Methods toHie :: HsMatchContext a -> HieM [HieAST Type] |
data HsStmtContext id #
Haskell Statement Context. It expects to be parameterised with one of
RdrName
, Name
or Id
Constructors
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 Methods fmap :: (a -> b) -> HsStmtContext a -> HsStmtContext b # (<$) :: a -> HsStmtContext b -> HsStmtContext a # | |
Data id => Data (HsStmtContext id) | |
Defined in GHC.Hs.Expr Methods 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 Methods 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
Constructors
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) |
Instances
p ~ GhcPs => ASTElement AnnListItem (HsDecl p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
OutputableBndrId p => Outputable (HsDecl (GhcPass p)) | |
Annotate (HsDecl GhcPs) | |
Constructors
HsGroup | |
Fields
| |
XHsGroup (XXHsGroup p) |
type LSpliceDecl pass = Located (SpliceDecl pass) #
Located Splice Declaration
data SpliceDecl p #
Splice Declaration
Constructors
SpliceDecl (XSpliceDecl p) (Located (HsSplice p)) SpliceExplicitFlag | |
XSpliceDecl (XXSpliceDecl p) |
Instances
OutputableBndrId p => Outputable (SpliceDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (SpliceDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LSpliceDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type] |
A type or class declaration.
Constructors
FamDecl | type/data family T :: *->* |
Fields
| |
SynDecl |
|
DataDecl |
|
Fields
| |
ClassDecl | |
Fields
| |
XTyClDecl (XXTyClDecl pass) |
Instances
OutputableBndrId p => Outputable (TyClDecl (GhcPass p)) | |
Annotate (TyClDecl GhcPs) | |
ToHie (LTyClDecl GhcRn) | |
data DataDeclRn #
Constructors
DataDeclRn | |
Fields
|
Instances
Data DataDeclRn | |
Defined in GHC.Hs.Decls Methods 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
Constructors
TyClGroup | |
Fields
| |
XTyClGroup (XXTyClGroup pass) |
type LFamilyResultSig pass = Located (FamilyResultSig pass) #
Located type Family Result Signature
data FamilyResultSig pass #
type Family Result Signature
Constructors
NoSig (XNoSig pass) | |
KindSig (XCKindSig pass) (LHsKind pass) | |
TyVarSig (XTyVarSig pass) (LHsTyVarBndr pass) | |
XFamilyResultSig (XXFamilyResultSig pass) |
Instances
Annotate (FamilyResultSig GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (RScoped (LFamilyResultSig GhcRn)) | |
Defined in Compat.HieAst Methods toHie :: RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type] |
type LFamilyDecl pass = Located (FamilyDecl pass) #
Located type Family Declaration
data FamilyDecl pass #
type Family Declaration
Constructors
FamilyDecl | |
Fields
| |
XFamilyDecl (XXFamilyDecl pass) |
Instances
OutputableBndrId p => Outputable (FamilyDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (FamilyDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LFamilyDecl GhcRn) | |
Defined in Compat.HieAst Methods 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
]"
Constructors
InjectivityAnn (Located (IdP pass)) [Located (IdP pass)] |
Instances
Annotate (InjectivityAnn GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LInjectivityAnn GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type] |
data FamilyInfo pass #
Constructors
DataFamily | |
OpenTypeFamily | |
ClosedTypeFamily (Maybe [LTyFamInstEqn pass]) |
|
Instances
Outputable (FamilyInfo pass) | |
Defined in GHC.Hs.Decls | |
ToHie (FamilyInfo GhcRn) | |
Defined in Compat.HieAst Methods toHie :: FamilyInfo GhcRn -> HieM [HieAST Type] |
data HsDataDefn pass #
Haskell Data type Definition
Constructors
HsDataDefn | Declares a data type or newtype, giving its constructors
|
Fields
| |
XHsDataDefn (XXHsDataDefn pass) |
Instances
OutputableBndrId p => Outputable (HsDataDefn (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
HasLoc (HsDataDefn GhcRn) | |
Defined in Compat.HieAst Methods loc :: HsDataDefn GhcRn -> SrcSpan | |
ToHie (HsDataDefn GhcRn) | |
Defined in Compat.HieAst Methods toHie :: HsDataDefn GhcRn -> HieM [HieAST Type] |
type HsDeriving pass #
Arguments
= 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.
Constructors
HsDerivingClause | |
Fields
| |
XHsDerivingClause (XXHsDerivingClause pass) |
Instances
OutputableBndrId p => Outputable (HsDerivingClause (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate [LHsDerivingClause GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsDerivingClause GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (HsDeriving GhcRn) | |
Defined in Compat.HieAst Methods toHie :: HsDeriving GhcRn -> HieM [HieAST Type] | |
ToHie (LHsDerivingClause GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LHsDerivingClause GhcRn -> HieM [HieAST Type] |
type LStandaloneKindSig pass = Located (StandaloneKindSig pass) #
Located Standalone Kind Signature
data StandaloneKindSig pass #
Constructors
StandaloneKindSig (XStandaloneKindSig pass) (Located (IdP pass)) (LHsSigType pass) | |
XStandaloneKindSig (XXStandaloneKindSig pass) |
Instances
OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (StandaloneKindSig GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LStandaloneKindSig GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LStandaloneKindSig GhcRn -> HieM [HieAST Type] | |
ToHie (StandaloneKindSig GhcRn) | |
Defined in Compat.HieAst Methods toHie :: StandaloneKindSig GhcRn -> HieM [HieAST Type] |
Instances
Eq NewOrData | |
Data NewOrData | |
Defined in GHC.Hs.Decls Methods 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 | |
Arguments
= 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
Constructors
ConDeclGADT | |
Fields
| |
ConDeclH98 | |
Fields
| |
XConDecl (XXConDecl pass) |
Instances
OutputableBndrId p => Outputable (ConDecl (GhcPass p)) | |
Annotate (ConDecl GhcPs) | |
ToHie (LConDecl GhcRn) | |
type HsConDeclDetails pass = HsConDetails (LBangType pass) (Located [LConDeclField pass]) #
Haskell data Constructor Declaration Details
type LTyFamInstEqn pass #
Arguments
= 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
Constructors
TyFamInstDecl | |
Fields
|
Instances
OutputableBndrId p => Outputable (TyFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (TyFamInstDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LTyFamInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type] |
type LDataFamInstDecl pass = Located (DataFamInstDecl pass) #
Located Data Family Instance Declaration
newtype DataFamInstDecl pass #
Data Family Instance Declaration
Constructors
DataFamInstDecl | |
Fields
|
Instances
OutputableBndrId p => Outputable (DataFamInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (DataFamInstDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LDataFamInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type] |
type LFamInstEqn pass rhs = Located (FamInstEqn pass rhs) #
Located Family Instance Equation
type FamInstEqn pass rhs #
Arguments
= 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]
Constructors
FamEqn | |
Fields
| |
XFamEqn (XXFamEqn pass rhs) |
Instances
Annotate (TyFamInstEqn GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
(ToHie rhs, HasLoc rhs) => ToHie (TScoped (FamEqn GhcRn rhs)) | |
HasLoc a => HasLoc (FamEqn s a) | |
Defined in Compat.HieAst | |
(ToHie rhs, HasLoc rhs) => ToHie (FamEqn GhcRn rhs) | |
type LClsInstDecl pass = Located (ClsInstDecl pass) #
Located Class Instance Declaration
data ClsInstDecl pass #
Class Instance Declaration
Constructors
ClsInstDecl | |
Fields
| |
XClsInstDecl (XXClsInstDecl pass) |
Instances
OutputableBndrId p => Outputable (ClsInstDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (ClsInstDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LClsInstDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type] |
Instance Declaration
Constructors
ClsInstD | |
Fields
| |
DataFamInstD | |
Fields
| |
TyFamInstD | |
Fields
| |
XInstDecl (XXInstDecl pass) |
Instances
OutputableBndrId p => Outputable (InstDecl (GhcPass p)) | |
Annotate (InstDecl GhcPs) | |
ToHie (LInstDecl GhcRn) | |
type LDerivDecl pass = Located (DerivDecl pass) #
Located stand-alone 'deriving instance' declaration
Stand-alone 'deriving instance' declaration
Constructors
DerivDecl | |
Fields
| |
XDerivDecl (XXDerivDecl pass) |
Instances
OutputableBndrId p => Outputable (DerivDecl (GhcPass p)) | |
Annotate (DerivDecl GhcPs) | |
ToHie (LDerivDecl GhcRn) | |
Defined in Compat.HieAst Methods 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.
Constructors
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 | |
Annotate (DerivStrategy GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (Located (DerivStrategy GhcRn)) | |
Defined in Compat.HieAst |
type LDefaultDecl pass = Located (DefaultDecl pass) #
Located Default Declaration
data DefaultDecl pass #
Default Declaration
Constructors
DefaultDecl (XCDefaultDecl pass) [LHsType pass] | |
XDefaultDecl (XXDefaultDecl pass) |
Instances
OutputableBndrId p => Outputable (DefaultDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (DefaultDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LDefaultDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type] |
type LForeignDecl pass = Located (ForeignDecl pass) #
Located Foreign Declaration
data ForeignDecl pass #
Foreign Declaration
Constructors
ForeignImport | |
Fields
| |
ForeignExport | |
Fields
| |
XForeignDecl (XXForeignDecl pass) |
Instances
OutputableBndrId p => Outputable (ForeignDecl (GhcPass p)) | |
Defined in GHC.Hs.Decls | |
Annotate (ForeignDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LForeignDecl GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LForeignDecl GhcRn -> HieM [HieAST Type] |
data ForeignImport #
Constructors
CImport (Located CCallConv) (Located Safety) (Maybe Header) CImportSpec (Located SourceText) |
Instances
Data ForeignImport | |
Defined in GHC.Hs.Decls Methods 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 | |
ToHie ForeignImport | |
Defined in Compat.HieAst Methods toHie :: ForeignImport -> HieM [HieAST Type] |
data CImportSpec #
Constructors
CLabel CLabelString | |
CFunction CCallTarget | |
CWrapper |
Instances
Data CImportSpec | |
Defined in GHC.Hs.Decls Methods 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 #
Constructors
CExport (Located CExportSpec) (Located SourceText) |
Instances
Data ForeignExport | |
Defined in GHC.Hs.Decls Methods 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 | |
ToHie ForeignExport | |
Defined in Compat.HieAst Methods toHie :: ForeignExport -> HieM [HieAST Type] |
type LRuleDecls pass = Located (RuleDecls pass) #
Located Rule Declarations
Rule Declarations
Constructors
HsRules | |
Fields
| |
XRuleDecls (XXRuleDecls pass) |
Instances
OutputableBndrId p => Outputable (RuleDecls (GhcPass p)) | |
Annotate (RuleDecls GhcPs) | |
ToHie (LRuleDecls GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LRuleDecls GhcRn -> HieM [HieAST Type] |
Rule Declaration
Constructors
HsRule | |
Fields
| |
XRuleDecl (XXRuleDecl pass) |
Instances
OutputableBndrId p => Outputable (RuleDecl (GhcPass p)) | |
Annotate (RuleDecl GhcPs) | |
ToHie (LRuleDecl GhcRn) | |
Instances
Data HsRuleRn | |
Defined in GHC.Hs.Decls Methods 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
Constructors
RuleBndr (XCRuleBndr pass) (Located (IdP pass)) | |
RuleBndrSig (XRuleBndrSig pass) (Located (IdP pass)) (LHsSigWcType pass) | |
XRuleBndr (XXRuleBndr pass) |
Instances
OutputableBndrId p => Outputable (RuleBndr (GhcPass p)) | |
Annotate (RuleBndr GhcPs) | |
ToHie (RScoped (LRuleBndr GhcRn)) | |
Documentation comment Declaration
Constructors
DocCommentNext HsDocString | |
DocCommentPrev HsDocString | |
DocCommentNamed String HsDocString | |
DocGroup Int HsDocString |
Instances
Data DocDecl | |
Defined in GHC.Hs.Decls Methods 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 | |
Annotate DocDecl | |
type LWarnDecls pass = Located (WarnDecls pass) #
Located Warning Declarations
Warning pragma Declarations
Constructors
Warnings | |
Fields
| |
XWarnDecls (XXWarnDecls pass) |
Instances
OutputableBndr (IdP (GhcPass p)) => Outputable (WarnDecls (GhcPass p)) | |
Annotate (WarnDecls GhcPs) | |
ToHie (LWarnDecls GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LWarnDecls GhcRn -> HieM [HieAST Type] |
Warning pragma Declaration
Constructors
Warning (XWarning pass) [Located (IdP pass)] WarningTxt | |
XWarnDecl (XXWarnDecl pass) |
Annotation Declaration
Constructors
HsAnnotation (XHsAnnotation pass) SourceText (AnnProvenance (IdP pass)) (Located (HsExpr pass)) | |
XAnnDecl (XXAnnDecl pass) |
Instances
OutputableBndrId p => Outputable (AnnDecl (GhcPass p)) | |
Annotate (AnnDecl GhcPs) | |
ToHie (LAnnDecl GhcRn) | |
data AnnProvenance name #
Annotation Provenance
Constructors
ValueAnnProvenance (Located name) | |
TypeAnnProvenance (Located name) | |
ModuleAnnProvenance |
Instances
Functor AnnProvenance | |
Defined in GHC.Hs.Decls Methods fmap :: (a -> b) -> AnnProvenance a -> AnnProvenance b # (<$) :: a -> AnnProvenance b -> AnnProvenance a # | |
Foldable AnnProvenance | |
Defined in GHC.Hs.Decls Methods 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 Methods 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 Methods 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 Methods toHie :: AnnProvenance a -> HieM [HieAST Type] |
type LRoleAnnotDecl pass = Located (RoleAnnotDecl pass) #
Located Role Annotation Declaration
data RoleAnnotDecl pass #
Role Annotation Declaration
Constructors
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 | |
Annotate (RoleAnnotDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LRoleAnnotDecl GhcRn) | |
Defined in Compat.HieAst Methods 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)
Constructors
HsRecFields | |
Fields
|
Instances
Functor (HsRecFields p) | |
Defined in GHC.Hs.Pat Methods fmap :: (a -> b) -> HsRecFields p a -> HsRecFields p b # (<$) :: a -> HsRecFields p b -> HsRecFields p a # | |
Foldable (HsRecFields p) | |
Defined in GHC.Hs.Pat Methods 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 Methods 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 Methods toHie :: RContext (HsRecFields a arg) -> HieM [HieAST Type] | |
Outputable arg => Outputable (HsRecFields p arg) | |
Defined in GHC.Hs.Pat |
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
Constructors
HsRecField | |
Fields
|
Instances
Functor (HsRecField' id) | |
Defined in GHC.Hs.Pat Methods fmap :: (a -> b) -> HsRecField' id a -> HsRecField' id b # (<$) :: a -> HsRecField' id b -> HsRecField' id a # | |
Foldable (HsRecField' id) | |
Defined in GHC.Hs.Pat Methods 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 Methods 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) # | |
Annotate (HsRecUpdField GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data label, Data arg) => ToHie (RContext (LHsRecField' label arg)) | |
Defined in Compat.HieAst Methods toHie :: RContext (LHsRecField' label arg) -> HieM [HieAST Type] | |
(Data id, Data arg) => Data (HsRecField' id arg) | |
Defined in GHC.Hs.Pat Methods 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 | |
Annotate (HsRecField GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsRecField GhcPs (Located (Pat GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater |
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
Constructors
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
Annotate (HsLocalBinds GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
(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 Methods 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
Constructors
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 Methods 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 Methods toHie :: RScoped (NHsValBindsLR GhcRn) -> HieM [HieAST Type] | |
ToHie (RScoped (NHsValBindsLR GhcTc)) | |
Defined in Compat.HieAst Methods 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
Constructors
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 |
Fields
| |
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 |
Fields
| |
PatSynBind (XPatSynBind idL idR) (PatSynBind idL idR) |
|
XHsBindsLR (XXHsBindsLR idL idR) |
Instances
Annotate (HsBind GhcPs) | |
HasType (LHsBind GhcRn) | |
Defined in Compat.HieAst Methods getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type] | |
HasType (LHsBind GhcTc) | |
Defined in Compat.HieAst Methods 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 #
Constructors
NPatBindTc | |
Fields
|
Instances
Data NPatBindTc | |
Defined in GHC.Hs.Binds Methods 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
Constructors
ABE | |
XABExport (XXABExport p) |
data PatSynBind idL idR #
AnnKeywordId
:AnnPattern
,AnnEqual
,AnnLarrow
AnnWhere
,AnnOpen
'{'
,AnnClose
'}'
,
Pattern Synonym binding
Constructors
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 Methods 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
Constructors
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.
Constructors
IPBind (XCIPBind id) (Either (Located HsIPName) (IdP id)) (LHsExpr id) | |
XIPBind (XXIPBind id) |
Instances
OutputableBndrId p => Outputable (IPBind (GhcPass p)) | |
Annotate (IPBind GhcPs) | |
Signatures and pragmas
Constructors
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) |
type LFixitySig pass = Located (FixitySig pass) #
Located Fixity Signature
Fixity Signature
Constructors
FixitySig (XFixitySig pass) [Located (IdP pass)] Fixity | |
XFixitySig (XXFixitySig pass) |
Instances
OutputableBndrId p => Outputable (FixitySig (GhcPass p)) | |
ToHie (LFixitySig GhcRn) | |
Defined in Compat.HieAst Methods toHie :: LFixitySig GhcRn -> HieM [HieAST Type] |
data TcSpecPrags #
Type checker Specialisation Pragmas
TcSpecPrags
conveys SPECIALISE
pragmas from the type checker to the desugarer
Constructors
IsDefaultMethod | Super-specialised: a default method should be macro-expanded at every call site |
SpecPrags [LTcSpecPrag] |
Instances
Data TcSpecPrags | |
Defined in GHC.Hs.Binds Methods 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
Constructors
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 Methods 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 |
type HsPatSynDetails arg = HsConDetails arg [RecordPatSynField arg] #
Haskell Pattern Synonym Details
data RecordPatSynField a #
Record Pattern Synonym Field
Constructors
RecordPatSynField | |
Fields
|
Instances
data HsPatSynDir id #
Haskell Pattern Synonym Direction
Constructors
Unidirectional | |
ImplicitBidirectional | |
ExplicitBidirectional (MatchGroup id (LHsExpr id)) |
Instances
ToHie (MatchGroup a (LHsExpr a)) => ToHie (HsPatSynDir a) | |
Defined in Compat.HieAst Methods toHie :: HsPatSynDir a -> HieM [HieAST Type] |
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 #
Arguments
= Located (HsContext pass) |
|
Located Haskell Context
Arguments
= 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
Constructors
HsQTvs | |
Fields
| |
XLHsQTyVars (XXLHsQTyVars pass) |
Instances
OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) | |
Defined in GHC.Hs.Types | |
HasLoc (LHsQTyVars GhcRn) | |
Defined in Compat.HieAst Methods loc :: LHsQTyVars GhcRn -> SrcSpan | |
ToHie (TScoped (LHsQTyVars GhcRn)) | |
Defined in Compat.HieAst Methods toHie :: TScoped (LHsQTyVars GhcRn) -> HieM [HieAST Type] |
data HsImplicitBndrs pass thing #
Haskell Implicit Binders
Constructors
HsIB | |
XHsImplicitBndrs (XXHsImplicitBndrs pass thing) |
Instances
Annotate [LHsSigType GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (TyFamInstEqn GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
(HasLoc thing, ToHie (TScoped thing)) => ToHie (TScoped (HsImplicitBndrs GhcRn thing)) | |
Defined in Compat.HieAst Methods toHie :: TScoped (HsImplicitBndrs GhcRn thing) -> HieM [HieAST Type] | |
ToHie (TScoped (LHsSigWcType GhcTc)) | Dummy instances - never called |
Defined in Compat.HieAst Methods toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] | |
Outputable thing => Outputable (HsImplicitBndrs (GhcPass p) thing) | |
Defined in GHC.Hs.Types | |
Annotate arg => Annotate (HsImplicitBndrs GhcPs (Located arg)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
HasLoc thing => HasLoc (HsImplicitBndrs a thing) | |
Defined in Compat.HieAst Methods loc :: HsImplicitBndrs a thing -> SrcSpan |
data HsWildCardBndrs pass thing #
Haskell Wildcard Binders
Constructors
HsWC | |
XHsWildCardBndrs (XXHsWildCardBndrs pass thing) |
Instances
(HasLoc thing, ToHie (TScoped thing)) => ToHie (TScoped (HsWildCardBndrs GhcRn thing)) | |
Defined in Compat.HieAst Methods toHie :: TScoped (HsWildCardBndrs GhcRn thing) -> HieM [HieAST Type] | |
ToHie (TScoped (LHsWcType GhcTc)) | |
ToHie (TScoped (LHsSigWcType GhcTc)) | Dummy instances - never called |
Defined in Compat.HieAst Methods 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 Methods 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.
Constructors
HsIPName FastString |
Instances
Eq HsIPName | |
Data HsIPName | |
Defined in GHC.Hs.Types Methods 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 Methods pprBndr :: BindingSite -> HsIPName -> SDoc # pprPrefixOcc :: HsIPName -> SDoc # pprInfixOcc :: HsIPName -> SDoc # bndrIsJoin_maybe :: HsIPName -> Maybe Int # | |
Annotate HsIPName | |
ToHie (Located HsIPName) | |
data HsTyVarBndr pass #
Haskell Type Variable Binder
Constructors
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 | |
OutputableBndrId p => Outputable (HsTyVarBndr (GhcPass p)) | |
Defined in GHC.Hs.Types | |
Annotate (HsTyVarBndr GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (TVScoped (LHsTyVarBndr GhcRn)) | |
Defined in Compat.HieAst Methods toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type] |
Haskell Type
Constructors
Instances
p ~ GhcPs => ASTElement AnnListItem (HsType p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
OutputableBndrId p => Outputable (HsType (GhcPass p)) | |
Annotate [LHsType GhcPs] | |
Annotate [LHsSigType GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (TyFamInstEqn GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsType GhcPs) | |
ToHie (LHsContext GhcRn) | |
Defined in Compat.HieAst Methods 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 Methods toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type] |
data NewHsTypeX #
Instances
Data NewHsTypeX |
|
Defined in GHC.Hs.Types Methods 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 |
Haskell Type Literal
Constructors
HsNumTy SourceText Integer | |
HsStrTy SourceText FastString |
Instances
Data HsTyLit | |
Defined in GHC.Hs.Types Methods 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 Methods 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 #
Arguments
= Located (ConDeclField pass) | May have |
Located Constructor Declaration Field
data ConDeclField pass #
Constructor Declaration Field
Constructors
ConDeclField | |
Fields
| |
XConDeclField (XXConDeclField pass) |
Instances
OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) | |
Defined in GHC.Hs.Types | |
Annotate [LConDeclField GhcPs] | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (ConDeclField GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LConDeclField GhcRn) | |
Defined in Compat.HieAst Methods 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 Methods 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 | |
(ToHie arg, ToHie rec) => ToHie (HsConDetails arg rec) | |
Defined in Compat.HieAst Methods 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.
Constructors
FieldOcc | |
Fields
| |
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 Methods 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) | |
Annotate (FieldOcc GhcPs) | |
ToHie (RFContext (LFieldOcc GhcRn)) | |
ToHie (RFContext (LFieldOcc GhcTc)) | |
Annotate (HsRecField GhcPs (LHsExpr GhcPs)) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (HsRecField GhcPs (Located (Pat GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater |
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
Constructors
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 Methods pprBndr :: BindingSite -> AmbiguousFieldOcc (GhcPass p) -> SDoc # pprPrefixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc # pprInfixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc # bndrIsJoin_maybe :: AmbiguousFieldOcc (GhcPass p) -> Maybe Int # | |
Annotate (HsRecUpdField GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
Annotate (AmbiguousFieldOcc GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) | |
Defined in Compat.HieAst | |
ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) | |
Defined in Compat.HieAst |
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)
Constructors
HsSrcBang SourceText SrcUnpackedness SrcStrictness |
Instances
Data HsSrcBang | |
Defined in DataCon Methods 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.
Constructors
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 Methods 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 |
data SrcStrictness #
Source Strictness
What strictness annotation the user wrote
Constructors
SrcLazy | Lazy, ie '~' |
SrcStrict | Strict, ie |
NoSrcStrict | no strictness annotation |
Instances
Eq SrcStrictness | |
Defined in DataCon Methods (==) :: SrcStrictness -> SrcStrictness -> Bool # (/=) :: SrcStrictness -> SrcStrictness -> Bool # | |
Data SrcStrictness | |
Defined in DataCon Methods 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 Methods put_ :: BinHandle -> SrcStrictness -> IO () # put :: BinHandle -> SrcStrictness -> IO (Bin SrcStrictness) # get :: BinHandle -> IO SrcStrictness # | |
Outputable SrcStrictness | |
Defined in DataCon |
data SrcUnpackedness #
Source Unpackedness
What unpackedness the user requested
Constructors
SrcUnpack | |
SrcNoUnpack | |
NoSrcUnpack | no unpack pragma |
Instances
Eq SrcUnpackedness | |
Defined in DataCon Methods (==) :: SrcUnpackedness -> SrcUnpackedness -> Bool # (/=) :: SrcUnpackedness -> SrcUnpackedness -> Bool # | |
Data SrcUnpackedness | |
Defined in DataCon Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcUnpackedness # toConstr :: SrcUnpackedness -> Constr # dataTypeOf :: SrcUnpackedness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcUnpackedness) # gmapT :: (forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcUnpackedness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness # | |
Binary SrcUnpackedness | |
Defined in DataCon Methods put_ :: BinHandle -> SrcUnpackedness -> IO () # put :: BinHandle -> SrcUnpackedness -> IO (Bin SrcUnpackedness) # get :: BinHandle -> IO SrcUnpackedness # | |
Outputable SrcUnpackedness | |
Defined in DataCon |
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
Constructors
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
Constructors
OverLit | |
Fields
| |
XOverLit (XXOverLit p) |
Instances
Eq (XXOverLit p) => Eq (HsOverLit p) | |
Ord (XXOverLit p) => Ord (HsOverLit p) | |
Defined in GHC.Hs.Lit | |
OutputableBndrId p => Outputable (HsOverLit (GhcPass p)) | |
Annotate (HsOverLit GhcPs) | |
Constructors
OverLitTc | |
Fields
|
Instances
Data OverLitTc | |
Defined in GHC.Hs.Lit Methods 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
Constructors
HsIntegral !IntegralLit | Integer-looking literals; |
HsFractional !FractionalLit | Frac-looking literals |
HsIsString !SourceText !FastString | String-looking literals |
Instances
Eq OverLitVal | |
Defined in GHC.Hs.Lit | |
Data OverLitVal | |
Defined in GHC.Hs.Lit Methods 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 Methods 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 |
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.
Constructors
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 |
HsDo (XDo p) (HsStmtContext Name) (Located [ExprLStmt p]) | |
ExplicitList (XExplicitList p) (Maybe (SyntaxExpr p)) [LHsExpr p] | Syntactic list: [a,b,c,...]
|
RecordCon | Record construction
|
Fields
| |
RecordUpd | Record update
|
Fields
| |
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
Haskell Command (e.g. a "statement" in an Arrow proc block)
Constructors
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
Constructors
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 #
Constructors
MG | |
XMatchGroup (XXMatchGroup p body) |
Instances
ToHie (LMatch a body) => ToHie (MatchGroup a body) | |
Defined in Compat.HieAst Methods toHie :: MatchGroup a body -> HieM [HieAST Type] |
Guarded Right-Hand Sides
GRHSs are used both for pattern bindings and for Matches
Constructors
GRHSs | |
Fields
| |
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.)
Constructors
SyntaxExpr | |
Fields
|
Instances
OutputableBndrId p => Outputable (SyntaxExpr (GhcPass p)) | |
Defined in GHC.Hs.Expr |
Arguments
= 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 #
Arguments
= Located (ImportDecl pass) | When in a list this may have |
Located Import Declaration
data ImportDeclQualifiedStyle #
If/how an import is qualified
.
Constructors
QualifiedPre |
|
QualifiedPost |
|
NotQualified | Not qualified. |
Instances
data ImportDecl pass #
Import Declaration
A single Haskell import
declaration.
Constructors
ImportDecl | |
Fields
| |
XImportDecl (XXImportDecl pass) |
Instances
p ~ GhcPs => ASTElement AnnListItem (ImportDecl p) Source # | |
Defined in Development.IDE.GHC.ExactPrint Methods parseAST :: Parser (LocatedAn AnnListItem (ImportDecl p)) Source # maybeParensAST :: LocatedAn AnnListItem (ImportDecl p) -> LocatedAn AnnListItem (ImportDecl p) Source # graft :: Data a => SrcSpan -> LocatedAn AnnListItem (ImportDecl p) -> Graft (Either String) a Source # | |
NFData (ImportDecl GhcPs) Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: ImportDecl GhcPs -> () # | |
OutputableBndrId p => Outputable (ImportDecl (GhcPass p)) | |
Defined in GHC.Hs.ImpExp | |
Annotate (ImportDecl GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (LImportDecl GhcRn) | |
Defined in Compat.HieAst Methods 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.
Constructors
IEName (Located name) | no extra |
IEPattern (Located name) | pattern X |
IEType (Located name) | type (:+:) |
Instances
Eq name => Eq (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods (==) :: IEWrappedName name -> IEWrappedName name -> Bool # (/=) :: IEWrappedName name -> IEWrappedName name -> Bool # | |
Data name => Data (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods 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 Methods occName :: IEWrappedName name -> OccName # | |
OutputableBndr name => Outputable (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp | |
OutputableBndr name => OutputableBndr (IEWrappedName name) | |
Defined in GHC.Hs.ImpExp Methods pprBndr :: BindingSite -> IEWrappedName name -> SDoc # pprPrefixOcc :: IEWrappedName name -> SDoc # pprInfixOcc :: IEWrappedName name -> SDoc # bndrIsJoin_maybe :: IEWrappedName name -> Maybe Int # | |
Annotate (IEWrappedName RdrName) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater | |
ToHie (IEContext (LIEWrappedName Name)) | |
Defined in Compat.HieAst Methods 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.
Constructors
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
Constructors
NoIEWildcard | |
IEWildcard Int |
Instances
Eq IEWildcard | |
Defined in GHC.Hs.ImpExp | |
Data IEWildcard | |
Defined in GHC.Hs.ImpExp Methods 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
Constructors
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
p ~ GhcPs => ASTElement AnnListItem (Pat p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
OutputableBndrId p => Outputable (Pat (GhcPass p)) | |
Annotate (Pat GhcPs) | |
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)))) | |
Annotate (HsRecField GhcPs (Located (Pat GhcPs))) | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater |
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.
Constructors
NoExtField |
Instances
Eq NoExtField | |
Defined in GHC.Hs.Extension | |
Data NoExtField | |
Defined in GHC.Hs.Extension Methods 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 Methods 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 | |
ToHie (TScoped NoExtField) | |
Defined in Compat.HieAst Methods toHie :: TScoped NoExtField -> HieM [HieAST Type] | |
ToHie (Context (Located NoExtField)) | |
Defined in Compat.HieAst Methods 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 Methods 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
Constructors
Parsed | |
Renamed | |
Typechecked |
Instances
Data Pass | |
Defined in GHC.Hs.Extension Methods 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.
Equations
NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass) | |
NoGhcTc other = other |
type family NoGhcTcPass (p :: Pass) :: Pass where ... #
Equations
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
Equations
NameOrRdrName Id = Name | |
NameOrRdrName Name = Name | |
NameOrRdrName RdrName = RdrName |
data ForallVisFlag #
Is a forall
invisible (e.g., forall a b. {...}
, with a dot) or visible
(e.g., forall a b -> {...}
, with an arrow)?
Constructors
ForallVis | A visible |
ForallInvis | An invisible |
Instances
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
Eq HsDocString | |
Defined in GHC.Hs.Doc | |
Data HsDocString | |
Defined in GHC.Hs.Doc Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDocString -> c HsDocString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsDocString # toConstr :: HsDocString -> Constr # dataTypeOf :: HsDocString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsDocString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsDocString) # gmapT :: (forall b. Data b => b -> b) -> HsDocString -> HsDocString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDocString -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDocString -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDocString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDocString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDocString -> m HsDocString # | |
Show HsDocString | |
Defined in GHC.Hs.Doc Methods showsPrec :: Int -> HsDocString -> ShowS # show :: HsDocString -> String # showList :: [HsDocString] -> ShowS # | |
NFData HsDocString Source # | |
Defined in Development.IDE.GHC.Orphans Methods rnf :: HsDocString -> () # | |
Binary HsDocString | |
Defined in GHC.Hs.Doc Methods put_ :: BinHandle -> HsDocString -> IO () # put :: BinHandle -> HsDocString -> IO (Bin HsDocString) # get :: BinHandle -> IO HsDocString # | |
Outputable HsDocString | |
Defined in GHC.Hs.Doc | |
Annotate HsDocString | |
Defined in Language.Haskell.GHC.ExactPrint.Annotater Methods markAST :: SrcSpan -> HsDocString -> Annotated () # |
type LHsDocString = Located HsDocString #
Located Haskell Documentation String
newtype DeclDocMap #
Docs for declarations: functions, data types, instances, methods etc.
Constructors
DeclDocMap (Map Name HsDocString) |
Instances
Binary DeclDocMap | |
Defined in GHC.Hs.Doc Methods put_ :: BinHandle -> DeclDocMap -> IO () # put :: BinHandle -> DeclDocMap -> IO (Bin DeclDocMap) # get :: BinHandle -> IO DeclDocMap # | |
Outputable DeclDocMap | |
Defined in GHC.Hs.Doc |
Docs for arguments. E.g. function arguments, method arguments.
Instances
Instances
Eq Fixity | |
Data Fixity | |
Defined in BasicTypes Methods 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 SpliceExplicitFlag #
Constructors
ExplicitSplice | = $(f x y) |
ImplicitSplice | = f x y, i.e. a naked top level expression |
Instances
Data SpliceExplicitFlag | |
Defined in BasicTypes Methods 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 # |
module ExtractDocs
module Parser
module Lexer