[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 13 commits: fs.h: Add missing declarations on Windows

Marge Bot gitlab at gitlab.haskell.org
Tue Mar 24 04:20:46 UTC 2020



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


Commits:
1542a626 by Ben Gamari at 2020-03-22T22:37:47-04:00
fs.h: Add missing declarations on Windows

- - - - -
3bcf2ccd by Ben Gamari at 2020-03-22T22:37:47-04:00
Bump process submodule

Avoids redundant case alternative warning.

- - - - -
3b363ef9 by Ben Gamari at 2020-03-22T22:37:47-04:00
testsuite: Normalize slashes in ghc-api annotations output

Enable `normalise_slashes` on `annotations`, `listcomps`, and
`parseTree` to fix Windows failures.

- - - - -
25fc9429 by Ben Gamari at 2020-03-22T22:37:47-04:00
testsuite: Update expected output on Windows

- - - - -
7f58ec6d by Ben Gamari at 2020-03-22T22:37:47-04:00
testsuite: Fix TOP of T17786

- - - - -
aadcd909 by GHC GitLab CI at 2020-03-22T22:37:47-04:00
testsuite: Update expected output on Windows

- - - - -
dc1eb10d by GHC GitLab CI at 2020-03-22T22:37:47-04:00
hadrian: Fix executable extension passed to testsuite driver

- - - - -
58f62e2c by GHC GitLab CI at 2020-03-22T22:37:47-04:00
gitlab-ci: Require that Windows-hadrian job passes

- - - - -
8dd2415d by Ben Gamari at 2020-03-22T22:37:47-04:00
hadrian: Eliminate redundant .exe from GHC path

Previously we were invoking:

    bash -c
    "c:/GitLabRunner/builds/eEQrxK4p/0/ghc/ghc/toolchain/bin/ghc.exe.exe
    testsuite/mk/ghc-config.hs -o _build/test/bin/ghc-config.exe"

- - - - -
373621f6 by Ben Gamari at 2020-03-22T22:37:47-04:00
Bump hsc2hs submodule

- - - - -
abc02b40 by Hécate at 2020-03-22T22:38:33-04:00
Annotate the non-total function in Data.Foldable as such

- - - - -
19f12557 by Josef Svenningsson at 2020-03-23T14:05:33-04:00
Fix ApplicativeDo regression #17835

A previous fix for #15344 made sure that monadic 'fail' is used properly
when translating ApplicativeDo. However, it didn't properly account
for when a 'fail' will be inserted which resulted in some programs
failing with a type error.

- - - - -
cc480cdc by Paavo at 2020-03-24T00:20:39-04:00
Add example and doc for Arg (Fixes #17153)

- - - - -


23 changed files:

- .gitlab-ci.yml
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Rename/Expr.hs
- hadrian/src/Rules/Test.hs
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/base/Data/Foldable.hs
- libraries/base/Data/Semigroup.hs
- libraries/process
- testsuite/tests/ado/T13242a.stderr
- + testsuite/tests/ado/T17835.hs
- testsuite/tests/ado/ado001.stdout
- testsuite/tests/ado/all.T
- testsuite/tests/driver/T12062/Makefile
- + testsuite/tests/driver/T365.stderr-mingw32
- testsuite/tests/ghc-api/annotations/all.T
- + testsuite/tests/ghc-api/annotations/annotations.stdout-mingw32
- + testsuite/tests/ghc-api/annotations/listcomps.stdout-mingw32
- + testsuite/tests/ghc-api/annotations/parseTree.stdout-mingw32
- testsuite/tests/ghci/scripts/T9293.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci057.stdout-mingw32
- utils/fs/fs.h
- utils/hsc2hs


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -806,9 +806,6 @@ validate-x86_64-linux-fedora27:
     # which might result in some broken perf tests?
     HADRIAN_ARGS: "--docs=no-sphinx --skip-perf"
 
-  # due to #16574 this currently fails
-  allow_failure: true
-
   script:
     - bash .gitlab/ci.sh configure
     - bash .gitlab/ci.sh build_hadrian


=====================================
compiler/GHC/Hs/Expr.hs
=====================================
@@ -2274,22 +2274,31 @@ pprStmt (ApplicativeStmt _ args mb_join)
        (if lengthAtLeast args 2 then parens else id) ap_expr
 
    pp_arg :: (a, ApplicativeArg (GhcPass idL)) -> SDoc
-   pp_arg (_, ApplicativeArgOne _ pat expr isBody _)
-     | isBody =  -- See Note [Applicative BodyStmt]
-     ppr (BodyStmt (panic "pprStmt") expr noSyntaxExpr noSyntaxExpr
+   pp_arg (_, applicativeArg) = ppr applicativeArg
+
+pprStmt (XStmtLR x) = ppr x
+
+
+instance (OutputableBndrId idL)
+      => Outputable (ApplicativeArg (GhcPass idL)) where
+  ppr = pprArg
+
+pprArg :: forall idL . (OutputableBndrId idL) => ApplicativeArg (GhcPass idL) -> SDoc
+pprArg (ApplicativeArgOne _ pat expr isBody _)
+  | isBody =  -- See Note [Applicative BodyStmt]
+    ppr (BodyStmt (panic "pprStmt") expr noSyntaxExpr noSyntaxExpr
             :: ExprStmt (GhcPass idL))
-     | otherwise =
-     ppr (BindStmt (panic "pprStmt") pat expr noSyntaxExpr noSyntaxExpr
+  | otherwise =
+    ppr (BindStmt (panic "pprStmt") pat expr noSyntaxExpr noSyntaxExpr
             :: ExprStmt (GhcPass idL))
-   pp_arg (_, ApplicativeArgMany _ stmts return pat) =
+pprArg (ApplicativeArgMany _ stmts return pat) =
      ppr pat <+>
      text "<-" <+>
      ppr (HsDo (panic "pprStmt") DoExpr (noLoc
                (stmts ++
                    [noLoc (LastStmt noExtField (noLoc return) Nothing noSyntaxExpr)])))
-   pp_arg (_, XApplicativeArg x) = ppr x
 
-pprStmt (XStmtLR x) = ppr x
+pprArg (XApplicativeArg x) = ppr x
 
 pprTransformStmt :: (OutputableBndrId p)
                  => [IdP (GhcPass p)] -> LHsExpr (GhcPass p)


=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -1498,7 +1498,7 @@ ApplicativeDo touches a few phases in the compiler:
   scheduled as outlined above and transformed into applicative
   combinators.  However, the code is still represented as a do-block
   with special forms of applicative statements. This allows us to
-  recover the original do-block when e.g.  printing type errors, where
+  recover the original do-block when e.g. printing type errors, where
   we don't want to show any of the applicative combinators since they
   don't exist in the source code.
   See ApplicativeStmt and ApplicativeArg in HsExpr.
@@ -1682,7 +1682,7 @@ stmtTreeToStmts monad_names ctxt (StmtTreeOne (L _ (BindStmt _ pat rhs _ fail_op
                             , is_body_stmt     = False
                             , fail_operator    = fail_op}]
                       False tail'
-stmtTreeToStmts monad_names ctxt (StmtTreeOne (L _ (BodyStmt _ rhs _ fail_op),_))
+stmtTreeToStmts monad_names ctxt (StmtTreeOne (L _ (BodyStmt _ rhs _ _),_))
                 tail _tail_fvs
   | (False,tail') <- needJoin monad_names tail
   = mkApplicativeStmt ctxt
@@ -1691,7 +1691,7 @@ stmtTreeToStmts monad_names ctxt (StmtTreeOne (L _ (BodyStmt _ rhs _ fail_op),_)
        , app_arg_pattern  = nlWildPatName
        , arg_expr         = rhs
        , is_body_stmt     = True
-       , fail_operator    = fail_op}] False tail'
+       , fail_operator    = noSyntaxExpr}] False tail'
 
 stmtTreeToStmts _monad_names _ctxt (StmtTreeOne (s,_)) tail _tail_fvs =
   return (s : tail, emptyNameSet)
@@ -1706,7 +1706,8 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do
    pairs <- mapM (stmtTreeArg ctxt tail_fvs) trees
    let (stmts', fvss) = unzip pairs
    let (need_join, tail') =
-         if any hasStrictPattern trees
+     -- See Note [ApplicativeDo and refutable patterns]
+         if any hasRefutablePattern stmts'
          then (True, tail)
          else needJoin monad_names tail
 
@@ -1721,13 +1722,13 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do
                , is_body_stmt     = False
                , fail_operator    = fail_op
                }, emptyFVs)
-   stmtTreeArg _ctxt _tail_fvs (StmtTreeOne (L _ (BodyStmt _ exp _ fail_op), _)) =
+   stmtTreeArg _ctxt _tail_fvs (StmtTreeOne (L _ (BodyStmt _ exp _ _), _)) =
      return (ApplicativeArgOne
              { xarg_app_arg_one = noExtField
              , app_arg_pattern  = nlWildPatName
              , arg_expr         = exp
              , is_body_stmt     = True
-             , fail_operator    = fail_op
+             , fail_operator    = noSyntaxExpr
              }, emptyFVs)
    stmtTreeArg ctxt tail_fvs tree = do
      let stmts = flattenStmtTree tree
@@ -1854,12 +1855,19 @@ isStrictPattern lpat =
     SplicePat{}     -> True
     _otherwise -> panic "isStrictPattern"
 
-hasStrictPattern :: ExprStmtTree -> Bool
-hasStrictPattern (StmtTreeOne (L _ (BindStmt _ pat _ _ _), _)) = isStrictPattern pat
-hasStrictPattern (StmtTreeOne _) = False
-hasStrictPattern (StmtTreeBind a b) = hasStrictPattern a || hasStrictPattern b
-hasStrictPattern (StmtTreeApplicative trees) = any hasStrictPattern trees
+{-
+Note [ApplicativeDo and refutable patterns]
+
+Refutable patterns in do blocks are desugared to use the monadic 'fail' operation.
+This means that sometimes an applicative block needs to be wrapped in 'join' simply because
+of a refutable pattern, in order for the types to work out.
+
+-}
 
+hasRefutablePattern :: ApplicativeArg GhcRn -> Bool
+hasRefutablePattern (ApplicativeArgOne { app_arg_pattern = pat
+                                       , is_body_stmt = False}) = not (isIrrefutableHsPat pat)
+hasRefutablePattern _ = False
 
 isLetStmt :: LStmt a b -> Bool
 isLetStmt (L _ LetStmt{}) = True


=====================================
hadrian/src/Rules/Test.hs
=====================================
@@ -48,7 +48,7 @@ testRules = do
 
     -- Using program shipped with testsuite to generate ghcconfig file.
     root -/- ghcConfigProgPath %> \_ -> do
-        ghc0Path <- (<.> exe) <$> getCompilerPath "stage0"
+        ghc0Path <- getCompilerPath "stage0"
         -- Invoke via bash to work around #17362.
         -- Reasons why this is required are not entirely clear.
         cmd ["bash"] ["-c", ghc0Path ++ " " ++ ghcConfigHsPath ++ " -o " ++ (root -/- ghcConfigProgPath)]


=====================================
hadrian/src/Settings/Builders/RunTest.hs
=====================================
@@ -106,7 +106,7 @@ runTestBuilderArgs = builder RunTest ? do
             , arg "-e", arg $ "config.accept=" ++ show accept
             , arg "-e", arg $ "config.accept_platform=" ++ show acceptPlatform
             , arg "-e", arg $ "config.accept_os=" ++ show acceptOS
-            , arg "-e", arg $ "config.exeext=" ++ quote exe
+            , arg "-e", arg $ "config.exeext=" ++ quote (if null exe then "" else "."<>exe)
             , arg "-e", arg $ "config.compiler_debugged=" ++
               show debugged
             , arg "-e", arg $ asBool "ghc_with_native_codegen=" withNativeCodeGen


=====================================
libraries/base/Data/Foldable.hs
=====================================
@@ -215,6 +215,8 @@ class Foldable t where
     -- | A variant of 'foldr' that has no base case,
     -- and thus may only be applied to non-empty structures.
     --
+    -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
+    --
     -- @'foldr1' f = 'List.foldr1' f . 'toList'@
     foldr1 :: (a -> a -> a) -> t a -> a
     foldr1 f xs = fromMaybe (errorWithoutStackTrace "foldr1: empty structure")
@@ -227,6 +229,8 @@ class Foldable t where
     -- | A variant of 'foldl' that has no base case,
     -- and thus may only be applied to non-empty structures.
     --
+    -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
+    --
     -- @'foldl1' f = 'List.foldl1' f . 'toList'@
     foldl1 :: (a -> a -> a) -> t a -> a
     foldl1 f xs = fromMaybe (errorWithoutStackTrace "foldl1: empty structure")
@@ -267,6 +271,14 @@ class Foldable t where
 
     -- | The largest element of a non-empty structure.
     --
+    -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty.
+    --
+    -- === __Examples__
+    -- >>> maximum [1..10]
+    -- 10
+    -- >>> maximum []
+    -- *** Exception: Prelude.maximum: empty list
+    --
     -- @since 4.8.0.0
     maximum :: forall a . Ord a => t a -> a
     maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") .
@@ -274,6 +286,14 @@ class Foldable t where
 
     -- | The least element of a non-empty structure.
     --
+    -- ⚠️ This function is non-total and will raise a runtime exception if the structure happens to be empty
+    --
+    -- === __Examples__
+    -- >>> minimum [1..10]
+    -- 1
+    -- >>> minimum []
+    -- *** Exception: Prelude.minimum: empty list
+    --
     -- @since 4.8.0.0
     minimum :: forall a . Ord a => t a -> a
     minimum = fromMaybe (errorWithoutStackTrace "minimum: empty structure") .


=====================================
libraries/base/Data/Semigroup.hs
=====================================
@@ -286,7 +286,15 @@ instance Num a => Num (Max a) where
 
 -- | 'Arg' isn't itself a 'Semigroup' in its own right, but it can be
 -- placed inside 'Min' and 'Max' to compute an arg min or arg max.
-data Arg a b = Arg a b deriving
+--
+-- >>> minimum [ Arg (x * x) x | x <- [-10 .. 10] ]
+-- Arg 0 0
+data Arg a b = Arg
+  a
+  -- ^ The argument used for comparisons in 'Eq' and 'Ord'.
+  b
+  -- ^ The "value" exposed via the 'Functor', 'Foldable' etc. instances.
+  deriving
   ( Show     -- ^ @since 4.9.0.0
   , Read     -- ^ @since 4.9.0.0
   , Data     -- ^ @since 4.9.0.0


=====================================
libraries/process
=====================================
@@ -1 +1 @@
-Subproject commit 26ea79ceb2193a86f76a302a126be3319f22700d
+Subproject commit 8fffea5ca319e85e1bc9e7cac39e5a2c8effefcc


=====================================
testsuite/tests/ado/T13242a.stderr
=====================================
@@ -32,10 +32,15 @@ T13242a.hs:13:11: error:
         ...plus 21 others
         ...plus six instances involving out-of-scope types
         (use -fprint-potential-instances to see them all)
-    • In the first argument of ‘return’, namely ‘(x == x)’
       In a stmt of a 'do' block: return (x == x)
       In the expression:
         do A x <- undefined
            _ <- return 'a'
            _ <- return 'b'
            return (x == x)
+      In an equation for ‘test’:
+          test
+            = do A x <- undefined
+                 _ <- return 'a'
+                 _ <- return 'b'
+                 return (x == x)


=====================================
testsuite/tests/ado/T17835.hs
=====================================
@@ -0,0 +1,38 @@
+-- Build.hs
+{-# LANGUAGE ApplicativeDo #-}
+module Build (configRules) where
+
+type Action = IO
+type Rules = IO
+
+type Config = ()
+
+(%>) :: String -> (String -> Action ()) -> Rules ()
+(%>) = undefined
+
+command_ :: [String] -> String -> [String] -> Action ()
+command_ = undefined
+
+recursive :: Config -> String -> [String] -> IO (FilePath, [String])
+recursive = undefined
+
+liftIO :: IO a -> Action a
+liftIO = id
+
+need :: [String] -> Action ()
+need = undefined
+
+historyDisable :: Action ()
+historyDisable = undefined
+
+get_config :: () -> Action Config
+get_config = undefined
+
+configRules :: Rules ()
+configRules = do
+  "snapshot" %> \out -> do
+    historyDisable -- 8.10-rc1 refuses to compile without bind here
+    config <- get_config ()
+    need []
+    (exe,args) <- liftIO $ recursive config "snapshot" []
+    command_ [] exe args


=====================================
testsuite/tests/ado/ado001.stdout
=====================================
@@ -9,4 +9,4 @@ a; ((b | c) | d)
 ((a | (b; c)) | d) | e
 ((a | b); (c | d)) | e
 a | b
-(a | (b; c))
+a | (b; c)


=====================================
testsuite/tests/ado/all.T
=====================================
@@ -17,3 +17,4 @@ test('T13875', normal, compile_and_run, [''])
 test('T14163', normal, compile_and_run, [''])
 test('T15344', normal, compile_and_run, [''])
 test('T16628', normal, compile_fail, [''])
+test('T17835', normal, compile, [''])


=====================================
testsuite/tests/driver/T12062/Makefile
=====================================
@@ -1,3 +1,3 @@
-TOP=../../../..
+TOP=../../..
 include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk


=====================================
testsuite/tests/driver/T365.stderr-mingw32
=====================================
@@ -0,0 +1 @@
+./test_preprocessor.txt: builderMainLoop: invalid argument (Exec format error)


=====================================
testsuite/tests/ghc-api/annotations/all.T
=====================================
@@ -1,12 +1,15 @@
 test('annotations', [extra_files(['AnnotationLet.hs']),
+                     normalise_slashes,
                      ignore_stderr], makefile_test, ['annotations'])
 test('parseTree',   [extra_files(['AnnotationTuple.hs']),
+                     normalise_slashes,
                      ignore_stderr], makefile_test, ['parseTree'])
 test('comments',    [extra_files(['CommentsTest.hs']),
                      ignore_stderr], makefile_test, ['comments'])
 test('exampleTest', [extra_files(['AnnotationTuple.hs']),
                      ignore_stderr], makefile_test, ['exampleTest'])
 test('listcomps',   [extra_files(['ListComprehensions.hs']),
+                     normalise_slashes,
                      ignore_stderr], makefile_test, ['listcomps'])
 test('T10255',      [extra_files(['Test10255.hs']),
                      ignore_stderr], makefile_test, ['T10255'])


=====================================
testsuite/tests/ghc-api/annotations/annotations.stdout-mingw32
=====================================
@@ -0,0 +1,86 @@
+[
+(AK AnnotationLet.hs:1:1 AnnCloseC = [AnnotationLet.hs:17:1])
+
+(AK AnnotationLet.hs:1:1 AnnModule = [AnnotationLet.hs:2:1-6])
+
+(AK AnnotationLet.hs:1:1 AnnOpenC = [AnnotationLet.hs:4:1])
+
+(AK AnnotationLet.hs:1:1 AnnWhere = [AnnotationLet.hs:2:28-32])
+
+(AK AnnotationLet.hs:2:22-26 AnnCloseP = [AnnotationLet.hs:2:26])
+
+(AK AnnotationLet.hs:2:22-26 AnnOpenP = [AnnotationLet.hs:2:22])
+
+(AK AnnotationLet.hs:5:1-32 AnnAs = [AnnotationLet.hs:5:28-29])
+
+(AK AnnotationLet.hs:5:1-32 AnnImport = [AnnotationLet.hs:5:1-6])
+
+(AK AnnotationLet.hs:5:1-32 AnnQualified = [AnnotationLet.hs:5:8-16])
+
+(AK AnnotationLet.hs:5:1-32 AnnSemi = [AnnotationLet.hs:6:1])
+
+(AK AnnotationLet.hs:(7,1)-(11,12) AnnEqual = [AnnotationLet.hs:7:5])
+
+(AK AnnotationLet.hs:(7,1)-(11,12) AnnFunId = [AnnotationLet.hs:7:1-3])
+
+(AK AnnotationLet.hs:(7,1)-(11,12) AnnSemi = [AnnotationLet.hs:12:1])
+
+(AK AnnotationLet.hs:(7,7)-(11,12) AnnIn = [AnnotationLet.hs:11:7-8])
+
+(AK AnnotationLet.hs:(7,7)-(11,12) AnnLet = [AnnotationLet.hs:7:7-9])
+
+(AK AnnotationLet.hs:8:9-15 AnnEqual = [AnnotationLet.hs:8:13])
+
+(AK AnnotationLet.hs:8:9-15 AnnFunId = [AnnotationLet.hs:8:9])
+
+(AK AnnotationLet.hs:8:9-15 AnnSemi = [AnnotationLet.hs:9:9])
+
+(AK AnnotationLet.hs:9:9-15 AnnEqual = [AnnotationLet.hs:9:13])
+
+(AK AnnotationLet.hs:9:9-15 AnnFunId = [AnnotationLet.hs:9:9])
+
+(AK AnnotationLet.hs:9:9-15 AnnSemi = [AnnotationLet.hs:10:9])
+
+(AK AnnotationLet.hs:10:9-13 AnnEqual = [AnnotationLet.hs:10:11])
+
+(AK AnnotationLet.hs:10:9-13 AnnFunId = [AnnotationLet.hs:10:9])
+
+(AK AnnotationLet.hs:13:1-10 AnnInfix = [AnnotationLet.hs:13:1-6])
+
+(AK AnnotationLet.hs:13:1-10 AnnSemi = [AnnotationLet.hs:14:1])
+
+(AK AnnotationLet.hs:13:1-10 AnnVal = [AnnotationLet.hs:13:8])
+
+(AK AnnotationLet.hs:15:1-40 AnnCloseP = [AnnotationLet.hs:15:14, AnnotationLet.hs:15:13])
+
+(AK AnnotationLet.hs:15:1-40 AnnData = [AnnotationLet.hs:15:1-4])
+
+(AK AnnotationLet.hs:15:1-40 AnnEqual = [AnnotationLet.hs:15:18])
+
+(AK AnnotationLet.hs:15:1-40 AnnOpenP = [AnnotationLet.hs:15:6, AnnotationLet.hs:15:7])
+
+(AK AnnotationLet.hs:15:1-40 AnnSemi = [AnnotationLet.hs:16:1])
+
+(AK AnnotationLet.hs:15:6-14 AnnCloseP = [AnnotationLet.hs:15:14])
+
+(AK AnnotationLet.hs:15:6-14 AnnOpenP = [AnnotationLet.hs:15:6])
+
+(AK AnnotationLet.hs:15:7-13 AnnCloseP = [AnnotationLet.hs:15:13])
+
+(AK AnnotationLet.hs:15:7-13 AnnOpenP = [AnnotationLet.hs:15:7])
+
+(AK AnnotationLet.hs:15:20-28 AnnVbar = [AnnotationLet.hs:15:30])
+
+(AK AnnotationLet.hs:15:24-28 AnnCloseP = [AnnotationLet.hs:15:28])
+
+(AK AnnotationLet.hs:15:24-28 AnnOpenP = [AnnotationLet.hs:15:24])
+
+(AK AnnotationLet.hs:15:36-40 AnnCloseP = [AnnotationLet.hs:15:40])
+
+(AK AnnotationLet.hs:15:36-40 AnnOpenP = [AnnotationLet.hs:15:36])
+]
+
+[AnnotationLet.hs:2:1-6]
+[]
+AnnotationLet.hs:1:1
+EOF: Just SrcSpanPoint ".\\AnnotationLet.hs" 18 1


=====================================
testsuite/tests/ghc-api/annotations/listcomps.stdout-mingw32
=====================================
@@ -0,0 +1,160 @@
+{ListComprehensions.hs:1:1, ListComprehensions.hs:6:8-25,
+ ListComprehensions.hs:10:1-15, ListComprehensions.hs:10:8-15,
+ ListComprehensions.hs:11:1-30, ListComprehensions.hs:11:18-25,
+ ListComprehensions.hs:11:30, ListComprehensions.hs:12:1-27,
+ ListComprehensions.hs:12:8-15, ListComprehensions.hs:12:17-27,
+ ListComprehensions.hs:12:18-26, ListComprehensions.hs:13:1-25,
+ ListComprehensions.hs:13:8-16, ListComprehensions.hs:13:18-25,
+ ListComprehensions.hs:13:19-24, ListComprehensions.hs:17:1-16,
+ ListComprehensions.hs:17:1-25, ListComprehensions.hs:17:21-25,
+ ListComprehensions.hs:17:22-24, ListComprehensions.hs:18:1-16,
+ ListComprehensions.hs:(18,1)-(22,20),
+ ListComprehensions.hs:(18,18)-(22,20),
+ ListComprehensions.hs:(18,20)-(22,20), ListComprehensions.hs:18:22,
+ ListComprehensions.hs:18:22-26, ListComprehensions.hs:18:22-30,
+ ListComprehensions.hs:(18,22)-(21,34), ListComprehensions.hs:18:24,
+ ListComprehensions.hs:18:26, ListComprehensions.hs:18:28,
+ ListComprehensions.hs:18:30, ListComprehensions.hs:19:22,
+ ListComprehensions.hs:19:22-33,
+ ListComprehensions.hs:(19,22)-(21,34),
+ ListComprehensions.hs:19:27-33, ListComprehensions.hs:19:28,
+ ListComprehensions.hs:19:31-32, ListComprehensions.hs:20:22,
+ ListComprehensions.hs:20:22-34, ListComprehensions.hs:20:27-34,
+ ListComprehensions.hs:20:28-29, ListComprehensions.hs:20:32-33,
+ ListComprehensions.hs:21:22, ListComprehensions.hs:21:22-34,
+ ListComprehensions.hs:21:27-34, ListComprehensions.hs:21:28-29,
+ ListComprehensions.hs:21:32-33, ListComprehensions.hs:24:1-6,
+ ListComprehensions.hs:24:1-27, ListComprehensions.hs:24:11-15,
+ ListComprehensions.hs:24:11-27, ListComprehensions.hs:24:12-14,
+ ListComprehensions.hs:24:20-27, ListComprehensions.hs:24:21-26,
+ ListComprehensions.hs:25:1-6, ListComprehensions.hs:(25,1)-(28,14),
+ ListComprehensions.hs:25:8-10,
+ ListComprehensions.hs:(25,12)-(28,14),
+ ListComprehensions.hs:(25,14)-(28,14),
+ ListComprehensions.hs:25:16-20,
+ ListComprehensions.hs:(25,16)-(27,22), ListComprehensions.hs:26:16,
+ ListComprehensions.hs:26:16-23,
+ ListComprehensions.hs:(26,16)-(27,22),
+ ListComprehensions.hs:26:21-23, ListComprehensions.hs:27:21-22}
+--------------------------------
+[
+(AK ListComprehensions.hs:1:1 AnnModule = [ListComprehensions.hs:6:1-6])
+
+(AK ListComprehensions.hs:1:1 AnnWhere = [ListComprehensions.hs:6:27-31])
+
+(AK ListComprehensions.hs:10:1-15 AnnImport = [ListComprehensions.hs:10:1-6])
+
+(AK ListComprehensions.hs:10:1-15 AnnSemi = [ListComprehensions.hs:11:1])
+
+(AK ListComprehensions.hs:11:1-30 AnnAs = [ListComprehensions.hs:11:27-28])
+
+(AK ListComprehensions.hs:11:1-30 AnnImport = [ListComprehensions.hs:11:1-6])
+
+(AK ListComprehensions.hs:11:1-30 AnnQualified = [ListComprehensions.hs:11:8-16])
+
+(AK ListComprehensions.hs:11:1-30 AnnSemi = [ListComprehensions.hs:12:1])
+
+(AK ListComprehensions.hs:12:1-27 AnnImport = [ListComprehensions.hs:12:1-6])
+
+(AK ListComprehensions.hs:12:1-27 AnnSemi = [ListComprehensions.hs:13:1])
+
+(AK ListComprehensions.hs:12:17-27 AnnCloseP = [ListComprehensions.hs:12:27])
+
+(AK ListComprehensions.hs:12:17-27 AnnOpenP = [ListComprehensions.hs:12:17])
+
+(AK ListComprehensions.hs:13:1-25 AnnImport = [ListComprehensions.hs:13:1-6])
+
+(AK ListComprehensions.hs:13:1-25 AnnSemi = [ListComprehensions.hs:17:1])
+
+(AK ListComprehensions.hs:13:18-25 AnnCloseP = [ListComprehensions.hs:13:25])
+
+(AK ListComprehensions.hs:13:18-25 AnnOpenP = [ListComprehensions.hs:13:18])
+
+(AK ListComprehensions.hs:17:1-25 AnnDcolon = [ListComprehensions.hs:17:18-19])
+
+(AK ListComprehensions.hs:17:1-25 AnnSemi = [ListComprehensions.hs:18:1])
+
+(AK ListComprehensions.hs:17:21-25 AnnCloseS = [ListComprehensions.hs:17:25])
+
+(AK ListComprehensions.hs:17:21-25 AnnOpenS = [ListComprehensions.hs:17:21])
+
+(AK ListComprehensions.hs:(18,1)-(22,20) AnnEqual = [ListComprehensions.hs:18:18])
+
+(AK ListComprehensions.hs:(18,1)-(22,20) AnnFunId = [ListComprehensions.hs:18:1-16])
+
+(AK ListComprehensions.hs:(18,1)-(22,20) AnnSemi = [ListComprehensions.hs:24:1])
+
+(AK ListComprehensions.hs:(18,20)-(22,20) AnnCloseS = [ListComprehensions.hs:22:20])
+
+(AK ListComprehensions.hs:(18,20)-(22,20) AnnOpenS = [ListComprehensions.hs:18:20])
+
+(AK ListComprehensions.hs:(18,20)-(22,20) AnnVbar = [ListComprehensions.hs:19:20])
+
+(AK ListComprehensions.hs:18:22-26 AnnVal = [ListComprehensions.hs:18:24])
+
+(AK ListComprehensions.hs:18:22-30 AnnVal = [ListComprehensions.hs:18:28])
+
+(AK ListComprehensions.hs:19:22-33 AnnLarrow = [ListComprehensions.hs:19:24-25])
+
+(AK ListComprehensions.hs:19:22-33 AnnVbar = [ListComprehensions.hs:20:20])
+
+(AK ListComprehensions.hs:19:27-33 AnnCloseS = [ListComprehensions.hs:19:33])
+
+(AK ListComprehensions.hs:19:27-33 AnnDotdot = [ListComprehensions.hs:19:29-30])
+
+(AK ListComprehensions.hs:19:27-33 AnnOpenS = [ListComprehensions.hs:19:27])
+
+(AK ListComprehensions.hs:20:22-34 AnnLarrow = [ListComprehensions.hs:20:24-25])
+
+(AK ListComprehensions.hs:20:22-34 AnnVbar = [ListComprehensions.hs:21:20])
+
+(AK ListComprehensions.hs:20:27-34 AnnCloseS = [ListComprehensions.hs:20:34])
+
+(AK ListComprehensions.hs:20:27-34 AnnDotdot = [ListComprehensions.hs:20:30-31])
+
+(AK ListComprehensions.hs:20:27-34 AnnOpenS = [ListComprehensions.hs:20:27])
+
+(AK ListComprehensions.hs:21:22-34 AnnLarrow = [ListComprehensions.hs:21:24-25])
+
+(AK ListComprehensions.hs:21:27-34 AnnCloseS = [ListComprehensions.hs:21:34])
+
+(AK ListComprehensions.hs:21:27-34 AnnDotdot = [ListComprehensions.hs:21:30-31])
+
+(AK ListComprehensions.hs:21:27-34 AnnOpenS = [ListComprehensions.hs:21:27])
+
+(AK ListComprehensions.hs:24:1-27 AnnDcolon = [ListComprehensions.hs:24:8-9])
+
+(AK ListComprehensions.hs:24:1-27 AnnSemi = [ListComprehensions.hs:25:1])
+
+(AK ListComprehensions.hs:24:11-15 AnnCloseS = [ListComprehensions.hs:24:15])
+
+(AK ListComprehensions.hs:24:11-15 AnnOpenS = [ListComprehensions.hs:24:11])
+
+(AK ListComprehensions.hs:24:11-15 AnnRarrow = [ListComprehensions.hs:24:17-18])
+
+(AK ListComprehensions.hs:24:11-27 AnnRarrow = [ListComprehensions.hs:24:17-18])
+
+(AK ListComprehensions.hs:24:20-27 AnnCloseS = [ListComprehensions.hs:24:27])
+
+(AK ListComprehensions.hs:24:20-27 AnnOpenS = [ListComprehensions.hs:24:20])
+
+(AK ListComprehensions.hs:(25,1)-(28,14) AnnEqual = [ListComprehensions.hs:25:12])
+
+(AK ListComprehensions.hs:(25,1)-(28,14) AnnFunId = [ListComprehensions.hs:25:1-6])
+
+(AK ListComprehensions.hs:(25,1)-(28,14) AnnSemi = [ListComprehensions.hs:29:1])
+
+(AK ListComprehensions.hs:(25,14)-(28,14) AnnCloseS = [ListComprehensions.hs:28:14])
+
+(AK ListComprehensions.hs:(25,14)-(28,14) AnnOpenS = [ListComprehensions.hs:25:14])
+
+(AK ListComprehensions.hs:(25,14)-(28,14) AnnVbar = [ListComprehensions.hs:26:14])
+
+(AK ListComprehensions.hs:26:16-23 AnnComma = [ListComprehensions.hs:27:14])
+
+(AK ListComprehensions.hs:26:16-23 AnnLarrow = [ListComprehensions.hs:26:18-19])
+
+(AK ListComprehensions.hs:(26,16)-(27,22) AnnThen = [ListComprehensions.hs:27:16-19])
+]
+
+EOF: Just SrcSpanPoint ".\\ListComprehensions.hs" 29 1


=====================================
testsuite/tests/ghc-api/annotations/parseTree.stdout-mingw32
=====================================
@@ -0,0 +1,160 @@
+[(AnnotationTuple.hs:14:20, [p], Unit 1),
+ (AnnotationTuple.hs:14:23-29, [p], Unit "hello"),
+ (AnnotationTuple.hs:14:35-37, [p], Unit 6.5),
+ (AnnotationTuple.hs:14:39, [m], ()),
+ (AnnotationTuple.hs:14:41-52, [p], Unit [5, 5, 6, 7]),
+ (AnnotationTuple.hs:16:8, [p], Unit 1),
+ (AnnotationTuple.hs:16:11-17, [p], Unit "hello"),
+ (AnnotationTuple.hs:16:20-22, [p], Unit 6.5),
+ (AnnotationTuple.hs:16:24, [m], ()),
+ (AnnotationTuple.hs:16:25, [m], ()),
+ (AnnotationTuple.hs:16:26, [m], ()), (<no location info>, [m], ())]
+[
+(AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:27:1])
+
+(AK AnnotationTuple.hs:1:1 AnnModule = [AnnotationTuple.hs:3:1-6])
+
+(AK AnnotationTuple.hs:1:1 AnnOpenC = [AnnotationTuple.hs:5:1])
+
+(AK AnnotationTuple.hs:1:1 AnnWhere = [AnnotationTuple.hs:3:30-34])
+
+(AK AnnotationTuple.hs:3:24-28 AnnCloseP = [AnnotationTuple.hs:3:28])
+
+(AK AnnotationTuple.hs:3:24-28 AnnOpenP = [AnnotationTuple.hs:3:24])
+
+(AK AnnotationTuple.hs:6:1-32 AnnAs = [AnnotationTuple.hs:6:28-29])
+
+(AK AnnotationTuple.hs:6:1-32 AnnImport = [AnnotationTuple.hs:6:1-6])
+
+(AK AnnotationTuple.hs:6:1-32 AnnQualified = [AnnotationTuple.hs:6:8-16])
+
+(AK AnnotationTuple.hs:6:1-32 AnnSemi = [AnnotationTuple.hs:7:1])
+
+(AK AnnotationTuple.hs:(8,1)-(11,14) AnnEqual = [AnnotationTuple.hs:8:5])
+
+(AK AnnotationTuple.hs:(8,1)-(11,14) AnnFunId = [AnnotationTuple.hs:8:1-3])
+
+(AK AnnotationTuple.hs:(8,1)-(11,14) AnnSemi = [AnnotationTuple.hs:13:1])
+
+(AK AnnotationTuple.hs:(8,7)-(11,14) AnnIn = [AnnotationTuple.hs:11:7-8])
+
+(AK AnnotationTuple.hs:(8,7)-(11,14) AnnLet = [AnnotationTuple.hs:8:7-9])
+
+(AK AnnotationTuple.hs:9:9-13 AnnEqual = [AnnotationTuple.hs:9:11])
+
+(AK AnnotationTuple.hs:9:9-13 AnnFunId = [AnnotationTuple.hs:9:9])
+
+(AK AnnotationTuple.hs:9:9-13 AnnSemi = [AnnotationTuple.hs:10:9])
+
+(AK AnnotationTuple.hs:10:9-13 AnnEqual = [AnnotationTuple.hs:10:11])
+
+(AK AnnotationTuple.hs:10:9-13 AnnFunId = [AnnotationTuple.hs:10:9])
+
+(AK AnnotationTuple.hs:11:10-14 AnnVal = [AnnotationTuple.hs:11:12])
+
+(AK AnnotationTuple.hs:14:1-72 AnnEqual = [AnnotationTuple.hs:14:5])
+
+(AK AnnotationTuple.hs:14:1-72 AnnFunId = [AnnotationTuple.hs:14:1-3])
+
+(AK AnnotationTuple.hs:14:1-72 AnnSemi = [AnnotationTuple.hs:15:1])
+
+(AK AnnotationTuple.hs:14:7-72 AnnVal = [AnnotationTuple.hs:14:13])
+
+(AK AnnotationTuple.hs:14:19-53 AnnCloseP = [AnnotationTuple.hs:14:53])
+
+(AK AnnotationTuple.hs:14:19-53 AnnOpenP = [AnnotationTuple.hs:14:19])
+
+(AK AnnotationTuple.hs:14:20 AnnComma = [AnnotationTuple.hs:14:21])
+
+(AK AnnotationTuple.hs:14:23-29 AnnComma = [AnnotationTuple.hs:14:33])
+
+(AK AnnotationTuple.hs:14:35-37 AnnComma = [AnnotationTuple.hs:14:38])
+
+(AK AnnotationTuple.hs:14:39 AnnComma = [AnnotationTuple.hs:14:39])
+
+(AK AnnotationTuple.hs:14:41-52 AnnCloseS = [AnnotationTuple.hs:14:52])
+
+(AK AnnotationTuple.hs:14:41-52 AnnOpenS = [AnnotationTuple.hs:14:41])
+
+(AK AnnotationTuple.hs:14:42 AnnComma = [AnnotationTuple.hs:14:43])
+
+(AK AnnotationTuple.hs:14:45 AnnComma = [AnnotationTuple.hs:14:46])
+
+(AK AnnotationTuple.hs:14:48 AnnComma = [AnnotationTuple.hs:14:49])
+
+(AK AnnotationTuple.hs:14:55-72 AnnCloseS = [AnnotationTuple.hs:14:72])
+
+(AK AnnotationTuple.hs:14:55-72 AnnOpenS = [AnnotationTuple.hs:14:55])
+
+(AK AnnotationTuple.hs:14:56-62 AnnComma = [AnnotationTuple.hs:14:63])
+
+(AK AnnotationTuple.hs:14:61-62 AnnCloseP = [AnnotationTuple.hs:14:62])
+
+(AK AnnotationTuple.hs:14:61-62 AnnOpenP = [AnnotationTuple.hs:14:61])
+
+(AK AnnotationTuple.hs:16:1-41 AnnEqual = [AnnotationTuple.hs:16:5])
+
+(AK AnnotationTuple.hs:16:1-41 AnnFunId = [AnnotationTuple.hs:16:1-3])
+
+(AK AnnotationTuple.hs:16:1-41 AnnSemi = [AnnotationTuple.hs:17:1])
+
+(AK AnnotationTuple.hs:16:7-27 AnnCloseP = [AnnotationTuple.hs:16:27])
+
+(AK AnnotationTuple.hs:16:7-27 AnnOpenP = [AnnotationTuple.hs:16:7])
+
+(AK AnnotationTuple.hs:16:8 AnnComma = [AnnotationTuple.hs:16:9])
+
+(AK AnnotationTuple.hs:16:11-17 AnnComma = [AnnotationTuple.hs:16:18])
+
+(AK AnnotationTuple.hs:16:20-22 AnnComma = [AnnotationTuple.hs:16:23])
+
+(AK AnnotationTuple.hs:16:24 AnnComma = [AnnotationTuple.hs:16:24])
+
+(AK AnnotationTuple.hs:16:25 AnnComma = [AnnotationTuple.hs:16:25])
+
+(AK AnnotationTuple.hs:16:26 AnnComma = [AnnotationTuple.hs:16:26])
+
+(AK AnnotationTuple.hs:16:33-41 AnnCloseP = [AnnotationTuple.hs:16:41])
+
+(AK AnnotationTuple.hs:16:33-41 AnnOpenP = [AnnotationTuple.hs:16:33])
+
+(AK AnnotationTuple.hs:16:39-40 AnnCloseP = [AnnotationTuple.hs:16:40])
+
+(AK AnnotationTuple.hs:16:39-40 AnnOpenP = [AnnotationTuple.hs:16:39])
+
+(AK AnnotationTuple.hs:18:1-28 AnnData = [AnnotationTuple.hs:18:1-4])
+
+(AK AnnotationTuple.hs:18:1-28 AnnDcolon = [AnnotationTuple.hs:18:20-21])
+
+(AK AnnotationTuple.hs:18:1-28 AnnFamily = [AnnotationTuple.hs:18:6-11])
+
+(AK AnnotationTuple.hs:18:1-28 AnnSemi = [AnnotationTuple.hs:19:1])
+
+(AK AnnotationTuple.hs:18:23 AnnRarrow = [AnnotationTuple.hs:18:25-26])
+
+(AK AnnotationTuple.hs:18:23-28 AnnRarrow = [AnnotationTuple.hs:18:25-26])
+
+(AK AnnotationTuple.hs:(20,1)-(24,14) AnnFunId = [AnnotationTuple.hs:20:1-5])
+
+(AK AnnotationTuple.hs:(20,1)-(24,14) AnnSemi = [AnnotationTuple.hs:25:1])
+
+(AK AnnotationTuple.hs:(21,7)-(24,14) AnnEqual = [AnnotationTuple.hs:24:7])
+
+(AK AnnotationTuple.hs:(21,7)-(24,14) AnnVbar = [AnnotationTuple.hs:21:7])
+
+(AK AnnotationTuple.hs:21:9-24 AnnComma = [AnnotationTuple.hs:22:7])
+
+(AK AnnotationTuple.hs:21:9-24 AnnLarrow = [AnnotationTuple.hs:21:16-17])
+
+(AK AnnotationTuple.hs:22:9-25 AnnComma = [AnnotationTuple.hs:23:7])
+
+(AK AnnotationTuple.hs:22:9-25 AnnLarrow = [AnnotationTuple.hs:22:16-17])
+
+(AK AnnotationTuple.hs:23:9-24 AnnLarrow = [AnnotationTuple.hs:23:16-17])
+
+(AK AnnotationTuple.hs:26:1-10 AnnDcolon = [AnnotationTuple.hs:26:5-6])
+
+(AK AnnotationTuple.hs:26:1-14 AnnEqual = [AnnotationTuple.hs:26:12])
+]
+
+EOF: Just SrcSpanPoint ".\\AnnotationTuple.hs" 32 1


=====================================
testsuite/tests/ghci/scripts/T9293.stdout-mingw32
=====================================
@@ -12,7 +12,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type
@@ -35,7 +34,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type
@@ -57,7 +55,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type
@@ -81,7 +78,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type


=====================================
testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
=====================================
@@ -13,7 +13,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type


=====================================
testsuite/tests/ghci/scripts/ghci057.stdout-mingw32
=====================================
@@ -12,7 +12,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type
@@ -35,7 +34,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type
@@ -57,7 +55,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type
@@ -81,7 +78,6 @@ other dynamic, non-language, flag settings:
   -fimplicit-import-qualified
   -fshow-warning-groups
 warning settings:
-  -Wmissing-monadfail-instances
   -Wsemigroup
   -Wnoncanonical-monoid-instances
   -Wstar-is-type


=====================================
utils/fs/fs.h
=====================================
@@ -37,6 +37,13 @@ int FS(_stat) (const char *path, struct _stat *buffer);
 int FS(_stat64) (const char *path, struct __stat64 *buffer);
 int FS(_wstat) (const wchar_t *path, struct _stat *buffer);
 int FS(_wstat64) (const wchar_t *path, struct __stat64 *buffer);
+int FS(_wrename) (const wchar_t *from, const wchar_t *to);
+int FS(rename) (const char *from, const char *to);
+int FS(unlink) (const char *filename);
+int FS(_unlink) (const char *filename);
+int FS(_wunlink) (const wchar_t *filename);
+int FS(remove) (const char *path);
+int FS(_wremove) (const wchar_t *path);
 #else
 
 FILE *FS(fopen) (const char* filename, const char* mode);


=====================================
utils/hsc2hs
=====================================
@@ -1 +1 @@
-Subproject commit 4089deb3295c28d6bca7d67322b408469a6f6496
+Subproject commit dff4ed1acf9ebbdd004fc833a474dc8c16a90f5b



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de104b898ae6f9a5a500195fea2c67cfe782265c...cc480cdcca610621429ca091869af10be8f415f7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de104b898ae6f9a5a500195fea2c67cfe782265c...cc480cdcca610621429ca091869af10be8f415f7
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/20200324/56ef7f84/attachment-0001.html>


More information about the ghc-commits mailing list