ghcide-1.4.2.1: The core of an IDE
Safe HaskellNone
LanguageHaskell2010

Development.IDE.GHC.Compat.Core

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

Session

data DynFlags #

Contains not only a collection of GeneralFlags but also a plethora of information relating to the compilation of a single file or GHC session

packageFlags :: DynFlags -> [PackageFlag] #

The -package and -hide-package flags from the command-line. In *reverse* order that they're specified on the command line.

flagsForCompletion :: Bool -> [String] #

Make a list of flags for shell completion. Filter all available flags into two groups, for interactive GHC vs all other.

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.

settings :: DynFlags -> Settings #

"unbuild" a Settings from a DynFlags. This shouldn't be needed in the vast majority of code. But GHCi questionably uses this to produce a default DynFlags from which to compute a flags diff for printing.

gopt :: GeneralFlag -> DynFlags -> Bool #

Test whether a GeneralFlag is set

wopt :: WarningFlag -> DynFlags -> Bool #

Test whether a WarningFlag is set

xFlags :: [FlagSpec Extension] #

These -Xblah flags can all be reversed with -XNoblah

xopt :: Extension -> DynFlags -> Bool #

Test whether a Extension is set

data FlagSpec flag #

Constructors

FlagSpec 

Fields

data WarningFlag #

Constructors

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 #

Enumerates the simple on-or-off dynamic flags

Constructors

Opt_DumpToFile

Append dump output to files instead of stdout.

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

Use the cfg based block layout algorithm.

Opt_WeightlessBlocklayout

Layout based on last instruction per block.

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
-fPIC
Opt_PIE
-fPIE
Opt_PICExecutable
-pie
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

Suppress timestamps in dumps

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 #

Flags for manipulating packages visibility.

Instances

Instances details
Eq PackageFlag 
Instance details

Defined in DynFlags

Show PackageFlag Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Outputable PackageFlag 
Instance details

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

-package, by PackageName

UnitIdArg UnitId

-package-id, by UnitId

Instances

Instances details
Eq PackageArg 
Instance details

Defined in DynFlags

Show PackageArg 
Instance details

Defined in DynFlags

Outputable PackageArg 
Instance details

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:

  • -package foo is ModRenaming True []
  • -package foo () is ModRenaming False []
  • -package foo (A) is ModRenaming False [(A, A)]
  • -package foo (A as B) is ModRenaming False [(A, B)]
  • -package foo with (A as B) is ModRenaming True [(A, B)]

Constructors

ModRenaming 

Fields

Instances

Instances details
Eq ModRenaming 
Instance details

Defined in DynFlags

Outputable ModRenaming 
Instance details

Defined in DynFlags

parseDynamicFlagsCmdLine #

Arguments

:: MonadIO m 
=> DynFlags 
-> [Located String] 
-> m (DynFlags, [Located String], [Warn])

Updated DynFlags, left-over arguments, and list of warnings.

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).

parseDynamicFilePragma #

Arguments

:: MonadIO m 
=> DynFlags 
-> [Located String] 
-> m (DynFlags, [Located String], [Warn])

Updated DynFlags, left-over arguments, and list of warnings.

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

Instances details
Show WarnReason 
Instance details

Defined in DynFlags

ToJson WarnReason 
Instance details

Defined in DynFlags

Methods

json :: WarnReason -> JsonDoc #

Outputable WarnReason 
Instance details

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

Linear Haskell

type Scaled a = a Source #

Interface Files

type IfaceExport = AvailInfo #

The original names declared of a certain module that are exported

data IfaceTyCon #

Instances

Instances details
Eq IfaceTyCon 
Instance details

Defined in IfaceType

NFData IfaceTyCon 
Instance details

Defined in IfaceType

Methods

rnf :: IfaceTyCon -> () #

Binary IfaceTyCon 
Instance details

Defined in IfaceType

Outputable IfaceTyCon 
Instance details

Defined in IfaceType

type ModIface = ModIface_ 'ModIfaceFinal #

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

  • mi_module :: !Module

    Name of the module we are for

  • mi_sig_of :: !(Maybe Module)

    Are we a sig of another mod?

  • mi_hsc_src :: !HscSource

    Boot? Signature?

  • mi_deps :: Dependencies

    The dependencies of the module. This is consulted for directly-imported modules, but not for anything else (hence lazy)

  • mi_usages :: [Usage]

    Usages; kept sorted so that it's easy to decide whether to write a new iface file (changing usages doesn't affect the hash of this module) NOT STRICT! we read this field lazily from the interface file It is *only* consulted by the recompilation checker

  • mi_exports :: ![IfaceExport]

    Exports Kept sorted by (mod,occ), to make version comparisons easier Records the modules that are the declaration points for things exported by this module, and the OccNames of those things

  • mi_used_th :: !Bool

    Module required TH splices when it was compiled. This disables recompilation avoidance (see #481).

  • mi_fixities :: [(OccName, Fixity)]

    Fixities NOT STRICT! we read this field lazily from the interface file

  • mi_warns :: Warnings

    Warnings NOT STRICT! we read this field lazily from the interface file

  • mi_anns :: [IfaceAnnotation]

    Annotations NOT STRICT! we read this field lazily from the interface file

  • mi_decls :: [IfaceDeclExts phase]

    Type, class and variable declarations The hash of an Id changes if its fixity or deprecations change (as well as its type of course) Ditto data constructors, class operations, except that the hash of the parent class/tycon changes

  • mi_globals :: !(Maybe GlobalRdrEnv)

    Binds all the things defined at the top level in the original source code for this module. which is NOT the same as mi_exports, nor mi_decls (which may contains declarations for things not actually defined by the user). Used for GHCi and for inspecting the contents of modules via the GHC API only.

    (We need the source file to figure out the top-level environment, if we didn't compile this module from source then this field contains Nothing).

    Strictly speaking this field should live in the HomeModInfo, but that leads to more plumbing.

  • mi_insts :: [IfaceClsInst]

    Sorted class instance

  • mi_fam_insts :: [IfaceFamInst]

    Sorted family instances

  • mi_rules :: [IfaceRule]

    Sorted rules

  • mi_hpc :: !AnyHpcUsage

    True if this program uses Hpc at any point in the program.

  • mi_trust :: !IfaceTrustInfo

    Safe Haskell Trust information for this module.

  • mi_trust_pkg :: !Bool

    Do we require the package this module resides in be trusted to trust this module? This is used for the situation where a module is Safe (so doesn't require the package be trusted itself) but imports some trustworthy modules from its own package (which does require its own package be trusted). See Note [RnNames . Trust Own Package]

  • mi_complete_sigs :: [IfaceCompleteMatch]
     
  • mi_doc_hdr :: Maybe HsDocString

    Module header.

  • mi_decl_docs :: DeclDocMap

    Docs on declarations.

  • mi_arg_docs :: ArgDocMap

    Docs on arguments.

  • mi_final_exts :: !(IfaceBackendExts phase)

    Either () or ModIfaceBackend for a fully instantiated interface.

Instances

Instances details
Binary ModIface 
Instance details

Defined in HscTypes

(NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) 
Instance details

Defined in HscTypes

Methods

rnf :: ModIface_ phase -> () #

data HscSource #

Constructors

HsSrcFile 
HsBootFile 
HsigFile 

Instances

Instances details
Eq HscSource 
Instance details

Defined in DriverPhases

Ord HscSource 
Instance details

Defined in DriverPhases

Show HscSource 
Instance details

Defined in DriverPhases

Binary HscSource 
Instance details

Defined in DriverPhases

data WhereFrom #

Instances

Instances details
Outputable WhereFrom 
Instance details

Defined in TcRnTypes

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.

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)

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.

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.

Constructors

Prefix 
Infix 

Instances

Instances details
Eq LexicalFixity 
Instance details

Defined in BasicTypes

Data LexicalFixity 
Instance details

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 
Instance details

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

Instances details
Show ModSummary Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ModSummary Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: ModSummary -> () #

Outputable ModSummary 
Instance details

Defined in HscTypes

HomeModInfo

data HomeModInfo #

Information about modules in the package being compiled

Constructors

HomeModInfo 

Fields

ModGuts

data 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

Instances

Instances details
Show ModGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ModGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: ModGuts -> () #

data CgGuts #

A restricted form of ModGuts for code generation purposes

Constructors

CgGuts 

Fields

Instances

Instances details
Show CgGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData CgGuts Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: CgGuts -> () #

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

Instances details
Show ModDetails Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ModDetails Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: ModDetails -> () #

Var

data Type #

Constructors

TyVarTy Var

Vanilla type or kind variable (*never* a coercion variable)

AppTy Type Type

Type application to something other than a TyCon. Parameters:

1) Function: must not be a TyConApp or CastTy, must be another AppTy, or TyVarTy See Note Respecting definitional equality about the no CastTy requirement

2) Argument type

TyConApp TyCon [KindOrType]

Application of a TyCon, including newtypes and synonyms. Invariant: saturated applications of FunTyCon must use FunTy and saturated synonyms must use their own constructors. However, unsaturated FunTyCons do appear as TyConApps. Parameters:

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

Instances details
Data Type 
Instance details

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 #

toConstr :: Type -> Constr #

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 # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Type -> () #

Outputable Type 
Instance details

Defined in TyCoRep

Methods

ppr :: Type -> SDoc #

pprPrec :: Rational -> Type -> SDoc #

Eq (DeBruijn Type) 
Instance details

Defined in CoreMap

Methods

(==) :: DeBruijn Type -> DeBruijn Type -> Bool #

(/=) :: DeBruijn Type -> DeBruijn Type -> Bool #

ToHie (TScoped Type) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped Type -> HieM [HieAST Type]

pattern FunTy :: Type -> Type -> Type Source #

Specs

data ImpDeclSpec #

Import Declaration Specification

Describes a particular import declaration and is shared among all the Provenances for that decl

Constructors

ImpDeclSpec 

Fields

  • is_mod :: ModuleName

    Module imported, e.g. import Muggle Note the Muggle may well not be the defining module for this thing!

  • is_as :: ModuleName

    Import alias, e.g. from as M (or Muggle if there is no as clause)

  • is_qual :: Bool

    Was this import qualified?

  • is_dloc :: SrcSpan

    The location of the entire import declaration

Instances

Instances details
Eq ImpDeclSpec 
Instance details

Defined in RdrName

Data ImpDeclSpec 
Instance details

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 
Instance details

Defined in RdrName

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 

Instances

Instances details
Eq ImportSpec 
Instance details

Defined in RdrName

Data ImportSpec 
Instance details

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 
Instance details

Defined in RdrName

Outputable ImportSpec 
Instance details

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

Instances details
Eq SourceText 
Instance details

Defined in BasicTypes

Data SourceText 
Instance details

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 
Instance details

Defined in BasicTypes

Outputable SourceText 
Instance details

Defined in BasicTypes

Annotate (SourceText, FastString) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

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

data Way #

Instances

Instances details
Eq Way 
Instance details

Defined in DynFlags

Methods

(==) :: Way -> Way -> Bool #

(/=) :: Way -> Way -> Bool #

Ord Way 
Instance details

Defined in DynFlags

Methods

compare :: Way -> Way -> Ordering #

(<) :: Way -> Way -> Bool #

(<=) :: Way -> Way -> Bool #

(>) :: Way -> Way -> Bool #

(>=) :: Way -> Way -> Bool #

max :: Way -> Way -> Way #

min :: Way -> Way -> Way #

Show Way 
Instance details

Defined in DynFlags

Methods

showsPrec :: Int -> Way -> ShowS #

show :: Way -> String #

showList :: [Way] -> ShowS #

AvailInfo

data AvailInfo #

Records what things are "available", i.e. in scope

Instances

Instances details
Eq AvailInfo

Used when deciding if the interface has changed

Instance details

Defined in Avail

Data AvailInfo 
Instance details

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 
Instance details

Defined in Avail

Outputable AvailInfo 
Instance details

Defined in Avail

pattern AvailTC :: Name -> [Name] -> [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)

TcGblEnv

data 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

Instances details
ContainsCostCentreState TcGblEnv 
Instance details

Defined in TcRnMonad

ContainsModule TcGblEnv 
Instance details

Defined in TcRnTypes

Parsing and LExer types

data HsParsedModule #

Constructors

HsParsedModule 

Fields

data ParsedModule #

The result of successful parsing.

Instances

Instances details
Show ParsedModule Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ParsedModule Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: ParsedModule -> () #

ParsedMod ParsedModule 
Instance details

Defined in GHC

Compilation Main

data HscEnv #

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.

runGhc #

Arguments

:: Maybe FilePath

See argument to initGhcMonad.

-> 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.

unGhc :: Ghc a -> Session -> IO a #

data Session #

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.

Constructors

Session !(IORef HscEnv) 

modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () #

Set the current session to the result of applying the current session to the argument.

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

getSession, setSession

Instances

Instances details
GhcMonad Ghc 
Instance details

Defined in GhcMonad

ExceptionMonad m => GhcMonad (GhcT m) 
Instance details

Defined in GhcMonad

Methods

getSession :: GhcT m HscEnv #

setSession :: HscEnv -> GhcT m () #

data Ghc a #

A minimal implementation of a GhcMonad. If you need a custom monad, e.g., to maintain additional state consider wrapping this monad or using GhcT.

Instances

Instances details
Monad Ghc 
Instance details

Defined in GhcMonad

Methods

(>>=) :: Ghc a -> (a -> Ghc b) -> Ghc b #

(>>) :: Ghc a -> Ghc b -> Ghc b #

return :: a -> Ghc a #

Functor Ghc 
Instance details

Defined in GhcMonad

Methods

fmap :: (a -> b) -> Ghc a -> Ghc b #

(<$) :: a -> Ghc b -> Ghc a #

MonadFix Ghc 
Instance details

Defined in GhcMonad

Methods

mfix :: (a -> Ghc a) -> Ghc a #

Applicative Ghc 
Instance details

Defined in GhcMonad

Methods

pure :: a -> Ghc a #

(<*>) :: Ghc (a -> b) -> Ghc a -> Ghc b #

liftA2 :: (a -> b -> c) -> Ghc a -> Ghc b -> Ghc c #

(*>) :: Ghc a -> Ghc b -> Ghc b #

(<*) :: Ghc a -> Ghc b -> Ghc a #

MonadIO Ghc 
Instance details

Defined in GhcMonad

Methods

liftIO :: IO a -> Ghc a #

GhcMonad Ghc 
Instance details

Defined in GhcMonad

HasDynFlags Ghc 
Instance details

Defined in GhcMonad

ExceptionMonad Ghc 
Instance details

Defined in GhcMonad

Methods

gcatch :: Exception e => Ghc a -> (e -> Ghc a) -> Ghc a #

gmask :: ((Ghc a -> Ghc a) -> Ghc b) -> Ghc b #

gbracket :: Ghc a -> (a -> Ghc b) -> (a -> Ghc c) -> Ghc c #

gfinally :: Ghc a -> Ghc b -> Ghc a #

runHsc :: HscEnv -> Hsc a -> IO a #

data Phase #

Instances

Instances details
Eq Phase 
Instance details

Defined in DriverPhases

Methods

(==) :: Phase -> Phase -> Bool #

(/=) :: Phase -> Phase -> Bool #

Show Phase 
Instance details

Defined in DriverPhases

Methods

showsPrec :: Int -> Phase -> ShowS #

show :: Phase -> String #

showList :: [Phase] -> ShowS #

Outputable Phase 
Instance details

Defined in DriverPhases

Methods

ppr :: Phase -> SDoc #

pprPrec :: Rational -> Phase -> SDoc #

hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts #

Convert a typechecked module to Core

hscGenHardCode #

Arguments

:: HscEnv 
-> CgGuts 
-> ModLocation 
-> FilePath 
-> IO (FilePath, Maybe FilePath, [(ForeignSrcLang, FilePath)])

Just f = _stub.c is f

Compile to hard-code.

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

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

Source Locations

unLoc :: HasSrcSpan a => a -> SrcSpanLess a #

data GenLocated l e #

We attach SrcSpans to lots of things, so let's have a datatype for it.

Constructors

L l e 

Instances

Instances details
HasDecls ParsedSource 
Instance details

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) 
Instance details

Defined in SrcLoc

Methods

fmap :: (a -> b) -> GenLocated l a -> GenLocated l b #

(<$) :: a -> GenLocated l b -> GenLocated l a #

Show (Annotated ParsedSource) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Foldable (GenLocated l) 
Instance details

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) 
Instance details

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 # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Annotated ParsedSource -> () #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in Name

HasSrcSpan (Located a) 
Instance details

Defined in SrcLoc

Annotate [ExprLStmt GhcPs]

Used for declarations that need to be aligned together, e.g. in a do or let .. in statement/expr

Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [ExprLStmt GhcPs] -> Annotated () #

