module GHC.CmmToAsm.X86.RegInfo (
        mkVirtualReg,
        regDotColor
)

where

import GHC.Prelude

import GHC.CmmToAsm.Format
import GHC.Platform.Reg

import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Platform
import GHC.Types.Unique

import GHC.Types.Unique.FM
import GHC.CmmToAsm.X86.Regs


mkVirtualReg :: Unique -> Format -> VirtualReg
mkVirtualReg :: Unique -> Format -> VirtualReg
mkVirtualReg Unique
u Format
format
   = case Format
format of
        Format
FF32    -> Unique -> VirtualReg
VirtualRegD Unique
u
        -- for scalar F32, we use the same xmm as F64!
        -- this is a hack that needs some improvement.
        -- For now we map both to being allocated as "Double" Registers
        -- on X86/X86_64
        Format
FF64    -> Unique -> VirtualReg
VirtualRegD Unique
u
        Format
_other  -> Unique -> VirtualReg
VirtualRegI Unique
u

regDotColor :: Platform -> RealReg -> SDoc
regDotColor :: Platform -> RealReg -> SDoc
regDotColor Platform
platform RealReg
reg
 = case (UniqFM RealReg [Char] -> RealReg -> Maybe [Char]
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM (Platform -> UniqFM RealReg [Char]
regColors Platform
platform) RealReg
reg) of
        Just [Char]
str -> [Char] -> SDoc
text [Char]
str
        Maybe [Char]
_        -> [Char] -> SDoc
forall a. [Char] -> a
panic [Char]
"Register not assigned a color"

regColors :: Platform -> UniqFM RealReg [Char]
regColors :: Platform -> UniqFM RealReg [Char]
regColors Platform
platform = [(RealReg, [Char])] -> UniqFM RealReg [Char]
forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM (Platform -> [(RealReg, [Char])]
normalRegColors Platform
platform)

normalRegColors :: Platform -> [(RealReg,String)]
normalRegColors :: Platform -> [(RealReg, [Char])]
normalRegColors Platform
platform =
    [RealReg] -> [[Char]] -> [(RealReg, [Char])]
forall a b. [a] -> [b] -> [(a, b)]
zip ((RegNo -> RealReg) -> [RegNo] -> [RealReg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> RealReg
realRegSingle [RegNo
0..Platform -> RegNo
lastint Platform
platform]) [[Char]]
colors
        [(RealReg, [Char])] -> [(RealReg, [Char])] -> [(RealReg, [Char])]
forall a. [a] -> [a] -> [a]
++ [RealReg] -> [[Char]] -> [(RealReg, [Char])]
forall a b. [a] -> [b] -> [(a, b)]
zip ((RegNo -> RealReg) -> [RegNo] -> [RealReg]
forall a b. (a -> b) -> [a] -> [b]
map RegNo -> RealReg
realRegSingle [RegNo
firstxmm..Platform -> RegNo
lastxmm Platform
platform]) [[Char]]
greys
  where
    -- 16 colors - enough for amd64 gp regs
    colors :: [[Char]]
colors = [[Char]
"#800000",[Char]
"#ff0000",[Char]
"#808000",[Char]
"#ffff00",[Char]
"#008000"
             ,[Char]
"#00ff00",[Char]
"#008080",[Char]
"#00ffff",[Char]
"#000080",[Char]
"#0000ff"
             ,[Char]
"#800080",[Char]
"#ff00ff",[Char]
"#87005f",[Char]
"#875f00",[Char]
"#87af00"
             ,[Char]
"#ff00af"]

    -- 16 shades of grey, enough for the currently supported
    -- SSE extensions.
    greys :: [[Char]]
greys = [[Char]
"#0e0e0e",[Char]
"#1c1c1c",[Char]
"#2a2a2a",[Char]
"#383838",[Char]
"#464646"
            ,[Char]
"#545454",[Char]
"#626262",[Char]
"#707070",[Char]
"#7e7e7e",[Char]
"#8c8c8c"
            ,[Char]
"#9a9a9a",[Char]
"#a8a8a8",[Char]
"#b6b6b6",[Char]
"#c4c4c4",[Char]
"#d2d2d2"
            ,[Char]
"#e0e0e0"]



--     32 shades of grey - use for avx 512 if we ever need it
--     greys = ["#070707","#0e0e0e","#151515","#1c1c1c"
--             ,"#232323","#2a2a2a","#313131","#383838","#3f3f3f"
--             ,"#464646","#4d4d4d","#545454","#5b5b5b","#626262"
--             ,"#696969","#707070","#777777","#7e7e7e","#858585"
--             ,"#8c8c8c","#939393","#9a9a9a","#a1a1a1","#a8a8a8"
--             ,"#afafaf","#b6b6b6","#bdbdbd","#c4c4c4","#cbcbcb"
--             ,"#d2d2d2","#d9d9d9","#e0e0e0"]