never executed always true always false
    1 {-# OPTIONS_GHC -fno-warn-orphans #-}
    2 
    3 -- | Native code generator for SPARC architectures
    4 module GHC.CmmToAsm.SPARC
    5    ( ncgSPARC
    6    )
    7 where
    8 
    9 import GHC.Prelude
   10 import GHC.Utils.Panic
   11 
   12 import GHC.CmmToAsm.Monad
   13 import GHC.CmmToAsm.Config
   14 import GHC.CmmToAsm.Types
   15 import GHC.CmmToAsm.Instr
   16 
   17 import qualified GHC.CmmToAsm.SPARC.Instr          as SPARC
   18 import qualified GHC.CmmToAsm.SPARC.Ppr            as SPARC
   19 import qualified GHC.CmmToAsm.SPARC.CodeGen        as SPARC
   20 import qualified GHC.CmmToAsm.SPARC.CodeGen.Expand as SPARC
   21 import qualified GHC.CmmToAsm.SPARC.Regs           as SPARC
   22 import qualified GHC.CmmToAsm.SPARC.ShortcutJump   as SPARC
   23 
   24 
   25 ncgSPARC :: NCGConfig -> NcgImpl RawCmmStatics SPARC.Instr SPARC.JumpDest
   26 ncgSPARC config = NcgImpl
   27    { ncgConfig                 = config
   28    , cmmTopCodeGen             = SPARC.cmmTopCodeGen
   29    , generateJumpTableForInstr = SPARC.generateJumpTableForInstr platform
   30    , getJumpDestBlockId        = SPARC.getJumpDestBlockId
   31    , canShortcut               = SPARC.canShortcut
   32    , shortcutStatics           = SPARC.shortcutStatics
   33    , shortcutJump              = SPARC.shortcutJump
   34    , pprNatCmmDecl             = SPARC.pprNatCmmDecl config
   35    , maxSpillSlots             = SPARC.maxSpillSlots config
   36    , allocatableRegs           = SPARC.allocatableRegs
   37    , ncgExpandTop              = map SPARC.expandTop
   38    , ncgMakeFarBranches        = const id
   39    , extractUnwindPoints       = const []
   40    , invertCondBranches        = \_ _ -> id
   41    -- Allocating more stack space for spilling isn't currently supported for the
   42    -- linear register allocator on SPARC, hence the panic below.
   43    , ncgAllocMoreStack         = noAllocMoreStack
   44    }
   45     where
   46       platform = ncgPlatform config
   47 
   48       noAllocMoreStack amount _
   49         = panic $   "Register allocator: out of stack slots (need " ++ show amount ++ ")\n"
   50               ++  "   If you are trying to compile SHA1.hs from the crypto library then this\n"
   51               ++  "   is a known limitation in the linear allocator.\n"
   52               ++  "\n"
   53               ++  "   Try enabling the graph colouring allocator with -fregs-graph instead."
   54               ++  "   You can still file a bug report if you like.\n"
   55 
   56 
   57 -- | instance for sparc instruction set
   58 instance Instruction SPARC.Instr where
   59    regUsageOfInstr         = SPARC.regUsageOfInstr
   60    patchRegsOfInstr        = SPARC.patchRegsOfInstr
   61    isJumpishInstr          = SPARC.isJumpishInstr
   62    jumpDestsOfInstr        = SPARC.jumpDestsOfInstr
   63    patchJumpInstr          = SPARC.patchJumpInstr
   64    mkSpillInstr            = SPARC.mkSpillInstr
   65    mkLoadInstr             = SPARC.mkLoadInstr
   66    takeDeltaInstr          = SPARC.takeDeltaInstr
   67    isMetaInstr             = SPARC.isMetaInstr
   68    mkRegRegMoveInstr       = SPARC.mkRegRegMoveInstr
   69    takeRegRegMoveInstr     = SPARC.takeRegRegMoveInstr
   70    mkJumpInstr             = SPARC.mkJumpInstr
   71    pprInstr                = SPARC.pprInstr
   72    mkComment               = pure . SPARC.COMMENT
   73    mkStackAllocInstr       = panic "no sparc_mkStackAllocInstr"
   74    mkStackDeallocInstr     = panic "no sparc_mkStackDeallocInstr"