summaryrefslogtreecommitdiff
path: root/compiler/GHC/Driver/Backend.hs
blob: 2642a2a9af517b8114fa295f1dd87b2e1c479029 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
{-# 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 (Eq,Ord,Show,Read)

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


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

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