ghc-9.6.0.20230302: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Driver.Backend

Description

This module exports the Backend type and all the available values of that type. The type is abstract, and GHC assumes a "closed world": all the back ends are known and are known here. The compiler driver chooses a Backend value based on how it is asked to generate code.

A Backend value encapsulates the knowledge needed to take Cmm, STG, or Core and write assembly language to a file. A back end also provides a function that enables the compiler driver to run an assembler on the code that is written, if any (the "post-backend pipeline"). Finally, a back end has myriad properties. Properties mediate interactions between a back end and the rest of the compiler, especially the driver. Examples include the following:

  • Property backendValidityOfCImport says whether the back end can import foreign C functions.
  • Property backendForcesOptimization0 says whether the back end can be used with optimization levels higher than `-O0`.
  • Property backendCDefs tells the compiler driver, "if you're using this back end, then these are the command-line flags you should add to any invocation of the C compiler."

These properties are used elsewhere in GHC, primarily in the driver, to fine-tune operations according to the capabilities of the chosen back end. You might use a property to make GHC aware of a potential limitation of certain back ends, or a special feature available only in certain back ends. If your client code needs to know a fact that is not exposed in an existing property, you would define and export a new property. Conditioning client code on the identity or name of a back end is Not Done.

For full details, see the documentation of each property.

Synopsis

The Backend type

data Backend Source #

A value of type Backend represents one of GHC's back ends. The set of back ends cannot be extended except by modifying the definition of Backend in this module.

The Backend type is abstract; that is, its value constructors are not exported. It's crucial that they not be exported, because a value of type Backend carries only the back end's name, not its behavior or properties. If Backend were not abstract, then code elsewhere in the compiler could depend directly on the name, not on the semantics, which would make it challenging to create a new back end. Because Backend is abstract, all the obligations of a new back end are enumerated in this module, in the form of functions that take Backend as an argument.

The issue of abstraction is discussed at great length in #20927 and !7442.

Instances

Instances details
Show Backend Source #

The Show instance is for messages only. If code depends on what's in the string, you deserve what happens to you.

Instance details

Defined in GHC.Driver.Backend

Available back ends

ncgBackend :: Backend Source #

The native code generator. Compiles Cmm code into textual assembler, then relies on an external assembler toolchain to produce machine code.

Only supports a few platforms (X86, PowerPC, SPARC).

See GHC.CmmToAsm.

llvmBackend :: Backend Source #

The LLVM backend.

Compiles Cmm code into LLVM textual IR, then relies on LLVM toolchain to produce machine code.

