[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: JS: Fix h$base_access implementation (issue 22576)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Apr 25 19:52:39 UTC 2023



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


Commits:
ba9a456a by Josh Meredith at 2023-04-25T15:52:28-04:00
JS: Fix h$base_access implementation (issue 22576)

- - - - -
743cd728 by Andrei Borzenkov at 2023-04-25T15:52:33-04:00
Give more guarntees about ImplicitParams (#23289)

- Added new section in the GHC user's guide that legends behavior of
nested implicit parameter bindings in these two cases:

  let ?f = 1 in let ?f = 2 in ?f

and

  data T where MkT :: (?f :: Int) => T

  f :: T -> T -> Int
  f MkT MkT = ?f

- Added new test case to examine this behavior.

- - - - -


9 changed files:

- docs/users_guide/exts/implicit_parameters.rst
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/base/jsbits/base.js
- testsuite/tests/ado/all.T
- testsuite/tests/rep-poly/all.T
- + testsuite/tests/simplCore/should_run/T23289.hs
- + testsuite/tests/simplCore/should_run/T23289.stdout
- testsuite/tests/simplCore/should_run/all.T
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
docs/users_guide/exts/implicit_parameters.rst
=====================================
@@ -180,6 +180,27 @@ parameter. So we get the following results in GHCi:
 Adding a type signature dramatically changes the result! This is a
 rather counter-intuitive phenomenon, worth watching out for.
 
+Implicit parameters scoping guarantees
+-------------------------------------
+
+GHC always takes the most nested implicit parameter binding from the
+context to find the value. Consider the following code::
+
+      let ?f = 1 in let ?f = 2 in ?f
+
+This expression will always return 2.
+
+Another example of this rule is matching over constructors with constraints.
+For example::
+
+      data T where
+        MkT :: (?f :: Int) => T
+
+      f :: T -> T -> Int
+      f MkT MkT = ?f
+
+Here GHC will always take ``?f`` from the last match.
+
 Implicit parameters and monomorphism
 ------------------------------------
 
@@ -199,5 +220,3 @@ a type signature for ``y``, then ``y`` will get type
 ``(?x::Int) => Int``, so the occurrence of ``y`` in the body of the
 ``let`` will see the inner binding of ``?x``, so ``(f 9)`` will return
 ``14``.
-
-


=====================================
hadrian/src/Settings/Builders/RunTest.hs
=====================================
@@ -105,7 +105,11 @@ inTreeCompilerArgs stg = do
     tables_next_to_code <- flag TablesNextToCode
     targetWithSMP       <- targetSupportsSMP
 
-    let ghcStage = succStage stg
+    cross <- flag CrossCompiling
+
+    let ghcStage
+          | cross, Stage1 <- stg = Stage1
+          | otherwise = succStage stg
     debugAssertions     <- ghcDebugAssertions <$> flavour <*> pure ghcStage
     debugged            <- ghcDebugged        <$> flavour <*> pure ghcStage
     profiled            <- ghcProfiled        <$> flavour <*> pure ghcStage


=====================================
libraries/base/jsbits/base.js
=====================================
@@ -14,11 +14,11 @@ function h$base_access(file, file_off, mode, c) {
     TRACE_IO("base_access")
 #ifndef GHCJS_BROWSER
     if(h$isNode()) {
-        h$fs.stat(fd, function(err, fs) {
-            if(err) {
+        h$fs.access(h$decodeUtf8z(file, file_off), mode, function(err) {
+            if (err) {
                 h$handleErrnoC(err, -1, 0, c);
             } else {
-                c(mode & fs.mode); // fixme is this ok?
+                c(0);
             }
         });
     } else


=====================================
testsuite/tests/ado/all.T
=====================================
@@ -20,5 +20,5 @@ test('T15344', normal, compile_and_run, [''])
 test('T16628', normal, compile_fail, [''])
 test('T17835', normal, compile, [''])
 test('T20540', normal, compile, [''])
-test('T16135', [when(compiler_debugged(),expect_broken(16135)), js_broken(22576)], compile_fail, [''])
+test('T16135', [when(compiler_debugged(),expect_broken(16135))], compile_fail, [''])
 test('T22483', normal, compile, ['-Wall'])


=====================================
testsuite/tests/rep-poly/all.T
=====================================
@@ -85,7 +85,7 @@ test('RepPolyUnliftedNewtype', normal, compile,
      ['-fno-warn-partial-type-signatures -fno-warn-deprecated-flags'])
 test('RepPolyWildcardPattern', normal, compile_fail, [''])
 test('RepPolyWrappedVar', normal, compile_fail, [''])
-test('RepPolyWrappedVar2', js_broken(22576), compile, [''])
+test('RepPolyWrappedVar2', js_broken(23280), compile, [''])
 test('UnliftedNewtypesCoerceFail', normal, compile_fail, [''])
 test('UnliftedNewtypesLevityBinder', normal, compile_fail, [''])
 


=====================================
testsuite/tests/simplCore/should_run/T23289.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE ImplicitParams, GADTs #-}
+module Main where
+
+data T where
+  MkT :: (?f :: Int) => T
+
+f :: T -> T -> Int
+f MkT MkT = ?f
+
+main :: IO ()
+main = do
+  print (let ?g = 1 in let ?g = 2 in ?g)
+  print $ f (let ?f = 3 in MkT) (let ?f = 4 in MkT)


=====================================
testsuite/tests/simplCore/should_run/T23289.stdout
=====================================
@@ -0,0 +1,2 @@
+2
+4


=====================================
testsuite/tests/simplCore/should_run/all.T
=====================================
@@ -111,3 +111,4 @@ test('T22448', normal, compile_and_run, ['-O1'])
 test('T22998', normal, compile_and_run, ['-O0 -fspecialise -dcore-lint'])
 test('T23184', normal, compile_and_run, ['-O'])
 test('T23134', normal, compile_and_run, ['-O0 -fcatch-nonexhaustive-cases'])
+test('T23289', normal, compile_and_run, [''])


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -328,7 +328,7 @@ test('T8262', normal, compile_fail, [''])
 
 # TcCoercibleFail times out with the compiler is compiled with -DDEBUG.
 # This is expected (see comment in source file).
-test('TcCoercibleFail', [when(compiler_debugged(), skip), js_broken(22576)], compile_fail, [''])
+test('TcCoercibleFail', [when(compiler_debugged(), skip)], compile_fail, [''])
 
 test('TcCoercibleFail2', [], compile_fail, [''])
 test('TcCoercibleFail3', [], compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8139a1666277d880c3a3fa57f503fae3f19e5a88...743cd728239f8775fab8d6f7d5638247a32d1031

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8139a1666277d880c3a3fa57f503fae3f19e5a88...743cd728239f8775fab8d6f7d5638247a32d1031
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/20230425/4773e8da/attachment-0001.html>


More information about the ghc-commits mailing list