never executed always true always false
    1 {-# LANGUAGE MultiWayIf #-}
    2 
    3 -- | Code generation backends
    4 module GHC.Driver.Backend
    5    ( Backend (..)
    6    , platformDefaultBackend
    7    , platformNcgSupported
    8    , backendProducesObject
    9    , backendRetainsAllBindings
   10    )
   11 where
   12 
   13 import GHC.Prelude
   14 import GHC.Platform
   15 
   16 -- | Code generation backends.
   17 --
   18 -- GHC supports several code generation backends serving different purposes
   19 -- (producing machine code, producing ByteCode for the interpreter) and
   20 -- supporting different platforms.
   21 --
   22 data Backend
   23    = NCG           -- ^ Native code generator backend.
   24                    --
   25                    -- Compiles Cmm code into textual assembler, then relies on
   26                    -- an external assembler toolchain to produce machine code.
   27                    --
   28                    -- Only supports a few platforms (X86, PowerPC, SPARC).
   29                    --
   30                    -- See "GHC.CmmToAsm".
   31 
   32 
   33    | LLVM          -- ^ LLVM backend.
   34                    --
   35                    -- Compiles Cmm code into LLVM textual IR, then relies on
   36                    -- LLVM toolchain to produce machine code.
   37                    --
   38                    -- It relies on LLVM support for the calling convention used
   39                    -- by the NCG backend to produce code objects ABI compatible
   40                    -- with it (see "cc 10" or "ghccc" calling convention in
   41                    -- https://llvm.org/docs/LangRef.html#calling-conventions).
   42                    --
   43                    -- Support a few platforms (X86, AArch64, s390x, ARM).
   44                    --
   45                    -- See "GHC.CmmToLlvm"
   46 
   47 
   48    | ViaC          -- ^ Via-C backend.
   49                    --
   50                    -- Compiles Cmm code into C code, then relies on a C compiler
   51                    -- to produce machine code.
   52                    --
   53                    -- It produces code objects that are *not* ABI compatible
   54                    -- with those produced by NCG and LLVM backends.
   55                    --
   56                    -- Produced code is expected to be less efficient than the
   57                    -- one produced by NCG and LLVM backends because STG
   58                    -- registers are not pinned into real registers.  On the
   59                    -- other hand, it supports more target platforms (those
   60                    -- having a valid C toolchain).
   61                    --
   62                    -- See "GHC.CmmToC"
   63 
   64 
   65    | Interpreter   -- ^ ByteCode interpreter.
   66                    --
   67                    -- Produce ByteCode objects (BCO, see "GHC.ByteCode") that
   68                    -- can be interpreted. It is used by GHCi.
   69                    --
   70                    -- Currently some extensions are not supported
   71                    -- (foreign primops).
   72                    --
   73                    -- See "GHC.StgToByteCode"
   74 
   75 
   76    | NoBackend     -- ^ No code generated.
   77                    --
   78                    -- Use this to disable code generation. It is particularly
   79                    -- useful when GHC is used as a library for other purpose
   80                    -- than generating code (e.g. to generate documentation with
   81                    -- Haddock) or when the user requested it (via -fno-code) for
   82                    -- some reason.
   83 
   84    deriving (Eq,Ord,Show,Read)
   85 
   86 -- | Default backend to use for the given platform.
   87 platformDefaultBackend :: Platform -> Backend
   88 platformDefaultBackend platform = if
   89       | platformUnregisterised platform -> ViaC
   90       | platformNcgSupported platform   -> NCG
   91       | otherwise                       -> LLVM
   92 
   93 
   94 -- | Is the platform supported by the Native Code Generator?
   95 platformNcgSupported :: Platform -> Bool
   96 platformNcgSupported platform = if
   97       | platformUnregisterised platform -> False -- NCG doesn't support unregisterised ABI
   98       | ncgValidArch                    -> True
   99       | otherwise                       -> False
  100    where
  101       ncgValidArch = case platformArch platform of
  102          ArchX86       -> True
  103          ArchX86_64    -> True
  104          ArchPPC       -> True
  105          ArchPPC_64 {} -> True
  106          ArchSPARC     -> True
  107          ArchAArch64   -> True
  108          _             -> False
  109 
  110 -- | Will this backend produce an object file on the disk?
  111 backendProducesObject :: Backend -> Bool
  112 backendProducesObject ViaC        = True
  113 backendProducesObject NCG         = True
  114 backendProducesObject LLVM        = True
  115 backendProducesObject Interpreter = False
  116 backendProducesObject NoBackend   = False
  117 
  118 -- | Does this backend retain *all* top-level bindings for a module,
  119 -- rather than just the exported bindings, in the TypeEnv and compiled
  120 -- code (if any)?
  121 --
  122 -- Interpreter backend does this, so that GHCi can call functions inside a
  123 -- module.
  124 --
  125 -- When no backend is used we also do it, so that Haddock can get access to the
  126 -- GlobalRdrEnv for a module after typechecking it.
  127 backendRetainsAllBindings :: Backend -> Bool
  128 backendRetainsAllBindings Interpreter = True
  129 backendRetainsAllBindings NoBackend   = True
  130 backendRetainsAllBindings ViaC        = False
  131 backendRetainsAllBindings NCG         = False
  132 backendRetainsAllBindings LLVM        = False