summaryrefslogtreecommitdiff
path: root/compiler/GHC/StgToCmm/ArgRep.hs
blob: 4d85d23d173748e1a2aac892376da4ed0a019755 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
-----------------------------------------------------------------------------
--
-- Argument representations used in GHC.StgToCmm.Layout.
--
-- (c) The University of Glasgow 2013
--
-----------------------------------------------------------------------------

{-# LANGUAGE LambdaCase #-}

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

        argRepString, isNonV, idArgRep,

        slowCallPattern,

        ) where

import GHC.Prelude
import GHC.Platform

import GHC.StgToCmm.Closure    ( idPrimRep )
import GHC.Runtime.Heap.Layout ( WordOff )
import GHC.Types.Id            ( Id )
import GHC.Core.TyCon          ( PrimRep(..), primElemRepSizeB )
import GHC.Types.Basic         ( RepArity )
import GHC.Settings.Constants  ( wORD64_SIZE, dOUBLE_SIZE )

import GHC.Utils.Outputable
import GHC.Data.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 = text . argRepString

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

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

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

argRepSizeW :: Platform -> ArgRep -> WordOff -- Size in words
argRepSizeW platform = \case
   N   -> 1
   P   -> 1
   F   -> 1
   L   -> wORD64_SIZE `quot` ws
   D   -> dOUBLE_SIZE `quot` ws
   V   -> 0
   V16 -> 16          `quot` ws
   V32 -> 32          `quot` ws
   V64 -> 64          `quot` ws
  where
   ws       = platformWordSizeInBytes platform

idArgRep :: Id -> ArgRep
idArgRep = toArgRep . 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 (P: P: P: P: P: P: _) = (fsLit "stg_ap_pppppp", 6)
slowCallPattern (P: P: P: P: P: _)    = (fsLit "stg_ap_ppppp", 5)
slowCallPattern (P: P: P: P: _)       = (fsLit "stg_ap_pppp", 4)
slowCallPattern (P: P: P: V: _)       = (fsLit "stg_ap_pppv", 4)
slowCallPattern (P: P: P: _)          = (fsLit "stg_ap_ppp", 3)
slowCallPattern (P: P: V: _)          = (fsLit "stg_ap_ppv", 3)
slowCallPattern (P: P: _)             = (fsLit "stg_ap_pp", 2)
slowCallPattern (P: V: _)             = (fsLit "stg_ap_pv", 2)
slowCallPattern (P: _)                = (fsLit "stg_ap_p", 1)
slowCallPattern (V: _)                = (fsLit "stg_ap_v", 1)
slowCallPattern (N: _)                = (fsLit "stg_ap_n", 1)
slowCallPattern (F: _)                = (fsLit "stg_ap_f", 1)
slowCallPattern (D: _)                = (fsLit "stg_ap_d", 1)
slowCallPattern (L: _)                = (fsLit "stg_ap_l", 1)
slowCallPattern (V16: _)              = (fsLit "stg_ap_v16", 1)
slowCallPattern (V32: _)              = (fsLit "stg_ap_v32", 1)
slowCallPattern (V64: _)              = (fsLit "stg_ap_v64", 1)
slowCallPattern []                    = (fsLit "stg_ap_0", 0)