[commit: ghc] wip/T15449, wip/T16188, wip/llvm-configure-opts: Replace a few uses of snocView with last/lastMaybe. (9170daa)
git at git.haskell.org
git at git.haskell.org
Sun Feb 10 21:31:15 UTC 2019
Repository : ssh://git@git.haskell.org/ghc
On branches: wip/T15449,wip/T16188,wip/llvm-configure-opts
Link : http://ghc.haskell.org/trac/ghc/changeset/9170daa859ca5845b95acc88d10c127fb55d66fa/ghc
>---------------------------------------------------------------
commit 9170daa859ca5845b95acc88d10c127fb55d66fa
Author: klebinger.andreas at gmx.at <klebinger.andreas at gmx.at>
Date: Mon Jan 21 17:55:22 2019 +0100
Replace a few uses of snocView with last/lastMaybe.
These never used the first part of the result from snocView.
Hence replacing them with last[Maybe] is both clearer and
gives better performance.
>---------------------------------------------------------------
9170daa859ca5845b95acc88d10c127fb55d66fa
compiler/typecheck/TcDerivUtils.hs | 2 +-
compiler/utils/Outputable.hs | 4 ++--
compiler/utils/Util.hs | 11 ++++++++++-
3 files changed, 13 insertions(+), 4 deletions(-)
diff --git a/compiler/typecheck/TcDerivUtils.hs b/compiler/typecheck/TcDerivUtils.hs
index 5f48e5f..32a7aca 100644
--- a/compiler/typecheck/TcDerivUtils.hs
+++ b/compiler/typecheck/TcDerivUtils.hs
@@ -801,7 +801,7 @@ cond_functorOK allowFunctions allowExQuantifiedLastTyVar _ _ rep_tc
= allValid (map check_con data_cons)
where
tc_tvs = tyConTyVars rep_tc
- Just (_, last_tv) = snocView tc_tvs
+ last_tv = last tc_tvs
bad_stupid_theta = filter is_bad (tyConStupidTheta rep_tc)
is_bad pred = last_tv `elemVarSet` exactTyCoVarsOfType pred
-- See Note [Check that the type variable is truly universal]
diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs
index bb3b9d3..b3d77aa 100644
--- a/compiler/utils/Outputable.hs
+++ b/compiler/utils/Outputable.hs
@@ -609,8 +609,8 @@ quotes d =
else SDoc $ \sty ->
let pp_d = runSDoc d sty
str = show pp_d
- in case (str, snocView str) of
- (_, Just (_, '\'')) -> pp_d
+ in case (str, lastMaybe str) of
+ (_, Just '\'') -> pp_d
('\'' : _, _) -> pp_d
_other -> Pretty.quotes pp_d
diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs
index 0c7bb4a..876cd1e 100644
--- a/compiler/utils/Util.hs
+++ b/compiler/utils/Util.hs
@@ -28,7 +28,7 @@ module Util (
mapAndUnzip, mapAndUnzip3, mapAccumL2,
nOfThem, filterOut, partitionWith,
- dropWhileEndLE, spanEnd, last2,
+ dropWhileEndLE, spanEnd, last2, lastMaybe,
foldl1', foldl2, count, countWhile, all2,
@@ -779,6 +779,15 @@ last2 = foldl' (\(_,x2) x -> (x2,x)) (partialError,partialError)
where
partialError = panic "last2 - list length less than two"
+lastMaybe :: [a] -> Maybe a
+lastMaybe [] = Nothing
+lastMaybe xs = Just $ last xs
+
+-- | If there is a good chance that you will only look at the last
+-- element prefer seperate calls to @last@ + @init at .
+-- @last@ does not allocate while traversing the list, while this
+-- will. But if you are guaranteed to use both this will
+-- usually be more efficient.
snocView :: [a] -> Maybe ([a],a)
-- Split off the last element
snocView [] = Nothing
More information about the ghc-commits
mailing list