[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Add @since annotation to Data.Data.mkConstrTag

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Feb 20 02:08:06 UTC 2024



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


Commits:
249caf0d by Matthew Craven at 2024-02-19T20:36:09-05:00
Add @since annotation to Data.Data.mkConstrTag

- - - - -
cdd939e7 by Jade at 2024-02-19T20:36:46-05:00
Enhance documentation of Data.Complex

- - - - -
5c70df45 by Ben Gamari at 2024-02-19T21:07:53-05:00
hadrian/bindist: Ensure that phony rules are marked as such

Otherwise make may not run the rule if file with the same name as the
rule happens to exist.

- - - - -
dc3e6d85 by Ben Gamari at 2024-02-19T21:07:53-05:00
hadrian: Generate HSC2HS_EXTRAS variable in bindist installation

We must generate the hsc2hs wrapper at bindist installation time since
it must contain `--lflag` and `--cflag` arguments which depend upon the
installation path.

The solution here is to substitute these variables in the configure
script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in
the install rules.

Fixes #24050.

- - - - -
5a9ff4c7 by Matthew Pickering at 2024-02-19T21:07:53-05:00
ci: Show --info for installed compiler

- - - - -
49414a37 by Matthew Pickering at 2024-02-19T21:07:53-05:00
configure: Correctly set --target flag for linker opts

Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4
arguments, when it only takes 3 arguments. Instead we need to use the
`FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags.

Actually fixes #24414

- - - - -
211ff99f by Ian-Woo Kim at 2024-02-19T21:07:59-05:00
mutex wrap in refreshProfilingCCSs

- - - - -


8 changed files:

- .gitlab/ci.sh
- distrib/configure.ac.in
- hadrian/bindist/Makefile
- hadrian/src/Rules/BinaryDist.hs
- libraries/base/src/Data/Complex.hs
- libraries/ghc-internal/src/Data/Data.hs
- + mk/hsc2hs.in
- rts/Profiling.c


Changes:

=====================================
.gitlab/ci.sh
=====================================
@@ -556,6 +556,8 @@ function install_bindist() {
           --prefix="$instdir" \
           "${args[@]+"${args[@]}"}"
       make_install_destdir "$TOP"/destdir "$instdir"
+      # And check the `--info` of the installed compiler, sometimes useful in CI log.
+      "$instdir"/bin/ghc --info
       ;;
   esac
   popd


=====================================
distrib/configure.ac.in
=====================================
@@ -254,8 +254,11 @@ AC_SUBST(TargetHasGnuNonexecStack)
 
 dnl ** See whether cc supports --target=<triple> and set
 dnl CONF_CC_OPTS_STAGE[12] accordingly.
-FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_CXX_OPTS_STAGE1], [CONF_GCC_LINKER_OPTS_STAGE1])
-FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_CXX_OPTS_STAGE2], [CONF_GCC_LINKER_OPTS_STAGE2])
+FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_CXX_OPTS_STAGE1])
+FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_CXX_OPTS_STAGE2])
+
+FP_PROG_CC_LINKER_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_GCC_LINKER_OPTS_STAGE1])
+FP_PROG_CC_LINKER_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_GCC_LINKER_OPTS_STAGE2])
 
 dnl Pass -Qunused-arguments or otherwise GHC will have very noisy invocations of Clang
 FP_CC_IGNORE_UNUSED_ARGS([$CC], [CONF_CC_OPTS_STAGE1])
@@ -325,6 +328,7 @@ FP_SETTINGS
 AC_CONFIG_FILES([config.mk])
 AC_CONFIG_FILES([default.host.target])
 AC_CONFIG_FILES([default.target])
+AC_CONFIG_FILES([mk/hsc2hs])
 AC_OUTPUT
 
 # We get caught by


=====================================
hadrian/bindist/Makefile
=====================================
@@ -55,27 +55,26 @@ endef
 
 # QUESTION : should we use shell commands?
 
-
+.PHONY: show
 show:
 	@echo '$(VALUE)="$($(VALUE))"'
 
 
-.PHONY: install
-
+.PHONY: install_extra
 ifeq "$(EnableDistroToolchain)" "NO"
 install_extra: install_mingw
 else
 install_extra:
 endif
 
+.PHONY: install_bin
 ifeq "$(RelocatableBuild)" "YES"
 install_bin: install_bin_direct
 else
 install_bin: install_bin_libdir install_wrappers
 endif
 
-
-
+.PHONY: install
 install: install_bin install_lib install_extra
 install: install_man install_docs update_package_db
 install: install_data
@@ -146,6 +145,7 @@ lib/settings : config.mk
 
 # We need to install binaries relative to libraries.
 BINARIES = $(wildcard ./bin/*)
+.PHONY: install_bin_libdir
 install_bin_libdir:
 	@echo "Copying binaries to $(DESTDIR)$(ActualBinsDir)"
 	$(INSTALL_DIR) "$(DESTDIR)$(ActualBinsDir)"
@@ -161,11 +161,13 @@ install_bin_libdir:
 		"${XATTR}" -c -r "$(DESTDIR)$(ActualBinsDir)"; \
 	fi
 
+.PHONY: install_bin_direct
 install_bin_direct:
 	@echo "Copying binaries to $(DESTDIR)$(WrapperBinsDir)"
 	$(INSTALL_DIR) "$(DESTDIR)$(WrapperBinsDir)"
 	$(INSTALL_PROGRAM) ./bin/* "$(DESTDIR)$(WrapperBinsDir)/"
 
+.PHONY: install_lib
 install_lib: lib/settings
 	@echo "Copying libraries to $(DESTDIR)$(ActualLibsDir)"
 	$(INSTALL_DIR) "$(DESTDIR)$(ActualLibsDir)"
@@ -196,6 +198,7 @@ install_lib: lib/settings
 		"${XATTR}" -c -r "$(DESTDIR)$(ActualLibsDir)"; \
 	fi
 
+.PHONY: install_docs
 install_docs:
 	@echo "Copying docs to $(DESTDIR)$(docdir)"
 	$(INSTALL_DIR) "$(DESTDIR)$(docdir)"
@@ -233,14 +236,21 @@ install_man:
 	fi
 
 export SHELL
-install_wrappers: install_bin_libdir
+.PHONY: install_wrappers
+install_wrappers: install_bin_libdir install_hsc2hs_wrapper
 	@echo "Installing wrapper scripts"
 	$(INSTALL_DIR) "$(DESTDIR)$(WrapperBinsDir)"
 	for p in `cd wrappers; $(FIND) . ! -type d`; do \
 	    mk/install_script.sh "$$p" "$(DESTDIR)/$(WrapperBinsDir)/$$p" "$(WrapperBinsDir)" "$(ActualBinsDir)" "$(ActualBinsDir)/$$p" "$(ActualLibsDir)" "$(docdir)" "$(includedir)"; \
 	done
 
+.PHONY: install_hsc2hs_wrapper
+install_hsc2hs_wrapper:
+	@echo Copying hsc2hs wrapper
+	cp mk/hsc2hs wrappers/hsc2hs-ghc-$(ProjectVersion)
+
 PKG_CONFS = $(shell find "$(DESTDIR)$(ActualLibsDir)/package.conf.d" -name '*.conf' | sed "s:   :\0xxx\0:g")
+.PHONY: update_package_db
 update_package_db: install_bin install_lib
 	@echo "Installing C++ standard library virtual package"
 	$(INSTALL_DATA) mk/system-cxx-std-lib-1.0.conf "$(DESTDIR)$(ActualLibsDir)/package.conf.d"
@@ -249,6 +259,7 @@ update_package_db: install_bin install_lib
 		$(call patchpackageconf,$(shell echo $(notdir $p) | sed 's/-[0-9.]*-[0-9a-zA-Z]*\.conf//g'),$(shell echo "$p" | sed 's:\0xxx\0:   :g'),$(docdir),$(shell mk/relpath.sh "$(ActualLibsDir)" "$(docdir)"),$(shell echo $(notdir $p) | sed 's/.conf//g')))
 	'$(DESTDIR)$(ActualBinsDir)/$(CrossCompilePrefix)ghc-pkg' --global-package-db "$(DESTDIR)$(ActualLibsDir)/package.conf.d" recache
 
+.PHONY: install_mingw
 install_mingw:
 	@echo "Installing MingGW"
 	$(INSTALL_DIR) "$(DESTDIR)$(prefix)/mingw"


=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -15,8 +15,6 @@ import Target
 import Utilities
 import qualified System.Directory.Extra as IO
 import Data.Either
-import GHC.Toolchain (ccProgram, tgtCCompiler, ccLinkProgram, tgtCCompilerLink)
-import GHC.Toolchain.Program (prgFlags)
 import qualified Data.Set as Set
 import Oracles.Flavour
 
@@ -400,6 +398,7 @@ bindistInstallFiles =
     , "mk" -/- "project.mk"
     , "mk" -/- "relpath.sh"
     , "mk" -/- "system-cxx-std-lib-1.0.conf.in"
+    , "mk" -/- "hsc2hs.in"
     , "mk" -/- "install_script.sh"
     , "README", "INSTALL" ]
 
@@ -464,17 +463,8 @@ haddockWrapper = pure $ "exec \"$executablename\" -B\"$libdir\" -l\"$libdir\" ${
 commonWrapper :: Action String
 commonWrapper = pure $ "exec \"$executablename\" ${1+\"$@\"}\n"
 
--- echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1)) $(addprefix --lflag=,$(CONF_GCC_LINKER_OPTS_STAGE1))"' >> "$(WRAPPER)"
 hsc2hsWrapper :: Action String
-hsc2hsWrapper = do
-  ccArgs <- map ("--cflag=" <>) . prgFlags . ccProgram . tgtCCompiler <$> targetStage Stage1
-  linkFlags <- map ("--lflag=" <>) . prgFlags . ccLinkProgram . tgtCCompilerLink <$> targetStage Stage1
-  wrapper <- drop 4 . lines <$> liftIO (readFile "utils/hsc2hs/hsc2hs.wrapper")
-  return $ unlines
-    ( "HSC2HS_EXTRA=\"" <> unwords (ccArgs ++ linkFlags) <> "\""
-    : "tflag=\"--template=$libdir/template-hsc.h\""
-    : "Iflag=\"-I$includedir/\""
-    : wrapper )
+hsc2hsWrapper = return "Copied from mk/hsc2hs"
 
 runGhcWrapper :: Action String
 runGhcWrapper = pure $ "exec \"$executablename\" -f \"$exedir/ghc\" ${1+\"$@\"}\n"


=====================================
libraries/base/src/Data/Complex.hs
=====================================
@@ -50,17 +50,41 @@ infix  6  :+
 -- -----------------------------------------------------------------------------
 -- The Complex type
 
--- | Complex numbers are an algebraic type.
+-- | A data type representing complex numbers.
 --
--- For a complex number @z@, @'abs' z@ is a number with the magnitude of @z@,
--- but oriented in the positive real direction, whereas @'signum' z@
--- has the phase of @z@, but unit magnitude.
+-- You can read about complex numbers [on wikipedia](https://en.wikipedia.org/wiki/Complex_number).
 --
--- The 'Foldable' and 'Traversable' instances traverse the real part first.
+-- In haskell, complex numbers are represented as @a :+ b@ which can be thought of
+-- as representing \(a + bi\). For a complex number @z@, @'abs' z@ is a number with the 'magnitude' of @z@,
+-- but oriented in the positive real direction, whereas @'signum' z@
+-- has the 'phase' of @z@, but unit 'magnitude'.
+-- Apart from the loss of precision due to IEEE754 floating point numbers,
+-- it holds that @z == 'abs' z * 'signum' z at .
 --
 -- Note that `Complex`'s instances inherit the deficiencies from the type
 -- parameter's. For example, @Complex Float@'s 'Ord' instance has similar
 -- problems to `Float`'s.
+--
+-- As can be seen in the examples, the 'Foldable'
+-- and 'Traversable' instances traverse the real part first.
+--
+-- ==== __Examples__
+--
+-- >>> (5.0 :+ 2.5) + 6.5
+-- 11.5 :+ 2.5
+--
+-- >>> abs (1.0 :+ 1.0) - sqrt 2.0
+-- 0.0 :+ 0.0
+--
+-- >>> abs (signum (4.0 :+ 3.0))
+-- 1.0 :+ 0.0
+--
+-- >>> foldr (:) [] (1 :+ 2)
+-- [1,2]
+--
+-- >>> mapM print (1 :+ 2)
+-- 1
+-- 2
 data Complex a
   = !a :+ !a    -- ^ forms a complex number from its real and imaginary
                 -- rectangular components.
@@ -80,38 +104,113 @@ data Complex a
 -- Functions over Complex
 
 -- | Extracts the real part of a complex number.
+--
+-- ==== __Examples__
+--
+-- >>> realPart (5.0 :+ 3.0)
+-- 5.0
+--
+-- >>> realPart ((5.0 :+ 3.0) * (2.0 :+ 3.0))
+-- 1.0
 realPart :: Complex a -> a
 realPart (x :+ _) =  x
 
 -- | Extracts the imaginary part of a complex number.
+--
+-- ==== __Examples__
+--
+-- >>> imagPart (5.0 :+ 3.0)
+-- 3.0
+--
+-- >>> imagPart ((5.0 :+ 3.0) * (2.0 :+ 3.0))
+-- 21.0
 imagPart :: Complex a -> a
 imagPart (_ :+ y) =  y
 
--- | The conjugate of a complex number.
+-- | The 'conjugate' of a complex number.
+--
+-- prop> conjugate (conjugate x) = x
+--
+-- ==== __Examples__
+--
+-- >>> conjugate (3.0 :+ 3.0)
+-- 3.0 :+ (-3.0)
+--
+-- >>> conjugate ((3.0 :+ 3.0) * (2.0 :+ 2.0))
+-- 0.0 :+ (-12.0)
 {-# SPECIALISE conjugate :: Complex Double -> Complex Double #-}
 conjugate        :: Num a => Complex a -> Complex a
 conjugate (x:+y) =  x :+ (-y)
 
--- | Form a complex number from polar components of magnitude and phase.
+-- | Form a complex number from 'polar' components of 'magnitude' and 'phase'.
+--
+-- ==== __Examples__
+--
+-- >>> mkPolar 1 (pi / 4)
+-- 0.7071067811865476 :+ 0.7071067811865475
+--
+-- >>> mkPolar 1 0
+-- 1.0 :+ 0.0
 {-# SPECIALISE mkPolar :: Double -> Double -> Complex Double #-}
 mkPolar          :: Floating a => a -> a -> Complex a
 mkPolar r theta  =  r * cos theta :+ r * sin theta
 
--- | @'cis' t@ is a complex value with magnitude @1@
--- and phase @t@ (modulo @2*'pi'@).
+-- | @'cis' t@ is a complex value with 'magnitude' @1@
+-- and 'phase' @t@ (modulo @2*'pi'@).
+--
+-- @
+-- 'cis' = 'mkPolar' 1
+-- @
+--
+-- ==== __Examples__
+--
+-- >>> cis 0
+-- 1.0 :+ 0.0
+--
+-- The following examples are not perfectly zero due to [IEEE 754](https://en.wikipedia.org/wiki/IEEE_754)
+--
+-- >>> cis pi
+-- (-1.0) :+ 1.2246467991473532e-16
+--
+-- >>> cis (4 * pi) - cis (2 * pi)
+-- 0.0 :+ (-2.4492935982947064e-16)
 {-# SPECIALISE cis :: Double -> Complex Double #-}
 cis              :: Floating a => a -> Complex a
 cis theta        =  cos theta :+ sin theta
 
 -- | The function 'polar' takes a complex number and
--- returns a (magnitude, phase) pair in canonical form:
--- the magnitude is non-negative, and the phase in the range @(-'pi', 'pi']@;
--- if the magnitude is zero, then so is the phase.
+-- returns a ('magnitude', 'phase') pair in canonical form:
+-- the 'magnitude' is non-negative, and the 'phase' in the range @(-'pi', 'pi']@;
+-- if the 'magnitude' is zero, then so is the 'phase'.
+--
+-- @'polar' z = ('magnitude' z, 'phase' z)@
+--
+-- ==== __Examples__
+--
+-- >>> polar (1.0 :+ 1.0)
+-- (1.4142135623730951,0.7853981633974483)
+--
+-- >>> polar ((-1.0) :+ 0.0)
+-- (1.0,3.141592653589793)
+--
+-- >>> polar (0.0 :+ 0.0)
+-- (0.0,0.0)
 {-# SPECIALISE polar :: Complex Double -> (Double,Double) #-}
 polar            :: (RealFloat a) => Complex a -> (a,a)
 polar z          =  (magnitude z, phase z)
 
--- | The non-negative magnitude of a complex number.
+-- | The non-negative 'magnitude' of a complex number.
+--
+-- ==== __Examples__
+--
+-- >>> magnitude (1.0 :+ 1.0)
+-- 1.4142135623730951
+--
+-- >>> magnitude (1.0 + 0.0)
+-- 1.0
+--
+-- >>> magnitude (0.0 :+ (-5.0))
+-- 5.0
 {-# SPECIALISE magnitude :: Complex Double -> Double #-}
 magnitude :: (RealFloat a) => Complex a -> a
 magnitude (x:+y) =  scaleFloat k
@@ -120,8 +219,16 @@ magnitude (x:+y) =  scaleFloat k
                           mk = - k
                           sqr z = z * z
 
--- | The phase of a complex number, in the range @(-'pi', 'pi']@.
--- If the magnitude is zero, then so is the phase.
+-- | The 'phase' of a complex number, in the range @(-'pi', 'pi']@.
+-- If the 'magnitude' is zero, then so is the 'phase'.
+--
+-- ==== __Examples__
+--
+-- >>> phase (0.5 :+ 0.5) / pi
+-- 0.25
+--
+-- >>> phase (0 :+ 4) / pi
+-- 0.5
 {-# SPECIALISE phase :: Complex Double -> Double #-}
 phase :: (RealFloat a) => Complex a -> a
 phase (0 :+ 0)   = 0            -- SLPJ July 97 from John Peterson


=====================================
libraries/ghc-internal/src/Data/Data.hs
=====================================
@@ -625,6 +625,8 @@ mkDataType str cs = DataType
                         }
 
 -- | Constructs a constructor
+--
+-- @since 4.16.0.0
 mkConstrTag :: DataType -> String -> Int -> [String] -> Fixity -> Constr
 mkConstrTag dt str idx fields fix =
         Constr


=====================================
mk/hsc2hs.in
=====================================
@@ -0,0 +1,41 @@
+HSC2HS_C="@SettingsCCompilerFlags@"
+
+HSC2HS_L="@SettingsCCompilerLinkFlags@"
+
+tflag="--template=$libdir/template-hsc.h"
+Iflag="-I$includedir/include/"
+
+for f in ${HSC2HS_C}; do
+  cflags="${cflags} --cflag=$f"
+done
+
+for f in ${HSC2HS_L}; do
+  lflags="${lflags} --lflag=$f"
+done
+
+HSC2HS_EXTRA="$cflags $lflags"
+
+read_response() {
+    response_file=$1
+    if [ -f "$response_file" ]; then
+        while read -r arg; do
+            case "$arg" in
+                -t*)          tflag=;;
+                --template=*) tflag=;;
+                @*)           read_response "${arg#"@"}" ;;
+                --)           break;;
+            esac
+        done < "$response_file"
+    fi
+}
+
+for arg do
+    case "$arg" in
+        -t*)          tflag=;;
+        --template=*) tflag=;;
+        @*)           read_response "${arg#"@"}" ;;
+        --)           break;;
+    esac
+done
+
+exec "$executablename" ${tflag:+"$tflag"} $HSC2HS_EXTRA ${1+"$@"} "$Iflag"


=====================================
rts/Profiling.c
=====================================
@@ -204,6 +204,7 @@ void initProfiling (void)
 //
 void refreshProfilingCCSs (void)
 {
+    ACQUIRE_LOCK(&ccs_mutex);
     // make CCS_MAIN the parent of all the pre-defined CCSs.
     CostCentreStack *next;
     for (CostCentreStack *ccs = CCS_LIST; ccs != NULL; ) {
@@ -214,6 +215,7 @@ void refreshProfilingCCSs (void)
         ccs = next;
     }
     CCS_LIST = NULL;
+    RELEASE_LOCK(&ccs_mutex);
 }
 
 void



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bda1549e9906df8b5337952cb44c7fe2f77e3f60...211ff99fab605ffbb78c87d41b56ab2f2a0cea4e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bda1549e9906df8b5337952cb44c7fe2f77e3f60...211ff99fab605ffbb78c87d41b56ab2f2a0cea4e
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/20240219/6f2176de/attachment-0001.html>


More information about the ghc-commits mailing list