[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: [hadrian] Fix multiline synopsis rendering

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Jun 3 18:49:44 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
412ea34a by Andrey Mokhov at 2023-06-03T14:49:37-04:00
[hadrian] Fix multiline synopsis rendering

- - - - -
079586c7 by Bodigrim at 2023-06-03T14:49:39-04:00
Elaborate on performance properties of Data.List.++

- - - - -


2 changed files:

- hadrian/src/Hadrian/Utilities.hs
- libraries/base/GHC/Base.hs


Changes:

=====================================
hadrian/src/Hadrian/Utilities.hs
=====================================
@@ -574,22 +574,36 @@ renderCreateFileLink linkTarget link' = do
     where
         link = unifyPath link'
 
+-- | Render a multiline string, prefixing the first line with a header.
+renderMultiLineString :: String -> String -> [String]
+renderMultiLineString header string =
+    [ linePrefix index ++ line | (index, line) <- zip [0..] (lines string) ]
+  where
+    linePrefix :: Int -> String
+    linePrefix index
+        | index == 0 = header
+        | otherwise  = replicate (length header) ' '
+
+-- | Render a (possibly multiline) synopsis, making sure it ends with a dot.
+renderSynopsis :: String -> String -> [String]
+renderSynopsis header synopsis
+    | null synopsis = []
+    | otherwise = renderMultiLineString header (endWithADot synopsis)
+  where
+    endWithADot :: String -> String
+    endWithADot s = dropWhileEnd isPunctuation s ++ "."
+
 -- | Render the successful build of a program.
 renderProgram :: String -> String -> String -> String
 renderProgram name bin synopsis = renderBox $
-    [ "Successfully built program " ++ name
-    , "Executable: " ++ bin ] ++
-    [ "Program synopsis: " ++ endWithADot synopsis | not (null synopsis) ]
+    [ "Successfully built program " ++ name, "Executable: " ++ bin ] ++
+    renderSynopsis "Program synopsis: " synopsis
 
 -- | Render the successful build of a library.
 renderLibrary :: String -> String -> String -> String
 renderLibrary name lib synopsis = renderBox $
-    [ "Successfully built library " ++ name
-    , "Library: " ++ lib ] ++
-    [ "Library synopsis: " ++ endWithADot synopsis | not (null synopsis) ]
-
-endWithADot :: String -> String
-endWithADot s = dropWhileEnd isPunctuation s ++ "."
+    [ "Successfully built library " ++ name, "Library: " ++ lib ] ++
+    renderSynopsis "Library synopsis: " synopsis
 
 -- | Render the given set of lines in an ASCII box. The minimum width and
 -- whether to use Unicode symbols are hardcoded in the function's body.


=====================================
libraries/base/GHC/Base.hs
=====================================
@@ -1461,8 +1461,13 @@ The rules for map work like this.
 --
 -- If the first list is not finite, the result is the first list.
 --
--- WARNING: This function takes linear time in the number of elements of the
--- first list.
+-- This function takes linear time in the number of elements of the
+-- __first__ list. Thus it is better to associate repeated
+-- applications of '(++)' to the right (which is the default behaviour):
+-- @xs ++ (ys ++ zs)@ or simply @xs ++ ys ++ zs@, but not @(xs ++ ys) ++ zs at .
+-- For the same reason 'Data.List.concat' @=@ 'Data.List.foldr' '(++)' @[]@
+-- has linear performance, while 'Data.List.foldl' '(++)' @[]@ is prone
+-- to quadratic slowdown.
 
 (++) :: [a] -> [a] -> [a]
 {-# NOINLINE [2] (++) #-}



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/77fb0aab9dc8fc73d2d2966d91b360beea3ee621...079586c7ca8f2645033a29568e471eae12896642

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/77fb0aab9dc8fc73d2d2966d91b360beea3ee621...079586c7ca8f2645033a29568e471eae12896642
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/20230603/4afa9742/attachment-0001.html>


More information about the ghc-commits mailing list