Skip to content

Commit 833cec8

Browse files
committed
Fix: eta reduction
1 parent bef2ba6 commit 833cec8

File tree

6 files changed

+46
-8
lines changed

6 files changed

+46
-8
lines changed

.hspec-failures

+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
FailureReport {failureReportSeed = 1246204243, failureReportMaxSuccess = 100, failureReportMaxSize = 100, failureReportMaxDiscardRatio = 10, failureReportPaths = []}

lib/Language/PureScript/Backend/IR/Optimizer.hs

+2-3
Original file line numberDiff line numberDiff line change
@@ -279,13 +279,12 @@ etaReduce ∷ RewriteRule Ann
279279
etaReduce =
280280
pure . \case
281281
Abs _ (ParamNamed _ param) (App _ m (Ref _ (Local param') 0))
282-
| param == param'
282+
| param == param' && countFreeRef (Local param) m == 0
283283
Rewritten Recurse m
284284
_ NoChange
285285

286286
betaReduceUnusedParams RewriteRule Ann
287-
betaReduceUnusedParams =
288-
pure . \case
287+
betaReduceUnusedParams = pure . \case
289288
App _ (Abs _ (ParamUnused _) body) _arg
290289
Rewritten Recurse body
291290
_ NoChange
+14-1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,9 @@
1-
module Golden.Inline.Test where
1+
module Golden.Inline.Test
2+
( main
3+
, Mu
4+
, runMu
5+
, iMu
6+
) where
27

38
main :: Int
49
main =
@@ -7,3 +12,11 @@ main =
712
in let y :: forall b. b -> Int
813
y _ = 2
914
in x y
15+
16+
newtype Mu a = MkMu (Mu a -> a)
17+
18+
runMu :: forall a. Mu a -> a
19+
runMu mu@(MkMu f) = f mu
20+
21+
iMu :: Mu Int
22+
iMu = MkMu runMu
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
{"builtWith":"0.15.15","comments":[],"decls":[{"annotation":{"meta":null,"sourceSpan":{"end":[3,12],"start":[3,1]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[9,13],"start":[5,3]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[5,30],"start":[5,7]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[5,30],"start":[5,7]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[6,14],"start":[6,13]}},"type":"Literal","value":{"literalType":"IntLiteral","value":1}},"type":"Abs"},"identifier":"x"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[9,13],"start":[7,6]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[7,34],"start":[7,11]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[7,34],"start":[7,11]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[8,18],"start":[8,17]}},"type":"Literal","value":{"literalType":"IntLiteral","value":2}},"type":"Abs"},"identifier":"y"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[9,11],"start":[9,10]}},"type":"Var","value":{"identifier":"x","sourcePos":[5,7]}},"annotation":{"meta":null,"sourceSpan":{"end":[9,13],"start":[9,10]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[9,13],"start":[9,12]}},"type":"Var","value":{"identifier":"y","sourcePos":[7,11]}},"type":"App"},"type":"Let"},"type":"Let"},"identifier":"main"}],"exports":["main"],"foreign":[],"imports":[{"annotation":{"meta":null,"sourceSpan":{"end":[9,13],"start":[1,1]}},"moduleName":["Prim"]}],"moduleName":["Golden","Inline","Test"],"modulePath":"golden/Golden/Inline/Test.purs","reExports":{},"sourceSpan":{"end":[9,13],"start":[1,1]}}
1+
{"builtWith":"0.15.15","comments":[],"decls":[{"annotation":{"meta":null,"sourceSpan":{"end":[16,32],"start":[16,1]}},"bindType":"NonRec","expression":{"annotation":{"meta":{"metaType":"IsNewtype"},"sourceSpan":{"end":[16,32],"start":[16,1]}},"argument":"x","body":{"annotation":{"meta":null,"sourceSpan":{"end":[16,32],"start":[16,1]}},"type":"Var","value":{"identifier":"x","sourcePos":[0,0]}},"type":"Abs"},"identifier":"MkMu"},{"annotation":{"meta":null,"sourceSpan":{"end":[18,29],"start":[18,1]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[18,29],"start":[18,1]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[18,29],"start":[18,1]}},"caseAlternatives":[{"binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[19,18],"start":[19,7]}},"binder":{"annotation":{"meta":{"metaType":"IsNewtype"},"sourceSpan":{"end":[19,17],"start":[19,11]}},"binderType":"ConstructorBinder","binders":[{"annotation":{"meta":null,"sourceSpan":{"end":[19,17],"start":[19,16]}},"binderType":"VarBinder","identifier":"f"}],"constructorName":{"identifier":"MkMu","moduleName":["Golden","Inline","Test"]},"typeName":{"identifier":"Mu","moduleName":["Golden","Inline","Test"]}},"binderType":"NamedBinder","identifier":"mu"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[19,22],"start":[19,21]}},"type":"Var","value":{"identifier":"f","sourcePos":[19,16]}},"annotation":{"meta":null,"sourceSpan":{"end":[19,25],"start":[19,21]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[19,25],"start":[19,23]}},"type":"Var","value":{"identifier":"mu","sourcePos":[19,7]}},"type":"App"},"isGuarded":false}],"caseExpressions":[{"annotation":{"meta":null,"sourceSpan":{"end":[19,25],"start":[19,1]}},"type":"Var","value":{"identifier":"v","sourcePos":[0,0]}}],"type":"Case"},"type":"Abs"},"identifier":"runMu"},{"annotation":{"meta":null,"sourceSpan":{"end":[8,12],"start":[8,1]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[14,13],"start":[10,3]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[10,30],"start":[10,7]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[10,30],"start":[10,7]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[11,14],"start":[11,13]}},"type":"Literal","value":{"literalType":"IntLiteral","value":1}},"type":"Abs"},"identifier":"x"}],"expression":{"annotation":{"meta":null,"sourceSpan":{"end":[14,13],"start":[12,6]}},"binds":[{"annotation":{"meta":null,"sourceSpan":{"end":[12,34],"start":[12,11]}},"bindType":"NonRec","expression":{"annotation":{"meta":null,"sourceSpan":{"end":[12,34],"start":[12,11]}},"argument":"v","body":{"annotation":{"meta":null,"sourceSpan":{"end":[13,18],"start":[13,17]}},"type":"Literal","value":{"literalType":"IntLiteral","value":2}},"type":"Abs"},"identifier":"y"}],"expression":{"abstraction":{"annotation":{"meta":null,"sourceSpan":{"end":[14,11],"start":[14,10]}},"type":"Var","value":{"identifier":"x","sourcePos":[10,7]}},"annotation":{"meta":null,"sourceSpan":{"end":[14,13],"start":[14,10]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[14,13],"start":[14,12]}},"type":"Var","value":{"identifier":"y","sourcePos":[12,11]}},"type":"App"},"type":"Let"},"type":"Let"},"identifier":"main"},{"annotation":{"meta":null,"sourceSpan":{"end":[21,14],"start":[21,1]}},"bindType":"NonRec","expression":{"abstraction":{"annotation":{"meta":{"metaType":"IsNewtype"},"sourceSpan":{"end":[22,11],"start":[22,7]}},"type":"Var","value":{"identifier":"MkMu","moduleName":["Golden","Inline","Test"]}},"annotation":{"meta":null,"sourceSpan":{"end":[22,17],"start":[22,7]}},"argument":{"annotation":{"meta":null,"sourceSpan":{"end":[22,17],"start":[22,12]}},"type":"Var","value":{"identifier":"runMu","moduleName":["Golden","Inline","Test"]}},"type":"App"},"identifier":"iMu"}],"exports":["main","runMu","iMu"],"foreign":[],"imports":[{"annotation":{"meta":null,"sourceSpan":{"end":[22,17],"start":[1,1]}},"moduleName":["Golden","Inline","Test"]},{"annotation":{"meta":null,"sourceSpan":{"end":[22,17],"start":[1,1]}},"moduleName":["Prim"]}],"moduleName":["Golden","Inline","Test"],"modulePath":"golden/Golden/Inline/Test.purs","reExports":{},"sourceSpan":{"end":[22,17],"start":[1,1]}}
+21-2
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,23 @@
11
UberModule
2-
{ uberModuleBindings = [], uberModuleForeigns = [], uberModuleExports =
3-
[ ( Name "main", LiteralInt Nothing 1 ) ]
2+
{ uberModuleBindings =
3+
[ Standalone
4+
( QName
5+
{ qnameModuleName = ModuleName "Golden.Inline.Test", qnameName = Name "runMu"
6+
}, Abs Nothing
7+
( ParamNamed Nothing ( Name "v" ) )
8+
( App Nothing
9+
( Ref Nothing ( Local ( Name "v" ) ) 0 )
10+
( Ref Nothing ( Local ( Name "v" ) ) 0 )
11+
)
12+
)
13+
], uberModuleForeigns = [], uberModuleExports =
14+
[
15+
( Name "main", LiteralInt Nothing 1 ),
16+
( Name "runMu", Ref Nothing
17+
( Imported ( ModuleName "Golden.Inline.Test" ) ( Name "runMu" ) ) 0
18+
),
19+
( Name "iMu", Ref Nothing
20+
( Imported ( ModuleName "Golden.Inline.Test" ) ( Name "runMu" ) ) 0
21+
)
22+
]
423
}
Original file line numberDiff line numberDiff line change
@@ -1 +1,7 @@
1-
return { main = 1 }
1+
local M = {}
2+
M.Golden_Inline_Test_runMu = function(v) return v(v) end
3+
return {
4+
main = 1,
5+
runMu = M.Golden_Inline_Test_runMu,
6+
iMu = M.Golden_Inline_Test_runMu
7+
}

0 commit comments

Comments
 (0)