never executed always true always false
    1 module GHC.CmmToAsm.SPARC.CodeGen.Base (
    2         InstrBlock,
    3         CondCode(..),
    4         ChildCode64(..),
    5         Amode(..),
    6 
    7         Register(..),
    8         setFormatOfRegister,
    9 
   10         getRegisterReg,
   11         mangleIndexTree
   12 )
   13 
   14 where
   15 
   16 import GHC.Prelude
   17 
   18 import GHC.CmmToAsm.SPARC.Instr
   19 import GHC.CmmToAsm.SPARC.Cond
   20 import GHC.CmmToAsm.SPARC.AddrMode
   21 import GHC.CmmToAsm.SPARC.Regs
   22 import GHC.CmmToAsm.Format
   23 import GHC.Platform.Reg
   24 
   25 import GHC.Platform.Regs
   26 import GHC.Cmm
   27 import GHC.Cmm.Ppr.Expr () -- For Outputable instances
   28 import GHC.Platform
   29 
   30 import GHC.Utils.Outputable
   31 import GHC.Utils.Panic
   32 import GHC.Data.OrdList
   33 
   34 --------------------------------------------------------------------------------
   35 -- | 'InstrBlock's are the insn sequences generated by the insn selectors.
   36 --      They are really trees of insns to facilitate fast appending, where a
   37 --      left-to-right traversal yields the insns in the correct order.
   38 --
   39 type InstrBlock
   40         = OrdList Instr
   41 
   42 
   43 -- | Condition codes passed up the tree.
   44 --
   45 data CondCode
   46         = CondCode Bool Cond InstrBlock
   47 
   48 
   49 -- | a.k.a \"Register64\"
   50 --      Reg is the lower 32-bit temporary which contains the result.
   51 --      Use getHiVRegFromLo to find the other VRegUnique.
   52 --
   53 --      Rules of this simplified insn selection game are therefore that
   54 --      the returned Reg may be modified
   55 --
   56 data ChildCode64
   57    = ChildCode64
   58         InstrBlock
   59         Reg
   60 
   61 
   62 -- | Holds code that references a memory address.
   63 data Amode
   64         = Amode
   65                 -- the AddrMode we can use in the instruction
   66                 --      that does the real load\/store.
   67                 AddrMode
   68 
   69                 -- other setup code we have to run first before we can use the
   70                 --      above AddrMode.
   71                 InstrBlock
   72 
   73 
   74 
   75 --------------------------------------------------------------------------------
   76 -- | Code to produce a result into a register.
   77 --      If the result must go in a specific register, it comes out as Fixed.
   78 --      Otherwise, the parent can decide which register to put it in.
   79 --
   80 data Register
   81         = Fixed Format Reg InstrBlock
   82         | Any   Format (Reg -> InstrBlock)
   83 
   84 
   85 -- | Change the format field in a Register.
   86 setFormatOfRegister
   87         :: Register -> Format -> Register
   88 
   89 setFormatOfRegister reg format
   90  = case reg of
   91         Fixed _ reg code        -> Fixed format reg code
   92         Any _ codefn            -> Any   format codefn
   93 
   94 
   95 --------------------------------------------------------------------------------
   96 -- | Grab the Reg for a CmmReg
   97 getRegisterReg :: Platform -> CmmReg -> Reg
   98 
   99 getRegisterReg _ (CmmLocal (LocalReg u pk))
  100         = RegVirtual $ mkVirtualReg u (cmmTypeFormat pk)
  101 
  102 getRegisterReg platform (CmmGlobal mid)
  103   = case globalRegMaybe platform mid of
  104         Just reg -> RegReal reg
  105         Nothing  -> pprPanic
  106                         "SPARC.CodeGen.Base.getRegisterReg: global is in memory"
  107                         (ppr $ CmmGlobal mid)
  108 
  109 
  110 -- Expand CmmRegOff.  ToDo: should we do it this way around, or convert
  111 -- CmmExprs into CmmRegOff?
  112 mangleIndexTree :: Platform -> CmmExpr -> CmmExpr
  113 
  114 mangleIndexTree platform (CmmRegOff reg off)
  115         = CmmMachOp (MO_Add width) [CmmReg reg, CmmLit (CmmInt (fromIntegral off) width)]
  116         where width = typeWidth (cmmRegType platform reg)
  117 
  118 mangleIndexTree _ _
  119         = panic "SPARC.CodeGen.Base.mangleIndexTree: no match"