-- | Formats on this architecture
--      A Format is a combination of width and class
--
--      TODO:   Signed vs unsigned?
--
--      TODO:   This module is currenly shared by all architectures because
--              NCGMonad need to know about it to make a VReg. It would be better
--              to have architecture specific formats, and do the overloading
--              properly. eg SPARC doesn't care about FF80.
--
module Format (
    Format(..),
    intFormat,
    floatFormat,
    isFloatFormat,
    cmmTypeFormat,
    formatToWidth,
    formatInBytes
)

where

import GhcPrelude

import Cmm
import Outputable

-- It looks very like the old MachRep, but it's now of purely local
-- significance, here in the native code generator.  You can change it
-- without global consequences.
--
-- A major use is as an opcode qualifier; thus the opcode
--      mov.l a b
-- might be encoded
--      MOV II32 a b
-- where the Format field encodes the ".l" part.

-- ToDo: it's not clear to me that we need separate signed-vs-unsigned formats
--        here.  I've removed them from the x86 version, we'll see what happens --SDM

-- ToDo: quite a few occurrences of Format could usefully be replaced by Width

data Format
        = II8
        | II16
        | II32
        | II64
        | FF32
        | FF64
        deriving (Int -> Format -> ShowS
[Format] -> ShowS
Format -> String
(Int -> Format -> ShowS)
-> (Format -> String) -> ([Format] -> ShowS) -> Show Format
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Format] -> ShowS
$cshowList :: [Format] -> ShowS
show :: Format -> String
$cshow :: Format -> String
showsPrec :: Int -> Format -> ShowS
$cshowsPrec :: Int -> Format -> ShowS
Show, Format -> Format -> Bool
(Format -> Format -> Bool)
-> (Format -> Format -> Bool) -> Eq Format
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Format -> Format -> Bool
$c/= :: Format -> Format -> Bool
== :: Format -> Format -> Bool
$c== :: Format -> Format -> Bool
Eq)


-- | Get the integer format of this width.
intFormat :: Width -> Format
intFormat :: Width -> Format
intFormat Width
width
 = case Width
width of
        Width
W8      -> Format
II8
        Width
W16     -> Format
II16
        Width
W32     -> Format
II32
        Width
W64     -> Format
II64
        Width
other   -> String -> Format
forall a. String -> a
sorry (String -> Format) -> String -> Format
forall a b. (a -> b) -> a -> b
$ String
"The native code generator cannot " String -> ShowS
forall a. [a] -> [a] -> [a]
++
            String
"produce code for Format.intFormat " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Width -> String
forall a. Show a => a -> String
show Width
other
            String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n\tConsider using the llvm backend with -fllvm"


-- | Get the float format of this width.
floatFormat :: Width -> Format
floatFormat :: Width -> Format
floatFormat Width
width
 = case Width
width of
        Width
W32     -> Format
FF32
        Width
W64     -> Format
FF64

        Width
other   -> String -> SDoc -> Format
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Format.floatFormat" (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
other)


-- | Check if a format represents a floating point value.
isFloatFormat :: Format -> Bool
isFloatFormat :: Format -> Bool
isFloatFormat Format
format
 = case Format
format of
        Format
FF32    -> Bool
True
        Format
FF64    -> Bool
True
        Format
_       -> Bool
False


-- | Convert a Cmm type to a Format.
cmmTypeFormat :: CmmType -> Format
cmmTypeFormat :: CmmType -> Format
cmmTypeFormat CmmType
ty
        | CmmType -> Bool
isFloatType CmmType
ty        = Width -> Format
floatFormat (CmmType -> Width
typeWidth CmmType
ty)
        | Bool
otherwise             = Width -> Format
intFormat (CmmType -> Width
typeWidth CmmType
ty)


-- | Get the Width of a Format.
formatToWidth :: Format -> Width
formatToWidth :: Format -> Width
formatToWidth Format
format
 = case Format
format of
        Format
II8             -> Width
W8
        Format
II16            -> Width
W16
        Format
II32            -> Width
W32
        Format
II64            -> Width
W64
        Format
FF32            -> Width
W32
        Format
FF64            -> Width
W64


formatInBytes :: Format -> Int
formatInBytes :: Format -> Int
formatInBytes = Width -> Int
widthInBytes (Width -> Int) -> (Format -> Width) -> Format -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Format -> Width
formatToWidth