[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: remove a no-warn directive from GHC.Cmm.ContFlowOpt

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Oct 21 07:31:23 UTC 2022



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


Commits:
8cd6f435 by Curran McConnell at 2022-10-21T02:58:01-04:00
remove a no-warn directive from GHC.Cmm.ContFlowOpt

This patch is motivated by the desire to remove the {-# OPTIONS_GHC
-fno-warn-incomplete-patterns #-} directive at the top of
GHC.Cmm.ContFlowOpt. (Based on the text in this coding standards doc, I
understand it's a goal of the project to remove such directives.) I
chose this task because I'm a new contributor to GHC, and it seemed like
a good way to get acquainted with the patching process.

In order to address the warning that arose when I removed the no-warn
directive, I added a case to removeUnreachableBlocksProc to handle the
CmmData constructor. Clearly, since this partial function has not been
erroring out in the wild, its inputs are always in practice wrapped by
the CmmProc constructor. Therefore the CmmData case is handled by a
precise panic (which is an improvement over the partial pattern match
from before).

- - - - -
a2af7c4c by Nicolas Trangez at 2022-10-21T02:58:39-04:00
build: get rid of `HAVE_TIME_H`

As advertized by `autoreconf`:

> All current systems provide time.h; it need not be checked for.

Hence, remove the check for it in `configure.ac` and remove conditional
inclusion of the header in `HAVE_TIME_H` blocks where applicable.

The `time.h` header was being included in various source files without a
`HAVE_TIME_H` guard already anyway.

- - - - -
25cdc630 by Nicolas Trangez at 2022-10-21T02:58:39-04:00
rts: remove use of `TIME_WITH_SYS_TIME`

`autoreconf` will insert an `m4_warning` when the obsolescent
`AC_HEADER_TIME` macro is used:

> Update your code to rely only on HAVE_SYS_TIME_H,
> then remove this warning and the obsolete code below it.
> All current systems provide time.h; it need not be checked for.
> Not all systems provide sys/time.h, but those that do, all allow
> you to include it and time.h simultaneously.

Presence of `sys/time.h` was already checked in an earlier
`AC_CHECK_HEADERS` invocation, so `AC_HEADER_TIME` can be dropped and
guards relying on `TIME_WITH_SYS_TIME` can be reworked to
(unconditionally) include `time.h` and include `sys/time.h` based on
`HAVE_SYS_TIME_H`.

Note the documentation of `AC_HEADER_TIME` in (at least) Autoconf 2.67
says

> This macro is obsolescent, as current systems can include both files
> when they exist. New programs need not use this macro.

- - - - -
1fe7921c by Eric Lindblad at 2022-10-21T02:59:21-04:00
runhaskell
- - - - -
e3b3986e by David Feuer at 2022-10-21T03:00:00-04:00
Document how to quote certain names with spaces

Quoting a name for Template Haskell is a bit tricky if the second
character of that name is a single quote. The User's Guide falsely
claimed that it was impossible. Document how to do it.

Fixes #22236
- - - - -
0eba81e8 by Krzysztof Gogolewski at 2022-10-21T03:00:00-04:00
Fix syntax
- - - - -
09312579 by Ben Gamari at 2022-10-21T03:30:59-04:00
Fix manifest filename when writing Windows .rc files

As noted in #12971, we previously used `show` which resulted in
inappropriate escaping of non-ASCII characters.

- - - - -
0605fa81 by Ben Gamari at 2022-10-21T03:30:59-04:00
Write response files in UTF-8 on Windows

This reverts the workaround introduced in
f63c8ef33ec9666688163abe4ccf2d6c0428a7e7, which taught our response file
logic to write response files with the `latin1` encoding to workaround
`gcc`'s lacking Unicode support. This is now no longer necessary (and in
fact actively unhelpful) since we rather use Clang.

- - - - -
bc72abff by M Farkas-Dyck at 2022-10-21T03:31:03-04:00
Scrub some partiality in `GHC.Core.Opt.Simplify.Utils`.

- - - - -


18 changed files:

- compiler/GHC/Cmm/ContFlowOpt.hs
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Linker/Windows.hs
- compiler/GHC/SysTools/Process.hs
- configure.ac
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/runghc.rst
- libraries/base/System/CPUTime/Posix/ClockGetTime.hsc
- libraries/base/aclocal.m4
- libraries/base/cbits/sysconf.c
- libraries/base/include/HsBase.h
- m4/fp_check_timer_create.m4
- rts/RtsUtils.c
- rts/posix/Clock.h
- rts/posix/ticker/Pthread.c
- rts/posix/ticker/Setitimer.c
- rts/win32/GetTime.c


Changes:

=====================================
compiler/GHC/Cmm/ContFlowOpt.hs
=====================================
@@ -1,6 +1,5 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE BangPatterns #-}
-{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
 {-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
 module GHC.Cmm.ContFlowOpt
     ( cmmCfgOpts
@@ -21,8 +20,10 @@ import GHC.Cmm
 import GHC.Cmm.Utils
 import GHC.Cmm.Switch (mapSwitchTargets, switchTargetsToList)
 import GHC.Data.Maybe
-import GHC.Utils.Panic
+import GHC.Platform
 import GHC.Utils.Misc
+import GHC.Utils.Outputable
+import GHC.Utils.Panic
 
 import Control.Monad
 
@@ -422,9 +423,9 @@ predMap blocks = foldr add_preds mapEmpty blocks
     add_preds block env = foldr add env (successors block)
       where add lbl env = mapInsertWith (+) lbl 1 env
 
--- Removing unreachable blocks
-removeUnreachableBlocksProc :: CmmDecl -> CmmDecl
-removeUnreachableBlocksProc proc@(CmmProc info lbl live g)
+-- Remove unreachable blocks from procs
+removeUnreachableBlocksProc :: Platform -> CmmDecl -> CmmDecl
+removeUnreachableBlocksProc _ proc@(CmmProc info lbl live g)
    | used_blocks `lengthLessThan` mapSize (toBlockMap g)
    = CmmProc info' lbl live g'
    | otherwise
@@ -446,3 +447,5 @@ removeUnreachableBlocksProc proc@(CmmProc info lbl live g)
 
      used_lbls :: LabelSet
      used_lbls = setFromList $ map entryLabel used_blocks
+removeUnreachableBlocksProc platform data'@(CmmData _ _) =
+    pprPanic "removeUnreachableBlocksProc: passed data declaration instead of procedure" (pdoc platform data')


=====================================
compiler/GHC/Cmm/Pipeline.hs
=====================================
@@ -156,7 +156,7 @@ cpsTop logger platform cfg proc =
            return $ if cmmOptControlFlow cfg
                     then map (cmmCfgOptsProc splitting_proc_points) g
                     else g
-      g <- return (map removeUnreachableBlocksProc g)
+      g <- return $ map (removeUnreachableBlocksProc platform) g
            -- See Note [unreachable blocks]
       dumps Opt_D_dump_cmm_cfg "Post control-flow optimisations" g
 


=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -42,7 +42,7 @@ module GHC.Core.Opt.Simplify.Utils (
         isExitJoinId
     ) where
 
-import GHC.Prelude
+import GHC.Prelude hiding (head, init, last, tail)
 
 import GHC.Core
 import GHC.Types.Literal ( isLitRubbish )
@@ -84,6 +84,7 @@ import GHC.Utils.Trace
 
 import Control.Monad    ( when )
 import Data.List        ( sortBy )
+import qualified Data.List as Partial ( head )
 
 {- *********************************************************************
 *                                                                      *
@@ -450,7 +451,7 @@ mkRhsStop ty is_rec bndr_dmd = Stop ty (RhsCtxt is_rec) (subDemandIfEvaluated bn
 mkLazyArgStop :: OutType -> ArgInfo -> SimplCont
 mkLazyArgStop ty fun_info = Stop ty (lazyArgContext fun_info) arg_sd
   where
-    arg_sd = subDemandIfEvaluated (head (ai_dmds fun_info))
+    arg_sd = subDemandIfEvaluated (Partial.head (ai_dmds fun_info))
 
 -------------------
 contIsRhs :: SimplCont -> Maybe RecFlag
@@ -592,7 +593,7 @@ contEvalContext k = case k of
     -- then it *should* be "C(1,C(S,C(1,L))", so perhaps correct after all.
     -- But for now we just panic:
   ApplyToVal{}               -> pprPanic "contEvalContext" (ppr k)
-  StrictArg{sc_fun=fun_info} -> subDemandIfEvaluated (head (ai_dmds fun_info))
+  StrictArg{sc_fun=fun_info} -> subDemandIfEvaluated (Partial.head (ai_dmds fun_info))
   StrictBind{sc_bndr=bndr}   -> subDemandIfEvaluated (idDemandInfo bndr)
   Select{}                   -> topSubDmd
     -- Perhaps reconstruct the demand on the scrutinee by looking at field
@@ -1665,7 +1666,7 @@ rebuildLam :: SimplEnv
 rebuildLam _env [] body _cont
   = return body
 
-rebuildLam env bndrs body cont
+rebuildLam env bndrs@(bndr:_) body cont
   = {-# SCC "rebuildLam" #-} try_eta bndrs body
   where
     rec_ids  = seRecIds env
@@ -1682,7 +1683,7 @@ rebuildLam env bndrs body cont
       | -- Try eta reduction
         seDoEtaReduction env
       , Just etad_lam <- tryEtaReduce rec_ids bndrs body eval_sd
-      = do { tick (EtaReduction (head bndrs))
+      = do { tick (EtaReduction bndr)
            ; return etad_lam }
 
       | -- Try eta expansion
@@ -1690,7 +1691,7 @@ rebuildLam env bndrs body cont
       , seEtaExpand env
       , any isRuntimeVar bndrs  -- Only when there is at least one value lambda already
       , Just body_arity <- exprEtaExpandArity (seArityOpts env) body
-      = do { tick (EtaExpansion (head bndrs))
+      = do { tick (EtaExpansion bndr)
            ; let body' = etaExpandAT in_scope body_arity body
            ; traceSmpl "eta expand" (vcat [text "before" <+> ppr body
                                           , text "after" <+> ppr body'])
@@ -2391,12 +2392,12 @@ mkCase mode scrut bndr alts_ty alts = mkCase1 mode scrut bndr alts_ty alts
 --      2. Eliminate Identity Case
 --------------------------------------------------
 
-mkCase1 _mode scrut case_bndr _ alts@(Alt _ _ rhs1 : _)      -- Identity case
+mkCase1 _mode scrut case_bndr _ alts@(Alt _ _ rhs1 : alts')      -- Identity case
   | all identity_alt alts
   = do { tick (CaseIdentity case_bndr)
        ; return (mkTicks ticks $ re_cast scrut rhs1) }
   where
-    ticks = concatMap (\(Alt _ _ rhs) -> stripTicksT tickishFloatable rhs) (tail alts)
+    ticks = concatMap (\(Alt _ _ rhs) -> stripTicksT tickishFloatable rhs) alts'
     identity_alt (Alt con args rhs) = check_eq rhs con args
 
     check_eq (Cast rhs co) con args        -- See Note [RHS casts]


=====================================
compiler/GHC/Linker/Windows.hs
=====================================
@@ -50,10 +50,8 @@ maybeCreateManifest logger tmpfs dflags exe_filename = do
            newTempName logger tmpfs (tmpDir dflags) TFL_GhcSession (objectSuf dflags)
 
          writeFile rc_filename $
-             "1 24 MOVEABLE PURE " ++ show manifest_filename ++ "\n"
+             "1 24 MOVEABLE PURE \"" ++ manifest_filename ++ "\"\n"
                -- magic numbers :-)
-               -- show is a bit hackish above, but we need to escape the
-               -- backslashes in the path.
 
          runWindres logger dflags $ map GHC.SysTools.Option $
                ["--input="++rc_filename,


=====================================
compiler/GHC/SysTools/Process.hs
=====================================
@@ -170,11 +170,7 @@ runSomethingResponseFile logger tmpfs dflags filter_fn phase_name pgm args mb_en
     getResponseFile args = do
       fp <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "rsp"
       withFile fp WriteMode $ \h -> do
-#if defined(mingw32_HOST_OS)
-          hSetEncoding h latin1
-#else
           hSetEncoding h utf8
-#endif
           hPutStr h $ unlines $ map escape args
       return fp
 


=====================================
configure.ac
=====================================
@@ -845,7 +845,7 @@ dnl    off_t, because it will affect the result of that test.
 AC_SYS_LARGEFILE
 
 dnl ** check for specific header (.h) files that we are interested in
-AC_CHECK_HEADERS([ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timerfd.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h time.h utime.h windows.h winsock.h sched.h])
+AC_CHECK_HEADERS([ctype.h dirent.h dlfcn.h errno.h fcntl.h grp.h limits.h locale.h nlist.h pthread.h pwd.h signal.h sys/param.h sys/mman.h sys/resource.h sys/select.h sys/time.h sys/timeb.h sys/timerfd.h sys/timers.h sys/times.h sys/utsname.h sys/wait.h termios.h utime.h windows.h winsock.h sched.h])
 
 dnl sys/cpuset.h needs sys/param.h to be included first on FreeBSD 9.1; #7708
 AC_CHECK_HEADERS([sys/cpuset.h], [], [],
@@ -857,9 +857,6 @@ AC_CHECK_HEADERS([sys/cpuset.h], [], [],
 dnl ** check whether a declaration for `environ` is provided by libc.
 FP_CHECK_ENVIRON
 
-dnl ** check if it is safe to include both <time.h> and <sys/time.h>
-AC_HEADER_TIME
-
 dnl ** do we have long longs?
 AC_CHECK_TYPES([long long])
 


=====================================
docs/users_guide/exts/template_haskell.rst
=====================================
@@ -159,13 +159,14 @@ The :extension:`TemplateHaskellQuotes` extension is considered safe under
       general ``'``\ ⟨thing⟩ interprets ⟨thing⟩ in an expression
       context.
 
-      A name whose second character is a single quote (sadly) cannot be
-      quoted in this way, because it will be parsed instead as a quoted
-      character. For example, if the function is called ``f'7`` (which
-      is a legal Haskell identifier), an attempt to quote it as ``'f'7``
-      would be parsed as the character literal ``'f'`` followed by the
-      numeric literal ``7``. There is no current escape mechanism in
-      this (unusual) situation.
+      A name whose second character is a single quote cannot be quoted in
+      exactly this way, because it will be parsed instead as a quoted
+      character. For example, if the function is called ``f'7`` (which is a
+      legal Haskell identifier), an attempt to quote it as ``'f'7`` would be
+      parsed as the character literal ``'f'`` followed by the numeric literal
+      ``7``. As for promoted constructors (:ref:`promotion-syntax`), the
+      workaround is to add a space between the quote and the name. The name of
+      the function ``f'7`` is thus written ``' f'7``.
 
    -  ``''T`` has type ``Name``, and names the type constructor ``T``.
       That is, ``''``\ ⟨thing⟩ interprets ⟨thing⟩ in a type context.


=====================================
docs/users_guide/runghc.rst
=====================================
@@ -7,7 +7,7 @@ Using runghc
    single: runghc
    single: runhaskell
 
-``runghc`` (or ``runhaskell``, which is its equivalent) allows you to run Haskell programs using the interpreter, instead of having to
+``runghc``/``runhaskell`` allows you to run Haskell programs using the interpreter, instead of having to
 compile them first.
 
 .. _runghc-introduction:


=====================================
libraries/base/System/CPUTime/Posix/ClockGetTime.hsc
=====================================
@@ -2,10 +2,8 @@
 
 #include "HsFFI.h"
 #include "HsBaseConfig.h"
-#if HAVE_TIME_H
 #include <unistd.h>
 #include <time.h>
-#endif
 
 module System.CPUTime.Posix.ClockGetTime
     ( getCPUTime


=====================================
libraries/base/aclocal.m4
=====================================
@@ -78,9 +78,7 @@ AC_DEFUN([FPTOOLS_HTYPE_INCLUDES],
 # include <signal.h>
 #endif
 
-#if HAVE_TIME_H
-# include <time.h>
-#endif
+#include <time.h>
 
 #if HAVE_TERMIOS_H
 # include <termios.h>


=====================================
libraries/base/cbits/sysconf.c
=====================================
@@ -6,9 +6,7 @@
 #endif
 
 /* for CLK_TCK */
-#if HAVE_TIME_H
 #include <time.h>
-#endif
 
 long clk_tck(void) {
 #if defined(CLK_TCK)


=====================================
libraries/base/include/HsBase.h
=====================================
@@ -74,9 +74,7 @@
 #  include <sys/timers.h>
 # endif
 #endif
-#if HAVE_TIME_H
 #include <time.h>
-#endif
 #if HAVE_SYS_TIMEB_H && !defined(__FreeBSD__)
 #include <sys/timeb.h>
 #endif


=====================================
m4/fp_check_timer_create.m4
=====================================
@@ -20,9 +20,7 @@ then
 #if defined(HAVE_STDLIB_H)
 #include <stdlib.h>
 #endif
-#if defined(HAVE_TIME_H)
 #include <time.h>
-#endif
 #if defined(HAVE_SIGNAL_H)
 #include <signal.h>
 #endif


=====================================
rts/RtsUtils.c
=====================================
@@ -15,9 +15,7 @@
 #include "Schedule.h"
 #include "RtsFlags.h"
 
-#if defined(HAVE_TIME_H)
 #include <time.h>
-#endif
 
 /* HACK: On Mac OS X 10.4 (at least), time.h doesn't declare ctime_r with
  *       _POSIX_C_SOURCE. If this is the case, we declare it ourselves.


=====================================
rts/posix/Clock.h
=====================================
@@ -12,9 +12,7 @@
 # include <unistd.h>
 #endif
 
-#if defined(HAVE_TIME_H)
-# include <time.h>
-#endif
+#include <time.h>
 
 #if defined(HAVE_SYS_TIME_H)
 # include <sys/time.h>


=====================================
rts/posix/ticker/Pthread.c
=====================================
@@ -44,17 +44,10 @@
 #include "Schedule.h"
 #include "posix/Clock.h"
 
-/* As recommended in the autoconf manual */
-# if defined(TIME_WITH_SYS_TIME)
-#  include <sys/time.h>
-#  include <time.h>
-# else
-#  if defined(HAVE_SYS_TIME_H)
-#   include <sys/time.h>
-#  else
-#   include <time.h>
-#  endif
-# endif
+#include <time.h>
+#if HAVE_SYS_TIME_H
+# include <sys/time.h>
+#endif
 
 #if defined(HAVE_SIGNAL_H)
 # include <signal.h>


=====================================
rts/posix/ticker/Setitimer.c
=====================================
@@ -15,17 +15,10 @@
 #include "posix/Clock.h"
 #include "posix/Signals.h"
 
-/* As recommended in the autoconf manual */
-# if defined(TIME_WITH_SYS_TIME)
-#  include <sys/time.h>
-#  include <time.h>
-# else
-#  if defined(HAVE_SYS_TIME_H)
-#   include <sys/time.h>
-#  else
-#   include <time.h>
-#  endif
-# endif
+#include <time.h>
+#if HAVE_SYS_TIME_H
+# include <sys/time.h>
+#endif
 
 #if defined(HAVE_SIGNAL_H)
 # include <signal.h>


=====================================
rts/win32/GetTime.c
=====================================
@@ -11,9 +11,7 @@
 
 #include <windows.h>
 
-#if defined(HAVE_TIME_H)
-# include <time.h>
-#endif
+#include <time.h>
 
 /* Convert FILETIMEs into secs */
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6e347bb379f01b633bee33c1f775474e2b4a63f7...bc72abff4d52a3c249215bdc95254bb59960dd66

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6e347bb379f01b633bee33c1f775474e2b4a63f7...bc72abff4d52a3c249215bdc95254bb59960dd66
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/20221021/99411b4f/attachment-0001.html>


More information about the ghc-commits mailing list