[commit: ghc] wip/ghc-8.0-det: Refactor match to not use Unique order (6fc97cd)
git at git.haskell.org
git at git.haskell.org
Mon Jul 25 14:59:34 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ghc-8.0-det
Link : http://ghc.haskell.org/trac/ghc/changeset/6fc97cd5f055d97c49646ee8c89762bd05e46b15/ghc
>---------------------------------------------------------------
commit 6fc97cd5f055d97c49646ee8c89762bd05e46b15
Author: Bartosz Nitka <niteria at gmail.com>
Date: Wed Jun 29 03:27:49 2016 -0700
Refactor match to not use Unique order
Unique order can introduce nondeterminism.
As a step towards removing the Ord Unique instance
I've refactored the code to use deterministic sets instead.
Test Plan: ./validate
Reviewers: simonmar, austin, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2369
GHC Trac Issues: #4012
(cherry picked from commit 9a645a1687aca21f965206f1d8c8bb23dd6410e5)
>---------------------------------------------------------------
6fc97cd5f055d97c49646ee8c89762bd05e46b15
compiler/deSugar/Match.hs | 32 +++++++++++++++++++++++---------
1 file changed, 23 insertions(+), 9 deletions(-)
diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs
index fc70cc6..ecbed46 100644
--- a/compiler/deSugar/Match.hs
+++ b/compiler/deSugar/Match.hs
@@ -46,6 +46,8 @@ import Util
import Name
import Outputable
import BasicTypes ( isGenerated )
+import Unique
+import UniqDFM
import Control.Monad( when, unless )
import qualified Data.Map as Map
@@ -196,9 +198,9 @@ match vars@(v:_) ty eqns -- Eqns *can* be empty
match_group [] = panic "match_group"
match_group eqns@((group,_) : _)
= case group of
- PgCon {} -> matchConFamily vars ty (subGroup [(c,e) | (PgCon c, e) <- eqns])
+ PgCon {} -> matchConFamily vars ty (subGroupUniq [(c,e) | (PgCon c, e) <- eqns])
PgSyn {} -> matchPatSyn vars ty (dropGroup eqns)
- PgLit {} -> matchLiterals vars ty (subGroup [(l,e) | (PgLit l, e) <- eqns])
+ PgLit {} -> matchLiterals vars ty (subGroupOrd [(l,e) | (PgLit l, e) <- eqns])
PgAny -> matchVariables vars ty (dropGroup eqns)
PgN {} -> matchNPats vars ty (dropGroup eqns)
PgNpK {} -> matchNPlusKPats vars ty (dropGroup eqns)
@@ -809,22 +811,34 @@ groupEquations dflags eqns
same_gp :: (PatGroup,EquationInfo) -> (PatGroup,EquationInfo) -> Bool
(pg1,_) `same_gp` (pg2,_) = pg1 `sameGroup` pg2
-subGroup :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]]
+subGroup :: (m -> [[EquationInfo]]) -- Map.elems
+ -> m -- Map.empty
+ -> (a -> m -> Maybe [EquationInfo]) -- Map.lookup
+ -> (a -> [EquationInfo] -> m -> m) -- Map.insert
+ -> [(a, EquationInfo)] -> [[EquationInfo]]
-- Input is a particular group. The result sub-groups the
-- equations by with particular constructor, literal etc they match.
-- Each sub-list in the result has the same PatGroup
-- See Note [Take care with pattern order]
-subGroup group
- = map reverse $ Map.elems $ foldl accumulate Map.empty group
+-- Parameterized by map operations to allow different implementations
+-- and constraints, eg. types without Ord instance.
+subGroup elems empty lookup insert group
+ = map reverse $ elems $ foldl accumulate empty group
where
accumulate pg_map (pg, eqn)
- = case Map.lookup pg pg_map of
- Just eqns -> Map.insert pg (eqn:eqns) pg_map
- Nothing -> Map.insert pg [eqn] pg_map
-
+ = case lookup pg pg_map of
+ Just eqns -> insert pg (eqn:eqns) pg_map
+ Nothing -> insert pg [eqn] pg_map
-- pg_map :: Map a [EquationInfo]
-- Equations seen so far in reverse order of appearance
+subGroupOrd :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]]
+subGroupOrd = subGroup Map.elems Map.empty Map.lookup Map.insert
+
+subGroupUniq :: Uniquable a => [(a, EquationInfo)] -> [[EquationInfo]]
+subGroupUniq =
+ subGroup eltsUDFM emptyUDFM (flip lookupUDFM) (\k v m -> addToUDFM m k v)
+
{- Note [Pattern synonym groups]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
If we see
More information about the ghc-commits
mailing list