[Git][ghc/ghc][master] 10 commits: Lowercase windows imports

Ben Gamari gitlab at gitlab.haskell.org
Tue May 28 03:51:32 UTC 2019



Ben Gamari pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
4b228768 by Moritz Angermann at 2019-05-27T05:19:49Z
Lowercase windows imports

While windows and macOS are currently on case-insensitive file
systems, this poses no issue on those.  When cross compiling from
linux with a case sensitive file system and mingw providing only
lowercase headers, this in fact produces an issue.  As such we just
lowercase the import headers, which should still work fine on a
case insensitive file system and also enable mingw's headers to
be usable porperly.

- - - - -
01f8e390 by Alp Mestanogullari at 2019-05-27T14:06:26Z
Hadrian: Fix problem with unlit path in settings file

e529c65e introduced a problem in the logic for generating the
path to the unlit command in the settings file, and this patches
fixes it.

This fixes many tests, the simplest of which is:

> _build/stage1/bin/ghc testsuite/tests/parser/should_fail/T8430.lhs

which failed because of a wrong path for unlit, and now fails for the right
reason, with the error message expected for this test.

This addresses #16659.

- - - - -
dcd843ac by mizunashi_mana at 2019-05-27T14:06:27Z
Fix typo of primop format
- - - - -
3f6e5b97 by Joshua Price at 2019-05-27T14:06:28Z
Correct the large tuples section in user's guide

Fixes #16644.

- - - - -
1f51aad6 by Krzysztof Gogolewski at 2019-05-27T14:06:28Z
Fix tcfail158 (#15899)

As described in #15899, this test was broken, but now it's back
to normal.

- - - - -
723216e3 by Sebastian Graf at 2019-05-27T14:06:29Z
Add a pprTraceWith function

- - - - -
6d188dd5 by Simon Jakobi at 2019-05-27T14:06:31Z
base: Include (<$) in all exports of Functor

Previously the haddocks for Control.Monad and Data.Functor gave
the impression that `fmap` was the only Functor method.

Fixes #16681.

- - - - -
95b79173 by Jasper Van der Jeugt at 2019-05-27T14:06:32Z
Fix padding of entries in .prof files

When the number of entries of a cost centre reaches 11 digits, it takes
up the whole space reserved for it and the prof file ends up looking
like:

    ... no.        entries  %time %alloc   %time %alloc

        ...
    ... 120918     978250    0.0    0.0     0.0    0.0
    ... 118891          0    0.0    0.0    73.3   80.8
    ... 11890229702412351    8.9   13.5    73.3   80.8
    ... 118903  153799689    0.0    0.1     0.0    0.1
        ...

This results in tooling not being able to parse the .prof file.  I
realise we have the JSON output as well now, but still it'd be good to
fix this little weirdness.

Original bug report and full prof file can be seen here:
<https://github.com/jaspervdj/profiteur/issues/28>.

- - - - -
f80d3afd by John Ericson at 2019-05-27T14:06:33Z
hadrian: Fix generation of settings

I jumbled some lines in e529c65eacf595006dd5358491d28c202d673732,
messing up the leading underscores and rts ways settings. This broke at
least stage1 linking on macOS, but probably loads of other things too.

Should fix #16685 and #16658.

- - - - -
db8e3275 by Ömer Sinan Ağacan at 2019-05-27T14:06:37Z
Add missing opening braces in Cmm dumps

Previously -ddump-cmm was generating code with unbalanced curly braces:

     stg_atomically_entry() //  [R1]
             { info_tbls: [(cfl,
                            label: stg_atomically_info
                            rep: tag:16 HeapRep 1 ptrs { Thunk }
                            srt: Nothing)]
               stack_info: arg_space: 8 updfr_space: Just 8
             }
         {offset
           cfl: // cfk
               unwind Sp = Just Sp + 0;
               _cfk::P64 = R1;
               //tick src<rts/PrimOps.cmm:(1243,1)-(1245,1)>
               R1 = I64[_cfk::P64 + 8 + 8 + 0 * 8];
               call stg_atomicallyzh(R1) args: 8, res: 0, upd: 8;
         }
     }, <---- OPENING BRACE MISSING

