never executed always true always false
    1 -- -----------------------------------------------------------------------------
    2 --
    3 -- (c) The University of Glasgow 1994-2004
    4 --
    5 -- -----------------------------------------------------------------------------
    6 
    7 module GHC.CmmToAsm.SPARC.Regs (
    8         -- registers
    9         showReg,
   10         virtualRegSqueeze,
   11         realRegSqueeze,
   12         classOfRealReg,
   13         allRealRegs,
   14 
   15         -- machine specific info
   16         gReg, iReg, lReg, oReg, fReg,
   17         fp, sp, g0, g1, g2, o0, o1, f0, f1, f6, f8, f22, f26, f27,
   18 
   19         -- allocatable
   20         allocatableRegs,
   21 
   22         -- args
   23         argRegs,
   24         allArgRegs,
   25         callClobberedRegs,
   26 
   27         --
   28         mkVirtualReg,
   29         regDotColor
   30 )
   31 
   32 where
   33 
   34 
   35 import GHC.Prelude
   36 
   37 import GHC.Platform.SPARC
   38 import GHC.Platform.Reg
   39 import GHC.Platform.Reg.Class
   40 import GHC.CmmToAsm.Format
   41 
   42 import GHC.Types.Unique
   43 import GHC.Utils.Outputable
   44 import GHC.Utils.Panic
   45 
   46 {-
   47         The SPARC has 64 registers of interest; 32 integer registers and 32
   48         floating point registers.  The mapping of STG registers to SPARC
   49         machine registers is defined in StgRegs.h.  We are, of course,
   50         prepared for any eventuality.
   51 
   52         The whole fp-register pairing thing on sparcs is a huge nuisance.  See
   53         rts/include/stg/MachRegs.h for a description of what's going on
   54         here.
   55 -}
   56 
   57 
   58 -- | Get the standard name for the register with this number.
   59 showReg :: RegNo -> String
   60 showReg n
   61         | n >= 0  && n < 8   = "%g" ++ show n
   62         | n >= 8  && n < 16  = "%o" ++ show (n-8)
   63         | n >= 16 && n < 24  = "%l" ++ show (n-16)
   64         | n >= 24 && n < 32  = "%i" ++ show (n-24)
   65         | n >= 32 && n < 64  = "%f" ++ show (n-32)
   66         | otherwise          = panic "SPARC.Regs.showReg: unknown sparc register"
   67 
   68 
   69 -- Get the register class of a certain real reg
   70 classOfRealReg :: RealReg -> RegClass
   71 classOfRealReg reg
   72  = case reg of
   73         RealRegSingle i
   74                 | i < 32        -> RcInteger
   75                 | otherwise     -> RcFloat
   76 
   77         RealRegPair{}           -> RcDouble
   78 
   79 
   80 -- | regSqueeze_class reg
   81 --      Calculate the maximum number of register colors that could be
   82 --      denied to a node of this class due to having this reg
   83 --      as a neighbour.
   84 --
   85 {-# INLINE virtualRegSqueeze #-}
   86 virtualRegSqueeze :: RegClass -> VirtualReg -> Int
   87 
   88 virtualRegSqueeze cls vr
   89  = case cls of
   90         RcInteger
   91          -> case vr of
   92                 VirtualRegI{}           -> 1
   93                 VirtualRegHi{}          -> 1
   94                 _other                  -> 0
   95 
   96         RcFloat
   97          -> case vr of
   98                 VirtualRegF{}           -> 1
   99                 VirtualRegD{}           -> 2
  100                 _other                  -> 0
  101 
  102         RcDouble
  103          -> case vr of
  104                 VirtualRegF{}           -> 1
  105                 VirtualRegD{}           -> 1
  106                 _other                  -> 0
  107 
  108 
  109 {-# INLINE realRegSqueeze #-}
  110 realRegSqueeze :: RegClass -> RealReg -> Int
  111 
  112 realRegSqueeze cls rr
  113  = case cls of
  114         RcInteger
  115          -> case rr of
  116                 RealRegSingle regNo
  117                         | regNo < 32    -> 1
  118                         | otherwise     -> 0
  119 
  120                 RealRegPair{}           -> 0
  121 
  122         RcFloat
  123          -> case rr of
  124                 RealRegSingle regNo
  125                         | regNo < 32    -> 0
  126                         | otherwise     -> 1
  127 
  128                 RealRegPair{}           -> 2
  129 
  130         RcDouble
  131          -> case rr of
  132                 RealRegSingle regNo
  133                         | regNo < 32    -> 0
  134                         | otherwise     -> 1
  135 
  136                 RealRegPair{}           -> 1
  137 
  138 
  139 -- | All the allocatable registers in the machine,
  140 --      including register pairs.
  141 allRealRegs :: [RealReg]
  142 allRealRegs
  143         =  [ (RealRegSingle i)          | i <- [0..63] ]
  144         ++ [ (RealRegPair   i (i+1))    | i <- [32, 34 .. 62 ] ]
  145 
  146 
  147 -- | Get the regno for this sort of reg
  148 gReg, lReg, iReg, oReg, fReg :: Int -> RegNo
  149 
  150 gReg x  = x             -- global regs
  151 oReg x  = (8 + x)       -- output regs
  152 lReg x  = (16 + x)      -- local regs
  153 iReg x  = (24 + x)      -- input regs
  154 fReg x  = (32 + x)      -- float regs
  155 
  156 
  157 -- | Some specific regs used by the code generator.
  158 g0, g1, g2, fp, sp, o0, o1, f0, f1, f6, f8, f22, f26, f27 :: Reg
  159 
  160 f6  = RegReal (RealRegSingle (fReg 6))
  161 f8  = RegReal (RealRegSingle (fReg 8))
  162 f22 = RegReal (RealRegSingle (fReg 22))
  163 f26 = RegReal (RealRegSingle (fReg 26))
  164 f27 = RegReal (RealRegSingle (fReg 27))
  165 
  166 -- g0 is always zero, and writes to it vanish.
  167 g0  = RegReal (RealRegSingle (gReg 0))
  168 g1  = RegReal (RealRegSingle (gReg 1))
  169 g2  = RegReal (RealRegSingle (gReg 2))
  170 
  171 -- FP, SP, int and float return (from C) regs.
  172 fp  = RegReal (RealRegSingle (iReg 6))
  173 sp  = RegReal (RealRegSingle (oReg 6))
  174 o0  = RegReal (RealRegSingle (oReg 0))
  175 o1  = RegReal (RealRegSingle (oReg 1))
  176 f0  = RegReal (RealRegSingle (fReg 0))
  177 f1  = RegReal (RealRegSingle (fReg 1))
  178 
  179 -- | Produce the second-half-of-a-double register given the first half.
  180 {-
  181 fPair :: Reg -> Maybe Reg
  182 fPair (RealReg n)
  183         | n >= 32 && n `mod` 2 == 0  = Just (RealReg (n+1))
  184 
  185 fPair (VirtualRegD u)
  186         = Just (VirtualRegHi u)
  187 
  188 fPair reg
  189         = trace ("MachInstrs.fPair: can't get high half of supposed double reg " ++ showPpr reg)
  190                 Nothing
  191 -}
  192 
  193 
  194 -- | All the regs that the register allocator can allocate to,
  195 --      with the fixed use regs removed.
  196 --
  197 allocatableRegs :: [RealReg]
  198 allocatableRegs
  199    = let isFree rr
  200            = case rr of
  201                 RealRegSingle r     -> freeReg r
  202                 RealRegPair   r1 r2 -> freeReg r1 && freeReg r2
  203      in filter isFree allRealRegs
  204 
  205 
  206 -- | The registers to place arguments for function calls,
  207 --      for some number of arguments.
  208 --
  209 argRegs :: RegNo -> [Reg]
  210 argRegs r
  211  = case r of
  212         0       -> []
  213         1       -> map (RegReal . RealRegSingle . oReg) [0]
  214         2       -> map (RegReal . RealRegSingle . oReg) [0,1]
  215         3       -> map (RegReal . RealRegSingle . oReg) [0,1,2]
  216         4       -> map (RegReal . RealRegSingle . oReg) [0,1,2,3]
  217         5       -> map (RegReal . RealRegSingle . oReg) [0,1,2,3,4]
  218         6       -> map (RegReal . RealRegSingle . oReg) [0,1,2,3,4,5]
  219         _       -> panic "MachRegs.argRegs(sparc): don't know about >6 arguments!"
  220 
  221 
  222 -- | All the regs that could possibly be returned by argRegs
  223 --
  224 allArgRegs :: [Reg]
  225 allArgRegs
  226         = map (RegReal . RealRegSingle) [oReg i | i <- [0..5]]
  227 
  228 
  229 -- These are the regs that we cannot assume stay alive over a C call.
  230 --      TODO: Why can we assume that o6 isn't clobbered? -- BL 2009/02
  231 --
  232 callClobberedRegs :: [Reg]
  233 callClobberedRegs
  234         = map (RegReal . RealRegSingle)
  235                 (  oReg 7 :
  236                   [oReg i | i <- [0..5]] ++
  237                   [gReg i | i <- [1..7]] ++
  238                   [fReg i | i <- [0..31]] )
  239 
  240 
  241 
  242 -- | Make a virtual reg with this format.
  243 mkVirtualReg :: Unique -> Format -> VirtualReg
  244 mkVirtualReg u format
  245         | not (isFloatFormat format)
  246         = VirtualRegI u
  247 
  248         | otherwise
  249         = case format of
  250                 FF32    -> VirtualRegF u
  251                 FF64    -> VirtualRegD u
  252                 _       -> panic "mkVReg"
  253 
  254 
  255 regDotColor :: RealReg -> SDoc
  256 regDotColor reg
  257  = case classOfRealReg reg of
  258         RcInteger       -> text "blue"
  259         RcFloat         -> text "red"
  260         _other          -> text "green"