[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: base/Event/Poll: Drop POLLRDHUP enum item

Marge Bot gitlab at gitlab.haskell.org
Sun Jun 16 16:28:49 UTC 2019



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


Commits:
db313f98 by Ben Gamari at 2019-06-16T10:26:38Z
base/Event/Poll: Drop POLLRDHUP enum item

Previously the Event enumeration produced by hsc2hs would sometimes
include a currently-unused POLLRDHUP item. This unused binding would
result in a build failure. Drop it.

- - - - -
81608e82 by Ben Gamari at 2019-06-16T10:26:38Z
testsuite: Fix T8602 on musl

Musl wants hash-bangs on all executables.

- - - - -
a0f68379 by Ben Gamari at 2019-06-16T10:26:38Z
testsuite: Ensure T5423 flushes C output buffer

Previously T5423 would fail to flush the printf output buffer.
Consequently it was platform-dependent whether the C or Haskell print
output would be emitted first.

- - - - -
543dfaab by Ben Gamari at 2019-06-16T10:26:38Z
testsuite: Flush conc059's printf buffer

Otherwise it the order out the Haskell and C output will be
system-dependent.

- - - - -
e647752e by Ben Gamari at 2019-06-16T10:26:38Z
testsuite: Ensure that ffi005 output order is predictable

The libc output buffer wasn't being flushed, making the order
system-depedent.

- - - - -
338336d3 by Ben Gamari at 2019-06-16T10:26:38Z
gitlab-ci: Build alpine release bindists

- - - - -
75c6ccf7 by Alp Mestanogullari at 2019-06-16T10:27:17Z
fix runghc's GHC detection logic to cover the "in-tree Hadrian build" scenario

Before this patch, runghc would only run the GHC detection logic on Windows and
assume that it was invoked through a wrapper script on all other platforms.
This patch lifts this limitation and makes that logic work for the scenario
where someone is calling the runghc executable directly, without passing an
explicit path to GHC.

- - - - -
46ecf5f0 by Ben Gamari at 2019-06-16T16:28:41Z
testsuite: Really fix #16741

The previous fix, !1095, didn't work as `--show-iface` ignores
`-dsuppress-ticks`. Rework the test instead.

- - - - -
3d21daa8 by Ben Gamari at 2019-06-16T16:28:41Z
gitlab-ci: Don't allow failure of deb9-dwarf job

This #16741 out of the way this should now pass.

- - - - -
58ba5844 by Ömer Sinan Ağacan at 2019-06-16T16:28:45Z
Use TupleSections in CmmParse.y, simplify a few exprs

- - - - -


17 changed files:

- .gitlab-ci.yml
- compiler/cmm/CmmParse.y
- libraries/base/GHC/Event/Poll.hsc
- testsuite/tests/concurrent/should_run/conc059.stdout
- testsuite/tests/concurrent/should_run/conc059_c.c
- testsuite/tests/driver/T8602/T8602.script
- testsuite/tests/ffi/should_run/all.T
- testsuite/tests/ffi/should_run/ffi005.hs
- testsuite/tests/ffi/should_run/ffi005.stdout
- + testsuite/tests/ffi/should_run/ffi005_c.c
- testsuite/tests/rts/Makefile
- testsuite/tests/rts/T5423.hs
- testsuite/tests/rts/T5423.stdout
- + testsuite/tests/rts/T5423_c.c
- testsuite/tests/simplCore/should_compile/Makefile
- testsuite/tests/simplCore/should_compile/T4918.stdout
- utils/runghc/Main.hs


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -546,11 +546,10 @@ release-x86_64-linux-deb9-dwarf:
   extends: .validate-linux
   stage: build
   image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV"
-  allow_failure: true
   variables:
     CONFIGURE_ARGS: "--enable-dwarf-unwind"
     BUILD_FLAVOUR: dwarf
-    TEST_ENV: "x86_64-linux-deb9"
+    TEST_ENV: "x86_64-linux-deb9-dwarf"
   artifacts:
     when: always
     expire_in: 2 week
@@ -577,6 +576,30 @@ release-x86_64-linux-deb8:
     when: always
     expire_in: 2 week
 
+#################################
+# x86_64-linux-alpine
+#################################
+
+release-x86_64-linux-alpine:
+  extends: .validate-linux
+  stage: full-build
+  image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine:$DOCKER_REV"
+  # There are currently a few failing tests
+  allow_failure: true
+  variables:
+    BUILD_SPHINX_PDF: "NO"
+    TEST_ENV: "x86_64-linux-alpine"
+    BIN_DIST_PREP_TAR_COMP: "bindistprep/ghc-x86_64-alpine-linux.tar.xz"
+    # Can't use ld.gold due to #13958.
+    CONFIGURE_ARGS: "--disable-ld-override"
+  only:
+    - tags
+  cache:
+    key: linux-x86_64-alpine
+  artifacts:
+    when: always
+    expire_in: 2 week
+
 #################################
 # x86_64-linux-centos7
 #################################


=====================================
compiler/cmm/CmmParse.y
=====================================
@@ -198,6 +198,8 @@ necessary to the stack to accommodate it (e.g. 2).
 ----------------------------------------------------------------------------- -}
 
 {
+{-# LANGUAGE TupleSections #-}
+
 module CmmParse ( parseCmmFile ) where
 
 import GhcPrelude
@@ -808,7 +810,7 @@ foreign_formals :: { [CmmParse (LocalReg, ForeignHint)] }
         | foreign_formal ',' foreign_formals    { $1 : $3 }
 
 foreign_formal :: { CmmParse (LocalReg, ForeignHint) }
-        : local_lreg            { do e <- $1; return (e, (inferCmmHint (CmmReg (CmmLocal e)))) }
+        : local_lreg            { do e <- $1; return (e, inferCmmHint (CmmReg (CmmLocal e))) }
         | STRING local_lreg     {% do h <- parseCmmHint $1;
                                       return $ do
                                          e <- $2; return (e,h) }
@@ -999,36 +1001,36 @@ machOps = listToUFM $
 callishMachOps :: UniqFM ([CmmExpr] -> (CallishMachOp, [CmmExpr]))
 callishMachOps = listToUFM $
         map (\(x, y) -> (mkFastString x, y)) [
-        ( "write_barrier", (,) MO_WriteBarrier ),
+        ( "write_barrier", (MO_WriteBarrier,)),
         ( "memcpy", memcpyLikeTweakArgs MO_Memcpy ),
         ( "memset", memcpyLikeTweakArgs MO_Memset ),
         ( "memmove", memcpyLikeTweakArgs MO_Memmove ),
         ( "memcmp", memcpyLikeTweakArgs MO_Memcmp ),
 
-        ("prefetch0", (,) $ MO_Prefetch_Data 0),
-        ("prefetch1", (,) $ MO_Prefetch_Data 1),
-        ("prefetch2", (,) $ MO_Prefetch_Data 2),
-        ("prefetch3", (,) $ MO_Prefetch_Data 3),
-
-        ( "popcnt8",  (,) $ MO_PopCnt W8  ),
-        ( "popcnt16", (,) $ MO_PopCnt W16 ),
-        ( "popcnt32", (,) $ MO_PopCnt W32 ),
-        ( "popcnt64", (,) $ MO_PopCnt W64 ),
-
-        ( "pdep8",  (,) $ MO_Pdep W8  ),
-        ( "pdep16", (,) $ MO_Pdep W16 ),
-        ( "pdep32", (,) $ MO_Pdep W32 ),
-        ( "pdep64", (,) $ MO_Pdep W64 ),
-
-        ( "pext8",  (,) $ MO_Pext W8  ),
-        ( "pext16", (,) $ MO_Pext W16 ),
-        ( "pext32", (,) $ MO_Pext W32 ),
-        ( "pext64", (,) $ MO_Pext W64 ),
-
-        ( "cmpxchg8",  (,) $ MO_Cmpxchg W8  ),
-        ( "cmpxchg16", (,) $ MO_Cmpxchg W16 ),
-        ( "cmpxchg32", (,) $ MO_Cmpxchg W32 ),
-        ( "cmpxchg64", (,) $ MO_Cmpxchg W64 )
+        ("prefetch0", (MO_Prefetch_Data 0,)),
+        ("prefetch1", (MO_Prefetch_Data 1,)),
+        ("prefetch2", (MO_Prefetch_Data 2,)),
+        ("prefetch3", (MO_Prefetch_Data 3,)),
+
+        ( "popcnt8",  (MO_PopCnt W8,)),
+        ( "popcnt16", (MO_PopCnt W16,)),
+        ( "popcnt32", (MO_PopCnt W32,)),
+        ( "popcnt64", (MO_PopCnt W64,)),
+
+        ( "pdep8",  (MO_Pdep W8,)),
+        ( "pdep16", (MO_Pdep W16,)),
+        ( "pdep32", (MO_Pdep W32,)),
+        ( "pdep64", (MO_Pdep W64,)),
+
+        ( "pext8",  (MO_Pext W8,)),
+        ( "pext16", (MO_Pext W16,)),
+        ( "pext32", (MO_Pext W32,)),
+        ( "pext64", (MO_Pext W64,)),
+
+        ( "cmpxchg8",  (MO_Cmpxchg W8,)),
+        ( "cmpxchg16", (MO_Cmpxchg W16,)),
+        ( "cmpxchg32", (MO_Cmpxchg W32,)),
+        ( "cmpxchg64", (MO_Cmpxchg W64,))
 
         -- ToDo: the rest, maybe
         -- edit: which rest?


=====================================
libraries/base/GHC/Event/Poll.hsc
=====================================
@@ -162,24 +162,12 @@ newtype Event = Event CShort
              , FiniteBits -- ^ @since 4.7.0.0
              )
 
--- We have to duplicate the whole enum like this in order for the
--- hsc2hs cross-compilation mode to work
-#if defined(POLLRDHUP)
 #{enum Event, Event
  , pollIn    = POLLIN
  , pollOut   = POLLOUT
- , pollRdHup = POLLRDHUP
  , pollErr   = POLLERR
  , pollHup   = POLLHUP
  }
-#else
-#{enum Event, Event
- , pollIn    = POLLIN
- , pollOut   = POLLOUT
- , pollErr   = POLLERR
- , pollHup   = POLLHUP
- }
-#endif
 
 fromEvent :: E.Event -> Event
 fromEvent e = remap E.evtRead  pollIn .|.


