[Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] 7 commits: users-guide: Fix stylistic issues in 9.12 release notes
Fabricio Nascimento (@fabu)
gitlab at gitlab.haskell.org
Wed Jun 12 09:27:00 UTC 2024
Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC
Commits:
e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00
users-guide: Fix stylistic issues in 9.12 release notes
- - - - -
8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00
fix typo in the simplifier debug output:
baling -> bailing
- - - - -
16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00
haddock: Correct the Makefile to take into account Darwin systems
- - - - -
a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00
haddock: Remove obsolete links to github.com/haskell/haddock in the docs
- - - - -
de4395cd by qqwy at 2024-06-12T03:09:12-04:00
Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set.
This allows users to create their own Control.Exception.assert-like functionality that
does something other than raising an `AssertFailed` exception.
Fixes #24967
- - - - -
0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00
compiler: add hint to TcRnBadlyStaged message
- - - - -
0b524559 by Fabricio de Sousa Nascimento at 2024-06-12T09:26:50+00:00
compiler: Rejects RULES whose LHS immediately fails to type-check
Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This
happens when we have a RULE that does not type check, and enable
`-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an
immediately LHS type error.
Fixes #24026
- - - - -
27 changed files:
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/Rule.hs
- docs/users_guide/9.12.1-notes.rst
- docs/users_guide/exts/assert.rst
- docs/users_guide/phases.rst
- + testsuite/tests/driver/cpp_assertions_ignored/Makefile
- + testsuite/tests/driver/cpp_assertions_ignored/all.T
- + testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout
- + testsuite/tests/driver/cpp_assertions_ignored/main.hs
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- + testsuite/tests/typecheck/T24026/T24026a.hs
- + testsuite/tests/typecheck/T24026/T24026a.stderr
- + testsuite/tests/typecheck/T24026/T24026b.hs
- + testsuite/tests/typecheck/T24026/T24026b.stderr
- + testsuite/tests/typecheck/T24026/all.T
- utils/haddock/Makefile
- utils/haddock/README.md
- utils/haddock/doc/intro.rst
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock-api/resources/html/package.json
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/haddock-test/haddock-test.cabal
- utils/haddock/haddock.cabal
Changes:
=====================================
compiler/GHC/Core/Opt/Simplify.hs
=====================================
@@ -199,7 +199,7 @@ simplifyPgm logger unit_env name_ppr_ctx opts
-- Subtract 1 from iteration_no to get the
-- number of iterations we actually completed
- return ( "Simplifier baled out", iteration_no - 1
+ return ( "Simplifier bailed out", iteration_no - 1
, totalise counts_so_far
, guts_no_binds { mg_binds = binds, mg_rules = local_rules } )
=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs
extra_bndrs = scopedSort extra_tvs ++ extra_dicts
where
extra_tvs = [ v | v <- extra_vars, isTyVar v ]
+
+ -- isEvVar: this includes coercions, matching what
+ -- happens in `split_lets` (isDictId, isCoVar)
extra_dicts =
- [ mkLocalId (localiseName (idName d)) ManyTy (idType d)
- | d <- extra_vars, isDictId d ]
+ [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d)
+ | d <- extra_vars, isEvVar d ]
extra_vars =
[ v
| v <- exprsFreeVarsList args
=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -168,6 +168,9 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do
backend_defs <- applyCDefs (backendCDefs $ backend dflags) logger dflags
let th_defs = [ "-D__GLASGOW_HASKELL_TH__" ]
+
+ let asserts_def = [ "-D__GLASGOW_HASKELL_ASSERTS_IGNORED__" | gopt Opt_IgnoreAsserts dflags]
+
-- Default CPP defines in Haskell source
ghcVersionH <- getGhcVersionPathName dflags unit_env
let hsSourceCppOpts = [ "-include", ghcVersionH ]
@@ -197,6 +200,7 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do
++ map GHC.SysTools.Option target_defs
++ map GHC.SysTools.Option backend_defs
++ map GHC.SysTools.Option th_defs
+ ++ map GHC.SysTools.Option asserts_def
++ map GHC.SysTools.Option hscpp_opts
++ map GHC.SysTools.Option sse_defs
++ map GHC.SysTools.Option fma_def
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -1417,9 +1417,16 @@ instance Diagnostic TcRnMessage where
, interpp'SP errorVars ]
TcRnBadlyStaged reason bind_lvl use_lvl
-> mkSimpleDecorated $
- text "Stage error:" <+> pprStageCheckReason reason <+>
- hsep [text "is bound at stage" <+> ppr bind_lvl,
- text "but used at stage" <+> ppr use_lvl]
+ vcat $
+ [ text "Stage error:" <+> pprStageCheckReason reason <+>
+ hsep [text "is bound at stage" <+> ppr bind_lvl,
+ text "but used at stage" <+> ppr use_lvl]
+ ] ++
+ [ hsep [ text "Hint: quoting" <+> thBrackets (ppUnless (isValName n) "t") (ppr n)
+ , text "or an enclosing expression would allow the quotation to be used in an earlier stage"
+ ]
+ | StageCheckSplice n <- [reason]
+ ]
TcRnBadlyStagedType name bind_lvl use_lvl
-> mkSimpleDecorated $
text "Badly staged type:" <+> ppr name <+>
=====================================
compiler/GHC/Tc/Gen/Rule.hs
=====================================
@@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls
tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc)
tcRuleDecls (HsRules { rds_ext = src
, rds_rules = decls })
- = do { tc_decls <- mapM (wrapLocMA tcRule) decls
+ = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls
+ ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls]
; return $ HsRules { rds_ext = src
, rds_rules = tc_decls } }
-tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc)
+
+tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc))
tcRule (HsRule { rd_ext = ext
, rd_name = rname@(L _ name)
, rd_act = act
@@ -181,14 +183,22 @@ tcRule (HsRule { rd_ext = ext
; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs
lhs_evs rhs_wanted
; emitImplications (lhs_implic `unionBags` rhs_implic)
- ; return $ HsRule { rd_ext = ext
+
+ -- insolubleImplic: if the LHS has an outright type error, drop the rule entirely
+ -- The error will be reported; but if `-fdefer-type-errors` is on we don't want
+ -- to continue, else we get a compiler crash (#24026)
+ ; if anyBag insolubleImplic lhs_implic
+ then
+ return Nothing -- The RULE LHS does not type-check and will be dropped.
+ else
+ return . Just $ HsRule { rd_ext = ext
, rd_name = rname
, rd_act = act
, rd_tyvs = ty_bndrs -- preserved for ppr-ing
, rd_tmvs = map (noLocA . RuleBndr noAnn . noLocA)
(qtkvs ++ tpl_ids)
, rd_lhs = mkHsDictLet lhs_binds lhs'
- , rd_rhs = mkHsDictLet rhs_binds rhs' } }
+ , rd_rhs = mkHsDictLet rhs_binds rhs' }}
generateRuleConstraints :: FastString
-> Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn]
=====================================
docs/users_guide/9.12.1-notes.rst
=====================================
@@ -31,10 +31,10 @@ Language
This means that code using :extension:`UnliftedDatatypes` or
:extension:`UnliftedNewtypes` can now use :extension:`OverloadedRecordDot`.
-- Unboxed Float#/Double# literals now support the HexFloatLiterals extension
+- Unboxed ``Float#``/``Double#`` literals now support the HexFloatLiterals extension
(`#22155 <https://gitlab.haskell.org/ghc/ghc/-/issues/22155>`_).
-- UnliftedFFITypes: GHC will now accept ffi types like: ``(# #) -> T`` where ``(# #)``
+- :extension:`UnliftedFFITypes`: GHC will now accept FFI types like: ``(# #) -> T`` where ``(# #)``
is used as the one and only function argument.
Compiler
@@ -75,6 +75,13 @@ Compiler
<https://gitlab.haskell.org/ghc/ghc/-/issues/24921>`_). This does
not affect existing support of apple systems on x86_64/aarch64.
+- The flag :ghc-flag:`-fignore-asserts` will now also enable the
+ :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` (`#24967
+ <https://gitlab.haskell.org/ghc/ghc/-/issues/24967>`_).
+ This enables people to write their own custom assertion functions.
+ See :ref:`assertions`.
+
+
GHCi
~~~~
=====================================
docs/users_guide/exts/assert.rst
=====================================
@@ -50,4 +50,20 @@ allows enabling assertions even when optimisation is turned on.
Assertion failures can be caught, see the documentation for the
:base-ref:`Control.Exception.` library for the details.
-
+The ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` CPP macro
+=====================================================
+
+When code is compiled with assertions ignored (using :ghc-flag:`-fignore-asserts` or :ghc-flag:`-O`),
+the :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` will be defined.
+This can be used to conditionally compile your own custom assert-like functions.
+For example: ::
+
+ checkedAdd :: Word -> Word -> Word
+ #ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__
+ checkedAdd lhs rhs = lhs + rhs
+ #else
+ checkedAdd lhs rhs
+ | res < lhs || res < rhs = raise OverflowException
+ | otherwise = res
+ where res = lhs + rhs
+ #endif
=====================================
docs/users_guide/phases.rst
=====================================
@@ -508,6 +508,13 @@ defined by your local GHC installation, the following trick is useful:
is added, so for example when using version 3.7 of LLVM,
``__GLASGOW_HASKELL_LLVM__==307``).
+``__GLASGOW_HASKELL_ASSERTS_IGNORED__``
+ .. index::
+ single: __GLASGOW_HASKELL_ASSERTS_IGNORED__
+
+ Only defined when :ghc-flag:`-fignore-asserts` is specified.
+ This can be used to create your own assertions, see :ref:`assertions`
+
``__PARALLEL_HASKELL__``
.. index::
single: __PARALLEL_HASKELL__
=====================================
testsuite/tests/driver/cpp_assertions_ignored/Makefile
=====================================
@@ -0,0 +1,11 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+cpp_assertions_ignored:
+ echo "Without -fignore-asserts"
+ '$(TEST_HC)' $(TEST_HC_OPTS) -v0 main.hs
+ (./main 2>&1); true
+ echo "With -fignore-asserts"
+ '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -fignore-asserts main.hs
+ ./main 2>&1
=====================================
testsuite/tests/driver/cpp_assertions_ignored/all.T
=====================================
@@ -0,0 +1,4 @@
+test('cpp_assertions_ignored',
+ [ extra_files(['main.hs'])
+ ],
+ makefile_test, ['cpp_assertions_ignored'])
=====================================
testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout
=====================================
@@ -0,0 +1,4 @@
+Without -fignore-asserts
+Assertions Enabled
+With -fignore-asserts
+Assertions Ignored
=====================================
testsuite/tests/driver/cpp_assertions_ignored/main.hs
=====================================
@@ -0,0 +1,14 @@
+{-# LANGUAGE CPP #-}
+import Control.Exception (assert)
+
+main =
+ if assertsEnabled
+ then putStrLn "Assertions Enabled"
+ else putStrLn "Assertions Ignored"
+
+assertsEnabled :: Bool
+#ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__
+assertsEnabled = False
+#else
+assertsEnabled = True
+#endif
=====================================
testsuite/tests/th/T17820d.stderr
=====================================
@@ -1,7 +1,8 @@
-
T17820d.hs:6:38: error: [GHC-28914]
• Stage error: ‘foo’ is bound at stage 2 but used at stage 1
+ Hint: quoting [| foo |] or an enclosing expression would allow the quotation to be used in an earlier stage
• In the untyped splice: $(const [| 0 |] foo)
In the Template Haskell quotation
[d| data D = MkD {foo :: Int}
blargh = $(const [| 0 |] foo) |]
+
=====================================
testsuite/tests/th/T23829_hasty_b.stderr
=====================================
@@ -1,6 +1,7 @@
-
T23829_hasty_b.hs:8:42: error: [GHC-28914]
• Stage error: ‘ty’ is bound at stage 2 but used at stage 1
+ Hint: quoting [t| ty |] or an enclosing expression would allow the quotation to be used in an earlier stage
• In the untyped splice: $ty
In the Template Haskell quotation
[t| forall (ty :: TypeQ). Proxy $ty |]
+
=====================================
testsuite/tests/typecheck/T24026/T24026a.hs
=====================================
@@ -0,0 +1,7 @@
+-- This rule has a type error on the LHS
+module T24026a where
+
+{-# RULES "f" forall (x :: Bool). f x = 0 #-}
+
+f :: Int -> Int
+f x = 0
=====================================
testsuite/tests/typecheck/T24026/T24026a.stderr
=====================================
@@ -0,0 +1,9 @@
+T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)]
+ Rule "f" may never fire because ‘f’ might inline first
+ Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’
+
+T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
+ • Couldn't match expected type ‘Int’ with actual type ‘Bool’
+ • In the first argument of ‘f’, namely ‘x’
+ In the expression: f x
+ When checking the rewrite rule "f"
\ No newline at end of file
=====================================
testsuite/tests/typecheck/T24026/T24026b.hs
=====================================
@@ -0,0 +1,7 @@
+-- This rule has a type error on the LHS
+module T24026b where
+
+{-# RULES "f" forall (x :: Bool). f x = 0 #-}
+
+f :: Int -> Int
+f x = 0
=====================================
testsuite/tests/typecheck/T24026/T24026b.stderr
=====================================
@@ -0,0 +1,5 @@
+T24026b.hs:4:37: error: [GHC-83865]
+ • Couldn't match expected type ‘Int’ with actual type ‘Bool’
+ • In the first argument of ‘f’, namely ‘x’
+ In the expression: f x
+ When checking the rewrite rule "f"
\ No newline at end of file
=====================================
testsuite/tests/typecheck/T24026/all.T
=====================================
@@ -0,0 +1,2 @@
+test('T24026a', normal, compile, ['-dlint -fdefer-type-errors'])
+test('T24026b', normal, compile_fail, [''])
\ No newline at end of file
=====================================
utils/haddock/Makefile
=====================================
@@ -8,18 +8,17 @@ test: ## Run the test suite
@cabal test
lint: ## Run the code linter (HLint)
- @find driver haddock-api haddock-library haddock-test hoogle-test hypsrc-test latex-test \
- -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {}
+ @find driver haddock-api haddock-library -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {}
style: ## Run the code styler (fourmolu and cabal-fmt)
@cabal-fmt -i **/*.cabal
@fourmolu -q --mode inplace driver haddock-api haddock-library
style-check: ## Check the code's style (fourmolu and cabal-fmt)
- @cabal-fmt -i **/*.cabal
+ @cabal-fmt -c **/*.cabal
@fourmolu -q --mode check driver haddock-api haddock-library
-style-quick: ## Run the code styler on modified files
+style-quick: ## Run the code styler on modified files tracked by git
@cabal-fmt -i **/*.cabal
@git diff origin --name-only driver haddock-api haddock-library | xargs -P $(PROCS) -I {} fourmolu -q -i {}
@@ -29,9 +28,12 @@ tags: ## Generate ctags and etags for the source code (ghc-tags)
help: ## Display this help message
@grep -E '^[a-zA-Z_-]+:.*?## .*$$' $(MAKEFILE_LIST) | awk 'BEGIN {FS = ":.* ?## "}; {printf "\033[36m%-30s\033[0m %s\n", $$1, $$2}'
-PROCS := $(shell nproc)
-
.PHONY: all $(MAKECMDGOALS)
.DEFAULT_GOAL := help
+ifeq ($(UNAME), Darwin)
+ PROCS := $(shell sysctl -n hw.logicalcpu)
+else
+ PROCS := $(shell nproc)
+endif
=====================================
utils/haddock/README.md
=====================================
@@ -1,4 +1,4 @@
-# Haddock [![CI][CI badge]][CI page] [![Hackage][Hackage badge]][Hackage page]
+# Haddock [![Hackage][Hackage badge]][Hackage page]
Haddock is the standard tool for generating documentation from Haskell code.
Full documentation about Haddock itself can be found in the `doc/` subdirectory,
@@ -25,8 +25,6 @@ See [CONTRIBUTING.md](CONTRIBUTING.md) to see how to make contributions to the
project.
-[CI page]: https://github.com/haskell/haddock/actions/workflows/ci.yml
-[CI badge]: https://github.com/haskell/haddock/actions/workflows/ci.yml/badge.svg
[Hackage page]: https://hackage.haskell.org/package/haddock
[Hackage badge]: https://img.shields.io/hackage/v/haddock.svg
[reST]: https://www.sphinx-doc.org/en/master/usage/restructuredtext/index.html
=====================================
utils/haddock/doc/intro.rst
=====================================
@@ -62,9 +62,7 @@ Obtaining Haddock
Haddock is distributed with GHC distributions, and will automatically be provided if you use
`ghcup <https://www.haskell.org/ghcup>`__, for instance.
-Up-to-date sources can also be obtained from our public GitHub
-repository. The Haddock sources are at
-``https://github.com/haskell/haddock``.
+Haddock lives in the GHC repository, which you can consult at ``https://gitlab.haskell.org/ghc/ghc``.
License
-------
@@ -99,12 +97,6 @@ code, except where otherwise indicated.
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
-Contributors
-------------
-
-A list of contributors to the project can be seen at
-``https://github.com/haskell/haddock/graphs/contributors``.
-
Acknowledgements
----------------
=====================================
utils/haddock/haddock-api/haddock-api.cabal
=====================================
@@ -7,13 +7,12 @@ description: Haddock is a documentation-generation tool for Haskell
license: BSD-2-Clause
license-file: LICENSE
author: Simon Marlow, David Waern
-maintainer: Alec Theriault <alec.theriault at gmail.com>, Alex Biehl <alexbiehl at gmail.com>, Simon Hengel <sol at typeful.net>, Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
+maintainer: Haddock Team
homepage: http://www.haskell.org/haddock/
-bug-reports: https://github.com/haskell/haddock/issues
+bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new
copyright: (c) Simon Marlow, David Waern
category: Documentation
build-type: Simple
-tested-with: GHC==9.6.*
extra-source-files:
CHANGES.md
@@ -39,6 +38,11 @@ data-files:
html/Linuwial.std-theme/synopsis.png
latex/haddock.sty
+source-repository head
+ type: git
+ location: https://gitlab.haskell.org/ghc/ghc.git
+ subdir: utils/haddock/haddock-api
+
library
default-language: Haskell2010
@@ -203,8 +207,3 @@ test-suite spec
build-tool-depends:
hspec-discover:hspec-discover ^>= 2.9
-
-source-repository head
- type: git
- subdir: haddock-api
- location: https://github.com/haskell/haddock.git
=====================================
utils/haddock/haddock-api/resources/html/package.json
=====================================
@@ -8,7 +8,8 @@
},
"repository": {
"type": "git",
- "url": "https://github.com/haskell/haddock.git"
+ "url": "https://gitlab.haskell.org/ghc/ghc.git"
+ "directory": "utils/haddock"
},
"author": "Tim Baumann <tim at timbaumann.info>",
"contributors": [
=====================================
utils/haddock/haddock-library/haddock-library.cabal
=====================================
@@ -2,7 +2,6 @@ cabal-version: 3.0
name: haddock-library
version: 1.11.0
synopsis: Library exposing some functionality of Haddock.
-
description: Haddock is a documentation-generation tool for Haskell
libraries. These modules expose some
functionality of it without pulling in the GHC
@@ -13,16 +12,10 @@ description: Haddock is a documentation-generation tool for Haskell
license: BSD-2-Clause
license-file: LICENSE
-maintainer: Alec Theriault <alec.theriault at gmail.com>, Alex Biehl <alexbiehl at gmail.com>, Simon Hengel <sol at typeful.net>, Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
+maintainer: Haddock Team
homepage: http://www.haskell.org/haddock/
-bug-reports: https://github.com/haskell/haddock/issues
+bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new
category: Documentation
-tested-with: GHC == 8.4.4
- , GHC == 8.6.5
- , GHC == 8.8.3
- , GHC == 8.10.1
- , GHC == 9.0.1
- , GHC == 9.2.0
extra-doc-files:
CHANGES.md
@@ -31,6 +24,11 @@ extra-source-files:
fixtures/examples/*.input
fixtures/examples/*.parsed
+source-repository head
+ type: git
+ location: https://gitlab.haskell.org/ghc/ghc.git
+ subdir: utils/haddock/haddock-library
+
common lib-defaults
default-language: Haskell2010
@@ -113,8 +111,3 @@ test-suite fixtures
, filepath ^>= 1.4.1.2
, optparse-applicative >= 0.15 && < 0.19
, tree-diff ^>= 0.2 || ^>= 0.3
-
-source-repository head
- type: git
- subdir: haddock-library
- location: https://github.com/haskell/haddock.git
=====================================
utils/haddock/haddock-test/haddock-test.cabal
=====================================
@@ -6,11 +6,10 @@ license: BSD-2-Clause
author: Simon Marlow, David Waern
maintainer: Simon Hengel <sol at typeful.net>, Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
homepage: http://www.haskell.org/haddock/
-bug-reports: https://github.com/haskell/haddock/issues
+bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new
copyright: (c) Simon Marlow, David Waern
category: Documentation
build-type: Simple
-tested-with: GHC==9.6.*
stability: experimental
library
=====================================
utils/haddock/haddock.cabal
=====================================
@@ -29,13 +29,12 @@ description:
license: BSD-3-Clause
license-file: LICENSE
author: Simon Marlow, David Waern
-maintainer: Alec Theriault <alec.theriault at gmail.com>, Alex Biehl <alexbiehl at gmail.com>, Simon Hengel <sol at typeful.net>, Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk>
+maintainer: Haddock Team
homepage: http://www.haskell.org/haddock/
-bug-reports: https://github.com/haskell/haddock/issues
+bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new
copyright: (c) Simon Marlow, David Waern
category: Documentation
build-type: Simple
-tested-with: GHC==9.6.*
extra-source-files:
CHANGES.md
@@ -65,6 +64,11 @@ flag threaded
default: True
manual: True
+source-repository head
+ type: git
+ location: https://gitlab.haskell.org/ghc/ghc.git
+ subdir: utils/haddock
+
executable haddock
default-language: Haskell2010
main-is: Main.hs
@@ -193,7 +197,3 @@ test-suite hoogle-test
main-is: Main.hs
hs-source-dirs: hoogle-test
build-depends: base, filepath, haddock-test == 0.0.1
-
-source-repository head
- type: git
- location: https://github.com/haskell/haddock.git
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/185986663d5ba14b00f836dfd1a915efdf36c94f...0b5245592b3dec53f0bf3a45c8eaf6aa8b56c65d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/185986663d5ba14b00f836dfd1a915efdf36c94f...0b5245592b3dec53f0bf3a45c8eaf6aa8b56c65d
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/20240612/aecb40ec/attachment-0001.html>
More information about the ghc-commits
mailing list