[Git][ghc/ghc][wip/js-staging] 359 commits: DmdAnal: Don't panic in addCaseBndrDmd (#22039)

doyougnu (@doyougnu) gitlab at gitlab.haskell.org
Sun Oct 2 19:53:07 UTC 2022



doyougnu pushed to branch wip/js-staging at Glasgow Haskell Compiler / GHC


Commits:
d2be80fd by Sebastian Graf at 2022-09-05T23:12:14-04:00
DmdAnal: Don't panic in addCaseBndrDmd (#22039)

Rather conservatively return Top.
See Note [Untyped demand on case-alternative binders].

I also factored `addCaseBndrDmd` into two separate functions `scrutSubDmd` and
`fieldBndrDmds`.

Fixes #22039.

- - - - -
25f68ace by Ben Gamari at 2022-09-05T23:12:50-04:00
gitlab-ci: Ensure that ghc derivation is in scope

Previously the lint-ci job attempted to use cabal-install (specifically
`cabal update`) without a GHC in PATH. However, cabal-install-3.8
appears to want GHC, even for `cabal update`.

- - - - -
f37b621f by sheaf at 2022-09-06T11:51:53+00:00
Update instances.rst, clarifying InstanceSigs

Fixes #22103

- - - - -
d4f908f7 by Jan Hrček at 2022-09-06T15:36:58-04:00
Fix :add docs in user guide

- - - - -
808bb793 by Cheng Shao at 2022-09-06T15:37:35-04:00
ci: remove unused build_make/test_make in ci script

- - - - -
d0a2efb2 by Eric Lindblad at 2022-09-07T16:42:45-04:00
typo
- - - - -
fac0098b by Eric Lindblad at 2022-09-07T16:42:45-04:00
typos

- - - - -
a581186f by Eric Lindblad at 2022-09-07T16:42:45-04:00
whitespace

- - - - -
04a738cb by Cheng Shao at 2022-09-07T16:43:22-04:00
CmmToAsm: remove unused ModLocation from NatM_State

- - - - -
ee1cfaa9 by Krzysztof Gogolewski at 2022-09-07T16:43:58-04:00
Minor SDoc cleanup

Change calls to renderWithContext with showSDocOneLine; it's more
efficient and explanatory.

Remove polyPatSig (unused)

- - - - -
7918265d by Krzysztof Gogolewski at 2022-09-07T16:43:58-04:00
Remove Outputable Char instance

Use 'text' instead of 'ppr'.
Using 'ppr' on the list "hello" rendered as "h,e,l,l,o".

- - - - -
77209ab3 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Export liftA2 from Prelude

Changes:
In order to be warning free and compatible, we hide Applicative(..)
from Prelude in a few places and instead import it directly from
Control.Applicative.
Please see the migration guide at
https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md
for more details.

This means that Applicative is now exported in its entirety from
Prelude.

Motivation:

This change is motivated by a few things:
* liftA2 is an often used function, even more so than (<*>) for some
  people.
* When implementing Applicative, the compiler will prompt you for either
  an implementation of (<*>) or of liftA2, but trying to use the latter
  ends with an error, without further imports. This could be confusing
  for newbies.
* For teaching, it is often times easier to introduce liftA2 first,
  as it is a natural generalisation of fmap.
* This change seems to have been unanimously and enthusiastically
  accepted by the CLC members, possibly indicating a lot of love for it.
* This change causes very limited breakage, see the linked issue below
  for an investigation on this.

See https://github.com/haskell/core-libraries-committee/issues/50
for the surrounding discussion and more details.

- - - - -
442a94e8 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Add changelog entry for liftA2 export from Prelude

- - - - -
fb968680 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Bump submodule containers to one with liftA2 warnings fixed

- - - - -
f54ff818 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Bump submodule Cabal to one with liftA2 warnings fixed

- - - - -
a4b34808 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00
Isolate some Applicative hidings to GHC.Prelude

By reexporting the entirety of Applicative from GHC.Prelude, we can save
ourselves some `hiding` and importing of `Applicative` in consumers of GHC.Prelude.
This also has the benefit of isolating this type of change to
GHC.Prelude, so that people in the future don't have to think about it.

- - - - -
9c4ea90c by Cheng Shao at 2022-09-08T17:49:47-04:00
CmmToC: enable 64-bit CallishMachOp on 32-bit targets

Normally, the unregisterised builds avoid generating 64-bit
CallishMachOp in StgToCmm, so CmmToC doesn't support these. However,
there do exist cases where we'd like to invoke cmmToC for other cmm
inputs which may contain such CallishMachOps, and it's a rather low
effort to add support for these since they only require calling into
existing ghc-prim cbits.

- - - - -
04062510 by Alexis King at 2022-09-11T11:30:32+02:00
Add native delimited continuations to the RTS

This patch implements GHC proposal 313, "Delimited continuation
primops", by adding native support for delimited continuations to the
GHC RTS.

All things considered, the patch is relatively small. It almost
exclusively consists of changes to the RTS; the compiler itself is
essentially unaffected. The primops come with fairly extensive Haddock
documentation, and an overview of the implementation strategy is given
in the Notes in rts/Continuation.c.

This first stab at the implementation prioritizes simplicity over
performance. Most notably, every continuation is always stored as a
single, contiguous chunk of stack. If one of these chunks is
particularly large, it can result in poor performance, as the current
implementation does not attempt to cleverly squeeze a subset of the
stack frames into the existing stack: it must fit all at once. If this
proves to be a performance issue in practice, a cleverer strategy would
be a worthwhile target for future improvements.

- - - - -
ee471dfb by Cheng Shao at 2022-09-12T07:07:33-04:00
rts: fix missing dirty_MVAR argument in stg_writeIOPortzh

- - - - -
a5f9c35f by Cheng Shao at 2022-09-12T13:29:05-04:00
ci: enable parallel compression for xz

- - - - -
3a815f30 by Ryan Scott at 2022-09-12T13:29:41-04:00
Windows: Always define _UCRT when compiling C code

As seen in #22159, this is required to ensure correct behavior when MinGW-w64
headers are in the `C_INCLUDE_PATH`.

Fixes #22159.

- - - - -
65a0bd69 by sheaf at 2022-09-13T10:27:52-04:00
Add diagnostic codes

This MR adds diagnostic codes, assigning unique numeric codes to
error and warnings, e.g.

  error: [GHC-53633]
  Pattern match is redundant

This is achieved as follows:

  - a type family GhcDiagnosticCode that gives the diagnostic code
    for each diagnostic constructor,
  - a type family ConRecursInto that specifies whether to recur into
    an argument of the constructor to obtain a more fine-grained code
    (e.g. different error codes for different 'deriving' errors),
  - generics machinery to generate the value-level function assigning
    each diagnostic its error code; see Note [Diagnostic codes using generics]
    in GHC.Types.Error.Codes.

The upshot is that, to add a new diagnostic code, contributors only need
to modify the two type families mentioned above. All logic relating to
diagnostic codes is thus contained to the GHC.Types.Error.Codes module,
with no code duplication.