=====================================
testsuite/tests/concurrent/should_run/conc059.stdout
=====================================
@@ -1,3 +1,3 @@
-500000
 exiting...
+500000
 exited.


=====================================
testsuite/tests/concurrent/should_run/conc059_c.c
=====================================
@@ -16,6 +16,7 @@ int main(int argc, char *argv[])
     usleep(100000);
 #endif
     printf("exiting...\n");
+    fflush(stdout);
     hs_exit();
     printf("exited.\n");
 #if mingw32_HOST_OS


=====================================
testsuite/tests/driver/T8602/T8602.script
=====================================
@@ -1,3 +1,4 @@
-:! echo 'echo $4 $5 $6; exit 1' > t8602.sh
+:! echo '#!/bin/sh' > t8602.sh
+:! echo 'echo $4 $5 $6; exit 1' >> t8602.sh
 :! chmod +x t8602.sh
 :load A


=====================================
testsuite/tests/ffi/should_run/all.T
=====================================
@@ -28,11 +28,11 @@ test('ffi004', skip, compile_and_run, [''])
 # On x86, the test suffers from floating-point differences due to the
 # use of 80-bit internal precision when using the native code generator.
 #
-test('ffi005', [ omit_ways(prof_ways),
+test('ffi005', [ omit_ways(prof_ways + ['ghci']),
                  when(arch('i386'), skip),
                  when(platform('i386-apple-darwin'), expect_broken(4105)),
                  exit_code(3) ],
-               compile_and_run, [''])
+               compile_and_run, ['ffi005_c.c'])
 
 test('ffi006', normal, compile_and_run, [''])
 


=====================================
testsuite/tests/ffi/should_run/ffi005.hs
=====================================
@@ -20,10 +20,12 @@ main = do
 --  putStrLn $ "errno == " ++ show err
 
   putStrLn "\nTesting puts (and withString)"
-  withCString "Test successful" puts
+  hFlush stdout
+  withCString "Test puts successful" puts
+  flushStdout  -- Flush the libc output buffer
 
   putStrLn "\nTesting peekArray0"
-  s <- withCString "Test successful" (peekArray0 (castCharToCChar '\0'))
+  s <- withCString "Test peekArray0 successful" (peekArray0 (castCharToCChar '\0'))
   putStr (map castCCharToChar s)
 
 -- disabled due to use of non-portable constants in arguments to open:
@@ -71,6 +73,7 @@ withBuffer sz m = do
   return s
 
 foreign import ccall puts :: CString -> IO CInt
+foreign import ccall "flush_stdout" flushStdout :: IO ()
 
 -- foreign import ccall "open" open'  :: CString -> CInt -> IO CInt
 -- foreign import ccall "open" open2' :: CString -> CInt -> CInt -> IO CInt


=====================================
testsuite/tests/ffi/should_run/ffi005.stdout
=====================================
@@ -3,9 +3,10 @@ Testing sin==mysin (should return lots of Trues)
 [True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True]
 
 Testing puts (and withString)
+Test puts successful
 
 Testing peekArray0
-Test successful
+Test peekArray0 successful
 Testing sin==dynamic_sin (should return lots of Trues)
 [True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True]
 
@@ -16,4 +17,3 @@ Testing sin==Id wrapped_sin (should return lots of Trues)
 [True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True,True]
 
 Testing exit
-Test successful


=====================================
testsuite/tests/ffi/should_run/ffi005_c.c
=====================================
@@ -0,0 +1,5 @@
+#include <stdio.h>
+void flush_stdout(void)
+{
+    fflush(stdout);
+}


=====================================
testsuite/tests/rts/Makefile
=====================================
@@ -37,7 +37,8 @@ T5423:
 	$(RM) T5423_cmm.o T5423.o T5423.hi T5423$(exeext)
 	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 -c T5423_cmm.cmm
 	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 -c T5423.hs
-	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 T5423.o T5423_cmm.o -o T5423$(exeext)
+	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 -c T5423_c.c
+	"$(TEST_HC)" $(TEST_HC_OPTS) -v0 T5423.o T5423_cmm.o T5423_c.o -o T5423$(exeext)
 	./T5423
 
 .PHONY: T9405


=====================================
testsuite/tests/rts/T5423.hs
=====================================
@@ -7,8 +7,13 @@ foreign import prim "test" test :: Int# -> Int# -> Int# -> Int# -> Int#
                                 -> Int# -> Int# -> Int# -> Int# -> Int#
                                 -> Int#
 
+foreign import ccall "flush_stdout" flush_stdout :: IO ()
+
 v :: Int
 v = I# (test 111# 112# 113# 114# 115# 116# 117# 118# 119# 120#)
 
 main :: IO ()
-main = print v
+main = do
+  n <- return $! v
+  flush_stdout -- Ensure that libc output buffer is flushed
+  print n


=====================================
testsuite/tests/rts/T5423.stdout
=====================================
@@ -1,2 +1,2 @@
-120
 111  112  113  114  115  116  117  118  119  120
+120


=====================================
testsuite/tests/rts/T5423_c.c
=====================================
@@ -0,0 +1,6 @@
+#include <stdio.h>
+
+void flush_stdout(void)
+{
+    fflush(stdout);
+}


=====================================
testsuite/tests/simplCore/should_compile/Makefile
=====================================
@@ -111,8 +111,7 @@ T4903:
 T4918:
 	$(RM) -f T4918.hi T4918.o T4918a.hi T4918a.o
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c -O T4918a.hs
-	'$(TEST_HC)' $(TEST_HC_OPTS) -c -O T4918.hs
-	'$(TEST_HC)' $(TEST_HC_OPTS) -dsuppress-ticks --show-iface T4918.hi | grep 'C#'
+	'$(TEST_HC)' $(TEST_HC_OPTS) -c -O T4918.hs -ddump-simpl -dsuppress-all 2>&1 | grep 'C#'
 
 EvalTest:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -c -O EvalTest.hs -ddump-simpl -dsuppress-uniques | grep 'rght.*Dmd' | sed 's/^ *//'


=====================================
testsuite/tests/simplCore/should_compile/T4918.stdout
=====================================
@@ -1,2 +1,3 @@
-  {- HasNoCafRefs, Strictness: m, Unfolding: (GHC.Types.C# 'p'#) -}
-  {- HasNoCafRefs, Strictness: m, Unfolding: (GHC.Types.C# 'q'#) -}
+f4 = C# 'p'#
+f5 = C# 'q'#
+


=====================================
utils/runghc/Main.hs
=====================================
@@ -65,6 +65,11 @@ main = do
 -- live, we check for the existence of ghc. If we can't find it, we assume that
 -- we're building ghc from source, in which case we fall back on ghc-stage2.
 -- (See #1185.)
+--
+-- In-tree Hadrian builds of GHC also happen to give us a wrapper-script-less
+-- runghc. In those cases, 'getExecPath' returns the directory where runghc
+-- lives, which is also where the 'ghc' executable lives, so the guessing logic
+-- covers this scenario just as nicely.
 findGhc :: FilePath -> IO FilePath
 findGhc path = do
     let ghcDir = takeDirectory (normalise path)
@@ -207,5 +212,5 @@ getExecPath = try_size 2048 -- plenty, PATH_MAX is 512 under Win32.
 foreign import WINDOWS_CCONV unsafe "windows.h GetModuleFileNameW"
   c_GetModuleFileName :: Ptr () -> CWString -> Word32 -> IO Word32
 #else
-getExecPath = return Nothing
+getExecPath = Just <$> getExecutablePath
 #endif



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/c921b4035e84117331f86b7f86f897caaad561f3...58ba5844e306efe35e7c0326089af1e9c89859f2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/c921b4035e84117331f86b7f86f897caaad561f3...58ba5844e306efe35e7c0326089af1e9c89859f2
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/20190616/c7f0628b/attachment-0001.html>


More information about the ghc-commits mailing list