never executed always true always false
    1 module GHC.Platform.Regs
    2        (callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg)
    3        where
    4 
    5 import GHC.Prelude
    6 
    7 import GHC.Cmm.Expr
    8 import GHC.Platform
    9 import GHC.Platform.Reg
   10 
   11 import qualified GHC.Platform.ARM        as ARM
   12 import qualified GHC.Platform.AArch64    as AArch64
   13 import qualified GHC.Platform.PPC        as PPC
   14 import qualified GHC.Platform.S390X      as S390X
   15 import qualified GHC.Platform.SPARC      as SPARC
   16 import qualified GHC.Platform.X86        as X86
   17 import qualified GHC.Platform.X86_64     as X86_64
   18 import qualified GHC.Platform.RISCV64    as RISCV64
   19 import qualified GHC.Platform.NoRegs     as NoRegs
   20 
   21 -- | Returns 'True' if this global register is stored in a caller-saves
   22 -- machine register.
   23 
   24 callerSaves :: Platform -> GlobalReg -> Bool
   25 callerSaves platform
   26  | platformUnregisterised platform = NoRegs.callerSaves
   27  | otherwise
   28  = case platformArch platform of
   29    ArchX86     -> X86.callerSaves
   30    ArchX86_64  -> X86_64.callerSaves
   31    ArchS390X   -> S390X.callerSaves
   32    ArchSPARC   -> SPARC.callerSaves
   33    ArchARM {}  -> ARM.callerSaves
   34    ArchAArch64 -> AArch64.callerSaves
   35    ArchRISCV64 -> RISCV64.callerSaves
   36    arch
   37     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
   38         PPC.callerSaves
   39 
   40     | otherwise -> NoRegs.callerSaves
   41 
   42 -- | Here is where the STG register map is defined for each target arch.
   43 -- The order matters (for the llvm backend anyway)! We must make sure to
   44 -- maintain the order here with the order used in the LLVM calling conventions.
   45 -- Note that also, this isn't all registers, just the ones that are currently
   46 -- possibly mapped to real registers.
   47 activeStgRegs :: Platform -> [GlobalReg]
   48 activeStgRegs platform
   49  | platformUnregisterised platform = NoRegs.activeStgRegs
   50  | otherwise
   51  = case platformArch platform of
   52    ArchX86     -> X86.activeStgRegs
   53    ArchX86_64  -> X86_64.activeStgRegs
   54    ArchS390X   -> S390X.activeStgRegs
   55    ArchSPARC   -> SPARC.activeStgRegs
   56    ArchARM {}  -> ARM.activeStgRegs
   57    ArchAArch64 -> AArch64.activeStgRegs
   58    ArchRISCV64 -> RISCV64.activeStgRegs
   59    arch
   60     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
   61         PPC.activeStgRegs
   62 
   63     | otherwise -> NoRegs.activeStgRegs
   64 
   65 haveRegBase :: Platform -> Bool
   66 haveRegBase platform
   67  | platformUnregisterised platform = NoRegs.haveRegBase
   68  | otherwise
   69  = case platformArch platform of
   70    ArchX86     -> X86.haveRegBase
   71    ArchX86_64  -> X86_64.haveRegBase
   72    ArchS390X   -> S390X.haveRegBase
   73    ArchSPARC   -> SPARC.haveRegBase
   74    ArchARM {}  -> ARM.haveRegBase
   75    ArchAArch64 -> AArch64.haveRegBase
   76    ArchRISCV64 -> RISCV64.haveRegBase
   77    arch
   78     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
   79         PPC.haveRegBase
   80 
   81     | otherwise -> NoRegs.haveRegBase
   82 
   83 globalRegMaybe :: Platform -> GlobalReg -> Maybe RealReg
   84 globalRegMaybe platform
   85  | platformUnregisterised platform = NoRegs.globalRegMaybe
   86  | otherwise
   87  = case platformArch platform of
   88    ArchX86     -> X86.globalRegMaybe
   89    ArchX86_64  -> X86_64.globalRegMaybe
   90    ArchS390X   -> S390X.globalRegMaybe
   91    ArchSPARC   -> SPARC.globalRegMaybe
   92    ArchARM {}  -> ARM.globalRegMaybe
   93    ArchAArch64 -> AArch64.globalRegMaybe
   94    ArchRISCV64 -> RISCV64.globalRegMaybe
   95    arch
   96     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
   97         PPC.globalRegMaybe
   98 
   99     | otherwise -> NoRegs.globalRegMaybe
  100 
  101 freeReg :: Platform -> RegNo -> Bool
  102 freeReg platform
  103  | platformUnregisterised platform = NoRegs.freeReg
  104  | otherwise
  105  = case platformArch platform of
  106    ArchX86     -> X86.freeReg
  107    ArchX86_64  -> X86_64.freeReg
  108    ArchS390X   -> S390X.freeReg
  109    ArchSPARC   -> SPARC.freeReg
  110    ArchARM {}  -> ARM.freeReg
  111    ArchAArch64 -> AArch64.freeReg
  112    ArchRISCV64 -> RISCV64.freeReg
  113    arch
  114     | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] ->
  115         PPC.freeReg
  116 
  117     | otherwise -> NoRegs.freeReg