{-# LANGUAGE MultiWayIf #-}

{-|
Module      : GHC.Driver.Backend
Description : Back ends for code generation

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

module GHC.Driver.Backend
   ( -- * The @Backend@ type
     Backend  -- note: type is abstract
   -- * Available back ends
   , ncgBackend
   , llvmBackend
   , jsBackend
   , viaCBackend
   , interpreterBackend
   , noBackend
   , allBackends

    -- * Types used to specify properties of back ends
   , PrimitiveImplementation(..)
     -- ** Properties that stand for functions
     -- *** Back-end function for code generation
   , DefunctionalizedCodeOutput(..)
     -- *** Back-end functions for assembly
   , DefunctionalizedPostHscPipeline(..)
   , DefunctionalizedAssemblerProg(..)
   , DefunctionalizedAssemblerInfoGetter(..)
     -- *** Other back-end functions
   , DefunctionalizedCDefs(..)
     -- ** Names of back ends (for API clients of version 9.4 or earlier)
   , BackendName



     -- * Properties of back ends
   , backendDescription
   , backendWritesFiles
   , backendPipelineOutput
   , backendCanReuseLoadedCode
   , backendGeneratesCode
   , backendGeneratesCodeForHsBoot
   , backendSupportsInterfaceWriting
   , backendRespectsSpecialise
   , backendWantsGlobalBindings
   , backendHasNativeSwitch
   , backendPrimitiveImplementation
   , backendSimdValidity
   , backendSupportsEmbeddedBlobs
   , backendNeedsPlatformNcgSupport
   , backendSupportsUnsplitProcPoints
   , backendSwappableWithViaC
   , backendUnregisterisedAbiOnly
   , backendGeneratesHc
   , backendSptIsDynamic
   , backendWantsBreakpointTicks
   , backendForcesOptimization0
   , backendNeedsFullWays
   , backendSpecialModuleSource
   , backendSupportsHpc
   , backendSupportsCImport
   , backendSupportsCExport
   , backendAssemblerProg
   , backendAssemblerInfoGetter
   , backendCDefs
   , backendCodeOutput
   , backendUseJSLinker
   , backendPostHscPipeline
   , backendNormalSuccessorPhase
   , backendName
   , backendValidityOfCImport
   , backendValidityOfCExport

   -- * Other functions of back ends
   , platformDefaultBackend
   , platformNcgSupported
   )

where


import GHC.Prelude

import GHC.Driver.Backend.Internal (BackendName(..))
import GHC.Driver.Phases


import GHC.Utils.Error
import GHC.Utils.Panic

import GHC.Driver.Pipeline.Monad
import GHC.Platform


---------------------------------------------------------------------------------
--
--   DESIGN CONSIDERATIONS
--
--
--
-- The `Backend` type is made abstract in order to make it possible to
-- add new back ends without having to inspect or modify much code
-- elsewhere in GHC.  Adding a new back end would be /easiest/ if
-- `Backend` were represented as a record type, but in peer review,
-- the clear will of the majority was to use a sum type.  As a result,
-- when adding a new back end it is necessary to modify /every/
-- function in this module that expects `Backend` as its first argument.
-- **By design, these functions have no default/wildcard cases.** This
-- design forces the author of a new back end to consider the semantics
-- in every case, rather than relying on a default that may be wrong.
-- The names and documentation of the functions defined in the `Backend`
-- record are sufficiently descriptive that the author of a new back
-- end will be able to identify correct result values without having to go
-- spelunking throughout the compiler.
--
-- While the design localizes /most/ back-end logic in this module,
-- the author of a new back end will still have to make changes
-- elsewhere in the compiler:
--
--   * For reasons described in Note [Backend Defunctionalization],
--     code-generation and post-backend pipeline functions, among other
--     functions, cannot be placed in the `Backend` record itself.
--     Instead, the /names/ of those functions are placed.  Each name is
--     a value constructor in one of the algebraic data types defined in
--     this module.  The named function is then defined near its point
--     of use.
--
--     The author of a new back end will have to consider whether an
--     existing function will do or whether a new function needs to be
--     defined.  When a new function needs to be defined, the author
--     must take two steps:
--
--       - Add a value constructor to the relevant data type here
--         in the `Backend` module
--
--       - Add a case to the location in the compiler (there should be
--         exactly one) where the value constructors of the relevant
--         data type are used
--
--   * When a new back end is defined, it's quite possible that the
--     compiler driver will have to be changed in some way.  Just because
--     the driver supports five back ends doesn't mean it will support a sixth
--     without changes.
--
-- The collection of functions exported from this module hasn't
-- really been "designed"; it's what emerged from a refactoring of
-- older code.  The real design criterion was "make it crystal clear
-- what has to be done to add a new back end."
--
-- One issue remains unresolved: some of the error messages and
-- warning messages used in the driver assume a "closed world": they
-- think they know all the back ends that exist, and they are not shy
-- about enumerating them.  Just one set of error messages has been
-- ported to have an open-world assumption: these are the error
-- messages associated with type checking of foreign imports and
-- exports.  To allow other errors to be issued with an open-world
-- assumption, use functions `backendValidityOfCImport` and
-- `backendValidityOfCExport` as models, and have a look at how the
-- 'expected back ends' are used in modules "GHC.Tc.Gen.Foreign" and
-- "GHC.Tc.Errors.Ppr"
--
---------------------------------------------------------------------------------


platformDefaultBackend :: Platform -> Backend
platformDefaultBackend :: Platform -> Backend
platformDefaultBackend Platform
platform = if
      | Platform -> Bool
platformUnregisterised Platform
platform -> Backend
viaCBackend
      | Platform -> Bool
platformNcgSupported Platform
platform   -> Backend
ncgBackend
      | Platform -> Bool
platformJSSupported Platform
platform    -> Backend
jsBackend
      | Bool
otherwise                       -> Backend
llvmBackend

-- | Is the platform supported by the Native Code Generator?
platformNcgSupported :: Platform -> Bool
platformNcgSupported :: Platform -> Bool
platformNcgSupported Platform
platform = if
      | Platform -> Bool
platformUnregisterised Platform
platform -> Bool
False -- NCG doesn't support unregisterised ABI
      | Bool
ncgValidArch                    -> Bool
True
      | Bool
otherwise                       -> Bool
False
   where
      ncgValidArch :: Bool
ncgValidArch = case Platform -> Arch
platformArch Platform
platform of
         Arch
ArchX86       -> Bool
True
         Arch
ArchX86_64    -> Bool
True
         Arch
ArchPPC       -> Bool
True
         ArchPPC_64 {} -> Bool
True
         Arch
ArchAArch64   -> Bool
True
         Arch
ArchWasm32    -> Bool
True
         Arch
_             -> Bool
False

-- | Is the platform supported by the JS backend?
platformJSSupported :: Platform -> Bool
platformJSSupported :: Platform -> Bool
platformJSSupported Platform
platform
  | Platform -> Arch
platformArch Platform
platform Arch -> Arch -> Bool
forall a. Eq a => a -> a -> Bool
== Arch
ArchJavaScript = Bool
True
  | Bool
otherwise                               = Bool
False


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


newtype Backend = Named BackendName
  -- Must be a newtype so that it has no `Eq` instance and
  -- a different `Show` instance.

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

instance Show Backend where
  show :: Backend -> String
show = Backend -> String
backendDescription


ncgBackend, llvmBackend, viaCBackend, interpreterBackend, jsBackend, noBackend
    :: Backend

-- | 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".
ncgBackend :: Backend
ncgBackend = BackendName -> Backend
Named BackendName
NCG

-- | 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"
llvmBackend :: Backend
llvmBackend = BackendName -> Backend
Named BackendName
LLVM

-- | The JavaScript Backend
--
-- See documentation in GHC.StgToJS
jsBackend :: Backend
jsBackend = BackendName -> Backend
Named BackendName
JavaScript

-- | 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"
viaCBackend :: Backend
viaCBackend = BackendName -> Backend
Named BackendName
ViaC

-- | 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"
interpreterBackend :: Backend
interpreterBackend = BackendName -> Backend
Named BackendName
Interpreter

-- | 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.
noBackend :: Backend
noBackend = BackendName -> Backend
Named BackendName
NoBackend

---------------------------------------------------------------------------------




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

data PrimitiveImplementation
    = 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
  deriving Int -> PrimitiveImplementation -> ShowS
[PrimitiveImplementation] -> ShowS
PrimitiveImplementation -> String
(Int -> PrimitiveImplementation -> ShowS)
-> (PrimitiveImplementation -> String)
-> ([PrimitiveImplementation] -> ShowS)
-> Show PrimitiveImplementation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimitiveImplementation -> ShowS
showsPrec :: Int -> PrimitiveImplementation -> ShowS
$cshow :: PrimitiveImplementation -> String
show :: PrimitiveImplementation -> String
$cshowList :: [PrimitiveImplementation] -> ShowS
showList :: [PrimitiveImplementation] -> ShowS
Show


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

data DefunctionalizedAssemblerProg
  = 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.



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

data DefunctionalizedAssemblerInfoGetter
  = 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.


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

data DefunctionalizedCodeOutput
  = NcgCodeOutput
  | ViaCCodeOutput
  | LlvmCodeOutput
  | JSCodeOutput


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

data DefunctionalizedPostHscPipeline
  = NcgPostHscPipeline
  | ViaCPostHscPipeline
  | LlvmPostHscPipeline
  | JSPostHscPipeline
  | NoPostHscPipeline -- ^ After code generation, nothing else need happen.

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

data DefunctionalizedCDefs
  = NoCDefs   -- ^ No additional command-line options are needed

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

---------------------------------------------------------------------------------



-- | 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.
backendDescription :: Backend -> String
backendDescription :: Backend -> String
backendDescription (Named BackendName
NCG)         = String
"native code generator"
backendDescription (Named BackendName
LLVM)        = String
"LLVM"
backendDescription (Named BackendName
ViaC)        = String
"compiling via C"
backendDescription (Named BackendName
JavaScript)  = String
"compiling to JavaScript"
backendDescription (Named BackendName
Interpreter) = String
"byte-code interpreter"
backendDescription (Named BackendName
NoBackend)   = String
"no code generated"

-- | 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.)
backendWritesFiles :: Backend -> Bool
backendWritesFiles :: Backend -> Bool
backendWritesFiles (Named BackendName
NCG)         = Bool
True
backendWritesFiles (Named BackendName
LLVM)        = Bool
True
backendWritesFiles (Named BackendName
ViaC)        = Bool
True
backendWritesFiles (Named BackendName
JavaScript)  = Bool
True
backendWritesFiles (Named BackendName
Interpreter) = Bool
False
backendWritesFiles (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendPipelineOutput :: Backend -> PipelineOutput
backendPipelineOutput :: Backend -> PipelineOutput
backendPipelineOutput (Named BackendName
NCG)  = PipelineOutput
Persistent
backendPipelineOutput (Named BackendName
LLVM) = PipelineOutput
Persistent
backendPipelineOutput (Named BackendName
ViaC) = PipelineOutput
Persistent
backendPipelineOutput (Named BackendName
JavaScript)  = PipelineOutput
Persistent
backendPipelineOutput (Named BackendName
Interpreter) = PipelineOutput
NoOutputFile
backendPipelineOutput (Named BackendName
NoBackend)   = PipelineOutput
NoOutputFile

-- | 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.
backendCanReuseLoadedCode :: Backend -> Bool
backendCanReuseLoadedCode :: Backend -> Bool
backendCanReuseLoadedCode (Named BackendName
NCG)         = Bool
False
backendCanReuseLoadedCode (Named BackendName
LLVM)        = Bool
False
backendCanReuseLoadedCode (Named BackendName
ViaC)        = Bool
False
backendCanReuseLoadedCode (Named BackendName
JavaScript)  = Bool
False
backendCanReuseLoadedCode (Named BackendName
Interpreter) = Bool
True
backendCanReuseLoadedCode (Named BackendName
NoBackend)   = Bool
False

-- | 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).
--
backendGeneratesCode :: Backend -> Bool
backendGeneratesCode :: Backend -> Bool
backendGeneratesCode (Named BackendName
NCG)         = Bool
True
backendGeneratesCode (Named BackendName
LLVM)        = Bool
True
backendGeneratesCode (Named BackendName
ViaC)        = Bool
True
backendGeneratesCode (Named BackendName
JavaScript)  = Bool
True
backendGeneratesCode (Named BackendName
Interpreter) = Bool
True
backendGeneratesCode (Named BackendName
NoBackend)   = Bool
False

backendGeneratesCodeForHsBoot :: Backend -> Bool
backendGeneratesCodeForHsBoot :: Backend -> Bool
backendGeneratesCodeForHsBoot (Named BackendName
NCG)         = Bool
True
backendGeneratesCodeForHsBoot (Named BackendName
LLVM)        = Bool
True
backendGeneratesCodeForHsBoot (Named BackendName
ViaC)        = Bool
True
backendGeneratesCodeForHsBoot (Named BackendName
JavaScript)  = Bool
True
backendGeneratesCodeForHsBoot (Named BackendName
Interpreter) = Bool
False
backendGeneratesCodeForHsBoot (Named BackendName
NoBackend)   = Bool
False

-- | 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].
backendSupportsInterfaceWriting :: Backend -> Bool
backendSupportsInterfaceWriting :: Backend -> Bool
backendSupportsInterfaceWriting (Named BackendName
NCG)         = Bool
True
backendSupportsInterfaceWriting (Named BackendName
LLVM)        = Bool
True
backendSupportsInterfaceWriting (Named BackendName
ViaC)        = Bool
True
backendSupportsInterfaceWriting (Named BackendName
JavaScript)  = Bool
True
backendSupportsInterfaceWriting (Named BackendName
Interpreter) = Bool
True
backendSupportsInterfaceWriting (Named BackendName
NoBackend)   = Bool
False

