[Git][ghc/ghc][master] Add type signatures in where-clause of Data.List.permutations

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Oct 14 11:46:37 UTC 2022



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
aec5a443 by Bodigrim at 2022-10-14T07:46:21-04:00
Add type signatures in where-clause of Data.List.permutations

The type of interleave' is very much revealing, otherwise it's extremely tough to decipher.

- - - - -


1 changed file:

- libraries/base/Data/OldList.hs


Changes:

=====================================
libraries/base/Data/OldList.hs
=====================================
@@ -1249,6 +1249,7 @@ nonEmptySubsequences (x:xs)  =  [x] : foldr f [] (nonEmptySubsequences xs)
 -- The 'permutations' function is maximally lazy:
 -- for each @n@, the value of @'permutations' xs@ starts with those permutations
 -- that permute @'take' n xs@ and keep @'drop' n xs at .
+--
 -- This function is productive on infinite inputs:
 --
 -- >>> take 6 $ map (take 3) $ permutations ['a'..]
@@ -1259,21 +1260,25 @@ nonEmptySubsequences (x:xs)  =  [x] : foldr f [] (nonEmptySubsequences xs)
 --
 -- > map (take n) (take (product [1..n]) (permutations ([1..n] ++ undefined))) == permutations [1..n]
 --
-permutations            :: [a] -> [[a]]
+permutations :: [a] -> [[a]]
 -- See https://stackoverflow.com/questions/24484348/what-does-this-list-permutations-implementation-in-haskell-exactly-do/24564307#24564307
 -- for the analysis of this rather cryptic implementation.
 -- Related discussions:
 -- * https://mail.haskell.org/pipermail/haskell-cafe/2021-December/134920.html
 -- * https://mail.haskell.org/pipermail/libraries/2007-December/008788.html
-permutations xs0        =  xs0 : perms xs0 []
+permutations xs0 = xs0 : perms xs0 []
   where
+    perms :: forall a. [a] -> [a] -> [[a]]
     perms []     _  = []
     perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations is)
-      where interleave    xs     r = let (_,zs) = interleave' id xs r in zs
-            interleave' _ []     r = (ts, r)
-            interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:)) ys r
-                                     in  (y:us, f (t:y:us) : zs)
-
+      where
+        interleave :: [a] -> [[a]] -> [[a]]
+        interleave xs r = let (_,zs) = interleave' id xs r in zs
+
+        interleave' :: ([a] -> b) -> [a] -> [b] -> ([a], [b])
+        interleave' _ []     r = (ts, r)
+        interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:)) ys r
+                                 in  (y:us, f (t:y:us) : zs)
 
 ------------------------------------------------------------------------------
 -- Quick Sort algorithm taken from HBC's QSort library.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aec5a443bc45ca99cfeedc1777edb0aceca142cf

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aec5a443bc45ca99cfeedc1777edb0aceca142cf
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/20221014/027b886e/attachment-0001.html>


More information about the ghc-commits mailing list