module SPARC.Base (
        wordLength,
        wordLengthInBits,
        spillAreaLength,
        spillSlotSize,
        extraStackArgsHere,
        fits13Bits,
        is32BitInteger,
        largeOffsetError
)
where
import GhcPrelude
import DynFlags
import Panic
import Data.Int
wordLength :: Int
wordLength = 4
wordLengthInBits :: Int
wordLengthInBits
        = wordLength * 8
spillAreaLength :: DynFlags -> Int
spillAreaLength
        = rESERVED_C_STACK_BYTES
spillSlotSize :: Int
spillSlotSize = 8
extraStackArgsHere :: Int
extraStackArgsHere = 23
{-# SPECIALIZE fits13Bits :: Int -> Bool, Integer -> Bool #-}
fits13Bits :: Integral a => a -> Bool
fits13Bits x = x >= -4096 && x < 4096
is32BitInteger :: Integer -> Bool
is32BitInteger i
        = i64 <= 0x7fffffff && i64 >= -0x80000000
        where i64 = fromIntegral i :: Int64
largeOffsetError :: (Show a) => a -> b
largeOffsetError i
  = panic ("ERROR: SPARC native-code generator cannot handle large offset ("
                ++ show i ++ ");\nprobably because of large constant data structures;" ++
                "\nworkaround: use -fllvm on this module.\n")