never executed always true always false
    1 -- Cmm representations using Hoopl's Graph CmmNode e x.
    2 {-# LANGUAGE GADTs #-}
    3 {-# LANGUAGE KindSignatures #-}
    4 {-# LANGUAGE DataKinds #-}
    5 {-# LANGUAGE ExplicitNamespaces #-}
    6 {-# LANGUAGE DeriveFunctor #-}
    7 {-# LANGUAGE MultiParamTypeClasses #-}
    8 {-# LANGUAGE FlexibleInstances #-}
    9 
   10 
   11 module GHC.Cmm (
   12      -- * Cmm top-level datatypes
   13      CmmProgram, CmmGroup, CmmGroupSRTs, RawCmmGroup, GenCmmGroup,
   14      CmmDecl, CmmDeclSRTs, GenCmmDecl(..),
   15      CmmGraph, GenCmmGraph(..),
   16      CmmBlock, RawCmmDecl,
   17      Section(..), SectionType(..),
   18      GenCmmStatics(..), type CmmStatics, type RawCmmStatics, CmmStatic(..),
   19      SectionProtection(..), sectionProtection,
   20 
   21      -- ** Blocks containing lists
   22      GenBasicBlock(..), blockId,
   23      ListGraph(..), pprBBlock,
   24 
   25      -- * Info Tables
   26      CmmTopInfo(..), CmmStackInfo(..), CmmInfoTable(..), topInfoTable,
   27      ClosureTypeInfo(..),
   28      ProfilingInfo(..), ConstrDescription,
   29 
   30      -- * Statements, expressions and types
   31      module GHC.Cmm.Node,
   32      module GHC.Cmm.Expr,
   33   ) where
   34 
   35 import GHC.Prelude
   36 
   37 import GHC.Types.Id
   38 import GHC.Types.CostCentre
   39 import GHC.Cmm.CLabel
   40 import GHC.Cmm.BlockId
   41 import GHC.Cmm.Node
   42 import GHC.Runtime.Heap.Layout
   43 import GHC.Cmm.Expr
   44 import GHC.Cmm.Dataflow.Block
   45 import GHC.Cmm.Dataflow.Collections
   46 import GHC.Cmm.Dataflow.Graph
   47 import GHC.Cmm.Dataflow.Label
   48 import GHC.Utils.Outputable
   49 import Data.ByteString (ByteString)
   50 
   51 -----------------------------------------------------------------------------
   52 --  Cmm, GenCmm
   53 -----------------------------------------------------------------------------
   54 
   55 -- A CmmProgram is a list of CmmGroups
   56 -- A CmmGroup is a list of top-level declarations
   57 
   58 -- When object-splitting is on, each group is compiled into a separate
   59 -- .o file. So typically we put closely related stuff in a CmmGroup.
   60 -- Section-splitting follows suit and makes one .text subsection for each
   61 -- CmmGroup.
   62 
   63 type CmmProgram = [CmmGroup]
   64 
   65 type GenCmmGroup d h g = [GenCmmDecl d h g]
   66 -- | Cmm group before SRT generation
   67 type CmmGroup     = GenCmmGroup CmmStatics    CmmTopInfo               CmmGraph
   68 -- | Cmm group with SRTs
   69 type CmmGroupSRTs = GenCmmGroup RawCmmStatics CmmTopInfo               CmmGraph
   70 -- | "Raw" cmm group (TODO (osa): not sure what that means)
   71 type RawCmmGroup  = GenCmmGroup RawCmmStatics (LabelMap RawCmmStatics) CmmGraph
   72 
   73 -----------------------------------------------------------------------------
   74 --  CmmDecl, GenCmmDecl
   75 -----------------------------------------------------------------------------
   76 
   77 -- GenCmmDecl is abstracted over
   78 --   d, the type of static data elements in CmmData
   79 --   h, the static info preceding the code of a CmmProc
   80 --   g, the control-flow graph of a CmmProc
   81 --
   82 -- We expect there to be two main instances of this type:
   83 --   (a) C--, i.e. populated with various C-- constructs
   84 --   (b) Native code, populated with data/instructions
   85 
   86 -- | A top-level chunk, abstracted over the type of the contents of
   87 -- the basic blocks (Cmm or instructions are the likely instantiations).
   88 data GenCmmDecl d h g
   89   = CmmProc     -- A procedure
   90      h                 -- Extra header such as the info table
   91      CLabel            -- Entry label
   92      [GlobalReg]       -- Registers live on entry. Note that the set of live
   93                        -- registers will be correct in generated C-- code, but
   94                        -- not in hand-written C-- code. However,
   95                        -- splitAtProcPoints calculates correct liveness
   96                        -- information for CmmProcs.
   97      g                 -- Control-flow graph for the procedure's code
   98 
   99   | CmmData     -- Static data
  100         Section
  101         d
  102 
  103   deriving (Functor)
  104 
  105 type CmmDecl     = GenCmmDecl CmmStatics    CmmTopInfo CmmGraph
  106 type CmmDeclSRTs = GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph
  107 
  108 type RawCmmDecl
  109    = GenCmmDecl
  110         RawCmmStatics
  111         (LabelMap RawCmmStatics)
  112         CmmGraph
  113 
  114 -----------------------------------------------------------------------------
  115 --     Graphs
  116 -----------------------------------------------------------------------------
  117 
  118 type CmmGraph = GenCmmGraph CmmNode
  119 data GenCmmGraph n = CmmGraph { g_entry :: BlockId, g_graph :: Graph n C C }
  120 type CmmBlock = Block CmmNode C C
  121 
  122 -----------------------------------------------------------------------------
  123 --     Info Tables
  124 -----------------------------------------------------------------------------
  125 
  126 -- | CmmTopInfo is attached to each CmmDecl (see defn of CmmGroup), and contains
  127 -- the extra info (beyond the executable code) that belongs to that CmmDecl.
  128 data CmmTopInfo   = TopInfo { info_tbls  :: LabelMap CmmInfoTable
  129                             , stack_info :: CmmStackInfo }
  130 
  131 topInfoTable :: GenCmmDecl a CmmTopInfo (GenCmmGraph n) -> Maybe CmmInfoTable
  132 topInfoTable (CmmProc infos _ _ g) = mapLookup (g_entry g) (info_tbls infos)
  133 topInfoTable _                     = Nothing
  134 
  135 data CmmStackInfo
  136    = StackInfo {
  137        arg_space :: ByteOff,
  138                -- number of bytes of arguments on the stack on entry to the
  139                -- the proc.  This is filled in by GHC.StgToCmm.codeGen, and
  140                -- used by the stack allocator later.
  141        do_layout :: Bool
  142                -- Do automatic stack layout for this proc.  This is
  143                -- True for all code generated by the code generator,
  144                -- but is occasionally False for hand-written Cmm where
  145                -- we want to do the stack manipulation manually.
  146   }
  147 
  148 -- | Info table as a haskell data type
  149 data CmmInfoTable
  150   = CmmInfoTable {
  151       cit_lbl  :: CLabel, -- Info table label
  152       cit_rep  :: SMRep,
  153       cit_prof :: ProfilingInfo,
  154       cit_srt  :: Maybe CLabel,   -- empty, or a closure address
  155       cit_clo  :: Maybe (Id, CostCentreStack)
  156         -- Just (id,ccs) <=> build a static closure later
  157         -- Nothing <=> don't build a static closure
  158         --
  159         -- Static closures for FUNs and THUNKs are *not* generated by
  160         -- the code generator, because we might want to add SRT
  161         -- entries to them later (for FUNs at least; THUNKs are
  162         -- treated the same for consistency). See Note [SRTs] in
  163         -- GHC.Cmm.Info.Build, in particular the [FUN] optimisation.
  164         --
  165         -- This is strictly speaking not a part of the info table that
  166         -- will be finally generated, but it's the only convenient
  167         -- place to convey this information from the code generator to
  168         -- where we build the static closures in
  169         -- GHC.Cmm.Info.Build.doSRTs.
  170     } deriving Eq
  171 
  172 data ProfilingInfo
  173   = NoProfilingInfo
  174   | ProfilingInfo ByteString ByteString -- closure_type, closure_desc
  175   deriving Eq
  176 -----------------------------------------------------------------------------
  177 --              Static Data
  178 -----------------------------------------------------------------------------
  179 
  180 data SectionType
  181   = Text
  182   | Data
  183   | ReadOnlyData
  184   | RelocatableReadOnlyData
  185   | UninitialisedData
  186   | ReadOnlyData16      -- .rodata.cst16 on x86_64, 16-byte aligned
  187   | CString
  188   | OtherSection String
  189   deriving (Show)
  190 
  191 data SectionProtection
  192   = ReadWriteSection
  193   | ReadOnlySection
  194   | WriteProtectedSection -- See Note [Relocatable Read-Only Data]
  195   deriving (Eq)
  196 
  197 -- | Should a data in this section be considered constant at runtime
  198 sectionProtection :: Section -> SectionProtection
  199 sectionProtection (Section t _) = case t of
  200     Text                    -> ReadOnlySection
  201     ReadOnlyData            -> ReadOnlySection
  202     RelocatableReadOnlyData -> WriteProtectedSection
  203     ReadOnlyData16          -> ReadOnlySection
  204     CString                 -> ReadOnlySection
  205     Data                    -> ReadWriteSection
  206     UninitialisedData       -> ReadWriteSection
  207     (OtherSection _)        -> ReadWriteSection
  208 
  209 {-
  210 Note [Relocatable Read-Only Data]
  211 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  212 
  213 Relocatable data are only read-only after relocation at the start of the
  214 program. They should be writable from the source code until then. Failure to
  215 do so would end up in segfaults at execution when using linkers that do not
  216 enforce writability of those sections, such as the gold linker.
  217 -}
  218 
  219 data Section = Section SectionType CLabel
  220 
  221 data CmmStatic
  222   = CmmStaticLit CmmLit
  223         -- ^ a literal value, size given by cmmLitRep of the literal.
  224   | CmmUninitialised Int
  225         -- ^ uninitialised data, N bytes long
  226   | CmmString ByteString
  227         -- ^ string of 8-bit values only, not zero terminated.
  228   | CmmFileEmbed FilePath
  229         -- ^ an embedded binary file
  230 
  231 instance Outputable CmmStatic where
  232   ppr (CmmStaticLit lit) = text "CmmStaticLit" <+> ppr lit
  233   ppr (CmmUninitialised n) = text "CmmUninitialised" <+> ppr n
  234   ppr (CmmString _) = text "CmmString"
  235   ppr (CmmFileEmbed fp) = text "CmmFileEmbed" <+> text fp
  236 
  237 -- Static data before SRT generation
  238 data GenCmmStatics (rawOnly :: Bool) where
  239     CmmStatics
  240       :: CLabel       -- Label of statics
  241       -> CmmInfoTable
  242       -> CostCentreStack
  243       -> [CmmLit]     -- Payload
  244       -> GenCmmStatics 'False
  245 
  246     -- | Static data, after SRTs are generated
  247     CmmStaticsRaw
  248       :: CLabel       -- Label of statics
  249       -> [CmmStatic]  -- The static data itself
  250       -> GenCmmStatics a
  251 
  252 type CmmStatics    = GenCmmStatics 'False
  253 type RawCmmStatics = GenCmmStatics 'True
  254 
  255 -- -----------------------------------------------------------------------------
  256 -- Basic blocks consisting of lists
  257 
  258 -- These are used by the LLVM and NCG backends, when populating Cmm
  259 -- with lists of instructions.
  260 
  261 data GenBasicBlock i
  262    = BasicBlock BlockId [i]
  263    deriving (Functor)
  264 
  265 
  266 -- | The branch block id is that of the first block in
  267 -- the branch, which is that branch's entry point
  268 blockId :: GenBasicBlock i -> BlockId
  269 blockId (BasicBlock blk_id _ ) = blk_id
  270 
  271 newtype ListGraph i
  272    = ListGraph [GenBasicBlock i]
  273    deriving (Functor)
  274 
  275 instance Outputable instr => Outputable (ListGraph instr) where
  276     ppr (ListGraph blocks) = vcat (map ppr blocks)
  277 
  278 instance OutputableP env instr => OutputableP env (ListGraph instr) where
  279     pdoc env g = ppr (fmap (pdoc env) g)
  280 
  281 
  282 instance Outputable instr => Outputable (GenBasicBlock instr) where
  283     ppr = pprBBlock
  284 
  285 instance OutputableP env instr => OutputableP env (GenBasicBlock instr) where
  286     pdoc env block = ppr (fmap (pdoc env) block)
  287 
  288 pprBBlock :: Outputable stmt => GenBasicBlock stmt -> SDoc
  289 pprBBlock (BasicBlock ident stmts) =
  290     hang (ppr ident <> colon) 4 (vcat (map ppr stmts))