[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Hadrian: enable GHCi support on riscv64

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Wed Jul 12 09:44:24 UTC 2023



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


Commits:
dd38aca9 by Andreas Schwab at 2023-07-11T13:55:56+00:00
Hadrian: enable GHCi support on riscv64

- - - - -
c4264e95 by Josh Meredith at 2023-07-12T05:44:13-04:00
JavaScript: support unicode code points > 2^16 in toJSString using String.fromCodePoint (#23628)

- - - - -
531da2bb by Matthew Pickering at 2023-07-12T05:44:13-04:00
Remove references to make build system in mk/build.mk

Fixes #23636

- - - - -
7a61593b by sheaf at 2023-07-12T05:44:16-04:00
Valid hole fits: don't panic on a Given

The function GHC.Tc.Errors.validHoleFits would end up panicking when
encountering a Given constraint. To fix this, it suffices to filter out
the Givens before continuing.

Fixes #22684

- - - - -


10 changed files:

- .gitlab/ci.sh
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Types.hs
- hadrian/src/Oracles/Setting.hs
- rts/js/string.js
- testsuite/tests/javascript/js-ffi-string.hs
- testsuite/tests/javascript/js-ffi-string.stdout
- + testsuite/tests/typecheck/should_fail/T22684.hs
- + testsuite/tests/typecheck/should_fail/T22684.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -75,16 +75,6 @@ Environment variables affecting both build systems:
                     (either "x86-64-darwin" or "aarch-darwin")
   NO_BOOT           Whether to run ./boot or not, used when testing the source dist
 
-Environment variables determining build configuration of Make system:
-
-  BUILD_FLAVOUR     Which flavour to build.
-  BUILD_SPHINX_HTML Whether to build Sphinx HTML documentation.
-  BUILD_SPHINX_PDF  Whether to build Sphinx PDF documentation.
-  INTEGER_LIBRARY   Which integer library to use (integer-simple or integer-gmp).
-  HADDOCK_HYPERLINKED_SOURCES
-                    Whether to build hyperlinked Haddock sources.
-  TEST_TYPE         Which test rule to run.
-
 Environment variables determining build configuration of Hadrian system:
 
   BUILD_FLAVOUR     Which flavour to build.
@@ -390,26 +380,6 @@ function cleanup_submodules() {
   end_section "clean submodules"
 }
 
-function prepare_build_mk() {
-  if [[ -z "$BUILD_FLAVOUR" ]]; then fail "BUILD_FLAVOUR is not set"; fi
-  if [[ -z ${BUILD_SPHINX_HTML:-} ]]; then BUILD_SPHINX_HTML=YES; fi
-  if [[ -z ${BUILD_SPHINX_PDF:-} ]]; then BUILD_SPHINX_PDF=YES; fi
-
-  cat > mk/build.mk <<EOF
-BIGNUM_BACKEND=${BIGNUM_BACKEND}
-include mk/flavours/${BUILD_FLAVOUR}.mk
-GhcLibHcOpts+=-haddock
-EOF
-
-  if [ -n "${HADDOCK_HYPERLINKED_SOURCES:-}" ]; then
-    echo "EXTRA_HADDOCK_OPTS += --hyperlinked-source --quickjump" >> mk/build.mk
-  fi
-
-
-  info "build.mk is:"
-  cat mk/build.mk
-}
-
 function configure() {
   case "${CONFIGURE_WRAPPER:-}" in
     emconfigure) source "$EMSDK/emsdk_env.sh" ;;


=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -1563,16 +1563,19 @@ validHoleFits :: SolverReportErrCtxt    -- ^ The context we're in, i.e. the
                 -- the valid hole fits.
 validHoleFits ctxt@(CEC { cec_encl = implics
                         , cec_tidy = lcl_env}) simps hole
-  = do { (tidy_env, fits) <- findValidHoleFits lcl_env implics (map mk_wanted simps) hole
+  = do { (tidy_env, fits) <- findValidHoleFits lcl_env implics (mapMaybe mk_wanted simps) hole
        ; return (ctxt {cec_tidy = tidy_env}, fits) }
   where
-    mk_wanted :: ErrorItem -> CtEvidence
-    mk_wanted (EI { ei_pred = pred, ei_evdest = Just dest, ei_loc = loc })
-         = CtWanted { ctev_pred      = pred
-                    , ctev_dest      = dest
-                    , ctev_loc       = loc
-                    , ctev_rewriters = emptyRewriterSet }
-    mk_wanted item = pprPanic "validHoleFits no evdest" (ppr item)
+    mk_wanted :: ErrorItem -> Maybe CtEvidence
+    mk_wanted (EI { ei_pred = pred, ei_evdest = m_dest, ei_loc = loc })
+      | Just dest <- m_dest
+      = Just (CtWanted { ctev_pred      = pred
+                       , ctev_dest      = dest
+                       , ctev_loc       = loc
+                       , ctev_rewriters = emptyRewriterSet })
+      | otherwise
+      = Nothing   -- The ErrorItem was a Given
+
 
 -- See Note [Constraints include ...]
 givenConstraints :: SolverReportErrCtxt -> [(Type, RealSrcSpan)]


=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -4867,7 +4867,9 @@ data ErrorItem
   = EI { ei_pred     :: PredType         -- report about this
          -- The ei_pred field will never be an unboxed equality with
          -- a (casted) tyvar on the right; this is guaranteed by the solver
-       , ei_evdest   :: Maybe TcEvDest   -- for Wanteds, where to put evidence
+       , ei_evdest   :: Maybe TcEvDest
+         -- ^ for Wanteds, where to put the evidence
+         --   for Givens, Nothing
        , ei_flavour  :: CtFlavour
        , ei_loc      :: CtLoc
        , ei_m_reason :: Maybe CtIrredReason  -- if this ErrorItem was made from a


=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -302,7 +302,8 @@ ghcWithInterpreter = do
                           , "darwin", "kfreebsdgnu" ]
     goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc"
                               , "arm", "aarch64", "s390x"
-                              , "powerpc64", "powerpc64le" ]
+                              , "powerpc64", "powerpc64le"
+                              , "riscv64" ]
     return $ goodOs && goodArch
 
 -- | Variants of the ARM architecture.


=====================================
rts/js/string.js
=====================================
@@ -628,7 +628,7 @@ function h$fromHsString(str) {
     var xs = '';
     while(IS_CONS(str)) {
 	var h = CONS_HEAD(str);
-	xs += String.fromCharCode(UNWRAP_NUMBER(h));
+	xs += String.fromCodePoint(UNWRAP_NUMBER(h));
         str = CONS_TAIL(str);
     }
     return xs;


=====================================
testsuite/tests/javascript/js-ffi-string.hs
=====================================
@@ -1,13 +1,49 @@
 import GHC.JS.Prim
+import System.IO
 
 foreign import javascript "((x) => { console.log(x); })"
   log_js_string :: JSVal -> IO ()
 
-foreign import javascript "(() => { return 'a string'; })"
-  a_string :: JSVal
+foreign import javascript "((x, y) => { return x === y; })"
+  eq_JSVal :: JSVal -> JSVal -> Bool
+
+foreign import javascript "(() => { return 'abc\\uD83D\\uDE0A'; })"
+  js_utf16_string :: JSVal
+foreign import javascript "(() => { return 'abc' + String.fromCodePoint(128522); })"
+  js_codepoint_string :: JSVal
+
+-- It's important that this String is defined using a function to avoid rewrite
+-- rules optimising away the use of `toJSString` called on a literal.
+hsString :: String
+hsString = "abc" ++ "\128522"
 
 main :: IO ()
 main = do
-  log_js_string (toJSString "test")
-  putStrLn (fromJSString a_string)
-  putStrLn (fromJSString $ toJSString "test")
+  putStrLn "Does JS `String.fromCodePoint` decode to the expected UTF-16 values? "
+  print (eq_JSVal js_utf16_string js_codepoint_string)
+  hFlush stdout
+  log_js_string js_utf16_string
+  log_js_string js_codepoint_string
+
+  putStrLn "\nDoes `GHC.JS.fromJSString` convert the JavaScript literal string correctly? "
+  print (hsString == fromJSString js_utf16_string)
+  putStrLn hsString
+  putStrLn (fromJSString js_utf16_string)
+
+  putStrLn "\nDoes `GHC.JS.toJSString` convert the Haskell-defined string correctly? "
+  print (eq_JSVal js_utf16_string (toJSString hsString))
+  hFlush stdout
+  log_js_string js_utf16_string
+  log_js_string (toJSString hsString)
+
+  putStrLn "\nDo values survive the Haskell -> JavaScript -> Haskell round-trip? "
+  print (hsString == fromJSString (toJSString hsString))
+  putStrLn hsString
+  putStrLn (fromJSString js_utf16_string)
+
+  putStrLn "\nDo values survive the JavaScript -> Haskell -> JavaScript round-trip? "
+  print (eq_JSVal js_utf16_string (toJSString $ fromJSString js_utf16_string))
+  hFlush stdout
+  log_js_string js_utf16_string
+  log_js_string (toJSString $ fromJSString js_utf16_string)
+


=====================================
testsuite/tests/javascript/js-ffi-string.stdout
=====================================
@@ -1,3 +1,25 @@
-test
-a string
-test
+Does JS `String.fromCodePoint` decode to the expected UTF-16 values? 
+True
+abc😊
+abc😊
+
+Does `GHC.JS.fromJSString` convert the JavaScript literal string correctly? 
+True
+abc😊
+abc😊
+
+Does `GHC.JS.toJSString` convert the Haskell-defined string correctly? 
+True
+abc😊
+abc😊
+
+Do values survive the Haskell -> JavaScript -> Haskell round-trip? 
+True
+abc😊
+abc😊
+
+Do values survive the JavaScript -> Haskell -> JavaScript round-trip? 
+True
+abc😊
+abc😊
+


=====================================
testsuite/tests/typecheck/should_fail/T22684.hs
=====================================
@@ -0,0 +1,19 @@
+module T22684 where
+
+-- Example 1 from #22684
+p :: (Int ~ Bool => r) -> r
+p _ = undefined
+
+q :: r
+q = p _
+
+-- Example 3 from #22684
+class Category k where
+  (.) :: k b c -> k a b -> k a c
+
+data Free p a b where
+  Prod :: Free p a (b, c)
+  Sum  :: Free p (Either a b) c
+
+instance Category (Free p) where
+  Sum . Prod = _


=====================================
testsuite/tests/typecheck/should_fail/T22684.stderr
=====================================
@@ -0,0 +1,35 @@
+
+T22684.hs:8:7: error: [GHC-88464]
+    • Found hole: _ :: r
+      Where: ‘r’ is a rigid type variable bound by
+               the type signature for:
+                 q :: forall r. r
+               at T22684.hs:7:1-6
+    • In the first argument of ‘p’, namely ‘_’
+      In the expression: p _
+      In an equation for ‘q’: q = p _
+    • Relevant bindings include q :: r (bound at T22684.hs:8:1)
+      Constraints include Int ~ Bool (from T22684.hs:8:7)
+      Valid hole fits include q :: r (bound at T22684.hs:8:1)
+
+T22684.hs:19:16: error: [GHC-88464]
+    • Found hole: _ :: Free p a c
+      Where: ‘k’, ‘p’ are rigid type variables bound by
+               the instance declaration
+               at T22684.hs:18:10-26
+             ‘a’, ‘c’ are rigid type variables bound by
+               the type signature for:
+                 (T22684..) :: forall b c a. Free p b c -> Free p a b -> Free p a c
+               at T22684.hs:19:7
+    • In an equation for ‘T22684..’: Sum T22684.. Prod = _
+      In the instance declaration for ‘Category (Free p)’
+    • Relevant bindings include
+        (.) :: Free p b c -> Free p a b -> Free p a c
+          (bound at T22684.hs:19:7)
+      Constraints include
+        b ~ (b2, c1) (from T22684.hs:19:9-12)
+        b ~ Either a1 b1 (from T22684.hs:19:3-5)
+      Valid hole fits include
+        q :: forall r. r
+          with q @(Free p a c)
+          (bound at T22684.hs:8:1)


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -696,4 +696,5 @@ test('VisFlag2', normal, compile_fail, [''])
 test('VisFlag3', normal, compile_fail, [''])
 test('VisFlag4', normal, compile_fail, [''])
 test('VisFlag5', normal, compile_fail, [''])
+test('T22684', normal, compile_fail, [''])
 test('T23514a', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f897f6908cc970f35fbbdf101bfc57bd55ab9248...7a61593be51d23938fcdbd702ad5aab1a4cd2107

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f897f6908cc970f35fbbdf101bfc57bd55ab9248...7a61593be51d23938fcdbd702ad5aab1a4cd2107
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/20230712/910f4712/attachment-0001.html>


More information about the ghc-commits mailing list