Annotate [LHsDerivingClause GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate [LHsType GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LHsType GhcPs] -> Annotated () #

Annotate [LHsSigType GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LHsSigType GhcPs] -> Annotated () #

Annotate [LConDeclField GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate [LIE GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LIE GhcPs] -> Annotated () #

Annotate body => Annotate [Located (Match GhcPs (Located body))] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [Located (Match GhcPs (Located body))] -> Annotated () #

Annotate [Located (StmtLR GhcPs GhcPs (LHsCmd GhcPs))] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (TyFamInstEqn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsRecUpdField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (FunDep (Located RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate name => Annotate (BooleanFormula (Located name)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> BooleanFormula (Located name) -> Annotated () #

(Data ast, Annotate ast) => Annotate (Located ast) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Located ast -> Annotated () #

HasDecls (LHsExpr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LHsExpr GhcPs -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LHsExpr GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsExpr GhcPs) #

HasLoc (Located a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: Located a -> SrcSpan

HasType (LHsBind GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type]

HasType (LHsBind GhcTc) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsBind GhcTc -> HieM [HieAST Type]

HasType (LHsExpr GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsExpr GhcRn -> HieM [HieAST Type]

HasType (LHsExpr GhcTc)

This instance tries to construct HieAST nodes which include the type of the expression. It is not yet possible to do this efficiently for all expression forms, so we skip filling in the type for those inputs.

HsApp, for example, doesn't have any type information available directly on the node. Our next recourse would be to desugar it into a CoreExpr then query the type of that. Yet both the desugaring call and the type query both involve recursive calls to the function and argument! This is particularly problematic when you realize that the HIE traversal will eventually visit those nodes too and ask for their types again.

Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive.

See #16233

Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsExpr GhcTc -> HieM [HieAST Type]

HasType (Located (Pat GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: Located (Pat GhcRn) -> HieM [HieAST Type]

HasType (Located (Pat GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: Located (Pat GhcTc) -> HieM [HieAST Type]

(a ~ GhcPass p, ToHie (LHsExpr a), Data (HsTupArg a)) => ToHie (LHsTupArg (GhcPass p)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsTupArg (GhcPass p) -> HieM [HieAST Type]

(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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsCmd (GhcPass p) -> HieM [HieAST Type]

(ToHie (LHsCmd a), Data (HsCmdTop a)) => ToHie (LHsCmdTop a) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsCmdTop a -> HieM [HieAST Type]

ToHie (LSpliceDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type]

ToHie (LTyClDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LTyClDecl GhcRn -> HieM [HieAST Type]

ToHie (LFamilyDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LFamilyDecl GhcRn -> HieM [HieAST Type]

ToHie (LInjectivityAnn GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type]

ToHie (HsDeriving GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsDeriving GhcRn -> HieM [HieAST Type]

ToHie (LHsDerivingClause GhcRn) 
Instance details

Defined in Compat.HieAst

ToHie (LStandaloneKindSig GhcRn) 
Instance details

Defined in Compat.HieAst

ToHie (LConDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LConDecl GhcRn -> HieM [HieAST Type]

ToHie (LTyFamInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LDataFamInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LClsInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LDerivDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LDerivDecl GhcRn -> HieM [HieAST Type]

ToHie (LDefaultDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type]

ToHie (LForeignDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LForeignDecl GhcRn -> HieM [HieAST Type]

ToHie (LRuleDecls GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LRuleDecls GhcRn -> HieM [HieAST Type]

ToHie (LRuleDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LRuleDecl GhcRn -> HieM [HieAST Type]

ToHie (LWarnDecls GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LWarnDecls GhcRn -> HieM [HieAST Type]

ToHie (LWarnDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LWarnDecl GhcRn -> HieM [HieAST Type]

ToHie (LAnnDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LAnnDecl GhcRn -> HieM [HieAST Type]

ToHie (LRoleAnnotDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type]

ToHie (LFixitySig GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LFixitySig GhcRn -> HieM [HieAST Type]

ToHie (LHsContext GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsContext GhcRn -> HieM [HieAST Type]

ToHie (LHsType GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsType GhcRn -> HieM [HieAST Type]

ToHie (LConDeclField GhcRn) 
Instance details

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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsExpr (GhcPass p) -> HieM [HieAST Type]

ToHie (LImportDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LImportDecl GhcRn -> HieM [HieAST Type]

ToHie (LBooleanFormula (Located Name)) 
Instance details

Defined in Compat.HieAst

ToHie (Located [LConDeclField GhcRn]) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located [LConDeclField GhcRn] -> HieM [HieAST Type]

ToHie (Located (DerivStrategy GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (DerivStrategy GhcRn) -> HieM [HieAST Type]

(ToHie (Context (Located (IdP a))), ToHie (PScoped (LPat a)), ToHie (HsPatSynDir a)) => ToHie (Located (PatSynBind a a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (PatSynBind a a) -> HieM [HieAST Type]

ToHie (Located HsIPName) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located HsIPName -> HieM [HieAST Type]

ToHie (Located (FunDep (Located Name))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (FunDep (Located Name)) -> HieM [HieAST Type]

(ToHie (LHsExpr a), Data (HsSplice a)) => ToHie (Located (HsSplice a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (HsSplice a) -> HieM [HieAST Type]

ToHie (Located OverlapMode) 
Instance details

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)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]

ToHie (TScoped (LHsType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LHsType GhcRn) -> HieM [HieAST Type]

ToHie (TScoped (LHsWcType GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LHsWcType GhcTc) -> HieM [HieAST Type]

ToHie (TScoped (LHsSigWcType GhcTc))

Dummy instances - never called

Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type]

ToHie (Context (Located NoExtField)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located NoExtField) -> HieM [HieAST Type]

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

ToHie (Context (Located Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Name) -> 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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: BindContext (LHsBind a) -> HieM [HieAST Type]

(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))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LStmt (GhcPass p) (Located body)) -> HieM [HieAST Type]

ToHie (RScoped (LFamilyResultSig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type]

ToHie (RScoped (LRuleBndr GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LRuleBndr GhcRn) -> HieM [HieAST Type]

(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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LHsLocalBinds a) -> HieM [HieAST Type]

ToHie (SigContext (LSig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LSig GhcRn) -> HieM [HieAST Type]

ToHie (SigContext (LSig GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LSig GhcTc) -> HieM [HieAST Type]

(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data label, Data arg) => ToHie (RContext (LHsRecField' label arg)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (LHsRecField' label arg) -> HieM [HieAST Type]

ToHie (RFContext (LFieldOcc GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (LFieldOcc GhcRn) -> HieM [HieAST Type]

ToHie (RFContext (LFieldOcc GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (LFieldOcc GhcTc) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcTc)) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

ToHie (IEContext (LIE GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIE GhcRn) -> HieM [HieAST Type]

ToHie (IEContext (Located (FieldLbl Name))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located (FieldLbl Name)) -> HieM [HieAST Type]

ToHie (IEContext (Located ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type]

ToHie (TVScoped (LHsTyVarBndr GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type]

(Eq l, Eq e) => Eq (GenLocated l e) 
Instance details

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) 
Instance details

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) 
Instance details

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 # 
Instance details

Defined in Development.IDE.GHC.Orphans

(NFData l, NFData e) => NFData (GenLocated l e) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: GenLocated l e -> () #

(Outputable l, Outputable e) => Outputable (GenLocated l e) 
Instance details

Defined in SrcLoc

Methods

ppr :: GenLocated l e -> SDoc #

pprPrec :: Rational -> GenLocated l e -> SDoc #

Annotate body => Annotate (Match GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Match GhcPs (Located body) -> Annotated () #

Annotate body => Annotate (GRHS GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> GRHS GhcPs (Located body) -> Annotated () #

Annotate body => Annotate (Stmt GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Stmt GhcPs (Located body) -> Annotated () #

Annotate (HsRecField GhcPs (LHsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsRecField GhcPs (Located (Pat GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate arg => Annotate (HsImplicitBndrs GhcPs (Located arg)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

HasDecls (LMatch GhcPs (LHsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LMatch GhcPs (LHsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LMatch GhcPs (LHsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LMatch GhcPs (LHsExpr GhcPs)) #

HasDecls (LStmt GhcPs (LHsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LStmt GhcPs (LHsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LStmt GhcPs (LHsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LStmt GhcPs (LHsExpr GhcPs)) #

(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) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LMatch (GhcPass p) body -> HieM [HieAST Type]

(ToHie (Located body), ToHie (RScoped (GuardLStmt a)), Data (GRHS a (Located body))) => ToHie (LGRHS a (Located body)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LGRHS a (Located body) -> HieM [HieAST Type]

type SrcSpanLess (GenLocated l e) 
Instance details

Defined in SrcLoc

type SrcSpanLess (GenLocated l e) = e

data SrcSpan #

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

Instances details
Eq SrcSpan 
Instance details

Defined in SrcLoc

Methods

(==) :: SrcSpan -> SrcSpan -> Bool #

(/=) :: SrcSpan -> SrcSpan -> Bool #

Data SrcSpan 
Instance details

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 
Instance details

Defined in SrcLoc

Show SrcSpan 
Instance details

Defined in SrcLoc

NFData SrcSpan 
Instance details

Defined in SrcLoc

Methods

rnf :: SrcSpan -> () #

ToJson SrcSpan 
Instance details

Defined in SrcLoc

Methods

json :: SrcSpan -> JsonDoc #

Outputable SrcSpan 
Instance details

Defined in SrcLoc

Methods

ppr :: SrcSpan -> SDoc #

pprPrec :: Rational -> SrcSpan -> SDoc #

HasDecls ParsedSource 
Instance details

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 #

Show (Annotated ParsedSource) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData (Annotated ParsedSource) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Annotated ParsedSource -> () #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in Name

HasSrcSpan (Located a) 
Instance details

Defined in SrcLoc

Annotate [ExprLStmt GhcPs]

Used for declarations that need to be aligned together, e.g. in a do or let .. in statement/expr

Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [ExprLStmt GhcPs] -> Annotated () #

Annotate [LHsDerivingClause GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate [LHsType GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LHsType GhcPs] -> Annotated () #

Annotate [LHsSigType GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LHsSigType GhcPs] -> Annotated () #

Annotate [LConDeclField GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate [LIE GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LIE GhcPs] -> Annotated () #

Annotate body => Annotate [Located (Match GhcPs (Located body))] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [Located (Match GhcPs (Located body))] -> Annotated () #

Annotate [Located (StmtLR GhcPs GhcPs (LHsCmd GhcPs))] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (TyFamInstEqn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsRecUpdField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (FunDep (Located RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate name => Annotate (BooleanFormula (Located name)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> BooleanFormula (Located name) -> Annotated () #

(Data ast, Annotate ast) => Annotate (Located ast) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Located ast -> Annotated () #

HasDecls (LHsExpr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LHsExpr GhcPs -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LHsExpr GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsExpr GhcPs) #

HasLoc (Located a) 
Instance details

Defined in Compat.HieAst

Methods

loc :: Located a -> SrcSpan

HasType (LHsBind GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsBind GhcRn -> HieM [HieAST Type]

HasType (LHsBind GhcTc) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsBind GhcTc -> HieM [HieAST Type]

HasType (LHsExpr GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsExpr GhcRn -> HieM [HieAST Type]

HasType (LHsExpr GhcTc)

This instance tries to construct HieAST nodes which include the type of the expression. It is not yet possible to do this efficiently for all expression forms, so we skip filling in the type for those inputs.

HsApp, for example, doesn't have any type information available directly on the node. Our next recourse would be to desugar it into a CoreExpr then query the type of that. Yet both the desugaring call and the type query both involve recursive calls to the function and argument! This is particularly problematic when you realize that the HIE traversal will eventually visit those nodes too and ask for their types again.

Since the above is quite costly, we just skip cases where computing the expression's type is going to be expensive.

See #16233

Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: LHsExpr GhcTc -> HieM [HieAST Type]

HasType (Located (Pat GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: Located (Pat GhcRn) -> HieM [HieAST Type]

HasType (Located (Pat GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

getTypeNode :: Located (Pat GhcTc) -> HieM [HieAST Type]

(a ~ GhcPass p, ToHie (LHsExpr a), Data (HsTupArg a)) => ToHie (LHsTupArg (GhcPass p)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsTupArg (GhcPass p) -> HieM [HieAST Type]

(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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsCmd (GhcPass p) -> HieM [HieAST Type]

(ToHie (LHsCmd a), Data (HsCmdTop a)) => ToHie (LHsCmdTop a) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsCmdTop a -> HieM [HieAST Type]

ToHie (LSpliceDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LSpliceDecl GhcRn -> HieM [HieAST Type]

ToHie (LTyClDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LTyClDecl GhcRn -> HieM [HieAST Type]

ToHie (LFamilyDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LFamilyDecl GhcRn -> HieM [HieAST Type]

ToHie (LInjectivityAnn GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LInjectivityAnn GhcRn -> HieM [HieAST Type]

ToHie (HsDeriving GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: HsDeriving GhcRn -> HieM [HieAST Type]

ToHie (LHsDerivingClause GhcRn) 
Instance details

Defined in Compat.HieAst

ToHie (LStandaloneKindSig GhcRn) 
Instance details

Defined in Compat.HieAst

ToHie (LConDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LConDecl GhcRn -> HieM [HieAST Type]

ToHie (LTyFamInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LTyFamInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LDataFamInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LDataFamInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LClsInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LClsInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LInstDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LInstDecl GhcRn -> HieM [HieAST Type]

ToHie (LDerivDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LDerivDecl GhcRn -> HieM [HieAST Type]

ToHie (LDefaultDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LDefaultDecl GhcRn -> HieM [HieAST Type]

ToHie (LForeignDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LForeignDecl GhcRn -> HieM [HieAST Type]

ToHie (LRuleDecls GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LRuleDecls GhcRn -> HieM [HieAST Type]

ToHie (LRuleDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LRuleDecl GhcRn -> HieM [HieAST Type]

ToHie (LWarnDecls GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LWarnDecls GhcRn -> HieM [HieAST Type]

ToHie (LWarnDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LWarnDecl GhcRn -> HieM [HieAST Type]

ToHie (LAnnDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LAnnDecl GhcRn -> HieM [HieAST Type]

ToHie (LRoleAnnotDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LRoleAnnotDecl GhcRn -> HieM [HieAST Type]

ToHie (LFixitySig GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LFixitySig GhcRn -> HieM [HieAST Type]

ToHie (LHsContext GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsContext GhcRn -> HieM [HieAST Type]

ToHie (LHsType GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsType GhcRn -> HieM [HieAST Type]

ToHie (LConDeclField GhcRn) 
Instance details

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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LHsExpr (GhcPass p) -> HieM [HieAST Type]

ToHie (LImportDecl GhcRn) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LImportDecl GhcRn -> HieM [HieAST Type]

ToHie (LBooleanFormula (Located Name)) 
Instance details

Defined in Compat.HieAst

ToHie (Located [LConDeclField GhcRn]) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located [LConDeclField GhcRn] -> HieM [HieAST Type]

ToHie (Located (DerivStrategy GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (DerivStrategy GhcRn) -> HieM [HieAST Type]

(ToHie (Context (Located (IdP a))), ToHie (PScoped (LPat a)), ToHie (HsPatSynDir a)) => ToHie (Located (PatSynBind a a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (PatSynBind a a) -> HieM [HieAST Type]

ToHie (Located HsIPName) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located HsIPName -> HieM [HieAST Type]

ToHie (Located (FunDep (Located Name))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (FunDep (Located Name)) -> HieM [HieAST Type]

(ToHie (LHsExpr a), Data (HsSplice a)) => ToHie (Located (HsSplice a)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (HsSplice a) -> HieM [HieAST Type]

ToHie (Located OverlapMode) 
Instance details

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)))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: PScoped (Located (Pat (GhcPass p))) -> HieM [HieAST Type]

ToHie (TScoped (LHsType GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LHsType GhcRn) -> HieM [HieAST Type]

ToHie (TScoped (LHsWcType GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LHsWcType GhcTc) -> HieM [HieAST Type]

ToHie (TScoped (LHsSigWcType GhcTc))

Dummy instances - never called

Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped (LHsSigWcType GhcTc) -> HieM [HieAST Type]

ToHie (Context (Located NoExtField)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located NoExtField) -> HieM [HieAST Type]

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

ToHie (Context (Located Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Name) -> 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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: BindContext (LHsBind a) -> HieM [HieAST Type]

(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))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LStmt (GhcPass p) (Located body)) -> HieM [HieAST Type]

ToHie (RScoped (LFamilyResultSig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LFamilyResultSig GhcRn) -> HieM [HieAST Type]

ToHie (RScoped (LRuleBndr GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LRuleBndr GhcRn) -> HieM [HieAST Type]

(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)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RScoped (LHsLocalBinds a) -> HieM [HieAST Type]

ToHie (SigContext (LSig GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LSig GhcRn) -> HieM [HieAST Type]

ToHie (SigContext (LSig GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: SigContext (LSig GhcTc) -> HieM [HieAST Type]

(ToHie (RFContext (Located label)), ToHie arg, HasLoc arg, Data label, Data arg) => ToHie (RContext (LHsRecField' label arg)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RContext (LHsRecField' label arg) -> HieM [HieAST Type]

ToHie (RFContext (LFieldOcc GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (LFieldOcc GhcRn) -> HieM [HieAST Type]

ToHie (RFContext (LFieldOcc GhcTc)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (LFieldOcc GhcTc) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcRn))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcRn)) -> HieM [HieAST Type]

ToHie (RFContext (Located (AmbiguousFieldOcc GhcTc))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: RFContext (Located (AmbiguousFieldOcc GhcTc)) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

ToHie (IEContext (LIE GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIE GhcRn) -> HieM [HieAST Type]

ToHie (IEContext (Located (FieldLbl Name))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located (FieldLbl Name)) -> HieM [HieAST Type]

ToHie (IEContext (Located ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type]

ToHie (TVScoped (LHsTyVarBndr GhcRn)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TVScoped (LHsTyVarBndr GhcRn) -> HieM [HieAST Type]

Outputable a => Show (GenLocated SrcSpan a) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Annotate body => Annotate (Match GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Match GhcPs (Located body) -> Annotated () #

Annotate body => Annotate (GRHS GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> GRHS GhcPs (Located body) -> Annotated () #

Annotate body => Annotate (Stmt GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Stmt GhcPs (Located body) -> Annotated () #

Annotate (HsRecField GhcPs (LHsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsRecField GhcPs (Located (Pat GhcPs))) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate arg => Annotate (HsImplicitBndrs GhcPs (Located arg)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

HasDecls (LMatch GhcPs (LHsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LMatch GhcPs (LHsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LMatch GhcPs (LHsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LMatch GhcPs (LHsExpr GhcPs)) #

HasDecls (LStmt GhcPs (LHsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LStmt GhcPs (LHsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] #

replaceDecls :: forall (m :: Type -> Type). Monad m => LStmt GhcPs (LHsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LStmt GhcPs (LHsExpr GhcPs)) #

(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) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LMatch (GhcPass p) body -> HieM [HieAST Type]

(ToHie (Located body), ToHie (RScoped (GuardLStmt a)), Data (GRHS a (Located body))) => ToHie (LGRHS a (Located body)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: LGRHS a (Located body) -> HieM [HieAST Type]

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

Instances details
Eq RealSrcSpan 
Instance details

Defined in SrcLoc

Data RealSrcSpan 
Instance details

Defined in SrcLoc

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RealSrcSpan -> c RealSrcSpan #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RealSrcSpan #

toConstr :: RealSrcSpan -> Constr #

dataTypeOf :: RealSrcSpan -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RealSrcSpan) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RealSrcSpan) #

gmapT :: (forall b. Data b => b -> b) -> RealSrcSpan -> RealSrcSpan #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RealSrcSpan -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RealSrcSpan -> r #

gmapQ :: (forall d. Data d => d -> u) -> RealSrcSpan -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RealSrcSpan -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RealSrcSpan -> m RealSrcSpan #

Ord RealSrcSpan 
Instance details

Defined in SrcLoc

Show RealSrcSpan 
Instance details

Defined in SrcLoc

ToJSON RealSrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

FromJSON RealSrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData RealSrcSpan Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: RealSrcSpan -> () #

ToJson RealSrcSpan 
Instance details

Defined in SrcLoc

Methods

json :: RealSrcSpan -> JsonDoc #

Outputable RealSrcSpan 
Instance details

Defined in SrcLoc

MapAge RealSrcSpan Source # 
Instance details

Defined in Development.IDE.Core.UseStale

Methods

mapAgeFrom :: forall (from :: Age) (to :: Age). PositionMap from to -> Tracked to RealSrcSpan -> Maybe (Tracked from RealSrcSpan) Source #

mapAgeTo :: forall (from :: Age) (to :: Age). PositionMap from to -> Tracked from RealSrcSpan -> Maybe (Tracked to RealSrcSpan) Source #

data RealSrcLoc #

Real Source Location

Represents a single point within a file

Instances

Instances details
Eq RealSrcLoc 
Instance details

Defined in SrcLoc

Ord RealSrcLoc 
Instance details

Defined in SrcLoc

Show RealSrcLoc 
Instance details

Defined in SrcLoc

Outputable RealSrcLoc 
Instance details

Defined in SrcLoc

data SrcLoc #

Source Location

Instances

Instances details
Eq SrcLoc 
Instance details

Defined in SrcLoc

Methods

(==) :: SrcLoc -> SrcLoc -> Bool #

(/=) :: SrcLoc -> SrcLoc -> Bool #

Ord SrcLoc 
Instance details

Defined in SrcLoc

Show SrcLoc 
Instance details

Defined in SrcLoc

Outputable SrcLoc 
Instance details

Defined in SrcLoc

Methods

ppr :: SrcLoc -> SDoc #

pprPrec :: Rational -> SrcLoc -> SDoc #

type BufSpan = () Source #

leftmost_smallest :: SrcSpan -> SrcSpan -> Ordering #

Alternative strategies for ordering SrcSpans

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

isSubspanOf #

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

wiredInSrcSpan :: SrcSpan #

Built-in "bad" SrcSpans for common sources of location uncertainty

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan #

Create a SrcSpan between two points in a file

srcSpanStart :: SrcSpan -> SrcLoc #

Returns the location at the start of the SrcSpan or a "bad" SrcSpan if that is unavailable

srcSpanEnd :: SrcSpan -> SrcLoc #

Returns the location at the end of the SrcSpan or a "bad" SrcSpan if that is unavailable

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

noSrcSpan :: SrcSpan #

Built-in "bad" SrcSpans for common sources of location uncertainty

noSrcLoc :: SrcLoc #

Built-in "bad" SrcLoc values for particular locations

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

addBootSuffixLocnOut :: ModLocation -> ModLocation Source #

Add the -boot suffix to all output file paths associated with the module, not including the input file itself

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 cause pkg 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 causes pkg 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. Let depExposedPackages be the transitive closure from exposedPackages 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

Instances details
Semigroup ModuleOrigin 
Instance details

Defined in Packages

Monoid ModuleOrigin 
Instance details

Defined in Packages

Outputable ModuleOrigin 
Instance details

Defined in Packages

Linker

data Unlinked #

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.

Instances

Instances details
Outputable Unlinked 
Instance details

Defined in LinkerTypes

data Linkable #

Information we can use to dynamically link modules into the compiler

Constructors

LM 

Fields

  • linkableTime :: UTCTime

    Time at which this linkable was built (i.e. when the bytecodes were produced, or the mod date on the files)

  • linkableModule :: Module

    The linkable module itself

  • linkableUnlinked :: [Unlinked]

    Those files and chunks of code we have yet to link.

    INVARIANT: A valid linkable always has at least one Unlinked item. If this list is empty, the Linkable represents a fake linkable, which is generated in HscNothing mode to avoid recompiling modules.

    ToDo: Do items get removed from this list when they get linked?

Instances

Instances details
Show Linkable Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData Linkable Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Linkable -> () #

Outputable Linkable 
Instance details

Defined in LinkerTypes

unload #

Arguments

:: HscEnv 
-> [Linkable]

The linkables to *keep*.

-> IO () 

Unloading old objects ready for a new compilation sweep.

The compilation manager provides us with a list of linkables that it considers "stable", i.e. won't be recompiled this time around. For each of the modules current linked in memory,

  • if the linkable is stable (and it's the same one -- the user may have recompiled the module on the side), we keep it,
  • otherwise, we unload it.
  • we also implicitly unload all temporary bindings at this point.

initDynLinker :: HscEnv -> IO () #

Initialise the dynamic linker. This entails

a) Calling the C initialisation procedure,

b) Loading any packages specified on the command line,

c) Loading any packages specified on the command line, now held in the -l options in v_Opt_l,

d) Loading any .o/.dll files specified on the command line, now held in ldInputs,

e) Loading any MacOS frameworks.

NOTE: This function is idempotent; if called more than once, it does nothing. This is useful in Template Haskell, where we call it before trying to link.

Hooks

data Hooks #

data MetaRequest #

The supported metaprogramming result types

HPT

Driver-Make

data Target #

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

  • targetId :: TargetId

    module or filename

  • targetAllowObjCode :: Bool

    object code allowed?

  • targetContents :: Maybe (InputFileBuffer, UTCTime)

    Optional in-memory buffer containing the source code GHC should use for this target instead of reading it from disk.

    Since GHC version 8.10 modules which require preprocessors such as Literate Haskell or CPP to run are also supported.

    If a corresponding source file does not exist on disk this will result in a SourceError exception if targetId = TargetModule _ is used. However together with targetId = TargetFile _ GHC will not complain about the file missing.

Instances

Instances details
Outputable Target 
Instance details

Defined in HscTypes

Methods

ppr :: Target -> SDoc #

pprPrec :: Rational -> Target -> SDoc #

data TargetId #

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.

Instances

Instances details
Eq TargetId 
Instance details

Defined in HscTypes

Outputable TargetId 
Instance details

Defined in HscTypes

GHCi

loadDLL :: HscEnv -> String -> IO (Maybe String) #

loadDLL loads a dynamic library using the OS's native linker (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either an absolute pathname to the file, or a relative filename (e.g. "libfoo.so" or "foo.dll"). In the latter case, loadDLL searches the standard locations for the appropriate library.

Returns:

Nothing => success Just err_msg => failure

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.

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.)

runDecls :: GhcMonad m => String -> m [Name] #

data Warn #

A command-line warning message and the reason it arose

Constructors

Warn 

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

Instances details
Show ModLocation 
Instance details

Defined in Module

Outputable ModLocation 
Instance details

Defined in Module

DataCon

Role

data Role #

Instances

Instances details
Eq Role 
Instance details

Defined in CoAxiom

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Data Role 
Instance details

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 #

toConstr :: Role -> Constr #

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 
Instance details

Defined in CoAxiom

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Binary Role 
Instance details

Defined in CoAxiom

Methods

put_ :: BinHandle -> Role -> IO () #

put :: BinHandle -> Role -> IO (Bin Role) #

get :: BinHandle -> IO Role #

Outputable Role 
Instance details

Defined in CoAxiom

Methods

ppr :: Role -> SDoc #

pprPrec :: Rational -> Role -> SDoc #

Annotate (Maybe Role) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Maybe Role -> Annotated () #

Panic

panic :: String -> a #

Panics and asserts.

Util Module re-exports

mkIntWithInf :: Int -> IntWithInf #

Inject any integer into an IntWithInf

treatZeroAsInf :: Int -> IntWithInf #

Turn a positive number into an IntWithInf, where 0 represents infinity

infinity :: IntWithInf #

A representation of infinity

pprWithSourceText :: SourceText -> SDoc -> SDoc #

Special combinator for showing string literals.

pprAlternative #

Arguments

:: (a -> SDoc)

The pretty printing function to use

-> a

The things to be pretty printed

-> ConTag

Alternative (one-based)

-> Arity

Arity

-> SDoc

SDoc where the alternative havs been pretty printed and finally packed into a paragraph.

Pretty print an alternative in an unboxed sum e.g. "| a | |".

unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b #

noOneShotInfo :: OneShotInfo #

It is always safe to assume that an Id has no lambda-bound variable information

fIRST_TAG :: ConTag #

Tags are allocated from here for real constructors or for superclass selectors

pickLR :: LeftOrRight -> (a, a) -> a #

data LeftOrRight #

Constructors

CLeft 
CRight 

Instances

Instances details
Eq LeftOrRight 
Instance details

Defined in BasicTypes

Data LeftOrRight 
Instance details

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 
Instance details

Defined in BasicTypes

type Arity = Int #

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

type RepArity = Int #

Representation Arity

The number of represented arguments that can be applied to a value before it does "real work". So: fib 100 has representation arity 0 x -> fib x has representation arity 1 () -> fib (x + y) has representation arity 2

type JoinArity = Int #

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.

type ConTag = Int #

Constructor Tag

Type of the tags associated with each constructor possibility or superclass selector

type ConTagZ = Int #

A *zero-indexed* constructor tag

data Alignment #

A power-of-two alignment

Instances

Instances details
Eq Alignment 
Instance details

Defined in BasicTypes

Ord Alignment 
Instance details

Defined in BasicTypes

Outputable Alignment 
Instance details

Defined in BasicTypes

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

Instances details
Eq OneShotInfo 
Instance details

Defined in BasicTypes

Outputable OneShotInfo 
Instance details

Defined in BasicTypes

data SwapFlag #

Constructors

NotSwapped 
IsSwapped 

Instances

Instances details
Outputable SwapFlag 
Instance details

Defined in BasicTypes

data PromotionFlag #

Is a TyCon a promoted data constructor or just a normal type constructor?

Constructors

NotPromoted 
IsPromoted 

Instances

Instances details
Eq PromotionFlag 
Instance details

Defined in BasicTypes

Data PromotionFlag 
Instance details

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

Instances details
Eq FunctionOrData 
Instance details

Defined in BasicTypes

Data FunctionOrData 
Instance details

Defined in BasicTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionOrData -> c FunctionOrData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionOrData #

toConstr :: FunctionOrData -> Constr #

dataTypeOf :: FunctionOrData -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionOrData) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionOrData) #

gmapT :: (forall b. Data b => b -> b) -> FunctionOrData -> FunctionOrData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionOrData -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionOrData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionOrData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionOrData -> m FunctionOrData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionOrData -> m FunctionOrData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionOrData -> m FunctionOrData #

Ord FunctionOrData 
Instance details

Defined in BasicTypes

Outputable FunctionOrData 
Instance details

Defined in BasicTypes

data StringLiteral #

A String Literal in the source, including its original raw format for use by source to source manipulation tools.

Constructors

StringLiteral 

Instances

Instances details
Eq StringLiteral 
Instance details

Defined in BasicTypes

Data StringLiteral 
Instance details

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 
Instance details

Defined in BasicTypes

Annotate StringLiteral 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

data WarningTxt #

Warning Text

reason/explanation from a WARNING or DEPRECATED pragma

Instances

Instances details
Eq WarningTxt 
Instance details

Defined in BasicTypes

Data WarningTxt 
Instance details

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 
Instance details

Defined in BasicTypes

Annotate WarningTxt 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> WarningTxt -> Annotated () #

data Fixity #

Instances

Instances details
Eq Fixity 
Instance details

Defined in BasicTypes

Methods

(==) :: Fixity -> Fixity -> Bool #

(/=) :: Fixity -> Fixity -> Bool #

Data Fixity 
Instance details

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 
Instance details

Defined in BasicTypes

Methods

ppr :: Fixity -> SDoc #

pprPrec :: Rational -> Fixity -> SDoc #

data FixityDirection #

Constructors

InfixL 
InfixR 
InfixN 

Instances

Instances details
Eq FixityDirection 
Instance details

Defined in BasicTypes

Data FixityDirection 
Instance details

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 
Instance details

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.

Constructors

Prefix 
Infix 

Instances

Instances details
Eq LexicalFixity 
Instance details

Defined in BasicTypes

Data LexicalFixity 
Instance details

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 
Instance details

Defined in BasicTypes

data TopLevelFlag #

Constructors

TopLevel 
NotTopLevel 

Instances

Instances details
Outputable TopLevelFlag 
Instance details

Defined in BasicTypes

data Boxity #

Constructors

Boxed 
Unboxed 

Instances

Instances details
Eq Boxity 
Instance details

Defined in BasicTypes

Methods

(==) :: Boxity -> Boxity -> Bool #

(/=) :: Boxity -> Boxity -> Bool #

Data Boxity 
Instance details

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 
Instance details

Defined in BasicTypes

Methods

ppr :: Boxity -> SDoc #

pprPrec :: Rational -> Boxity -> SDoc #

data RecFlag #

Recursivity Flag

Constructors

Recursive 
NonRecursive 

Instances

Instances details
Eq RecFlag 
Instance details

Defined in BasicTypes

Methods

(==) :: RecFlag -> RecFlag -> Bool #

(/=) :: RecFlag -> RecFlag -> Bool #

Data RecFlag 
Instance details

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 
Instance details

Defined in BasicTypes

Methods

ppr :: RecFlag -> SDoc #

pprPrec :: Rational -> RecFlag -> SDoc #

data Origin #

Constructors

FromSource 
Generated 

Instances

Instances details
Eq Origin 
Instance details

Defined in BasicTypes

Methods

(==) :: Origin -> Origin -> Bool #

(/=) :: Origin -> Origin -> Bool #

Data Origin 
Instance details

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 
Instance details

Defined in BasicTypes

Methods

ppr :: Origin -> SDoc #

pprPrec :: Rational -> Origin -> SDoc #

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.

Instances

Instances details
Eq OverlapFlag 
Instance details

Defined in BasicTypes

Data OverlapFlag 
Instance details

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 
Instance details

Defined in BasicTypes

data OverlapMode #

Constructors

NoOverlap SourceText

This instance must not overlap another NoOverlap instance. However, it may be overlapped by Overlapping instances, and it may overlap Overlappable instances.

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 Overlapping and Overlappable flags.

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 b would change which instance was chosen. See also note [Incoherent instances] in InstEnv

Instances

Instances details
Eq OverlapMode 
Instance details

Defined in BasicTypes

Data OverlapMode 
Instance details

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 
Instance details

Defined in BasicTypes

Annotate OverlapMode 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

ToHie (Located OverlapMode) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located OverlapMode -> HieM [HieAST Type]

newtype PprPrec #

A general-purpose pretty-printing precedence type.

Constructors

PprPrec Int 

Instances

Instances details
Eq PprPrec 
Instance details

Defined in BasicTypes

Methods

(==) :: PprPrec -> PprPrec -> Bool #

(/=) :: PprPrec -> PprPrec -> Bool #

Ord PprPrec 
Instance details

Defined in BasicTypes

Show PprPrec 
Instance details

Defined in BasicTypes

data TupleSort #

Instances

Instances details
Eq TupleSort 
Instance details

Defined in BasicTypes

Data TupleSort 
Instance details

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 
Instance details

Defined in BasicTypes

data EP a #

Embedding Projection pair

Constructors

EP 

Fields

data OccInfo #

identifier Occurrence Information

Constructors

ManyOccs

There are many occurrences, or unknown occurrences

IAmDead

Marks unused variables. Sometimes useful for lambda and case-bound variables.

OneOcc

Occurs exactly once (per branch), not inside a rule

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

Instances

Instances details
Eq OccInfo 
Instance details

Defined in BasicTypes

Methods

(==) :: OccInfo -> OccInfo -> Bool #

(/=) :: OccInfo -> OccInfo -> Bool #

Outputable OccInfo 
Instance details

Defined in BasicTypes

Methods

ppr :: OccInfo -> SDoc #

pprPrec :: Rational -> OccInfo -> SDoc #

type InterestingCxt = Bool #

Interesting Context

type InsideLam = Bool #

Inside Lambda

data TailCallInfo #

Instances

Instances details
Eq TailCallInfo 
Instance details

Defined in BasicTypes

Outputable TailCallInfo 
Instance details

Defined in BasicTypes

data DefMethSpec ty #

Default Method Specification

Constructors

VanillaDM 
GenericDM ty 

Instances

Instances details
Binary (DefMethSpec IfaceType) 
Instance details

Defined in IfaceType

Outputable (DefMethSpec ty) 
Instance details

Defined in BasicTypes

Methods

ppr :: DefMethSpec ty -> SDoc #

pprPrec :: Rational -> DefMethSpec ty -> SDoc #

data SuccessFlag #

Constructors

Succeeded 
Failed 

Instances

Instances details
Outputable SuccessFlag 
Instance details

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

Instances details
Eq SourceText 
Instance details

Defined in BasicTypes

Data SourceText 
Instance details

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 
Instance details

Defined in BasicTypes

Outputable SourceText 
Instance details

Defined in BasicTypes

Annotate (SourceText, FastString) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

type PhaseNum = Int #

Phase Number

data CompilerPhase #

Constructors

Phase PhaseNum 
InitialPhase 

Instances

Instances details
Outputable CompilerPhase 
Instance details

Defined in BasicTypes

data Activation #

Instances

Instances details
Eq Activation 
Instance details

Defined in BasicTypes

Data Activation 
Instance details

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 
Instance details

Defined in BasicTypes

data RuleMatchInfo #

Rule Match Information

Constructors

ConLike 
FunLike 

Instances

Instances details
Eq RuleMatchInfo 
Instance details

Defined in BasicTypes

Data RuleMatchInfo 
Instance details

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 
Instance details

Defined in BasicTypes

Outputable RuleMatchInfo 
Instance details

Defined in BasicTypes

data InlinePragma #

Instances

Instances details
Eq InlinePragma 
Instance details

Defined in BasicTypes

Data InlinePragma 
Instance details

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 
Instance details

Defined in BasicTypes

data InlineSpec #

Inline Specification

Instances

Instances details
Eq InlineSpec 
Instance details

Defined in BasicTypes

Data InlineSpec 
Instance details

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 
Instance details

Defined in BasicTypes

Outputable InlineSpec 
Instance details

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.

Constructors

IL 

Instances

Instances details
Eq IntegralLit 
Instance details

Defined in BasicTypes

Data IntegralLit 
Instance details

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 
Instance details

Defined in BasicTypes

Show IntegralLit 
Instance details

Defined in BasicTypes

Outputable IntegralLit 
Instance details

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.

Constructors

FL 

Instances

Instances details
Eq FractionalLit 
Instance details

Defined in BasicTypes

Data FractionalLit 
Instance details

Defined in BasicTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FractionalLit -> c FractionalLit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FractionalLit #

toConstr :: FractionalLit -> Constr #

dataTypeOf :: FractionalLit -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FractionalLit) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FractionalLit) #

gmapT :: (forall b. Data b => b -> b) -> FractionalLit -> FractionalLit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FractionalLit -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FractionalLit -> r #

gmapQ :: (forall d. Data d => d -> u) -> FractionalLit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FractionalLit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FractionalLit -> m FractionalLit #

Ord FractionalLit 
Instance details

Defined in BasicTypes

Show FractionalLit 
Instance details

Defined in BasicTypes

Outputable FractionalLit 
Instance details

Defined in BasicTypes

data SpliceExplicitFlag #

Constructors

ExplicitSplice

= $(f x y)

ImplicitSplice

= f x y, i.e. a naked top level expression

Instances

Instances details
Data SpliceExplicitFlag 
Instance details

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

Constructors

TypeLevel 
KindLevel 

Instances

Instances details
Eq TypeOrKind 
Instance details

Defined in BasicTypes

Outputable TypeOrKind 
Instance details

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

buildSynTyCon #

Arguments

:: Name 
-> [KnotTied TyConBinder] 
-> Kind

result kind

-> [Role] 
-> KnotTied Type 
-> TyCon 

buildAlgTyCon #

Arguments

:: Name 
-> [TyVar]

Kind variables and type variables

-> [Role] 
-> Maybe CType 
-> ThetaType

Stupid theta

-> AlgTyConRhs 
-> Bool

True = was declared in GADT syntax

-> AlgTyConFlav 
-> TyCon 

splitDataProductType_maybe #

Arguments

:: Type

A product type, perhaps

-> Maybe (TyCon, [Type], DataCon, [Type]) 

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

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.

specialPromotedDc :: DataCon -> Bool #

Should this DataCon be allowed in a type even without -XDataKinds? Currently, only Lifted & Unlifted

isVanillaDataCon :: DataCon -> Bool #

Vanilla DataCons are those that are nice boring Haskell 98 constructors

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

dataConInstArgTys #

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.

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 ThetaTypes 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

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 DataCons runtime representation type See Note [DataCon arities]

isNullarySrcDataCon :: DataCon -> Bool #

Return whether there are any argument types for this DataCons 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) #

Extract the label and type for any given labelled field of the DataCon, or return Nothing if the field does not belong to it

dataConFieldType :: DataCon -> FieldLabelString -> Type #

Extract the type for any given labelled field of the DataCon

dataConImplicitTyThings :: DataCon -> [TyThing] #

Find all the Ids 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 #

Get the Id of the DataCon worker: a function that is the "actual" constructor and has no top level binding in the program. The type may be different from the obvious one written in the source program. Panics if there is no such Id for this DataCon

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.

dataConTag :: DataCon -> ConTag #

The tag used for ordering DataCons

mkDataCon #

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 TyVarBinders. These must be Inferred/Specified. See Note [TyVarBinders in DataCons]

-> [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 RuntimeRepInfo

-> KnotTied TyCon

Representation type constructor

-> ConTag

Constructor tag

-> ThetaType

The "stupid theta", context of the data declaration e.g. data Eq a => T a ...

-> Id

Worker Id

-> DataConRep

Representation

-> DataCon 

Build a new data constructor

eqHsBang :: HsImplBang -> HsImplBang -> Bool #

Compare strictness annotations

filterEqSpec :: [EqSpec] -> [TyVar] -> [TyVar] #

Filter out any TyVars mentioned in an EqSpec.

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.

mkEqSpec :: TyVar -> Type -> EqSpec #

Make a non-dependent EqSpec

data HsSrcBang #

Haskell Source Bang

Bangs on data constructor arguments as the user wrote them in the source code.

(HsSrcBang _ SrcUnpack SrcLazy) and (HsSrcBang _ SrcUnpack NoSrcStrict) (without StrictData) makes no sense, we emit a warning (in checkValidDataCon) and treat it like (HsSrcBang _ NoSrcUnpack SrcLazy)

Instances

Instances details
Data HsSrcBang 
Instance details

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 
Instance details

Defined in DataCon

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

Instances details
Data HsImplBang 
Instance details

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 
Instance details

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

Instances details
Eq SrcStrictness 
Instance details

Defined in DataCon

Data SrcStrictness 
Instance details

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 
Instance details

Defined in DataCon

Outputable SrcStrictness 
Instance details

Defined in DataCon

data SrcUnpackedness #

Source Unpackedness

What unpackedness the user requested

Constructors

SrcUnpack

{--} specified

SrcNoUnpack

{--} specified

NoSrcUnpack

no unpack pragma

Instances

Instances details
Eq SrcUnpackedness 
Instance details

Defined in DataCon

Data SrcUnpackedness 
Instance details

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 
Instance details

Defined in DataCon

Outputable SrcUnpackedness 
Instance details

Defined in DataCon

data StrictnessMark #

Instances

Instances details
Outputable StrictnessMark 
Instance details

Defined in DataCon

dataConName :: DataCon -> Name #

The Name of the DataCon, giving it a unique, rooted identification

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] #

TyCoVarBinders 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

data DataCon #

A data constructor

Instances

Instances details
Eq DataCon 
Instance details

Defined in DataCon

Methods

(==) :: DataCon -> DataCon -> Bool #

(/=) :: DataCon -> DataCon -> Bool #

Data DataCon 
Instance details

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 
Instance details

Defined in DataCon

Uniquable DataCon 
Instance details

Defined in DataCon

Methods

getUnique :: DataCon -> Unique #

Outputable DataCon 
Instance details

Defined in DataCon

Methods

ppr :: DataCon -> SDoc #

pprPrec :: Rational -> DataCon -> SDoc #

OutputableBndr DataCon 
Instance details

Defined in DataCon

data DataConRep #

Data Constructor Representation See Note [Data constructor workers and wrappers]

data EqSpec #

An EqSpec is a tyvar/type pair representing an equality made in rejigging a GADT constructor

Instances

Instances details
Outputable EqSpec 
Instance details

Defined in DataCon

Methods

ppr :: EqSpec -> SDoc #

pprPrec :: Rational -> EqSpec -> SDoc #

type FieldLabelString = FastString #

Field labels are just represented as strings; they are not necessarily unique (even within a module)

data FieldLbl a #

Fields in an algebraic record type

Constructors

FieldLabel 

Fields

Instances

Instances details
Functor FieldLbl 
Instance details

Defined in FieldLabel

Methods

fmap :: (a -> b) -> FieldLbl a -> FieldLbl b #

(<$) :: a -> FieldLbl b -> FieldLbl a #

Foldable FieldLbl 
Instance details

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 #

toList :: FieldLbl a -> [a] #

null :: FieldLbl a -> Bool #

length :: FieldLbl a -> Int #

elem :: Eq a => a -> FieldLbl a -> Bool #

maximum :: Ord a => FieldLbl a -> a #

minimum :: Ord a => FieldLbl a -> a #

sum :: Num a => FieldLbl a -> a #

product :: Num a => FieldLbl a -> a #

Traversable FieldLbl 
Instance details

Defined in FieldLabel

Methods

traverse :: Applicative f => (a -> f b) -> FieldLbl a -> f (FieldLbl b) #

sequenceA :: Applicative f => FieldLbl (f a) -> f (FieldLbl a) #

mapM :: Monad m => (a -> m b) -> FieldLbl a -> m (FieldLbl b) #

sequence :: Monad m => FieldLbl (m a) -> m (FieldLbl a) #

Eq a => Eq (FieldLbl a) 
Instance details

Defined in FieldLabel

Methods

(==) :: FieldLbl a -> FieldLbl a -> Bool #

(/=) :: FieldLbl a -> FieldLbl a -> Bool #

Data a => Data (FieldLbl a) 
Instance details

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) 
Instance details

Defined in FieldLabel

Methods

put_ :: BinHandle -> FieldLbl a -> IO () #

put :: BinHandle -> FieldLbl a -> IO (Bin (FieldLbl a)) #

get :: BinHandle -> IO (FieldLbl a) #

Outputable a => Outputable (FieldLbl a) 
Instance details

Defined in FieldLabel

Methods

ppr :: FieldLbl a -> SDoc #

pprPrec :: Rational -> FieldLbl a -> SDoc #

ToHie (IEContext (Located (FieldLbl Name))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located (FieldLbl Name)) -> HieM [HieAST Type]

fIRST_TAG :: ConTag #

Tags are allocated from here for real constructors or for superclass selectors

type ConTag = Int #

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

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*> and liftA2).

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).

Minimal complete definition

pure, ((<*>) | liftA2)

Methods

pure :: a -> f a #

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 <*> as' can be understood as the do 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: 'liftA2 f as bs' can be understood as the do 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 *> bs' can be understood as the do 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 <* bs' can be understood as the do expression

do a <- as
   bs
   pure a

Instances

Instances details
Applicative []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> [a] #

(<*>) :: [a -> b] -> [a] -> [b] #

liftA2 :: (a -> b -> c) -> [a] -> [b] -> [c] #

(*>) :: [a] -> [b] -> [b] #

(<*) :: [a] -> [b] -> [a] #

Applicative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Applicative IO

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> IO a #

(<*>) :: IO (a -> b) -> IO a -> IO b #

liftA2 :: (a -> b -> c) -> IO a -> IO b -> IO c #

(*>) :: IO a -> IO b -> IO b #

(<*) :: IO a -> IO b -> IO a #

Applicative Par1

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> Par1 a #

(<*>) :: Par1 (a -> b) -> Par1 a -> Par1 b #

liftA2 :: (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c #

(*>) :: Par1 a -> Par1 b -> Par1 b #

(<*) :: Par1 a -> Par1 b -> Par1 a #

Applicative Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

pure :: a -> Q a #

(<*>) :: Q (a -> b) -> Q a -> Q b #

liftA2 :: (a -> b -> c) -> Q a -> Q b -> Q c #

(*>) :: Q a -> Q b -> Q b #

(<*) :: Q a -> Q b -> Q a #

Applicative IResult 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

pure :: a -> IResult a #

(<*>) :: IResult (a -> b) -> IResult a -> IResult b #

liftA2 :: (a -> b -> c) -> IResult a -> IResult b -> IResult c #

(*>) :: IResult a -> IResult b -> IResult b #

(<*) :: IResult a -> IResult b -> IResult a #

Applicative Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Applicative Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Applicative Tree 
Instance details

Defined in Data.Tree

Methods

pure :: a -> Tree a #

(<*>) :: Tree (a -> b) -> Tree a -> Tree b #

liftA2 :: (a -> b -> c) -> Tree a -> Tree b -> Tree c #

(*>) :: Tree a -> Tree b -> Tree b #

(<*) :: Tree a -> Tree b -> Tree a #

Applicative NonNegative 
Instance details

Defined in Algebra.Graph.Label

Methods

pure :: a -> NonNegative a #

(<*>) :: NonNegative (a -> b) -> NonNegative a -> NonNegative b #

liftA2 :: (a -> b -> c) -> NonNegative a -> NonNegative b -> NonNegative c #

(*>) :: NonNegative a -> NonNegative b -> NonNegative b #

(<*) :: NonNegative a -> NonNegative b -> NonNegative a #

Applicative Minimum 
Instance details

Defined in Algebra.Graph.Label

Methods

pure :: a -> Minimum a #

(<*>) :: Minimum (a -> b) -> Minimum a -> Minimum b #

liftA2 :: (a -> b -> c) -> Minimum a -> Minimum b -> Minimum c #

(*>) :: Minimum a -> Minimum b -> Minimum b #

(<*) :: Minimum a -> Minimum b -> Minimum a #

Applicative Graph

<*> is a good consumer of its first agument and producer.

Instance details

Defined in Algebra.Graph

Methods

pure :: a -> Graph a #

(<*>) :: Graph (a -> b) -> Graph a -> Graph b #

liftA2 :: (a -> b -> c) -> Graph a -> Graph b -> Graph c #

(*>) :: Graph a -> Graph b -> Graph b #

(<*) :: Graph a -> Graph b -> Graph a #

Applicative List 
Instance details

Defined in Algebra.Graph.Internal

Methods

pure :: a -> List a #

(<*>) :: List (a -> b) -> List a -> List b #

liftA2 :: (a -> b -> c) -> List a -> List b -> List c #

(*>) :: List a -> List b -> List b #

(<*) :: List a -> List b -> List a #

Applicative Concurrently 
Instance details

Defined in Control.Concurrent.Async

Applicative Complex

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

pure :: a -> Complex a #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b #

liftA2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c #

(*>) :: Complex a -> Complex b -> Complex b #

(<*) :: Complex a -> Complex b -> Complex a #

Applicative Min

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

liftA2 :: (a -> b -> c) -> Min a -> Min b -> Min c #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Applicative Max

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

liftA2 :: (a -> b -> c) -> Max a -> Max b -> Max c #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Applicative First

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

liftA2 :: (a -> b -> c) -> First a -> First b -> First c #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative Option

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

pure :: a -> Option a #

(<*>) :: Option (a -> b) -> Option a -> Option b #

liftA2 :: (a -> b -> c) -> Option a -> Option b -> Option c #

(*>) :: Option a -> Option b -> Option b #

(<*) :: Option a -> Option b -> Option a #

Applicative ZipList
f <$> ZipList xs1 <*> ... <*> ZipList xsN
    = ZipList (zipWithN f xs1 ... xsN)

where zipWithN refers to the zipWith function of the appropriate arity (zipWith, zipWith3, zipWith4, ...). For example:

(\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
    = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
    = ZipList {getZipList = ["a5","b6b6","c7c7c7"]}

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

pure :: a -> ZipList a #

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b #

liftA2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c #

(*>) :: ZipList a -> ZipList b -> ZipList b #

(<*) :: ZipList a -> ZipList b -> ZipList a #

Applicative Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Applicative STM

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

pure :: a -> STM a #

(<*>) :: STM (a -> b) -> STM a -> STM b #

liftA2 :: (a -> b -> c) -> STM a -> STM b -> STM c #

(*>) :: STM a -> STM b -> STM b #

(<*) :: STM a -> STM b -> STM a #

Applicative First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

liftA2 :: (a -> b -> c) -> First a -> First b -> First c #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Dual a #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b #

liftA2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c #

(*>) :: Dual a -> Dual b -> Dual b #

(<*) :: Dual a -> Dual b -> Dual a #

Applicative Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Applicative Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Applicative Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

pure :: a -> Down a #

(<*>) :: Down (a -> b) -> Down a -> Down b #

liftA2 :: (a -> b -> c) -> Down a -> Down b -> Down c #

(*>) :: Down a -> Down b -> Down b #

(<*) :: Down a -> Down b -> Down a #

Applicative ReadPrec

Since: base-4.6.0.0

Instance details

Defined in Text.ParserCombinators.ReadPrec

Methods

pure :: a -> ReadPrec a #

(<*>) :: ReadPrec (a -> b) -> ReadPrec a -> ReadPrec b #

liftA2 :: (a -> b -> c) -> ReadPrec a -> ReadPrec b -> ReadPrec c #

(*>) :: ReadPrec a -> ReadPrec b -> ReadPrec b #

(<*) :: ReadPrec a -> ReadPrec b -> ReadPrec a #

Applicative ReadP

Since: base-4.6.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

pure :: a -> ReadP a #

(<*>) :: ReadP (a -> b) -> ReadP a -> ReadP b #

liftA2 :: (a -> b -> c) -> ReadP a -> ReadP b -> ReadP c #

(*>) :: ReadP a -> ReadP b -> ReadP b #

(<*) :: ReadP a -> ReadP b -> ReadP a #

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Applicative PutM 
Instance details

Defined in Data.Binary.Put

Methods

pure :: a -> PutM a #

(<*>) :: PutM (a -> b) -> PutM a -> PutM b #

liftA2 :: (a -> b -> c) -> PutM a -> PutM b -> PutM c #

(*>) :: PutM a -> PutM b -> PutM b #

(<*) :: PutM a -> PutM b -> PutM a #

Applicative Get 
Instance details

Defined in Data.Binary.Get.Internal

Methods

pure :: a -> Get a #

(<*>) :: Get (a -> b) -> Get a -> Get b #

liftA2 :: (a -> b -> c) -> Get a -> Get b -> Get c #

(*>) :: Get a -> Get b -> Get b #

(<*) :: Get a -> Get b -> Get a #

Applicative Put 
Instance details

Defined in Data.ByteString.Builder.Internal

Methods

pure :: a -> Put a #

(<*>) :: Put (a -> b) -> Put a -> Put b #

liftA2 :: (a -> b -> c) -> Put a -> Put b -> Put c #

(*>) :: Put a -> Put b -> Put b #

(<*) :: Put a -> Put b -> Put a #

Applicative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

pure :: a -> Seq a #

(<*>) :: Seq (a -> b) -> Seq a -> Seq b #

liftA2 :: (a -> b -> c) -> Seq a -> Seq b -> Seq c #

(*>) :: Seq a -> Seq b -> Seq b #

(<*) :: Seq a -> Seq b -> Seq a #

Applicative DNonEmpty 
Instance details

Defined in Data.DList.DNonEmpty.Internal

Methods

pure :: a -> DNonEmpty a #

(<*>) :: DNonEmpty (a -> b) -> DNonEmpty a -> DNonEmpty b #

liftA2 :: (a -> b -> c) -> DNonEmpty a -> DNonEmpty b -> DNonEmpty c #

(*>) :: DNonEmpty a -> DNonEmpty b -> DNonEmpty b #

(<*) :: DNonEmpty a -> DNonEmpty b -> DNonEmpty a #

Applicative DList 
Instance details

Defined in Data.DList.Internal

Methods

pure :: a -> DList a #

(<*>) :: DList (a -> b) -> DList a -> DList b #

liftA2 :: (a -> b -> c) -> DList a -> DList b -> DList c #

(*>) :: DList a -> DList b -> DList b #

(<*) :: DList a -> DList b -> DList a #

Applicative TcPluginM 
Instance details

Defined in TcRnTypes

Methods

pure :: a -> TcPluginM a #

(<*>) :: TcPluginM (a -> b) -> TcPluginM a -> TcPluginM b #

liftA2 :: (a -> b -> c) -> TcPluginM a -> TcPluginM b -> TcPluginM c #

(*>) :: TcPluginM a -> TcPluginM b -> TcPluginM b #

(<*) :: TcPluginM a -> TcPluginM b -> TcPluginM a #

Applicative Ghc 
Instance details

Defined in GhcMonad

Methods

pure :: a -> Ghc a #

(<*>) :: Ghc (a -> b) -> Ghc a -> Ghc b #

liftA2 :: (a -> b -> c) -> Ghc a -> Ghc b -> Ghc c #

(*>) :: Ghc a -> Ghc b -> Ghc b #

(<*) :: Ghc a -> Ghc b -> Ghc a #

Applicative CompPipeline 
Instance details

Defined in PipelineMonad

Applicative Hsc 
Instance details

Defined in HscTypes

Methods

pure :: a -> Hsc a #

(<*>) :: Hsc (a -> b) -> Hsc a -> Hsc b #

liftA2 :: (a -> b -> c) -> Hsc a -> Hsc b -> Hsc c #

(*>) :: Hsc a -> Hsc b -> Hsc b #

(<*) :: Hsc a -> Hsc b -> Hsc a #

Applicative PV 
Instance details

Defined in RdrHsSyn

Methods

pure :: a -> PV a #

(<*>) :: PV (a -> b) -> PV a -> PV b #

liftA2 :: (a -> b -> c) -> PV a -> PV b -> PV c #

(*>) :: PV a -> PV b -> PV b #

(<*) :: PV a -> PV b -> PV a #

Applicative UnifyResultM 
Instance details

Defined in Unify

Applicative P 
Instance details

Defined in Lexer

Methods

pure :: a -> P a #

(<*>) :: P (a -> b) -> P a -> P b #

liftA2 :: (a -> b -> c) -> P a -> P b -> P c #

(*>) :: P a -> P b -> P b #

(<*) :: P a -> P b -> P a #

Applicative CoreM 
Instance details

Defined in CoreMonad

Methods

pure :: a -> CoreM a #

(<*>) :: CoreM (a -> b) -> CoreM a -> CoreM b #

liftA2 :: (a -> b -> c) -> CoreM a -> CoreM b -> CoreM c #

(*>) :: CoreM a -> CoreM b -> CoreM b #

(<*) :: CoreM a -> CoreM b -> CoreM a #

Applicative UniqSM 
Instance details

Defined in UniqSupply

Methods

pure :: a -> UniqSM a #

(<*>) :: UniqSM (a -> b) -> UniqSM a -> UniqSM b #

liftA2 :: (a -> b -> c) -> UniqSM a -> UniqSM b -> UniqSM c #

(*>) :: UniqSM a -> UniqSM b -> UniqSM b #

(<*) :: UniqSM a -> UniqSM b -> UniqSM a #

Applicative Pair 
Instance details

Defined in Pair

Methods

pure :: a -> Pair a #

(<*>) :: Pair (a -> b) -> Pair a -> Pair b #

liftA2 :: (a -> b -> c) -> Pair a -> Pair b -> Pair c #

(*>) :: Pair a -> Pair b -> Pair b #

(<*) :: Pair a -> Pair b -> Pair a #

Applicative Heapsize 
Instance details

Defined in HeapSize

Methods

pure :: a -> Heapsize a #

(<*>) :: Heapsize (a -> b) -> Heapsize a -> Heapsize b #

liftA2 :: (a -> b -> c) -> Heapsize a -> Heapsize b -> Heapsize c #

(*>) :: Heapsize a -> Heapsize b -> Heapsize b #

(<*) :: Heapsize a -> Heapsize b -> Heapsize a #

Applicative CradleLoadResult 
Instance details

Defined in HIE.Bios.Types

Applicative Rules 
Instance details

Defined in Development.IDE.Graph.Internal.Rules

Methods

pure :: a -> Rules a #

(<*>) :: Rules (a -> b) -> Rules a -> Rules b #

liftA2 :: (a -> b -> c) -> Rules a -> Rules b -> Rules c #

(*>) :: Rules a -> Rules b -> Rules b #

(<*) :: Rules a -> Rules b -> Rules a #

Applicative Action 
Instance details

Defined in Development.IDE.Graph.Internal.Action

Methods

pure :: a -> Action a #

(<*>) :: Action (a -> b) -> Action a -> Action b #

liftA2 :: (a -> b -> c) -> Action a -> Action b -> Action c #

(*>) :: Action a -> Action b -> Action b #

(<*) :: Action a -> Action b -> Action a #

Applicative Eval 
Instance details

Defined in Control.Parallel.Strategies

Methods

pure :: a -> Eval a #

(<*>) :: Eval (a -> b) -> Eval a -> Eval b #

liftA2 :: (a -> b -> c) -> Eval a -> Eval b -> Eval c #

(*>) :: Eval a -> Eval b -> Eval b #

(<*) :: Eval a -> Eval b -> Eval a #

Applicative Vector 
Instance details

Defined in Data.Vector

Methods

pure :: a -> Vector a #

(<*>) :: Vector (a -> b) -> Vector a -> Vector b #

liftA2 :: (a -> b -> c) -> Vector a -> Vector b -> Vector c #

(*>) :: Vector a -> Vector b -> Vector b #

(<*) :: Vector a -> Vector b -> Vector a #

Applicative ReadM 
Instance details

Defined in Options.Applicative.Types

Methods

pure :: a -> ReadM a #

(<*>) :: ReadM (a -> b) -> ReadM a -> ReadM b #

liftA2 :: (a -> b -> c) -> ReadM a -> ReadM b -> ReadM c #

(*>) :: ReadM a -> ReadM b -> ReadM b #

(<*) :: ReadM a -> ReadM b -> ReadM a #

Applicative Parser 
Instance details

Defined in Options.Applicative.Types

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Applicative ParserM 
Instance details

Defined in Options.Applicative.Types

Methods

pure :: a -> ParserM a #

(<*>) :: ParserM (a -> b) -> ParserM a -> ParserM b #

liftA2 :: (a -> b -> c) -> ParserM a -> ParserM b -> ParserM c #

(*>) :: ParserM a -> ParserM b -> ParserM b #

(<*) :: ParserM a -> ParserM b -> ParserM a #

Applicative ParserResult 
Instance details

Defined in Options.Applicative.Types

Applicative SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Methods

pure :: a -> SmallArray a #

(<*>) :: SmallArray (a -> b) -> SmallArray a -> SmallArray b #

liftA2 :: (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c #

(*>) :: SmallArray a -> SmallArray b -> SmallArray b #

(<*) :: SmallArray a -> SmallArray b -> SmallArray a #

Applicative Array 
Instance details

Defined in Data.Primitive.Array

Methods

pure :: a -> Array a #

(<*>) :: Array (a -> b) -> Array a -> Array b #

liftA2 :: (a -> b -> c) -> Array a -> Array b -> Array c #

(*>) :: Array a -> Array b -> Array b #

(<*) :: Array a -> Array b -> Array a #

Applicative Rules 
Instance details

Defined in Development.Shake.Internal.Core.Rules

Methods

pure :: a -> Rules a #

(<*>) :: Rules (a -> b) -> Rules a -> Rules b #

liftA2 :: (a -> b -> c) -> Rules a -> Rules b -> Rules c #

(*>) :: Rules a -> Rules b -> Rules b #

(<*) :: Rules a -> Rules b -> Rules a #

Applicative Action 
Instance details

Defined in Development.Shake.Internal.Core.Types

Methods

pure :: a -> Action a #

(<*>) :: Action (a -> b) -> Action a -> Action b #

liftA2 :: (a -> b -> c) -> Action a -> Action b -> Action c #

(*>) :: Action a -> Action b -> Action b #

(<*) :: Action a -> Action b -> Action a #

Applicative RowParser 
Instance details

Defined in Database.SQLite.Simple.Internal

Methods

pure :: a -> RowParser a #

(<*>) :: RowParser (a -> b) -> RowParser a -> RowParser b #

liftA2 :: (a -> b -> c) -> RowParser a -> RowParser b -> RowParser c #

(*>) :: RowParser a -> RowParser b -> RowParser b #

(<*) :: RowParser a -> RowParser b -> RowParser a #

Applicative Flat 
Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> Flat a #

(<*>) :: Flat (a -> b) -> Flat a -> Flat b #

liftA2 :: (a -> b -> c) -> Flat a -> Flat b -> Flat c #

(*>) :: Flat a -> Flat b -> Flat b #

(<*) :: Flat a -> Flat b -> Flat a #

Applicative FlatApp 
Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> FlatApp a #

(<*>) :: FlatApp (a -> b) -> FlatApp a -> FlatApp b #

liftA2 :: (a -> b -> c) -> FlatApp a -> FlatApp b -> FlatApp c #

(*>) :: FlatApp a -> FlatApp b -> FlatApp b #

(<*) :: FlatApp a -> FlatApp b -> FlatApp a #

Applicative Id 
Instance details

Defined in Data.Vector.Fusion.Util

Methods

pure :: a -> Id a #

(<*>) :: Id (a -> b) -> Id a -> Id b #

liftA2 :: (a -> b -> c) -> Id a -> Id b -> Id c #

(*>) :: Id a -> Id b -> Id b #

(<*) :: Id a -> Id b -> Id a #

Applicative Box 
Instance details

Defined in Data.Vector.Fusion.Util

Methods

pure :: a -> Box a #

(<*>) :: Box (a -> b) -> Box a -> Box b #

liftA2 :: (a -> b -> c) -> Box a -> Box b -> Box c #

(*>) :: Box a -> Box b -> Box b #

(<*) :: Box a -> Box b -> Box a #

Applicative P

Since: base-4.5.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

pure :: a -> P a #

(<*>) :: P (a -> b) -> P a -> P b #

liftA2 :: (a -> b -> c) -> P a -> P b -> P c #

(*>) :: P a -> P b -> P b #

(<*) :: P a -> P b -> P a #

Applicative PositionResult Source # 
Instance details

Defined in Development.IDE.Core.PositionMapping

Applicative NormM 
Instance details

Defined in FamInstEnv

Methods

pure :: a -> NormM a #

(<*>) :: NormM (a -> b) -> NormM a -> NormM b #

liftA2 :: (a -> b -> c) -> NormM a -> NormM b -> NormM c #

(*>) :: NormM a -> NormM b -> NormM b #

(<*) :: NormM a -> NormM b -> NormM a #

Applicative DFFV 
Instance details

Defined in TidyPgm

Methods

pure :: a -> DFFV a #

(<*>) :: DFFV (a -> b) -> DFFV a -> DFFV b #

liftA2 :: (a -> b -> c) -> DFFV a -> DFFV b -> DFFV c #

(*>) :: DFFV a -> DFFV b -> DFFV b #

(<*) :: DFFV a -> DFFV b -> DFFV a #

Applicative UM 
Instance details

Defined in Unify

Methods

pure :: a -> UM a #

(<*>) :: UM (a -> b) -> UM a -> UM b #

liftA2 :: (a -> b -> c) -> UM a -> UM b -> UM c #

(*>) :: UM a -> UM b -> UM b #

(<*) :: UM a -> UM b -> UM a #

Applicative Extended 
Instance details

Defined in Algebra.Graph.Label

Methods

pure :: a -> Extended a #

(<*>) :: Extended (a -> b) -> Extended a -> Extended b #

liftA2 :: (a -> b -> c) -> Extended a -> Extended b -> Extended c #

(*>) :: Extended a -> Extended b -> Extended b #

(<*) :: Extended a -> Extended b -> Extended a #

Applicative IdeAction Source # 
Instance details

Defined in Development.IDE.Core.Shake

Methods

pure :: a -> IdeAction a #

(<*>) :: IdeAction (a -> b) -> IdeAction a -> IdeAction b #

liftA2 :: (a -> b -> c) -> IdeAction a -> IdeAction b -> IdeAction c #

(*>) :: IdeAction a -> IdeAction b -> IdeAction b #

(<*) :: IdeAction a -> IdeAction b -> IdeAction a #

Applicative (Either e)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

pure :: a -> Either e a #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b #

liftA2 :: (a -> b -> c) -> Either e a -> Either e b -> Either e c #

(*>) :: Either e a -> Either e b -> Either e b #

(<*) :: Either e a -> Either e b -> Either e a #

Applicative (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> U1 a #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b #

liftA2 :: (a -> b -> c) -> U1 a -> U1 b -> U1 c #

(*>) :: U1 a -> U1 b -> U1 b #

(<*) :: U1 a -> U1 b -> U1 a #

Monoid a => Applicative ((,) a)

For tuples, the Monoid constraint on a determines how the first values merge. For example, Strings concatenate:

("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, a0) #

(<*>) :: (a, a0 -> b) -> (a, a0) -> (a, b) #

liftA2 :: (a0 -> b -> c) -> (a, a0) -> (a, b) -> (a, c) #

(*>) :: (a, a0) -> (a, b) -> (a, b) #

(<*) :: (a, a0) -> (a, b) -> (a, a0) #

Representable f => Applicative (Co f) 
Instance details

Defined in Data.Functor.Rep

Methods

pure :: a -> Co f a #

(<*>) :: Co f (a -> b) -> Co f a -> Co f b #

liftA2 :: (a -> b -> c) -> Co f a -> Co f b -> Co f c #

(*>) :: Co f a -> Co f b -> Co f b #

(<*) :: Co f a -> Co f b -> Co f a #

Applicative (ST s)

Since: base-4.4.0.0

Instance details

Defined in GHC.ST

Methods

pure :: a -> ST s a #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b #

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c #

(*>) :: ST s a -> ST s b -> ST s b #

(<*) :: ST s a -> ST s b -> ST s a #

Applicative (Parser i) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

pure :: a -> Parser i a #

(<*>) :: Parser i (a -> b) -> Parser i a -> Parser i b #

liftA2 :: (a -> b -> c) -> Parser i a -> Parser i b -> Parser i c #

(*>) :: Parser i a -> Parser i b -> Parser i b #

(<*) :: Parser i a -> Parser i b -> Parser i a #

Applicative (ST s)

Since: base-2.1

Instance details

Defined in Control.Monad.ST.Lazy.Imp

Methods

pure :: a -> ST s a #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b #

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c #

(*>) :: ST s a -> ST s b -> ST s b #

(<*) :: ST s a -> ST s b -> ST s a #

Monad m => Applicative (WrappedMonad m)

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

pure :: a -> WrappedMonad m a #

(<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c #

(*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Applicative (ArrowMonad a)

Since: base-4.6.0.0

Instance details

Defined in Control.Arrow

Methods

pure :: a0 -> ArrowMonad a a0 #

(<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b #

liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c #

(*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b #

(<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

(Functor m, Monad m) => Applicative (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

pure :: a -> MaybeT m a #

(<*>) :: MaybeT m (a -> b) -> MaybeT m a -> MaybeT m b #

liftA2 :: (a -> b -> c) -> MaybeT m a -> MaybeT m b -> MaybeT m c #

(*>) :: MaybeT m a -> MaybeT m b -> MaybeT m b #

(<*) :: MaybeT m a -> MaybeT m b -> MaybeT m a #

Monad m => Applicative (ZipSource m) 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

pure :: a -> ZipSource m a #

(<*>) :: ZipSource m (a -> b) -> ZipSource m a -> ZipSource m b #

liftA2 :: (a -> b -> c) -> ZipSource m a -> ZipSource m b -> ZipSource m c #

(*>) :: ZipSource m a -> ZipSource m b -> ZipSource m b #

(<*) :: ZipSource m a -> ZipSource m b -> ZipSource m a #

Applicative m => Applicative (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

pure :: a -> ResourceT m a #

(<*>) :: ResourceT m (a -> b) -> ResourceT m a -> ResourceT m b #

liftA2 :: (a -> b -> c) -> ResourceT m a -> ResourceT m b -> ResourceT m c #

(*>) :: ResourceT m a -> ResourceT m b -> ResourceT m b #

(<*) :: ResourceT m a -> ResourceT m b -> ResourceT m a #

Alternative f => Applicative (Cofree f) 
Instance details

Defined in Control.Comonad.Cofree

Methods

pure :: a -> Cofree f a #

(<*>) :: Cofree f (a -> b) -> Cofree f a -> Cofree f b #

liftA2 :: (a -> b -> c) -> Cofree f a -> Cofree f b -> Cofree f c #

(*>) :: Cofree f a -> Cofree f b -> Cofree f b #

(<*) :: Cofree f a -> Cofree f b -> Cofree f a #

Functor f => Applicative (Free f) 
Instance details

Defined in Control.Monad.Free

Methods

pure :: a -> Free f a #

(<*>) :: Free f (a -> b) -> Free f a -> Free f b #

liftA2 :: (a -> b -> c) -> Free f a -> Free f b -> Free f c #

(*>) :: Free f a -> Free f b -> Free f b #

(<*) :: Free f a -> Free f b -> Free f a #

Applicative m => Applicative (GhcT m) 
Instance details

Defined in GhcMonad

Methods

pure :: a -> GhcT m a #

(<*>) :: GhcT m (a -> b) -> GhcT m a -> GhcT m b #

liftA2 :: (a -> b -> c) -> GhcT m a -> GhcT m b -> GhcT m c #

(*>) :: GhcT m a -> GhcT m b -> GhcT m b #

(<*) :: GhcT m a -> GhcT m b -> GhcT m a #

Applicative (IOEnv m) 
Instance details

Defined in IOEnv

Methods

pure :: a -> IOEnv m a #

(<*>) :: IOEnv m (a -> b) -> IOEnv m a -> IOEnv m b #

liftA2 :: (a -> b -> c) -> IOEnv m a -> IOEnv m b -> IOEnv m c #

(*>) :: IOEnv m a -> IOEnv m b -> IOEnv m b #

(<*) :: IOEnv m a -> IOEnv m b -> IOEnv m a #

Monad m => Applicative (EwM m) 
Instance details

Defined in CmdLineParser

Methods

pure :: a -> EwM m a #

(<*>) :: EwM m (a -> b) -> EwM m a -> EwM m b #

liftA2 :: (a -> b -> c) -> EwM m a -> EwM m b -> EwM m c #

(*>) :: EwM m a -> EwM m b -> EwM m b #

(<*) :: EwM m a -> EwM m b -> EwM m a #

Applicative (CmdLineP s) 
Instance details

Defined in CmdLineParser

Methods

pure :: a -> CmdLineP s a #

(<*>) :: CmdLineP s (a -> b) -> CmdLineP s a -> CmdLineP s b #

liftA2 :: (a -> b -> c) -> CmdLineP s a -> CmdLineP s b -> CmdLineP s c #

(*>) :: CmdLineP s a -> CmdLineP s b -> CmdLineP s b #

(<*) :: CmdLineP s a -> CmdLineP s b -> CmdLineP s a #

Applicative (MaybeErr err) 
Instance details

Defined in Maybes

Methods

pure :: a -> MaybeErr err a #

(<*>) :: MaybeErr err (a -> b) -> MaybeErr err a -> MaybeErr err b #

liftA2 :: (a -> b -> c) -> MaybeErr err a -> MaybeErr err b -> MaybeErr err c #

(*>) :: MaybeErr err a -> MaybeErr err b -> MaybeErr err b #

(<*) :: MaybeErr err a -> MaybeErr err b -> MaybeErr err a #

Monad m => Applicative (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

pure :: a -> TransformT m a #

(<*>) :: TransformT m (a -> b) -> TransformT m a -> TransformT m b #

liftA2 :: (a -> b -> c) -> TransformT m a -> TransformT m b -> TransformT m c #

(*>) :: TransformT m a -> TransformT m b -> TransformT m b #

(<*) :: TransformT m a -> TransformT m b -> TransformT m a #

Monad m => Applicative (DbMonadT m) 
Instance details

Defined in HieDb.Types

Methods

pure :: a -> DbMonadT m a #

(<*>) :: DbMonadT m (a -> b) -> DbMonadT m a -> DbMonadT m b #

liftA2 :: (a -> b -> c) -> DbMonadT m a -> DbMonadT m b -> DbMonadT m c #

(*>) :: DbMonadT m a -> DbMonadT m b -> DbMonadT m b #

(<*) :: DbMonadT m a -> DbMonadT m b -> DbMonadT m a #

Applicative f => Applicative (Yoneda f) 
Instance details

Defined in Data.Functor.Yoneda

Methods

pure :: a -> Yoneda f a #

(<*>) :: Yoneda f (a -> b) -> Yoneda f a -> Yoneda f b #

liftA2 :: (a -> b -> c) -> Yoneda f a -> Yoneda f b -> Yoneda f c #

(*>) :: Yoneda f a -> Yoneda f b -> Yoneda f b #

(<*) :: Yoneda f a -> Yoneda f b -> Yoneda f a #

Applicative (ReifiedGetter s) 
Instance details

Defined in Control.Lens.Reified

Methods

pure :: a -> ReifiedGetter s a #

(<*>) :: ReifiedGetter s (a -> b) -> ReifiedGetter s a -> ReifiedGetter s b #

liftA2 :: (a -> b -> c) -> ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s c #

(*>) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s b #

(<*) :: ReifiedGetter s a -> ReifiedGetter s b -> ReifiedGetter s a #

Applicative (ReifiedFold s) 
Instance details

Defined in Control.Lens.Reified

Methods

pure :: a -> ReifiedFold s a #

(<*>) :: ReifiedFold s (a -> b) -> ReifiedFold s a -> ReifiedFold s b #

liftA2 :: (a -> b -> c) -> ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s c #

(*>) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s b #

(<*) :: ReifiedFold s a -> ReifiedFold s b -> ReifiedFold s a #

Applicative f => Applicative (Indexing f) 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

pure :: a -> Indexing f a #

(<*>) :: Indexing f (a -> b) -> Indexing f a -> Indexing f b #

liftA2 :: (a -> b -> c) -> Indexing f a -> Indexing f b -> Indexing f c #

(*>) :: Indexing f a -> Indexing f b -> Indexing f b #

(<*) :: Indexing f a -> Indexing f b -> Indexing f a #

Applicative f => Applicative (Indexing64 f) 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

pure :: a -> Indexing64 f a #

(<*>) :: Indexing64 f (a -> b) -> Indexing64 f a -> Indexing64 f b #

liftA2 :: (a -> b -> c) -> Indexing64 f a -> Indexing64 f b -> Indexing64 f c #

(*>) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f b #

(<*) :: Indexing64 f a -> Indexing64 f b -> Indexing64 f a #

Applicative f => Applicative (WrappedPoly f) 
Instance details

Defined in Data.MonoTraversable

Methods

pure :: a -> WrappedPoly f a #

(<*>) :: WrappedPoly f (a -> b) -> WrappedPoly f a -> WrappedPoly f b #

liftA2 :: (a -> b -> c) -> WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f c #

(*>) :: WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f b #

(<*) :: WrappedPoly f a -> WrappedPoly f b -> WrappedPoly f a #

Applicative m => Applicative (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

pure :: a -> ListT m a #

(<*>) :: ListT m (a -> b) -> ListT m a -> ListT m b #

liftA2 :: (a -> b -> c) -> ListT m a -> ListT m b -> ListT m c #

(*>) :: ListT m a -> ListT m b -> ListT m b #

(<*) :: ListT m a -> ListT m b -> ListT m a #

Semigroup a => Applicative (These a) 
Instance details

Defined in Data.Strict.These

Methods

pure :: a0 -> These a a0 #

(<*>) :: These a (a0 -> b) -> These a a0 -> These a b #

liftA2 :: (a0 -> b -> c) -> These a a0 -> These a b -> These a c #

(*>) :: These a a0 -> These a b -> These a b #

(<*) :: These a a0 -> These a b -> These a a0 #

Semigroup a => Applicative (These a) 
Instance details

Defined in Data.These

Methods

pure :: a0 -> These a a0 #

(<*>) :: These a (a0 -> b) -> These a a0 -> These a b #

liftA2 :: (a0 -> b -> c) -> These a a0 -> These a b -> These a c #

(*>) :: These a a0 -> These a b -> These a b #

(<*) :: These a a0 -> These a b -> These a a0 #

MonadUnliftIO m => Applicative (Concurrently m)

Since: unliftio-0.1.0.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> Concurrently m a #

(<*>) :: Concurrently m (a -> b) -> Concurrently m a -> Concurrently m b #

liftA2 :: (a -> b -> c) -> Concurrently m a -> Concurrently m b -> Concurrently m c #

(*>) :: Concurrently m a -> Concurrently m b -> Concurrently m b #

(<*) :: Concurrently m a -> Concurrently m b -> Concurrently m a #

MonadUnliftIO m => Applicative (Conc m)

Since: unliftio-0.2.9.0

Instance details

Defined in UnliftIO.Internals.Async

Methods

pure :: a -> Conc m a #

(<*>) :: Conc m (a -> b) -> Conc m a -> Conc m b #

liftA2 :: (a -> b -> c) -> Conc m a -> Conc m b -> Conc m c #

(*>) :: Conc m a -> Conc m b -> Conc m b #

(<*) :: Conc m a -> Conc m b -> Conc m a #

Applicative (SetM s) 
Instance details

Defined in Data.Graph

Methods

pure :: a -> SetM s a #

(<*>) :: SetM s (a -> b) -> SetM s a -> SetM s b #

liftA2 :: (a -> b -> c) -> SetM s a -> SetM s b -> SetM s c #

(*>) :: SetM s a -> SetM s b -> SetM s b #

(<*) :: SetM s a -> SetM s b -> SetM s a #

Applicative m => Applicative (QuoteToQuasi m) 
Instance details

Defined in Language.Haskell.TH.Syntax.Compat

Methods

pure :: a -> QuoteToQuasi m a #

(<*>) :: QuoteToQuasi m (a -> b) -> QuoteToQuasi m a -> QuoteToQuasi m b #

liftA2 :: (a -> b -> c) -> QuoteToQuasi m a -> QuoteToQuasi m b -> QuoteToQuasi m c #

(*>) :: QuoteToQuasi m a -> QuoteToQuasi m b -> QuoteToQuasi m b #

(<*) :: QuoteToQuasi m a -> QuoteToQuasi m b -> QuoteToQuasi m a #

Monad m => Applicative (ExceptStringT m) Source # 
Instance details

Defined in Development.IDE.GHC.ExactPrint

Methods

pure :: a -> ExceptStringT m a #

(<*>) :: ExceptStringT m (a -> b) -> ExceptStringT m a -> ExceptStringT m b #

liftA2 :: (a -> b -> c) -> ExceptStringT m a -> ExceptStringT m b -> ExceptStringT m c #

(*>) :: ExceptStringT m a -> ExceptStringT m b -> ExceptStringT m b #

(<*) :: ExceptStringT m a -> ExceptStringT m b -> ExceptStringT m a #

Applicative (Tracked age) Source # 
Instance details

Defined in Development.IDE.Core.UseStale

Methods

pure :: a -> Tracked age a #

(<*>) :: Tracked age (a -> b) -> Tracked age a -> Tracked age b #

liftA2 :: (a -> b -> c) -> Tracked age a -> Tracked age b -> Tracked age c #

(*>) :: Tracked age a -> Tracked age b -> Tracked age b #

(<*) :: Tracked age a -> Tracked age b -> Tracked age a #

Applicative f => Applicative (Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> Rec1 f a #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b #

liftA2 :: (a -> b -> c) -> Rec1 f a -> Rec1 f b -> Rec1 f c #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a #

(Monoid a, Monoid b) => Applicative ((,,) a b)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, b, a0) #

(<*>) :: (a, b, a0 -> b0) -> (a, b, a0) -> (a, b, b0) #

liftA2 :: (a0 -> b0 -> c) -> (a, b, a0) -> (a, b, b0) -> (a, b, c) #

(*>) :: (a, b, a0) -> (a, b, b0) -> (a, b, b0) #

(<*) :: (a, b, a0) -> (a, b, b0) -> (a, b, a0) #

Arrow a => Applicative (WrappedArrow a b)

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

pure :: a0 -> WrappedArrow a b a0 #

(<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 #

liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c #

(*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 #

(<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 #

Applicative m => Applicative (Kleisli m a)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Methods

pure :: a0 -> Kleisli m a a0 #

(<*>) :: Kleisli m a (a0 -> b) -> Kleisli m a a0 -> Kleisli m a b #

liftA2 :: (a0 -> b -> c) -> Kleisli m a a0 -> Kleisli m a b -> Kleisli m a c #

(*>) :: Kleisli m a a0 -> Kleisli m a b -> Kleisli m a b #

(<*) :: Kleisli m a a0 -> Kleisli m a b -> Kleisli m a a0 #

Monoid m => Applicative (Const m :: Type -> Type)

Since: base-2.0.1

Instance details

Defined in Data.Functor.Const

Methods

pure :: a -> Const m a #

(<*>) :: Const m (a -> b) -> Const m a -> Const m b #

liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c #

(*>) :: Const m a -> Const m b -> Const m b #

(<*) :: Const m a -> Const m b -> Const m a #

Applicative f => Applicative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Ap f a #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c #

(*>) :: Ap f a -> Ap f b -> Ap f b #

(<*) :: Ap f a -> Ap f b -> Ap f a #

Applicative f => Applicative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Alt f a #

(<*>) :: Alt f (a -> b) -> Alt f a -> Alt f b #

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c #

(*>) :: Alt f a -> Alt f b -> Alt f b #

(<*) :: Alt f a -> Alt f b -> Alt f a #

Biapplicative p => Applicative (Join p) 
Instance details

Defined in Data.Bifunctor.Join

Methods

pure :: a -> Join p a #

(<*>) :: Join p (a -> b) -> Join p a -> Join p b #

liftA2 :: (a -> b -> c) -> Join p a -> Join p b -> Join p c #

(*>) :: Join p a -> Join p b -> Join p b #

(<*) :: Join p a -> Join p b -> Join p a #

Biapplicative p => Applicative (Fix p) 
Instance details

Defined in Data.Bifunctor.Fix

Methods

pure :: a -> Fix p a #

(<*>) :: Fix p (a -> b) -> Fix p a -> Fix p b #

liftA2 :: (a -> b -> c) -> Fix p a -> Fix p b -> Fix p c #

(*>) :: Fix p a -> Fix p b -> Fix p b #

(<*) :: Fix p a -> Fix p b -> Fix p a #

Applicative m => Applicative (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

pure :: a -> IdentityT m a #

(<*>) :: IdentityT m (a -> b) -> IdentityT m a -> IdentityT m b #

liftA2 :: (a -> b -> c) -> IdentityT m a -> IdentityT m b -> IdentityT m c #

(*>) :: IdentityT m a -> IdentityT m b -> IdentityT m b #

(<*) :: IdentityT m a -> IdentityT m b -> IdentityT m a #

(Monoid w, Applicative m) => Applicative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

liftA2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

(Monoid w, Applicative m) => Applicative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

liftA2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

(Functor m, Monad m) => Applicative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

liftA2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

liftA2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

Applicative m => Applicative (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

pure :: a -> ReaderT r m a #

(<*>) :: ReaderT r m (a -> b) -> ReaderT r m a -> ReaderT r m b #

liftA2 :: (a -> b -> c) -> ReaderT r m a -> ReaderT r m b -> ReaderT r m c #

(*>) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m b #

(<*) :: ReaderT r m a -> ReaderT r m b -> ReaderT r m a #

(Functor m, Monad m) => Applicative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

pure :: a -> ExceptT e m a #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b #

liftA2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a #

Monad m => Applicative (ZipSink i m) 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

pure :: a -> ZipSink i m a #

(<*>) :: ZipSink i m (a -> b) -> ZipSink i m a -> ZipSink i m b #

liftA2 :: (a -> b -> c) -> ZipSink i m a -> ZipSink i m b -> ZipSink i m c #

(*>) :: ZipSink i m a -> ZipSink i m b -> ZipSink i m b #

(<*) :: ZipSink i m a -> ZipSink i m b -> ZipSink i m a #

(Applicative f, Monad f) => Applicative (WhenMissing f x)

Equivalent to ReaderT k (ReaderT x (MaybeT f)).

Since: containers-0.5.9

Instance details

Defined in Data.IntMap.Internal

Methods

pure :: a -> WhenMissing f x a #

(<*>) :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b #

liftA2 :: (a -> b -> c) -> WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x c #

(*>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b #

(<*) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x a #

(Functor f, Monad m) => Applicative (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

pure :: a -> FreeT f m a #

(<*>) :: FreeT f m (a -> b) -> FreeT f m a -> FreeT f m b #

liftA2 :: (a -> b -> c) -> FreeT f m a -> FreeT f m b -> FreeT f m c #

(*>) :: FreeT f m a -> FreeT f m b -> FreeT f m b #

(<*) :: FreeT f m a -> FreeT f m b -> FreeT f m a #

(Alternative f, Applicative w) => Applicative (CofreeT f w) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

pure :: a -> CofreeT f w a #

(<*>) :: CofreeT f w (a -> b) -> CofreeT f w a -> CofreeT f w b #

liftA2 :: (a -> b -> c) -> CofreeT f w a -> CofreeT f w b -> CofreeT f w c #

(*>) :: CofreeT f w a -> CofreeT f w b -> CofreeT f w b #

(<*) :: CofreeT f w a -> CofreeT f w b -> CofreeT f w a #

Applicative f => Applicative (Indexing f) 
Instance details

Defined in WithIndex

Methods

pure :: a -> Indexing f a #

(<*>) :: Indexing f (a -> b) -> Indexing f a -> Indexing f b #

liftA2 :: (a -> b -> c) -> Indexing f a -> Indexing f b -> Indexing f c #

(*>) :: Indexing f a -> Indexing f b -> Indexing f b #

(<*) :: Indexing f a -> Indexing f b -> Indexing f a #

(Applicative f, Applicative g) => Applicative (Day f g) 
Instance details

Defined in Data.Functor.Day

Methods

pure :: a -> Day f g a #

(<*>) :: Day f g (a -> b) -> Day f g a -> Day f g b #

liftA2 :: (a -> b -> c) -> Day f g a -> Day f g b -> Day f g c #

(*>) :: Day f g a -> Day f g b -> Day f g b #

(<*) :: Day f g a -> Day f g b -> Day f g a #

(Functor m, Monad m) => Applicative (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

pure :: a -> ErrorT e m a #

(<*>) :: ErrorT e m (a -> b) -> ErrorT e m a -> ErrorT e m b #

liftA2 :: (a -> b -> c) -> ErrorT e m a -> ErrorT e m b -> ErrorT e m c #

(*>) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m b #

(<*) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m a #

Applicative (Tagged s) 
Instance details

Defined in Data.Tagged

Methods

pure :: a -> Tagged s a #

(<*>) :: Tagged s (a -> b) -> Tagged s a -> Tagged s b #

liftA2 :: (a -> b -> c) -> Tagged s a -> Tagged s b -> Tagged s c #

(*>) :: Tagged s a -> Tagged s b -> Tagged s b #

(<*) :: Tagged s a -> Tagged s b -> Tagged s a #

Applicative (Mafic a b) 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

pure :: a0 -> Mafic a b a0 #

(<*>) :: Mafic a b (a0 -> b0) -> Mafic a b a0 -> Mafic a b b0 #

liftA2 :: (a0 -> b0 -> c) -> Mafic a b a0 -> Mafic a b b0 -> Mafic a b c #

(*>) :: Mafic a b a0 -> Mafic a b b0 -> Mafic a b b0 #

(<*) :: Mafic a b a0 -> Mafic a b b0 -> Mafic a b a0 #

Applicative (Indexed i a) 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

pure :: a0 -> Indexed i a a0 #

(<*>) :: Indexed i a (a0 -> b) -> Indexed i a a0 -> Indexed i a b #

liftA2 :: (a0 -> b -> c) -> Indexed i a a0 -> Indexed i a b -> Indexed i a c #

(*>) :: Indexed i a a0 -> Indexed i a b -> Indexed i a b #

(<*) :: Indexed i a a0 -> Indexed i a b -> Indexed i a a0 #

Applicative (Flows i b)

This is an illegal Applicative.

Instance details

Defined in Control.Lens.Internal.Level

Methods

pure :: a -> Flows i b a #

(<*>) :: Flows i b (a -> b0) -> Flows i b a -> Flows i b b0 #

liftA2 :: (a -> b0 -> c) -> Flows i b a -> Flows i b b0 -> Flows i b c #

(*>) :: Flows i b a -> Flows i b b0 -> Flows i b b0 #

(<*) :: Flows i b a -> Flows i b b0 -> Flows i b a #

Applicative m => Applicative (LspT config m) 
Instance details

Defined in Language.LSP.Server.Core

Methods

pure :: a -> LspT config m a #

(<*>) :: LspT config m (a -> b) -> LspT config m a -> LspT config m b #

liftA2 :: (a -> b -> c) -> LspT config m a -> LspT config m b -> LspT config m c #

(*>) :: LspT config m a -> LspT config m b -> LspT config m b #

(<*) :: LspT config m a -> LspT config m b -> LspT config m a #

(Applicative (Rep p), Representable p) => Applicative (Prep p) 
Instance details

Defined in Data.Profunctor.Rep

Methods

pure :: a -> Prep p a #

(<*>) :: Prep p (a -> b) -> Prep p a -> Prep p b #

liftA2 :: (a -> b -> c) -> Prep p a -> Prep p b -> Prep p c #

(*>) :: Prep p a -> Prep p b -> Prep p b #

(<*) :: Prep p a -> Prep p b -> Prep p a #

(Monoid w, Functor m, Monad m) => Applicative (AccumT w m) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

pure :: a -> AccumT w m a #

(<*>) :: AccumT w m (a -> b) -> AccumT w m a -> AccumT w m b #

liftA2 :: (a -> b -> c) -> AccumT w m a -> AccumT w m b -> AccumT w m c #

(*>) :: AccumT w m a -> AccumT w m b -> AccumT w m b #

(<*) :: AccumT w m a -> AccumT w m b -> AccumT w m a #

(Functor m, Monad m) => Applicative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

liftA2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

(Functor m, Monad m) => Applicative (SelectT r m) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

pure :: a -> SelectT r m a #

(<*>) :: SelectT r m (a -> b) -> SelectT r m a -> SelectT r m b #

liftA2 :: (a -> b -> c) -> SelectT r m a -> SelectT r m b -> SelectT r m c #

(*>) :: SelectT r m a -> SelectT r m b -> SelectT r m b #

(<*) :: SelectT r m a -> SelectT r m b -> SelectT r m a #

Applicative (Mag a b) 
Instance details

Defined in Data.Biapplicative

Methods

pure :: a0 -> Mag a b a0 #

(<*>) :: Mag a b (a0 -> b0) -> Mag a b a0 -> Mag a b b0 #

liftA2 :: (a0 -> b0 -> c) -> Mag a b a0 -> Mag a b b0 -> Mag a b c #

(*>) :: Mag a b a0 -> Mag a b b0 -> Mag a b b0 #

(<*) :: Mag a b a0 -> Mag a b b0 -> Mag a b a0 #

Monoid m => Applicative (Holes t m) 
Instance details

Defined in Control.Lens.Traversal

Methods

pure :: a -> Holes t m a #

(<*>) :: Holes t m (a -> b) -> Holes t m a -> Holes t m b #

liftA2 :: (a -> b -> c) -> Holes t m a -> Holes t m b -> Holes t m c #

(*>) :: Holes t m a -> Holes t m b -> Holes t m b #

(<*) :: Holes t m a -> Holes t m b -> Holes t m a #

Applicative ((->) r :: Type -> Type)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> r -> a #

(<*>) :: (r -> (a -> b)) -> (r -> a) -> r -> b #

liftA2 :: (a -> b -> c) -> (r -> a) -> (r -> b) -> r -> c #

(*>) :: (r -> a) -> (r -> b) -> r -> b #

(<*) :: (r -> a) -> (r -> b) -> r -> a #

Monoid c => Applicative (K1 i c :: Type -> Type)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> K1 i c a #

(<*>) :: K1 i c (a -> b) -> K1 i c a -> K1 i c b #

liftA2 :: (a -> b -> c0) -> K1 i c a -> K1 i c b -> K1 i c c0 #

(*>) :: K1 i c a -> K1 i c b -> K1 i c b #

(<*) :: K1 i c a -> K1 i c b -> K1 i c a #

(Applicative f, Applicative g) => Applicative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> (f :*: g) a #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b #

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a #

(Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, b, c, a0) #

(<*>) :: (a, b, c, a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) #

liftA2 :: (a0 -> b0 -> c0) -> (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, c0) #

(*>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) #

(<*) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, a0) #

(Applicative f, Applicative g) => Applicative (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

pure :: a -> Product f g a #

(<*>) :: Product f g (a -> b) -> Product f g a -> Product f g b #

liftA2 :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c #

(*>) :: Product f g a -> Product f g b -> Product f g b #

(<*) :: Product f g a -> Product f g b -> Product f g a #

Applicative (ConduitT i o m) 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

pure :: a -> ConduitT i o m a #

(<*>) :: ConduitT i o m (a -> b) -> ConduitT i o m a -> ConduitT i o m b #

liftA2 :: (a -> b -> c) -> ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m c #

(*>) :: ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m b #

(<*) :: ConduitT i o m a -> ConduitT i o m b -> ConduitT i o m a #

Monad m => Applicative (ZipConduit i o m) 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

pure :: a -> ZipConduit i o m a #

(<*>) :: ZipConduit i o m (a -> b) -> ZipConduit i o m a -> ZipConduit i o m b #

liftA2 :: (a -> b -> c) -> ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m c #

(*>) :: ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m b #

(<*) :: ZipConduit i o m a -> ZipConduit i o m b -> ZipConduit i o m a #

(Monad f, Applicative f) => Applicative (WhenMatched f x y)

Equivalent to ReaderT Key (ReaderT x (ReaderT y (MaybeT f)))

Since: containers-0.5.9

Instance details

Defined in Data.IntMap.Internal

Methods

pure :: a -> WhenMatched f x y a #

(<*>) :: WhenMatched f x y (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b #

liftA2 :: (a -> b -> c) -> WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y c #

(*>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b #

(<*) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y a #

(Applicative f, Monad f) => Applicative (WhenMissing f k x)

Equivalent to ReaderT k (ReaderT x (MaybeT f)) .

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

pure :: a -> WhenMissing f k x a #

(<*>) :: WhenMissing f k x (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b #

liftA2 :: (a -> b -> c) -> WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x c #

(*>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b #

(<*) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x a #

Applicative (Molten i a b) 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

pure :: a0 -> Molten i a b a0 #

(<*>) :: Molten i a b (a0 -> b0) -> Molten i a b a0 -> Molten i a b b0 #

liftA2 :: (a0 -> b0 -> c) -> Molten i a b a0 -> Molten i a b b0 -> Molten i a b c #

(*>) :: Molten i a b a0 -> Molten i a b b0 -> Molten i a b b0 #

(<*) :: Molten i a b a0 -> Molten i a b b0 -> Molten i a b a0 #

Applicative (Bazaar p a b) 
Instance details

Defined in Control.Lens.Internal.Bazaar

Methods

pure :: a0 -> Bazaar p a b a0 #

(<*>) :: Bazaar p a b (a0 -> b0) -> Bazaar p a b a0 -> Bazaar p a b b0 #

liftA2 :: (a0 -> b0 -> c) -> Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b c #

(*>) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b b0 #

(<*) :: Bazaar p a b a0 -> Bazaar p a b b0 -> Bazaar p a b a0 #

Applicative (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

pure :: a -> ContT r m a #

(<*>) :: ContT r m (a -> b) -> ContT r m a -> ContT r m b #

liftA2 :: (a -> b -> c) -> ContT r m a -> ContT r m b -> ContT r m c #

(*>) :: ContT r m a -> ContT r m b -> ContT r m b #

(<*) :: ContT r m a -> ContT r m b -> ContT r m a #

Applicative f => Applicative (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> M1 i c f a #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b #

liftA2 :: (a -> b -> c0) -> M1 i c f a -> M1 i c f b -> M1 i c f c0 #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a #

(Applicative f, Applicative g) => Applicative (f :.: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> (f :.: g) a #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a #

(Applicative f, Applicative g) => Applicative (Compose f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

pure :: a -> Compose f g a #

(<*>) :: Compose f g (a -> b) -> Compose f g a -> Compose f g b #

liftA2 :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c #

(*>) :: Compose f g a -> Compose f g b -> Compose f g b #

(<*) :: Compose f g a -> Compose f g b -> Compose f g a #

(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

pure :: a -> RWST r w s m a #

(<*>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b #

liftA2 :: (a -> b -> c) -> RWST r w s m a -> RWST r w s m b -> RWST r w s m c #

(*>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b #

(<*) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a #

(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

pure :: a -> RWST r w s m a #

(<*>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b #

liftA2 :: (a -> b -> c) -> RWST r w s m a -> RWST r w s m b -> RWST r w s m c #

(*>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b #

(<*) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a #

(Monad f, Applicative f) => Applicative (WhenMatched f k x y)

Equivalent to ReaderT k (ReaderT x (ReaderT y (MaybeT f)))

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

pure :: a -> WhenMatched f k x y a #

(<*>) :: WhenMatched f k x y (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b #

liftA2 :: (a -> b -> c) -> WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y c #

(*>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b #

(<*) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y a #

Applicative (TakingWhile p f a b) 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

pure :: a0 -> TakingWhile p f a b a0 #

(<*>) :: TakingWhile p f a b (a0 -> b0) -> TakingWhile p f a b a0 -> TakingWhile p f a b b0 #

liftA2 :: (a0 -> b0 -> c) -> TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b c #

(*>) :: TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b b0 #

(<*) :: TakingWhile p f a b a0 -> TakingWhile p f a b b0 -> TakingWhile p f a b a0 #

Applicative (BazaarT p g a b) 
Instance details

Defined in Control.Lens.Internal.Bazaar

Methods

pure :: a0 -> BazaarT p g a b a0 #

(<*>) :: BazaarT p g a b (a0 -> b0) -> BazaarT p g a b a0 -> BazaarT p g a b b0 #

liftA2 :: (a0 -> b0 -> c) -> BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b c #

(*>) :: BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b b0 #

(<*) :: BazaarT p g a b a0 -> BazaarT p g a b b0 -> BazaarT p g a b a0 #

Reifies s (ReifiedApplicative f) => Applicative (ReflectedApplicative f s) 
Instance details

Defined in Data.Reflection

(Functor m, Monad m) => Applicative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

pure :: a -> RWST r w s m a #

(<*>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b #

liftA2 :: (a -> b -> c) -> RWST r w s m a -> RWST r w s m b -> RWST r w s m c #

(*>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b #

(<*) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a #

Monad m => Applicative (Pipe l i o u m) 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

pure :: a -> Pipe l i o u m a #

(<*>) :: Pipe l i o u m (a -> b) -> Pipe l i o u m a -> Pipe l i o u m b #

liftA2 :: (a -> b -> c) -> Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m c #

(*>) :: Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m b #

(<*) :: Pipe l i o u m a -> Pipe l i o u m b -> Pipe l i o u m a #

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

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an 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.

pprRuntimeTrace #

Arguments

:: String

header

-> SDoc

information to output

-> CoreExpr

expression

-> DsM CoreExpr 

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.

dsGetCompleteMatches :: TyCon -> DsM [CompleteMatch] #

The COMPLETE pragmas provided by the user for a given TyCon.

askNoErrsDs :: DsM a -> DsM (a, Bool) #

failDs :: DsM a #

errDsCoreExpr :: SDoc -> DsM CoreExpr #

Issue an error, but return the expression for (), so that we can continue reporting errors.

errDs :: SDoc -> DsM () #

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

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.

initDsWithModGuts :: HscEnv -> ModGuts -> DsM a -> IO (Messages, Maybe a) #

Run a DsM action in the context of an existing ModGuts

initDs :: HscEnv -> TcGblEnv -> DsM a -> IO (Messages, Maybe a) #

Run a DsM action inside the IO monad.

initDsTc :: DsM a -> TcM a #

Run a DsM action inside the TcM monad.

fixDs :: (a -> DsM a) -> DsM a #

data DsMatchContext #

Instances

Instances details
Outputable DsMatchContext 
Instance details

Defined in DsMonad

data EquationInfo #

Constructors

EqnInfo 

Fields

  • eqn_pats :: [Pat GhcTc]

    The patterns for an equation

    NB: We have already applied decideBangHood to these patterns. See Note [decideBangHood] in DsUtils

  • eqn_orig :: Origin

    Was this equation present in the user source?

    This helps us avoid warnings on patterns that GHC elaborated.

    For instance, the pattern -1 :: Word gets desugared into W# :: Word, but we shouldn't warn about an overflowed literal for both of these cases.

  • eqn_rhs :: MatchResult

    What to do after match

Instances

Instances details
Outputable EquationInfo 
Instance details

Defined in DsMonad

data CanItFail #

Constructors

CanFail 
CantFail 

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 #

data DsMetaVal #

Constructors

DsBound Id 
DsSplice (HsExpr GhcTc) 

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.

traceCmd :: DynFlags -> String -> String -> IO a -> IO a #

isWarnMsgFatal :: DynFlags -> WarnMsg -> Maybe (Maybe WarningFlag) #

Checks if given WarnMsg is a fatal warning.

logOutput :: DynFlags -> PprStyle -> MsgDoc -> IO () #

Like logInfo but with SevOutput rather then SevInfo

putMsg :: DynFlags -> MsgDoc -> IO () #

withTimingSilentD #

Arguments

:: (MonadIO m, HasDynFlags m) 
=> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> 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.

withTimingSilent #

Arguments

:: MonadIO m 
=> DynFlags

DynFlags

-> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> 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.

withTimingD #

Arguments

:: (MonadIO m, HasDynFlags m) 
=> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> m a

The body of the phase to be timed

-> m a 

Like withTiming but get DynFlags from the Monad.

withTiming #

Arguments

:: MonadIO m 
=> DynFlags

DynFlags

-> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> 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 result r 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.

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

dumpIfSet :: DynFlags -> Bool -> String -> SDoc -> IO () #

doIfSet :: Bool -> IO () -> IO () #

ghcExit :: DynFlags -> Int -> IO () #

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

errDoc :: [MsgDoc] -> [MsgDoc] -> [MsgDoc] -> ErrDoc #

allValid :: [Validity] -> Validity #

If they aren't all valid, return the first

data Validity #

Constructors

IsValid

Everything is fine

NotValid MsgDoc

A problem, and some indication of why

data ErrMsg #

Instances

Instances details
Show ErrMsg 
Instance details

Defined in ErrUtils

data ErrDoc #

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.

mkLocMessageAnn #

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.

data Severity #

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

Instances

Instances details
Show Severity 
Instance details

Defined in ErrUtils

ToJson Severity 
Instance details

Defined in ErrUtils

Methods

json :: Severity -> JsonDoc #

type MsgDoc = SDoc #

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.

getOptions #

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.)

getOptionsFromFile #

Arguments

:: DynFlags 
-> FilePath

Input file

-> IO [Located String]

Parsed options, if any.

Parse OPTIONS and LANGUAGE pragmas of the source file.

Throws a SourceError if flag parsing fails (including unsupported flags.)

module Id

module InstEnv

module IfaceSyn

mkModuleEnv :: [(Module, a)] -> ModuleEnv a #

mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b #

plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a #

extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)] -> ModuleEnv a #

extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a -> ModuleEnv a #

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.

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 #

Substitutes holes in a UnitId, suitable for renaming when an include occurs; see Note [Representation of module/name variable].

p[A=A] maps to p[A=B] with A=B.

renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module #

Substitutes holes in a Module. NOT suitable for being called directly on a nameModule, see Note [Representation of module/name variable]. p[A=A]:B maps to p[A=q():A]:B with A=q():A; similarly, A maps to q():A.

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 Uniques

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.

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.

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.

stableModuleCmp :: Module -> Module -> Ordering #

This gives a stable ordering, as opposed to the Ord instance which gives an ordering based on the Uniques 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.

moduleStableString :: Module -> String #

Get a string representation of a Module that's unique and stable across recompilations. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal"

stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering #

Compares module names lexically, rather than by their Uniques

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

Instances details
ContainsModule DsGblEnv 
Instance details

Defined in TcRnTypes

ContainsModule TcGblEnv 
Instance details

Defined in TcRnTypes

ContainsModule gbl => ContainsModule (Env gbl lcl) 
Instance details

Defined in TcRnTypes

Methods

extractModule :: Env gbl lcl -> Module #

class HasModule (m :: Type -> Type) where #

Methods

getModule :: m Module #

Instances

Instances details
HasModule CoreM 
Instance details

Defined in CoreMonad

ContainsModule env => HasModule (IOEnv env) 
Instance details

Defined in IOEnv

Methods

getModule :: IOEnv env 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

Instances details
Eq IndefUnitId 
Instance details

Defined in Module

Ord IndefUnitId 
Instance details

Defined in Module

Binary IndefUnitId 
Instance details

Defined in Module

Outputable IndefUnitId 
Instance details

Defined in Module

newtype DefUnitId #

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 

Instances

Instances details
Eq DefUnitId 
Instance details

Defined in Module

Ord DefUnitId 
Instance details

Defined in Module

Binary DefUnitId 
Instance details

Defined in Module

Outputable DefUnitId 
Instance details

Defined in Module

data InstalledModuleEnv elt #

A map keyed off of InstalledModule

type ShHoleSubst = ModuleNameEnv Module #

Substitution on module variables, mapping module names to module identifiers.

data ModuleEnv elt #

A map keyed off of Modules

type ModuleSet = Set NDModule #

A set of Modules

type ModuleNameEnv elt = UniqFM elt #

A map keyed off of ModuleNames (actually, their Uniques)

type DModuleNameEnv elt = UniqDFM elt #

A map keyed off of ModuleNames (actually, their Uniques) Has deterministic folds and can be deterministically converted to a list

data Module #

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

Instances details
Eq Module 
Instance details

Defined in Module

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Data Module 
Instance details

Defined in Module

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module #

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) #

gmapT :: (forall b. Data b => b -> b) -> Module -> Module #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r #

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module #

Ord Module 
Instance details

Defined in Module

Show Module Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData Module 
Instance details

Defined in Module

Methods

rnf :: Module -> () #

Binary Module 
Instance details

Defined in Module

Methods

put_ :: BinHandle -> Module -> IO () #

put :: BinHandle -> Module -> IO (Bin Module) #

get :: BinHandle -> IO Module #

Uniquable Module 
Instance details

Defined in Module

Methods

getUnique :: Module -> Unique #

Outputable Module 
Instance details

Defined in Module

Methods

ppr :: Module -> SDoc #

pprPrec :: Rational -> Module -> SDoc #

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module 
Instance details

Defined in Module

data ModuleName #

A ModuleName is essentially a simple string, e.g. Data.List.

Instances

Instances details
Eq ModuleName 
Instance details

Defined in Module

Data ModuleName 
Instance details

Defined in Module

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleName -> c ModuleName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleName #

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleName) #

gmapT :: (forall b. Data b => b -> b) -> ModuleName -> ModuleName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleName -> m ModuleName #

Ord ModuleName 
Instance details

Defined in Module

Show ModuleName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Hashable ModuleName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData ModuleName 
Instance details

Defined in Module

Methods

rnf :: ModuleName -> () #

Binary ModuleName 
Instance details

Defined in Module

Uniquable ModuleName 
Instance details

Defined in Module

Outputable ModuleName 
Instance details

Defined in Module

BinaryStringRep ModuleName 
Instance details

Defined in Module

Annotate ModuleName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> ModuleName -> Annotated () #

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module 
Instance details

Defined in Module

ToHie (IEContext (Located ModuleName)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located ModuleName) -> HieM [HieAST Type]

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

Instances details
Eq InstalledUnitId 
Instance details

Defined in Module

Ord InstalledUnitId 
Instance details

Defined in Module

Show InstalledUnitId Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Hashable InstalledUnitId Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData InstalledUnitId Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: InstalledUnitId -> () #

Binary InstalledUnitId 
Instance details

Defined in Module

Uniquable InstalledUnitId 
Instance details

Defined in Module

Outputable InstalledUnitId 
Instance details

Defined in Module

BinaryStringRep InstalledUnitId 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module 
Instance details

Defined in Module

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

Instances details
Eq ComponentId 
Instance details

Defined in Module

Ord ComponentId 
Instance details

Defined in Module

Show ComponentId Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Binary ComponentId 
Instance details

Defined in Module

Uniquable ComponentId 
Instance details

Defined in Module

Outputable ComponentId 
Instance details

Defined in Module

BinaryStringRep ComponentId 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module 
Instance details

Defined in Module

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"

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

mkFCallName :: Unique -> String -> Name #

Make a name for a foreign call

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

mkInternalName :: Unique -> OccName -> SrcSpan -> Name #

Create a name which is (for now at least) local to the current module and hence does not need a Module to disambiguate it from other Names

nameIsFromExternalPackage :: UnitId -> Name -> Bool #

Returns True if the Name comes from some other package: neither this package nor the interactive package.

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

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

getName

Methods

getOccName :: a -> OccName #

getName :: a -> Name #

Instances

Instances details
NamedThing HoleFitCandidate 
Instance details

Defined in TcHoleFitTypes

NamedThing ClsInst 
Instance details

Defined in InstEnv

NamedThing FamInst 
Instance details

Defined in FamInstEnv

NamedThing IfaceDecl 
Instance details

Defined in IfaceSyn

NamedThing IfaceClassOp 
Instance details

Defined in IfaceSyn

NamedThing IfaceConDecl 
Instance details

Defined in IfaceSyn

NamedThing Class 
Instance details

Defined in Class

NamedThing ConLike 
Instance details

Defined in ConLike

NamedThing DataCon 
Instance details

Defined in DataCon

NamedThing PatSyn 
Instance details

Defined in PatSyn

NamedThing TyThing 
Instance details

Defined in TyCoRep

NamedThing Var 
Instance details

Defined in Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

NamedThing TyCon 
Instance details

Defined in TyCon

NamedThing Name 
Instance details

Defined in Name

NamedThing (HsTyVarBndr GhcRn) 
Instance details

Defined in GHC.Hs.Types

NamedThing (CoAxiom br) 
Instance details

Defined in CoAxiom

Methods

getOccName :: CoAxiom br -> OccName #

getName :: CoAxiom br -> Name #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in Name

NamedThing tv => NamedThing (VarBndr tv flag) 
Instance details

Defined in Var

Methods

getOccName :: VarBndr tv flag -> OccName #

getName :: VarBndr tv flag -> Name #

mkDataCOcc #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

mkDataTOcc #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

mkDFunOcc #

Arguments

:: String

Typically the class and type glommed together e.g. OrdMaybe. Only used in debug mode, for extra clarity

-> Bool

Is this a hs-boot instance DFun?

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe

mkInstTyTcOcc #

Arguments

:: String

Family name, e.g. Map

-> OccSet

avoid these Occs

-> OccName
R:Map

Derive a name for the representation type constructor of a data/newtype instance.

mkLocalOcc #

Arguments

:: Unique

Unique to combine with the OccName

-> OccName

Local name, e.g. sat

-> OccName

Nice unique version, e.g. $L23sat

mkSuperDictSelOcc #

Arguments

:: Int

Index of superclass, e.g. 3

-> OccName

Class, e.g. Ord

-> OccName

Derived Occname, e.g. $p3Ord

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.

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

isSymOcc :: OccName -> Bool #

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 [])

isValOcc :: OccName -> Bool #

Value OccNamess are those that are either in the variable or data constructor namespaces

pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc #

alterOccEnv :: (Maybe elt -> Maybe elt) -> OccEnv elt -> OccName -> OccEnv elt #

filterOccEnv :: (elt -> Bool) -> OccEnv elt -> OccEnv elt #

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 #

occEnvElts :: OccEnv a -> [a] #

foldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b #

mkOccEnv :: [(OccName, a)] -> OccEnv a #

extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a #

extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a #

unitOccEnv :: OccName -> a -> OccEnv a #

data NameSpace #

Instances

Instances details
Eq NameSpace 
Instance details

Defined in OccName

Ord NameSpace 
Instance details

Defined in OccName

Binary NameSpace 
Instance details

Defined in OccName

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.

Methods

occName :: name -> OccName #

Instances

Instances details
HasOccName HoleFitCandidate 
Instance details

Defined in TcHoleFitTypes

HasOccName TcBinder 
Instance details

Defined in TcRnTypes

Methods

occName :: TcBinder -> OccName #

HasOccName IfaceDecl 
Instance details

Defined in IfaceSyn

Methods

occName :: IfaceDecl -> OccName #

HasOccName IfaceClassOp 
Instance details

Defined in IfaceSyn

HasOccName IfaceConDecl 
Instance details

Defined in IfaceSyn

HasOccName RdrName 
Instance details

Defined in RdrName

Methods

occName :: RdrName -> OccName #

HasOccName Var 
Instance details

Defined in Var

Methods

occName :: Var -> OccName #

HasOccName OccName 
Instance details

Defined in OccName

Methods

occName :: OccName -> OccName #

HasOccName Name 
Instance details

Defined in Name

Methods

occName :: Name -> OccName #

HasOccName name => HasOccName (IEWrappedName name) 
Instance details

Defined in GHC.Hs.ImpExp

Methods

occName :: IEWrappedName name -> OccName #

data OccEnv a #

Instances

Instances details
Data a => Data (OccEnv a) 
Instance details

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) 
Instance details

Defined in OccName

Methods

ppr :: OccEnv a -> SDoc #

pprPrec :: Rational -> OccEnv a -> SDoc #

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.

data OccName #

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

Instances details
Eq OccName 
Instance details

Defined in OccName

Methods

(==) :: OccName -> OccName -> Bool #

(/=) :: OccName -> OccName -> Bool #

Data OccName 
Instance details

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 
Instance details

Defined in OccName

Show OccName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Hashable OccName Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

hashWithSalt :: Int -> OccName -> Int #

hash :: OccName -> Int #

NFData OccName 
Instance details

Defined in OccName

Methods

rnf :: OccName -> () #

HasOccName OccName 
Instance details

Defined in OccName

Methods

occName :: OccName -> OccName #

Binary OccName 
Instance details

Defined in OccName

Uniquable OccName 
Instance details

Defined in OccName

Methods

getUnique :: OccName -> Unique #

Outputable OccName 
Instance details

Defined in OccName

Methods

ppr :: OccName -> SDoc #

pprPrec :: Rational -> OccName -> SDoc #

OutputableBndr OccName 
Instance details

Defined in OccName

data Name #

A unique, unambiguous name for something, containing information about where that thing originated.

Instances

Instances details
Eq Name

The same comments as for Name's Ord instance apply.

Instance details

Defined in Name

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Data Name 
Instance details

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 #

toConstr :: Name -> Constr #

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 nonDetCmpUnique, which means that the ordering is not stable across deserialization or rebuilds.

See nonDetCmpUnique for further information, and trac #15240 for a bug caused by improper use of this instance.

Instance details

Defined in Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

NFData Name 
Instance details

Defined in Name

Methods

rnf :: Name -> () #

NamedThing Name 
Instance details

Defined in Name

HasOccName Name 
Instance details

Defined in Name

Methods

occName :: Name -> OccName #

Binary Name

Assumes that the Name is a non-binding one. See putIfaceTopBndr and getIfaceTopBndr for serializing binding Names. See UserData for the rationale for this distinction.

Instance details

Defined in Name

Methods

put_ :: BinHandle -> Name -> IO () #

put :: BinHandle -> Name -> IO (Bin Name) #

get :: BinHandle -> IO Name #

Uniquable Name 
Instance details

Defined in Name

Methods

getUnique :: Name -> Unique #

HasSrcSpan Name 
Instance details

Defined in Name

Outputable Name 
Instance details

Defined in Name

Methods

ppr :: Name -> SDoc #

pprPrec :: Rational -> Name -> SDoc #

OutputableBndr Name 
Instance details

Defined in Name

ModifyState Name 
Instance details

Defined in Compat.HieAst

Methods

addSubstitution :: Name -> Name -> HieState -> HieState

ToHie (LBooleanFormula (Located Name)) 
Instance details

Defined in Compat.HieAst

ToHie (Located (FunDep (Located Name))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Located (FunDep (Located Name)) -> HieM [HieAST Type]

ToHie (Context (Located Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Name) -> HieM [HieAST Type]

ToHie (IEContext (LIEWrappedName Name)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (LIEWrappedName Name) -> HieM [HieAST Type]

ToHie (IEContext (Located (FieldLbl Name))) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: IEContext (Located (FieldLbl Name)) -> HieM [HieAST Type]

type SrcSpanLess Name 
Instance details

Defined in Name

module NameCache

module NameEnv

module NameSet

module PatSyn

pprTyThing :: ShowSub -> TyThing -> SDoc #

Pretty-prints a TyThing.

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

hasKey :: Uniquable a => a -> Unique -> Bool #

class Uniquable a where #

Class of things that we can obtain a Unique from

Methods

getUnique :: a -> Unique #

Instances

Instances details
Uniquable Int 
Instance details

Defined in Unique

Methods

getUnique :: Int -> Unique #

Uniquable EvBindsVar 
Instance details

Defined in TcEvidence

Uniquable LocalReg 
Instance details

Defined in CmmExpr

Methods

getUnique :: LocalReg -> Unique #

Uniquable Label 
Instance details

Defined in Hoopl.Label

Methods

getUnique :: Label -> Unique #

Uniquable Class 
Instance details

Defined in Class

Methods

getUnique :: Class -> Unique #

Uniquable CoAxiomRule 
Instance details

Defined in CoAxiom

Uniquable ConLike 
Instance details

Defined in ConLike

Methods

getUnique :: ConLike -> Unique #

Uniquable DataCon 
Instance details

Defined in DataCon

Methods

getUnique :: DataCon -> Unique #

Uniquable PatSyn 
Instance details

Defined in PatSyn

Methods

getUnique :: PatSyn -> Unique #

Uniquable Var 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique #

Uniquable SourcePackageId 
Instance details

Defined in PackageConfig

Uniquable PackageName 
Instance details

Defined in PackageConfig

Uniquable Unique 
Instance details

Defined in Unique

Methods

getUnique :: Unique -> Unique #

Uniquable Module 
Instance details

Defined in Module

Methods

getUnique :: Module -> Unique #

Uniquable ModuleName 
Instance details

Defined in Module

Uniquable UnitId 
Instance details

Defined in Module

Methods

getUnique :: UnitId -> Unique #

Uniquable InstalledUnitId 
Instance details

Defined in Module

Uniquable ComponentId 
Instance details

Defined in Module

Uniquable FastString 
Instance details

Defined in Unique

Uniquable TyCon 
Instance details

Defined in TyCon

Methods

getUnique :: TyCon -> Unique #

Uniquable OccName 
Instance details

Defined in OccName

Methods

getUnique :: OccName -> Unique #

Uniquable Name 
Instance details

Defined in Name

Methods

getUnique :: Name -> Unique #

Uniquable (CoAxiom br) 
Instance details

Defined in CoAxiom

Methods

getUnique :: CoAxiom br -> Unique #

Uniquable name => Uniquable (AnnTarget name) 
Instance details

Defined in Annotations

Methods

getUnique :: AnnTarget name -> Unique #

module RdrName

module RnSplice

module RnNames

module TcEnv

wrapIP :: Type -> CoercionR #

Create a Coercion that wraps a value in an implicit-parameter dictionary. See unwrapIP.

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.

evSelector :: Id -> [Type] -> [EvExpr] -> EvExpr #

evCast :: EvExpr -> TcCoercion -> EvTerm #

d |> co

evId :: EvId -> EvExpr #

Any sort of evidence Id, including coercions

foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a #

isErasableHsWrapper :: HsWrapper -> Bool #

Is the wrapper erasable, i.e., will not affect runtime semantics?

maybeTcSubCo :: EqRel -> TcCoercion -> TcCoercion #

If the EqRel is ReprEq, makes a SubCo; otherwise, does nothing. Note that the input coercion should always be nominal.

isTcReflexiveCo :: TcCoercion -> Bool #

This version does a slow check, calculating the related types and seeing if they are equal.

mkTcAxInstCo :: forall (br :: BranchFlag). Role -> CoAxiom br -> BranchIndex -> [TcType] -> [TcCoercion] -> TcCoercion #

data HsWrapper #

Instances

Instances details
Data HsWrapper 
Instance details

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 
Instance details

Defined in TcEvidence

data TcEvBinds #

Instances

Instances details
Data TcEvBinds 
Instance details

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 
Instance details

Defined in TcEvidence

data EvBindsVar #

Instances

Instances details
Uniquable EvBindsVar 
Instance details

Defined in TcEvidence

Outputable EvBindsVar 
Instance details

Defined in TcEvidence

newtype EvBindMap #

Constructors

EvBindMap 

Instances

Instances details
Outputable EvBindMap 
Instance details

Defined in TcEvidence

data EvBind #

Constructors

EvBind 

Instances

Instances details
Outputable EvBind 
Instance details

Defined in TcEvidence

Methods

ppr :: EvBind -> SDoc #

pprPrec :: Rational -> EvBind -> SDoc #

data EvTerm #

Instances

Instances details
Data EvTerm 
Instance details

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 
Instance details

Defined in TcEvidence

Methods

ppr :: EvTerm -> SDoc #

pprPrec :: Rational -> EvTerm -> SDoc #

data EvTypeable #

Instructions on how to make a Typeable dictionary. See Note [Typeable evidence terms]

Constructors

EvTypeableTyCon TyCon [EvTerm]

Dictionary for Typeable T where T is a type constructor with all of its kind variables saturated. The [EvTerm] is Typeable evidence for the applied kinds..

EvTypeableTyApp EvTerm EvTerm

Dictionary for Typeable (s t), given a dictionaries for s and t.

EvTypeableTrFun EvTerm EvTerm

Dictionary for Typeable (s -> t), given a dictionaries for s and t.

EvTypeableTyLit EvTerm

Dictionary for a type literal, e.g. Typeable "foo" or Typeable 3 The EvTerm is evidence of, e.g., KnownNat 3 (see #10348)

Instances

Instances details
Data EvTypeable 
Instance details

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 
Instance details

Defined in TcEvidence

data EvCallStack #

Evidence for CallStack implicit parameters.

Constructors

EvCsEmpty 
EvCsPushCall Name RealSrcSpan EvExpr

EvCsPushCall name loc stk represents a call to name, occurring at loc, in a calling context stk.

Instances

Instances details
Data EvCallStack 
Instance details

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 
Instance details

Defined in TcEvidence

data CoercionHole #

A coercion to be filled in by the type-checker. See Note [Coercion holes]

Instances

Instances details
Data CoercionHole 
Instance details

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 
Instance details

Defined in TyCoRep

data Role #

Instances

Instances details
Eq Role 
Instance details

Defined in CoAxiom

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Data Role 
Instance details

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 #

toConstr :: Role -> Constr #

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 
Instance details

Defined in CoAxiom

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Binary Role 
Instance details

Defined in CoAxiom

Methods

put_ :: BinHandle -> Role -> IO () #

put :: BinHandle -> Role -> IO (Bin Role) #

get :: BinHandle -> IO Role #

Outputable Role 
Instance details

Defined in CoAxiom

Methods

ppr :: Role -> SDoc #

pprPrec :: Rational -> Role -> SDoc #

Annotate (Maybe Role) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Maybe Role -> Annotated () #

pickLR :: LeftOrRight -> (a, a) -> a #

data LeftOrRight #

Constructors

CLeft 
CRight 

Instances

Instances details
Eq LeftOrRight 
Instance details

Defined in BasicTypes

Data LeftOrRight 
Instance details

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 
Instance details

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.

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?

isRhoExpTy :: ExpType -> Bool #

Like isRhoTy, but also says True for Infer types

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.

mkMinimalBySCs :: (a -> PredType) -> [a] -> [a] #

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]

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.

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.

tcFunResultTyN :: HasDebugCallStack => Arity -> Type -> Type #

Strips off n *visible* arguments and returns the resulting 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

tcTyConAppTyCon_maybe :: Type -> Maybe TyCon #

Like tcRepSplitTyConApp_maybe, but only returns the TyCon.

tcSplitNestedSigmaTys :: Type -> ([TyVar], ThetaType, Type) #

Split a sigma type into its parts, going underneath as many ForAllTys 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).

tcSplitSigmaTy :: Type -> ([TyVar], ThetaType, Type) #

Split a sigma type into its parts.

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 sameVis argf supplied_argf is True, 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.

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 TyBinders and the inner type. Always succeeds, even if it returns an empty list.

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.

isFlattenTyVar :: TcTyVar -> Bool #

True of both given and wanted flatten-skolems (fmv and fsk)

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 tcTyFamInstsAndVis (C (T @(F Int) (F Bool))) will return:

[ (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

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 TcCoVar = CoVar #

type TcType = Type #

type TcTyCoVar = Var #

type TcTyCon = TyCon #

type TcKind = Kind #

data ExpType #

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 

Instances

Instances details
Outputable ExpType 
Instance details

Defined in TcType

Methods

ppr :: ExpType -> SDoc #

pprPrec :: Rational -> ExpType -> SDoc #

data InferResult #

Constructors

IR 

Instances

Instances details
Outputable InferResult 
Instance details

Defined in TcType

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.

data MetaInfo #

Instances

Instances details
Outputable MetaInfo 
Instance details

Defined in TcType

newtype TcLevel #

Constructors

TcLevel Int 

Instances

Instances details
Eq TcLevel 
Instance details

Defined in TcType

Methods

(==) :: TcLevel -> TcLevel -> Bool #

(/=) :: TcLevel -> TcLevel -> Bool #

Ord TcLevel 
Instance details

Defined in TcType

Outputable TcLevel 
Instance details

Defined in TcType

Methods

ppr :: TcLevel -> SDoc #

pprPrec :: Rational -> TcLevel -> SDoc #

orphNamesOfCoCon :: forall (br :: BranchFlag). CoAxiom br -> NameSet #

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

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.

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

mkTyCoInvForAllTy :: TyCoVar -> Type -> Type #

Make a dependent forall over an Inferred variable

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 #

A key function: builds a TyConApp or FunTy as appropriate to its arguments. Applies its arguments to the constructor from left to right.

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)

mkAppTys :: Type -> [Type] -> Type #

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.

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 Types 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 Types 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].

substTyWithCoVars :: [CoVar] -> [Coercion] -> Type -> Type #

Substitute covars within a type

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

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!

mkTvSubst :: InScopeSet -> TvSubstEnv -> TCvSubst #

Make a TCvSubst with specified tyvar subst and empty covar subst

data TCvSubst #

Type & coercion substitution

The following invariants must hold of a TCvSubst:

  1. The in-scope set is needed only to guide the generation of fresh uniques
  2. In particular, the kind of the type variables in the in-scope set is not relevant
  3. The substitution is only applied ONCE! This is because in general such application will not reach a fixed point.

Instances

Instances details
Outputable TCvSubst 
Instance details

Defined in TyCoSubst

type TvSubstEnv = TyVarEnv Type #

A substitution of Types for TyVars and Kinds for KindVars

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.

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.

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.

mkTyConTy :: TyCon -> Type #

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 TyCoVars from left to right

mkInvisFunTys :: [Type] -> Type -> Type #

Make nested arrow types

mkInvisFunTy :: Type -> Type -> Type infixr 3 #

mkVisFunTy :: Type -> Type -> Type infixr 3 #

isVisibleBinder :: TyCoBinder -> Bool #

Does this binder bind a visible argument?

isInvisibleBinder :: TyCoBinder -> Bool #

Does this binder bind an invisible argument?

type KnotTied ty = ty #

A type labeled KnotTied might have knot-tied tycons in it. See Note [Type checking recursive type and class declarations] in TcTyClsDecls

mkAppTy :: Type -> Type -> Type #

Applies a type to another, as in e.g. k a

eqType :: Type -> Type -> Bool #

Type equality on source types. Does not look through newtypes or PredTypes, 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]

type TcTyVar = Var #

Type variable that might be a metavariable

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 forall (with an arrow)

ForallInvis

An invisible forall (with a dot)

Instances

Instances details
Eq ForallVisFlag 
Instance details

Defined in Var

Data ForallVisFlag 
Instance details

Defined in Var

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForallVisFlag -> c ForallVisFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForallVisFlag #

toConstr :: ForallVisFlag -> Constr #

dataTypeOf :: ForallVisFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForallVisFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForallVisFlag) #

gmapT :: (forall b. Data b => b -> b) -> ForallVisFlag -> ForallVisFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForallVisFlag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForallVisFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> ForallVisFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForallVisFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForallVisFlag -> m ForallVisFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForallVisFlag -> m ForallVisFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForallVisFlag -> m ForallVisFlag #

Ord ForallVisFlag 
Instance details

Defined in Var

Outputable ForallVisFlag 
Instance details

Defined in Var

mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type #

Like mkTyCoForAllTy, but does not check the occurrence of the binder See Note [Unused coercion variable in ForAllTy]

data Type #

Instances

Instances details
Data Type 
Instance details

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 #

toConstr :: Type -> Constr #

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 # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Type -> () #

Outputable Type 
Instance details

Defined in TyCoRep

Methods

ppr :: Type -> SDoc #

pprPrec :: Rational -> Type -> SDoc #

Eq (DeBruijn Type) 
Instance details

Defined in CoreMap

Methods

(==) :: DeBruijn Type -> DeBruijn Type -> Bool #

(/=) :: DeBruijn Type -> DeBruijn Type -> Bool #

ToHie (TScoped Type) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped Type -> HieM [HieAST Type]

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

Instances details
Data TyCoBinder 
Instance details

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 
Instance details

Defined in TyCoRep

type PredType = Type #

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"

type Kind = Type #

The key type representing kinds in the compiler.

type ThetaType = [PredType] #

A collection of PredTypes

data ArgFlag #

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

Constructors

Inferred 
Specified 
Required 

Instances

Instances details
Eq ArgFlag 
Instance details

Defined in Var

Methods

(==) :: ArgFlag -> ArgFlag -> Bool #

(/=) :: ArgFlag -> ArgFlag -> Bool #

Data ArgFlag 
Instance details

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 
Instance details

Defined in Var

Binary ArgFlag 
Instance details

Defined in Var

Outputable ArgFlag 
Instance details

Defined in Var

Methods

ppr :: ArgFlag -> SDoc #

pprPrec :: Rational -> ArgFlag -> SDoc #

Outputable tv => Outputable (VarBndr tv ArgFlag) 
Instance details

Defined in Var

data AnonArgFlag #

The non-dependent version of ArgFlag.

Constructors

VisArg

Used for (->): an ordinary non-dependent arrow. The argument is visible in source code.

InvisArg

Used for (=>): a non-dependent predicate arrow. The argument is invisible in source code.

Instances

Instances details
Eq AnonArgFlag 
Instance details

Defined in Var

Data AnonArgFlag 
Instance details

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 
Instance details

Defined in Var

Binary AnonArgFlag 
Instance details

Defined in Var

Outputable AnonArgFlag 
Instance details

Defined in Var

data MetaDetails #

Constructors

Flexi 
Indirect TcType 

Instances

Instances details
Outputable MetaDetails 
Instance details

Defined in TcType

data TcTyVarDetails #

Instances

Instances details
Outputable TcTyVarDetails 
Instance details

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.

forkM :: SDoc -> IfL a -> IfL a #

forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a) #

initIfaceLclWithSubst :: Module -> SDoc -> Bool -> NameShape -> IfL a -> IfM lcl a #

Initialize interface typechecking, but with a NameShape to apply when typechecking top-level OccNames (see lookupIfaceTop)

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 #

Run an IfG (top-level interface monad) computation inside an existing TcRn (typecheck-renaming monad) computation by initializing an IfGblEnv based on TcGblEnv.

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.

setStage :: ThStage -> TcM a -> TcRn a #

keepAlive :: Name -> TcRn () #

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.

setTcLevel :: TcLevel -> TcM a -> TcM a #

pushTcLevelsM :: Int -> TcM a -> TcM (a, TcLevel) #

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

emitSimples :: Cts -> TcM () #

emitSimple :: Ct -> TcM () #

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

debugTc :: TcM () -> TcM () #

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.

warnTc :: WarnReason -> Bool -> MsgDoc -> TcM () #

Display a warning if a condition is met.

warnIf :: Bool -> MsgDoc -> TcRn () #

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

failIfTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM () #

failIfTc :: Bool -> MsgDoc -> TcM () #

checkTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM () #

checkTc :: Bool -> MsgDoc -> TcM () #

addErrsTc :: [MsgDoc] -> TcM () #

addErrTc :: MsgDoc -> TcM () #

tryTc :: TcRn a -> TcRn (Maybe a, Messages) #

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

recoverM :: TcRn r -> TcRn r -> TcRn r #

attemptM :: TcRn r -> TcRn (Maybe r) #

askNoErrs :: TcRn a -> TcRn (a, Bool) #

setCtLocM :: CtLoc -> TcM a -> TcM a #

popErrCtxt :: TcM a -> TcM a #

updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> 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 #

ifErrsM :: TcRn r -> TcRn r -> TcRn r #

whenNoErrs :: TcM () -> TcM () #

checkNoErrs :: TcM r -> TcM r #

checkErr :: Bool -> MsgDoc -> TcRn () #

addErrs :: [(SrcSpan, MsgDoc)] -> TcRn () #

addErr :: MsgDoc -> TcRn () #

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 #

extendFixityEnv :: [(Name, FixItem)] -> RnM a -> RnM a #

traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () #

traceHiDiffs :: SDoc -> TcRnIf m n () #

traceIf :: 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 () #

Output a doc if the given DumpFlag is set.

By default this logs to stdout However, if the `-ddump-to-file` flag is set, then this will dump output to a file

Just a wrapper for dumpSDoc

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) #

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.

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.

withDoDynamicToo :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a #

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 () #

Do it flag is true

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 #

discardResult :: TcM a -> TcM () #

initTcRnIf #

Arguments

:: Char

Mask for unique supply

-> HscEnv 
-> gbl 
-> lcl 
-> TcRnIf gbl lcl a 
-> IO a 

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

Instances

Instances details
ContainsCostCentreState DsGblEnv 
Instance details

Defined in TcRnMonad

ContainsCostCentreState TcGblEnv 
Instance details

Defined in TcRnMonad

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 #

This function provides an escape for direct access to the TcM monad. It should not be used lightly, and the provided TcPluginM API should be favoured instead.

hasCompleteSig :: TcSigFun -> Name -> Bool #

No signature or a partial signature

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.

data NameShape #

A NameShape is a substitution on Names 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 AvailInfos 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 AvailInfos 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.

type TcRnIf a b = IOEnv (Env a b) #

type IfM lcl = TcRnIf IfGblEnv lcl #

type IfG = IfM () #

type IfL = IfM IfLclEnv #

type RnM = TcRn #

Historical "renaming monad" (now it's just TcRn).

type TcM = TcRn #

Historical "type-checking monad" (now it's just TcRn).

data Env gbl lcl #

Constructors

Env 

Fields

Instances

Instances details
ContainsDynFlags (Env gbl lcl) 
Instance details

Defined in TcRnTypes

Methods

extractDynFlags :: Env gbl lcl -> DynFlags #

ContainsModule gbl => ContainsModule (Env gbl lcl) 
Instance details

Defined in TcRnTypes

Methods

extractModule :: Env gbl lcl -> Module #

data IfGblEnv #

Constructors

IfGblEnv 

data DsLclEnv #

Constructors

DsLclEnv 

data DsMetaVal #

Constructors

DsBound Id 
DsSplice (HsExpr GhcTc) 

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.

data 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

Instances details
ContainsCostCentreState TcGblEnv 
Instance details

Defined in TcRnMonad

ContainsModule TcGblEnv 
Instance details

Defined in TcRnTypes

data SelfBootInfo #

Constructors

NoSelfBoot 
SelfBoot 

type TcRef a = IORef a #

Type alias for IORef; the convention is we'll use this for mutable bits of data in TcGblEnv which are updated during typechecking and returned at the end.

type TcId = Id #

type TcIdSet = IdSet #

data TcBinder #

Instances

Instances details
HasOccName TcBinder 
Instance details

Defined in TcRnTypes

Methods

occName :: TcBinder -> OccName #

Outputable TcBinder 
Instance details

Defined in TcRnTypes

data SpliceType #

Constructors

Typed 
Untyped 

data ThStage #

Instances

Instances details
Outputable ThStage 
Instance details

Defined in TcRnTypes

Methods

ppr :: ThStage -> SDoc #

pprPrec :: Rational -> ThStage -> SDoc #

type ThLevel = Int #

data TcTyThing #

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.

Instances

Instances details
Outputable TcTyThing 
Instance details

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.

Instances

Instances details
Outputable IdBindingInfo 
Instance details

Defined in TcRnTypes

data IsGroupClosed #

IsGroupClosed describes a group of mutually-recursive bindings

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

  • imp_mods :: ImportedMods

    Domain is all directly-imported modules

    See the documentation on ImportedModsVal in HscTypes for the meaning of the fields.

    We need a full ModuleEnv rather than a ModuleNameEnv here, because we might be importing modules of the same name from different packages. (currently not the case, but might be in the future).

  • imp_dep_mods :: ModuleNameEnv (ModuleName, IsBootInterface)

    Home-package modules needed by the module being compiled

    It doesn't matter whether any of these dependencies are actually used when compiling the module; they are listed if they are below it at all. For example, suppose M imports A which imports X. Then compiling M might not need to consult X.hi, but X is still listed in M's dependencies.

  • imp_dep_pkgs :: Set InstalledUnitId

    Packages needed by the module being compiled, whether directly, or via other modules in this package, or via modules imported from other packages.

  • imp_trust_pkgs :: Set InstalledUnitId

    This is strictly a subset of imp_dep_pkgs and records the packages the current module needs to trust for Safe Haskell compilation to succeed. A package is required to be trusted if we are dependent on a trustworthy module in that package. While perhaps making imp_dep_pkgs a tuple of (UnitId, Bool) where True for the bool indicates the package is required to be trusted is the more logical design, doing so complicates a lot of code not concerned with Safe Haskell. See Note [RnNames . Tracking Trust Transitively]

  • imp_trust_own_pkg :: Bool

    Do we require that our own package is trusted? This is to handle efficiently the case where a Safe module imports a Trustworthy module that resides in the same package as it. See Note [RnNames . Trust Own Package]

  • imp_orphs :: [Module]

    Orphan modules below us in the import tree (and maybe including us for imported modules)

  • imp_finsts :: [Module]

    Family instance modules below us in the import tree (and maybe including us for imported modules)

data WhereFrom #

Instances

Instances details
Outputable WhereFrom 
Instance details

Defined in TcRnTypes

data TcSigInfo #

Instances

Instances details
Outputable TcSigInfo 
Instance details

Defined in TcRnTypes

data TcIdSigInfo #

Instances

Instances details
Outputable TcIdSigInfo 
Instance details

Defined in TcRnTypes

data TcIdSigInst #

Instances

Instances details
Outputable TcIdSigInst 
Instance details

Defined in TcRnTypes

data TcPluginM a #

Instances

Instances details
Monad TcPluginM 
Instance details

Defined in TcRnTypes

Methods

(>>=) :: TcPluginM a -> (a -> TcPluginM b) -> TcPluginM b #

(>>) :: TcPluginM a -> TcPluginM b -> TcPluginM b #

return :: a -> TcPluginM a #

Functor TcPluginM 
Instance details

Defined in TcRnTypes

Methods

fmap :: (a -> b) -> TcPluginM a -> TcPluginM b #

(<$) :: a -> TcPluginM b -> TcPluginM a #

MonadFail TcPluginM 
Instance details

Defined in TcRnTypes

Methods

fail :: String -> TcPluginM a #

Applicative TcPluginM 
Instance details

Defined in TcRnTypes

Methods

pure :: a -> TcPluginM a #

(<*>) :: TcPluginM (a -> b) -> TcPluginM a -> TcPluginM b #

liftA2 :: (a -> b -> c) -> TcPluginM a -> TcPluginM b -> TcPluginM c #

(*>) :: TcPluginM a -> TcPluginM b -> TcPluginM b #

(<*) :: TcPluginM a -> TcPluginM b -> TcPluginM a #

data TcPlugin #

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.

data Hole #

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)

Instances

Instances details
Outputable Hole 
Instance details

Defined in Constraint

Methods

ppr :: Hole -> SDoc #

pprPrec :: Rational -> Hole -> SDoc #

data CompleteMatch #

A list of conlikes which represents a complete pattern match. These arise from COMPLETE signatures.

Constructors

CompleteMatch 

Fields

Instances

Instances details
Outputable CompleteMatch 
Instance details

Defined in HscTypes

updEnv :: (env -> env') -> IOEnv env' a -> IOEnv env a #

Perform a computation with an altered environment

setEnv :: env' -> IOEnv env' a -> IOEnv env a #

Perform a computation with a different environment

getEnv :: IOEnv env env #

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'.

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) #

unsafeInterleaveM :: IOEnv env a -> IOEnv env a #

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 #

Instances

Instances details
Monad (IOEnv m) 
Instance details

Defined in IOEnv

Methods

(>>=) :: IOEnv m a -> (a -> IOEnv m b) -> IOEnv m b #

(>>) :: IOEnv m a -> IOEnv m b -> IOEnv m b #

return :: a -> IOEnv m a #

Functor (IOEnv env) 
Instance details

Defined in IOEnv

Methods

fmap :: (a -> b) -> IOEnv env a -> IOEnv env b #

(<$) :: a -> IOEnv env b -> IOEnv env a #

MonadFail (IOEnv m) 
Instance details

Defined in IOEnv

Methods

fail :: String -> IOEnv m a #

Applicative (IOEnv m) 
Instance details

Defined in IOEnv

Methods

pure :: a -> IOEnv m a #

(<*>) :: IOEnv m (a -> b) -> IOEnv m a -> IOEnv m b #

liftA2 :: (a -> b -> c) -> IOEnv m a -> IOEnv m b -> IOEnv m c #

(*>) :: IOEnv m a -> IOEnv m b -> IOEnv m b #

(<*) :: IOEnv m a -> IOEnv m b -> IOEnv m a #

MonadPlus (IOEnv env) 
Instance details

Defined in IOEnv

Methods

mzero :: IOEnv env a #

mplus :: IOEnv env a -> IOEnv env a -> IOEnv env a #

MonadIO (IOEnv env) 
Instance details

Defined in IOEnv

Methods

liftIO :: IO a -> IOEnv env a #

Alternative (IOEnv env) 
Instance details

Defined in IOEnv

Methods

empty :: IOEnv env a #

(<|>) :: IOEnv env a -> IOEnv env a -> IOEnv env a #

some :: IOEnv env a -> IOEnv env [a] #

many :: IOEnv env a -> IOEnv env [a] #

ContainsDynFlags env => HasDynFlags (IOEnv env) 
Instance details

Defined in IOEnv

Methods

getDynFlags :: IOEnv env DynFlags #

ContainsModule env => HasModule (IOEnv env) 
Instance details

Defined in IOEnv

Methods

getModule :: IOEnv env Module #

ExceptionMonad (IOEnv a) 
Instance details

Defined in IOEnv

Methods

gcatch :: Exception e => IOEnv a a0 -> (e -> IOEnv a a0) -> IOEnv a a0 #

gmask :: ((IOEnv a a0 -> IOEnv a a0) -> IOEnv a b) -> IOEnv a b #

gbracket :: IOEnv a a0 -> (a0 -> IOEnv a b) -> (a0 -> IOEnv a c) -> IOEnv a c #

gfinally :: IOEnv a a0 -> IOEnv a b -> IOEnv a a0 #

data IOEnvFailure #

Constructors

IOEnvFailure 

Instances

Instances details
Show IOEnvFailure 
Instance details

Defined in IOEnv

Exception IOEnvFailure 
Instance details

Defined in IOEnv

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

orM :: Monad m => m Bool -> m Bool -> m Bool #

Monadic version of or

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

mapSndM :: Monad m => (b -> m c) -> [(a, b)] -> m [(a, c)] #

Monadic version of mapSnd

mapAccumLM #

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]) #

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 #

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

Instances details
Eq ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Show ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

type Rep ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.ForeignSrcLang.Type" "ghc-boot-th-8.10.2" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type))))

module TidyPgm

module TyCon

module TysPrim

module TysWiredIn

tyConAppNeedsKindSig #

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 TyCon is applied to.

-> Bool

Does T t_1 ... t_n need a kind signature? (Where n is the number of arguments)

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

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 #

Find the result Kind of a type synonym, after applying it to its arity number of type variables Actually this function works fine on data types too, but they'd always return *, so we never need to ask

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)

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.

nonDetCmpTc :: TyCon -> TyCon -> Ordering #

Compare two TyCons. NB: This should never see Constraint (as recognized by Kind.isConstraintKindCon) which is considered a synonym for Type in Core. See Note [Kind Constraint and kind Type] in Kind. See Note [nonDetCmpType nondeterminism]

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.

seqTypes :: [Type] -> () #

seqType :: Type -> () #

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

isAlgType :: Type -> Bool #

See Type for what an algebraic type is. Should only be applied to types, as opposed to e.g. partially saturated type constructors

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 TyConApps. Useful for e.g. dropping 'LiftedRep arguments of unboxed tuple TyCon applications:

dropRuntimeRepArgs [ 'LiftedRep, 'IntRep , String, Int]

isRuntimeRepKindedTy :: Type -> Bool #

Is this a type of kind RuntimeRep? (e.g. LiftedRep)

mightBeUnliftedType :: Type -> Bool #

Returns:

  • False if the type is guaranteed lifted or
  • True if it is unlifted, OR we aren't sure (e.g. in a levity-polymorphic case)

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 #

Does this type classify a core (unlifted) Coercion? At either role nominal or representational (t1 ~ t2) See Note [Types for coercions, predicates, and evidence] in TyCoRep

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.

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 AppTys. (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] #

Given a TyCon and a list of argument types, filter out any Inferred arguments.

filterOutInvisibleTypes :: TyCon -> [Type] -> [Type] #

Given a TyCon and a list of argument types, filter out any invisible (i.e., Inferred or Specified) arguments.

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.

isFunTy :: Type -> Bool #

Is this a function?

isPiTy :: Type -> Bool #

Is this a function or forall?

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 sameVis argf supplied_argf is True, 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.

mkTyConBindersPreferAnon #

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.

mkLamTypes :: [Var] -> Type -> Type #

mkLamType for multiple type or value arguments

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

mkTyCoInvForAllTy :: TyCoVar -> Type -> Type #

Make a dependent forall over an Inferred variable

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.

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

tyConAppArgs_maybe :: Type -> Maybe [Type] #

The same as snd . splitTyConApp

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 #

A key function: builds a TyConApp or FunTy as appropriate to its arguments. Applies its arguments to the constructor from left to right.

applyTysX :: [TyVar] -> Type -> [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 undefineds type.

funArgTy :: Type -> 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

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.

isLitTy :: Type -> Maybe TyLit #

Is this a type literal (symbol or numeric).

isStrLitTy :: Type -> Maybe FastString #

Is this a symbol literal. We also look through type synonyms.

isNumLitTy :: Type -> Maybe Integer #

Is this a numeric literal. We also look through type synonyms.

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!

mkAppTys :: Type -> [Type] -> Type #

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_maybe :: Type -> Maybe TyVar #

Attempts to obtain the type variable underlying a Type

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 #

mapType :: Monad m => TyCoMapper env m -> env -> Type -> m Type #

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.

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

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 Types 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 Types 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

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!

getTCvSubstRangeFVs :: TCvSubst -> VarSet #

Returns the free variables of the types in the range of a substitution as a non-deterministic set.

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

data TCvSubst #

Type & coercion substitution

The following invariants must hold of a TCvSubst:

  1. The in-scope set is needed only to guide the generation of fresh uniques
  2. In particular, the kind of the type variables in the in-scope set is not relevant
  3. The substitution is only applied ONCE! This is because in general such application will not reach a fixed point.

Instances

Instances details
Outputable TCvSubst 
Instance details

Defined in TyCoSubst

type TvSubstEnv = TyVarEnv Type #

A substitution of Types for TyVars and Kinds for KindVars

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

tidyTypes :: TidyEnv -> [Type] -> [Type] #

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 TyVars 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.

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.

funTyCon :: TyCon #

The (->) type constructor.

(->) :: forall (rep1 :: RuntimeRep) (rep2 :: RuntimeRep).
        TYPE rep1 -> TYPE rep2 -> *

mkTyConTy :: TyCon -> Type #

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 TyCoVars from left to right

mkInvisFunTys :: [Type] -> Type -> Type #

Make nested arrow types

mkInvisFunTy :: Type -> Type -> Type infixr 3 #

mkVisFunTy :: Type -> Type -> Type infixr 3 #

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

type KnotTied ty = ty #

A type labeled KnotTied might have knot-tied tycons in it. See Note [Type checking recursive type and class declarations] in TcTyClsDecls

mkAppTy :: Type -> Type -> Type #

Applies a type to another, as in e.g. k a

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

eqType :: Type -> Type -> Bool #

Type equality on source types. Does not look through newtypes or PredTypes, 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

partitionInvisibleTypes :: TyCon -> [Type] -> ([Type], [Type]) #

Given a TyCon and a list of argument types, partition the arguments into:

  1. Inferred or Specified (i.e., invisible) arguments and
  2. Required (i.e., visible) arguments

isTyVar :: Var -> Bool #

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

binderArgFlag :: VarBndr tv argf -> argf #

binderVars :: [VarBndr tv argf] -> [tv] #

binderVar :: VarBndr tv argf -> tv #

sameVis :: ArgFlag -> ArgFlag -> Bool #

Do these denote the same level of visibility? Required arguments are visible, others are not. So this function equates Specified and Inferred. Used for printing.

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?

type TyVar = Var #

Type or kind Variable

type TyCoVar = Id #

Type or Coercion Variable

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 forall (with an arrow)

ForallInvis

An invisible forall (with a dot)

Instances

Instances details
Eq ForallVisFlag 
Instance details

Defined in Var

Data ForallVisFlag 
Instance details

Defined in Var

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForallVisFlag -> c ForallVisFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForallVisFlag #

toConstr :: ForallVisFlag -> Constr #

dataTypeOf :: ForallVisFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForallVisFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForallVisFlag) #

gmapT :: (forall b. Data b => b -> b) -> ForallVisFlag -> ForallVisFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForallVisFlag -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForallVisFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> ForallVisFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForallVisFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForallVisFlag -> m ForallVisFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForallVisFlag -> m ForallVisFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForallVisFlag -> m ForallVisFlag #

Ord ForallVisFlag 
Instance details

Defined in Var

Outputable ForallVisFlag 
Instance details

Defined in Var

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

mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type #

Like mkTyCoForAllTy, but does not check the occurrence of the binder See Note [Unused coercion variable in ForAllTy]

data Type #

Instances

Instances details
Data Type 
Instance details

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 #

toConstr :: Type -> Constr #

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 # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: Type -> () #

Outputable Type 
Instance details

Defined in TyCoRep

Methods

ppr :: Type -> SDoc #

pprPrec :: Rational -> Type -> SDoc #

Eq (DeBruijn Type) 
Instance details

Defined in CoreMap

Methods

(==) :: DeBruijn Type -> DeBruijn Type -> Bool #

(/=) :: DeBruijn Type -> DeBruijn Type -> Bool #

ToHie (TScoped Type) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: TScoped Type -> HieM [HieAST Type]

data TyThing #

A global typecheckable-thing, essentially anything that has a name. Not to be confused with a TcTyThing, which is also a typecheckable thing but in the *local* context. See TcEnv for how to retrieve a TyThing given a Name.

Instances

Instances details
NamedThing TyThing 
Instance details

Defined in TyCoRep

Outputable TyThing 
Instance details

Defined in TyCoRep

Methods

ppr :: TyThing -> SDoc #

pprPrec :: Rational -> TyThing -> SDoc #

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

Instances details
Data TyCoBinder 
Instance details

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 
Instance details

Defined in TyCoRep

type PredType = Type #

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"

type Kind = Type #

The key type representing kinds in the compiler.

type ThetaType = [PredType] #

A collection of PredTypes

data ArgFlag #

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

Constructors

Inferred 
Specified 
Required 

Instances

Instances details
Eq ArgFlag 
Instance details

Defined in Var

Methods

(==) :: ArgFlag -> ArgFlag -> Bool #

(/=) :: ArgFlag -> ArgFlag -> Bool #

Data ArgFlag 
Instance details

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 
Instance details

Defined in Var

Binary ArgFlag 
Instance details

Defined in Var

Outputable ArgFlag 
Instance details

Defined in Var

Methods

ppr :: ArgFlag -> SDoc #

pprPrec :: Rational -> ArgFlag -> SDoc #

Outputable tv => Outputable (VarBndr tv ArgFlag) 
Instance details

Defined in Var

data AnonArgFlag #

The non-dependent version of ArgFlag.

Constructors

VisArg

Used for (->): an ordinary non-dependent arrow. The argument is visible in source code.

InvisArg

Used for (=>): a non-dependent predicate arrow. The argument is invisible in source code.

Instances

Instances details
Eq AnonArgFlag 
Instance details

Defined in Var

Data AnonArgFlag 
Instance details

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 
Instance details

Defined in Var

Binary AnonArgFlag 
Instance details

Defined in Var

Outputable AnonArgFlag 
Instance details

Defined in Var

data Var #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
Eq Var 
Instance details

Defined in Var

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Data Var 
Instance details

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 #

toConstr :: Var -> Constr #

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 
Instance details

Defined in Var

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

NamedThing Var 
Instance details

Defined in Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in Var

Methods

occName :: Var -> OccName #

Uniquable Var 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in Var

Methods

ppr :: Var -> SDoc #

pprPrec :: Rational -> Var -> SDoc #

ModifyState Id 
Instance details

Defined in Compat.HieAst

Methods

addSubstitution :: Id -> Id -> HieState -> HieState

Eq (DeBruijn CoreExpr) 
Instance details

Defined in CoreMap

Methods

(==) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

(/=) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

Eq (DeBruijn CoreAlt) 
Instance details

Defined in CoreMap

Methods

(==) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

(/=) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

module Unify

module UniqSupply

data Var #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
Eq Var 
Instance details

Defined in Var

Methods

(==) :: Var -> Var -> Bool #

(/=) :: Var -> Var -> Bool #

Data Var 
Instance details

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 #

toConstr :: Var -> Constr #

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 
Instance details

Defined in Var

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

(>=) :: Var -> Var -> Bool #

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

NamedThing Var 
Instance details

Defined in Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in Var

Methods

occName :: Var -> OccName #

Uniquable Var 
Instance details

Defined in Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in Var

Methods

ppr :: Var -> SDoc #

pprPrec :: Rational -> Var -> SDoc #

ModifyState Id 
Instance details

Defined in Compat.HieAst

Methods

addSubstitution :: Id -> Id -> HieState -> HieState

Eq (DeBruijn CoreExpr) 
Instance details

Defined in CoreMap

Methods

(==) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

(/=) :: DeBruijn CoreExpr -> DeBruijn CoreExpr -> Bool #

Eq (DeBruijn CoreAlt) 
Instance details

Defined in CoreMap

Methods

(==) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

(/=) :: DeBruijn CoreAlt -> DeBruijn CoreAlt -> Bool #

ToHie (Context (Located Var)) 
Instance details

Defined in Compat.HieAst

Methods

toHie :: Context (Located Var) -> HieM [HieAST Type]

Syntax re-exports

module GHC.Hs

module Parser

module Lexer