Skip to content

Commit 5eca4c4

Browse files
authored
Merge pull request #71 from grin-compiler/32-trf-case-elims-2
Extended syntax: case eliminating transformations
2 parents 5dc6980 + ec365a2 commit 5eca4c4

File tree

5 files changed

+125
-0
lines changed

5 files changed

+125
-0
lines changed

grin/grin.cabal

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -146,6 +146,8 @@ library
146146
Transformations.ExtendedSyntax.GenerateEval
147147
Transformations.ExtendedSyntax.MangleNames
148148
Transformations.ExtendedSyntax.StaticSingleAssignment
149+
Transformations.ExtendedSyntax.Optimising.EvaluatedCaseElimination
150+
Transformations.ExtendedSyntax.Optimising.TrivialCaseElimination
149151

150152
Transformations.BindNormalisation
151153
Transformations.CountVariableUse
@@ -297,6 +299,8 @@ test-suite grin-test
297299
Transformations.ExtendedSyntax.ConversionSpec
298300
Transformations.ExtendedSyntax.MangleNamesSpec
299301
Transformations.ExtendedSyntax.StaticSingleAssignmentSpec
302+
Transformations.ExtendedSyntax.Optimising.EvaluatedCaseEliminationSpec
303+
Transformations.ExtendedSyntax.Optimising.TrivialCaseEliminationSpec
300304

301305
Transformations.Simplifying.RegisterIntroductionSpec
302306
Transformations.Simplifying.CaseSimplificationSpec
Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
{-# LANGUAGE LambdaCase, TupleSections #-}
2+
module Transformations.ExtendedSyntax.Optimising.EvaluatedCaseElimination where
3+
4+
import Data.Functor.Foldable as Foldable
5+
import Grin.ExtendedSyntax.Grin
6+
7+
evaluatedCaseElimination :: Exp -> Exp
8+
evaluatedCaseElimination = ana builder where
9+
builder :: Exp -> ExpF Exp
10+
builder = \case
11+
ECase scrut alts | all (altBodyEQ $ SReturn (Var scrut)) alts -> SReturnF (Var scrut)
12+
exp -> project exp
13+
14+
altBodyEQ :: Exp -> Alt -> Bool
15+
altBodyEQ exp (Alt _cpat _altName body) = exp == body
16+
Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
{-# LANGUAGE LambdaCase, TupleSections #-}
2+
module Transformations.ExtendedSyntax.Optimising.TrivialCaseElimination where
3+
4+
import Data.Functor.Foldable as Foldable
5+
import Grin.ExtendedSyntax.Grin
6+
import Transformations.ExtendedSyntax.Util
7+
8+
trivialCaseElimination :: Exp -> Exp
9+
trivialCaseElimination = ana builder where
10+
builder :: Exp -> ExpF Exp
11+
builder = \case
12+
ECase scrut [Alt DefaultPat altName body] -> SBlockF $ EBind (SReturn (Var scrut)) (VarPat altName) body
13+
ECase scrut [Alt cpat altName body] -> SBlockF $ EBind (SReturn (Var scrut)) (cPatToAsPat altName cpat) body
14+
exp -> project exp
Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
{-# LANGUAGE OverloadedStrings, QuasiQuotes, ViewPatterns #-}
2+
module Transformations.ExtendedSyntax.Optimising.EvaluatedCaseEliminationSpec where
3+
4+
import Transformations.ExtendedSyntax.Optimising.EvaluatedCaseElimination
5+
6+
import Test.Hspec
7+
import Grin.ExtendedSyntax.TH
8+
import Test.ExtendedSyntax.New.Test hiding (newVar)
9+
import Test.ExtendedSyntax.Assertions
10+
11+
12+
runTests :: IO ()
13+
runTests = hspec spec
14+
15+
spec :: Spec
16+
spec = do
17+
testExprContextE $ \ctx -> do
18+
it "Figure 4.22" $ do
19+
let before = [expr|
20+
case v of
21+
(CLeft l) @ alt1 -> pure v
22+
(CRight r) @ alt2 -> pure v
23+
|]
24+
let after = [expr|
25+
pure v
26+
|]
27+
evaluatedCaseElimination (ctx before) `sameAs` (ctx after)
28+
29+
it "default case" $ do
30+
let before = [expr|
31+
case v of
32+
(CLeft l) @ alt1 -> pure v
33+
#default @ alt2 -> pure v
34+
|]
35+
let after = [expr|
36+
pure v
37+
|]
38+
evaluatedCaseElimination (ctx before) `sameAs` (ctx after)
Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
{-# LANGUAGE OverloadedStrings, QuasiQuotes, ViewPatterns #-}
2+
module Transformations.ExtendedSyntax.Optimising.TrivialCaseEliminationSpec where
3+
4+
import Transformations.ExtendedSyntax.Optimising.TrivialCaseElimination
5+
6+
import Test.Hspec
7+
import Grin.ExtendedSyntax.TH
8+
import Test.ExtendedSyntax.New.Test hiding (newVar)
9+
import Test.ExtendedSyntax.Assertions
10+
11+
12+
runTests :: IO ()
13+
runTests = hspec spec
14+
15+
spec :: Spec
16+
spec = do
17+
testExprContextE $ \ctx -> do
18+
it "Figure 4.24" $ do
19+
let before = [expr|
20+
case v of
21+
(Ffun a1 a2 a3) @ alt1 -> fun a1 a2 a3
22+
|]
23+
let after = [expr|
24+
do
25+
(Ffun a1 a2 a3) @ alt1 <- pure v
26+
fun a1 a2 a3
27+
|]
28+
trivialCaseElimination (ctx before) `sameAs` (ctx after)
29+
30+
it "bypass" $ do
31+
let before = [expr|
32+
case v of
33+
(Ffun1 a1 a2 a3) @ alt1 -> fun1 a1 a2 a3
34+
#default @ alt2 -> pure 2
35+
|]
36+
let after = [expr|
37+
case v of
38+
(Ffun1 a1 a2 a3) @ alt1 -> fun1 a1 a2 a3
39+
#default @ alt2 -> pure 2
40+
|]
41+
trivialCaseElimination (ctx before) `sameAs` (ctx after)
42+
43+
it "default alternative" $ do
44+
let before = [expr|
45+
case v of
46+
#default @ alt1 -> pure 2
47+
|]
48+
let after = [expr|
49+
do
50+
alt1 <- pure v
51+
pure 2
52+
|]
53+
trivialCaseElimination (ctx before) `sameAs` (ctx after)

0 commit comments

Comments
 (0)