never executed always true always false
    1 -- | Formats on this architecture
    2 --      A Format is a combination of width and class
    3 --
    4 --      TODO:   Signed vs unsigned?
    5 --
    6 --      TODO:   This module is currently shared by all architectures because
    7 --              NCGMonad need to know about it to make a VReg. It would be better
    8 --              to have architecture specific formats, and do the overloading
    9 --              properly. eg SPARC doesn't care about FF80.
   10 --
   11 module GHC.CmmToAsm.Format (
   12     Format(..),
   13     intFormat,
   14     floatFormat,
   15     isIntFormat,
   16     isFloatFormat,
   17     cmmTypeFormat,
   18     formatToWidth,
   19     formatInBytes
   20 )
   21 
   22 where
   23 
   24 import GHC.Prelude
   25 
   26 import GHC.Cmm
   27 import GHC.Utils.Outputable
   28 import GHC.Utils.Panic
   29 
   30 -- It looks very like the old MachRep, but it's now of purely local
   31 -- significance, here in the native code generator.  You can change it
   32 -- without global consequences.
   33 --
   34 -- A major use is as an opcode qualifier; thus the opcode
   35 --      mov.l a b
   36 -- might be encoded
   37 --      MOV II32 a b
   38 -- where the Format field encodes the ".l" part.
   39 
   40 -- ToDo: it's not clear to me that we need separate signed-vs-unsigned formats
   41 --        here.  I've removed them from the x86 version, we'll see what happens --SDM
   42 
   43 -- ToDo: quite a few occurrences of Format could usefully be replaced by Width
   44 
   45 data Format
   46         = II8
   47         | II16
   48         | II32
   49         | II64
   50         | FF32
   51         | FF64
   52         deriving (Show, Eq)
   53 
   54 
   55 -- | Get the integer format of this width.
   56 intFormat :: Width -> Format
   57 intFormat width
   58  = case width of
   59         W8      -> II8
   60         W16     -> II16
   61         W32     -> II32
   62         W64     -> II64
   63         other   -> sorry $ "The native code generator cannot " ++
   64             "produce code for Format.intFormat " ++ show other
   65             ++ "\n\tConsider using the llvm backend with -fllvm"
   66 
   67 
   68 -- | Get the float format of this width.
   69 floatFormat :: Width -> Format
   70 floatFormat width
   71  = case width of
   72         W32     -> FF32
   73         W64     -> FF64
   74 
   75         other   -> pprPanic "Format.floatFormat" (ppr other)
   76 
   77 -- | Check if a format represent an integer value.
   78 isIntFormat :: Format -> Bool
   79 isIntFormat = not . isFloatFormat
   80 
   81 -- | Check if a format represents a floating point value.
   82 isFloatFormat :: Format -> Bool
   83 isFloatFormat format
   84  = case format of
   85         FF32    -> True
   86         FF64    -> True
   87         _       -> False
   88 
   89 
   90 -- | Convert a Cmm type to a Format.
   91 cmmTypeFormat :: CmmType -> Format
   92 cmmTypeFormat ty
   93         | isFloatType ty        = floatFormat (typeWidth ty)
   94         | otherwise             = intFormat (typeWidth ty)
   95 
   96 
   97 -- | Get the Width of a Format.
   98 formatToWidth :: Format -> Width
   99 formatToWidth format
  100  = case format of
  101         II8             -> W8
  102         II16            -> W16
  103         II32            -> W32
  104         II64            -> W64
  105         FF32            -> W32
  106         FF64            -> W64
  107 
  108 
  109 formatInBytes :: Format -> Int
  110 formatInBytes = widthInBytes . formatToWidth