summaryrefslogtreecommitdiff
path: root/compiler/vectorise/Vectorise/Utils/Base.hs
blob: 0bd54f4408d3b63c7648fc6d97a9105e9cd07733 (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
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
module Vectorise.Utils.Base 
  ( voidType
  , newLocalVVar

  , mkDataConTag, dataConTagZ
  , mkWrapType
  , mkClosureTypes
  , mkPReprType
  , mkPDataType, mkPDatasType
  , splitPrimTyCon
  , mkBuiltinCo

  , wrapNewTypeBodyOfWrap
  , unwrapNewTypeBodyOfWrap
  , wrapNewTypeBodyOfPDataWrap
  , unwrapNewTypeBodyOfPDataWrap
  , wrapNewTypeBodyOfPDatasWrap
  , unwrapNewTypeBodyOfPDatasWrap
  
  , pdataReprTyCon
  , pdataReprTyConExact
  , pdatasReprTyConExact
  , pdataUnwrapScrut
  
  , preprSynTyCon
) where

import Vectorise.Monad
import Vectorise.Vect
import Vectorise.Builtins

import CoreSyn
import CoreUtils
import FamInstEnv
import Coercion
import Type
import TyCon
import DataCon
import MkId
import DynFlags
import FastString

#include "HsVersions.h"

-- Simple Types ---------------------------------------------------------------

voidType :: VM Type
voidType = mkBuiltinTyConApp voidTyCon []


-- Name Generation ------------------------------------------------------------

newLocalVVar :: FastString -> Type -> VM VVar
newLocalVVar fs vty
  = do
      lty <- mkPDataType vty
      vv  <- newLocalVar fs vty
      lv  <- newLocalVar fs lty
      return (vv,lv)


-- Constructors ---------------------------------------------------------------

mkDataConTag :: DynFlags -> DataCon -> CoreExpr
mkDataConTag dflags = mkIntLitInt dflags . dataConTagZ

dataConTagZ :: DataCon -> Int
dataConTagZ con = dataConTag con - fIRST_TAG


-- Type Construction ----------------------------------------------------------

-- |Make an application of the 'Wrap' type constructor.
--
mkWrapType :: Type -> VM Type
mkWrapType ty = mkBuiltinTyConApp wrapTyCon [ty]

-- |Make an application of the closure type constructor.
--
mkClosureTypes :: [Type] -> Type -> VM Type
mkClosureTypes = mkBuiltinTyConApps closureTyCon

-- |Make an application of the 'PRepr' type constructor.
--
mkPReprType :: Type -> VM Type
mkPReprType ty = mkBuiltinTyConApp preprTyCon [ty]

-- | Make an appliction of the 'PData' tycon to some argument.
--
mkPDataType :: Type -> VM Type
mkPDataType ty = mkBuiltinTyConApp pdataTyCon [ty]

-- | Make an application of the 'PDatas' tycon to some argument.
--
mkPDatasType :: Type -> VM Type
mkPDatasType ty = mkBuiltinTyConApp pdatasTyCon [ty]

-- Make an application of a builtin type constructor to some arguments.
--
mkBuiltinTyConApp :: (Builtins -> TyCon) -> [Type] -> VM Type
mkBuiltinTyConApp get_tc tys
  = do { tc <- builtin get_tc
       ; return $ mkTyConApp tc tys
       }

-- Make a cascading application of a builtin type constructor.
--
mkBuiltinTyConApps :: (Builtins -> TyCon) -> [Type] -> Type -> VM Type
mkBuiltinTyConApps get_tc tys ty
 = do { tc <- builtin get_tc
      ; return $ foldr (mk tc) ty tys
      }
  where
    mk tc ty1 ty2 = mkTyConApp tc [ty1,ty2]


-- Type decomposition ---------------------------------------------------------

-- |Checks if a type constructor is defined in 'GHC.Prim' (e.g., 'Int#'); if so, returns it.
--
splitPrimTyCon :: Type -> Maybe TyCon
splitPrimTyCon ty
  | Just (tycon, []) <- splitTyConApp_maybe ty
  , isPrimTyCon tycon
  = Just tycon
  | otherwise = Nothing


-- Coercion Construction -----------------------------------------------------

-- |Make a coersion to some builtin type.
--
mkBuiltinCo :: (Builtins -> TyCon) -> VM Coercion
mkBuiltinCo get_tc
  = do { tc <- builtin get_tc
       ; return $ mkTyConAppCo tc []
       }


-- Wrapping and unwrapping the 'Wrap' newtype ---------------------------------

-- |Apply the constructor wrapper of the 'Wrap' /newtype/.
--
wrapNewTypeBodyOfWrap :: CoreExpr -> Type -> VM CoreExpr
wrapNewTypeBodyOfWrap e ty
  = do { wrap_tc <- builtin wrapTyCon
       ; return $ wrapNewTypeBody wrap_tc [ty] e
       }

-- |Strip the constructor wrapper of the 'Wrap' /newtype/.
--
unwrapNewTypeBodyOfWrap :: CoreExpr -> Type -> VM CoreExpr
unwrapNewTypeBodyOfWrap e ty
  = do { wrap_tc <- builtin wrapTyCon
       ; return $ unwrapNewTypeBody wrap_tc [ty] e
       }

-- |Apply the constructor wrapper of the 'PData' /newtype/ instance of 'Wrap'.
--
wrapNewTypeBodyOfPDataWrap :: CoreExpr -> Type -> VM CoreExpr
wrapNewTypeBodyOfPDataWrap e ty
  = do { wrap_tc  <- builtin wrapTyCon
       ; pwrap_tc <- pdataReprTyConExact wrap_tc
       ; return $ wrapNewTypeBody pwrap_tc [ty] e
       }

-- |Strip the constructor wrapper of the 'PData' /newtype/ instance of 'Wrap'.
--
unwrapNewTypeBodyOfPDataWrap :: CoreExpr -> Type -> VM CoreExpr
unwrapNewTypeBodyOfPDataWrap e ty
  = do { wrap_tc  <- builtin wrapTyCon
       ; pwrap_tc <- pdataReprTyConExact wrap_tc
       ; return $ unwrapNewTypeBody pwrap_tc [ty] (unwrapFamInstScrut pwrap_tc [ty] e)
       }

-- |Apply the constructor wrapper of the 'PDatas' /newtype/ instance of 'Wrap'.
--
wrapNewTypeBodyOfPDatasWrap :: CoreExpr -> Type -> VM CoreExpr
wrapNewTypeBodyOfPDatasWrap e ty
  = do { wrap_tc  <- builtin wrapTyCon
       ; pwrap_tc <- pdatasReprTyConExact wrap_tc
       ; return $ wrapNewTypeBody pwrap_tc [ty] e
       }

-- |Strip the constructor wrapper of the 'PDatas' /newtype/ instance of 'Wrap'.
--
unwrapNewTypeBodyOfPDatasWrap :: CoreExpr -> Type -> VM CoreExpr
unwrapNewTypeBodyOfPDatasWrap e ty
  = do { wrap_tc  <- builtin wrapTyCon
       ; pwrap_tc <- pdatasReprTyConExact wrap_tc
       ; return $ unwrapNewTypeBody pwrap_tc [ty] (unwrapFamInstScrut pwrap_tc [ty] e)
       }


-- 'PData' representation types ----------------------------------------------

-- |Get the representation tycon of the 'PData' data family for a given type.
--
-- This tycon does not appear explicitly in the source program — see Note [PData TyCons] in
-- 'Vectorise.Generic.Description':
--
--   @pdataReprTyCon {Sum2} = {PDataSum2}@
--
-- The type for which we look up a 'PData' instance may be more specific than the type in the
-- instance declaration.  In that case the second component of the result will be more specific than
-- a set of distinct type variables.
-- 
pdataReprTyCon :: Type -> VM (TyCon, [Type])
pdataReprTyCon ty 
  = do 
    { FamInstMatch { fim_instance = famInst
                   , fim_tys      = tys } <- builtin pdataTyCon >>= (`lookupFamInst` [ty])
    ; return (dataFamInstRepTyCon famInst, tys)
    }

-- |Get the representation tycon of the 'PData' data family for a given type constructor.
--
-- For example, for a binary type constructor 'T', we determine the representation type constructor
-- for 'PData (T a b)'.
--
pdataReprTyConExact :: TyCon -> VM TyCon
pdataReprTyConExact tycon
  = do {   -- look up the representation tycon; if there is a match at all, it will be be exact
       ;   -- (i.e.,' _tys' will be distinct type variables)
       ; (ptycon, _tys) <- pdataReprTyCon (tycon `mkTyConApp` mkTyVarTys (tyConTyVars tycon))
       ; return ptycon
       }

-- |Get the representation tycon of the 'PDatas' data family for a given type constructor.
--
-- For example, for a binary type constructor 'T', we determine the representation type constructor
-- for 'PDatas (T a b)'.
--
pdatasReprTyConExact :: TyCon -> VM TyCon
pdatasReprTyConExact tycon
  = do {   -- look up the representation tycon; if there is a match at all, it will be be exact
       ; (FamInstMatch { fim_instance = ptycon }) <- pdatasReprTyCon (tycon `mkTyConApp` mkTyVarTys (tyConTyVars tycon))
       ; return $ dataFamInstRepTyCon ptycon
       }
  where
    pdatasReprTyCon ty = builtin pdatasTyCon >>= (`lookupFamInst` [ty])

-- |Unwrap a 'PData' representation scrutinee.
--
pdataUnwrapScrut :: VExpr -> VM (CoreExpr, CoreExpr, DataCon)
pdataUnwrapScrut (ve, le)
  = do { (tc, arg_tys) <- pdataReprTyCon ty
       ; let [dc] = tyConDataCons tc
       ; return (ve, unwrapFamInstScrut tc arg_tys le, dc)
       }
  where
    ty = exprType ve


-- 'PRepr' representation types ----------------------------------------------

-- |Get the representation tycon of the 'PRepr' type family for a given type.
--
preprSynTyCon :: Type -> VM FamInstMatch
preprSynTyCon ty = builtin preprTyCon >>= (`lookupFamInst` [ty])