Skip to content

Commit b79af65

Browse files
committed
WIP: clash-ghc: Fixup files for formatting compatibility
1 parent 287e761 commit b79af65

File tree

5 files changed

+96
-65
lines changed

5 files changed

+96
-65
lines changed

clash-ghc/src-ghc/Clash/GHC/ClashFlags.hs

+9-5
Original file line numberDiff line numberDiff line change
@@ -43,14 +43,18 @@ parseClashFlags :: IORef ClashOpts -> [Located String]
4343
-> IO ([Located String],[Warn])
4444
parseClashFlags r = parseClashFlagsFull (flagsClash r)
4545

46-
parseClashFlagsFull :: [Flag IO] -> [Located String]
47-
-> IO ([Located String],[Warn])
48-
parseClashFlagsFull flagsAvialable args = do
49-
(leftovers,errs,warns) <- processArgs flagsAvialable args
46+
processGhcArgs :: [Flag IO] -> [Located String] -> IO ([Located String], [Err], [Warn])
5047
#if MIN_VERSION_ghc(9,4,0)
51-
parseResponseFile
48+
processGhcArgs flagsAvailable args = processArgs flagsAvailable args parseResponseFile
49+
#else
50+
processGhcArgs flagsAvailable args = processArgs flagsAvailable args
5251
#endif
5352

53+
parseClashFlagsFull :: [Flag IO] -> [Located String]
54+
-> IO ([Located String],[Warn])
55+
parseClashFlagsFull flagsAvailable args = do
56+
(leftovers,errs,warns) <- processGhcArgs flagsAvailable args
57+
5458
unless (null errs) $ throwGhcExceptionIO $
5559
errorsToGhcException . map (("on the commandline", ) . unLoc . errMsg)
5660
$ errs

clash-ghc/src-ghc/Clash/GHC/Evaluator.hs

+20-15
Original file line numberDiff line numberDiff line change
@@ -367,6 +367,23 @@ instantiate tcm pVal@(PrimVal (PrimInfo{primType}) tys es) ty m
367367

368368
instantiate _ p _ _ = error $ "Evaluator.instantiate: Not a tylambda: " ++ show p
369369

370+
getByteArrayIP :: Integer -> BA.ByteArray#
371+
#if MIN_VERSION_base(4,15,0)
372+
getByteArrayIP !(IP ba0) = ba0
373+
#else
374+
getByteArrayIP !(Jp# !(BN# ba0)) = ba0
375+
#endif
376+
getByteArrayIP _ = error "getByteArrayIP: not IP"
377+
378+
getByteArrayIN :: Integer -> BA.ByteArray#
379+
#if MIN_VERSION_base(4,15,0)
380+
getByteArrayIN !(IN ba0) = ba0
381+
#else
382+
getByteArrayIN !(Jn# !(BN# ba0)) = ba0
383+
#endif
384+
getByteArrayIN _ = error "getByteArrayIN: not IN"
385+
386+
370387
-- | Evaluate a case-expression
371388
scrutinise :: Value -> Type -> [Alt] -> Machine -> Machine
372389
scrutinise v _altTy [] m = setTerm (valToTerm v) m
@@ -390,19 +407,11 @@ scrutinise (Lit l) _altTy alts m = case alts of
390407
1 | l1 >= ((-2)^(63::Int)) && l1 < 2^(63::Int) ->
391408
Just (IntLiteral l1)
392409
2 | l1 >= (2^(63::Int)) ->
393-
#if MIN_VERSION_base(4,15,0)
394-
let !(IP ba0) = l1
395-
#else
396-
let !(Jp# !(BN# ba0)) = l1
397-
#endif
410+
let ba0 = getByteArrayIP l1
398411
ba1 = BA.ByteArray ba0
399412
in Just (ByteArrayLiteral ba1)
400413
3 | l1 < ((-2)^(63::Int)) ->
401-
#if MIN_VERSION_base(4,15,0)
402-
let !(IN ba0) = l1
403-
#else
404-
let !(Jn# !(BN# ba0)) = l1
405-
#endif
414+
let ba0 = getByteArrayIN l1
406415
ba1 = BA.ByteArray ba0
407416
in Just (ByteArrayLiteral ba1)
408417
_ -> Nothing
@@ -415,11 +424,7 @@ scrutinise (Lit l) _altTy alts m = case alts of
415424
1 | l1 >= 0 && l1 < 2^(64::Int) ->
416425
Just (WordLiteral l1)
417426
2 | l1 >= (2^(64::Int)) ->
418-
#if MIN_VERSION_base(4,15,0)
419-
let !(IP ba0) = l1
420-
#else
421-
let !(Jp# !(BN# ba0)) = l1
422-
#endif
427+
let ba0 = getByteArrayIP l1
423428
ba1 = BA.ByteArray ba0
424429
in Just (ByteArrayLiteral ba1)
425430
_ -> Nothing

clash-ghc/src-ghc/Clash/GHC/Evaluator/Primitive.hs

+2
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{- FOURMOLU_DISABLE -}
2+
13
{-|
24
Copyright : (C) 2013-2016, University of Twente,
35
2016-2017, Myrtle Software Ltd,

clash-ghc/src-ghc/Clash/GHC/GHC2Core.hs

+2
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{- FOURMOLU_DISABLE -}
2+
13
{-|
24
Copyright : (C) 2013-2016, University of Twente,
35
2016-2017, Myrtle Software Ltd,

clash-ghc/src-ghc/Clash/GHC/GenerateBindings.hs

+63-45
Original file line numberDiff line numberDiff line change
@@ -107,6 +107,19 @@ indexMaybe [] _ = Nothing
107107
indexMaybe (x:_) 0 = Just x
108108
indexMaybe (_:xs) n = indexMaybe xs (n-1)
109109

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+
110123
generateBindings
111124
:: ClashOpts
112125
-> GHC.Ghc ()
@@ -155,11 +168,7 @@ generateBindings opts startAction primDirs importDirs dbs hdl modName dflagsM =
155168
-- selectors, no need to check free vars.
156169
clsMap =
157170
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
163172
(mkClassSelector inScope0 allTcCache (varType v) i) False))
164173
clsVMap
165174
allBindings = bindingsMap `unionVarEnv` clsMap
@@ -210,11 +219,7 @@ setNoInlineTopEntities bm tes =
210219

211220
go b@Binding{bindingId}
212221
| 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 }
218223
| otherwise = b
219224

220225
-- TODO This function should be changed to provide the information that
@@ -274,6 +279,48 @@ mkBindings primMap bindings clsOps unlocatable = do
274279

275280
return (mkVarEnv (concat bindingsList), mkVarEnv clsOpList)
276281

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+
277324
{-
278325
NOTE [bindings in recursive groups]
279326
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -316,30 +363,11 @@ checkPrimitive primMap v = do
316363
let
317364
info = GHC.idInfo v
318365
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
324367
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
343371
warnIf cond msg = traceIf cond ("\n"++loc++"Warning: "++msg) return ()
344372
qName <- Text.unpack <$> qualifiedNameString (GHC.varName v)
345373
let primStr = "primitive " ++ qName ++ " "
@@ -360,19 +388,9 @@ checkPrimitive primMap v = do
360388

361389
unless (qName == "Clash.XException.errorX" || "GHC." `isPrefixOf` qName) $ do
362390
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 ++ "."
368392
++ "\nThis 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)
376394
("The Haskell implementation of " ++ primStr
377395
++ "produces a result that always results in an error.\n"
378396
++ "This can lead to compile failures because GHC can replace entire "

0 commit comments

Comments
 (0)