{-# LANGUAGE MultiWayIf #-}

-- | Code generation backends
module GHC.Driver.Backend
   ( Backend (..)
   , platformDefaultBackend
   , platformNcgSupported
   , backendProducesObject
   , backendRetainsAllBindings
   )
where

import GHC.Prelude
import GHC.Platform

-- | Code generation backends.
--
-- GHC supports several code generation backends serving different purposes
-- (producing machine code, producing ByteCode for the interpreter) and
-- supporting different platforms.
--
data Backend
   = NCG           -- ^ Native code generator backend.
                   --
                   -- 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".


   | LLVM          -- ^ 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).
                   --
                   -- Support a few platforms (X86, AArch64, s390x, ARM).
                   --
                   -- See "GHC.CmmToLlvm"


   | ViaC          -- ^ Via-C 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"


   | Interpreter   -- ^ 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     -- ^ No code generated.
                   --
                   -- Use this 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.

   deriving (Backend -> Backend -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Backend -> Backend -> Bool
$c/= :: Backend -> Backend -> Bool
== :: Backend -> Backend -> Bool
$c== :: Backend -> Backend -> Bool
Eq,Eq Backend
Backend -> Backend -> Bool
Backend -> Backend -> Ordering
Backend -> Backend -> Backend
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Backend -> Backend -> Backend
$cmin :: Backend -> Backend -> Backend
max :: Backend -> Backend -> Backend
$cmax :: Backend -> Backend -> Backend
>= :: Backend -> Backend -> Bool
$c>= :: Backend -> Backend -> Bool
> :: Backend -> Backend -> Bool
$c> :: Backend -> Backend -> Bool
<= :: Backend -> Backend -> Bool
$c<= :: Backend -> Backend -> Bool
< :: Backend -> Backend -> Bool
$c< :: Backend -> Backend -> Bool
compare :: Backend -> Backend -> Ordering
$ccompare :: Backend -> Backend -> Ordering
Ord,Int -> Backend -> ShowS
[Backend] -> ShowS
Backend -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Backend] -> ShowS
$cshowList :: [Backend] -> ShowS
show :: Backend -> String
$cshow :: Backend -> String
showsPrec :: Int -> Backend -> ShowS
$cshowsPrec :: Int -> Backend -> ShowS
Show,ReadPrec [Backend]
ReadPrec Backend
Int -> ReadS Backend
ReadS [Backend]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Backend]
$creadListPrec :: ReadPrec [Backend]
readPrec :: ReadPrec Backend
$creadPrec :: ReadPrec Backend
readList :: ReadS [Backend]
$creadList :: ReadS [Backend]
readsPrec :: Int -> ReadS Backend
$creadsPrec :: Int -> ReadS Backend
Read)

-- | Default backend to use for the given platform.
platformDefaultBackend :: Platform -> Backend
platformDefaultBackend :: Platform -> Backend
platformDefaultBackend Platform
platform = if
      | Platform -> Bool
platformUnregisterised Platform
platform -> Backend
ViaC
      | Platform -> Bool
platformNcgSupported Platform
platform   -> Backend
NCG
      | Bool
otherwise                       -> Backend
LLVM


-- | 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
ArchSPARC     -> Bool
True
         Arch
ArchAArch64   -> Bool
True
         Arch
_             -> Bool
False

-- | Will this backend produce an object file on the disk?
backendProducesObject :: Backend -> Bool
backendProducesObject :: Backend -> Bool
backendProducesObject Backend
ViaC        = Bool
True
backendProducesObject Backend
NCG         = Bool
True
backendProducesObject Backend
LLVM        = Bool
True
backendProducesObject Backend
Interpreter = Bool
False
backendProducesObject Backend
NoBackend   = Bool
False

-- | Does this backend retain *all* top-level bindings for a module,
-- rather than just the exported bindings, in the TypeEnv and compiled
-- code (if any)?
--
-- Interpreter backend does this, so that GHCi can call functions inside a
-- module.
--
-- When no backend is used we also do it, so that Haddock can get access to the
-- GlobalRdrEnv for a module after typechecking it.
backendRetainsAllBindings :: Backend -> Bool
backendRetainsAllBindings :: Backend -> Bool
backendRetainsAllBindings Backend
Interpreter = Bool
True
backendRetainsAllBindings Backend
NoBackend   = Bool
True
backendRetainsAllBindings Backend
ViaC        = Bool
False
backendRetainsAllBindings Backend
NCG         = Bool
False
backendRetainsAllBindings Backend
LLVM        = Bool
False