-----------------------------------------------------------------------------
--
-- Argument representations used in GHC.StgToCmm.Layout.
--
-- (c) The University of Glasgow 2013
--
-----------------------------------------------------------------------------

module GHC.StgToCmm.ArgRep (
        ArgRep(..), toArgRep, argRepSizeW,

        argRepString, isNonV, idArgRep,

        slowCallPattern,

        ) where

import GhcPrelude

import GHC.StgToCmm.Closure ( idPrimRep )

import SMRep            ( WordOff )
import Id               ( Id )
import TyCon            ( PrimRep(..), primElemRepSizeB )
import BasicTypes       ( RepArity )
import Constants        ( wORD64_SIZE )
import DynFlags

import Outputable
import FastString

-- I extricated this code as this new module in order to avoid a
-- cyclic dependency between GHC.StgToCmm.Layout and GHC.StgToCmm.Ticky.
--
-- NSF 18 Feb 2013

-------------------------------------------------------------------------
--      Classifying arguments: ArgRep
-------------------------------------------------------------------------

-- ArgRep is re-exported by GHC.StgToCmm.Layout, but only for use in the
-- byte-code generator which also needs to know about the
-- classification of arguments.

data ArgRep = P   -- GC Ptr
            | N   -- Word-sized non-ptr
            | L   -- 64-bit non-ptr (long)
            | V   -- Void
            | F   -- Float
            | D   -- Double
            | V16 -- 16-byte (128-bit) vectors of Float/Double/Int8/Word32/etc.
            | V32 -- 32-byte (256-bit) vectors of Float/Double/Int8/Word32/etc.
            | V64 -- 64-byte (512-bit) vectors of Float/Double/Int8/Word32/etc.
instance Outputable ArgRep where ppr :: ArgRep -> SDoc
ppr = String -> SDoc
text (String -> SDoc) -> (ArgRep -> String) -> ArgRep -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArgRep -> String
argRepString

argRepString :: ArgRep -> String
argRepString :: ArgRep -> String
argRepString ArgRep
P = String
"P"
argRepString ArgRep
N = String
"N"
argRepString ArgRep
L = String
"L"
argRepString ArgRep
V = String
"V"
argRepString ArgRep
F = String
"F"
argRepString ArgRep
D = String
"D"
argRepString ArgRep
V16 = String
"V16"
argRepString ArgRep
V32 = String
"V32"
argRepString ArgRep
V64 = String
"V64"

toArgRep :: PrimRep -> ArgRep
toArgRep :: PrimRep -> ArgRep
toArgRep PrimRep
VoidRep           = ArgRep
V
toArgRep PrimRep
LiftedRep         = ArgRep
P
toArgRep PrimRep
UnliftedRep       = ArgRep
P
toArgRep PrimRep
IntRep            = ArgRep
N
toArgRep PrimRep
WordRep           = ArgRep
N
toArgRep PrimRep
Int8Rep           = ArgRep
N  -- Gets widened to native word width for calls
toArgRep PrimRep
Word8Rep          = ArgRep
N  -- Gets widened to native word width for calls
toArgRep PrimRep
Int16Rep          = ArgRep
N  -- Gets widened to native word width for calls
toArgRep PrimRep
Word16Rep         = ArgRep
N  -- Gets widened to native word width for calls
toArgRep PrimRep
Int32Rep          = ArgRep
N  -- Gets widened to native word width for calls
toArgRep PrimRep
Word32Rep         = ArgRep
N  -- Gets widened to native word width for calls
toArgRep PrimRep
AddrRep           = ArgRep
N
toArgRep PrimRep
Int64Rep          = ArgRep
L
toArgRep PrimRep
Word64Rep         = ArgRep
L
toArgRep PrimRep
FloatRep          = ArgRep
F
toArgRep PrimRep
DoubleRep         = ArgRep
D
toArgRep (VecRep Int
len PrimElemRep
elem) = case Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
*PrimElemRep -> Int
primElemRepSizeB PrimElemRep
elem of
                               Int
16 -> ArgRep
V16
                               Int
32 -> ArgRep
V32
                               Int
64 -> ArgRep
V64
                               Int
_  -> String -> ArgRep
forall a. HasCallStack => String -> a
error String
"toArgRep: bad vector primrep"

isNonV :: ArgRep -> Bool
isNonV :: ArgRep -> Bool
isNonV ArgRep
V = Bool
False
isNonV ArgRep
_ = Bool
True

