[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: JS: Implement missing C functions `rename`, `realpath`, and `getcwd` (#23806)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Aug 31 00:44:40 UTC 2023



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


Commits:
d07080d2 by Josh Meredith at 2023-08-30T19:42:32-04:00
JS: Implement missing C functions `rename`, `realpath`, and `getcwd` (#23806)

- - - - -
e2940272 by David Binder at 2023-08-30T19:43:08-04:00
Bump submodules of hpc and hpc-bin to version 0.7.0.0

hpc 0.7.0.0 dropped SafeHaskell safety guarantees in order to simplify
compatibility with newer versions of the directory package which
dropped all SafeHaskell guarantees.

- - - - -
5d56d05c by David Binder at 2023-08-30T19:43:08-04:00
Bump hpc bound in ghc.cabal.in

- - - - -
c959d579 by Dominik Schrempf at 2023-08-30T20:44:30-04:00
ghc classes documentation: rm redundant comment

- - - - -
4d220259 by Dominik Schrempf at 2023-08-30T20:44:30-04:00
prelude documentation: various nits

- - - - -
4a0d5e43 by Dominik Schrempf at 2023-08-30T20:44:30-04:00
integer documentation: minor corrections

- - - - -
fa9e324a by Dominik Schrempf at 2023-08-30T20:44:30-04:00
real documentation: nits

- - - - -
804d5e88 by sheaf at 2023-08-30T20:44:34-04:00
Add a test for #21765

This issue (of reporting a constraint as being redundant even though
removing it causes typechecking to fail) was fixed in aed1974e.
This commit simply adds a regression test.

Fixes #21765

- - - - -


13 changed files:

- compiler/ghc.cabal.in
- libraries/base/Data/Tuple.hs
- libraries/base/GHC/Enum.hs
- libraries/base/GHC/Real.hs
- libraries/base/jsbits/base.js
- libraries/ghc-bignum/src/GHC/Num/Integer.hs
- libraries/ghc-prim/GHC/Classes.hs
- libraries/hpc
- testsuite/tests/ghc-api/downsweep/all.T
- testsuite/tests/rename/prog006/all.T
- + testsuite/tests/typecheck/should_compile/T21765.hs
- testsuite/tests/typecheck/should_compile/all.T
- utils/hpc


Changes:

=====================================
compiler/ghc.cabal.in
=====================================
@@ -105,7 +105,7 @@ Library
                    array      >= 0.1 && < 0.6,
                    filepath   >= 1   && < 1.5,
                    template-haskell == 2.21.*,
-                   hpc        == 0.6.*,
+                   hpc        >= 0.6 && < 0.8,
                    transformers >= 0.5 && < 0.7,
                    exceptions == 0.10.*,
                    semaphore-compat,


=====================================
libraries/base/Data/Tuple.hs
=====================================
@@ -41,7 +41,7 @@ fst (x,_)               =  x
 snd                     :: (a,b) -> b
 snd (_,y)               =  y
 
--- | 'curry' converts an uncurried function to a curried function.
+-- | Convert an uncurried function to a curried function.
 --
 -- ==== __Examples__
 --


=====================================
libraries/base/GHC/Enum.hs
=====================================
@@ -82,9 +82,9 @@ class  Bounded a  where
 -- >              | otherwise                = minBound
 --
 class  Enum a   where
-    -- | the successor of a value.  For numeric types, 'succ' adds 1.
+    -- | Successor of a value. For numeric types, 'succ' adds 1.
     succ                :: a -> a
-    -- | the predecessor of a value.  For numeric types, 'pred' subtracts 1.
+    -- | Predecessor of a value. For numeric types, 'pred' subtracts 1.
     pred                :: a -> a
     -- | Convert from an 'Int'.
     toEnum              :: Int -> a
@@ -92,11 +92,10 @@ class  Enum a   where
     -- It is implementation-dependent what 'fromEnum' returns when
     -- applied to a value that is too large to fit in an 'Int'.
     fromEnum            :: a -> Int
-
     -- | Used in Haskell's translation of @[n..]@ with @[n..] = enumFrom n@,
     --   a possible implementation being @enumFrom n = n : enumFrom (succ n)@.
-    --   For example:
     --
+    --   ==== __Examples__
     --     * @enumFrom 4 :: [Integer] = [4,5,6,7,...]@
     --     * @enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]@
     enumFrom            :: a -> [a]
@@ -104,22 +103,28 @@ class  Enum a   where
     --   with @[n,n'..] = enumFromThen n n'@, a possible implementation being
     --   @enumFromThen n n' = n : n' : worker (f x) (f x n')@,
     --   @worker s v = v : worker s (s v)@, @x = fromEnum n' - fromEnum n@ and
-    --   @f n y
+    --
+    --   @
+    --   f n y
     --     | n > 0 = f (n - 1) (succ y)
     --     | n < 0 = f (n + 1) (pred y)
-    --     | otherwise = y@
-    --   For example:
+    --     | otherwise = y
+    --   @
     --
+    --   ==== __Examples__
     --     * @enumFromThen 4 6 :: [Integer] = [4,6,8,10...]@
     --     * @enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]@
     enumFromThen        :: a -> a -> [a]
     -- | Used in Haskell's translation of @[n..m]@ with
     --   @[n..m] = enumFromTo n m@, a possible implementation being
-    --   @enumFromTo n m
+    --
+    --   @
+    --   enumFromTo n m
     --      | n <= m = n : enumFromTo (succ n) m
-    --      | otherwise = []@.
-    --   For example:
+    --      | otherwise = []
+    --   @
     --
+    --   ==== __Examples__
     --     * @enumFromTo 6 10 :: [Int] = [6,7,8,9,10]@
     --     * @enumFromTo 42 1 :: [Integer] = []@
     enumFromTo          :: a -> a -> [a]
@@ -127,15 +132,23 @@ class  Enum a   where
     --   @[n,n'..m] = enumFromThenTo n n' m@, a possible implementation
     --   being @enumFromThenTo n n' m = worker (f x) (c x) n m@,
     --   @x = fromEnum n' - fromEnum n@, @c x = bool (>=) (<=) (x > 0)@
-    --   @f n y
+    --
+    --   @
+    --   f n y
     --      | n > 0 = f (n - 1) (succ y)
     --      | n < 0 = f (n + 1) (pred y)
-    --      | otherwise = y@ and
-    --   @worker s c v m
+    --      | otherwise = y
+    --   @
+    --
+    --   and
+    --
+    --   @
+    --   worker s c v m
     --      | c v m = v : worker s c (s v) m
-    --      | otherwise = []@
-    --   For example:
+    --      | otherwise = []
+    --   @
     --
+    --   ==== __Examples__
     --     * @enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]@
     --     * @enumFromThenTo 6 8 2 :: [Int] = []@
     enumFromThenTo      :: a -> a -> a -> [a]


=====================================
libraries/base/GHC/Real.hs
=====================================
@@ -212,7 +212,7 @@ denominator (_ :% y)    =  y
 -- 'Foreign.C.Types.CDouble', etc., because these types contain non-finite values,
 -- which cannot be roundtripped through 'Rational'.
 class  (Num a, Ord a) => Real a  where
-    -- | the rational equivalent of its real argument with full precision
+    -- | Rational equivalent of its real argument with full precision.
     toRational          ::  a -> Rational
 
 -- | Integral numbers, supporting integer division.
@@ -233,41 +233,41 @@ class  (Num a, Ord a) => Real a  where
 -- In addition, 'toInteger` should be total, and 'fromInteger' should be a left
 -- inverse for it, i.e. @fromInteger (toInteger i) = i at .
 class  (Real a, Enum a) => Integral a  where
-    -- | integer division truncated toward zero
+    -- | Integer division truncated toward zero.
     --
     -- WARNING: This function is partial (because it throws when 0 is passed as
     -- the divisor) for all the integer types in @base at .
     quot                :: a -> a -> a
-    -- | integer remainder, satisfying
+    -- | Integer remainder, satisfying
     --
     -- > (x `quot` y)*y + (x `rem` y) == x
     --
     -- WARNING: This function is partial (because it throws when 0 is passed as
     -- the divisor) for all the integer types in @base at .
     rem                 :: a -> a -> a
-    -- | integer division truncated toward negative infinity
+    -- | Integer division truncated toward negative infinity.
     --
     -- WARNING: This function is partial (because it throws when 0 is passed as
     -- the divisor) for all the integer types in @base at .
     div                 :: a -> a -> a
-    -- | integer modulus, satisfying
+    -- | Integer modulus, satisfying
     --
     -- > (x `div` y)*y + (x `mod` y) == x
     --
     -- WARNING: This function is partial (because it throws when 0 is passed as
     -- the divisor) for all the integer types in @base at .
     mod                 :: a -> a -> a
-    -- | simultaneous 'quot' and 'rem'
+    -- | Simultaneous 'quot' and 'rem'.
     --
     -- WARNING: This function is partial (because it throws when 0 is passed as
     -- the divisor) for all the integer types in @base at .
     quotRem             :: a -> a -> (a,a)
-    -- | simultaneous 'div' and 'mod'
+    -- | simultaneous 'div' and 'mod'.
     --
     -- WARNING: This function is partial (because it throws when 0 is passed as
     -- the divisor) for all the integer types in @base at .
     divMod              :: a -> a -> (a,a)
-    -- | conversion to 'Integer'
+    -- | Conversion to 'Integer'.
     toInteger           :: a -> Integer
 
     {-# INLINE quot #-}


=====================================
libraries/base/jsbits/base.js
=====================================
@@ -280,6 +280,59 @@ function h$rmdir(file, file_off) {
     h$unsupported(-1);
 }
 
+function h$rename(old_path, old_path_off, new_path, new_path_off) {
+  TRACE_IO("rename")
+#ifndef GHCJS_BROWSER
+  if (h$isNode()) {
+    try {
+      fs.renameSync(h$decodeUtf8z(old_path, old_path_off), h$decodeUtf8z(new_path, new_path_off));
+      return 0;
+    } catch(e) {
+      h$setErrno(e);
+      return -1;
+    }
+  } else
+#endif
+    h$unsupported(-1);
+}
+
+function h$getcwd(buf, off, buf_size) {
+  TRACE_IO("getcwd")
+#ifndef GHCJS_BROWSER
+  if (h$isNode()) {
+    try {
+      var cwd = h$encodeUtf8(process.cwd());
+      h$copyMutableByteArray(cwd, 0, buf, off, cwd.len);
+      RETURN_UBX_TUP2(cwd, 0);
+    } catch (e) {
+      h$setErrno(e);
+      return -1;
+    }
+  } else
+#endif
+    h$unsupported(-1);
+}
+
+function h$realpath(path,off,resolved,resolved_off) {
+  TRACE_IO("realpath")
+#ifndef GHCJS_BROWSER
+  if (h$isNode()) {
+    try {
+      var rp = h$encodeUtf8(fs.realpathSync(h$decodeUtf8z(path,off)));
+      if (resolved !== null) {
+        h$copyMutableByteArray(rp, 0, resolved, resolved_off, Math.min(resolved.len - resolved_off, rp.len));
+        RETURN_UBX_TUP2(resolved, resolved_off);
+      }
+      RETURN_UBX_TUP2(rp, 0);
+    } catch (e) {
+      h$setErrno(e);
+      return -1;
+    }
+  } else
+#endif
+    h$unsupported(-1);
+}
+
 function h$base_open(file, file_off, how, mode, c) {
   return h$open(file,file_off,how,mode,c);
 }


=====================================
libraries/ghc-bignum/src/GHC/Num/Integer.hs
=====================================
@@ -167,11 +167,11 @@ default ()
 -- Integers are stored in a kind of sign-magnitude form, hence do not expect
 -- two's complement form when using bit operations.
 --
--- If the value is small (fit into an 'Int'), 'IS' constructor is used.
--- Otherwise 'IP' and 'IN' constructors are used to store a 'BigNat'
--- representing respectively the positive or the negative value magnitude.
+-- If the value is small (i.e., fits into an 'Int'), the 'IS' constructor is
+-- used. Otherwise 'IP' and 'IN' constructors are used to store a 'BigNat'
+-- representing the positive or the negative value magnitude, respectively.
 --
--- Invariant: 'IP' and 'IN' are used iff value doesn't fit in 'IS'
+-- Invariant: 'IP' and 'IN' are used iff the value does not fit in 'IS'.
 data Integer
    = IS !Int#    -- ^ iff value in @[minBound::'Int', maxBound::'Int']@ range
    | IP !BigNat# -- ^ iff value in @]maxBound::'Int', +inf[@ range


=====================================
libraries/ghc-prim/GHC/Classes.hs
=====================================
@@ -141,9 +141,6 @@ and @('>=')@ for the types in "GHC.Word" and "GHC.Int".
 -- [__Extensionality__]: if @x == y@ = 'True' and @f@ is a function
 -- whose return type is an instance of 'Eq', then @f x == f y@ = 'True'
 -- [__Negation__]: @x /= y@ = @not (x == y)@
---
--- Minimal complete definition: either '==' or '/='.
---
 class  Eq a  where
     (==), (/=)           :: a -> a -> Bool
 


=====================================
libraries/hpc
=====================================
@@ -1 +1 @@
-Subproject commit 50d520bf6002ab55032e233dced0556ad63ad0c0
+Subproject commit 0ad03de570771bb04f383a04886bc58071b50b7b


=====================================
testsuite/tests/ghc-api/downsweep/all.T
=====================================
@@ -7,7 +7,6 @@ test('PartialDownsweep',
 
 test('OldModLocation',
      [ extra_run_opts('"' + config.libdir + '"')
-     , js_broken(22362)
      , when(opsys('mingw32'), expect_broken(16772))
      ],
      compile_and_run,


=====================================
testsuite/tests/rename/prog006/all.T
=====================================
@@ -1 +1 @@
-test('rn.prog006', [extra_files(['A.hs', 'B/', 'Main.hs', 'pwd.hs']), js_broken(22261)], makefile_test, [])
+test('rn.prog006', [extra_files(['A.hs', 'B/', 'Main.hs', 'pwd.hs'])], makefile_test, [])


=====================================
testsuite/tests/typecheck/should_compile/T21765.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE UndecidableInstances, FlexibleInstances #-}
+
+{-# OPTIONS_GHC -Wredundant-constraints #-}
+
+module T21765 where
+
+class Functor f => C f where c :: f Int
+
+instance (Functor f, Applicative f) => C f where c = pure 42


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -847,6 +847,7 @@ test('DeepSubsumption06', normal, compile, ['-XHaskell98'])
 test('DeepSubsumption07', normal, compile, ['-XHaskell2010'])
 test('DeepSubsumption08', normal, compile, [''])
 test('DeepSubsumption09', normal, compile, [''])
+test('T21765', normal, compile, [''])
 test('T21951a', normal, compile, ['-Wredundant-strictness-flags'])
 test('T21951b', normal, compile, ['-Wredundant-strictness-flags'])
 test('T21550', normal, compile, [''])


=====================================
utils/hpc
=====================================
@@ -1 +1 @@
-Subproject commit eb800fe76409f54660335496592f777ae215ff92
+Subproject commit 2d75eb33d4c179b1c21000d32c2906ad273de0de



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/03460ad9836414e98ac36ab61ed781f4ce468758...804d5e88e7598ce6a42916179c227aa74e89c0e3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/03460ad9836414e98ac36ab61ed781f4ce468758...804d5e88e7598ce6a42916179c227aa74e89c0e3
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/20230830/539c0796/attachment-0001.html>


More information about the ghc-commits mailing list