tl;dr. Have a look at [1], feel free to submit merge requests, issues,
comments, code review, etc. Some documentation describing
a few common tasks can be found here[2].
However, be aware that we this is not the final instance and will
be cleared before the final migration in around two weeks.
Hello everyone,
A few weeks ago I wrote to this list proposing that we consider moving
GHC's development infrastructure to GitLab. While the original proposal
provided a small test instance to play with, it wasn't complete enough
to use in earnest.
Today I would like to announce the availability of
https://gitlab.staging.haskell.org for your perusal and usage. While
this is not the final migrated instance, it does have all of the
features that one can expect from the final migration. These include,
* a full import of Trac tickets (as of last week), including
attachments
* continuous integration via CircleCI
* mirrors of all boot libraries
* the ability to login using GitHub credentials
There are a few issues that we are still working on sorting out:
* the timestamps associated with ticket open and close events aren't
quite right
* some milestone changes aren't properly imported
* CircleCI currently fails on forks (this should be resolved shortly)
* we currently don't import Trac Wiki pages
All of these issues have either already been resolved in the import tool
or are in-progress.
# The plan moving forward
The goal of this instance is to allow contributors to gain experience
using GitLab and identify potential friction points. Towards that end,
please do make good use of it. In particular we are interested in
identifying:
* workflows that will become harder under GitLab (and ways that we
could improve these)
* remaining issues in the Trac import
* areas lacking in documentation
Please do let us know if you encounter any of the above.
Ultimately the goal remains to cut over to GitLab on December 18. This
will require that we bring down this instance for roughly a day to seed
it with a new import. Note that we will not make any attempt to preserve
any comments, merge requests, or issues created on this instance.
Cheers,
- Ben
[1] https://gitlab.staging.haskell.org/ghc/ghc
[2] https://gitlab.staging.haskell.org/ghc/ghc/wikis/home
Hello Devs,
I've started thinking about the implementation of
https://github.com/ghc-proposals/ghc-proposals/pull/182 recently. (Add
control flow hint pragmas.)
For this purpose I've rebased D4327 "WIP: Add likelyhood to alternatives
from stg onwards" which already does a lot of the work at the Cmm/Stg level.
The issue I ask you for feedback now is how to best attach branch
weights to case alternatives in core.
My prefered approach would be to expand core data types to include them
unconditionally.
While this is quite far reaching in the amount of code it touches it
would be rather straight forward to implement:
Alternative 1: Putting the weights directly into the case alternative tuple:
+ It it's trivial to check which places manipulate case alternatives as
they will initially fail to compile.
+ It's very mechanical, almost all use sites won't actually change the
weight.
+ It's easy to keep this working going forward as any new optimizations
can't "forget" they have to consider them.
- It will introduce a cost in compiler performance.
- New optimization who don't have to care about branchweights still have
to at least pipe them through.
- While syntactically heavy in terms of real complexity it's a simply
approach.
Alternative 2: Putting the weights into the case constructor.
+ Might give better compiler performance as I expect us to rebuild cases
less often than alternatives.
- Seems kind of clunky.
- Weaker coupling between case alternatives and their weights.
Or we could use ticks:
+ There is some machinery already there
+ Can be turned off for -O0
+ Can be ignored when convenient.
- Can be ignored when convenient.
- Very weak coupling between case alternatives and their weights.
- The existing machinery doesn't exactly match the needs of this.
- We would have to extend tick semantics to a degree where complexity
might grow too large
for me to successfully implement this.
- If new optimizations end up just removing these ticks because they are
allowed to then
the whole exercise becomes rather pointless.
- Makes it harder to ensure all relevant code paths in GHC are actually
updated.
In particular there is currently no tick category which can stick to
case alternatives but just get's removed in case
it get's in the way of optimizations.
The closest match is SoftScope which allows ticks to be floated up,
something that could impact performance quite badly
in this case. As then we might float something intended to mark a branch
as unlikely into another branch that is actually
along the hot path.
I think the core variant(s) mostly stand and fall with the actual
compile time impact. For -O0 the impact
would be negligible as the compile time is already dominated by codegen
and typechecking. For the rest
it's hard to say.
So I'm looking for feedback on this. Maybe you have other suggestions I
haven't considered?
How much compile time cost increase would be acceptable for what kind of
performance boost?
Cheers,
Andreas Klebinger
Hi all,
I'm attempting to make a simple evaluator for GHC core, but I'm not
clear on how to reliably looking up names. I'm compiling each of
ghc-prim, integer-simple and base with a patched version of GHC which
performs an extra output step with the Core AST to a file for each
module.
Later, I load those files in. So for an input Haskell file like this:
module Main (main,Foo(..)) where
class Foo a where foo :: a -> Int
instance Foo Int where foo x = x * x
instance Foo Char where foo x = 99
main = print (foo (123 :: Int))
I have an output set of bindings like this:
https://gist.github.com/chrisdone/cb05a77d3fcb081a4580b5f85289674a
One thing that I immediately notice is that the names of things are
completely non-unique, especially in generated names. So here are two
implementations of the method "foo" for the class "Foo":
( Id {idStableName = "main:Main:$cfoo", idUnique = Unique
6989586621679010917}, ...) -- Int
( Id {idStableName = "main:Main:$cfoo", idUnique = Unique
6989586621679010923}, ...) -- Char
So e.g. the instance for "Foo Int" refers to the above method
implementation via its Unique (6989586621679010923):
( Id
{idStableName = "main:Main:$fFooInt", idUnique = Unique
8214565720323784705}
, CastE
(VarE
(Id
{ idStableName = "main:Main:$cfoo"
, idUnique = Unique 6989586621679010923 <---- HERE
})))
At first, I thought I would use the Unique associated with every Name to
make a lookup. This is completely reliable within one GHC compilation,
but I've read in the docs that it's not stable across multiple
invocations? What does that mean for my case?
Another thing I notice is that type-class methods are not generated at
the core level. I have, for example, this method call that provides it
the instance dictionary,
(AppE
(AppE
(VarE
(Id
{ idStableName = "main:Main:foo"
, idUnique = Unique 8214565720323784707 <---- MISSING
}))
(TypE (Typ "Int")))
(VarE
(Id
{ idStableName = "main:Main:$fFooInt"
, idUnique = Unique 8214565720323784705
})))
But the "main:Main:foo" (8214565720323784707) is not produced in the
CoreProgram, it seems. My compile step is very simple:
compile ::
GHC.GhcMonad m
=> GHC.ModSummary
-> m [CoreSyn.Bind GHC.Var]
compile modSummary = do
parsedModule <- GHC.parseModule modSummary
typecheckedModule <- GHC.typecheckModule parsedModule
desugared <- GHC.desugarModule typecheckedModule
let binds = GHC.mg_binds (GHC.dm_core_module desugared)
pure binds
It simply gets the bindings and that's all from the ModGuts.
mg_binds :: !CoreProgram
Two questions:
1) How do I recognize class methods when I see one, like the
"main:Main:foo" above?
Maybe this? isClassOpId_maybe :: Id -> Maybe Class
Is an "op" what GHC calls type-class methods?
2) If I compile e.g. ghc-prim and that generates a binding Name with ID
123, and then I compile base -- will the ID 123 be re-used by base
for something else, or will any reference to 123 in the compiled
Names for base refer ONLY to that one in ghc-prim? In other words,
when GHC loads the iface for ghc-prim, does it generate a fresh set
of names for everything in ghc-prim, or does it load them from file?
Cheers!