After this patch:

     stg_atomically_entry() { //  [R1] <---- MISSING OPENING BRACE HERE
             { info_tbls: [(cfl,
                            label: stg_atomically_info
                            rep: tag:16 HeapRep 1 ptrs { Thunk }
                            srt: Nothing)]
               stack_info: arg_space: 8 updfr_space: Just 8
             }
         {offset
           cfl: // cfk
               unwind Sp = Just Sp + 0;
               _cfk::P64 = R1;
               //tick src<rts/PrimOps.cmm:(1243,1)-(1245,1)>
               R1 = I64[_cfk::P64 + 8 + 8 + 0 * 8];
               call stg_atomicallyzh(R1) args: 8, res: 0, upd: 8;
         }
     },

- - - - -


12 changed files:

- compiler/cmm/PprCmmDecl.hs
- compiler/prelude/primops.txt.pp
- compiler/utils/Outputable.hs
- docs/users_guide/bugs.rst
- driver/utils/dynwrapper.c
- hadrian/src/Rules/Generate.hs
- libraries/base/Control/Monad.hs
- libraries/base/Data/Functor.hs
- rts/ProfilerReport.c
- rules/build-prog.mk
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail158.stderr


Changes:

=====================================
compiler/cmm/PprCmmDecl.hs
=====================================
@@ -94,7 +94,7 @@ pprTop :: (Outputable d, Outputable info, Outputable i)
 
 pprTop (CmmProc info lbl live graph)
 
