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

Commits:

2 changed files:

Changes:

  • libraries/base/changelog.md
    ... ... @@ -8,6 +8,7 @@
    8 8
       * `GHC.Exts.IOPort#` and its related operations have been removed  ([CLC #213](https://github.com/haskell/core-libraries-committee/issues/213))
    
    9 9
       * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
    
    10 10
       * Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
    
    11
    +  * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
    
    11 12
     
    
    12 13
     ## 4.22.0.0 *TBA*
    
    13 14
       * Shipped with GHC 9.14.1
    

  • libraries/ghc-internal/src/GHC/Internal/List.hs
    ... ... @@ -854,11 +854,17 @@ minimum xs = foldl1' min xs
    854 854
     -- ==== __Laziness__
    
    855 855
     --
    
    856 856
     -- Note that 'iterate' is lazy, potentially leading to thunk build-up if
    
    857
    --- the consumer doesn't force each iterate. See 'iterate'' for a strict
    
    857
    +-- the consumer doesn't force each element. See 'iterate'' for a strict
    
    858 858
     -- variant of this function.
    
    859 859
     --
    
    860
    --- >>> take 1 $ iterate undefined 42
    
    861
    --- [42]
    
    860
    +-- >>> let xs = iterate (\x -> if x == 0 then undefined else x - 1) 2
    
    861
    +-- >>> xs
    
    862
    +-- [2,1,0,*** Exception: Prelude.undefined
    
    863
    +-- >>> length (take 10 xs)
    
    864
    +-- 10
    
    865
    +--
    
    866
    +-- In @xs@ every element following @0@ is bottom, but the list itself is
    
    867
    +-- infinitely long because it is generated without forcing its elements.
    
    862 868
     --
    
    863 869
     -- ==== __Examples__
    
    864 870
     --
    
    ... ... @@ -889,24 +895,26 @@ iterateFB c f x0 = go x0
    889 895
     
    
    890 896
     -- | 'iterate'' is the strict version of 'iterate'.
    
    891 897
     --
    
    892
    --- It forces the result of each application of the function to weak head normal
    
    893
    --- form (WHNF)
    
    894
    --- before proceeding.
    
    898
    +-- It forces each element to weak head normal form (WHNF) before proceeding.
    
    895 899
     --
    
    896
    --- >>> take 1 $ iterate' undefined 42
    
    900
    +-- ==== __Laziness__
    
    901
    +--
    
    902
    +-- >>> let xs = iterate' (\x -> if x == 0 then undefined else x - 1) 2
    
    903
    +-- >>> xs
    
    904
    +-- [2,1,0*** Exception: Prelude.undefined
    
    905
    +-- >>> length (take 10 xs)
    
    897 906
     -- *** Exception: Prelude.undefined
    
    907
    +--
    
    908
    +-- The list @xs@ has 3 elements followed by a tail that is bottom.
    
    909
    +--
    
    898 910
     {-# NOINLINE [1] iterate' #-}
    
    899 911
     iterate' :: (a -> a) -> a -> [a]
    
    900
    -iterate' f x =
    
    901
    -    let x' = f x
    
    902
    -    in x' `seq` (x : iterate' f x')
    
    912
    +iterate' f !x = x : iterate' f (f x)
    
    903 913
     
    
    904 914
     {-# INLINE [0] iterate'FB #-} -- See Note [Inline FB functions]
    
    905 915
     iterate'FB :: (a -> b -> b) -> (a -> a) -> a -> b
    
    906 916
     iterate'FB c f x0 = go x0
    
    907
    -  where go x =
    
    908
    -            let x' = f x
    
    909
    -            in x' `seq` (x `c` go x')
    
    917
    +  where go !x = x `c` go (f x)
    
    910 918
     
    
    911 919
     {-# RULES
    
    912 920
     "iterate'"    [~1] forall f x.   iterate' f x = build (\c _n -> iterate'FB c f x)