module Format (
Format(..),
intFormat,
floatFormat,
isFloatFormat,
cmmTypeFormat,
formatToWidth,
formatInBytes
)
where
import GhcPrelude
import Cmm
import Outputable
data Format
= II8
| II16
| II32
| II64
| FF32
| FF64
| FF80
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)
intFormat :: Width -> Format
intFormat :: Width -> Format
intFormat width :: Width
width
= case Width
width of
W8 -> Format
II8
W16 -> Format
II16
W32 -> Format
II32
W64 -> Format
II64
other :: Width
other -> String -> Format
forall a. String -> a
sorry (String -> Format) -> String -> Format
forall a b. (a -> b) -> a -> b
$ "The native code generator cannot " String -> ShowS
forall a. [a] -> [a] -> [a]
++
"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]
++ "\n\tConsider using the llvm backend with -fllvm"
floatFormat :: Width -> Format
floatFormat :: Width -> Format
floatFormat width :: Width
width
= case Width
width of
W32 -> Format
FF32
W64 -> Format
FF64
W80 -> Format
FF80
other :: Width
other -> String -> SDoc -> Format
forall a. HasCallStack => String -> SDoc -> a
pprPanic "Format.floatFormat" (Width -> SDoc
forall a. Outputable a => a -> SDoc
ppr Width
other)
isFloatFormat :: Format -> Bool
isFloatFormat :: Format -> Bool
isFloatFormat format :: Format
format
= case Format
format of
FF32 -> Bool
True
FF64 -> Bool
True
FF80 -> Bool
True
_ -> Bool
False
cmmTypeFormat :: CmmType -> Format
cmmTypeFormat :: CmmType -> Format
cmmTypeFormat ty :: 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)
formatToWidth :: Format -> Width
formatToWidth :: Format -> Width
formatToWidth format :: Format
format
= case Format
format of
II8 -> Width
W8
II16 -> Width
W16
II32 -> Width
W32
II64 -> Width
W64
FF32 -> Width
W32
FF64 -> Width
W64
FF80 -> Width
W80
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