argRepSizeW :: DynFlags -> ArgRep -> WordOff                -- Size in words
argRepSizeW :: DynFlags -> ArgRep -> Int
argRepSizeW DynFlags
_      ArgRep
N   = Int
1
argRepSizeW DynFlags
_      ArgRep
P   = Int
1
argRepSizeW DynFlags
_      ArgRep
F   = Int
1
argRepSizeW DynFlags
dflags ArgRep
L   = Int
wORD64_SIZE        Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` DynFlags -> Int
wORD_SIZE DynFlags
dflags
argRepSizeW DynFlags
dflags ArgRep
D   = DynFlags -> Int
dOUBLE_SIZE DynFlags
dflags Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` DynFlags -> Int
wORD_SIZE DynFlags
dflags
argRepSizeW DynFlags
_      ArgRep
V   = Int
0
argRepSizeW DynFlags
dflags ArgRep
V16 = Int
16                 Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` DynFlags -> Int
wORD_SIZE DynFlags
dflags
argRepSizeW DynFlags
dflags ArgRep
V32 = Int
32                 Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` DynFlags -> Int
wORD_SIZE DynFlags
dflags
argRepSizeW DynFlags
dflags ArgRep
V64 = Int
64                 Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` DynFlags -> Int
wORD_SIZE DynFlags
dflags

idArgRep :: Id -> ArgRep
idArgRep :: Id -> ArgRep
idArgRep = PrimRep -> ArgRep
toArgRep (PrimRep -> ArgRep) -> (Id -> PrimRep) -> Id -> ArgRep
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> PrimRep
idPrimRep

-- This list of argument patterns should be kept in sync with at least
-- the following:
--
--  * GHC.StgToCmm.Layout.stdPattern maybe to some degree?
--
--  * the RTS_RET(stg_ap_*) and RTS_FUN_DECL(stg_ap_*_fast)
--  declarations in includes/stg/MiscClosures.h
--
--  * the SLOW_CALL_*_ctr declarations in includes/stg/Ticky.h,
--
--  * the TICK_SLOW_CALL_*() #defines in includes/Cmm.h,
--
--  * the PR_CTR(SLOW_CALL_*_ctr) calls in rts/Ticky.c,
--
--  * and the SymI_HasProto(stg_ap_*_{ret,info,fast}) calls and
--  SymI_HasProto(SLOW_CALL_*_ctr) calls in rts/Linker.c
--
-- There may be more places that I haven't found; I merely igrep'd for
-- pppppp and excluded things that seemed ghci-specific.
--
-- Also, it seems at the moment that ticky counters with void
-- arguments will never be bumped, but I'm still declaring those
-- counters, defensively.
--
-- NSF 6 Mar 2013

slowCallPattern :: [ArgRep] -> (FastString, RepArity)
-- Returns the generic apply function and arity
--
-- The first batch of cases match (some) specialised entries
-- The last group deals exhaustively with the cases for the first argument
--   (and the zero-argument case)
--
-- In 99% of cases this function will match *all* the arguments in one batch

slowCallPattern :: [ArgRep] -> (FastString, Int)
slowCallPattern (ArgRep
P: ArgRep
P: ArgRep
P: ArgRep
P: ArgRep
P: ArgRep
P: [ArgRep]
_) = (String -> FastString
fsLit String
"stg_ap_pppppp", Int
6)
slowCallPattern (ArgRep
P: ArgRep
P: ArgRep
P: ArgRep
P: ArgRep
P: [ArgRep]
_)    = (String -> FastString
fsLit String
"stg_ap_ppppp", Int
5)
slowCallPattern (ArgRep
P: ArgRep
P: ArgRep
P: ArgRep
P: [ArgRep]
_)       = (String -> FastString
fsLit String
"stg_ap_pppp", Int
4)
slowCallPattern (ArgRep
P: ArgRep
P: ArgRep
P: ArgRep
V: [ArgRep]
_)       = (String -> FastString
fsLit String
"stg_ap_pppv", Int
4)
slowCallPattern (ArgRep
P: ArgRep
P: ArgRep
P: [ArgRep]
_)          = (String -> FastString
fsLit String
"stg_ap_ppp", Int
3)
slowCallPattern (ArgRep
P: ArgRep
P: ArgRep
V: [ArgRep]
_)          = (String -> FastString
fsLit String
"stg_ap_ppv", Int
3)
slowCallPattern (ArgRep
P: ArgRep
P: [ArgRep]
_)             = (String -> FastString
fsLit String
"stg_ap_pp", Int
2)
slowCallPattern (ArgRep
P: ArgRep
V: [ArgRep]
_)             = (String -> FastString
fsLit String
"stg_ap_pv", Int
2)
slowCallPattern (ArgRep
P: [ArgRep]
_)                = (String -> FastString
fsLit String
"stg_ap_p", Int
1)
slowCallPattern (ArgRep
V: [ArgRep]
_)                = (String -> FastString
fsLit String
"stg_ap_v", Int
1)
slowCallPattern (ArgRep
N: [ArgRep]
_)                = (String -> FastString
fsLit String
"stg_ap_n", Int
1)
slowCallPattern (ArgRep
F: [ArgRep]
_)                = (String -> FastString
fsLit String
"stg_ap_f", Int
1)
slowCallPattern (ArgRep
D: [ArgRep]
_)                = (String -> FastString
fsLit String
"stg_ap_d", Int
1)
slowCallPattern (ArgRep
L: [ArgRep]
_)                = (String -> FastString
fsLit String
"stg_ap_l", Int
1)
slowCallPattern (ArgRep
V16: [ArgRep]
_)              = (String -> FastString
fsLit String
"stg_ap_v16", Int
1)
slowCallPattern (ArgRep
V32: [ArgRep]
_)              = (String -> FastString
fsLit String
"stg_ap_v32", Int
1)
slowCallPattern (ArgRep
V64: [ArgRep]
_)              = (String -> FastString
fsLit String
"stg_ap_v64", Int
1)
slowCallPattern []                    = (String -> FastString
fsLit String
"stg_ap_0", Int
0)