-- | 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?).
backendRespectsSpecialise :: Backend -> Bool
backendRespectsSpecialise :: Backend -> Bool
backendRespectsSpecialise (Named BackendName
NCG)         = Bool
True
backendRespectsSpecialise (Named BackendName
LLVM)        = Bool
True
backendRespectsSpecialise (Named BackendName
ViaC)        = Bool
True
backendRespectsSpecialise (Named BackendName
JavaScript)  = Bool
True
backendRespectsSpecialise (Named BackendName
Interpreter) = Bool
False
backendRespectsSpecialise (Named BackendName
NoBackend)   = Bool
False

-- | 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`.)
backendWantsGlobalBindings :: Backend -> Bool
backendWantsGlobalBindings :: Backend -> Bool
backendWantsGlobalBindings (Named BackendName
NCG)         = Bool
False
backendWantsGlobalBindings (Named BackendName
LLVM)        = Bool
False
backendWantsGlobalBindings (Named BackendName
ViaC)        = Bool
False
backendWantsGlobalBindings (Named BackendName
JavaScript)  = Bool
False
backendWantsGlobalBindings (Named BackendName
Interpreter) = Bool
True
backendWantsGlobalBindings (Named BackendName
NoBackend)   = Bool
True

-- | 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.
backendHasNativeSwitch :: Backend -> Bool
backendHasNativeSwitch :: Backend -> Bool
backendHasNativeSwitch (Named BackendName
NCG)         = Bool
False
backendHasNativeSwitch (Named BackendName
LLVM)        = Bool
True
backendHasNativeSwitch (Named BackendName
ViaC)        = Bool
True
backendHasNativeSwitch (Named BackendName
JavaScript)  = Bool
True
backendHasNativeSwitch (Named BackendName
Interpreter) = Bool
False
backendHasNativeSwitch (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendPrimitiveImplementation :: Backend -> PrimitiveImplementation
backendPrimitiveImplementation :: Backend -> PrimitiveImplementation
backendPrimitiveImplementation (Named BackendName
NCG)         = PrimitiveImplementation
NcgPrimitives
backendPrimitiveImplementation (Named BackendName
LLVM)        = PrimitiveImplementation
LlvmPrimitives
backendPrimitiveImplementation (Named BackendName
JavaScript)  = PrimitiveImplementation
JSPrimitives
backendPrimitiveImplementation (Named BackendName
ViaC)        = PrimitiveImplementation
GenericPrimitives
backendPrimitiveImplementation (Named BackendName
Interpreter) = PrimitiveImplementation
GenericPrimitives
backendPrimitiveImplementation (Named BackendName
NoBackend)   = PrimitiveImplementation
GenericPrimitives

-- | 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.
backendSimdValidity :: Backend -> Validity' String
backendSimdValidity :: Backend -> Validity' String
backendSimdValidity (Named BackendName
NCG)         = String -> Validity' String
forall a. a -> Validity' a
NotValid (String -> Validity' String) -> String -> Validity' String
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [String
"SIMD vector instructions require the LLVM back-end.",String
"Please use -fllvm."]
backendSimdValidity (Named BackendName
LLVM)        = Validity' String
forall a. Validity' a
IsValid
backendSimdValidity (Named BackendName
ViaC)        = String -> Validity' String
forall a. a -> Validity' a
NotValid (String -> Validity' String) -> String -> Validity' String
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [String
"SIMD vector instructions require the LLVM back-end.",String
"Please use -fllvm."]
backendSimdValidity (Named BackendName
JavaScript)  = String -> Validity' String
forall a. a -> Validity' a
NotValid (String -> Validity' String) -> String -> Validity' String
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [String
"SIMD vector instructions require the LLVM back-end.",String
"Please use -fllvm."]
backendSimdValidity (Named BackendName
Interpreter) = String -> Validity' String
forall a. a -> Validity' a
NotValid (String -> Validity' String) -> String -> Validity' String
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [String
"SIMD vector instructions require the LLVM back-end.",String
"Please use -fllvm."]
backendSimdValidity (Named BackendName
NoBackend)   = String -> Validity' String
forall a. a -> Validity' a
NotValid (String -> Validity' String) -> String -> Validity' String
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines [String
"SIMD vector instructions require the LLVM back-end.",String
"Please use -fllvm."]

-- | This flag says whether the back end supports large
-- binary blobs.  See Note [Embedding large binary blobs]
-- in "GHC.CmmToAsm.Ppr".
backendSupportsEmbeddedBlobs :: Backend -> Bool
backendSupportsEmbeddedBlobs :: Backend -> Bool
backendSupportsEmbeddedBlobs (Named BackendName
NCG)         = Bool
True
backendSupportsEmbeddedBlobs (Named BackendName
LLVM)        = Bool
False
backendSupportsEmbeddedBlobs (Named BackendName
ViaC)        = Bool
False
backendSupportsEmbeddedBlobs (Named BackendName
JavaScript)  = Bool
False
backendSupportsEmbeddedBlobs (Named BackendName
Interpreter) = Bool
False
backendSupportsEmbeddedBlobs (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendNeedsPlatformNcgSupport :: Backend -> Bool
backendNeedsPlatformNcgSupport :: Backend -> Bool
backendNeedsPlatformNcgSupport (Named BackendName
NCG)         = Bool
True
backendNeedsPlatformNcgSupport (Named BackendName
LLVM)        = Bool
False
backendNeedsPlatformNcgSupport (Named BackendName
ViaC)        = Bool
False
backendNeedsPlatformNcgSupport (Named BackendName
JavaScript)  = Bool
False
backendNeedsPlatformNcgSupport (Named BackendName
Interpreter) = Bool
False
backendNeedsPlatformNcgSupport (Named BackendName
NoBackend)   = Bool
False

-- | 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).
backendSupportsUnsplitProcPoints :: Backend -> Bool
backendSupportsUnsplitProcPoints :: Backend -> Bool
backendSupportsUnsplitProcPoints (Named BackendName
NCG)         = Bool
True
backendSupportsUnsplitProcPoints (Named BackendName
LLVM)        = Bool
False
backendSupportsUnsplitProcPoints (Named BackendName
ViaC)        = Bool
False
backendSupportsUnsplitProcPoints (Named BackendName
JavaScript)  = Bool
False
backendSupportsUnsplitProcPoints (Named BackendName
Interpreter) = Bool
False
backendSupportsUnsplitProcPoints (Named BackendName
NoBackend)   = Bool
False

-- | 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.
--
backendSwappableWithViaC :: Backend -> Bool
backendSwappableWithViaC :: Backend -> Bool
backendSwappableWithViaC (Named BackendName
NCG)         = Bool
True
backendSwappableWithViaC (Named BackendName
LLVM)        = Bool
True
backendSwappableWithViaC (Named BackendName
ViaC)        = Bool
False
backendSwappableWithViaC (Named BackendName
JavaScript)  = Bool
False
backendSwappableWithViaC (Named BackendName
Interpreter) = Bool
False
backendSwappableWithViaC (Named BackendName
NoBackend)   = Bool
False

-- | This flag is true if the back end works *only* with
-- the unregisterised ABI.
backendUnregisterisedAbiOnly :: Backend -> Bool
backendUnregisterisedAbiOnly :: Backend -> Bool
backendUnregisterisedAbiOnly (Named BackendName
NCG)         = Bool
False
backendUnregisterisedAbiOnly (Named BackendName
LLVM)        = Bool
False
backendUnregisterisedAbiOnly (Named BackendName
ViaC)        = Bool
True
backendUnregisterisedAbiOnly (Named BackendName
JavaScript)  = Bool
False
backendUnregisterisedAbiOnly (Named BackendName
Interpreter) = Bool
False
backendUnregisterisedAbiOnly (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendGeneratesHc :: Backend -> Bool
backendGeneratesHc :: Backend -> Bool
backendGeneratesHc (Named BackendName
NCG)         = Bool
False
backendGeneratesHc (Named BackendName
LLVM)        = Bool
False
backendGeneratesHc (Named BackendName
ViaC)        = Bool
True
backendGeneratesHc (Named BackendName
JavaScript)  = Bool
False
backendGeneratesHc (Named BackendName
Interpreter) = Bool
False
backendGeneratesHc (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendSptIsDynamic :: Backend -> Bool
backendSptIsDynamic :: Backend -> Bool
backendSptIsDynamic (Named BackendName
NCG)         = Bool
False
backendSptIsDynamic (Named BackendName
LLVM)        = Bool
False
backendSptIsDynamic (Named BackendName
ViaC)        = Bool
False
backendSptIsDynamic (Named BackendName
JavaScript)  = Bool
False
backendSptIsDynamic (Named BackendName
Interpreter) = Bool
True
backendSptIsDynamic (Named BackendName
NoBackend)   = Bool
False

-- | If this flag is set, then "GHC.HsToCore.Ticks"
-- inserts `Breakpoint` ticks.  Used only for the
-- interpreter.
backendWantsBreakpointTicks :: Backend -> Bool
backendWantsBreakpointTicks :: Backend -> Bool
backendWantsBreakpointTicks (Named BackendName
NCG)         = Bool
False
backendWantsBreakpointTicks (Named BackendName
LLVM)        = Bool
False
backendWantsBreakpointTicks (Named BackendName
ViaC)        = Bool
False
backendWantsBreakpointTicks (Named BackendName
JavaScript)  = Bool
False
backendWantsBreakpointTicks (Named BackendName
Interpreter) = Bool
True
backendWantsBreakpointTicks (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendForcesOptimization0 :: Backend -> Bool
backendForcesOptimization0 :: Backend -> Bool
backendForcesOptimization0 (Named BackendName
NCG)         = Bool
False
backendForcesOptimization0 (Named BackendName
LLVM)        = Bool
False
backendForcesOptimization0 (Named BackendName
ViaC)        = Bool
False
backendForcesOptimization0 (Named BackendName
JavaScript)  = Bool
False
backendForcesOptimization0 (Named BackendName
Interpreter) = Bool
True
backendForcesOptimization0 (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendNeedsFullWays :: Backend -> Bool
backendNeedsFullWays :: Backend -> Bool
backendNeedsFullWays (Named BackendName
NCG)         = Bool
False
backendNeedsFullWays (Named BackendName
LLVM)        = Bool
False
backendNeedsFullWays (Named BackendName
ViaC)        = Bool
False
backendNeedsFullWays (Named BackendName
JavaScript)  = Bool
False
backendNeedsFullWays (Named BackendName
Interpreter) = Bool
True
backendNeedsFullWays (Named BackendName
NoBackend)   = Bool
False

-- | 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.
backendSpecialModuleSource :: Backend -> Bool -> Maybe String
backendSpecialModuleSource :: Backend -> Bool -> Maybe String
backendSpecialModuleSource (Named BackendName
NCG)         = Maybe String -> Bool -> Maybe String
forall a b. a -> b -> a
const Maybe String
forall a. Maybe a
Nothing
backendSpecialModuleSource (Named BackendName
LLVM)        = Maybe String -> Bool -> Maybe String
forall a b. a -> b -> a
const Maybe String
forall a. Maybe a
Nothing
backendSpecialModuleSource (Named BackendName
ViaC)        = Maybe String -> Bool -> Maybe String
forall a b. a -> b -> a
const Maybe String
forall a. Maybe a
Nothing
backendSpecialModuleSource (Named BackendName
JavaScript)  = Maybe String -> Bool -> Maybe String
forall a b. a -> b -> a
const Maybe String
forall a. Maybe a
Nothing
backendSpecialModuleSource (Named BackendName
Interpreter) = \Bool
b -> if Bool
b then String -> Maybe String
forall a. a -> Maybe a
Just String
"interpreted" else Maybe String
forall a. Maybe a
Nothing
backendSpecialModuleSource (Named BackendName
NoBackend)   = Maybe String -> Bool -> Maybe String
forall a b. a -> b -> a
const (String -> Maybe String
forall a. a -> Maybe a
Just String
"nothing")

-- | 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).
backendSupportsHpc :: Backend -> Bool
backendSupportsHpc :: Backend -> Bool
backendSupportsHpc (Named BackendName
NCG)         = Bool
True
backendSupportsHpc (Named BackendName
LLVM)        = Bool
True
backendSupportsHpc (Named BackendName
ViaC)        = Bool
True
backendSupportsHpc (Named BackendName
JavaScript)  = Bool
False
backendSupportsHpc (Named BackendName
Interpreter) = Bool
False
backendSupportsHpc (Named BackendName
NoBackend)   = Bool
True

-- | 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.)
backendSupportsCImport :: Backend -> Bool
backendSupportsCImport :: Backend -> Bool
backendSupportsCImport (Named BackendName
NCG)         = Bool
True
backendSupportsCImport (Named BackendName
LLVM)        = Bool
True
backendSupportsCImport (Named BackendName
ViaC)        = Bool
True
backendSupportsCImport (Named BackendName
JavaScript)  = Bool
True
backendSupportsCImport (Named BackendName
Interpreter) = Bool
True
backendSupportsCImport (Named BackendName
NoBackend)   = Bool
True

-- | This flag says whether the back end supports foreign
-- export of Haskell functions to C.
backendSupportsCExport :: Backend -> Bool
backendSupportsCExport :: Backend -> Bool
backendSupportsCExport (Named BackendName
NCG)         = Bool
True
backendSupportsCExport (Named BackendName
LLVM)        = Bool
True
backendSupportsCExport (Named BackendName
ViaC)        = Bool
True
backendSupportsCExport (Named BackendName
JavaScript)  = Bool
True
backendSupportsCExport (Named BackendName
Interpreter) = Bool
False
backendSupportsCExport (Named BackendName
NoBackend)   = Bool
True

-- | 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
-- `Option`s.
--
-- The function's type is
-- @
-- Logger -> DynFlags -> Platform -> [Option] -> IO ()
-- @
--
-- This field is usually defaulted.
backendAssemblerProg :: Backend -> DefunctionalizedAssemblerProg
backendAssemblerProg :: Backend -> DefunctionalizedAssemblerProg
backendAssemblerProg (Named BackendName
NCG)  = DefunctionalizedAssemblerProg
StandardAssemblerProg
backendAssemblerProg (Named BackendName
LLVM) = DefunctionalizedAssemblerProg
DarwinClangAssemblerProg
backendAssemblerProg (Named BackendName
ViaC) = DefunctionalizedAssemblerProg
StandardAssemblerProg
backendAssemblerProg (Named BackendName
JavaScript)  = DefunctionalizedAssemblerProg
JSAssemblerProg
backendAssemblerProg (Named BackendName
Interpreter) = DefunctionalizedAssemblerProg
StandardAssemblerProg
backendAssemblerProg (Named BackendName
NoBackend)   = DefunctionalizedAssemblerProg
StandardAssemblerProg

-- | 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.
backendAssemblerInfoGetter :: Backend -> DefunctionalizedAssemblerInfoGetter
backendAssemblerInfoGetter :: Backend -> DefunctionalizedAssemblerInfoGetter
backendAssemblerInfoGetter (Named BackendName
NCG)         = DefunctionalizedAssemblerInfoGetter
StandardAssemblerInfoGetter
backendAssemblerInfoGetter (Named BackendName
LLVM)        = DefunctionalizedAssemblerInfoGetter
DarwinClangAssemblerInfoGetter
backendAssemblerInfoGetter (Named BackendName
ViaC)        = DefunctionalizedAssemblerInfoGetter
StandardAssemblerInfoGetter
backendAssemblerInfoGetter (Named BackendName
JavaScript)  = DefunctionalizedAssemblerInfoGetter
JSAssemblerInfoGetter
backendAssemblerInfoGetter (Named BackendName
Interpreter) = DefunctionalizedAssemblerInfoGetter
StandardAssemblerInfoGetter
backendAssemblerInfoGetter (Named BackendName
NoBackend)   = DefunctionalizedAssemblerInfoGetter
StandardAssemblerInfoGetter

-- | 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.
backendCDefs :: Backend -> DefunctionalizedCDefs
backendCDefs :: Backend -> DefunctionalizedCDefs
backendCDefs (Named BackendName
NCG)         = DefunctionalizedCDefs
NoCDefs
backendCDefs (Named BackendName
LLVM)        = DefunctionalizedCDefs
LlvmCDefs
backendCDefs (Named BackendName
ViaC)        = DefunctionalizedCDefs
NoCDefs
backendCDefs (Named BackendName
JavaScript)  = DefunctionalizedCDefs
NoCDefs
backendCDefs (Named BackendName
Interpreter) = DefunctionalizedCDefs
NoCDefs
backendCDefs (Named BackendName
NoBackend)   = DefunctionalizedCDefs
NoCDefs

-- | 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
backendCodeOutput :: Backend -> DefunctionalizedCodeOutput
backendCodeOutput :: Backend -> DefunctionalizedCodeOutput
backendCodeOutput (Named BackendName
NCG)         = DefunctionalizedCodeOutput
NcgCodeOutput
backendCodeOutput (Named BackendName
LLVM)        = DefunctionalizedCodeOutput
LlvmCodeOutput
backendCodeOutput (Named BackendName
ViaC)        = DefunctionalizedCodeOutput
ViaCCodeOutput
backendCodeOutput (Named BackendName
JavaScript)  = DefunctionalizedCodeOutput
JSCodeOutput
backendCodeOutput (Named BackendName
Interpreter) = String -> DefunctionalizedCodeOutput
forall a. HasCallStack => String -> a
panic String
"backendCodeOutput: interpreterBackend"
backendCodeOutput (Named BackendName
NoBackend)   = String -> DefunctionalizedCodeOutput
forall a. HasCallStack => String -> a
panic String
"backendCodeOutput: noBackend"

backendUseJSLinker :: Backend -> Bool
backendUseJSLinker :: Backend -> Bool
backendUseJSLinker (Named BackendName
NCG)         = Bool
False
backendUseJSLinker (Named BackendName
LLVM)        = Bool
False
backendUseJSLinker (Named BackendName
ViaC)        = Bool
False
backendUseJSLinker (Named BackendName
JavaScript)  = Bool
True
backendUseJSLinker (Named BackendName
Interpreter) = Bool
False
backendUseJSLinker (Named BackendName
NoBackend)   = Bool
False

-- | 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)
backendPostHscPipeline :: Backend -> DefunctionalizedPostHscPipeline
backendPostHscPipeline :: Backend -> DefunctionalizedPostHscPipeline
backendPostHscPipeline (Named BackendName
NCG)  = DefunctionalizedPostHscPipeline
NcgPostHscPipeline
backendPostHscPipeline (Named BackendName
LLVM) = DefunctionalizedPostHscPipeline
LlvmPostHscPipeline
backendPostHscPipeline (Named BackendName
ViaC) = DefunctionalizedPostHscPipeline
ViaCPostHscPipeline
backendPostHscPipeline (Named BackendName
JavaScript)  = DefunctionalizedPostHscPipeline
JSPostHscPipeline
backendPostHscPipeline (Named BackendName
Interpreter) = DefunctionalizedPostHscPipeline
NoPostHscPipeline
backendPostHscPipeline (Named BackendName
NoBackend) = DefunctionalizedPostHscPipeline
NoPostHscPipeline

-- | 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."
backendNormalSuccessorPhase :: Backend -> Phase
backendNormalSuccessorPhase :: Backend -> Phase
backendNormalSuccessorPhase (Named BackendName
NCG)  = Bool -> Phase
As Bool
False
backendNormalSuccessorPhase (Named BackendName
LLVM) = Phase
LlvmOpt
backendNormalSuccessorPhase (Named BackendName
ViaC) = Phase
HCc
backendNormalSuccessorPhase (Named BackendName
JavaScript)  = Phase
StopLn
backendNormalSuccessorPhase (Named BackendName
Interpreter) = Phase
StopLn
backendNormalSuccessorPhase (Named BackendName
NoBackend)   = Phase
StopLn

-- | 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.
backendName :: Backend -> BackendName
backendName :: Backend -> BackendName
backendName (Named BackendName
NCG)  = BackendName
NCG
backendName (Named BackendName
LLVM) = BackendName
LLVM
backendName (Named BackendName
ViaC) = BackendName
ViaC
backendName (Named BackendName
JavaScript)  = BackendName
JavaScript
backendName (Named BackendName
Interpreter) = BackendName
Interpreter
backendName (Named BackendName
NoBackend)   = BackendName
NoBackend



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

allBackends :: [Backend]
allBackends :: [Backend]
allBackends = [ Backend
ncgBackend
              , Backend
llvmBackend
              , Backend
viaCBackend
              , Backend
jsBackend
              , Backend
interpreterBackend
              , Backend
noBackend
              ]

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

backendValidityOfCImport, backendValidityOfCExport :: Backend -> Validity' [Backend]

backendValidityOfCImport :: Backend -> Validity' [Backend]
backendValidityOfCImport Backend
backend =
    if Backend -> Bool
backendSupportsCImport Backend
backend then
        Validity' [Backend]
forall a. Validity' a
IsValid
    else
        [Backend] -> Validity' [Backend]
forall a. a -> Validity' a
NotValid ([Backend] -> Validity' [Backend])
-> [Backend] -> Validity' [Backend]
forall a b. (a -> b) -> a -> b
$ (Backend -> Bool) -> [Backend] -> [Backend]
forall a. (a -> Bool) -> [a] -> [a]
filter Backend -> Bool
backendSupportsCImport [Backend]
allBackends

backendValidityOfCExport :: Backend -> Validity' [Backend]
backendValidityOfCExport Backend
backend =
    if Backend -> Bool
backendSupportsCExport Backend
backend then
        Validity' [Backend]
forall a. Validity' a
IsValid
    else
        [Backend] -> Validity' [Backend]
forall a. a -> Validity' a
NotValid ([Backend] -> Validity' [Backend])
-> [Backend] -> Validity' [Backend]
forall a b. (a -> b) -> a -> b
$ (Backend -> Bool) -> [Backend] -> [Backend]
forall a. (a -> Bool) -> [a] -> [a]
filter Backend -> Bool
backendSupportsCExport [Backend]
allBackends




{-
Note [Backend Defunctionalization]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
I had hoped to include code-output and post-hsc-pipeline functions
directly in the `Backend` record itself.  But this agenda was derailed
by mutual recursion in the types:

  - A `DynFlags` record contains a back end of type `Backend`.
  - A `Backend` contains a code-output function.
  - A code-output function takes Cmm as input.
  - Cmm can include a `CLabel`.
  - A `CLabel` can have elements that are defined in
    `GHC.Driver.Session`, where `DynFlags` is defined.

There is also a nasty issue in the values: a typical post-backend
pipeline function both depends on and is depended upon by functions in
"GHC.Driver.Pipeline".

I'm cut the Gordian not by removing the function types from the
`Backend` record.  Instead, a function is represented by its /name/.
This representation is an example of an old trick called
/defunctionalization/, which has been used in both compilers and
interpreters for languages with first-class, nested functions.  Here,
a function's name is a value of an algebraic data type.  For example,
a code-output function is represented by a value of this type:

    data DefunctionalizedCodeOutput
      = NcgCodeOutput
      | ViaCCodeOutput
      | LlvmCodeOutput

Such a function may be applied in one of two ways:

  - In this particular example, a `case` expression in module
    "GHC.Driver.CodeOutput" discriminates on the value and calls the
    designated function.

  - In another example, a function of type `DefunctionalizedCDefs` is
    applied by calling function `applyCDefs`, which has this type:

    @
    applyCDefs :: DefunctionalizedCDefs -> Logger -> DynFlags -> IO [String]
    @

    Function `applyCDefs` is defined in module "GHC.SysTools.Cpp".

I don't love this solution, but defunctionalization is a standard
thing, and it makes the meanings of the enumeration values clear.

Anyone defining a new back end will need to extend both the
`DefunctionalizedCodeOutput` type and the corresponding apply
function.
-}