Skip to content

Commit f946617

Browse files
authored
Fix eta-expansion in evaluator (#2782)
For some eta-reduced 'e', we used to bogusly eta-expand to: \x.(\y. e y) x We now correctly expand to: \x.\y.(e x) y Fixes #2781
1 parent b14ff0e commit f946617

File tree

4 files changed

+52
-12
lines changed

4 files changed

+52
-12
lines changed
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
FIXED: Bug in the compile-time evaluator [#2781](https://github.com/clash-lang/clash-compiler/issues/2781)

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

Lines changed: 15 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -268,19 +268,22 @@ ghcStep m = case mTerm m of
268268
-- for each one around the given term.
269269
--
270270
newBinder :: [Either TyVar Type] -> Term -> Step
271-
newBinder tys x m tcm =
272-
let (s', iss', x') = mkAbstr (mSupply m, mScopeNames m, x) tys
273-
m' = m { mSupply = s', mScopeNames = iss', mTerm = x' }
274-
in ghcStep m' tcm
271+
newBinder tys e m tcm =
272+
let ((supply1,_), e1) = etaExpand (mSupply m, mScopeNames m) tys
273+
m1 = m { mSupply = supply1, mTerm = e1 }
274+
in ghcStep m1 tcm
275275
where
276-
mkAbstr = foldr go
277-
where
278-
go (Left tv) (s', iss', e') =
279-
(s', iss', TyLam tv (TyApp e' (VarTy tv)))
280-
281-
go (Right ty) (s', iss', e') =
282-
let ((s'', _), n) = mkUniqSystemId (s', iss') ("x", ty)
283-
in (s'', iss' ,Lam n (App e' (Var n)))
276+
etaExpand env args =
277+
let (env1,args1) = mapAccumL go env args
278+
in (env1,mkAbstraction (foldl' go2 e args1) args1)
279+
280+
go env (Left tv) = (env, Right tv)
281+
go env (Right ty) =
282+
let (env1, n) = mkUniqSystemId env ("x", ty)
283+
in (env1, Left n)
284+
285+
go2 u (Left i) = App u (Var i)
286+
go2 u (Right tv) = TyApp u (VarTy tv)
284287

285288
newLetBinding
286289
:: TyConMap

tests/Main.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -632,6 +632,7 @@ runClashTest = defaultMain $ clashTestRoot
632632
, outputTest "T2542" def{hdlTargets=[VHDL]}
633633
, runTest "T2593" def{hdlSim=[]}
634634
, runTest "T2623CaseConFVs" def{hdlLoad=[],hdlSim=[],hdlTargets=[VHDL]}
635+
, runTest "T2781" def{hdlLoad=[],hdlSim=[],hdlTargets=[VHDL]}
635636
] <>
636637
if compiledWith == Cabal then
637638
-- This tests fails without environment files present, which are only

tests/shouldwork/Issues/T2781.hs

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,35 @@
1+
module T2781
2+
( fullMeshSwCcTest
3+
) where
4+
5+
import Clash.Explicit.Prelude
6+
import Clash.Cores.Xilinx.Ila (IlaConfig(..), Depth(..), ila, ilaConfig)
7+
8+
fullMeshHwTestDummy ::
9+
Clock System ->
10+
( Signal System Bool
11+
, Vec 1 (Signal System Bool)
12+
)
13+
fullMeshHwTestDummy sysClk =
14+
fincFdecIla `hwSeqX`
15+
( pure False
16+
, repeat (pure True)
17+
)
18+
where
19+
fincFdecIla :: Signal System ()
20+
fincFdecIla = ila
21+
(ilaConfig ("trigger_0" :> Nil))
22+
sysClk
23+
(pure True :: Signal System Bool)
24+
25+
-- | Top entity for this test. See module documentation for more information.
26+
fullMeshSwCcTest ::
27+
Clock System ->
28+
(Signal System Bool
29+
)
30+
fullMeshSwCcTest sysClk = spiDone
31+
where
32+
(spiDone
33+
, ugnsStable
34+
) = fullMeshHwTestDummy sysClk
35+
{-# ANN fullMeshSwCcTest (defSyn "fullMeshSwCcTest") #-}

0 commit comments

Comments
 (0)