[Git][ghc/ghc][wip/three-way-merge-sort] WIP
Jade (@Jade)
gitlab at gitlab.haskell.org
Mon Apr 1 12:43:43 UTC 2024
Jade pushed to branch wip/three-way-merge-sort at Glasgow Haskell Compiler / GHC
Commits:
6da36b2e by Jade at 2024-04-01T14:48:11+02:00
WIP
- - - - -
1 changed file:
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
=====================================
@@ -1645,15 +1645,8 @@ Further improved using a four-way merge, with an additional performance increase
https://gitlab.haskell.org/ghc/ghc/issues/24280
-}
-{-# INLINEABLE sort #-}
-sort = actualSort (>)
-
-{-# INLINEABLE sortBy #-}
-sortBy cmp = actualSort (\x y -> cmp x y == GT)
-
-{-# INLINE actualSort #-}
-actualSort :: (a -> a -> Bool) -> [a] -> [a]
-actualSort gt ns
+sort = sortBy compare
+sortBy cmp ns
| [] <- ns = []
| [a] <- ns = [a]
| [a,b] <- ns = merge [a] [b]
@@ -1661,6 +1654,8 @@ actualSort gt ns
| [a,b,c,d] <- ns = merge4 [a] [b] [c] [d]
| otherwise = merge_all (sequences ns)
where
+ x `gt` y = x `cmp` y == GT
+
sequences (a:b:xs)
| a `gt` b = descending b [a] xs
| otherwise = ascending b (a:) xs
@@ -1668,7 +1663,7 @@ actualSort gt ns
descending a as (b:bs)
| a `gt` b = descending b (a:as) bs
- descending a as bs = (a:as) : sequences bs
+ descending a as bs = (a:as): sequences bs
ascending a as (b:bs)
| not (a `gt` b) = ascending b (\ys -> as (a:ys)) bs
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6da36b2e1355abaec6fae1e1d6bbb470e0e43397
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6da36b2e1355abaec6fae1e1d6bbb470e0e43397
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240401/11f4acad/attachment-0001.html>
More information about the ghc-commits
mailing list