@@ -107,6 +107,19 @@ indexMaybe [] _ = Nothing
107
107
indexMaybe (x: _) 0 = Just x
108
108
indexMaybe (_: xs) n = indexMaybe xs (n- 1 )
109
109
110
+ opaqueBindingSpec :: GHC. InlineSpec
111
+ inlineBindingSpec :: GHC. InlineSpec
112
+ opaqueString :: String
113
+ #if MIN_VERSION_ghc(9,4,0)
114
+ opaqueBindingSpec = GHC. Opaque GHC. NoSourceText
115
+ inlineBindingSpec = GHC. Inline GHC. NoSourceText
116
+ opaqueString = " OPAQUE"
117
+ #else
118
+ opaqueBindingSpec = GHC. NoInline
119
+ inlineBindingSpec = GHC. Inline
120
+ opaqueString = " INLINE"
121
+ #endif
122
+
110
123
generateBindings
111
124
:: ClashOpts
112
125
-> GHC. Ghc ()
@@ -155,11 +168,7 @@ generateBindings opts startAction primDirs importDirs dbs hdl modName dflagsM =
155
168
-- selectors, no need to check free vars.
156
169
clsMap =
157
170
fmap (\ (v,i) ->
158
- #if MIN_VERSION_ghc(9,4,0)
159
- (Binding v GHC. noSrcSpan (GHC. Inline GHC. NoSourceText ) IsFun
160
- #else
161
- (Binding v GHC. noSrcSpan GHC. Inline IsFun
162
- #endif
171
+ (Binding v GHC. noSrcSpan inlineBindingSpec IsFun
163
172
(mkClassSelector inScope0 allTcCache (varType v) i) False ))
164
173
clsVMap
165
174
allBindings = bindingsMap `unionVarEnv` clsMap
@@ -210,11 +219,7 @@ setNoInlineTopEntities bm tes =
210
219
211
220
go b@ Binding {bindingId}
212
221
| bindingId `elemVarSet` ids
213
- #if MIN_VERSION_ghc(9,4,0)
214
- = b { bindingSpec = GHC. Opaque GHC. NoSourceText }
215
- #else
216
- = b { bindingSpec = GHC. NoInline }
217
- #endif
222
+ = b { bindingSpec = opaqueBindingSpec }
218
223
| otherwise = b
219
224
220
225
-- TODO This function should be changed to provide the information that
@@ -274,6 +279,48 @@ mkBindings primMap bindings clsOps unlocatable = do
274
279
275
280
return (mkVarEnv (concat bindingsList), mkVarEnv clsOpList)
276
281
282
+ #if MIN_VERSION_ghc(9,4,0)
283
+ strictnessInfo :: GHC. IdInfo -> GHC. DmdSig
284
+ strictnessInfo info = GHC. dmdSigInfo info
285
+
286
+ argDemands :: GHC. DmdSig -> [GHC. Demand ]
287
+ argDemands strictness = fst $ GHC. splitDmdSig strictness
288
+ #else
289
+ strictnessInfo :: GHC. IdInfo -> GHC. StrictSig
290
+ strictnessInfo info = GHC. strictnessInfo info
291
+
292
+ argDemands :: GHC. StrictSig -> [GHC. Demand ]
293
+ argDemands strictness = fst $ GHC. splitStrictSig strictness
294
+ #endif
295
+
296
+ #if MIN_VERSION_ghc(9,4,0)
297
+ appIsDeadEnd :: GHC. DmdSig -> Int -> Bool
298
+ #else
299
+ appIsDeadEnd :: GHC. StrictSig -> Int -> Bool
300
+ #endif
301
+ #if MIN_VERSION_ghc(9,2,0)
302
+ appIsDeadEnd = GHC. isDeadEndAppSig
303
+ #elif MIN_VERSION_ghc(9,0,0)
304
+ appIsDeadEnd = GHC. appIsDeadEnd
305
+ #else
306
+ appIsDeadEnd = GHC. appIsBottom
307
+ #endif
308
+
309
+ funArity :: GHC. Type -> Int
310
+ #if MIN_VERSION_ghc(9,2,0)
311
+ funArity ty = length . fst . GHC. splitFunTys . snd . GHC. splitForAllTyCoVars $ ty
312
+ #else
313
+ funArity ty = length . fst . GHC. splitFunTys . snd . GHC. splitForAllTys $ ty
314
+ #endif
315
+
316
+ realSrcLoc :: GHC. SrcLoc -> Maybe GHC. RealSrcLoc
317
+ realSrcLoc (GHC. UnhelpfulLoc _) = Nothing
318
+ #if MIN_VERSION_ghc(9,0,0)
319
+ realSrcLoc (GHC. RealSrcLoc l _) = Just l
320
+ #else
321
+ realSrcLoc (GHC. RealSrcLoc l _) = Just l
322
+ #endif
323
+
277
324
{-
278
325
NOTE [bindings in recursive groups]
279
326
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -316,30 +363,11 @@ checkPrimitive primMap v = do
316
363
let
317
364
info = GHC. idInfo v
318
365
inline = GHC. inlinePragmaSpec $ GHC. inlinePragInfo info
319
- #if MIN_VERSION_ghc(9,4,0)
320
- strictness = GHC. dmdSigInfo info
321
- #else
322
- strictness = GHC. strictnessInfo info
323
- #endif
366
+ strictness = strictnessInfo info
324
367
ty = GHC. varType v
325
- #if MIN_VERSION_ghc(9,2,0)
326
- (argTys,_resTy) = GHC. splitFunTys (snd (GHC. splitForAllTyCoVars ty))
327
- #else
328
- (argTys,_resTy) = GHC. splitFunTys . snd . GHC. splitForAllTys $ ty
329
- #endif
330
- #if MIN_VERSION_ghc(9,4,0)
331
- (dmdArgs,_dmdRes) = GHC. splitDmdSig strictness
332
- #else
333
- (dmdArgs,_dmdRes) = GHC. splitStrictSig strictness
334
- #endif
335
- nrOfArgs = length argTys
336
- loc = case GHC. getSrcLoc v of
337
- GHC. UnhelpfulLoc _ -> " "
338
- #if MIN_VERSION_ghc(9,0,0)
339
- GHC. RealSrcLoc l _ -> showPpr l ++ " : "
340
- #else
341
- GHC. RealSrcLoc l -> showPpr l ++ " : "
342
- #endif
368
+ dmdArgs = argDemands strictness
369
+ nrOfArgs = funArity ty
370
+ loc = maybe " " (\ l -> showPpr l ++ " : " ) $ realSrcLoc $ GHC. getSrcLoc v
343
371
warnIf cond msg = traceIf cond (" \n " ++ loc++ " Warning: " ++ msg) return ()
344
372
qName <- Text. unpack <$> qualifiedNameString (GHC. varName v)
345
373
let primStr = " primitive " ++ qName ++ " "
@@ -360,19 +388,9 @@ checkPrimitive primMap v = do
360
388
361
389
unless (qName == " Clash.XException.errorX" || " GHC." `isPrefixOf` qName) $ do
362
390
warnIf (not (isOpaque inline))
363
- #if MIN_VERSION_ghc(9,4,0)
364
- (primStr ++ " isn't marked OPAQUE."
365
- #else
366
- (primStr ++ " isn't marked NOINLINE."
367
- #endif
391
+ (primStr ++ " isn't marked " ++ opaqueString ++ " ."
368
392
++ " \n This might make Clash ignore this primitive." )
369
- #if MIN_VERSION_ghc(9,2,0)
370
- warnIf (GHC. isDeadEndAppSig strictness nrOfArgs)
371
- #elif MIN_VERSION_ghc(9,0,0)
372
- warnIf (GHC. appIsDeadEnd strictness nrOfArgs)
373
- #else
374
- warnIf (GHC. appIsBottom strictness nrOfArgs)
375
- #endif
393
+ warnIf (appIsDeadEnd strictness nrOfArgs)
376
394
(" The Haskell implementation of " ++ primStr
377
395
++ " produces a result that always results in an error.\n "
378
396
++ " This can lead to compile failures because GHC can replace entire "
0 commit comments