never executed always true always false
    1 
    2 -- | Bits and pieces on the bottom of the module dependency tree.
    3 --      Also import the required constants, so we know what we're using.
    4 --
    5 --      In the interests of cross-compilation, we want to free ourselves
    6 --      from the autoconf generated modules like "GHC.Settings.Constants"
    7 
    8 module GHC.CmmToAsm.SPARC.Base (
    9         wordLength,
   10         wordLengthInBits,
   11         spillSlotSize,
   12         extraStackArgsHere,
   13         fits13Bits,
   14         is32BitInteger,
   15         largeOffsetError
   16 )
   17 
   18 where
   19 
   20 import GHC.Prelude
   21 
   22 import GHC.Utils.Panic
   23 
   24 import Data.Int
   25 
   26 
   27 -- On 32 bit SPARC, pointers are 32 bits.
   28 wordLength :: Int
   29 wordLength = 4
   30 
   31 wordLengthInBits :: Int
   32 wordLengthInBits
   33         = wordLength * 8
   34 
   35 -- | We need 8 bytes because our largest registers are 64 bit.
   36 spillSlotSize :: Int
   37 spillSlotSize = 8
   38 
   39 
   40 -- | We (allegedly) put the first six C-call arguments in registers;
   41 --      where do we start putting the rest of them?
   42 extraStackArgsHere :: Int
   43 extraStackArgsHere = 23
   44 
   45 
   46 {-# SPECIALIZE fits13Bits :: Int -> Bool, Integer -> Bool #-}
   47 -- | Check whether an offset is representable with 13 bits.
   48 fits13Bits :: Integral a => a -> Bool
   49 fits13Bits x = x >= -4096 && x < 4096
   50 
   51 -- | Check whether an integer will fit in 32 bits.
   52 --      A CmmInt is intended to be truncated to the appropriate
   53 --      number of bits, so here we truncate it to Int64.  This is
   54 --      important because e.g. -1 as a CmmInt might be either
   55 --      -1 or 18446744073709551615.
   56 --
   57 is32BitInteger :: Integer -> Bool
   58 is32BitInteger i
   59         = i64 <= 0x7fffffff && i64 >= -0x80000000
   60         where i64 = fromIntegral i :: Int64
   61 
   62 
   63 -- | Sadness.
   64 largeOffsetError :: (Show a) => a -> b
   65 largeOffsetError i
   66   = panic ("ERROR: SPARC native-code generator cannot handle large offset ("
   67                 ++ show i ++ ");\nprobably because of large constant data structures;" ++
   68                 "\nworkaround: use -fllvm on this module.\n")
   69 
   70