It relies on LLVM support for the calling convention used by the NCG backend to produce code objects ABI compatible with it (see "cc 10" or "ghccc" calling convention in https://llvm.org/docs/LangRef.html#calling-conventions).

Supports a few platforms (X86, AArch64, s390x, ARM).

See GHC.CmmToLlvm

jsBackend :: Backend Source #

The JavaScript Backend

See documentation in GHC.StgToJS

viaCBackend :: Backend Source #

Via-C ("unregisterised") backend.

Compiles Cmm code into C code, then relies on a C compiler to produce machine code.

It produces code objects that are not ABI compatible with those produced by NCG and LLVM backends.

Produced code is expected to be less efficient than the one produced by NCG and LLVM backends because STG registers are not pinned into real registers. On the other hand, it supports more target platforms (those having a valid C toolchain).

See GHC.CmmToC

interpreterBackend :: Backend Source #

The ByteCode interpreter.

Produce ByteCode objects (BCO, see GHC.ByteCode) that can be interpreted. It is used by GHCi.

Currently some extensions are not supported (foreign primops).

See GHC.StgToByteCode

noBackend :: Backend Source #

A dummy back end that generates no code.

Use this back end to disable code generation. It is particularly useful when GHC is used as a library for other purpose than generating code (e.g. to generate documentation with Haddock) or when the user requested it (via `-fno-code`) for some reason.

allBackends :: [Backend] Source #

A list of all back ends. They are ordered as we wish them to appear when they are enumerated in error messages.

Types used to specify properties of back ends

data PrimitiveImplementation Source #

This enumeration type specifies how the back end wishes GHC's primitives to be implemented. (Module GHC.StgToCmm.Prim provides a generic implementation of every primitive, but some primitives, like IntQuotRemOp, can be implemented more efficiently by certain back ends on certain platforms. For example, by using a machine instruction that simultaneously computes quotient and remainder.)

For the meaning of each alternative, consult GHC.StgToCmm.Config. (In a perfect world, type PrimitiveImplementation would be defined there, in the module that determines its meaning. But I could not figure out how to do it without mutual recursion across module boundaries.)

Constructors

LlvmPrimitives

Primitives supported by LLVM

NcgPrimitives

Primitives supported by the native code generator

JSPrimitives

Primitives supported by JS backend

GenericPrimitives

Primitives supported by all back ends

Properties that stand for functions

Back-end function for code generation

data DefunctionalizedCodeOutput Source #

Names a function that generates code and writes the results to a file, of this type:

   Logger
-> DynFlags
-> Module -- ^ module being compiled
-> ModLocation
-> FilePath -- ^ Where to write output
-> Set UnitId -- ^ dependencies
-> Stream IO RawCmmGroup a -- results from `StgToCmm`
-> IO a

The functions so named are defined in GHC.Driver.CodeOutput.

We expect one function per back end—or more precisely, one function for each back end that writes code to a file. (The interpreter does not write to files; its output lives only in memory.)

Back-end functions for assembly

data DefunctionalizedPostHscPipeline Source #

Names a function that tells the driver what should happen after assembly code is written. This might include running a C compiler, running LLVM, running an assembler, or various similar activities. The function named normally has this type:

   TPipelineClass TPhase m
=> PipeEnv
-> HscEnv
-> Maybe ModLocation
-> FilePath
-> m (Maybe FilePath)

The functions so named are defined in GHC.Driver.Pipeline.

Constructors

NcgPostHscPipeline 
ViaCPostHscPipeline 
LlvmPostHscPipeline 
JSPostHscPipeline 
NoPostHscPipeline

After code generation, nothing else need happen.

data DefunctionalizedAssemblerProg Source #

Names a function that runs the assembler, of this type:

Logger -> DynFlags -> Platform -> [Option] -> IO ()

The functions so named are defined in GHC.Driver.Pipeline.Execute.

Constructors

StandardAssemblerProg

Use the standard system assembler

JSAssemblerProg

JS Backend compile to JS via Stg, and so does not use any assembler

DarwinClangAssemblerProg

If running on Darwin, use the assembler from the clang toolchain. Otherwise use the standard system assembler.

data DefunctionalizedAssemblerInfoGetter Source #

Names a function that discover from what toolchain the assembler is coming, of this type:

Logger -> DynFlags -> Platform -> IO CompilerInfo

The functions so named are defined in GHC.Driver.Pipeline.Execute.

Constructors

StandardAssemblerInfoGetter

Interrogate the standard system assembler

JSAssemblerInfoGetter

If using the JS backend; return Emscripten

DarwinClangAssemblerInfoGetter

If running on Darwin, return Clang; otherwise interrogate the standard system assembler.

Other back-end functions

data DefunctionalizedCDefs Source #

Names a function that tells the driver what command-line options to include when invoking a C compiler. It's meant for -D options that define symbols for the C preprocessor. Because the exact symbols defined might depend on versions of tools located in the file system (cough LLVM cough), the function requires an IO action. The function named has this type:

Logger -> DynFlags -> IO [String]

Constructors

NoCDefs

No additional command-line options are needed

LlvmCDefs

Return command-line options that tell GHC about the LLVM version.

Names of back ends (for API clients of version 9.4 or earlier)

Properties of back ends

backendDescription :: Backend -> String Source #

An informal description of the back end, for use in issuing warning messages only. If code depends on what's in the string, you deserve what happens to you.

backendWritesFiles :: Backend -> Bool Source #

This flag tells the compiler driver whether the back end will write files: interface files and object files. It is typically true for "real" back ends that generate code into the filesystem. (That means, not the interpreter.)

backendPipelineOutput :: Backend -> PipelineOutput Source #

When the back end does write files, this value tells the compiler in what manner of file the output should go: temporary, persistent, or specific.

backendCanReuseLoadedCode :: Backend -> Bool Source #

This flag tells the driver whether the back end can reuse code (bytecode or object code) that has been loaded dynamically. Likely true only of the interpreter.

backendGeneratesCode :: Backend -> Bool Source #

It is is true of every back end except -fno-code that it "generates code." Surprisingly, this property influences the driver in a ton of ways. Some examples:

  • If the back end does not generate code, then the driver needs to turn on code generation for Template Haskell (because that code needs to be generated and run at compile time).
  • If the back end does not generate code, then the driver does not need to deal with an output file.
  • If the back end does generated code, then the driver supports HscRecomp. If not, recompilation does not need a linkable (and is automatically up to date).

backendSupportsInterfaceWriting :: Backend -> Bool Source #

When set, this flag turns on interface writing for Backpack. It should probably be the same as backendGeneratesCode, but it is kept distinct for reasons described in Note [-fno-code mode].

backendRespectsSpecialise :: Backend -> Bool Source #

When preparing code for this back end, the type checker should pay attention to SPECIALISE pragmas. If this flag is False, then the type checker ignores SPECIALISE pragmas (for imported things?).

backendWantsGlobalBindings :: Backend -> Bool Source #

This back end wants the mi_globals field of a ModIface to be populated (with the top-level bindings of the original source). True for the interpreter, and also true for "no backend", which is used by Haddock. (After typechecking a module, Haddock wants access to the module's GlobalRdrEnv.)

backendHasNativeSwitch :: Backend -> Bool Source #

The back end targets a technology that implements switch natively. (For example, LLVM or C.) Therefore it is not necessary for GHC to ccompile a Cmm Switch form into a decision tree with jump tables at the leaves.

backendPrimitiveImplementation :: Backend -> PrimitiveImplementation Source #

As noted in the documentation for PrimitiveImplementation, certain primitives have multiple implementations, depending on the capabilities of the back end. This field signals to module GHC.StgToCmm.Prim what implementations to use with this back end.

backendSimdValidity :: Backend -> Validity' String Source #

When this value is IsValid, the back end is compatible with vector instructions. When it is NotValid, it carries a message that is shown to users.

backendSupportsEmbeddedBlobs :: Backend -> Bool Source #

This flag says whether the back end supports large binary blobs. See Note [Embedding large binary blobs] in GHC.CmmToAsm.Ppr.

backendNeedsPlatformNcgSupport :: Backend -> Bool Source #

This flag tells the compiler driver that the back end does not support every target platform; it supports only platforms that claim NCG support. (It's set only for the native code generator.) Crufty. If the driver tries to use the native code generator without platform support, the driver fails over to the LLVM back end.

backendSupportsUnsplitProcPoints :: Backend -> Bool Source #

This flag is set if the back end can generate code for proc points. If the flag is not set, then a Cmm pass needs to split proc points (that is, turn each proc point into a standalone procedure).

backendSwappableWithViaC :: Backend -> Bool Source #

This flag guides the driver in resolving issues about API support on the target platform. If the flag is set, then these things are true:

  • When the target platform supports only an unregisterised API, this backend can be replaced with compilation via C.
  • When the target does not support an unregisterised API, this back end can replace compilation via C.

backendUnregisterisedAbiOnly :: Backend -> Bool Source #

This flag is true if the back end works *only* with the unregisterised ABI.

backendGeneratesHc :: Backend -> Bool Source #

This flag is set if the back end generates C code in a .hc file. The flag lets the compiler driver know if the command-line flag -C is meaningful.

backendSptIsDynamic :: Backend -> Bool Source #

This flag says whether SPT (static pointer table) entries will be inserted dynamically if needed. If this flag is False, then GHC.Iface.Tidy should emit C stubs that initialize the SPT entries.

backendWantsBreakpointTicks :: Backend -> Bool Source #

If this flag is set, then GHC.HsToCore.Ticks inserts Breakpoint ticks. Used only for the interpreter.

backendForcesOptimization0 :: Backend -> Bool Source #

If this flag is set, then the driver forces the optimization level to 0, issuing a warning message if the command line requested a higher optimization level.

backendNeedsFullWays :: Backend -> Bool Source #

I don't understand exactly how this works. But if this flag is set *and* another condition is met, then ghc/Main.hs will alter the DynFlags so that all the hostFullWays are asked for. It is set only for the interpreter.

backendSpecialModuleSource :: Backend -> Bool -> Maybe String Source #

This flag is also special for the interpreter: if a message about a module needs to be shown, do we know anything special about where the module came from? The Boolean argument is a recomp flag.

backendSupportsHpc :: Backend -> Bool Source #

This flag says whether the back end supports Haskell Program Coverage (HPC). If not, the compiler driver will ignore the `-fhpc` option (and will issue a warning message if it is used).

backendSupportsCImport :: Backend -> Bool Source #

This flag says whether the back end supports foreign import of C functions. (Supports means "does not barf on," so -fno-code supports foreign C imports.)

backendSupportsCExport :: Backend -> Bool Source #

This flag says whether the back end supports foreign export of Haskell functions to C.

backendAssemblerProg :: Backend -> DefunctionalizedAssemblerProg Source #

This (defunctionalized) function runs the assembler used on the code that is written by this back end. A program determined by a combination of back end, DynFlags, and Platform is run with the given Options.

The function's type is Logger -> DynFlags -> Platform -> [Option] -> IO ()

This field is usually defaulted.

backendAssemblerInfoGetter :: Backend -> DefunctionalizedAssemblerInfoGetter Source #

This (defunctionalized) function is used to retrieve an enumeration value that characterizes the C/assembler part of a toolchain. The function caches the info in a mutable variable that is part of the DynFlags.

The function's type is Logger -> DynFlags -> Platform -> IO CompilerInfo

This field is usually defaulted.

backendCDefs :: Backend -> DefunctionalizedCDefs Source #

When using this back end, it may be necessary or advisable to pass some `-D` options to a C compiler. This (defunctionalized) function produces those options, if any. An IO action may be necessary in order to interrogate external tools about what version they are, for example.

The function's type is Logger -> DynFlags -> IO [String]

This field is usually defaulted.

backendCodeOutput :: Backend -> DefunctionalizedCodeOutput Source #

This (defunctionalized) function generates code and writes it to a file. The type of the function is

   Logger
-> DynFlags
-> Module -- ^ module being compiled
-> ModLocation
-> FilePath -- ^ Where to write output
-> Set UnitId -- ^ dependencies
-> Stream IO RawCmmGroup a -- results from `StgToCmm`
-> IO a

backendPostHscPipeline :: Backend -> DefunctionalizedPostHscPipeline Source #

This (defunctionalized) function tells the compiler driver what else has to be run after code output. The type of the function is

   TPipelineClass TPhase m
=> PipeEnv
-> HscEnv
-> Maybe ModLocation
-> FilePath
-> m (Maybe FilePath)

backendNormalSuccessorPhase :: Backend -> Phase Source #

Somewhere in the compiler driver, when compiling Haskell source (as opposed to a boot file or a sig file), it needs to know what to do with the code that the backendCodeOutput writes to a file. This Phase value gives instructions like "run the C compiler", "run the assembler," or "run the LLVM Optimizer."

backendName :: Backend -> BackendName Source #

Name of the back end, if any. Used to migrate legacy clients of the GHC API. Code within the GHC source tree should not refer to a back end's name.

backendValidityOfCImport :: Backend -> Validity' [Backend] Source #

When foreign C import or export is invalid, the carried value enumerates the valid back ends.

backendValidityOfCExport :: Backend -> Validity' [Backend] Source #

When foreign C import or export is invalid, the carried value enumerates the valid back ends.

Other functions of back ends

platformNcgSupported :: Platform -> Bool Source #

Is the platform supported by the Native Code Generator?