-  = vcat [ ppr lbl <> lparen <> rparen <+> text "// " <+> ppr live
+  = vcat [ ppr lbl <> lparen <> rparen <+> lbrace <+> text "// " <+> ppr live
          , nest 8 $ lbrace <+> ppr info $$ rbrace
          , nest 4 $ ppr graph
          , rbrace ]


=====================================
compiler/prelude/primops.txt.pp
=====================================
@@ -33,7 +33,7 @@
 --
 -- The format of each primop entry is as follows:
 --
---      primop internal-name "name-in-program-text" type category {description} attributes
+--      primop internal-name "name-in-program-text" category type {description} attributes
 
 -- The default attribute values which apply if you don't specify
 -- other ones.  Attribute values can be True, False, or arbitrary


=====================================
compiler/utils/Outputable.hs
=====================================
@@ -81,8 +81,8 @@ module Outputable (
 
         -- * Error handling and debugging utilities
         pprPanic, pprSorry, assertPprPanic, pprPgmError,
-        pprTrace, pprTraceDebug, pprTraceIt, warnPprTrace, pprSTrace,
-        pprTraceException, pprTraceM,
+        pprTrace, pprTraceDebug, pprTraceWith, pprTraceIt, warnPprTrace,
+        pprSTrace, pprTraceException, pprTraceM,
         trace, pgmError, panic, sorry, assertPanic,
         pprDebugAndThen, callStackDoc,
     ) where
@@ -1196,9 +1196,15 @@ pprTrace str doc x
 pprTraceM :: Applicative f => String -> SDoc -> f ()
 pprTraceM str doc = pprTrace str doc (pure ())
 
+-- | @pprTraceWith desc f x@ is equivalent to @pprTrace desc (f x) x at .
+-- This allows you to print details from the returned value as well as from
+-- ambient variables.
+pprTraceWith :: Outputable a => String -> (a -> SDoc) -> a -> a
+pprTraceWith desc f x = pprTrace desc (f x) x
+
 -- | @pprTraceIt desc x@ is equivalent to @pprTrace desc (ppr x) x@
 pprTraceIt :: Outputable a => String -> a -> a
-pprTraceIt desc x = pprTrace desc (ppr x) x
+pprTraceIt desc x = pprTraceWith desc ppr x
 
 -- | @pprTraceException desc x action@ runs action, printing a message
 -- if it throws an exception.


=====================================
docs/users_guide/bugs.rst
=====================================
@@ -312,14 +312,6 @@ Multiply-defined array elements not checked
 In ``Prelude`` support
 ^^^^^^^^^^^^^^^^^^^^^^
 
-Arbitrary-sized tuples
-    Tuples are currently limited to size 100. However, standard
-    instances for tuples (``Eq``, ``Ord``, ``Bounded``, ``Ix``, ``Read``,
-    and ``Show``) are available *only* up to 16-tuples.
-
-    This limitation is easily subvertible, so please ask if you get
-    stuck on it.
-
 ``splitAt`` semantics
     ``Data.List.splitAt`` is more strict than specified in the Report.
     Specifically, the Report specifies that ::
@@ -481,6 +473,14 @@ Unchecked floating-point arithmetic
     .. index::
         single: floating-point exceptions.
 
+Large tuple support
+    The Haskell Report only requires implementations to provide tuple
+    types and their accompanying standard instances up to size 15. GHC
+    limits the size of tuple types to 62 and provides instances of
+    ``Eq``, ``Ord``, ``Bounded``, ``Read``, and ``Show`` for tuples up
+    to size 15. However, ``Ix`` instances are provided only for tuples
+    up to size 5.
+
 .. _bugs:
 
 Known bugs or infelicities


=====================================
driver/utils/dynwrapper.c
=====================================
@@ -9,8 +9,8 @@ int rtsOpts;
 
 #include <stdarg.h>
 #include <stdio.h>
-#include <Windows.h>
-#include <Shlwapi.h>
+#include <windows.h>
+#include <shlwapi.h>
 
 #include "Rts.h"
 


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -5,6 +5,7 @@ module Rules.Generate (
     ) where
 
 import Base
+import qualified Context
 import Expression
 import Flavour
 import Hadrian.Oracles.TextFile (lookupValueOrError)
@@ -271,6 +272,7 @@ generateGhcPlatformH = do
 
 generateSettings :: Expr String
 generateSettings = do
+    ctx <- getContext
     settings <- traverse sequence $
         [ ("GCC extra via C opts", expr $ lookupValueOrError configFile "gcc-extra-via-c-opts")
         , ("C compiler command", expr $ settingsFileSetting SettingsFileSetting_CCompilerCommand)
@@ -293,7 +295,7 @@ generateSettings = do
         , ("dllwrap command", expr $ settingsFileSetting SettingsFileSetting_DllWrapCommand)
         , ("windres command", expr $ settingsFileSetting SettingsFileSetting_WindresCommand)
         , ("libtool command", expr $ settingsFileSetting SettingsFileSetting_LibtoolCommand)
-        , ("unlit command", ("$topdir/bin/" <>) <$> getBuilderPath Unlit)
+        , ("unlit command", ("$topdir/bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
         , ("cross compiling", expr $ yesNo <$> flag CrossCompiling)
         , ("target platform string", getSetting TargetPlatform)
         , ("target os", expr $ lookupValueOrError configFile "haskell-target-os")
@@ -312,9 +314,9 @@ generateSettings = do
         , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter)
         , ("Use native code generator", expr $ yesNo <$> ghcWithNativeCodeGen)
         , ("Support SMP", expr $ yesNo <$> ghcWithSMP)
-        , ("RTS ways", expr $ yesNo <$> flag LeadingUnderscore)
+        , ("RTS ways", unwords . map show <$> getRtsWays)
         , ("Tables next to code", expr $ yesNo <$> ghcEnableTablesNextToCode)
-        , ("Leading underscore", expr $ yesNo <$> useLibFFIForAdjustors)
+        , ("Leading underscore", expr $ yesNo <$> flag LeadingUnderscore)
         , ("Use LibFFI", expr $ yesNo <$> useLibFFIForAdjustors)
         , ("Use Threads", yesNo . any (wayUnit Threaded) <$> getRtsWays)
         , ("Use Debugging", expr $ yesNo . ghcDebugged <$> flavour)


=====================================
libraries/base/Control/Monad.hs
=====================================
@@ -18,7 +18,7 @@ module Control.Monad
     (
     -- * Functor and monad classes
 
-      Functor(fmap)
+      Functor(..)
     , Monad((>>=), (>>), return)
     , MonadFail(fail)
     , MonadPlus(mzero, mplus)


=====================================
libraries/base/Data/Functor.hs
=====================================
@@ -39,8 +39,7 @@
 
 module Data.Functor
     (
-      Functor(fmap),
-      (<$),
+      Functor(..),
       ($>),
       (<$>),
       (<&>),


=====================================
rts/ProfilerReport.c
=====================================
@@ -233,7 +233,7 @@ logCCS(FILE *prof_file, CostCentreStack const *ccs, ProfilerTotals totals,
                 max_src_len - strlen_utf8(cc->srcloc), "");
 
         fprintf(prof_file,
-                " %*" FMT_Int "%11" FMT_Word64 "  %5.1f  %5.1f   %5.1f  %5.1f",
+                " %*" FMT_Int " %11" FMT_Word64 "  %5.1f  %5.1f   %5.1f  %5.1f",
                 max_id_len, ccs->ccsID, ccs->scc_count,
                 totals.total_prof_ticks == 0 ? 0.0 : ((double)ccs->time_ticks / (double)totals.total_prof_ticks * 100.0),
                 totals.total_alloc == 0 ? 0.0 : ((double)ccs->mem_alloc / (double)totals.total_alloc * 100.0),


=====================================
rules/build-prog.mk
=====================================
@@ -230,7 +230,7 @@ endif
 
 $1/$2/build/tmp/$$($1_$2_PROG)-inplace-wrapper.c: driver/utils/dynwrapper.c | $$$$(dir $$$$@)/.
 	$$(call removeFiles,$$@)
-	echo '#include <Windows.h>' >> $$@
+	echo '#include <windows.h>' >> $$@
 	echo '#include "Rts.h"' >> $$@
 	echo 'LPTSTR path_dirs[] = {' >> $$@
 	$$(foreach d,$$($1_$2_DEP_LIB_REL_DIRS),$$(call make-command,echo '    TEXT("/../../$$d")$$(comma)' >> $$@))
@@ -243,7 +243,7 @@ $1/$2/build/tmp/$$($1_$2_PROG)-inplace-wrapper.c: driver/utils/dynwrapper.c | $$
 
 $1/$2/build/tmp/$$($1_$2_PROG)-wrapper.c: driver/utils/dynwrapper.c | $$$$(dir $$$$@)/.
 	$$(call removeFiles,$$@)
-	echo '#include <Windows.h>' >> $$@
+	echo '#include <windows.h>' >> $$@
 	echo '#include "Rts.h"' >> $$@
 	echo 'LPTSTR path_dirs[] = {' >> $$@
 	$$(foreach p,$$($1_$2_TRANSITIVE_DEP_COMPONENT_IDS),$$(call make-command,echo '    TEXT("/../lib/$$p")$$(comma)' >> $$@))


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -140,8 +140,7 @@ test('tcfail154', normal, compile_fail, [''])
 test('tcfail155', normal, compile_fail, [''])
 test('tcfail156', normal, compile_fail, [''])
 test('tcfail157', normal, compile_fail, [''])
-# Skip tcfail158 until #15899 fixes the broken test
-test('tcfail158', skip, compile_fail, [''])
+test('tcfail158', normal, compile_fail, [''])
 test('tcfail159', normal, compile_fail, [''])
 test('tcfail160', normal, compile_fail, [''])
 test('tcfail161', normal, compile_fail, [''])


=====================================
testsuite/tests/typecheck/should_fail/tcfail158.stderr
=====================================
@@ -1,3 +1,5 @@
 
-tcfail158.hs:1:1: error:
-    The IO action ‘main’ is not defined in module ‘Main’
+tcfail158.hs:14:19: error:
+    • Expecting one more argument to ‘Val v’
+      Expected a type, but ‘Val v’ has kind ‘* -> *’
+    • In the type signature: bar :: forall v. Val v



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/2d0cf6252957b8980d89481ecd0b79891da4b14b...db8e3275080173cc36af9f8e51636ee506e7c872

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/2d0cf6252957b8980d89481ecd0b79891da4b14b...db8e3275080173cc36af9f8e51636ee506e7c872
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/20190527/e2a17d2c/attachment-0001.html>


More information about the ghc-commits mailing list