This MR also refactors error message datatypes a bit, ensuring we can
derive Generic for them, and cleans up the logic around constraint
solver reports by splitting up 'TcSolverReportInfo' into separate
datatypes (see #20772).

Fixes #21684

- - - - -
362cca13 by sheaf at 2022-09-13T10:27:53-04:00
Diagnostic codes: acccept test changes

The testsuite output now contains diagnostic codes, so many tests need
to be updated at once.
We decided it was best to keep the diagnostic codes in the testsuite
output, so that contributors don't inadvertently make changes to the
diagnostic codes.

- - - - -
08f6730c by Adam Gundry at 2022-09-13T10:28:29-04:00
Allow imports to reference multiple fields with the same name (#21625)

If a module `M` exports two fields `f` (using DuplicateRecordFields), we can
still accept

    import M (f)
    import M hiding (f)

and treat `f` as referencing both of them.  This was accepted in GHC 9.0, but gave
rise to an ambiguity error in GHC 9.2.  See #21625.

This patch also documents this behaviour in the user's guide, and updates the
test for #16745 which is now treated differently.

- - - - -
c14370d7 by Cheng Shao at 2022-09-13T10:29:07-04:00
ci: remove unused appveyor config

- - - - -
dc6af9ed by Cheng Shao at 2022-09-13T10:29:45-04:00
compiler: remove unused lazy state monad

- - - - -
646d15ad by Eric Lindblad at 2022-09-14T03:13:56-04:00
Fix typos

This fixes various typos and spelling mistakes
in the compiler.

Fixes #21891

- - - - -
7d7e71b0 by Matthew Pickering at 2022-09-14T03:14:32-04:00
hadrian: Bump index state

This bumps the index state so a build plan can also be found when
booting with 9.4.

Fixes #22165

- - - - -
98b62871 by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Use a stamp file to record when a package is built in a certain way

Before this patch which library ways we had built wasn't recorded
directly. So you would run into issues if you build the .conf file with
some library ways before switching the library ways which you wanted to
build.

Now there is one stamp file for each way, so in order to build a
specific way you can need that specific stamp file rather than going
indirectly via the .conf file.

- - - - -
b42cedbe by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Inplace/Final package databases

There are now two different package databases per stage. An inplace
package database contains .conf files which point directly into the
build directories. The final package database contains .conf files which
point into the installed locations. The inplace .conf files are created
before any building happens and have fake ABI hash values. The final
.conf files are created after a package finished building and contains
the proper ABI has.

The motivation for this is to make the dependency structure more
fine-grained when building modules. Now a module depends just depends
directly on M.o from package p rather than the .conf file depend on the
.conf file for package p. So when all of a modules direct dependencies
have finished building we can start building it rather than waiting for
the whole package to finish.

The secondary motivation is that the multi-repl doesn't need to build
everything before starting the multi-repl session. We can just configure
the inplace package-db and use that in order to start the repl.

- - - - -
6515c32b by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Add some more packages to multi-cradle

The main improvement here is to pass `-this-unit-id` for executables so
that they can be added to the multi-cradle if desired as well as normal
library packages.

- - - - -
e470e91f by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Need builders needed by Cabal Configure in parallel

Because of the use of withStaged (which needs the necessary builder)
when configuring a package, the builds of stage1:exe:ghc-bin and
stage1:exe:ghc-pkg where being linearised when building a specific
target like `binary-dist-dir`.

Thankfully the fix is quite local, to supply all the `withStaged`
arguments together so the needs can be batched together and hence
performed in parallel.

Fixes #22093

- - - - -
c4438347 by Matthew Pickering at 2022-09-14T17:17:04-04:00
Remove stage1:exe:ghc-bin pre-build from CI script

CI builds stage1:exe:ghc-bin before the binary-dist target which
introduces some quite bad linearisation (see #22093) because we don't
build stage1 compiler in parallel with anything. Then when the
binary-dist target is started we have to build stage1:exe:ghc-pkg before
doing anything.

Fixes #22094

- - - - -
71d8db86 by Matthew Pickering at 2022-09-14T17:17:04-04:00
hadrian: Add extra implicit dependencies from DeriveLift

ghc -M should know that modules which use DeriveLift (or
TemplateHaskellQuotes) need TH.Lib.Internal but until it does, we have
to add these extra edges manually or the modules will be compiled before
TH.Lib.Internal is compiled which leads to a desugarer error.

- - - - -
43e574f0 by Greg Steuck at 2022-09-14T17:17:43-04:00
Repair c++ probing on OpenBSD

Failure without this change:
```
checking C++ standard library flavour... libc++
checking for linkage against 'c++ c++abi'... failed
checking for linkage against 'c++ cxxrt'... failed
configure: error: Failed to find C++ standard library
```

- - - - -
534b39ee by Douglas Wilson at 2022-09-14T17:18:21-04:00
libraries: template-haskell: vendor filepath differently

Vendoring with ../ in hs-source-dirs prevents upload to hackage.

(cherry picked from commit 1446be7586ba70f9136496f9b67f792955447842)

- - - - -
bdd61cd6 by M Farkas-Dyck at 2022-09-14T22:39:34-04:00
Unbreak Hadrian with Cabal 3.8.

- - - - -
df04d6ec by Krzysztof Gogolewski at 2022-09-14T22:40:09-04:00
Fix typos

- - - - -
d6ea8356 by Andreas Klebinger at 2022-09-15T10:12:41+02:00
Tag inference: Fix #21954 by retaining tagsigs of vars in function position.

For an expression like:

    case x of y
      Con z -> z

If we also retain the tag sig for z we can generate code to immediately return
it rather than calling out to stg_ap_0_fast.

- - - - -
7cce7007 by Andreas Klebinger at 2022-09-15T10:12:42+02:00
Stg.InferTags.Rewrite - Avoid some thunks.

- - - - -
88c4cbdb by Cheng Shao at 2022-09-16T13:57:56-04:00
hadrian: enable -fprof-late only for profiling ways

- - - - -
d7235831 by Cheng Shao at 2022-09-16T13:57:56-04:00
hadrian: add late_ccs flavour transformer

- - - - -
ce203753 by Cheng Shao at 2022-09-16T13:58:34-04:00
configure: remove unused program checks

- - - - -
9b4c1056 by Pierre Le Marre at 2022-09-16T13:59:16-04:00
Update to Unicode 15.0

- - - - -
c6e9b89a by Bodigrim at 2022-09-16T13:59:55-04:00
Avoid partial head and tail in ghc-heap; replace with total pattern-matching

- - - - -
616afde3 by Cheng Shao at 2022-09-16T14:00:33-04:00
hadrian: relax Cabal upper bound to allow building with Cabal-3.8

A follow up of !8910.

- - - - -
df35d994 by Alexis King at 2022-09-16T14:01:11-04:00
Add links to the continuations haddocks in the docs for each primop

fixes #22176

- - - - -
383f7549 by Matthew Pickering at 2022-09-16T21:42:10-04:00
-Wunused-pattern-binds: Recurse into patterns to check whether there's a splice

See the examples in #22057 which show we have to traverse deeply into a
pattern to determine whether it contains a splice or not. The original
implementation pointed this out but deemed this very shallow traversal
"too expensive".

Fixes #22057

I also fixed an oversight in !7821 which meant we lost a warning which
was present in 9.2.2.

Fixes #22067

- - - - -
5031bf49 by sheaf at 2022-09-16T21:42:49-04:00
Hadrian: Don't try to build terminfo on Windows

Commit b42cedbe introduced a dependency on terminfo on Windows,
but that package isn't available on Windows.

- - - - -
c9afe221 by M Farkas-Dyck at 2022-09-17T06:44:47-04:00
Clean up some. In particular:
• Delete some dead code, largely under `GHC.Utils`.
• Clean up a few definitions in `GHC.Utils.(Misc, Monad)`.
• Clean up `GHC.Types.SrcLoc`.
• Derive stock `Functor, Foldable, Traversable` for more types.
• Derive more instances for newtypes.

Bump haddock submodule.

- - - - -
85431ac3 by Cheng Shao at 2022-09-17T06:45:25-04:00
driver: pass original Cmm filename in ModLocation

When compiling Cmm, the ml_hs_file field is used to indicate Cmm
filename when later generating DWARF information. We should pass the
original filename here, otherwise for preprocessed Cmm files, the
filename will be a temporary filename which is confusing.

- - - - -
63aa0069 by Cheng Shao at 2022-09-17T06:46:04-04:00
rts: remove legacy logging cabal flag

- - - - -
bd0f4184 by Cheng Shao at 2022-09-17T06:46:04-04:00
rts: make threaded ways optional

For certain targets (e.g. wasm32-wasi), the threaded rts is known not to
work. This patch adds a "threaded" cabal flag to rts to make threaded
rts ways optional. Hadrian enables this flag iff the flavour rtsWays
contains threaded ways.

- - - - -
8a666ad2 by Ryan Scott at 2022-09-18T08:00:44-04:00
DeriveFunctor: Check for last type variables using dataConUnivTyVars

Previously, derived instances of `Functor` (as well as the related classes
`Foldable`, `Traversable`, and `Generic1`) would determine which constraints to
infer by checking for fields that contain the last type variable. The problem
was that this last type variable was taken from `tyConTyVars`. For GADTs, the
type variables in each data constructor are _not_ the same type variables as
in `tyConTyVars`, leading to #22167.

This fixes the issue by instead checking for the last type variable using
`dataConUnivTyVars`. (This is very similar in spirit to the fix for #21185,
which also replaced an errant use of `tyConTyVars` with type variables from
each data constructor.)

Fixes #22167.

- - - - -
78037167 by Vladislav Zavialov at 2022-09-18T08:01:20-04:00
Lexer: pass updated buffer to actions (#22201)

In the lexer, predicates have the following type:
	{ ... } :: user       -- predicate state
		-> AlexInput  -- input stream before the token
		-> Int        -- length of the token
		-> AlexInput  -- input stream after the token
		-> Bool       -- True <=> accept the token
This is documented in the Alex manual.

There is access to the input stream both before and after the token.
But when the time comes to construct the token, GHC passes only the
initial string buffer to the lexer action. This patch fixes it:

	- type Action = PsSpan -> StringBuffer -> Int ->                 P (PsLocated Token)
	+ type Action = PsSpan -> StringBuffer -> Int -> StringBuffer -> P (PsLocated Token)

Now lexer actions have access to the string buffer both before and after
the token, just like the predicates. It's just a matter of passing an
additional function parameter throughout the lexer.

- - - - -
75746594 by Vladislav Zavialov at 2022-09-18T08:01:20-04:00
Lexer: define varsym without predicates (#22201)

Before this patch, the varsym lexing rules were defined as follows:

	<0> {
	  @varsym / { precededByClosingToken `alexAndPred` followedByOpeningToken } { varsym_tight_infix }
	  @varsym / { followedByOpeningToken }  { varsym_prefix }
	  @varsym / { precededByClosingToken }  { varsym_suffix }
	  @varsym                               { varsym_loose_infix }
	}

Unfortunately, this meant that the predicates 'precededByClosingToken' and
'followedByOpeningToken' were recomputed several times before we could figure
out the whitespace context.

With this patch, we check for whitespace context directly in the lexer
action:

	<0> {
	  @varsym { with_op_ws varsym }
	}

The checking for opening/closing tokens happens in 'with_op_ws' now,
which is part of the lexer action rather than the lexer predicate.

- - - - -
c1f81b38 by M Farkas-Dyck at 2022-09-19T09:07:05-04:00
Scrub partiality about `NewOrData`.

Rather than a list of constructors and a `NewOrData` flag, we define `data DataDefnCons a = NewTypeCon a | DataTypeCons [a]`, which enforces a newtype to have exactly one constructor.

Closes #22070.

Bump haddock submodule.

- - - - -
1e1ed8c5 by Cheng Shao at 2022-09-19T09:07:43-04:00
CmmToC: emit __builtin_unreachable() after noreturn ccalls

Emit a __builtin_unreachable() call after a foreign call marked as
CmmNeverReturns. This is crucial to generate correctly typed code for
wasm; as for other archs, this is also beneficial for the C compiler
optimizations.

- - - - -
19f45a25 by Jan Hrček at 2022-09-20T03:49:29-04:00
Document :unadd GHCi command in user guide

- - - - -
545ff490 by sheaf at 2022-09-20T03:50:06-04:00
Hadrian: merge archives even in stage 0

We now always merge .a archives when ar supports -L.
This change is necessary in order to bootstrap GHC using GHC 9.4
on Windows, as nested archives aren't supported.
Not doing so triggered bug #21990 when trying to use the Win32
package, with errors such as:

  Not a x86_64 PE+ file.
  Unknown COFF 4 type in getHeaderInfo.

  ld.lld: error: undefined symbol: Win32zm2zi12zi0zi0_SystemziWin32ziConsoleziCtrlHandler_withConsoleCtrlHandler1_info

We have to be careful about which ar is meant: in stage 0, the check
should be done on the system ar (system-ar in system.config).

- - - - -
59fe128c by Vladislav Zavialov at 2022-09-20T03:50:42-04:00
Fix -Woperator-whitespace for consym (part of #19372)

Due to an oversight, the initial specification and implementation of
-Woperator-whitespace focused on varsym exclusively and completely
ignored consym.

This meant that expressions such as "x+ y" would produce a warning,
while "x:+ y" would not.

The specification was corrected in ghc-proposals pull request #404,
and this patch updates the implementation accordingly.

Regression test included.

- - - - -
c4c2cca0 by John Ericson at 2022-09-20T13:11:49-04:00
Add `Eq` and `Ord` instances for `Generically1`

These are needed so the subsequent commit overhauling the `*1` classes
type-checks.

- - - - -
7beb356e by John Ericson at 2022-09-20T13:11:50-04:00
Relax instances for Functor combinators; put superclass on Class1 and Class2 to make non-breaking

This change is approved by the Core Libraries commitee in
https://github.com/haskell/core-libraries-committee/issues/10

The first change makes the `Eq`, `Ord`, `Show`, and `Read` instances for
`Sum`, `Product`, and `Compose` match those for `:+:`, `:*:`, and `:.:`.
These have the proper flexible contexts that are exactly what the
instance needs:

For example, instead of
```haskell
instance (Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) where
  (==) = eq1
```
we do
```haskell
deriving instance Eq (f (g a)) => Eq (Compose f g a)
```

But, that change alone is rather breaking, because until now `Eq (f a)`
and `Eq1 f` (and respectively the other classes and their `*1`
equivalents too) are *incomparable* constraints. This has always been an
annoyance of working with the `*1` classes, and now it would rear it's
head one last time as an pesky migration.

Instead, we give the `*1` classes superclasses, like so:
```haskell
(forall a. Eq a => Eq (f a)) => Eq1 f
```
along with some laws that canonicity is preserved, like:
```haskell
liftEq (==) = (==)
```

and likewise for `*2` classes:
```haskell
(forall a. Eq a => Eq1 (f a)) => Eq2 f
```
and laws:
```haskell
liftEq2 (==) = liftEq1
```

The `*1` classes also have default methods using the `*2` classes where
possible.

What this means, as explained in the docs, is that `*1` classes really
are generations of the regular classes, indicating that the methods can
be split into a canonical lifting combined with a canonical inner, with
the super class "witnessing" the laws[1] in a fashion.

Circling back to the pragmatics of migrating, note that the superclass
means evidence for the old `Sum`, `Product`, and `Compose` instances is
(more than) sufficient, so breakage is less likely --- as long no
instances are "missing", existing polymorphic code will continue to
work.

Breakage can occur when a datatype implements the `*1` class but not the
corresponding regular class, but this is almost certainly an oversight.
For example, containers made that mistake for `Tree` and `Ord`, which I
fixed in https://github.com/haskell/containers/pull/761, but fixing the
issue by adding `Ord1` was extremely *un*controversial.

`Generically1` was also missing `Eq`, `Ord`, `Read,` and `Show`
instances. It is unlikely this would have been caught without
implementing this change.

-----

[1]: In fact, someday, when the laws are part of the language and not
only documentation, we might be able to drop the superclass field of the
dictionary by using the laws to recover the superclass in an
instance-agnostic manner, e.g. with a *non*-overloaded function with
type:

```haskell
DictEq1 f -> DictEq a -> DictEq (f a)
```

But I don't wish to get into optomizations now, just demonstrate the
close relationship between the law and the superclass.

Bump haddock submodule because of test output changing.

- - - - -
6a8c6b5e by Tom Ellis at 2022-09-20T13:12:27-04:00
Add notes to ghc-prim Haddocks that users should not import it

- - - - -
ee9d0f5c by matoro at 2022-09-20T13:13:06-04:00
docs: clarify that LLVM codegen is not available in unregisterised mode

The current docs are misleading and suggest that it is possible to use
LLVM codegen from an unregisterised build.  This is not the case;
attempting to pass `-fllvm` to an unregisterised build warns:

```
when making flags consistent: warning:
    Target platform uses unregisterised ABI, so compiling via C
```

and uses the C codegen anyway.

- - - - -
854224ed by Nicolas Trangez at 2022-09-20T20:14:29-04:00
rts: remove copy-paste error from `cabal.rts.in`

This was, likely accidentally, introduced in 4bf542bf1c.

See: 4bf542bf1cdf2fa468457fc0af21333478293476

- - - - -
c8ae3add by Matthew Pickering at 2022-09-20T20:15:04-04:00
hadrian: Add extra_dependencies edges for all different ways

The hack to add extra dependencies needed by DeriveLift extension missed
the cases for profiles and dynamic ways. For the profiled way this leads
to errors like:

```
GHC error in desugarer lookup in Data.IntSet.Internal:
  Failed to load interface for ‘Language.Haskell.TH.Lib.Internal’
  Perhaps you haven't installed the profiling libraries for package ‘template-haskell’?
  Use -v (or `:set -v` in ghci) to see a list of the files searched for.
ghc: panic! (the 'impossible' happened)
  GHC version 9.5.20220916:
        initDs
```

Therefore the fix is to add these extra edges in.

Fixes #22197

- - - - -
a971657d by Mon Aaraj at 2022-09-21T06:41:24+03:00
users-guide: fix incorrect ghcappdata folder for unix and windows

- - - - -
06ccad0d by sheaf at 2022-09-21T08:28:49-04:00
Don't use isUnliftedType in isTagged

The function GHC.Stg.InferTags.Rewrite.isTagged can be given
the Id of a join point, which might be representation polymorphic.
This would cause the call to isUnliftedType to crash. It's better
to use typeLevity_maybe instead.

Fixes #22212

- - - - -
c0ba775d by Teo Camarasu at 2022-09-21T14:30:37-04:00
Add fragmentation statistic to GHC.Stats

Implements #21537

- - - - -
2463df2f by Torsten Schmits at 2022-09-21T14:31:24-04:00
Rename Solo[constructor] to MkSolo

Part of proposal 475 (https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst)

Moves all tuples to GHC.Tuple.Prim
Updates ghc-prim version (and bumps bounds in dependents)

updates haddock submodule
updates deepseq submodule
updates text submodule

- - - - -
9034fada by Matthew Pickering at 2022-09-22T09:25:29-04:00
Update filepath to filepath-1.4.100.0

Updates submodule

* Always rely on vendored filepath
* filepath must be built as stage0 dependency because it uses
  template-haskell.

Towards #22098

- - - - -
615e2278 by Krzysztof Gogolewski at 2022-09-22T09:26:05-04:00
Minor refactor around Outputable

* Replace 'text . show' and 'ppr' with 'int'.
* Remove Outputable.hs-boot, no longer needed
* Use pprWithCommas
* Factor out instructions in AArch64 codegen

- - - - -
aeafdba5 by Sebastian Graf at 2022-09-27T15:14:54+02:00
Demand: Clear distinction between Call SubDmd and eval Dmd (#21717)

In #21717 we saw a reportedly unsound strictness signature due to an unsound
definition of plusSubDmd on Calls. This patch contains a description and the fix
to the unsoundness as outlined in `Note [Call SubDemand vs. evaluation Demand]`.

This fix means we also get rid of the special handling of `-fpedantic-bottoms`
in eta-reduction. Thanks to less strict and actually sound strictness results,
we will no longer eta-reduce the problematic cases in the first place, even
without `-fpedantic-bottoms`.

So fixing the unsoundness also makes our eta-reduction code simpler with less
hacks to explain. But there is another, more unfortunate side-effect:
We *unfix* #21085, but fortunately we have a new fix ready:
See `Note [mkCall and plusSubDmd]`.

There's another change:
I decided to make `Note [SubDemand denotes at least one evaluation]` a lot
simpler by using `plusSubDmd` (instead of `lubPlusSubDmd`) even if both argument
demands are lazy. That leads to less precise results, but in turn rids ourselves
from the need for 4 different `OpMode`s and the complication of
`Note [Manual specialisation of lub*Dmd/plus*Dmd]`. The result is simpler code
that is in line with the paper draft on Demand Analysis.

I left the abandoned idea in `Note [Unrealised opportunity in plusDmd]` for
posterity. The fallout in terms of regressions is negligible, as the testsuite
and NoFib shows.

```
        Program         Allocs    Instrs
--------------------------------------------------------------------------------
         hidden          +0.2%     -0.2%
         linear          -0.0%     -0.7%
--------------------------------------------------------------------------------
            Min          -0.0%     -0.7%
            Max          +0.2%     +0.0%
 Geometric Mean          +0.0%     -0.0%
```

Fixes #21717.

- - - - -
9b1595c8 by Ross Paterson at 2022-09-27T14:12:01-04:00
implement proposal 106 (Define Kinds Without Promotion) (fixes #6024)

includes corresponding changes to haddock submodule

- - - - -
c2d73cb4 by Andreas Klebinger at 2022-09-28T15:07:30-04:00
Apply some tricks to speed up core lint.

Below are the noteworthy changes and if given their impact on compiler
allocations for a type heavy module:

* Use the oneShot trick on LintM
* Use a unboxed tuple for the result of LintM: ~6% reduction
* Avoid a thunk for the result of typeKind in lintType: ~5% reduction
* lint_app: Don't allocate the error msg in the hot code path: ~4%
  reduction
* lint_app: Eagerly force the in scope set: ~4%
* nonDetCmpType: Try to short cut using reallyUnsafePtrEquality#: ~2%
* lintM: Use a unboxed maybe for the `a` result: ~12%
* lint_app: make go_app tail recursive to avoid allocating the go function
            as heap closure: ~7%
* expandSynTyCon_maybe: Use a specialized data type

For a less type heavy module like nofib/spectral/simple compiled with
-O -dcore-lint allocations went down by ~24% and compile time by ~9%.

-------------------------
Metric Decrease:
    T1969
-------------------------

- - - - -
b74b6191 by sheaf at 2022-09-28T15:08:10-04:00
matchLocalInst: do domination analysis

When multiple Given quantified constraints match a Wanted, and there is
a quantified constraint that dominates all others, we now pick it
to solve the Wanted.

See Note [Use only the best matching quantified constraint].

For example:

  [G] d1: forall a b. ( Eq a, Num b, C a b  ) => D a b
  [G] d2: forall a  .                C a Int  => D a Int
  [W] {w}: D a Int

When solving the Wanted, we find that both Givens match, but we pick
the second, because it has a weaker precondition, C a Int, compared
to (Eq a, Num Int, C a Int). We thus say that d2 dominates d1;
see Note [When does a quantified instance dominate another?].

This domination test is done purely in terms of superclass expansion,
in the function GHC.Tc.Solver.Interact.impliedBySCs. We don't attempt
to do a full round of constraint solving; this simple check suffices
for now.

Fixes #22216 and #22223

- - - - -
2a53ac18 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00
Improve aggressive specialisation

This patch fixes #21286, by not unboxing dictionaries in
worker/wrapper (ever). The main payload is tiny:

* In `GHC.Core.Opt.DmdAnal.finaliseArgBoxities`, do not unbox
  dictionaries in `get_dmd`.  See Note [Do not unbox class dictionaries]
  in that module

* I also found that imported wrappers were being fruitlessly
  specialised, so I fixed that too, in canSpecImport.
  See Note [Specialising imported functions] point (2).

In doing due diligence in the testsuite I fixed a number of
other things:

* Improve Note [Specialising unfoldings] in GHC.Core.Unfold.Make,
  and Note [Inline specialisations] in GHC.Core.Opt.Specialise,
  and remove duplication between the two. The new Note describes
  how we specialise functions with an INLINABLE pragma.

  And simplify the defn of `spec_unf` in `GHC.Core.Opt.Specialise.specCalls`.

* Improve Note [Worker/wrapper for INLINABLE functions] in
  GHC.Core.Opt.WorkWrap.

  And (critially) make an actual change which is to propagate the
  user-written pragma from the original function to the wrapper; see
  `mkStrWrapperInlinePrag`.

* Write new Note [Specialising imported functions] in
  GHC.Core.Opt.Specialise

All this has a big effect on some compile times. This is
compiler/perf, showing only changes over 1%:

Metrics: compile_time/bytes allocated
-------------------------------------
                LargeRecord(normal)  -50.2% GOOD
           ManyConstructors(normal)   +1.0%
MultiLayerModulesTH_OneShot(normal)   +2.6%
                  PmSeriesG(normal)   -1.1%
                     T10547(normal)   -1.2%
                     T11195(normal)   -1.2%
                     T11276(normal)   -1.0%
                    T11303b(normal)   -1.6%
                     T11545(normal)   -1.4%
                     T11822(normal)   -1.3%
                     T12150(optasm)   -1.0%
                     T12234(optasm)   -1.2%
                     T13056(optasm)   -9.3% GOOD
                     T13253(normal)   -3.8% GOOD
                     T15164(normal)   -3.6% GOOD
                     T16190(normal)   -2.1%
                     T16577(normal)   -2.8% GOOD
                     T16875(normal)   -1.6%
                     T17836(normal)   +2.2%
                    T17977b(normal)   -1.0%
                     T18223(normal)  -33.3% GOOD
                     T18282(normal)   -3.4% GOOD
                     T18304(normal)   -1.4%
                    T18698a(normal)   -1.4% GOOD
                    T18698b(normal)   -1.3% GOOD
                     T19695(normal)   -2.5% GOOD
                      T5837(normal)   -2.3%
                      T9630(normal)  -33.0% GOOD
                      WWRec(normal)   -9.7% GOOD
             hard_hole_fits(normal)   -2.1% GOOD
                     hie002(normal)   +1.6%

                          geo. mean   -2.2%
                          minimum    -50.2%
                          maximum     +2.6%

I diligently investigated some of the big drops.

* Caused by not doing w/w for dictionaries:
    T13056, T15164, WWRec, T18223

* Caused by not fruitlessly specialising wrappers
    LargeRecord, T9630

For runtimes, here is perf/should+_run:

Metrics: runtime/bytes allocated
--------------------------------
               T12990(normal)   -3.8%
                T5205(normal)   -1.3%
                T9203(normal)  -10.7% GOOD
        haddock.Cabal(normal)   +0.1%
         haddock.base(normal)   -1.1%
     haddock.compiler(normal)   -0.3%
        lazy-bs-alloc(normal)   -0.2%
------------------------------------------
                    geo. mean   -0.3%
                    minimum    -10.7%
                    maximum     +0.1%

I did not investigate exactly what happens in T9203.

Nofib is a wash:

+-------------------------------++--+-----------+-----------+
|                               ||  | tsv (rel) | std. err. |
+===============================++==+===========+===========+
|                     real/anna ||  |    -0.13% |      0.0% |
|                      real/fem ||  |    +0.13% |      0.0% |
|                   real/fulsom ||  |    -0.16% |      0.0% |
|                     real/lift ||  |    -1.55% |      0.0% |
|                  real/reptile ||  |    -0.11% |      0.0% |
|                  real/smallpt ||  |    +0.51% |      0.0% |
|          spectral/constraints ||  |    +0.20% |      0.0% |
|               spectral/dom-lt ||  |    +1.80% |      0.0% |
|               spectral/expert ||  |    +0.33% |      0.0% |
+===============================++==+===========+===========+
|                     geom mean ||  |           |           |
+-------------------------------++--+-----------+-----------+

I spent quite some time investigating dom-lt, but it's pretty
complicated.  See my note on !7847.  Conclusion: it's just a delicate
inlining interaction, and we have plenty of those.

Metric Decrease:
    LargeRecord
    T13056
    T13253
    T15164
    T16577
    T18223
    T18282
    T18698a
    T18698b
    T19695
    T9630
    WWRec
    hard_hole_fits
    T9203

- - - - -
addeefc0 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00
Refactor UnfoldingSource and IfaceUnfolding

I finally got tired of the way that IfaceUnfolding reflected
a previous structure of unfoldings, not the current one. This
MR refactors UnfoldingSource and IfaceUnfolding to be simpler
and more consistent.

It's largely just a refactor, but in UnfoldingSource (which moves
to GHC.Types.Basic, since it is now used in IfaceSyn too), I
distinguish between /user-specified/ and /system-generated/ stable
unfoldings.

    data UnfoldingSource
      = VanillaSrc
      | StableUserSrc   -- From a user-specified pragma
      | StableSystemSrc -- From a system-generated unfolding
      | CompulsorySrc

This has a minor effect in CSE (see the use of isisStableUserUnfolding
in GHC.Core.Opt.CSE), which I tripped over when working on
specialisation, but it seems like a Good Thing to know anyway.

- - - - -
7be6f9a4 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00
INLINE/INLINEABLE pragmas in Foreign.Marshal.Array

Foreign.Marshal.Array contains many small functions, all of which are
overloaded, and which are critical for performance. Yet none of them
had pragmas, so it was a fluke whether or not they got inlined.

This patch makes them all either INLINE (small ones) or
INLINEABLE and hence specialisable (larger ones).

See Note [Specialising array operations] in that module.

- - - - -
b0c89dfa by Jade Lovelace at 2022-09-28T17:49:49-04:00
Export OnOff from GHC.Driver.Session

I was working on fixing an issue where HLS was trying to pass its
DynFlags to HLint, but didn't pass any of the disabled language
extensions, which HLint would then assume are on because of their
default values.

Currently it's not possible to get any of the "No" flags because the
`DynFlags.extensions` field can't really be used since it is [OnOff
Extension] and OnOff is not exported.

So let's export it.

- - - - -
2f050687 by Bodigrim at 2022-09-28T17:50:28-04:00
Avoid Data.List.group; prefer Data.List.NonEmpty.group

This allows to avoid further partiality, e. g., map head . group is
replaced by map NE.head . NE.group, and there are less panic calls.

- - - - -
bc0020fa by M Farkas-Dyck at 2022-09-28T22:51:59-04:00
Clean up `findWiredInUnit`. In particular, avoid `head`.

- - - - -
6a2eec98 by Bodigrim at 2022-09-28T22:52:38-04:00
Eliminate headFS, use unconsFS instead

A small step towards #22185 to avoid partial functions + safe implementation
of `startsWithUnderscore`.

- - - - -
5a535172 by Sebastian Graf at 2022-09-29T17:04:20+02:00
Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231)

Justification in #22231. Short form: In a demand like `1C1(C1(L))`
it was too easy to confuse which `1` belongs to which `C`. Now
that should be more obvious.

Fixes #22231

- - - - -
ea0083bf by Bryan Richter at 2022-09-29T15:48:38-04:00
Revert "ci: enable parallel compression for xz"

Combined wxth XZ_OPT=9, this blew the memory capacity of CI runners.

This reverts commit a5f9c35f5831ef5108e87813a96eac62803852ab.

- - - - -
f5e8f493 by Sebastian Graf at 2022-09-30T18:42:13+02:00
Boxity: Don't update Boxity unless worker/wrapper follows (#21754)

A small refactoring in our Core Opt pipeline and some new functions for
transfering argument boxities from one signature to another to facilitate
`Note [Don't change boxity without worker/wrapper]`.

Fixes #21754.

- - - - -
4baf7b1c by M Farkas-Dyck at 2022-09-30T17:45:47-04:00
Scrub various partiality involving empty lists.

Avoids some uses of `head` and `tail`, and some panics when an argument is null.

- - - - -
95ead839 by Alexis King at 2022-10-01T00:37:43-04:00
Fix a bug in continuation capture across multiple stack chunks

- - - - -
22096652 by Bodigrim at 2022-10-01T00:38:22-04:00
Enforce internal invariant of OrdList and fix bugs in viewCons / viewSnoc

`viewCons` used to ignore `Many` constructor completely, returning `VNothing`.
`viewSnoc` violated internal invariant of `Many` being a non-empty list.

- - - - -
bea3e880 by Josh Meredith at 2022-10-02T14:32:18-04:00
Add ghcjs changes to deriveConstants:

- change String targetOS option in deriveConstants to an enum
- separate out getWantedGHSJS, removing generated c file in this path

- - - - -
905c954e by doyougnu at 2022-10-02T14:32:18-04:00
Add JavaScript code generator

Adapt code generator of GHCJS to GHC head. Currently it is only enabled
with the hidden -fjavascript flag. It produces .o files that can't be
used yet except by GHCJS's linker.

Codegen: doc

Codegen: correctly return linkable object

Now we can build a static library (-staticlib)

Codegen: doc genLit

Codegen: use assignAll

Codegen: introduce TypedExpr

Refactor assignAll et al, add documentation

Codegen: minor changes

Doc

- - - - -
fe226d6e by doyougnu at 2022-10-02T14:32:18-04:00
Add JS.Rts

JS.Rts: compiles

reword: progress on RtsTypes

StgToJS.Config: add SDoc Context

JSRts: move ppr, workaround def type

JSRts.Types: compiles

JS.Rts: closer to compiling

JS.Rts: move jsIdIdent' to StgToJS.Monad

JS.Rts: remove unused predicates

JS: cleanup, comment sections, math funcs to Make

JS.Rts.Types: compiles

StgToJS.Expr: fix compilation errors

StgToJS.DataCon: move initClosure

JS.Rts: remove Alloc module

JS.Rts: initalize Rts module, remove redundant fs

JS: init Rts.Alloc move initClosure

JS.Apply: unwinding combinators in progress

JS: add helpers and fixmes

JS.Rts.Apply: no more e's, add closure, reg helper

StgToJS: add ToStat instance ClosureInfo

JS.Rts.Apply: closer to compiling

JS.Rts.Apply: more removal of #

JS.Rts.Apply: (#) removed

JS.Rts.Apply: compiles

JS.Rts.Rts: just pretty printing left

JS.Rts: Add Notes

JS.Rts: add file headers and notes

JS.Rts.Rts: fixing stringy issues

JS.Rts.Rts: compiles

JS.Rts.Rts: fix non-exhaustive patterns warnings

- - - - -
ee79436c by Sylvain Henry at 2022-10-02T14:32:18-04:00
Doc has been moved into GHC.StgToJs top-level module

- - - - -
d1f1e910 by Sylvain Henry at 2022-10-02T14:32:19-04:00
JS.Rts; refactoring and move to StgToJS

* add closure manipulation helpers and use them in Apply
* add cache (Array) for pre-generated PAP names
* reduce line length:
  * use BlockArguments instead of parens
  * remove implicit mconcat in jVar's body

Rts: more refactorings

Rts: move into StgToJS hierarchy

- - - - -
b861896b by Sylvain Henry at 2022-10-02T14:32:19-04:00
JS: cleanup, renaming, better module layout

Various degrees of cleanup adapting GHCJS to GHC. We move several
functions to CoreUtils, remove duplication between the JS.Rts.Apply and
Apply module and factor out closure related code into a Closure module
for cohesion.

Deduplicate code between Rts.Apply and Apply

Move might_be_a_function into CoreUtils

Factorize closure stuff into Closure module

Rename closureExtra into closureField

Minor renamings, comments...

- - - - -
20a01a8f by Sylvain Henry at 2022-10-02T14:32:19-04:00
JS.Backend: add FFI code but don't implement yet

FFI: don't crash on JavaScript foreign imports

Note that they are still not desugared properly!!

But the following cmd doesn't crash anymore:

  ghc -fjavascript Test.hs -fforce-recomp -ddump-tc -fno-code -ddump-ds

FFI: adapt GHCJS desugarer

FFI: support direct application

The following example:

  foo :: Int# -> Int#
  foo = add 50000#

  foreign import javascript
    "(function(x,y) { return (x + y) })"
    add :: Int# -> Int# -> Int#

is compiled into an application like this:

  var h$mainZCMzifoozur2_e;
  h$mainZCMzifoozur2_e = (function()
                            {
                            var h$mainZCMziaddzur1;
                            h$mainZCMziaddzur1 = h$r1.d1;
                            var h$$mainZCMzietazuB0_8KXnScrCjF5;
                            h$$mainZCMzietazuB0_8KXnScrCjF5 = h$r2;
                            h$r3 = h$$mainZCMzietazuB0_8KXnScrCjF5;
                            h$r2 = 50000;
                            h$r1 = h$mainZCMziaddzur1;
                            return h$ap_2_2_fast();
                            return h$rs();
                          });
  var h$mainZCMziaddzur1_e;
  h$mainZCMziaddzur1_e = (function()
                            {
                            var h$$mainZCMzidszusAk_236l8r0P8S9;
                            h$$mainZCMzidszusAk_236l8r0P8S9 = h$r2;
                            var h$$mainZCMzids1zusAl_336l8r0P8S9;
                            h$$mainZCMzids1zusAl_336l8r0P8S9 = h$r3;
                            var h$$mainZCM_2;
                            var h$$mainZCMziwildzusAn_536l8r0P8S9;
                            try
                              {
                              h$$mainZCMziwildzusAn_536l8r0P8S9 = (function(x,y) { return (x + y) })(h$$mainZCMzidszusAk_236l8r0P8S9, h$$mainZCMzids1zusAl_336l8r0P8S9)
                            }
                            catch(except)
                              {
                              return h$throwJSException(except)
                            };
                            var h$$mainZCMzids3zusAp_736l8r0P8S9;
                            h$$mainZCMzids3zusAp_736l8r0P8S9 = h$$mainZCMziwildzusAn_536l8r0P8S9;
                            h$r1 = h$$mainZCMzids3zusAp_736l8r0P8S9;
                            return h$rs();
                          });

FFI: correctly dispatch for foreign exports too

FFI: move C FFI desugaring into its own module

FFI: avoid DynFlags in toJsName (copy of toCName)

- - - - -
a1732f18 by Sylvain Henry at 2022-10-02T14:32:19-04:00
Configure: preliminary support for triple js-unknown-ghcjs

- - - - -
0b91daee by Sylvain Henry at 2022-10-02T14:32:20-04:00
Driver: enable JS backend by default for JS arch

- - - - -
57957cb4 by doyougnu at 2022-10-02T14:32:20-04:00
JS.Backend: Add JS specific Linker

JS: initialize Linker, DynamicLinking

JS.Printer: adapted to GHC Head

JS.Printer: some cleanup and init Printer

StgToJS.Printer: Compiles

JS.Linker: Add types, expose JS keywords

JS.Syntax: add Binary instance on Ident's

JS.Linker: Migrate more Types to Data.Binary

JS.Linker.Types: compiles and adapted to GHC Head

JS.Linker.Types: compiles

JS.Linker.Types: add UseBase type

JS.Linker: Comments and Cleanup

JS.Linker.Types: add TH types, Env type, DepsLoc

JS.Linker: more FIXMEs numerous Linker fixes

JS.Linker: removed Text references

JS.UnitUtils: add package related helper functions

JS.Linker: more DynFlags removal

JS.Linker: Time for semantic errors

JS.Linker: DynFlags finally removed

JS.Linker: 107 compile errors to go

JS.Linker.Utils: initialized, adapted to GHC Head

JS.Linker.Utils: initialize Utils module

JS.Linker.Utils: more utils

JS.Rts: move rtsText to Rts

JS.Linker: linkerStats implemented

JS.Compactor: compiles, adapted to GHC Head

JS.Compactor: have to retrofit compact for linker

JS.Linker.Compactor: unwinding lenses

JS.Linker.Compactor: comments over addItem

JS.Linker.Compactor: Lenses removed

JS.Linker.Compactor: SHA256 removed

JS.Linker.Compactor: only missing instances left

JS.Linker.Compactor: compiles

JS.Linker: compiles, adapted to ghc Head

JS.Linker: More progress

JS.Linker: link in memory compiles

JS.Linker: just shims left

JS.Linker.DynamicLinking compiles: adapted to head

JS.Linker.DynamicLinking: initialization

JS.Linker.DynamicLinking: compiles up to Variants

JS.Variants: initialize

JS.Linker: numerous and various fixes

JS.Linker.DynamicLinking: only small errors left

JS.Linker.Archive: compiles, adapted to GHC Head

JS.Linker: initialize Archive compat module

JS.Linker.Archive: minor fixes

JS.Linker.DynamicLinking: compiles

JS.Linker: cleanup, remove Variants, add comments

fixup: more cleanup

JS.Linker: more cleanup and comments

- - - - -
342e2d0a by Sylvain Henry at 2022-10-02T14:32:20-04:00
Minor panic fix

- - - - -
a327451f by Sylvain Henry at 2022-10-02T14:32:20-04:00
Linker: fix stage2 build

- - - - -
90e08bfe by Sylvain Henry at 2022-10-02T14:32:21-04:00
Configure: Add support fo JS as unregistered ABI

Configure: detect emscripten tools

e.g. on ArchLinux:

  EMSDK=/usr/lib/emscripten EMSDK_LLVM=/opt/emscripten-llvm ./configure --target=js-unknown-ghcjs

Configure: detect nm tool too, required by Hadrian

Configure: make StgToJS use non-unregisterised ABI

It should probably be a third kind of ABI...

- - - - -
0ab051c2 by doyougnu at 2022-10-02T14:32:21-04:00
JS.Linker: Hook up to GHC.Driver.Pipeline

JS.Linker.Types: Add newGhcjsEnv function

JS.UnitUtils: fix encodeModule api

JS.Linker: more removal of HscEnv

JS.Linker: hooked into GHC.Driver.Pipeline

- - - - -
8617b12d by Sylvain Henry at 2022-10-02T14:34:44-04:00
VERY WIP Hadrian/rts fixes

export EMSDK_LLVM=/opt/emscripten-llvm
export EMSDK=/usr/lib/emscripten
export PATH=./inplace/ghcjs_toolchain/bin:$PATH

./configure --target=js-unknown-ghcjs
./hadrian/build --flavour=quick-js -j --bignum=native --docs=none -V

- - - - -
49ac32f1 by Sylvain Henry at 2022-10-02T14:34:49-04:00
Force creation of rts library with dummy file

- - - - -
b490b19c by Sylvain Henry at 2022-10-02T14:34:49-04:00
ghc-prim: avoid building C files

- - - - -
376cfb32 by Sylvain Henry at 2022-10-02T14:34:49-04:00
Hadrian: disable -fllvm

- - - - -
c48f2ff1 by Sylvain Henry at 2022-10-02T14:34:50-04:00
JS: fix caches

Note that the fact that we need index 0 may hide another issue...

- - - - -
2c79cd1e by Sylvain Henry at 2022-10-02T14:34:50-04:00
codegen: enhance genCon debug message

- - - - -
fad0bde0 by Sylvain Henry at 2022-10-02T14:34:50-04:00
RTS: fix stupid comment

- - - - -
20e68576 by Sylvain Henry at 2022-10-02T14:34:50-04:00
RTS: embed headers

- - - - -
8c876598 by Sylvain Henry at 2022-10-02T14:34:50-04:00
JS.StgToJS: add documentation header for JS Types

- - - - -
068618a0 by Sylvain Henry at 2022-10-02T14:34:51-04:00
CodeGen: refactor ExprCtx code

- - - - -
aa981870 by Sylvain Henry at 2022-10-02T14:34:51-04:00
CodeGen: cache LNE frame size

- - - - -
bd8d55c3 by doyougnu at 2022-10-02T14:34:51-04:00
JS.Types: Add Outputable for TypedExpr

- - - - -
e7ab82f0 by doyougnu at 2022-10-02T14:34:51-04:00
JS.CoreUtils: handle IOPort case

- - - - -
be61f5e6 by doyougnu at 2022-10-02T14:34:51-04:00
JS.Expr: Fix unhandled datacon for RuntimeRep

- - - - -
4573084b by doyougnu at 2022-10-02T14:34:52-04:00
JS.Literals: Adapt genLit to new Literal domain

- - - - -
8921ab0d by Sylvain Henry at 2022-10-02T14:34:52-04:00
RTS: expose more headers (required to build base)

- - - - -
6b290d5e by Sylvain Henry at 2022-10-02T14:34:52-04:00
Base: don't build C and Cmm sources with ghcjs

- - - - -
d7d0a007 by Sylvain Henry at 2022-10-02T14:34:52-04:00
Tentatively set NO_REGS for JS platforms

- - - - -
a0c1b082 by Sylvain Henry at 2022-10-02T14:34:52-04:00
CodeGen: output LitRubbish as null JS values

- - - - -
8db5980b by Sylvain Henry at 2022-10-02T14:34:53-04:00
base: disable forkOS and bound thread machinery

- - - - -
9f4fb961 by Sylvain Henry at 2022-10-02T14:34:53-04:00
CodeGen: support StackSnapshot# in primTypeVt

- - - - -
2b508b5e by Sylvain Henry at 2022-10-02T14:34:53-04:00
CodeGen: better debug message for assignCoerce1

- - - - -
179e9717 by Sylvain Henry at 2022-10-02T14:34:53-04:00
Misc: enable HasDebugCallStack for zipWithEqual*

- - - - -
06a14daa by Sylvain Henry at 2022-10-02T14:34:53-04:00
CodeGen: remove useless imports

- - - - -
966b3896 by Sylvain Henry at 2022-10-02T14:34:54-04:00
Stg: expose pprStgAlt

- - - - -
c8e1ae63 by Sylvain Henry at 2022-10-02T14:34:54-04:00
CodeGen: restore assignAll (instead of assignAllEqual)

- - - - -
a3f1e56a by Sylvain Henry at 2022-10-02T14:34:54-04:00
CodeGen: handle proxy#

- - - - -
ab1eb451 by doyougnu at 2022-10-02T14:34:54-04:00
ghc-heap: Don't compile Cmm file for JS-Backend

- - - - -
5c552bdd by doyougnu at 2022-10-02T14:34:54-04:00
Driver.Main: minor refactor do_code_gen

To clearly separate the JS-Backend from any other backend

- - - - -
d1741871 by Sylvain Henry at 2022-10-02T14:34:54-04:00
Configure: fix echo on Mac, add ghcjs target OS

- - - - -
ef65a12d by Sylvain Henry at 2022-10-02T14:34:55-04:00
Configure: fix previous commit

- - - - -
4c642f9f by Luite Stegeman at 2022-10-02T14:34:55-04:00
fix package name in module name field of system dependencies

- - - - -
51a73fe4 by Luite Stegeman at 2022-10-02T14:34:55-04:00
fix duplicate module name in symbols

- - - - -
95015786 by doyougnu at 2022-10-02T14:34:55-04:00
GHCi.FFI: ignore ffi.h and friends for js-backend

- - - - -
39fa3fa3 by Sylvain Henry at 2022-10-02T14:34:55-04:00
RTS: fix build of native rts

- - - - -
83571f4c by Sylvain Henry at 2022-10-02T14:34:56-04:00
Remove temporary -fjavascript flag

- - - - -
bb74d223 by Sylvain Henry at 2022-10-02T14:34:56-04:00
Codegen: fix symbol names ppr

- - - - -
8bec6029 by Sylvain Henry at 2022-10-02T14:34:56-04:00
Outputable: add ShortText instance

- - - - -
71ba2a1a by Sylvain Henry at 2022-10-02T14:34:56-04:00
Linker: enhance debugging message

- - - - -
367f4e5b by Sylvain Henry at 2022-10-02T14:34:56-04:00
Remove unused ghcjs unit related code

- - - - -
fd018282 by Sylvain Henry at 2022-10-02T14:34:57-04:00
ghci: Avoid unused-xyz warnings

- - - - -
2e830e94 by Sylvain Henry at 2022-10-02T14:34:57-04:00
Linker: remove wiring of ghcjs-prim and ghcjs-th

They will be replaced by ghc-prim, base, template-haskell, etc.

- - - - -
1e04274a by Sylvain Henry at 2022-10-02T14:34:57-04:00
Add outputable instance for Deps

- - - - -
a22744fa by doyougnu at 2022-10-02T14:34:57-04:00
Docs: JS.Syntax, JS.Make docs done

JS-backend: Add documentation headers

Docs: JS.Syntax done

Docs: JS.Make done

Docs: JS.Make JS.Syntax refined a bit

- - - - -
7cd6a8d5 by Sylvain Henry at 2022-10-02T14:34:57-04:00
Rename u_env into unit_env (more common)

- - - - -
c0e09342 by Sylvain Henry at 2022-10-02T14:34:58-04:00
Linker: deduplication + fixes

- deduplicate code that was copied from old GHC
- explicitly add preloadUnits to the link
- avoid calling getShims

- - - - -
3b6544f4 by Sylvain Henry at 2022-10-02T14:34:58-04:00
Linker: reenable packStrings (not yet implemented though)

- - - - -
1bfbb146 by Sylvain Henry at 2022-10-02T14:34:58-04:00
ShortText: add singleton

- - - - -
0b27abf6 by Sylvain Henry at 2022-10-02T14:34:58-04:00
Linker: force less efficient (but working) static encoding

- - - - -
6f852d18 by Luite Stegeman at 2022-10-02T14:34:58-04:00
add GHCJS modules to base package

- - - - -
be2a2ba1 by Sylvain Henry at 2022-10-02T14:34:59-04:00
Linker: remove JS Shims,tiny GHC.Linker refactor

- - - - -
1534bcae by doyougnu at 2022-10-02T14:34:59-04:00
Hadrian: QuickJS ways [] --> Set

- - - - -
ead3a2d3 by doyougnu at 2022-10-02T14:34:59-04:00
JS-Backend: rebased to master 468f919b

First rebase of the JS-Backend. This rebase includes the JS backend
combined with !7442 (new backend design). Unfortunately we have to short
circuit the new backend design because the JS backend takes over after
STG and not after StgToCmm.

What's working:
  - hadrian builds JS backend
  - JS backend outputs .js files and "links" them

What still has to be done:
   - JS backend is missing core js libraries as we add these we
   discover bugs in the linker and js rts.

- - - - -
cd114848 by doyougnu at 2022-10-02T14:34:59-04:00
JS: silence haddock warnings

JS Backend: remove misc. warnings

- - - - -
54f943fa by doyougnu at 2022-10-02T14:34:59-04:00
JS Backend: ghcjs_HOST_OS --> js_HOST_ARCH

- - - - -
6d25a9cc by Sylvain Henry at 2022-10-02T14:35:00-04:00
JS.Linker: add shims

GHCJS uses JS files for primitive things like the GC and RTS. We call
these JS files "shims". This sequence of commits adds shims from JS and
includes them for linking. In addition the shim directory is controlled
via an evironment variable JS_RTS_PATH...at least for now.

Linker: implement tryReadShimFile

Linker: link with shims provided via an env variable

Use JS_RTS_PATH to provide a directory into which .js and .js.pp files
will be linked into rts.js

JS.Linker: add js dir at root, fix js cpp includes

JS.gc.pp: remove variadic macro

JS.RTS: add rts JS shims files, remove shim CPP

RTS: remove the need for rts.h and add rts JS files

rts.h only contained a few constants duplicated in the codegen. Let's
use the Haskell version as the single source of truth and pass defined
values explicitly to cpp command line ("-DXYZ=abc" arguments).

Also switch from "raw" (use_cpp_and_not_cc_dash_E = True) to the
opposite: in both case we call "cc -E" (meh), but with False the
preprocessor doesn't choke one varargs in macros.

RTS: remove integer.js.pp

We use the native ghc-bignum backend, so we don't need the GMP
compatible JS code.

In addition, this code was failing to run as it requires the JSBN
(https://www.npmjs.com/package/jsbn) "Javascript big number" library,
which we don't necessarily have installed.

RTS: fix typo in field name

RTS: generate CPP macros in Haskell

RTS: share common CPP def into CAFs

- - - - -
4620ec86 by Sylvain Henry at 2022-10-02T14:35:00-04:00
CPP: disable line markers

CPP: move option before input filename (to be squashed)

- - - - -
ba30a8f5 by Sylvain Henry at 2022-10-02T14:35:00-04:00
Linker: add more types

Some cleanup

Enhance and fix LinkerStats

Document and refactor renderLinker

Split collectDeps

Fix collectDeps

Fix linker stats rendering

Remove unused seqListSpine

It isn't used in ghcjs either

- - - - -
c69e10ce by Sylvain Henry at 2022-10-02T14:35:00-04:00
Add some missing primops (Word32,Int32)

Also fix the rendering of missing primops (they must be z-encoded to
avoid having a "#" in their JS name)

- - - - -
6ce342e0 by Sylvain Henry at 2022-10-02T14:35:00-04:00
FFI: desugar every foreign import/export in JS with JS backend

It means we also desugar CApi calls into JS.

It's probably wrong but instead of generating invalid JS we will only
get the failure at runtime when we will use the function.

fixup

- - - - -
1738ffe9 by doyougnu at 2022-10-02T14:35:01-04:00
JS.Linker: remove dflags includePath workaround.

We implemented a workaround for shims that modified the dynflags
includePaths so that the JS backend would find the rts.h file during CPP
of shims. Since aebcca98 this is no longer required because we've
removed the need for rts.h completely. Thus, this commit reverts that
modification.

- - - - -
bd080245 by Sylvain Henry at 2022-10-02T14:35:01-04:00
Temporarily wire-in base's shim

Use JS_BASE_PATH env var to set base's shim directory (js_base for now)

Also minor other changes

base: fix encoding for JS arch

- - - - -
84214c20 by Sylvain Henry at 2022-10-02T14:35:01-04:00
Add primops

Add primop

- - - - -
aa0db4b0 by doyougnu at 2022-10-02T14:35:01-04:00
Make Shims type, refactor JS Linker

This commit:
 - Adds a proper Shim type and associated utilities. These utitlies are
 purposefully limited to ensure the ShimLbl tag is preserved thus
 guarenteeing shim ordering at link time.
 - Refactors the JS backend linker to use this ordering and Shim API.
 The ordering is not correct (yet!) but with this API its much easier to
 triage, experiment and diagnose link time issues.

Refactor linker to compile time shim ordering

- - - - -
3d418975 by doyougnu at 2022-10-02T14:35:01-04:00
Base: Adapt primitives to JS backend, add base.js

- - - - -
961b41d4 by doyougnu at 2022-10-02T14:35:01-04:00
Base: Remove binding forms in JS ffi

- - - - -
077669aa by Josh Meredith at 2022-10-02T14:35:02-04:00
Replace GHCJS Objectable with GHC Binary

- - - - -
e7d16352 by Sylvain Henry at 2022-10-02T14:35:02-04:00
Binary: remove unused Map instance

- - - - -
028b842b by Sylvain Henry at 2022-10-02T14:35:02-04:00
CodeGen: Add export list

- - - - -
525f8904 by Sylvain Henry at 2022-10-02T14:35:02-04:00
Primops: add some Int64/Word64 primops

- - - - -
7d1d87e2 by Sylvain Henry at 2022-10-02T14:35:03-04:00
base: fix one ffi import

- - - - -
f838ff59 by doyougnu at 2022-10-02T14:35:03-04:00
base: CPP for JS-backend, adapt write in base shim

This commit ports over each CPP directive from GHCJS to base. In
addition, it adds struct.js.pp to Base shim directory and modifies
h$base_write to always take 6 arguments. Thereby avoiding errors such as
"c(bytesWritten) is not a function". The missing parameter was the file
descriptor object, fdo, which was looked up in the function itself and
is now passed through to comport with the FFI expectations.

- - - - -
095620c3 by doyougnu at 2022-10-02T14:35:03-04:00
fixup: remove redundant struct.js.pp in js_base

- - - - -
ef0e8d34 by doyougnu at 2022-10-02T14:35:03-04:00
JS.Linker: enable linker RTS symbols

- - - - -
bd889329 by doyougnu at 2022-10-02T14:35:03-04:00
base.GHCJS: adapt Prim to direct call FFI format

- - - - -
c574a945 by doyougnu at 2022-10-02T14:35:04-04:00
Linker: Load JSVal from base not ghc-prim

- - - - -
484d4a93 by doyougnu at 2022-10-02T14:35:04-04:00
fixup: caught one more reference to JSVal in prim

- - - - -
0f903562 by Sylvain Henry at 2022-10-02T14:35:04-04:00
base: match on js arch , not ghcjs os

- - - - -
3ace99b6 by Sylvain Henry at 2022-10-02T14:35:04-04:00
Fix MK_JSVAL

- - - - -
a4f658bf by doyougnu at 2022-10-02T14:35:05-04:00
Prim: cleanup comments

- - - - -
56a2dc7e by doyougnu at 2022-10-02T14:35:05-04:00
JS.Prim: add Int64 PrimOps

- - - - -
96cc328f by Sylvain Henry at 2022-10-02T14:35:05-04:00
Vendor MD5 lib

- - - - -
b34a53d7 by Sylvain Henry at 2022-10-02T14:35:05-04:00
More 64-bit primops

- - - - -
1261fb76 by Sylvain Henry at 2022-10-02T14:35:05-04:00
CodeGen: use if10 helper

- - - - -
e0f7281f by Sylvain Henry at 2022-10-02T14:35:06-04:00
Ppr: fix selector to avoid adding a newline

- - - - -
8b9f5355 by doyougnu at 2022-10-02T14:35:06-04:00
base: GHCJS.Prim make ffi imports use anon funcs

- - - - -
31af9a82 by Sylvain Henry at 2022-10-02T14:35:06-04:00
Linker: disable invalid constructors again

- - - - -
8a8a7648 by Sylvain Henry at 2022-10-02T14:35:06-04:00
More 64-bits primops

- - - - -
4654ba8f by Sylvain Henry at 2022-10-02T14:35:06-04:00
Fix base_write function

- - - - -
eefb7b75 by Sylvain Henry at 2022-10-02T14:35:07-04:00
Fix base_write for 32-bit size_t

- - - - -
60bcef03 by Sylvain Henry at 2022-10-02T14:35:07-04:00
Configure: fix detection of the target toolchain

- - - - -
ce80fb8a by Sylvain Henry at 2022-10-02T14:35:07-04:00
Remove js_base directory

- - - - -
63038b6b by Sylvain Henry at 2022-10-02T14:35:07-04:00
Kill Node when the main loop reports an unhandled exception

- - - - -
c326778f by Sylvain Henry at 2022-10-02T14:35:07-04:00
CodeGen: preparation to make match on primops complete

- - - - -
748d722a by Sylvain Henry at 2022-10-02T14:35:07-04:00
Primops: fix Compact primops

- - - - -
100c696d by Sylvain Henry at 2022-10-02T14:35:08-04:00
Ignore result arity for some exception primops

- - - - -
36c4b6ed by Sylvain Henry at 2022-10-02T14:35:08-04:00
Fix more primops. Bump array submodule!

- - - - -
f5b83bce by Sylvain Henry at 2022-10-02T14:35:08-04:00
Compact: fix return of 3 values

- - - - -
7ed29cfd by Sylvain Henry at 2022-10-02T14:35:08-04:00
Configure: switch to absolute path

- - - - -
e08711ee by Sylvain Henry at 2022-10-02T14:35:08-04:00
Add a few primops

- - - - -
aafb39bd by Sylvain Henry at 2022-10-02T14:35:09-04:00
Primop: implement WordAdd2

- - - - -
5d3964a2 by Luite Stegeman at 2022-10-02T14:35:09-04:00
quick fix for uTypeVt and typePrimRep panics

this may cause other panics, a full fix will require a bit
more rework and probably removal of VarType

- - - - -
c6fdb0b7 by Josh Meredith at 2022-10-02T14:35:09-04:00
Replace ShortText with (Lexical)FastString in GHCJS backend

- - - - -
c9dd28b6 by Sylvain Henry at 2022-10-02T14:35:09-04:00
Primops: add arithmetic ops

Primops: add decodeDoubleInt64 back

Primop: added timesInt2#

Primop: add mulWord32 and mul2Word32

- - - - -
8011da77 by Sylvain Henry at 2022-10-02T14:35:09-04:00
Reduce dependency on goog

- - - - -
3ca0ebbe by Sylvain Henry at 2022-10-02T14:35:10-04:00
Primop: implement quotWord32, remWord32, and quotRemWord32

- - - - -
9f411739 by Sylvain Henry at 2022-10-02T14:35:10-04:00
Primop: Implement quotRem2Word32, misc fixes

Primop: implement quotRem2Word32

Primop: fix timesInt2#

Primop: fix some shifting primops

- - - - -
9a6ea784 by Sylvain Henry at 2022-10-02T14:35:10-04:00
Fix bug in upd_frame

I've introduced this bug when I've refactored the code to use helpers to
assign closures.

- - - - -
72de8930 by Sylvain Henry at 2022-10-02T14:35:10-04:00
Primop: throw an exception for unimplemented primops

- - - - -
21afdae8 by Sylvain Henry at 2022-10-02T14:35:10-04:00
Primop: fix remWord32

- - - - -
e0aec61f by Josh Meredith at 2022-10-02T14:35:11-04:00
Configure: add EMSDK_BIN, match emsdk expectations

Change EMSDK vars to match emscripten/emsdk_env.sh definitions

Add EMSDK_BIN environment variable to configure

- - - - -
16e09ac9 by Sylvain Henry at 2022-10-02T14:35:11-04:00
resultSize: correctly handle Void#

- - - - -
ce29eb73 by Sylvain Henry at 2022-10-02T14:35:11-04:00
Primop: fix Sized test, more shifting fixes

Primop: ensure that we return u32 values for word primops

Also a refactoring from i3 to i32 for clarity.

Primop: add/fix more shifting primops

Primops: fix Sized test!

- - - - -
89afe98a by Sylvain Henry at 2022-10-02T14:35:11-04:00
StgToJS.Apply: Docs

Doc

Doc

- - - - -
05949bea by Josh Meredith at 2022-10-02T14:35:11-04:00
Fix EMSDK configure condition

- - - - -
5e007d22 by doyougnu at 2022-10-02T14:35:12-04:00
StgToJS.Arg: Unboxable Literal Optimization note

- - - - -
fe911a64 by Sylvain Henry at 2022-10-02T14:35:12-04:00
Fix Outputable instances for JExpr/JVal

- Put orphan instances in JS.Ppr
- Also fix some redundant imports

- - - - -
49effd4b by doyougnu at 2022-10-02T14:35:12-04:00
configure: avoid CXX stdlib check for js backend

and some cleanup for a previously mis-applied commit during rebasing

- - - - -
34d01c3c by doyougnu at 2022-10-02T14:35:12-04:00
fixup: misc. fixes post rebase

- - - - -
1c6726e7 by Sylvain Henry at 2022-10-02T14:35:12-04:00
PrimOps: add more 64-bit primops

PrimOp: implement more 64-bit primops + PM fix

Ensure that we cover every primop explicitly

- - - - -
103c0062 by Sylvain Henry at 2022-10-02T14:35:13-04:00
PrimOp: correclty (un)handle new thread related primops

- - - - -
314cfb54 by Sylvain Henry at 2022-10-02T14:35:13-04:00
PrimOp: disable LabelThreadOp for now

- - - - -
0bf05b17 by Sylvain Henry at 2022-10-02T14:35:13-04:00
Minor doc/cleanup

Fix more redundant imports

- - - - -
7c46109f by doyougnu at 2022-10-02T14:35:13-04:00
base: GHCJS.Prim directory --> GHC.JS.Prim

- - - - -
d7454442 by Luite Stegeman at 2022-10-02T14:35:14-04:00
implement KeepAlive primop

- - - - -
03fcccce by Sylvain Henry at 2022-10-02T14:35:14-04:00
Remove orphan instance for StaticArg

- - - - -
d4c9dca2 by Sylvain Henry at 2022-10-02T14:35:14-04:00
Remove redundant jsIdIdent' function

- - - - -
ec7df189 by Sylvain Henry at 2022-10-02T14:35:14-04:00
Split StgToJS.Monad into StgToJS.{Monad,Ids,Stack}

- - - - -
9f083fb1 by Sylvain Henry at 2022-10-02T14:35:14-04:00
Apply: remove commented case (wasn't optimized either in latest ghcjs)

- - - - -
07ea2b0b by Sylvain Henry at 2022-10-02T14:35:15-04:00
Doc: Apply

Apply: doc and refactoring

- use new types instead of Bool/Int
- factorize some code

- - - - -
3aace720 by Sylvain Henry at 2022-10-02T14:35:15-04:00
Primop: arith fixes

Primop: fix 64-bit shifting primops + add some traces

Primop: fix quotRem2Word32

Primop: fix timesInt2. Progress towards passing arith003

PrimOp: fix timesInt32

PrimOp: use mulWord32 when appropriate

- - - - -
45c0b30c by doyougnu at 2022-10-02T14:35:15-04:00
Configure: remove EMSDK hacks and wrapper scripts

configure JS: remove wrapper scripts

Configure: remove EMSDK hacks. Use emconfigure instead

emconfigure ./configure --target=js-unknown-ghcjs

- - - - -
cfc4ffc8 by Sylvain Henry at 2022-10-02T14:35:15-04:00
GHCJS.Prim leftovers

- - - - -
f50a946c by Sylvain Henry at 2022-10-02T14:35:15-04:00
Linker: fix linking issue for tuples

- - - - -
7a9c0afe by Sylvain Henry at 2022-10-02T14:35:16-04:00
FFI: remove narrowing

Fix tests such as cgrun015 (Core lint error)

- - - - -
804e6fe1 by Sylvain Henry at 2022-10-02T14:35:16-04:00
Linker: disable logs with default verbosity

- - - - -
28aa7302 by Sylvain Henry at 2022-10-02T14:35:16-04:00
Append program name in top-level exception handler

- - - - -
b456884e by doyougnu at 2022-10-02T14:35:16-04:00
GHC.JS: Remove FIXMEs

JS.Syntax: Remove FIXMEs

JS.Make: remove FIXMEs

JS.Ppr/Transform: Remove FIXMEs

- - - - -
cba7f9a3 by Sylvain Henry at 2022-10-02T14:35:16-04:00
Primop: fix timesInt2#

Pass arith003 test

- - - - -
6fabd857 by doyougnu at 2022-10-02T14:35:17-04:00
JS.Linker.Linker: remove FIXMEs, clean dead code

- - - - -
be2519ed by Sylvain Henry at 2022-10-02T14:35:17-04:00
Linker: link platform shim before the others

- - - - -
1f842564 by Sylvain Henry at 2022-10-02T14:35:17-04:00
Primops: rework 64-bit and Word32 primops

- Use BigInt instead of complex and buggy bit twiddling. We'll assess
  performance later. Let's use a correct and simple implementation for
  now.

- Implement previously missing 64-bit quot and rem

- Refactor logical operators and Prim module more generally

- - - - -
69770001 by Sylvain Henry at 2022-10-02T14:35:17-04:00
PrimOp: fixup previous commit...

- - - - -
277b73d7 by Sylvain Henry at 2022-10-02T14:35:18-04:00
Primop: fixup previous commit

- - - - -
0fc9ade3 by Sylvain Henry at 2022-10-02T14:35:18-04:00
Doc: minor changes

- - - - -
b9495f6d by Sylvain Henry at 2022-10-02T14:35:18-04:00
Add debug option to watch for insertion of undefined/null in the stack

- - - - -
183f9fff by Sylvain Henry at 2022-10-02T14:35:18-04:00
Apply: fix tag generation

- - - - -
6f33191c by Sylvain Henry at 2022-10-02T14:35:18-04:00
Remove redundant import

- - - - -
73e793b3 by Sylvain Henry at 2022-10-02T14:35:19-04:00
Testsuite: disable Cmm tests with the JS backend

- - - - -
d291d080 by Sylvain Henry at 2022-10-02T14:35:19-04:00
Base: fix c_interruptible_open

- - - - -
5aaec337 by Sylvain Henry at 2022-10-02T14:35:19-04:00
Base: fix typo in long_from_number

- - - - -
694e0734 by Sylvain Henry at 2022-10-02T14:35:19-04:00
Env: only add program name to errors, not to traces

- - - - -
645e96fb by Sylvain Henry at 2022-10-02T14:35:19-04:00
Testsuite: disable more Cmm tests

- - - - -
75b180b6 by doyougnu at 2022-10-02T14:35:19-04:00
JS.Linker: removes FIXMEs

JS.Linker.Linker: remove FIXMEs, clean dead code

StgToJS.Linker.Utils: remove FIXMEs

Compactor: Remove FIXMEs

StgToJS.Linker.Types: Remove FIXMEs

JS.Linker.Archive/Dynamic: remove FIXMEs

StgToJS.Linker.Shims: remove FIXMEs

- - - - -
e108ae59 by doyougnu at 2022-10-02T14:35:20-04:00
JS RTS: remove FIXMEs

StgToJS.Rts.Types: Remove FIXMEs

- - - - -
37407855 by Sylvain Henry at 2022-10-02T14:35:20-04:00
Primop: fix bswap32/64 (cf cgrun072)

- - - - -
ae66c1a7 by Sylvain Henry at 2022-10-02T14:35:20-04:00
Testsuite: normalise ghc program name

- - - - -
a984939f by doyougnu at 2022-10-02T14:35:20-04:00
JS Backend: Remove FIXMEs

StgToJS.Apply: Remove FIXMEs

StgToJS.FFI: remove FIXMEs

StgToJS.Expr: remove FIXMEs

StgToJS: Remove FIXMEs

- - - - -
646b82ba by Sylvain Henry at 2022-10-02T14:35:20-04:00
Enable RTS args filtering (cf cgrun025)

- - - - -
31f10ddd by Sylvain Henry at 2022-10-02T14:35:21-04:00
Remove trailing whitespaces (whitespace test)

- - - - -
289f8d2c by Sylvain Henry at 2022-10-02T14:35:21-04:00
Testsuite: remove platform prefix for unlit tool

- - - - -
18ed51e4 by Sylvain Henry at 2022-10-02T14:35:21-04:00
Primop: fix Int64 conversion/negate (integerConversions test)

- - - - -
c9b6d1c4 by Sylvain Henry at 2022-10-02T14:35:21-04:00
Linker: remove message with default verbosity

- - - - -
771bb0f5 by Sylvain Henry at 2022-10-02T14:35:22-04:00
Testsuite: normalise .jsexe suffix

- - - - -
2c536507 by Sylvain Henry at 2022-10-02T14:35:22-04:00
Remove warning about orphan instance

- - - - -
1d7b442f by Sylvain Henry at 2022-10-02T14:35:22-04:00
Compactor: disable dead code

- - - - -
0279057b by Sylvain Henry at 2022-10-02T14:35:22-04:00
Exception: implement raiseUnderflow etc. as primops

- - - - -
ebbc5777 by Sylvain Henry at 2022-10-02T14:35:22-04:00
Primop: fix Int8/18 quot/rem

- - - - -
e53eab67 by Sylvain Henry at 2022-10-02T14:35:23-04:00
Linker: refactor wired-in deps

- - - - -
58afdfb8 by Sylvain Henry at 2022-10-02T14:35:23-04:00
Ppr: remove useless left padding for functions in JS dumps

- - - - -
a15ea327 by Josh Meredith at 2022-10-02T14:35:23-04:00
Disable llvm ways and ghci for JS backend testsuite

- - - - -
a5e899b9 by Sylvain Henry at 2022-10-02T14:35:23-04:00
StaticPtr: don't generate CStubs for the JS backend

- - - - -
c14be598 by Sylvain Henry at 2022-10-02T14:35:23-04:00
StaticPtr: fix hs_spt_lookup after upstream change

- - - - -
190a863e by Sylvain Henry at 2022-10-02T14:35:24-04:00
Testsuite: fix normalisation for unlit

T8430 shows:
  `js-unknown-ghcjs-unlit' failed in phase `Literate pre-processor'. (Exit code: 1)

Notice the quote around the program name. So I've made the regex match
more cases (i.e. not only lines starting with the program name).

- - - - -
7c4353d7 by Sylvain Henry at 2022-10-02T14:35:24-04:00
Codegen: fix codegen of string literals

Due to FastString change:
 Before: Text.pack . BSC.unpack
 After:  mkFastString . BSC.unpack

It seems that Text handles buggy multi-byte codepoints split into
several String Chars.

- - - - -
e3032ffc by Sylvain Henry at 2022-10-02T14:35:24-04:00
CPP: fix LINE markers. Only disable them for JS

- - - - -
54645bc5 by Luite Stegeman at 2022-10-02T14:37:55-04:00
add JavaScript files listed in js-sources to package archives

- - - - -
f6bbfabe by Luite Stegeman at 2022-10-02T14:37:59-04:00
update rts js files to include recent fixes

- - - - -
80993453 by Luite Stegeman at 2022-10-02T14:37:59-04:00
fix definitions in js/rts.h

- - - - -
658eaa3a by Josh Meredith at 2022-10-02T14:38:00-04:00
stopgap fix for missing ghc-pkg in cross-compiler tests

- - - - -
bc7e12bb by Sylvain Henry at 2022-10-02T14:38:00-04:00
Testsuite: better fix for finding prefixed tools

- - - - -
fdc31c5e by Sylvain Henry at 2022-10-02T14:38:00-04:00
Ppr: add hangBrace helper

- - - - -
5da49c85 by Sylvain Henry at 2022-10-02T14:38:00-04:00
Only declare ccs var in profiling mode

- - - - -
85e45c64 by Sylvain Henry at 2022-10-02T14:38:00-04:00
Don't consider recursive bindings as inline nor as evaluated

Fix mdo001

- - - - -
1c38b7d5 by Sylvain Henry at 2022-10-02T14:38:01-04:00
Hadrian: disable shared libs for JS target

- - - - -
868b86b0 by Sylvain Henry at 2022-10-02T14:38:01-04:00
Support -ddump-stg-final with the JS backend

- - - - -
1495d7f3 by Sylvain Henry at 2022-10-02T14:38:01-04:00
Add ticky_ghc0 flavour transformer to ticky stage1

- - - - -
246cb9e1 by Sylvain Henry at 2022-10-02T14:38:01-04:00
Don't read object file when -ddump-js isn't passed

- - - - -
a7f8d415 by Sylvain Henry at 2022-10-02T14:38:01-04:00
Object: remove dead code + renaming

- - - - -
caff1451 by Sylvain Henry at 2022-10-02T14:38:02-04:00
Object: replace SymbolTableR with Dictionary

- - - - -
6f47c83d by Sylvain Henry at 2022-10-02T14:38:02-04:00
Object: refactoring

- - - - -
c499a09c by Sylvain Henry at 2022-10-02T14:38:02-04:00
RTS: link platform.js before the others!

- - - - -
ca5011bc by Sylvain Henry at 2022-10-02T14:38:02-04:00
Hadrian: treat JS objects similarly to other objects

- - - - -
b5e5f1f1 by Luite Stegeman at 2022-10-02T14:38:02-04:00
fix javascript FFI calls for read and write

- - - - -
88507917 by doyougnu at 2022-10-02T14:38:03-04:00
propagate ppr code changes to JS backend

- - - - -
7843ade6 by Sylvain Henry at 2022-10-02T14:38:03-04:00
Switch from Data.Binary and ByteString to BinHandle

- - - - -
b3304f0d by Sylvain Henry at 2022-10-02T14:38:03-04:00
Perf: use Ppr's LeftMode to output JS

- - - - -
67b53f7c by doyougnu at 2022-10-02T14:38:03-04:00
Primops: Add {Index,Write,Read}ByteArrayAs ops

Still need to check for correctness based on T4442.

minor doc fixes

fixup: add some Index..As primops

fixup missed type signature

Primops: Add WriteByteArrayOp_Word8AsFoo ops

Primops: {Index,Read,Write}FooAsBar done except Addr's

Primops: add {Index,Read,Write}ByteArrayAsAddr ops

These will need to be tested for correctness with T4442.hs

- - - - -
025ce0b1 by Sylvain Henry at 2022-10-02T14:38:03-04:00
Move platform.js to base (it must be linked first)

- - - - -
f523bc7e by Sylvain Henry at 2022-10-02T14:38:04-04:00
Remove old shim directory

- - - - -
0f6ffc6a by doyougnu at 2022-10-02T15:49:29-04:00
JS.Prim: more PrimOps {IndexByteArrayAs, CAS}

Primop: WriteByteArrayOp_Word8AsChar use setInt8

Primops: remove dv_s_u8

This function is non-sensical. Due to the infelicities of JS as a
platform we must use Int8 and friends to write, then coerce to a word,
thus dv_s_iN are the only legal calls for a write, and dv_s_uN legal for
Index and Reads.

Primops: set dv_u8 to correct method call

should be getUint8, not getUInt8, of course the naming convention
changes ever so slightly for Words.

Primops: T4442 finishes ByteArrayAs still fails

JS.Prim: More IndexByteAAs primops

JS.Prim: Prefetch PrimOps are noOps

JS.Primops: Doc explaining lack of vector support

JS.Prim: add CAS and Fetch Ops

- - - - -
7c0d9f71 by doyougnu at 2022-10-02T15:50:45-04:00
GHC.Utils.Binary: BinDictionary -> FSTable

Rename to avoid naming conflict with haddock.

- - - - -
09f1ed63 by Josh Meredith at 2022-10-02T15:50:45-04:00
Adjust derefnull test exit code for ghcjs

- - - - -
86c66d33 by doyougnu at 2022-10-02T15:50:45-04:00
Fix Driver missing type signature warnings

- - - - -
00c09dd6 by doyougnu at 2022-10-02T15:50:45-04:00
PipeLine.Execute: silence warnings on JS backend

- - - - -
5903d8a6 by doyougnu at 2022-10-02T15:50:45-04:00
JS.Primops: Add Bit reverse ops

- - - - -
66dc3924 by doyougnu at 2022-10-02T15:50:46-04:00
SysTools.Tasks: quiet non-totality warnings

- - - - -
15e6d84a by doyougnu at 2022-10-02T15:50:46-04:00
JS.Primops: Add InterlockedExchange Addr Word

- - - - -
0fd97149 by Sylvain Henry at 2022-10-02T15:50:46-04:00
base: conditional js-sources

- - - - -
7031f2cd by Sylvain Henry at 2022-10-02T15:50:46-04:00
TH: add support for JS files

- - - - -
26874f14 by Sylvain Henry at 2022-10-02T15:50:46-04:00
Linker: fix creation of directories in output paths

- - - - -
f972a2c4 by Sylvain Henry at 2022-10-02T15:50:46-04:00
Backpack: fix empty stubs

- - - - -
d9555749 by Sylvain Henry at 2022-10-02T15:50:47-04:00
Add encodeDouble/Float RTS functions

- - - - -
7367b122 by Sylvain Henry at 2022-10-02T15:50:47-04:00
encodeDouble: correctly handle 0 base

- - - - -
c69c84a5 by doyougnu at 2022-10-02T15:50:47-04:00
JS.Primops: Add listThreads op

- - - - -
2242ff55 by doyougnu at 2022-10-02T15:50:47-04:00
JS.Primops: Add Read/WriteAddrOp ops

- - - - -
09411526 by doyougnu at 2022-10-02T15:50:47-04:00
JS: Linker and Compactor: cleanup and docs

Compactor: Cleanup: Remove dead comments

JS.Linker.Types: cleanup and document module

- - - - -
c80f12ca by doyougnu at 2022-10-02T15:50:47-04:00
StgToJS.Linker: Add docs to utility modules

StgToJS.Linker.Utils: more docs

StgToJS.Linker.Archive: more docs

- - - - -
d5e2684c by doyougnu at 2022-10-02T15:50:48-04:00
StgToJS.Object: Add documentation

- - - - -
98cf128a by Sylvain Henry at 2022-10-02T15:50:48-04:00
Refactor Expr

- - - - -
f3950422 by Sylvain Henry at 2022-10-02T15:50:48-04:00
Object: reduce pinned allocation. And don't forget to hClose invalid objects

- - - - -
d104517c by Sylvain Henry at 2022-10-02T15:50:48-04:00
Fix pdep (cgrun075)

- - - - -
9deb6f4d by Sylvain Henry at 2022-10-02T15:50:48-04:00
Fix error message (don't mention emscripten)

- - - - -
38edfcb7 by Sylvain Henry at 2022-10-02T15:50:49-04:00
Add Float/Word casts

- - - - -
36e64d74 by Sylvain Henry at 2022-10-02T15:50:49-04:00
Disable HPC tests with JS backend

- - - - -
e589c3d2 by Sylvain Henry at 2022-10-02T15:50:49-04:00
Fix encodeDouble/Float

- - - - -
d57e76ed by Sylvain Henry at 2022-10-02T15:50:49-04:00
Implement putchar (fix cgrun015)

- - - - -
289691bf by Sylvain Henry at 2022-10-02T15:50:49-04:00
Fix decoding of denormalized floats

- - - - -
abad80bd by Sylvain Henry at 2022-10-02T15:50:49-04:00
Fix isFloatDenormalized function

- - - - -
ffeb892d by Sylvain Henry at 2022-10-02T15:50:50-04:00
Reuse convert buffer

- - - - -
8a02e46f by Sylvain Henry at 2022-10-02T15:50:50-04:00
Reuse convert buffer bis

- - - - -
af01f3e7 by Sylvain Henry at 2022-10-02T15:50:50-04:00
Skip some tests that require the dynamic linker

- - - - -
4616a911 by Josh Meredith at 2022-10-02T15:50:50-04:00
JavaScript ShrinkSmallMutableArrayOp_Char & GetSizeofSmallMutableArrayOp

- - - - -
3af8aa5a by Sylvain Henry at 2022-10-02T15:50:50-04:00
Disable more linker tests

- - - - -
34e3eca5 by Sylvain Henry at 2022-10-02T15:50:50-04:00
Testsuite: better normalisation for ghc and ghc-pkg

Allow normalisation for ghc and ghc-pkg anywhere in the output, not just
at the beginning of the line.

Fix T1750 and ghcpkg05 for example

- - - - -
60c08ad7 by Sylvain Henry at 2022-10-02T15:50:50-04:00
Skip T14373 because it requires Cmm

- - - - -
123fe84e by Sylvain Henry at 2022-10-02T15:50:51-04:00
Disable cg010 with JS backend

- - - - -
1b674f7c by Sylvain Henry at 2022-10-02T15:50:51-04:00
Testsuite: better normalisation of .jsexe extension

- - - - -
cf50e08d by doyougnu at 2022-10-02T15:52:06-04:00
JS: Linker,Rts docs and cleanup

JS.Linker: Cleanup: remove unused functions/types

JS.Rts.Types: remove dead code, docs

StgToJS.RTS: cleanup and more docs

- - - - -
26fb6a91 by Sylvain Henry at 2022-10-02T15:52:18-04:00
Disable recomp015

- - - - -
6ca51286 by Sylvain Henry at 2022-10-02T15:52:18-04:00
Minor refactoring

- - - - -
238f66eb by Sylvain Henry at 2022-10-02T15:52:18-04:00
Temporary fix the testsuite bug

- - - - -
42db926e by doyougnu at 2022-10-02T15:52:18-04:00
JS.StgToJS.Types: Docs and cleanup

- - - - -
17cd1502 by Josh Meredith at 2022-10-02T15:52:19-04:00
change JS.Transform.Idents* to use UniqDSet from Set

- - - - -
25b82eed by Sylvain Henry at 2022-10-02T15:52:19-04:00
Minor Linker cleanup

Minor cleanup

- - - - -
186b8b60 by Sylvain Henry at 2022-10-02T15:52:19-04:00
Linker: load all the dependent units transitively

- - - - -
178a1724 by doyougnu at 2022-10-02T15:52:19-04:00
JS: Add Docs and cleanup StgToJS.{Arg,Ids}

JS.Arg: docs and cleanup

StgToJS.Arg: add minimal docs

StgToJS.Ids: Add header

- - - - -
c12a233f by Sylvain Henry at 2022-10-02T15:52:19-04:00
Implement h$sleep (T5611)

- - - - -
260e5b88 by Sylvain Henry at 2022-10-02T15:52:20-04:00
Linker: don't link the same unit twice

- - - - -
1e645ecc by doyougnu at 2022-10-02T15:52:20-04:00
JS:  docs, cleanup, StgToJS.{Expr,DataCon,Stack}

StgToJS.Deps/Expr: add docs

StgToJS.DataCon: add minor docs

StgToJS.Stack: Docs and cleanup

In particular:

-- Removing some single use functions
-- Some minor refactors related to these removals

StgToJS: comments on static args and optimizeFree

- - - - -
1eba6392 by Sylvain Henry at 2022-10-02T15:52:20-04:00
Disable compact tests

- - - - -
e1a040b0 by Sylvain Henry at 2022-10-02T15:52:20-04:00
Add support for JS files passed on the command line

- - - - -
d38164af by Sylvain Henry at 2022-10-02T15:52:20-04:00
Minor cleanup in compactor

- - - - -
ace64c34 by Sylvain Henry at 2022-10-02T15:52:20-04:00
Fix encoding of unboxed strings (don't pass through FastString/h$str)

- - - - -
109e40c9 by doyougnu at 2022-10-02T15:52:20-04:00
JS: Misc fixes post Del-Cont rebase

- - - - -


30 changed files:

- − .appveyor.sh
- .gitlab-ci.yml
- .gitlab/ci.sh
- − appveyor.yml
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CommonBlockElim.hs
- compiler/GHC/Cmm/ContFlowOpt.hs
- compiler/GHC/Cmm/Dataflow.hs
- compiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/Dominators.hs
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs
- compiler/GHC/Cmm/Node.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Reg.hs
- compiler/GHC/Cmm/Sink.hs
- compiler/GHC/Cmm/Switch.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bed7d64a1572c4cd677e72fb016be50404098b86...109e40c9c08822cbbb4eba3b52f448cd8a050895

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bed7d64a1572c4cd677e72fb016be50404098b86...109e40c9c08822cbbb4eba3b52f448cd8a050895
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/20221002/917b42bc/attachment-0001.html>


More information about the ghc-commits mailing list