Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
0
Issues
0
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
0
Merge Requests
0
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Packages & Registries
Packages & Registries
Package Registry
Container Registry
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Alex D
GHC
Commits
e97df85e
Commit
e97df85e
authored
Nov 10, 2009
by
simonpj@microsoft.com
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Preserve strictness when floating coercions
See Note [Preserve strictness when floating coercions]
parent
6b539626
Changes
1
Hide whitespace changes
Inline
Side-by-side
Showing
1 changed file
with
31 additions
and
12 deletions
+31
-12
compiler/simplCore/Simplify.lhs
compiler/simplCore/Simplify.lhs
+31
-12
No files found.
compiler/simplCore/Simplify.lhs
View file @
e97df85e
...
...
@@ -18,6 +18,7 @@ import Id
import MkId ( mkImpossibleExpr, seqId )
import Var
import IdInfo
import Name ( mkSystemVarName )
import Coercion
import FamInstEnv ( topNormaliseType )
import DataCon ( DataCon, dataConWorkId, dataConRepStrictness )
...
...
@@ -337,7 +338,7 @@ simplLazyBind env top_lvl is_rec bndr bndr1 rhs rhs_se
-- Simplify the RHS
; (body_env1, body1) <- simplExprF body_env body mkRhsStop
-- ANF-ise a constructor or PAP rhs
; (body_env2, body2) <- prepareRhs body_env1 body1
; (body_env2, body2) <- prepareRhs body_env1 b
ndr1 b
ody1
; (env', rhs')
<- if not (doFloatFromRhs top_lvl is_rec False body2 body_env2)
...
...
@@ -383,7 +384,7 @@ completeNonRecX :: SimplEnv
-> SimplM SimplEnv
completeNonRecX env is_strict old_bndr new_bndr new_rhs
= do { (env1, rhs1) <- prepareRhs (zapFloats env) new_rhs
= do { (env1, rhs1) <- prepareRhs (zapFloats env) new_
bndr new_
rhs
; (env2, rhs2) <-
if doFloatFromRhs NotTopLevel NonRecursive is_strict rhs1 env1
then do { tick LetFloatFromLet
...
...
@@ -434,15 +435,19 @@ Here we want to make e1,e2 trivial and get
That's what the 'go' loop in prepareRhs does
\begin{code}
prepareRhs :: SimplEnv -> OutExpr -> SimplM (SimplEnv, OutExpr)
prepareRhs :: SimplEnv -> Out
Id -> Out
Expr -> SimplM (SimplEnv, OutExpr)
-- Adds new floats to the env iff that allows us to return a good RHS
prepareRhs env (Cast rhs co) -- Note [Float coercions]
prepareRhs env
id
(Cast rhs co) -- Note [Float coercions]
| (ty1, _ty2) <- coercionKind co -- Do *not* do this if rhs has an unlifted type
, not (isUnLiftedType ty1) -- see Note [Float coercions (unlifted)]
= do { (env', rhs') <- makeTrivial
env
rhs
= do { (env', rhs') <- makeTrivial
WithInfo env sanitised_info
rhs
; return (env', Cast rhs' co) }
where
sanitised_info = vanillaIdInfo `setNewStrictnessInfo` newStrictnessInfo info
`setNewDemandInfo` newDemandInfo info
info = idInfo id
prepareRhs env0 rhs0
prepareRhs env0
_
rhs0
= do { (_is_val, env1, rhs1) <- go 0 env0 rhs0
; return (env1, rhs1) }
where
...
...
@@ -492,6 +497,17 @@ and lead to further optimisation. Example:
go n = case x of { T m -> go (n-m) }
-- This case should optimise
Note [Preserve strictness when floating coercions]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
In the Note [Float coercions] transformation, keep the strictness info.
Eg
f = e `cast` co -- f has strictness SSL
When we transform to
f' = e -- f' also has strictness SSL
f = f' `cast` co -- f still has strictness SSL
Its not wrong to drop it on the floor, but better to keep it.
Note [Float coercions (unlifted)]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
BUT don't do [Float coercions] if 'e' has an unlifted type.
...
...
@@ -512,16 +528,19 @@ These strange casts can happen as a result of case-of-case
\begin{code}
makeTrivial :: SimplEnv -> OutExpr -> SimplM (SimplEnv, OutExpr)
-- Binds the expression to a variable, if it's not trivial, returning the variable
makeTrivial env expr
makeTrivial env expr = makeTrivialWithInfo env vanillaIdInfo expr
makeTrivialWithInfo :: SimplEnv -> IdInfo -> OutExpr -> SimplM (SimplEnv, OutExpr)
-- Propagate strictness and demand info to the new binder
-- Note [Preserve strictness when floating coercions]
makeTrivialWithInfo env info expr
| exprIsTrivial expr
= return (env, expr)
| otherwise -- See Note [Take care] below
= do { var <- newId (fsLit "a") (exprType expr)
= do { uniq <- getUniqueM
; let name = mkSystemVarName uniq (fsLit "a")
var = mkLocalIdWithInfo name (exprType expr) info
; env' <- completeNonRecX env False var var expr
-- pprTrace "makeTrivial" (vcat [ppr var <+> ppr (exprArity (substExpr env' (Var var)))
-- , ppr expr
-- , ppr (substExpr env' (Var var))
-- , ppr (idArity (fromJust (lookupInScope (seInScope env') var))) ]) $
; return (env', substExpr env' (Var var)) }
-- The substitution is needed becase we're constructing a new binding
-- a = rhs
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment