Re: How does GHC implement layout?

2021-04-06 Thread Simon Marlow
The history here: several people independently noticed that it might be
better to implement the "parse error" part of layout by doing something
simpler than full parsing. For example, if we just count brackets in the
lexer, then we can handle things like

   f (case x of y -> z)

and if we treat let/in as a pair of brackets too, then the common case of

  let x = y in z

also works. The AlternativeLayoutRule was Ian's implementation of this
idea, and (if I remember correctly) contains a number of fixes that arose
from discovering interesting cases of code in the wild that weren't handled
by the obvious bracket-matching techniques.

My conclusion from this experiment - which is a bit subjective and might
differ from others - is that
* you need a lot of special cases to handle code that Haskell users expect
to parse
* and then the specification becomes pretty complex, and hard to explain to
someone

So ultimately it didn't solve the problem in a nice way, unfortunately. The
"parse error" rule is hard for implementers, but it's not actually that
hard for users.

If other people agree with this conclusion, we should kill off the ALR code
now.

Someone is going to ask me for examples of those "special cases", I'm
afraid I don't remember - I only cached the answer to the question, not the
working :) You'd probably have to go digging through the ALR code.

Cheers
Simon


On Tue, 6 Apr 2021 at 01:36, Alexis King  wrote:

> On 4/5/21 2:36 PM, Ian Lynagh wrote:
>
> It was originally designed by John Meacham:
> https://gitlab.haskell.org/haskell/prime/-/wikis/alternative-layout-rule
> https://www.mail-archive.com/haskell-prime@haskell.org/msg01938.html
>
> Thanks, Ian—I had stumbled across a link to the old Haskell Prime trac
> wiki while I was searching for information, but I didn’t realize where it
> had been migrated to.
>
> It isn't exactly equivalent to the Haskell layout rule, but it's fairly
> close and much simpler (due to not having the "on a parse error" case).
>
> Yes, I gathered as much from the implementation. The idea makes sense, but
> of course it doesn’t provide much benefit to have a simpler implementation
> unless it actually *replaces* the “on parse error” approach.
>
> Given this appears to be a long-defunct proposal, a natural followup
> question is to ask whether there’s any reason this code is still in GHC. Is
> it used for any purpose, or could it be removed?
>
> Alexis
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


ApplicativeDo needs a bit of love

2020-08-12 Thread Simon Marlow
Folks,

ApplicativeDo does what it does quite well, indeed it's in heavy use doing
what we built it for, and I was pleasantly surprised to see that 12% of
people would even like it to be enabled by default
. But a number
of issues have arisen around it, some stemming from limitations in the
original implementation and others due to interactions with other features
that we didn't consider at the time.

This message is just to point out that I'd be delighted if anyone wanted to
jump on any of these tickets and work on them, as it's unlikely I'll find
the bandwidth to work on them myself. All the tickets are tagged with
ApplicativeDo:

https://gitlab.haskell.org/ghc/ghc/-/issues?scope=all=%E2%9C%93=opened_name[]=ApplicativeDo

Have at it!

Cheers
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Recompilation avoidance questions

2020-04-23 Thread Simon Marlow
On Thu, 23 Apr 2020 at 09:17, Ömer Sinan Ağacan 
wrote:

> Thanks Simon,
>
> > We don't want to include the *definitions* of things that are
> re-exported,
> > because that would bloat interface files a lot.
>
> I think by definition you mean unfoldings, pragmas, annotations, and rules,
> right?
>

And the types of bindings, and the definitions of types. Everything that is
not the name, basically.


> I'm a bit surprised by this, because this would require tracking transitive
> dependencies, which is opposite of what we want to do in #16885.
>

Not really. It's just a tradeoff between copying all the definitions
(recursively) of things we need into the current module vs. leaving the
definitions in the interface of the original module where the entity was
defined.

Even if we were to copy the definitions of things we depend on into the
current module's interface, we still have to know where they came from, and
to know when the original definition changes so that we can recompile. So I
don't think there would be any difference in which modules we have to list
in the current module's interface file usage list.

Note: the "usages" in the interface file is different from the
"dependencies". We're not proposing to change how "usages" work. The
difference is explained in
https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/recompilation-avoidance#deciding-whether-to-recompile

If M1 re-exports something from M2 and M0 imports M1 then I think we could
> consider M2 a direct import, but that complicates the story a little bit. I
> think we don't have to track *all* transitive deps though, only tracking
> re-export paths should be enough. So maybe this is not too bad.
>

I think we already arrived at a reasonable design on #16885, what do you
think of it? Also, David already listed all the places that would
potentially need to change if we no longer include transitive dependencies
in `dep_mods`: https://gitlab.haskell.org/ghc/ghc/issues/16885#note_215715

And a useful summary of the background is
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/931#note_208414

There was some subsequent discussion on #16885 about how to handle boot
modules, and a proposal to fix that. Aside from that, the idea is to just
remove transitive dependencies from `dep_mods` and fix up the places that
used it, which David listed in that comment.

Cheers
Simon


>
> Ömer
>
> Simon Marlow , 22 Nis 2020 Çar, 12:02 tarihinde şunu
> yazdı:
> >
> > On Tue, 21 Apr 2020 at 11:38, Ömer Sinan Ağacan 
> wrote:
> >>
> >> Hi all,
> >>
> >> I'm currently reading the "recompilation avoidance" wiki page [1], and
> I have a
> >> few questions about the current design.
> >>
> >> The wiki page says (in the paragraph "Suppose the change to D ...") if
> a module
> >> B re-exports x from module D, changing x in D does not cause any
> changes in B's
> >> interface.
> >>
> >> I'm wondering why this is the case. To me this doesn't make sense.
> Anything that
> >> can potentially effect users of B should be a part of B's interface.
> This
> >> includes re-exports. I don't understand why there is a difference
> between normal
> >> exports and re-exports. As far as users of the module concerned there's
> no
> >> difference. So I'd expect any changes in re-exports to make a
> difference in B's
> >> interface.
> >
> >
> > Yes, that's already the case. Under "Deciding whether to recompile", we
> say:
> >
> > * If anything else has changed in a way that would affect the results of
> compiling this module, we must recompile.
> >
> > so that's the basic requirement.
> >
> > We don't want to include the *definitions* of things that are
> re-exported, because that would bloat interface files a lot. Consider that
> an interface would have to contain the unfoldings for every exported
> identifier, and the unfoldings of anything referred to by those unfoldings,
> and so on. Imagine the size of Prelude.hi! (historical note: it did work
> this way a long time ago, I think GHC 2.x was when it changed)
> >
> >> The wiki page says (in "Why not do (1)", where (1) refers to making D.x
> part of
> >> B's interface)
> >
> >
> > here (1) refers to
> >
> > 1. arrange that make knows about the dependency of A on D.
> >
> > which is not the same as making D.x part of B's interface.
> >
> > This section of the wiki page is about "make", incidentally.
> >
> >>
> >> that this is because sometimes changes in D.x should not cause
> >> recompiling B's users. I don't 

Re: Recompilation avoidance questions

2020-04-22 Thread Simon Marlow
On Tue, 21 Apr 2020 at 11:38, Ömer Sinan Ağacan 
wrote:

> Hi all,
>
> I'm currently reading the "recompilation avoidance" wiki page [1], and I
> have a
> few questions about the current design.
>
> The wiki page says (in the paragraph "Suppose the change to D ...") if a
> module
> B re-exports x from module D, changing x in D does not cause any changes
> in B's
> interface.
>
> I'm wondering why this is the case. To me this doesn't make sense.
> Anything that
> can potentially effect users of B should be a part of B's interface. This
> includes re-exports. I don't understand why there is a difference between
> normal
> exports and re-exports. As far as users of the module concerned there's no
> difference. So I'd expect any changes in re-exports to make a difference
> in B's
> interface.
>

Yes, that's already the case. Under "Deciding whether to recompile", we say:

* If anything else has changed in a way that would affect the results of
compiling this module, we must recompile.

so that's the basic requirement.

We don't want to include the *definitions* of things that are re-exported,
because that would bloat interface files a lot. Consider that an interface
would have to contain the unfoldings for every exported identifier, and the
unfoldings of anything referred to by those unfoldings, and so on. Imagine
the size of Prelude.hi! (historical note: it did work this way a long time
ago, I think GHC 2.x was when it changed)

The wiki page says (in "Why not do (1)", where (1) refers to making D.x
> part of
> B's interface)


here (1) refers to

1. arrange that make knows about the dependency of A on D.

which is not the same as making D.x part of B's interface.

This section of the wiki page is about "make", incidentally.


> that this is because sometimes changes in D.x should not cause
> recompiling B's users. I don't understand why (1) would cause this
> problem. If
> we make x a part of B, as if it's defined in B, similar to how we can avoid
> recompilation of users of B when a definition of B changes but the
> interface is
> the same, we could avoid recompiling users when D.x changes.
>
> For example,
>
> -- B.hs
> module B where
>
> b = 123123
>
> -- Main.hs
> import B
>
> main = print b
>
>
> $ ghc-stage1 Main.hs
> [1 of 2] Compiling B( B.hs, B.o )
> [2 of 2] Compiling Main ( Main.hs, Main.o )
> Linking Main ...
>
> Now if I update B and recompile I'll only link Main, won't recompile it:
>
> -- B.hs
> module B where
>
> b = 123123 + 12308
>
> $ ghc-stage1 Main.hs
> [1 of 2] Compiling B( B.hs, B.o )
> Linking Main ...
>
> Now suppose B.b was a re-export from D. I don't understand why changing it
> in D
> would cause recompiling Main if we make b a part of B's interface. I think
> what
> would happen is: because D's interface hash won't change we won't
> recompile B.
> No problems at all.
>

I think this all stems from the confusion above.


>
> Finally, I'm a bit confused about this part
>
> > To ensure that A is recompiled, we therefore have two options:
> > ...
> > (2) arrange to touch B.hi and C.hi even if they haven't changed.
>
> I don't understand how touching is relevant, as far as I understand
> touching
> can't force recompilation. Example:
>
> $ ghc-stage1 Main.hs
> [1 of 3] Compiling A( A.hs, A.o )
> [2 of 3] Compiling B( B.hs, B.o )
> [3 of 3] Compiling Main ( Main.hs, Main.o )
> Linking Main ...
> $ touch A.hi
> $ ghc-stage1 Main.hs
> $ touch B.hi
> $ ghc-stage1 Main.hs
>
> Am I missing anything?
>

Touching is relevant to "make" only, not ghc --make.  Under " Why do we
need recompilation avoidance?" there are two sections: "GHCi and --make"
and "make", but the formatting doesn't make the structure very clear here.
Perhaps this got worse when we migrated to gitlab?. Maybe adding an outline
would help make the structure clearer?

Cheers
Simon


>
> Thanks,
>
> Ömer
>
> [1]:
> https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/recompilation-avoidance
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Object unloading confusion

2020-04-16 Thread Simon Marlow
Hi Omer

The point of the heap scan is to find *info pointers* into objects that we
want to unload, since we can't unload those.

What about static object pointers? Well, those would be found by traversing
the static_objects list, which we also do in checkUnload. Except that
static_objects doesn't contain all the static objects - that's one of the
problems identified by this ticket.

Primitive objects can't have an info pointer into a dynamically loaded
object, because all their info pointers point into the RTS.

Hope that helps!

Simon

On Wed, 15 Apr 2020 at 13:06, Ömer Sinan Ağacan 
wrote:

> To answer my own question
>
> > So if I see a constructor with a reference to an object code in its
> payload
> > I'll not mark the object code.
>
> We don't visit payload as objects pointed from the payload will be visited
> during the scan later (or they're already visited if they come before the
> constructor in a block).
>
> The 'prim' variable in that code is still a little bit confusing. For
> example we
> never check an MVAR for whether it's an unloadable object or not:
>
> case MVAR_CLEAN:
> case MVAR_DIRTY:
> prim = true;
> size = sizeW_fromITBL(info);
> break;
>
> ...
>
> if (!prim) {
> checkAddress(addrs,info, s_indices);
> }
>
> Would be good to know why it's fine to not check MVARs and other kinds of
> objects that we skip in that code.
>
> Ömer
>
> Ömer Sinan Ağacan , 15 Nis 2020 Çar, 12:35
> tarihinde şunu yazdı:
> >
> > Hi Simon,
> >
> > I'm looking at object unloading code in CheckUnload.c. My understanding
> of how
> > unloading works is:
> >
> > - When unloading of an object is requested the object is added to
> >   `unloaded_objects`.
> > - When `unloaded_objects` is not empty, after  GC, we scan the heap for
> any
> >   references to objects. This is done in `searchHeapBlocks` called by
> >   `checkUnload`.
> > - When `searchHeapBlocks` finds a reference to an object code it marks
> the
> >   object code.
> > - After scanning the heap any objects in `unloaded_objects` that are not
> marked
> >   are unloaded.
> >
> > Does this sound right so far?
> >
> > What I'm confused about is `searchHeapBlocks`. As far as I can see it
> just skips
> > all objects other than stacks. For example here's the code for scanning a
> > constructor:
> >
> > case CONSTR:
> > case CONSTR_NOCAF:
> > case CONSTR_1_0:
> > case CONSTR_0_1:
> > case CONSTR_1_1:
> > case CONSTR_0_2:
> > case CONSTR_2_0:
> > size = sizeW_fromITBL(info);
> > break;
> >
> > So if I see a constructor with a reference to an object code in its
> payload I'll
> > not mark the object code. This looks wrong to me. I don't understand why
> we only
> > care about stacks and nothing else. Could you comment on this?
> >
> > Thanks,
> >
> > Ömer
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Confused about PAP object layout

2020-02-27 Thread Simon Marlow
On Wed, 26 Feb 2020 at 18:48, Ömer Sinan Ağacan 
wrote:

> So the key points from this thread are:
>
> - PAP payloads are scavenged using the function's bitmap. Because a PAPs
> payload
>   will have less number of closures than the function's arity the bitmap
> will
>   always have enough bits.
>
> - A bit in a function bitmap is NOT for liveness (e.g. does not indicate
> whether
>   an argument used or not), but for pointers vs. non-pointers. Function
> bitmaps
>   are called "liveness bits" in the code generator which is misleading.
>

I think of all bitmaps as representing "liveness" (or equivalently
"pointerhood") for the purposes of GC. There's no difference from the GC's
perspective between a non-pointer and a pointer that it doesn't need to
follow.

In fact there's nothing to prevent us using the function bitmap to indicate
dead arguments too - it would require zero changes in the RTS, the compiler
would only need to mark unused pointer arguments as non-pointers in the
bitmap. Probably wouldn't be worth very much overall, but I do recall one
space leak that would have been cured by this.

- In a function bitmap (small or large), 0 means pointer, 1 means
> non-pointer.
>

This is true of bitmaps generally I think, not just function bitmaps.

  This is really what confused me in my last email above. For some reason I
>   intuitively expected 1 to mean pointer, not 0. Simon M also got this
> wrong
>

Oops :)

I think there may originally have been a good reason to have it this way
around: before eval/apply, we used bitmaps to describe stack frames, but we
didn't need to encode a size in the bitmap because the default was for the
stack contents to be pointers unless there was something to tell us
otherwise. So a zero suffix of a bitmap just meant "the rest is just normal
stack". This changed with eval/apply, but we kept the convention that zero
meant pointer in a bitmap.


>   ("So a 0 in the bitmap always means non-pointer.") so maybe this is
> confusing
>   to others too.
>
> - For functions with known argument patterns we don't use the function's
> bitmap.
>   These function's type are greater than ARG_BCO (2), and for those we use
> the
>   stg_arg_bitmaps array to get the bitmap.
>
>   For example, the bitmap for ARG_PPP (function with 3 pointer arguments)
> is at
>   index 23 in this array, which is 0b11. For ARG_PNN it's 0b11011. The
> least
>   significant 6 bits are for the size (3), the remaining 0b110 means the
> first
>   argument is a pointer, rest of the two are non-pointers.
>

Actually I think documentation on this is missing in the wiki, I guess I
never got around to updating it when we implemented eval/apply. This page
should really describe function info tables:
https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/heap-objects#info-tables

If you want to add documentation that would be a good place.

Cheers
Simon

I still don't understand why this assertion
>
> ASSERT(BITMAP_SIZE(bitmap) >= size);
>
> I added to scavenge_small_bitmap in !2727 is failing though.
>
> Ömer
>
> Simon Peyton Jones , 24 Şub 2020 Pzt, 13:45
> tarihinde şunu yazdı:
> >
> > I’m not following this in detail, but do please make sure that the
> results of this discussion end up in a suitable Note.  Obviously it’s not
> transparently clear as-is, and I can see clarity emerging
> >
> >
> >
> > Thanks!
> >
> >
> > Simon
> >
> >
> >
> > From: ghc-devs  On Behalf Of Simon Marlow
> > Sent: 24 February 2020 08:22
> > To: Ömer Sinan Ağacan 
> > Cc: ghc-devs 
> > Subject: Re: Confused about PAP object layout
> >
> >
> >
> > On Thu, 20 Feb 2020 at 09:21, Ömer Sinan Ağacan 
> wrote:
> >
> > > I'm not sure what you mean by "garbage". The bitmap merely determines
> whether
> > > a field is a pointer,
> >
> > I think the bitmap is for liveness, not for whether a field is pointer
> or not.
> > Relevant code for building an info table for a function:
> >
> > mk_pieces (Fun arity (ArgGen arg_bits)) srt_label
> >   = do { (liveness_lit, liveness_data) <- mkLivenessBits dflags
> arg_bits
> >; let fun_type | null liveness_data = aRG_GEN
> >   | otherwise  = aRG_GEN_BIG
> >  extra_bits = [ packIntsCLit dflags fun_type arity ]
> >++ (if inlineSRT dflags then [] else [
> srt_lit ])
> >++ [ liveness_lit, slow_entry ]
> >; return (Nothing, Nothing, extra_bits, liveness_data) }
> >
> > This uses the word "liveness&q

Re: Confused about PAP object layout

2020-02-24 Thread Simon Marlow
On Thu, 20 Feb 2020 at 09:21, Ömer Sinan Ağacan 
wrote:

> > I'm not sure what you mean by "garbage". The bitmap merely determines
> whether
> > a field is a pointer,
>
> I think the bitmap is for liveness, not for whether a field is pointer or
> not.
> Relevant code for building an info table for a function:
>
> mk_pieces (Fun arity (ArgGen arg_bits)) srt_label
>   = do { (liveness_lit, liveness_data) <- mkLivenessBits dflags
> arg_bits
>; let fun_type | null liveness_data = aRG_GEN
>   | otherwise  = aRG_GEN_BIG
>  extra_bits = [ packIntsCLit dflags fun_type arity ]
>++ (if inlineSRT dflags then [] else [ srt_lit
> ])
>++ [ liveness_lit, slow_entry ]
>; return (Nothing, Nothing, extra_bits, liveness_data) }
>
> This uses the word "liveness" rather than "pointers".
>
> However I just realized that the word "garbage" is still not the best way
> to
> describe what I'm trying to say. In the example
>
> [pap_info, x, y, z]
>
> If the function's bitmap is [1, 0, 1], then `y` may be a dead (an unused
> argument, or "garbage" as I describe in my previous email) OR it may be a
> non-pointer, but used (i.e. not a garbage).
>

I don't think we ever put a zero in the bitmap for a pointer-but-not-used
argument. We don't do liveness analysis for function arguments, as far as
I'm aware. So a 0 in the bitmap always means "non-pointer".

The only reaosn the code uses the terminology "liveness" here is that it's
sharing code with the code that handles bitmaps for stack frames, which do
deal with liveness.


> So maybe "liveness" is also not the best way to describe this bitmap, as 0
> does
> not mean dead but rather "don't follow in GC".
>

> On my quest to understand and document this code better I have one more
> question. When generating info tables for functions with know argument
> patterns
> (ArgSpec) we initialize the bitmap as 0. Relevant code:
>
> mk_pieces (Fun arity (ArgSpec fun_type)) srt_label
>   = do { let extra_bits = packIntsCLit dflags fun_type arity :
> srt_label
>; return (Nothing, Nothing,  extra_bits, []) }
>
> Here the last return value is for the liveness data. I don't understand
> how can
> this be correct, because when we use this function in a PAP this will
> cause NOT
> scavenging the PAP payload. Relevant code (simplified):
>
> STATIC_INLINE GNUC_ATTR_HOT StgPtr
> scavenge_PAP_payload (StgClosure *fun, StgClosure **payload, StgWord
> size)
> {
> const StgFunInfoTable *fun_info =
> get_fun_itbl(UNTAG_CONST_CLOSURE(fun));
>
> StgPtr p = (StgPtr)payload;
>
> StgWord bitmap;
> switch (fun_info->f.fun_type) {
> ...
>
default:
> bitmap = BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]);
> small_bitmap:
> p = scavenge_small_bitmap(p, size, bitmap);
> break;
> }
> return p;
> }
>

> Here if I have a function with three pointer args (ARG_PPP) the shown
> branch
> that will be taken, but because the bitmap is 0 (as shown in the mk_pieces
> code
> above) nothing in the PAPs payload will be scavenged.
>

It gets the bitmap from stg_arg_bitmaps[fun_info->f.fun_type], not from the
info table.  Hope this helps.

Cheers
Simon



>
> Here's an example from a debugging session:
>
> >>> print pap
> $10 = (StgPAP *) 0x42001fe030
>
> >>> print *pap
> $11 = {
>   header = {
> info = 0x7fbdd1f06640 
>   },
>   arity = 2,
>   n_args = 1,
>   fun = 0x7fbdd2d23ffb,
>   payload = 0x42001fe048
> }
>
> So this PAP is applied one argument, which is a boxed object (a FUN_2_0):
>
> >>> print *get_itbl(UNTAG_CLOSURE(pap->payload[0]))
> $20 = {
>   layout = {
> payload = {
>   ptrs = 2,
>   nptrs = 0
> },
> bitmap = 2,
> large_bitmap_offset = 2,
> __pad_large_bitmap_offset = 2,
> selector_offset = 2
>   },
>   type = 11,
>   srt = 1914488,
>   code = 0x7fbdd2b509c0 "H\215E\370L9\370r[I\203\304 M;\245X\003"
> }
>
> However if I look at the function of this PAP:
>
> >>> print *get_fun_itbl(UNTAG_CLOSURE(pap->fun))
> $21 = {
>   f = {
> slow_apply_offset = 16,
> __pad_slow_apply_offset = 3135120895,
> b = {
>   bitmap = 74900193017889,
>   bitmap_offset = 258342945,
>   __pad_bitmap_offset = 258342945
> },
> fun_type = 23,
> arity = 3
>   },
>   i = {
> layout = {
>   payload = {
> ptrs = 0,
> nptrs = 0
>   },
>   bitmap = 0,
>   large_bitmap_offset = 0,
>   __pad_large_bitmap_offset = 0,
>   selector_offset = 0
> },
> type = 14,
> srt = 1916288,
> code = 0x7fbdd2b50260 
> 

Re: Confused about PAP object layout

2020-02-14 Thread Simon Marlow
On Fri, 14 Feb 2020 at 11:49, Ömer Sinan Ağacan 
wrote:

> Hi Simon,
>
> In this code: (slightly simplified)
>
> StgPtr
> scavenge_PAP (StgPAP *pap)
> {
> evacuate(>fun);
> return scavenge_PAP_payload (pap->fun, pap->payload, pap->n_args);
> }
>
> StgPtr
> scavenge_PAP_payload (StgClosure *fun, StgClosure **payload, StgWord
> size)
> {
> const StgFunInfoTable *fun_info =
> get_fun_itbl(UNTAG_CONST_CLOSURE(fun));
> StgPtr p = (StgPtr)payload;
>
> switch (fun_info->f.fun_type) {
> case ARG_GEN_BIG:
> scavenge_large_bitmap(p, GET_FUN_LARGE_BITMAP(fun_info), size);
> p += size;
> break;
> ...
> }
> return p;
> }
>
> Here the `size` argument in `scavenge_PAP_payload` is the number of
> arguments
> applied to the function in `pap->fun`. But when scavenging the function's
> bitmap
> we're using this number as the size of the bitmap which doesn't make sense
> to
> me, because I think size of the function's bitmap and size of the PAP's
> payload
> may be different.
>

"size" is an argument to scavenge_PAP_payload(), and when we call it we
pass pap->n_args as the value, not the bitmap's size.

Does that help?

Cheers
Simon



>
> Or in other words I may have the same function used in many PAPs with
> different
> n_args, but that'd be buggy if this code is correct.
>
> I haven't checked every single place where we build a PAP but for example
> the
> `NEW_PAP` macro uses the argument's (another PAP) function directly,
> without
> making any bitmap-related changes, but bumps n_args by one. If the code
> above is
> right, then this new PAP will be scavenged incorrectly.
>
> Am I missing anything?
>
> Thanks,
>
> Ömer
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Feasibility of native RTS support for continuations?

2020-02-10 Thread Simon Marlow
On Mon, 10 Feb 2020 at 08:17, Simon Marlow  wrote:

> On Mon, 10 Feb 2020 at 08:10, Alexis King  wrote:
>
>> On Feb 6, 2020, at 02:28, Simon Marlow  wrote:
>>
>> The issue here is that raiseAsync is destructive - it *moves* the stack
>> to the heap, rather than copying it. So if you want to continue execution
>> where you left off, for shift#, you would have to copy it back onto the
>> stack again. That's the point I was trying to highlight here.
>>
>>
>> Ah, yes, I see what you mean! It happens that for my use case I actually
>> do want to unwind the stack when I capture a continuation, so that isn’t a
>> problem for me.
>>
>> Yes, these are all the things that make raiseAsync tricky! You can either
>> copy what raiseAsync does (but be warned, it has taken a lot of iteration
>> to get right) or try to use raiseAsync and/or modify it to do what you want.
>>
>>
>> My point was more that I’m unsure that shift# *should* handle most of
>> those cases. For raiseAsync, it makes sense, since asynchronous interrupts
>> can, by their nature, occur at any time, even during pure code. But my
>> shift# operation lives in IO, and the intent is to only capture up to a
>> reset# in the same state thread.
>>
>> My justification for this is that if you could use shift# in pure code,
>> it would be ill-defined what you’d even be capturing. Suppose you return a
>> thunk containing a call to shift#. When the thunk is evaluated, you capture
>> up to the nearest reset#… but who knows what that is now? This opens you up
>> to all sorts of general badness.
>>
>> Therefore, I don’t think there should ever be an UPDATE_FRAME in the
>> captured continuation—if there is, it’s probably a bug. So unless someone
>> can think of any valid use cases, I’ll make that more explicit by modifying
>> the continuation-capturing code to add some assertions that those frames
>> never appear in the captured stack.
>>
>
> Let me just say "unsafePerformIO" :)  You probably want to at least ensure
> that things don't crash in that case, even if you can't give a sensible
> semantics to what actually happens. We have a similar situation with
> unsafeIOToST - we can't tell you exactly what it does in general, except
> that it doesn't crash (I hope!).
>

Typo - I meant unsafeIOToSTM here.


>
> Cheers
> Simon
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Feasibility of native RTS support for continuations?

2020-02-10 Thread Simon Marlow
On Mon, 10 Feb 2020 at 08:10, Alexis King  wrote:

> On Feb 6, 2020, at 02:28, Simon Marlow  wrote:
>
> The issue here is that raiseAsync is destructive - it *moves* the stack to
> the heap, rather than copying it. So if you want to continue execution
> where you left off, for shift#, you would have to copy it back onto the
> stack again. That's the point I was trying to highlight here.
>
>
> Ah, yes, I see what you mean! It happens that for my use case I actually
> do want to unwind the stack when I capture a continuation, so that isn’t a
> problem for me.
>
> Yes, these are all the things that make raiseAsync tricky! You can either
> copy what raiseAsync does (but be warned, it has taken a lot of iteration
> to get right) or try to use raiseAsync and/or modify it to do what you want.
>
>
> My point was more that I’m unsure that shift# *should* handle most of
> those cases. For raiseAsync, it makes sense, since asynchronous interrupts
> can, by their nature, occur at any time, even during pure code. But my
> shift# operation lives in IO, and the intent is to only capture up to a
> reset# in the same state thread.
>
> My justification for this is that if you could use shift# in pure code, it
> would be ill-defined what you’d even be capturing. Suppose you return a
> thunk containing a call to shift#. When the thunk is evaluated, you capture
> up to the nearest reset#… but who knows what that is now? This opens you up
> to all sorts of general badness.
>
> Therefore, I don’t think there should ever be an UPDATE_FRAME in the
> captured continuation—if there is, it’s probably a bug. So unless someone
> can think of any valid use cases, I’ll make that more explicit by modifying
> the continuation-capturing code to add some assertions that those frames
> never appear in the captured stack.
>

Let me just say "unsafePerformIO" :)  You probably want to at least ensure
that things don't crash in that case, even if you can't give a sensible
semantics to what actually happens. We have a similar situation with
unsafeIOToST - we can't tell you exactly what it does in general, except
that it doesn't crash (I hope!).

Cheers
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Feasibility of native RTS support for continuations?

2020-02-06 Thread Simon Marlow
On Sun, 2 Feb 2020 at 04:26, Alexis King  wrote:

> I took a stab at implementing this today, using the “continuation is a
> stack” implementation strategy I described in my previous email. I
> haven’t tried very hard to break it yet, but this tiny test program
> works:
>
> {-# LANGUAGE BangPatterns, BlockArguments, MagicHash,
>  ScopedTypeVariables, UnboxedTuples #-}
>
> import GHC.Prim
> import GHC.Types
>
> data Continuation a b = Continuation# (Continuation# RealWorld a b)
>
> reset :: IO a -> IO a
> reset (IO m) = IO (reset# m)
>
> shift :: (Continuation a b -> IO b) -> IO a
> shift f = IO (shift# \k -> let !(IO m) = f (Continuation# k) in m)
>
> applyContinuation :: Continuation a b -> a -> IO b
> applyContinuation (Continuation# k) a = IO (applyContinuation# k a)
>
> main :: IO ()
> main = do
>   ns <- reset do
> n <- shift \(k :: Continuation Integer [Integer]) -> do
>   a <- applyContinuation k 2
>   b <- applyContinuation k 3
>   pure (a ++ b)
> pure [n]
>   print ns
>
> The output of this program is [2, 3], as expected.
>

That's impressive!


>
> My implementation doesn’t share any code with raiseAsync. Currently, it
> isn’t very clever:
>
> * reset# pushes a RET_SMALL frame with a well-known info pointer,
>   _reset_frame_info.
>
> * shift# walks the stack and copies it up to the nearest reset
>   frame. If the stack consists of several chunks, it only copies the
>   chunk that contains the reset frame, and it just repurposes the
>   other chunks as the continuation (since the stack is unwinding
>   anyway).
>
> * applyContinuation# copies the captured stack and updates the
>   UNDERFLOW frames as needed to point to the current stack.
>
> * I haven’t implemented it yet, but it would be straightforward to
>   implement an applyContinuationOneShot# operation that works like
>   applyContinuation#, but doesn’t actually copy anything and just
>   updates the UNDERFLOW frames in the captured stack itself.
>
> This seems to work in my very simple examples, but there are also things
> I know it doesn’t handle properly:
>
> * It doesn’t make any attempt to handle modifications to the
>   interrupt masking state properly. The right thing to do here is
>   probably to look for mask/unmask frames on the stack during
>   unwinding and to stash that information somewhere.
>
> * It doesn’t do anything special for UPDATE_FRAMEs, so if there’s an
>   UPDATE_FRAME that owns a blackhole on the stack, things will go
>   quite wrong.
>
>   I haven’t been worrying about this because I don’t think there
>   should ever be any update frames between shift# and reset#. In the
>   case of raiseAsync, the location of the “prompt” is well-defined:
>   it’s the update frame. But shift# captures up to an explicit
>   prompt, so using shift# when there’s an update frame on the stack
>   can surely only lead to nonsense... right?
>
> * It doesn’t do anything special for STM frames, so trying to
>   capture a continuation through those will be similarly broken.
>

Yes, these are all the things that make raiseAsync tricky! You can either
copy what raiseAsync does (but be warned, it has taken a lot of iteration
to get right) or try to use raiseAsync and/or modify it to do what you want.

Cheers
Simon



> There are also probably bugs I don’t know about — I haven’t exercised
> the implementation very hard yet — but I’ll keep playing with it. If
> anyone is at all interested, I’ve pushed the code to a branch here:
>
>
> https://gitlab.haskell.org/lexi.lambda/ghc/compare/master...first-class-continuations
>
> My thanks again to everyone’s help!
>
> Alexis
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Feasibility of native RTS support for continuations?

2020-02-06 Thread Simon Marlow
On Sat, 1 Feb 2020 at 00:23, Alexis King  wrote:

> > On Jan 30, 2020, at 02:35, Simon Marlow  wrote:
>
> > Also you might want to optimise the implementation so that it doesn't
> actually tear down the stack as it copies it into the heap, so that you
> could avoid the need to copy it back from the heap again in shift#.
>
> I don’t fully understand this point — do you mean “avoid the need to copy
> it back on continuation application”? shift# just copies the stack slice to
> the heap, so it doesn’t need to copy it back.
>

The issue here is that raiseAsync is destructive - it *moves* the stack to
the heap, rather than copying it. So if you want to continue execution
where you left off, for shift#, you would have to copy it back onto the
stack again. That's the point I was trying to highlight here.

 Cheers
Simon


> If I was right, and you were referring to continuation application rather
> than shift#, I agree with you there. It seems as though it ought to be
> possible to represent the stack slice as a stack itself, so if the stack
> looks like
>
> ┌───┐
> │ RET_SMALL │
> ├───┤
> │ CATCH │
> ├───┤
> │ RESET │
> ├───┤
>
> then the captured continuation could itself essentially be a stack like
>
> ┌───┐
> │ RET_SMALL │
> ├───┤
> │ CATCH │
> ├───┤
> │ UNDERFLOW │
> └───┘
>
> where restoring a continuation just copies the captured stack and updates
> its underflow frame to point at the top of the current stack. If the caller
> promises not to use the continuation again after applying it, the copying
> could be skipped entirely, and the captured stack could just become the new
> stack.
>
> However, I don’t understand enough about the way the RTS currently works
> to know if this is viable. For example, what if I write this:
>
> reset (mask_ (shift f))
>
> Now presumably I want to ensure the masking state is restored when I
> invoke the continuation. But it can’t just be unconditionally restored,
> since if I write
>
> mask_ (reset (shift f >>= g))
>
> then the mask frame isn’t included on the stack, so applying the
> continuation shouldn’t affect the masking state. Presumably this means a
> continuation restore can’t be as simple as copying the captured stack
> frames onto the current stack, since restoring certain frames affects other
> parts of the RTS state.
>
> (Tangentially, it seems like this particular example is not handled
> properly in the existing capture/restore code, as this comment in
> Exception.cmm notes:
>
>  NB. there's a bug in here.  If a thread is inside an
>  unsafePerformIO, and inside maskAsyncExceptions# (there is an
>  unmaskAsyncExceptions_ret on the stack), and it is blocked in an
>  interruptible operation, and it receives an exception, then the
>  unsafePerformIO thunk will be updated with a stack object
>  containing the unmaskAsyncExceptions_ret frame.  Later, when
>  someone else evaluates this thunk, the original masking state is
>  not restored.
>
> I think getting this right probably matters more if continuations are
> added, so that’s something else to worry about.)
>
> > So that's shift#. What about reset#? I expect it's something like
> `unsafeInterleaveIO`, that is it creates a thunk to name the continuation.
> You probably also want a `catch` in there, so that we don't tear down more
> of the stack than we need to.
>
> It would be nice to be able to capture slices of the stack that include
> catch frames, though theoretically it isn’t necessary — it would be
> possible to arrange for a continuation that wants to capture through a
> catch to do something like
>
> reset (... (catch (reset ...) ...))
>
> instead, then call shift twice and compose the two continuations by hand
> (inserting another call to catch in between). I don’t know enough yet to
> understand all the tradeoffs involved, but I’ll see if it’s possible to get
> away with the userland emulation, since I figure the less code in the RTS
> the better!
>
> > Hope this is helpful.
>
> Very much so, thank you!
>
> > On Jan 30, 2020, at 10:31, Ben Gamari  wrote:
> >
> > For the record, runtime system captures the stack state in an AP_STACK
> > closure. This is done in rts/RaiseAsync.c:raiseAsync and some of this is
> > described in the comment attached to that function.
> >
> > As Simon PJ points out, this is all very tricky stuff, especially in a
> > concurrent context. If you make any changes in this area do be sure to
> > keep in mind the considerations described i

Re: Feasibility of native RTS support for continuations?

2020-01-30 Thread Simon Marlow
My guess is you can almost do what you want with asynchronous exceptions
but some changes to the RTS would be needed.

There's a bit of code in the IO library that literally looks like this (
https://gitlab.haskell.org/ghc/ghc/blob/master/libraries%2Fbase%2FGHC%2FIO%2FHandle%2FInternals.hs#L175
):

t <- myThreadId
throwTo t e
... carry on ...

that is, it throws an exception to the current thread using throwTo, and
then there is code to handle what happens if the enclosing thunk is
evaluated after the exception has been thrown.

That is, throwing an exception to the current thread is an IO operation
that returns later! This only works with throwTo, not with throwIO, because
throwIO is a *synchronous* exception that destructively tears down the
stack.

I suppose if you want to pass a value to the thread after resumption you
could do it via an IORef.

But the issue with this is that you can only apply the continuation once:
GHC treats the captured continuation like a thunk, which means that after
evaluating it, it will be updated with its value. But for your purposes you
need to be able to apply it at least twice - once because we want to
continue after shift#, and again when we apply the continuation later.
Somehow the thunks we build this way would need to be marked non-updatable.
Perhaps this could be done with a new primitive `throwToNonUpdatable`
(hopefully with a better name) that creates non-updatable thunks. Also you
might want to optimise the implementation so that it doesn't actually tear
down the stack as it copies it into the heap, so that you could avoid the
need to copy it back from the heap again in shift#.

So that's shift#. What about reset#? I expect it's something like
`unsafeInterleaveIO`, that is it creates a thunk to name the continuation.
You probably also want a `catch` in there, so that we don't tear down more
of the stack than we need to.

Hope this is helpful.

Cheers
Simon


On Thu, 30 Jan 2020 at 00:55, Alexis King  wrote:

> > On Jan 29, 2020, at 03:32, Simon Peyton Jones 
> wrote:
> >
> > Suppose a thread happens to be evaluating a pure thunk for (factorial
> 200). […] This stack-freezing stuff is definitely implemented.
>
> That’s fascinating! I had no idea, but your explanation makes sense (as do
> the papers you linked). That is definitely promising, as it seems like many
> of the tricky cases may already be accounted for? I’ll see if I can follow
> the Cmm code well enough to hunt down how it’s implemented.
>
> One other thing I have been thinking about: this is completely
> incompatible with the state hack, isn’t it? That is not a showstopper, of
> course—I do not intend to suggest that continuations be capturable in
> ordinary IO—but it does mean I probably want a way to selectively opt out.
> (But I’ll worry about that if I ever get that far.)
>
> Alexis
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Bug in SRT generation for procs in .cmm files?

2020-01-24 Thread Simon Marlow
Yes, I think my assumption was that we wouldn't be referring to any CAFs
from .cmm source code so we didn't need to track the CAFyness of labels. It
would be quite a pain to support this I think - in .cmm you can refer to
anything by its raw label, so we would have to either declare whether
something is CAFy or reverse engineer the original entity name and load the
interface file etc.  Furthermore we would need to tell the compiler about
the CAFyness of RTS labels somehow so that they could be added to SRTs
where necessary.

I'm fine with not running the SRT analysis on .cmm code.

Cheers
Simon


On Thu, 23 Jan 2020 at 14:57, Ömer Sinan Ağacan 
wrote:

> The main problem I'm trying to solve is explained in my comment [1].
> Basically
> when building .cmm files the new SRT algorithm re-order definitions in a
> way
> that breaks dependency ordering, which in turn breaks C backend, because
> in C we
> should declare before using. (see my comment for why we don't have this
> problem
> when building Haskell modules)
>
> If we don't allow defining CAFFY things in Cmm files then I can simply not
> do
> SRT analysis on Cmm files and avoid the problem.
>
> Ömer
>
> [1]: https://gitlab.haskell.org/ghc/ghc/merge_requests/1304#note_248547
>
> Ben Gamari , 23 Oca 2020 Per, 15:17 tarihinde şunu
> yazdı:
> >
> > While it's true that in principle one could imagine a case where you
> would want a CAFfy Cmm proc, I can't think of any stuck cases in the RTS
> today. Consequently it wouldn't surprise me if this was broken.
> >
> > Frankly, I wouldn't worry too much about this if it's nontrivial to fix.
> >
> > Cheers,
> >
> > - Ben
> >
> > On January 23, 2020 1:54:04 AM EST, "Ömer Sinan Ağacan" <
> omeraga...@gmail.com> wrote:
> >>
> >> Hi Simon,
> >>
> >> Currently CmmParse only generates CmmLabels for procs, and those are
> considered
> >> non-CAFFY by hasCAF (and thus CmmBuildInfoTables).
> >>
> >> As a result if I have two procs in a .cmm file:
> >>
> >> - p1, refers to a CAF in base
> >> - p2, refers to p1
> >>
> >> I *think* (haven't checked) we don't consider p1 as CAFFY, and even if
> we do, we
> >> don't consider p2 as CAFFY becuase the reference from p2 to p1 won't be
> >> considered CAFFY by hasCAF.
> >>
> >> So we currently can't define a CAFFY Cmm proc in .cmm files as the SRT
> algorithm
> >> will never build SRTs for procs in .cmm files.
> >>
> >> Is this intentional? I'd expect this to be possible, because there's
> nothing
> >> preventing me from referring to a CAFFY definition in a library (e.g.
> base) in a
> >> .cmm file, but doing this would be a bug in runtime.
> >>
> >> Thanks,
> >>
> >> Ömer
> >> 
> >> ghc-devs mailing list
> >> ghc-devs@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >
> >
> > --
> > Sent from my Android device with K-9 Mail. Please excuse my brevity.
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Code generation/SRT question

2020-01-07 Thread Simon Marlow
On Tue, 7 Jan 2020 at 05:59, Ömer Sinan Ağacan  wrote:

> Hi all,
>
> > There's no need to set the srt field of f_info if f_closure is the SRT,
> since
> > any reference to f_info in the code will give rise to a reference to
> f_closure
> > in the SRT corresponding to that code fragment. Does that make sense?
>
> Makes sense, thanks.
>
> > The use of a closure as an SRT is really quite a nice optimisation
> actually.
>
> Agreed.
>
> > · If f is top level, and calls itself, there is no need to include a
> pointer
> > to f’s closure in f’s own SRT.
> >
> > I think this last point is the one you are asking, but I’m not certain.
>
> Close, I'm asking whether we should include a pointer to f in f's SRT
> (when f is
> recursive) when we're using f as the SRT (the [FUN] optimisation).
>

I think your original question was slightly different, it was about f's
info table:

> should f's entry block's info table have f_closure as its SRT?

anyway, the answer to both questions is "no."

Cheers
Simon



> I'll document the code I quoted in my original email with this info.
>
> Thanks,
>
> Ömer
>
> Simon Peyton Jones , 7 Oca 2020 Sal, 00:11
> tarihinde şunu yazdı:
> >
> > Aha, great.  Well at least [Note SRTs] should point back to the wiki
> page.
> >
> >
> >
> > Omer's question is referring specifically to the [FUN] optimisation
> described in the Note.
> >
> > Hmm.  So is he asking whether f’s SRT should have an entry for itself?
> No, that’ would be silly!  It would not lead to any more CAFs being
> reachable.
> >
> >
> >
> > Omer, maybe we are misunderstanding.   But if so, can you cast your
> question more precisely in terms of which lines of the wiki page or Note
> are you asking about?  And let’s make sure that the appropriate bit gets
> updated when you’ve nailed the answer
> >
> >
> >
> > Simon
> >
> >
> >
> > From: Simon Marlow 
> > Sent: 06 January 2020 18:17
> > To: Simon Peyton Jones 
> > Cc: Ömer Sinan Ağacan ; ghc-devs <
> ghc-devs@haskell.org>
> > Subject: Re: Code generation/SRT question
> >
> >
> >
> > We have:
> >
> > * wiki:
> https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc/cafs
> >
> > * a huge Note in CmmBuildInfoTables:
> https://gitlab.haskell.org/ghc/ghc/blob/master/compiler%2Fcmm%2FCmmBuildInfoTables.hs#L42
> >
> >
> >
> > Maybe we need links to these from other places?
> >
> >
> >
> > Omer's question is referring specifically to the [FUN] optimisation
> described in the Note.
> >
> >
> >
> > Cheers
> >
> > Simon
> >
> >
> >
> > On Mon, 6 Jan 2020 at 17:50, Simon Peyton Jones 
> wrote:
> >
> > Omer,
> >
> >
> >
> > I think I’m not understanding all the details, but I have a clear “big
> picture”.   Simon can correct me if I’m wrong.
> >
> >
> >
> > ·The info table for any closure (top-level or otherwise) has a
> (possibly empty) Static Reference Table, SRT.
> >
> > ·The SRT for an info table identifies the static top level
> closures that the code for that info table mentions.   (In principle the
> garbage collector could parse the code! But it’s easier to find these
> references if they in a dedicated table alongside the code.)
> >
> > ·A top level closure is a CAF if it is born updatable.
> >
> > ·A top level closure is CAFFY if it is a CAF, or mentions
> another CAFFY closure.
> >
> > ·An entry in the SRT can point
> >
> > o   To a top-level updatable closure. This may now point into the
> dynamic heap, and is what we want to keep alive.  If the closure hasn’t
> been updated, we should keep alive anything its SRT points to.
> >
> > o   Directly to another SRT (or info table?) for a CAFFY top-level
> closure, which is a bit faster if we know the thing is non-updatable.
> >
> > ·If a function f calls a top-level function g, and g is CAFFY,
> then f’s SRT should point to g’s closure or (if g is not a CAF) directly to
> its SRT.
> >
> > ·If f is top level, and calls itself, there is no need to
> include a pointer to f’s closure in f’s own SRT.
> >
> > I think this last point is the one you are asking, but I’m not certain.
> >
> > All this should be written down somewhere, and perhaps is.  But where?
> >
> > Simon
> >
> >
> >
> > From: ghc-devs  On Behalf Of Simon Marlow
> > Sent: 06 January 2020

Re: Code generation/SRT question

2020-01-06 Thread Simon Marlow
We have:
* wiki:
https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc/cafs
* a huge Note in CmmBuildInfoTables:
https://gitlab.haskell.org/ghc/ghc/blob/master/compiler%2Fcmm%2FCmmBuildInfoTables.hs#L42

Maybe we need links to these from other places?

Omer's question is referring specifically to the [FUN] optimisation
described in the Note.

Cheers
Simon

On Mon, 6 Jan 2020 at 17:50, Simon Peyton Jones 
wrote:

> Omer,
>
>
>
> I think I’m not understanding all the details, but I have a clear “big
> picture”.   Simon can correct me if I’m wrong.
>
>
>
> ·The *info table* for any *closure* (top-level or otherwise) has
> a (possibly empty) Static Reference Table, *SRT*.
>
> ·The SRT for an info table identifies the static top level
> closures that the *code* for that info table mentions.   (In principle
> the garbage collector could parse the code! But it’s easier to find these
> references if they in a dedicated table alongside the code.)
>
> ·A top level closure is a *CAF* if it is born updatable.
>
> ·A top level closure is *CAFFY* if it is a CAF, or mentions
> another CAFFY closure.
>
> ·An entry in the SRT can point
>
> o   To a top-level updatable closure. This may now point into the dynamic
> heap, and is what we want to keep alive.  If the closure hasn’t been
> updated, we should keep alive anything its SRT points to.
>
> o   Directly to another SRT (or info table?) for a CAFFY top-level
> closure, which is a bit faster if we know the thing is non-updatable.
>
> ·If a function f calls a top-level function g, and g is CAFFY,
> then f’s SRT should point to g’s closure or (if g is not a CAF) directly to
> its SRT.
>
> ·If f is top level, and calls itself, there is no need to include
> a pointer to f’s closure in f’s own SRT.
>
> I think this last point is the one you are asking, but I’m not certain.
>
> All this should be written down somewhere, and perhaps is.  But where?
>
> Simon
>
>
>
> *From:* ghc-devs  *On Behalf Of *Simon
> Marlow
> *Sent:* 06 January 2020 08:17
> *To:* Ömer Sinan Ağacan 
> *Cc:* ghc-devs 
> *Subject:* Re: Code generation/SRT question
>
>
>
> There's no need to set the srt field of f_info if f_closure is the SRT,
> since any reference to f_info in the code will give rise to a reference to
> f_closure in the SRT corresponding to that code fragment. Does that make
> sense?
>
>
>
> The use of a closure as an SRT is really quite a nice optimisation
> actually.
>
>
>
> Cheers
>
> Simon
>
>
>
> On Wed, 1 Jan 2020 at 09:35, Ömer Sinan Ağacan 
> wrote:
>
> Hi Simon,
>
> In Cmm if I have a recursive group of functions f and g, and I'm using f's
> closure as the SRT for this group, should f's entry block's info table have
> f_closure as its SRT?
>
> In Cmm syntax
>
>  f_entry() {
>  { info_tbls: [...
>(c1vn,
> label: ...
> rep: ...
> srt: ??]
>stack_info: ...
>  }
>  {offset
>c1vn:
>  ...
>  }
>  }
>
> Here should I have `f_closure` in the srt field?
>
> I'd expect yes, but looking at the current SRT code, in
> CmmBuildInfoTables.updInfoSRTs, we have this:
>
>   (newInfo, srtEntries) = case mapLookup (g_entry g) funSRTEnv of
>
> Nothing ->
>   -- if we don't add SRT entries to this closure, then we
>   -- want to set the srt field in its info table as usual
>   (info_tbl { cit_srt = mapLookup (g_entry g) srt_env }, [])
>
> Just srtEntries -> srtTrace "maybeStaticFun" (ppr res)
>   (info_tbl { cit_rep = new_rep }, res)
>   where res = [ CmmLabel lbl | SRTEntry lbl <- srtEntries ]
>
> Here we only update SRT field of the block if we're not adding SRT entries
> to
> the function's closure, so in the example above, because we're using the
> function as SRT (and adding SRT entries to its closure) SRT field of c1vn
> won't
> be updated.
>
> Am I missing anything?
>
> Thanks,
>
> Ömer
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Code generation/SRT question

2020-01-06 Thread Simon Marlow
There's no need to set the srt field of f_info if f_closure is the SRT,
since any reference to f_info in the code will give rise to a reference to
f_closure in the SRT corresponding to that code fragment. Does that make
sense?

The use of a closure as an SRT is really quite a nice optimisation actually.

Cheers
Simon

On Wed, 1 Jan 2020 at 09:35, Ömer Sinan Ağacan  wrote:

> Hi Simon,
>
> In Cmm if I have a recursive group of functions f and g, and I'm using f's
> closure as the SRT for this group, should f's entry block's info table have
> f_closure as its SRT?
>
> In Cmm syntax
>
>  f_entry() {
>  { info_tbls: [...
>(c1vn,
> label: ...
> rep: ...
> srt: ??]
>stack_info: ...
>  }
>  {offset
>c1vn:
>  ...
>  }
>  }
>
> Here should I have `f_closure` in the srt field?
>
> I'd expect yes, but looking at the current SRT code, in
> CmmBuildInfoTables.updInfoSRTs, we have this:
>
>   (newInfo, srtEntries) = case mapLookup (g_entry g) funSRTEnv of
>
> Nothing ->
>   -- if we don't add SRT entries to this closure, then we
>   -- want to set the srt field in its info table as usual
>   (info_tbl { cit_srt = mapLookup (g_entry g) srt_env }, [])
>
> Just srtEntries -> srtTrace "maybeStaticFun" (ppr res)
>   (info_tbl { cit_rep = new_rep }, res)
>   where res = [ CmmLabel lbl | SRTEntry lbl <- srtEntries ]
>
> Here we only update SRT field of the block if we're not adding SRT entries
> to
> the function's closure, so in the example above, because we're using the
> function as SRT (and adding SRT entries to its closure) SRT field of c1vn
> won't
> be updated.
>
> Am I missing anything?
>
> Thanks,
>
> Ömer
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Parser performance: 10% regression in 8.8

2019-05-09 Thread Simon Marlow
Thanks for bringing this up.  I've merged the PR and uploaded Happy 1.19.10
to Hackage.  Can someone else look at steps 3-5?

Cheers
Simon

On Wed, 8 May 2019 at 09:51, Vladislav Zavialov 
wrote:

> Hello ghc-devs,
>
> This February I did some changes to the parser that require higher rank
> types support in ‘happy’. Unfortunately, as I discovered, happy’s --coerce
> option is severely broken in the presence of higher rank types, so I had to
> disable it. My benchmarks have shown a 10% slowdown from disabling --coerce
> (https://gist.github.com/int-index/38af0c5dd801088dc1de59eca4e55df4).
>
> Alongside my changes I submitted a pull request to happy which fixes the
> issue (https://github.com/simonmar/happy/pull/134), in the hope that it
> would get merged, released, and I could re-enable --coerce in GHC ‘happy'
> configuration.
>
> Unfortunately, my patch has been ignored to this day (for 3 months now),
> and the performance regression reached 8.8-alpha. We need to act swiftly if
> we want to avoid a performance regression in the actual release. Here’s
> what needs to be done:
>
> 1. Merge https://github.com/simonmar/happy/pull/134
> 2. Release a new ‘happy’
> 3. (Optional) Specify in GHC’s build system that it builds only with the
> latest 'happy' release
> 4. Restore the --coerce option in GHC’s build system ‘happy’ configuration
> 5. Backport it to the ghc-8.8 branch
>
> I have no access to do 1 & 2, I believe Simon Marlow does. I’d appreciate
> if someone took care of 3, currently the build system does not install
> ‘happy’ and assumes a system-wide installation without checking its
> version. This means that users of all but the newly released version will
> encounter obscure error messages. We need a version check. Then I will do
> 4, as planned, and create a merge request for 5.
>
> All the best,
> - Vladislav
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Why not short out IND_STATICs in the GC?

2019-04-29 Thread Simon Marlow
On Sat, 27 Apr 2019 at 07:44, Ömer Sinan Ağacan 
wrote:

> Hi Simon,
>
> I'm wondering why in the GC we don't short out IND_STATICs like we do in
> INDs
> and BLACKHOLEs. Is there a reason for that? In this code in evacuate():
>
>   case IND_STATIC:
>   evacuate_static_object(IND_STATIC_LINK((StgClosure *)q), q);
>   return;
>
> Why not do something like
>
>   case IND_STATIC:
>   q = ((StgIndStatic*)q)->indirectee;
>   *p = q;
>   goto loop;
>
> I actually tried it and it broke a lot of things, but I don't understand
> why.
> We basically turn this
>
> heap closure -> IND_STATIC -> heap closure
>
> into
>
> heap closure -> heap closure
>
> To me this should work, but for some reason it doesn't. Could you comment
> on why
> this doesn't work?
>

I think it might be to do with generational GC, although I'm not completely
sure and it would be good to nail down the precise reasoning and document
it.

CAFs live in the old generation, and when we first enter a CAF we add it to
the mutable list (remembered set). If we ignore the IND_STATIC, then the
closure will never get re-added to the mutable list, even if it still
points into the young generation. So the data will remain live for one GC,
but not the next GC. When we do an old-generation GC we might find the CAF
to be live (via the SRTs), but we've already GC'd the value it pointed to,
so it's too late.

Cheers
Simon

>
>
> Thanks,
>
> Ömer
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Proposal: Don't read environment files by default

2019-04-08 Thread Simon Marlow
On Sun, 7 Apr 2019 at 16:57, Oleg Grenrus  wrote:

>
> On 7.4.2019 17.21, Simon Marlow wrote:
> > As I understand it, the aim is to support workflows like "cabal
> > install $pkg; ghci" (amongst other things). This currently works with
> > 'cabal install' because it installs into the global package DB, but it
> > doesn't work with 'cabal new-install' which installs into
> > `~/.cabal/store`. Is the plan that 'cabal new-install' will drop a
> > .ghc-environment file in the current directory, even outside of a
> > cabal package/project? I would find that *very* surprising as a user.
>
> This is not correct.


Well, it was a question :)


> Cabal doesn't write (local) .ghc.environment files
> when you `cabal v2-install` __outside__ the project (actually it
> doesn't, even when you `v2-install` the local project either, as you
> don't build the local project then).
> - When you install an executable, say `cabal v2-install alex` it do
> nothing related to environment files (there is inference in reading them
> atm though)
> - When you install a library, say `cabal v2-install distributive --lib`,
> then `cabal` (tries to) update
> `~/.ghc/-/environments/default` (or specified
> environment), so following
> `ghci` or `(ghci -package-env=somename) could pickup that library.
>

Thanks, I wasn't aware of the default environment file. Seems perfectly
reasonable to me.


> Instead of cabal ghci -package $pkg you can do
>
> cabal v2-install $pkg1 --lib --package-env=foo
> cabal v2-install $pkg2 --lib --package-env=foo
> ...
> ghci -package-env=foo
>
> Or alternatively
>
> cabal v2-repl -b $pkg
>
> Unfortunately neither way is (known) bug free at the moment. I mostly
> use the former, with the `default` package-env (then I can omit
> --package-env flags) for all kind of experiments, e.g. to try out things
> when answering people on `#haskell` or Stack Overflow; but I have my own
> way to create environment file (i.e. I don't use v2-install --lib), as
> cabal is atm not perfect, see Cabal's issue 5888. It's however important
> to note, that `cabal` makes `ghc` ignore these global environments
> (especially the default one) in builds etc, so `cabal v2-build` works.
>

This all sounds good to me. I hope you can work out the bugs!

Cheers
Simon


> I suppose I somewhat agree with those who are calling for environment
> > files to require a command-line flag. We've gone to all this trouble
> > to make a nice stateless model for the package DB, but then we've
> > lobbed a stateful UI on top of it, which seems odd and is clearly
> > surprising a lot of people.
>
> I disagree. I created `~/.ghci` and `~/.../environments/default` because
> I want some defaults. Note: with v1-install people managed
> user-package-db, with v2-install you are supposed to manage
> environment(s). Yet, you can also only use `cabal v2-repl` or `cabal
> v2-run` (See "new-run also supports running script files that ..." in
> https://cabal.readthedocs.io/en/latest/nix-local-build.html#cabal-new-run
> ).
>
> Most of the above works (sans known bugs), and if you run Ubuntu, I
> invite you to try it out, as it's easy to install from Herbert's PPA:
> https://launchpad.net/~hvr/+archive/ubuntu/ghc
>
> >
> > Cheers
> > Simon
> >
> > On Thu, 28 Mar 2019 at 12:25, Herbert Valerio Riedel
> > mailto:hvrie...@gmail.com>> wrote:
> >
> > Matthew,
> >
> > I realize this to be a controversial issue, but what you're
> suggesting
> > is effectively an attempt at cutting this cabal V2 feature off at
> > the knees
> > ("If Cabal won't change its default let's cripple this feature on
> > GHC's
> > side by rendering it pointless to use in cabal").
> >
> > If ghc environment aren't read anymore by default they fail to have
> > the purpose they were invented for in the first place!
> >
> > At the risk of repeating things I've tried to explain already in the
> > GitHub issue let me motivate (again) why we have these env files: We
> > want to be able to provide a stateful interface providing the common
> > idiom users from non-Nix UIs are used to, and which `cabal` and `ghc`
> > already provided in the past; e.g.
> >
> >
> > ,
> > | $ cabal v1-install lens lens-aeson
> > |
> > | $ ghc --make MyProgUsingLens.hs
> > | [1 of 1] ...
> > | ...
> > |
> > | $ ghci
> > | GHCi, version 8.4.4: http://www.haskell.org/ghc/  :? for help
> > | Prelude> import Control.Lens
> > | Prelude Co

Re: Proposal: Don't read environment files by default

2019-04-07 Thread Simon Marlow
I've also been surprised (not in a good way) by environment files. But I
haven't followed all the discussion so I still have some questions.

As I understand it, the aim is to support workflows like "cabal install
$pkg; ghci" (amongst other things). This currently works with 'cabal
install' because it installs into the global package DB, but it doesn't
work with 'cabal new-install' which installs into `~/.cabal/store`. Is the
plan that 'cabal new-install' will drop a .ghc-environment file in the
current directory, even outside of a cabal package/project? I would find
that *very* surprising as a user.

Indeed it almost works to say 'ghci -package-db
~/.cabal/store/ghc-8.4.3/package.db` after 'cabal new-install $pkg', but
this might fail if there are conflicts in the package DB preventing the use
of $pkg. GHC does some not-very-clever constraint solving to end up with a
consistent set of packages, and you can guide it by adding '-package $pkg'
flags. But it's still not very clever, and might fail.

Instead what if we had something like 'cabal ghci -package $pkg' to
indicate that you want to start GHCi with $pkg available? It would be
Cabal's job to ensure that $pkg was built and made available to GHCi. For
more complex cases, you can create a package or a project, but simple
ad-hoc invocations would be well supported by this.

I suppose I somewhat agree with those who are calling for environment files
to require a command-line flag. We've gone to all this trouble to make a
nice stateless model for the package DB, but then we've lobbed a stateful
UI on top of it, which seems odd and is clearly surprising a lot of people.

Cheers
Simon

On Thu, 28 Mar 2019 at 12:25, Herbert Valerio Riedel 
wrote:

> Matthew,
>
> I realize this to be a controversial issue, but what you're suggesting
> is effectively an attempt at cutting this cabal V2 feature off at the knees
> ("If Cabal won't change its default let's cripple this feature on GHC's
> side by rendering it pointless to use in cabal").
>
> If ghc environment aren't read anymore by default they fail to have
> the purpose they were invented for in the first place!
>
> At the risk of repeating things I've tried to explain already in the
> GitHub issue let me motivate (again) why we have these env files: We
> want to be able to provide a stateful interface providing the common
> idiom users from non-Nix UIs are used to, and which `cabal` and `ghc`
> already provided in the past; e.g.
>
>
> ,
> | $ cabal v1-install lens lens-aeson
> |
> | $ ghc --make MyProgUsingLens.hs
> | [1 of 1] ...
> | ...
> |
> | $ ghci
> | GHCi, version 8.4.4: http://www.haskell.org/ghc/  :? for help
> | Prelude> import Control.Lens
> | Prelude Control.Lens>
> `
>
> or similarly, when you had just `cabal v1-build` something, you'd get
> access to your projects dependencies which were installed into ghc's
> user pkg-db.
>
> This is also a workflow which has been well documented for over a decade
> in Haskell's literature and instructions *and* this is the same idiom as
> used by many popular package managers out there ("${pkgmgr} install
> somelibrary")
>
> So `cabal v1-build` made use of the user package-db facility to achieve
> this; but now with `cabal v2-build` the goal was to improve this
> workflow, but the user pkg-db facility wasn't a good fit anymore for the
> nix-style pkg store cache which can easily have dozens instances for the
> same lens-4.17 pkg-id cached (I just checked, I currently have 9
> instances of `lens-4.17` cached in my GHC 8.4.4 pkg store).
>
> So ghc environment files were born as a clever means to provide a
> thinned slice/view into the nix-style pkg store.
>
> And with these we can provide those workflows *without* the needed to pass
> extra flags or having to prefix each `ghc` invocation with `cabal
> repl`/`cabal exec`:
>
> ,
> | $ cabal v2-install --lib lens lens-aeson
> |
> | $ ghc --make MyProgUsingLens.hs
> | Loaded package environment from
> /home/hvr/.ghc/x86_64-linux-8.4.4/environments/default
> | [1 of 1] ...
> | ...
> |
> | $ ghci
> | GHCi, version 8.4.4: http://www.haskell.org/ghc/  :? for help
> | Loaded package environment from
> /home/hvr/.ghc/x86_64-linux-8.4.4/environments/default
> | Prelude> import Control.Lens
> | Prelude Control.Lens>
> `
>
> (and respectively for the `cabal v2-build` workflow)
>
> However, if we now had to explicitly pass a flag to ghc in order to have
> it pick up ghc env files, this would severly break this workflow
> everytime you forget about it, and it would certainly cause a lot of
> confusion (of e.g. users following instructions such as `cabal install
> lens` and then being confused that GHCi doesn't pick it up) and
> therefore a worse user experience for cabal users.
>
> Even more confusing is that GHCs GHC 8.0, GHC 8.2, GHC 8.4, and GHC 8.6
> have been picking up ghc env files by default (and finally we've reached
> the point where the pkg-env-file-agnostic GHC versions are old enough to
> have moved 

Re: How do I find out which info table a continuation belongs to?

2019-02-10 Thread Simon Marlow
I believe this is due to https://phabricator.haskell.org/D4722

(cc Sergei Azovskov)

I'm a bit surprised that gdb isn't showing anything though, it should know
that the address corresponds to a temporary symbol like `.L1234`. Perhaps
you need to compile with -g to make this work, I'm not sure.

On Sun, 10 Feb 2019 at 07:50, Ömer Sinan Ağacan 
wrote:

> I'm currently working on a bug and one of the things I often want to know
> is
> what's on the stack. The problem is I can't see labels of continuations so
> the
> information is really useless. Example:
>
> >>> call printStack(((StgTSO*)0x42000e0198)->stackobj)
> 0x42000c8788: RET_SMALL (0x512d70)
> 0x42000c8790: RET_SMALL (0x40edf0)
>stk[5] (0x42000c8798) = 0x7b3938
> 0x42000c87a0: CATCH_FRAME(0x735a98,0x7d3ff2)
> 0x42000c87b8: STOP_FRAME(0x7311b8)
>
> (I modified the printer to print stack locations when printing stacks)
>
> Here I need to know which info table the RET_SMALLs return to. Normally I
> do
> this for other kinds of closures:
>
> >>> print ((StgClosure*)...)->header.info
> $15 = (const StgInfoTable *) 0x404dc0 
>
> But for continuations that doesn't work:
>
> >>> print ((StgClosure*)0x42000c8788)->header.info
> $11 = (const StgInfoTable *) 0x512d80
> >>> info symbol 0x512d80
> No symbol matches 0x512d80.
>
> Anyone know how to make this work? Can I maybe mark the continuations
> label in
> the generated assembly somehow to make those labels available in gdb?
>
> Thanks
>
> Ömer
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [GHC DevOps Group] Welcome to GitLab!

2019-01-07 Thread Simon Marlow
Congrats Ben and co! This is a huge step forwards.

On Thu, 27 Dec 2018 at 06:27, Ben Gamari  wrote:

>
> git remote set-url origin https://gitlab.haskell.org/ghc/ghc.git
> git remote set-url --push origin g...@gitlab.haskell.org:ghc/ghc
>
> This is all that should be necessary; a quick `git pull origin master`
> should verify that everything is working as expected.
>

submodules are still pulling from git.haskell.org, is there an easy way to
fix that?

Cheers
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [GHC DevOps Group] GitLab migration status

2018-12-17 Thread Simon Marlow
Hi Ben - this sounds good, a couple of questions:

- What about the performance issue we noticed last week?
- What will happen to Phabricator diffs that are still mid-review? It would
be a shame to have to move them to gitlab and interrupt the review trail.
Can't we just shut Phabricator to new diffs but keep the possibility of
working on existing ones?

Cheers
Simon

On Mon, 17 Dec 2018 at 05:29, Ben Gamari  wrote:

> TL;DR. Given somewhat slower-than-expected progress on the Trac import I
>suggest that we implement a pared-down migration on Tuesday.
>See "The Plan" below.
>
>
> Hello everyone,
>
> Over the last few weeks we have been hard at work preparing the
> migration to GitLab. Currently the following things are ready:
>
>  * Hosting of GHC's repositories and those of its mirrors have been
>prepared.
>
>  * Continuous integration has been configured for GHC.
>
>All-in-all the GitLab migration has been quite timely since we were
>recently notified by CircleCI of billing changes which will soon make
>it quite difficult for us to continue using their services (see the
>thread on ghc-devops for details).
>
>Thankfully, moving CI to GitLab has been mostly painless and has
>even enabled us to introduce testing of platforms which were
>previously inaccessible to us under CircleCI.
>
>  * The various linters which previously ran via `arc lint` and gitolite
>post-receive hooks have been ported to CI jobs.
>
>  * The Trac ticket migration is looking good although there are still a
>significant number of details which need to be sorted out.
>
>  * The Wiki migration is in a similar state.
>
> Over the past weeks we have been in constant contact with GitLab's FOSS
> outreach group, who have been quite helpful in getting the eyes of
> GitLab employees on the issues affecting our transition. Thanks to
> especially to David Planella for his help so far.
>
> Unfortunately, there is one issue in particular [1] which is currently
> blocking the Trac migration. From my discussions with GitLab's upstream
> it sounds like it may be possible for them to prioritize a fix in the
> short-term. However, our aggressive migration timeline is a fair bit
> faster than GitLab's development cycle and consequently this certainly
> won't happen before our planned migration on Tuesday.
>
>
> # The Plan
>
> Given what remains to be done in the Trac migration I believe it would
> be a mistake to move ahead with the full migration as planned. However,
> in the interest of re-gaining functional continuous integration of
> patches as soon as possible I propose that we move ahead with moving
> code review on Tuesday.
>
> The plan would be as follows:
>
>  1. We setup the final gitlab.haskell.org instance tomorrow; since the
> Trac migration will not be run will need to create new accounts on
> instance.
>
>  2. We begin officially accepting merge requests on this fresh GitLab
> instance on Tuesday. At this point gitlab.haskell.org:ghc/ghc will
> become GHC's official upstream repository.
>
>  3. We allow a week of transition time where new Differentials will
> continue to be accepted via Phabricator.
>
>  4. After this transition period we place Phabricator in read-only mode.
>
>  5. When we are confident in the Trac migration (likely after the new
> year) we move ahead with importing tickets and the wiki
>
> Previously I was skeptical of any plan that involved running the Trac
> migration against a live GitLab instance. However, further reflection
> I believe such a migration is safe and feasible. Moreover, given the
> constraints set upon us by the impending CircleCI changes, I think this
> is our best option to ensure continuity of CI.
>
> Thoughts?
>
> Cheers,
>
> - Ben
>
>
> [1] https://gitlab.com/gitlab-org/gitlab-ce/issues/46980
> ___
> Ghc-devops-group mailing list
> ghc-devops-gr...@haskell.org
> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devops-group
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Residency profiles

2018-12-10 Thread Simon Marlow
https://phabricator.haskell.org/D5428


On Sun, 9 Dec 2018 at 10:12, Sebastian Graf  wrote:

> Ah, I was only looking at `+RTS --help`, not the users guide. Silly me.
>
> Am Do., 6. Dez. 2018 um 20:53 Uhr schrieb Simon Marlow  >:
>
>> It is documented!
>> https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/runtime_control.html#rts-flag--F%20%E2%9F%A8factor%E2%9F%A9
>>
>> On Thu, 6 Dec 2018 at 16:21, Sebastian Graf  wrote:
>>
>>> Hey,
>>>
>>> thanks, all! Measuring with `-A1M -F1` delivers much more reliable
>>> residency numbers.
>>> `-F` doesn't seem to be documented. From reading `rts/RtsFlags.c` and
>>> `rts/sm/GC.c` I gather that it's the factor by which to multiply the number
>>> of live bytes by to get the new old gen size?
>>> So effectively, the old gen will 'overflow' on every minor GC, neat!
>>>
>>> Greetings
>>> Sebastian
>>>
>>> Am Do., 6. Dez. 2018 um 12:52 Uhr schrieb Simon Peyton Jones via
>>> ghc-devs :
>>>
>>>> |  Right. A parameter for fixing the nursery size would be easy to
>>>> implement,
>>>> |  I think. Just a new flag, then in GC.c:resize_nursery() use the flag
>>>> as the
>>>> |  nursery size.
>>>>
>>>> Super!  That would be v useful.
>>>>
>>>> |  "Max. residency" is really hard to measure (need to do very frequent
>>>> GCs),
>>>> |  perhaps a better question to ask is "residency when the program is
>>>> in state
>>>> |  S".
>>>>
>>>> Actually, Sebastian simply wants to see an accurate, reproducible
>>>> residency profile, and doing frequent GCs might well be an acceptable
>>>> cost.
>>>>
>>>> Simon
>>>> ___
>>>> ghc-devs mailing list
>>>> ghc-devs@haskell.org
>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>>
>>>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Cmm Memory Model (Understanding #15449)

2018-12-07 Thread Simon Marlow
FWIW, my main reference at the time when this stuff was implemented was
this page by Doug Lea: http://gee.cs.oswego.edu/dl/jmm/cookbook.html

As Ben says, things have evolved a lot since then. I'm not an expert at
all, but I know from experience that getting this stuff right is really
hard. Even on x86 we had a tough time figuring out where to put this
barrier:
https://phabricator.haskell.org/diffusion/GHC/browse/master/rts%2FWSDeque.c$135-137

My understanding of the current memory model is this:
- we give no guarantees about ordering between non-atomic IORef operations,
except that: doing things in parallel shouldn't segfault". So if a
processor can see a pointer in an IORef, it can safely follow the pointer
and find the memory it points to correctly initialized. This may require
barriers on some architectures, but not x86(_64) as I understand it.
- MVar operations and atomicModifyIORef are full barriers. Or something.

Cheers
Simon


On Thu, 29 Nov 2018 at 04:44, Travis Whitaker 
wrote:

> Hello GHC Devs,
>
> I'm trying to get my head around ticket #15449 (
> https://ghc.haskell.org/trac/ghc/ticket/15449). This gist of things is
> that GHC generates incorrect aarch64 code that causes memory corruption in
> multithreaded programs run on out-of-order machines. User trommler
> discovered that similar issues are present on PowerPC, and indeed ARMv7 and
> PowerPC support the same types of load/store reorderings. The LLVM code
> emitted by GHC may be incorrect with respect to LLVM's memory model, but
> this isn't a problem on architectures with minimal reordering like x86.
>
> I had initially thought that GHC simply wasn't emitting the appropriate
> LLVM fences; there's an elephant-gun-approach here (
> https://github.com/TravisWhitaker/ghc/commits/ghc843-wip/T15449) that
> guards each atomic operation with a full barrier. I still believe that GHC
> is omitting necessary LLVM fences, but this change is insufficient to fix
> the behavior of the test case (which is simply GHC itself compiling a test
> package with '-jN', N > 1).
>
> It seems there's a long and foggy history of the Cmm memory model. Edward
> Yang discusses this a bit in his post here (
> http://blog.ezyang.com/2014/01/so-you-want-to-add-a-new-concurrency-primitive-to-ghc/)
> and issues similar to #15449 have plagued GHC in the past, like #12469 (
> https://ghc.haskell.org/trac/ghc/ticket/12469). Worryingly, GHC only has
> MO_WriteBarrier, whereas PowerPC and ARMv7 really need read, write, and
> full memory barriers. On ARM an instruction memory barrier might be
> required as well, but I don't know enough about STG/Cmm to say for sure,
> and it'd likely be LLVM's responsibility to emit that anyway.
>
> I'm hoping that someone with more tribal knowledge than I might be able to
> give me some pointers with regards to the following areas:
>
>
>- Does STG itself have anything like a memory model? My intuition says
>'definitely not', but given that STG expressions may contain Cmm operations
>(via StgCmmPrim), there may be STG-to-STG transformations that need to care
>about the target machine's memory model.
>- With respect to Cmm, what reorderings does GHC perform? What are the
>relevant parts of the compiler to begin studying?
>- Are the LLVM atomics that GHC emits correct with respect to the LLVM
>memory model? As it stands now LLVM fences are only emitted for
>MO_WriteBarrier. Without fences accompanying the atomics, it seems the LLVM
>compiler could float dependent loads/stores past atomic operations.
>- Why is MO_WriteBarrier the only provided memory barrier? My hunch is
>that it's because this is the only sort of barrier required on x86, which
>only allows loads to be reordered with older stores, but perhaps I'm
>missing something? Is it plausible that Cmm simply needs additional barrier
>primitives to target these weaker memory models? Conversely, is there some
>property of Cmm that let's us get away without read barriers at all?
>
>
> Naturally, if I've got any of this wrong or are otherwise barking up the
> wrong tree, please let me know.
>
> Thanks for all your efforts!
>
> Travis Whitaker
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Residency profiles

2018-12-06 Thread Simon Marlow
It is documented!
https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/runtime_control.html#rts-flag--F%20%E2%9F%A8factor%E2%9F%A9

On Thu, 6 Dec 2018 at 16:21, Sebastian Graf  wrote:

> Hey,
>
> thanks, all! Measuring with `-A1M -F1` delivers much more reliable
> residency numbers.
> `-F` doesn't seem to be documented. From reading `rts/RtsFlags.c` and
> `rts/sm/GC.c` I gather that it's the factor by which to multiply the number
> of live bytes by to get the new old gen size?
> So effectively, the old gen will 'overflow' on every minor GC, neat!
>
> Greetings
> Sebastian
>
> Am Do., 6. Dez. 2018 um 12:52 Uhr schrieb Simon Peyton Jones via ghc-devs <
> ghc-devs@haskell.org>:
>
>> |  Right. A parameter for fixing the nursery size would be easy to
>> implement,
>> |  I think. Just a new flag, then in GC.c:resize_nursery() use the flag
>> as the
>> |  nursery size.
>>
>> Super!  That would be v useful.
>>
>> |  "Max. residency" is really hard to measure (need to do very frequent
>> GCs),
>> |  perhaps a better question to ask is "residency when the program is in
>> state
>> |  S".
>>
>> Actually, Sebastian simply wants to see an accurate, reproducible
>> residency profile, and doing frequent GCs might well be an acceptable
>> cost.
>>
>> Simon
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [GHC DevOps Group] The future of Phabricator

2018-11-06 Thread Simon Marlow
For those of us that like to upload code for review without having to go to
a website and click buttons, it looks like there's this CLI tool for GitLab:

  https://github.com/zaquestion/lab

Unfortunately it's written in Go. But I guess that's an improvement over
PHP :)

Cheers
Simon


On Sat, 3 Nov 2018 at 16:35, Ben Gamari  wrote:

> Simon Marlow  writes:
>
> > On Fri, 2 Nov 2018 at 08:59, Herbert Valerio Riedel 
> > wrote:
> >
> >> On 2018-11-02 at 08:13:37 +, Simon Marlow wrote:
> >>
> >> > I suppose we can do a squash-merge when committing to keep the history
> >> > clean, but then contributors have a choice - either do GitHub-style
> >> > where you add commits to a PR to update it and we squash on merge, OR
> >> > Phabricator-style where you keep the same set of commits and rebase
> >> > the stack to update it.
> >> [..]
> >>
> >> Well, if MRs are to be squashed on merge anyway, I'm definitely not
> >> going to waste my time carefully grooming a stack of atomic individually
> >> validating commits via git-rebase-interactive...
> >>
> >
> > Sorry I wasn't very clear. We would *only* squash if the author had been
> > using the workflow where they add commits to revise the MR. If the author
> > wants to use the stacked-diff-like workflow where they keep a groomed set
> > of commits in the MR, then we would rebase and fast-forward the MR.
> >
> > My concern here is that we have two different workflows. People used to
> > GitHub would want to use one, and people used to Phabricator would want
> to
> > use the other. We have to check which workflow people are using so that
> we
> > can decide whether to squash on merge or not.
> >
> Ahh, yes, I see.
>
> > Ben said:
> >
> >> This shouldn't be a problem. One can easily configure a project such
> > that users are *only* allowed to fast-forward/rebase, disallowing the
> > creation of merge commits.
> >
> > but that doesn't fully address the problem, because the series of commits
> > that would get rebased onto master would include all the commits added to
> > the MR to update it during the review process. Actually what we wanted to
> > do in this case was squash, not rebase+fast-forward.
> >
> Indeed, this is a problem that we already have in the case of GitHub
> pull requests. In most of these cases I end up squashing the branch
> myself when I merge (in practice this contributes very little overhead;
> I need to merge GitHub PR's myself anyways as we cannot use GitHub's
> merge button since github.com:ghc/ghc is merely a mirror of
> git.haskell.org:ghc).
>
> Of course, if we start taking *all* of our patches via MRs then I agree
> that this may become a bit more tiresome.
>
> > If there was a nice way to guide people into using the Phabricator-style
> > workflow, I think that would help a lot.
> >
> I think this is primarily a social problem and consequently it is
> probably best handled by a combination of documentation (both in the
> contributor documentation and the MR template text) and code review.
>
> One of the things I would like to do in the near future is consolidate
> (and, in some cases, rewrite) our contributor documentation. The survey
> indicated that there is plenty of room for improvement here. In this
> past we have discussed improving in this area but lacked the bandwidth
> to give the task the attention it deserves. I think now we are in better
> shape to resource it sufficiently.
>
> Cheers,
>
> - Ben
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [GHC DevOps Group] The future of Phabricator

2018-11-03 Thread Simon Marlow
On Fri, 2 Nov 2018 at 08:59, Herbert Valerio Riedel 
wrote:

> On 2018-11-02 at 08:13:37 +0000, Simon Marlow wrote:
>
> > I suppose we can do a squash-merge when committing to keep the history
> > clean, but then contributors have a choice - either do GitHub-style
> > where you add commits to a PR to update it and we squash on merge, OR
> > Phabricator-style where you keep the same set of commits and rebase
> > the stack to update it.
> [..]
>
> Well, if MRs are to be squashed on merge anyway, I'm definitely not
> going to waste my time carefully grooming a stack of atomic individually
> validating commits via git-rebase-interactive...
>

Sorry I wasn't very clear. We would *only* squash if the author had been
using the workflow where they add commits to revise the MR. If the author
wants to use the stacked-diff-like workflow where they keep a groomed set
of commits in the MR, then we would rebase and fast-forward the MR.

My concern here is that we have two different workflows. People used to
GitHub would want to use one, and people used to Phabricator would want to
use the other. We have to check which workflow people are using so that we
can decide whether to squash on merge or not.

Ben said:

> This shouldn't be a problem. One can easily configure a project such
that users are *only* allowed to fast-forward/rebase, disallowing the
creation of merge commits.

but that doesn't fully address the problem, because the series of commits
that would get rebased onto master would include all the commits added to
the MR to update it during the review process. Actually what we wanted to
do in this case was squash, not rebase+fast-forward.

If there was a nice way to guide people into using the Phabricator-style
workflow, I think that would help a lot.

Cheers
Simon



>
> > If you want to do dependent commits then you have to use Phabricator
> > style. Choices between workflows make things more complicated for
> > contributors, and that worries me.
>
> ...submitting a stacked set of commits as invidual overlapping MRs
> (i.e. where the first MR has only the first commit, the 2nd has the
> first two commits from the stack, and so on) -- if that's what you're
> referring to as "Phabricator-style" -- sounds like an awkward workflow
> to me.
>
> > Does GitLab keep the history of a PR after it has been updated, like in
> > Phabricator? So we can see what happened between versions of a PR?
>
> I wonder too how this is represented in GitLab... especially when a MR
> is comprised of multiple commits, and those individual commits evolve,
> might get reordered, commits added or removed fromt he stack, or when
> the whole MR gets rebased in the process...
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [GHC DevOps Group] The future of Phabricator

2018-11-02 Thread Simon Marlow
What about the wiki? Can we migrate that off Trac too?

We'd have to keep redirects in place on ghc.haskell.org to avoid breaking
links to tickets and wiki pages from elsewhere.

If we really can do a stacked-diff-style workflow using PRs on GitLab then
that at least for me removes one of the big drawbacks of moving. But how
easy will it be to enforce that workflow and will it be going against the
grain on GitLab? I imagine people used to adding extra commits to a PR will
tend to do that rather than amending+rebasing. I suppose we can do a
squash-merge when committing to keep the history clean, but then
contributors have a choice - either do GitHub-style where you add commits
to a PR to update it and we squash on merge, OR Phabricator-style where you
keep the same set of commits and rebase the stack to update it. If you want
to do dependent commits then you have to use Phabricator style. Choices
between workflows make things more complicated for contributors, and that
worries me.

Does GitLab keep the history of a PR after it has been updated, like in
Phabricator? So we can see what happened between versions of a PR?

Cheers
Simon

On Tue, 30 Oct 2018 at 19:22, Ben Gamari  wrote:

> Simon Marlow  writes:
>
> > I'm entirely happy to move, provided (1) whatever we move to provides the
> > functionality we need, and (2) it's clearly what the community wants
> > (considering both current and future contributors). In the past when
> moving
> > to GitHub was brought up, there were a handful of core contributors who
> > argued strongly in favour of Phabricator, do we think that's changed? Do
> we
> > have any indication of whether the survey respondents who were
> > anti-Phabricator would be pro- or anti-GitLab?
> >
> The comments fell into several buckets:
>
>  a. Those who spoke in favor of GitHub in particular
>  b. Those who spoke in favor of GitHub and GitLab
>  c. Those who spoke against Phabricator
>
> I seem to recall that (a) was the largest group. No one explicitly
> stated that they would be against GitLab, although this is not terribly
> surprising given we didn't ask.
>
> Frankly I doubt there would be people who would actively support GitHub
> but not GitLab given how similar the workflows are. However, collecting
> data for this hunch is one of the reasons for this thread.
>
> > Personally I'd like to optimise for more code review, because I think
> that
> > more than anything else will increase quality and community ownership of
> > the project. If using new tooling will make code review a more central
> part
> > of our workflow, then that would be a good thing.
>
> Agreed, currently we have too few reviewers for the volume of code we
> are pushing into the tree.
>
> > Right now I think we're
> > very Trac-centric, and the integration between Trac and Phabricator isn't
> > great; if we could move to a solution with tighter integration between
> > tickets/code-review/wiki, that would be an improvement in my view. But
> not
> > GitHub, for the reasons you gave.
> >
> Yes, I agree. Currently I spend too much time keeping tickets in sync and
> this is almost entirely wasted time.
>
>
> > Would GitLab solve the CI issues? I don't think you mentioned that
> > explicitly.
> >
> It helps, yes. As Andres pointed out, Appveyor has native support for
> GitLab, which we use for Windows validation. Furthermore, GitLab's
> native CI would allow us to test non-x86 platforms.
>
> CircleCI lacks GitLab support however I believe the integration we have
> already developed to support integration with Phabricator could be
> easily adapted for GitLab.
>
> Moreover, given that the "Add GitLab support" request is at the top of
> CircleCI's feature request tracker, it seems likely that there will be
> native support in the future.
>
> Cheers,
>
> - Ben
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Hitting RTS bug on GHC 8.0.2

2018-10-30 Thread Simon Marlow
Looking at the code I can't see how that assertion could possibly fail.  Is
it reproducible?

On Tue, 30 Oct 2018 at 08:38, Harendra Kumar 
wrote:

> Hi,
>
> I got the following crash in one of my CI tests (
> https://travis-ci.org/composewell/streamly/jobs/448112763):
>
> test: internal error: RELEASE_LOCK: I do not own this lock: rts/Messages.c
> 54
> (GHC version 8.0.2 for x86_64_unknown_linux)
> Please report this as a GHC bug:
> http://www.haskell.org/ghc/reportabug
>
> I have hit this just once yet. Is this worth opening a ticket, given that
> this is an older version of the compiler? Has something like been fixed
> since then or might this be present in newer versions as well?
>
> -harendra
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [GHC DevOps Group] The future of Phabricator

2018-10-30 Thread Simon Marlow
I'm entirely happy to move, provided (1) whatever we move to provides the
functionality we need, and (2) it's clearly what the community wants
(considering both current and future contributors). In the past when moving
to GitHub was brought up, there were a handful of core contributors who
argued strongly in favour of Phabricator, do we think that's changed? Do we
have any indication of whether the survey respondents who were
anti-Phabricator would be pro- or anti-GitLab?

Personally I'd like to optimise for more code review, because I think that
more than anything else will increase quality and community ownership of
the project. If using new tooling will make code review a more central part
of our workflow, then that would be a good thing. Right now I think we're
very Trac-centric, and the integration between Trac and Phabricator isn't
great; if we could move to a solution with tighter integration between
tickets/code-review/wiki, that would be an improvement in my view. But not
GitHub, for the reasons you gave.

Would GitLab solve the CI issues? I don't think you mentioned that
explicitly.

Cheers
Simon

On Tue, 30 Oct 2018 at 04:54, Ben Gamari  wrote:

>
> TL;DR. For several reasons I think we should consider alternatives to
>Phabricator. My view is that GitLab seems like the best option.
>
>
> Hello everyone,
>
> Over the past year I have been growing increasingly weary of our
> continued dependence on Phabricator. Without a doubt, its code review
> interface is the best I have used. However, for a myriad of reasons I
> am recently questioning whether it is still the best tool for GHC's
> needs.
>
>
> # The problem
>
> There are a number of reasons why I am currently uncertain about
> Phabricator.
>
> For one, at this point we have no options for support in the event that
> something goes wrong as the company responsible for Phabricator,
> Phacility, has closed their support channels to non-paying customers.
> Furthermore, in the past year or two Phacility has been placing their
> development resources in the parts their customers pay them for, which
> appear to be much different that the parts that we actively use. For
> this reason, some parts that we rely on seem oddly half-finished.
>
> This concern was recently underscored by some rather unfortunate
> misfeatures in Harbormaster which resulted in broken CI after the
> Hadrian merge and now apparent bugs which have made it difficult to
> migrate to the CircleCI integration we previously prepared.
>
> Perhaps most importantly, in our recent development priorities survey
> our use of Phabricator was the most common complaint by a fair margin,
> both in case of respondents who have contributed patches and those who
> have not. On the whole, past contributors and potential future
> contributors alike have strongly indicated that they want a more
> Git-like experience. Of course, this wasn't terribly surprising; this
> is just the most recent case where contributors have made this
> preference known.
>
> Frankly, in a sense it is hard to blame them. The fact that users need
> to install a PHP tool, Arcanist, to contribute anything but
> documentation patches has always seemed like unnecessary friction to me
> and I would be quite happy to be rid of it. Indeed we have had a quite
> healthy number of GitHub documentation patches since we started
> accepting them. This makes me thing that there may indeed be potential
> contributoes that we are leaving on the table.
>
>
> # What to do
>
> With Rackspace support ending at the end of year, now may be a good
> time to consider whether we really want to continue on this road.
> Phabricator is great at code review but I am less and less certain that
> it is worth the maintenance uncertainty and potential lost contributors
> that it costs.
>
> Moreover, good alternatives seem closer at-hand than they were when we
> deployed Phabricator.
>
>
> ## Move to GitHub
>
> When people complain about our infrastructure, they often use GitHub as
> the example of what they would like to see. However, realistically I
> have a hard time seeing GitHub as a viable option. Its feature set is
> simply
> insufficient enough to handle the needs of a larger project like GHC
> without significant external tooling (as seen in the case of Rust-lang).
>
> The concrete reasons have been well-documented in previous discussions
> but, to summarize,
>
>  * its review functionality is extremely painful to use with larger
>patches
>
>  * rebased patches lead to extreme confusion and lost review comments
>
>  * it lacks support for pre-receive hooks, which serve as a last line of
>defense to prevent unintended submodule changes
>
>  * its inability to deal with external tickets is problematic
>
>  * there is essentially no possibility that we could eventually migrate
>GHC's tickets to GitHub's ticket tracker without considerable data
>loss (much less manage the ticket load that would result), meaning
>that we 

Re: Treatment of unknown pragmas

2018-10-26 Thread Simon Marlow
What pragma syntax should other Haskell compilers use? I don't think it's
fair for GHC to have exclusive rights to the pragma syntax form the report,
and other compilers should not be relegated to using {-# X-FOOHC ... #-}.
But now we have all the same issues again.

Cheers
Simon

On Thu, 25 Oct 2018 at 21:32, Ben Gamari  wrote:

> Niklas Larsson  writes:
>
> > Hi!
> >
> > Why not follow the standard in that pragmas were intended for all
> > tools consuming Haskell ...
>
> That much isn't clear to me. The Report defines the syntax very
> specifically to be for "compiler pragmas" to be used by "compiler
> implementations". I personally consider "the compiler" to be something
> different from tools like HLint.
>
> Of course, on the other hand it also specified that implementations
> should ignore unknown pragmas, so the original authors clearly didn't
> anticipate that non-compiler tooling would be so common.
>
> > ... and not for GHCs exclusive use?
> > All that would require is to make the warning opt-in.
> >
> Disabling the unknown pragma warning by default would mean that users
> not be warned if they mis-spelled LANGAGE or INILNE, which could result
> in frustrating error messages for the uninitiated. It seems to me that
> we should try to avoid this given just how common these pragmas are in
> practice.
>
> Finally, in general I think it would be generally useful to have a
> properly namespaced syntax for tooling pragmas. Afterall, we otherwise
> end up with tools claiming random bits of syntax, resulting in an
> unnecessarily steep learning curve and potentially
> syntactically-colliding tools.
>
> Cheers,
>
> - Ben
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Shall we make -dsuppress-uniques default?

2018-10-24 Thread Simon Marlow
For what it's worth, I put this in my .zshrc

cleancore=(-ddump-simpl -dsuppress-coercions -dsuppress-var-kinds
-dsuppress-idinfo -dsuppress-type-signatures -dsuppress-type-applications)

and then ghc $cleancore -c Foo.hs

but this is mainly for the use case of "I wonder if this thing is getting
optimised the way I hope, let's have a look at the Core".

There's also this little tool which is aimed at the same kind of thing:
https://github.com/shachaf/ghc-core

So I'd say there's definitely a demand for something, but it's not entirely
clear what the something is.  Someone could make a proposal...

On Sat, 6 Oct 2018 at 00:12, Simon Peyton Jones via ghc-devs <
ghc-devs@haskell.org> wrote:

> Like Richard I use the uniques all the time.
>
> I'd prefer to leave it as-is, unless there is widespread support for a
> change
>
> S
>
>
> | -Original Message-
> | From: ghc-devs  On Behalf Of Ömer Sinan
> | Agacan
> | Sent: 05 October 2018 20:02
> | To: r...@cs.brynmawr.edu
> | Cc: ghc-devs 
> | Subject: Re: Shall we make -dsuppress-uniques default?
> |
> | > What do you say to GHC to get it to print the uniques that you don't
> | like?
> |
> | I usually use one of these: -ddump-simpl, -dverbose-core2core,
> | -ddump-simpl-iterations, -ddump-stg. All of these print variables with
> | unique
> | details and I literally never need those details. Rarely I use -ddump-cmm
> | too.
> |
> | Agreed that having different defaults in different dumps/traces might
> | work ..
> |
> | Ömer
> |
> | Richard Eisenberg , 5 Eki 2018 Cum, 21:54
> | tarihinde şunu yazdı:
> | >
> | > I'm in the opposite camp. More often than not, the biggest advantage of
> | dumps during GHC development is to see the uniques. Indeed, I often
> | ignore the actual names of variables and just work in my head with the
> | uniques.
> | >
> | > Perhaps the more complete answer is to fine-tune what settings cause
> | the uniques to be printed. -ddump-xx-trace should almost certainly.
> | Perhaps other modes needn't. What do you say to GHC to get it to print
> | the uniques that you don't like?
> | >
> | > Richard
> | >
> | > > On Oct 5, 2018, at 2:48 PM, Ömer Sinan Ağacan 
> | wrote:
> | > >
> | > > I asked this on IRC and didn't hear a lot of opposition, so as the
> | next step
> | > > I'd like to ask ghc-devs.
> | > >
> | > > I literally never need the details on uniques that we currently print
> | by
> | > > default. I either don't care about variables too much (when not
> | comparing the
> | > > output with some other output), or I need -dsuppress-uniques (when
> | comparing
> | > > outputs). The problem is I have to remember to add -dsuppress-uniques
> | if I'm
> | > > going to compare the outputs, and if I decide to compare outputs
> | after the fact
> | > > I need to re-generate them with -dsuppress-uniques. This takes time
> | and effort.
> | > >
> | > > If you're also of the same opinion I suggest making -dsuppress-
> | uniques default,
> | > > and providing a -dno-suppress-uniques (if it doesn't already exist).
> | > >
> | > > Ömer
> | > > ___
> | > > ghc-devs mailing list
> | > > ghc-devs@haskell.org
> | > >
> |
> https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.hask
> | ell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
> | devsdata=02%7C01%7Csimonpj%40microsoft.com
> %7C07ec32bd26d149c457ab08d
> | 62af537c9%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636743630029759709
> | sdata=4DVsRJ4Burv2%2BZGf38py%2FNRqM5j5%2FJAUkJPrUl7%2F%2Fm0%3Dr
> | eserved=0
> | >
> | ___
> | ghc-devs mailing list
> | ghc-devs@haskell.org
> |
> https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.hask
> | ell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
> | devsdata=02%7C01%7Csimonpj%40microsoft.com
> %7C07ec32bd26d149c457ab08d
> | 62af537c9%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636743630029759709
> | sdata=4DVsRJ4Burv2%2BZGf38py%2FNRqM5j5%2FJAUkJPrUl7%2F%2Fm0%3Dr
> | eserved=0
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Why align all pinned array payloads on 16 bytes?

2018-10-24 Thread Simon Marlow
I don't imagine anyone wants to align to anything that's not a power of 2,
or less than a word size. Still, unless the current generality results in
extra complication or overheads I wouldn't change it.

On Mon, 22 Oct 2018 at 11:44, Ömer Sinan Ağacan 
wrote:

> Thanks for all the answers. Another surprising thing about the pinned
> object
> allocation primops is that the aligned allocator allows alignment to bytes,
> rather than to words (the documentation doesn't say whether it's words or
> bytes,
> but it can be seen from the code that it's actually aligning to the given
> byte). Is there a use case for this or people mostly use alignment on word
> boundaries?
>
> Ömer
>
> Sven Panne , 17 Eki 2018 Çar, 10:29 tarihinde şunu
> yazdı:
> >
> > Am Di., 16. Okt. 2018 um 23:18 Uhr schrieb Simon Marlow <
> marlo...@gmail.com>:
> >>
> >> I vaguely recall that this was because 16 byte alignment is the minimum
> you need for certain foreign types, and it's what malloc() does.  Perhaps
> check the FFI spec and the guarantees that mallocForeignPtrBytes and
> friends provide?
> >
> >
> > mallocForeignPtrBytes is defined in terms of malloc (
> https://www.haskell.org/onlinereport/haskell2010/haskellch29.html#x37-28400029.1.3),
> which in turn has the following guarantee (
> https://www.haskell.org/onlinereport/haskell2010/haskellch31.html#x39-28700031.1
> ):
> >
> >"... All storage allocated by functions that allocate based on a size
> in bytes must be sufficiently aligned for any of the basic foreign types
> that fits into the newly allocated storage. ..."
> >
> > The largest basic foreign types are Word64/Double and probably
> Ptr/FunPtr/StablePtr (
> https://www.haskell.org/onlinereport/haskell2010/haskellch8.html#x15-178.7),
> so per spec you need at least an 8-byte alignement. But in an SSE-world I
> would be *very* reluctant to use an alignment less strict than 16 bytes,
> otherwise people will probably hate you... :-]
> >
> > Cheers,
> >S.
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Treatment of unknown pragmas

2018-10-17 Thread Simon Marlow
On Wed, 17 Oct 2018 at 15:02, Ben Gamari  wrote:

> Simon Marlow  writes:
>
> > Simon - GHC provides some protection against mistyped pragma names, in
> the
> > form of the -Wunrecognised-pragmas warning, but only for {-# ... #-}
> > pragmas. If tools decide to use their own pragma syntax, they don't
> benefit
> > from this. That's one downside, in addition to the others that Neil
> > mentioned.
> >
> > You might say we shouldn't care about mistyped pragma names. If the user
> > accidentally writes {- HLNIT -} and it is silently ignored, that's not
> our
> > problem. OK, but we cared about it enough for the pragmas that GHC
> > understands to add the special warning, and it's reasonable to expect
> that
> > HLint users also care about it.
> >
> If this is the case then in my opinion HLint should be the one that
> checks for mis-spelling.


But there's no way that HLint can know what is a misspelled pragma name.

If we look beyond HLint, there is no way that
> GHC could know generally what tokens are misspelled pragmas and which
> are tool names.
>

Well this is the problem we created by adding -Wunrecognised-pragmas :)
Now GHC has to know what all the correctly-spelled pragma names are, and
the HLint diff is just following this path.

Arguably -Wunrecognised-pragmas is ill-conceived.  I'm surprised we didn't
have this discussion when it was added (or maybe we did?). But since we
have it, it comes with an obligation to have a centralised registry of
pragma names, which is currently in GHC. (it doesn't have to be in the
source code, of course)

I'm trying to view the pragma question from the perspective of setting a
> precedent for other tools. If a dozen Haskell tools were to approach us
> tomorrow and ask for similar treatment to HLint it's clear that
> hardcoding pragma lists in the lexer would be unsustainable.
>
> Is this likely to happen? Of course not. However, it is an indication to
> me that the root cause of this current debate is our lack of a good
> extensible pragmas. It seems to me that introducing a tool pragma
> convention, from which tool users can claim namespaces at will, is the
> right way to fix this.
>

And sacrifice checking for misspelled pragma names in those namespaces?
Sure we can say {-# TOOL FOO .. #-} is ignored by GHC, but then nothing wil
notice if you say {-# TOOL HLNIT ... #-} by mistake.  If we decide to do
that then fine, it just seems like an inconsistent design.

Cheers
Simon


>
> Cheers,
>
> - Ben
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Treatment of unknown pragmas

2018-10-17 Thread Simon Marlow
Simon - GHC provides some protection against mistyped pragma names, in the
form of the -Wunrecognised-pragmas warning, but only for {-# ... #-}
pragmas. If tools decide to use their own pragma syntax, they don't benefit
from this. That's one downside, in addition to the others that Neil
mentioned.

You might say we shouldn't care about mistyped pragma names. If the user
accidentally writes {- HLNIT -} and it is silently ignored, that's not our
problem. OK, but we cared about it enough for the pragmas that GHC
understands to add the special warning, and it's reasonable to expect that
HLint users also care about it.

(personally I have no stance on whether we should have this warning, there
are upsides and downsides. But that's where we are now.)

Cheers
Simon

On Tue, 16 Oct 2018 at 23:34, Simon Peyton Jones 
wrote:

> I’m still not understanding what’s wrong with
>
>
>
> {- HLINT blah blah -}
>
>
>
> GHC will ignore it.  HLint can look at it.  Simple.
>
>
>
> I must be missing something obvious.
>
>
>
> Simon
>
>
>
> *From:* ghc-devs  *On Behalf Of *Simon
> Marlow
> *Sent:* 16 October 2018 21:44
> *To:* Neil Mitchell 
> *Cc:* ghc-devs 
> *Subject:* Re: Treatment of unknown pragmas
>
>
>
> I suggested to Neil that he add the {-# HLINT #-} pragma to GHC. It seemed
> like the least worst option taking into account the various issues that
> have already been described in this thread. I'm OK with adding HLINT; after
> all we already ignore OPTIONS_HADDOCK, OPTIONS_NHC98, a bunch of other
> OPTIONS, CFILES (a Hugs relic), and several more that GHC ignores.
>
>
>
> We can either
>
> (a) not protect people from mistyped pragmas, or
>
> (b) protect people from mistyped pragma names, but then we have to bake in
> the set of known pragmas
>
>
>
> We could choose to have a different convention for pragmas that GHC
> doesn't know about (as Ben suggests), but then of course we don't get any
> protection for mistyped pragma names when using that convention.
>
>
>
> Cheers
>
> Simon
>
>
>
>
>
> On Tue, 16 Oct 2018 at 21:12, Neil Mitchell  wrote:
>
> > A warning flag is an interesting way to deal with the issue. On the
> > other hand, it's not great from an ergonomic perspective; afterall, this
> > would mean that all users of HLint (and any other tool requiring special
>
> Yep, this means every HLint user has to do an extra thing. I (the
> HLint author) now have a whole pile of "how do I disable warnings in
> Stack", and "what's the equivalent of this in Nix". Personally, it ups
> the support level significantly that I wouldn't go this route.
>
> I think it might be a useful feature in general, as new tools could
> use the flag to prototype new types of warning, but I imagine once a
> feature gets popular it becomes too much fuss.
>
> > > I think it makes a lot of sense to have a standard way for
> third-parties
> > > to attach string-y information to Haskell source constructs. While it's
> > > not strictly speaking necessary to standardize the syntax, doing
> > > so minimizes the chance that tools overlap and hopefully reduces
> > > the language ecosystem learning curve.
> >
> > This sounds exactly like the existing ANN pragma, which is what I've
> wanted LiquidHaskell to move towards for a long time. What is wrong with
> using the ANN pragma?
>
> Significant compilation performance penalty and extra recompilation.
> ANN pragmas is what HLint currently uses.
>
> >  I'm a bit skeptical of this idea. Afterall, adding cases to the
> > lexer for every tool that wants a pragma seems quite unsustainable.
>
> I don't find this argument that convincing. Given the list already
> includes CATCH and DERIVE, the bar can't have been _that_ high to
> entry. And yet, the list remains pretty short. My guess is the demand
> is pretty low - we're just whitelisting a handful of additional words
> that aren't misspellings.
>
> Thanks, Neil
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> <https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs=02%7C01%7Csimonpj%40microsoft.com%7Cdb8a204f9dad40d006c208d633a82851%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636753194654711612=YkmmZJVadGOaWzWtSRQf18D058PdEhj8IiGwF%2B%2BGZFs%3D=0>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Why align all pinned array payloads on 16 bytes?

2018-10-16 Thread Simon Marlow
I vaguely recall that this was because 16 byte alignment is the minimum you
need for certain foreign types, and it's what malloc() does.  Perhaps check
the FFI spec and the guarantees that mallocForeignPtrBytes and friends
provide?

Cheers
Simon

On Thu, 11 Oct 2018 at 18:44, Ömer Sinan Ağacan 
wrote:

> Hi,
>
> I just found out we currently align all pinned array payloads to 16 bytes
> and
> I'm wondering why. I don't see any comments/notes on this, and it's also
> not
> part of the primop documentation. We also have another primop for aligned
> allocation: newAlignedPinnedByteArray#. Given that alignment behavior of
> newPinnedByteArray# is not documented and we have another one for aligned
> allocation, perhaps we can remove alignment in newPinnedByteArray#.
>
> Does anyone remember what was the motivation for always aligning pinned
> arrays?
>
> Thanks
>
> Ömer
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Parser.y rewrite with parser combinators

2018-10-16 Thread Simon Marlow
I personally love to hack things up with parser combinators, but for
anything longer term where I want a degree of confidence that changes
aren't going to introduce new problems I'd still use Happy. Yes it's a
total pain sometimes, and LALR(1) is very restrictive, but I wouldn't want
to lose the guarantees of unambiguity and performance. We have *always* had
to shoehorn the Haskell grammar into LALR(1) - patterns and expressions had
to be parsed using the same grammar fragment from the start due to the list
comprehension syntax. And some post-processing is inevitable - it's
technically not possible to parse Haskell without rearranging infix
expressions later, because you don't know the fixities of imported
operators.  And layout is truly horrible to deal with - Happy's error token
is designed purely to handle the layout rule, and it differs in semantics
from yacc's error token for this reason (that is, if yacc's error token has
a semantics, I could never figure out what it was supposed to do). Dealing
with layout using parser combinators would probably require at least one
layer of backtracking in addition to whatever other backtracking you needed
to handle the other parts of the grammar.

Cheers
Simon


On Tue, 9 Oct 2018 at 15:18, Sven Panne  wrote:

> Am Di., 9. Okt. 2018 um 15:45 Uhr schrieb Richard Eisenberg <
> r...@cs.brynmawr.edu>:
>
>> [...] What I'm trying to say here is that tracking the backtracking level
>> in types doesn't seem like it will fly (tempting though it may be).
>>
>
> ... and even if it did fly, parser combinators with backtracking have a
> strong tendency to introduce space leaks: To backtrack, you have too keep
> previous input somehow, at least up to some point. So to keep the memory
> requirements sane, you have to explicitly commit to one parse or another at
> some point. Different combinator libraries have different ways to do that,
> but you have to do that by hand somehow, and that's where the beauty and
> maintainability of the combinator approach really suffers.
>
> Note that I'm not against parser combinators, far from it, but I don't
> think they are necessarily the right tool for the problem at hand. The
> basic problem is: Haskell's syntax, especially with all those extensions,
> is quite tricky, and this will be reflected in any parser for it. IMHO a
> parser generator is the lesser evil here, at least it points you to the
> ugly places of your language (on a syntactic level). If Haskell had a few
> more syntactic hints, reading code would be easier, not only for a
> compiler, but (more importantly) for humans, too. Richard's code snippet is
> a good example where some hint would be very useful for the casual reader,
> in some sense humans have to "backtrack", too, when reading such code.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Treatment of unknown pragmas

2018-10-16 Thread Simon Marlow
I suggested to Neil that he add the {-# HLINT #-} pragma to GHC. It seemed
like the least worst option taking into account the various issues that
have already been described in this thread. I'm OK with adding HLINT; after
all we already ignore OPTIONS_HADDOCK, OPTIONS_NHC98, a bunch of other
OPTIONS, CFILES (a Hugs relic), and several more that GHC ignores.

We can either
(a) not protect people from mistyped pragmas, or
(b) protect people from mistyped pragma names, but then we have to bake in
the set of known pragmas

We could choose to have a different convention for pragmas that GHC doesn't
know about (as Ben suggests), but then of course we don't get any
protection for mistyped pragma names when using that convention.

Cheers
Simon


On Tue, 16 Oct 2018 at 21:12, Neil Mitchell  wrote:

> > A warning flag is an interesting way to deal with the issue. On the
> > other hand, it's not great from an ergonomic perspective; afterall, this
> > would mean that all users of HLint (and any other tool requiring special
>
> Yep, this means every HLint user has to do an extra thing. I (the
> HLint author) now have a whole pile of "how do I disable warnings in
> Stack", and "what's the equivalent of this in Nix". Personally, it ups
> the support level significantly that I wouldn't go this route.
>
> I think it might be a useful feature in general, as new tools could
> use the flag to prototype new types of warning, but I imagine once a
> feature gets popular it becomes too much fuss.
>
> > > I think it makes a lot of sense to have a standard way for
> third-parties
> > > to attach string-y information to Haskell source constructs. While it's
> > > not strictly speaking necessary to standardize the syntax, doing
> > > so minimizes the chance that tools overlap and hopefully reduces
> > > the language ecosystem learning curve.
> >
> > This sounds exactly like the existing ANN pragma, which is what I've
> wanted LiquidHaskell to move towards for a long time. What is wrong with
> using the ANN pragma?
>
> Significant compilation performance penalty and extra recompilation.
> ANN pragmas is what HLint currently uses.
>
> >  I'm a bit skeptical of this idea. Afterall, adding cases to the
> > lexer for every tool that wants a pragma seems quite unsustainable.
>
> I don't find this argument that convincing. Given the list already
> includes CATCH and DERIVE, the bar can't have been _that_ high to
> entry. And yet, the list remains pretty short. My guess is the demand
> is pretty low - we're just whitelisting a handful of additional words
> that aren't misspellings.
>
> Thanks, Neil
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Phabricator workflow vs. GitHub

2018-10-06 Thread Simon Marlow
On Fri, 5 Oct 2018 at 15:22, Niklas Hambüchen  wrote:

> > I think the article is assuming the base for `arc diff` is always the
> parent revision, i.e. `arc diff HEAD^`, which is how the workflow works
> best. Strangely I don't think the open source Phabricator is set up to do
> this by default so you have to actually type `arc diff HEAD^`
>
> Perhaps that is exactly to address the problem in my example:
> If you submit a patch B that depends on A, by default this patch will fail
> to apply against master on the Phabricator side unless you manually set up
> dependencies? I suppose this is why it defaults to submitting the whole
> master-A-B history instead?
>
> > for now manually specifying the dependencies is not terrible.
>
> I have found it pretty terrible:
> Setting up dependencies between commits by hand is time consuming, and you
> can do it wrong, which easily leads to confusion.
>
> If I do 4 refactor commits and on top a new feature that needs them, why
> should I have to manually click together the dependencies between those
> commits? The whole point of git is that it tracks that already for me in
> its DAG.
>
> It gets worse if I have to react to review feedback:
>
> Say Ben tells me in review that I should really squash commits 2 and 3
> because they don't work independent of each other. Easily done with `git
> rebase -i` as suggested, but now I have to go and reflect what I just did
> in version control by manual clicking in an external tool again (and I
> better kick out the right Diff).
>
> Similarly, if want to rename all occurrences of my_var to myVar across my
> 5 commits using rebase -i, I have to manually invoke the right arc
> invocation after each commit.
>
> So I've found it a big pain to maintain a series of dependent commits with
> this workflow.
>
> I can imagine this to be only painless if you have access to the tooling
> you said you have at facebook, that automates these things for you.
>

In fact we did it manually for a long time, the tool support is a recent
development. Tool support can always improve things, but I'll take the
inconvenience of having to specify dependencies manually in exchange for
the other benefits of stacked diffs. You can put the dependencies in the
commit log using "Depends on: D1234", as an alternative to the UI.

'git rebase -i' with 'x arc diff HEAD^ -m rebase' is a nice trick for
rebasing your stack.

Cheers
Simon


> In my ideal world, it should work like this:
>
> * Locally, a series of dependent patches goes into a git branch.
> * Branches that are dependent on each other are based on each other.
> * You have a tool that, if you amend a commit in a branch, can rebase all
> the dependent branches accordingly.
> * You can tell `arc` to submit a whole branch, and it will automatically
> upload all dependent branches and set up the Phabricator dependency
> relationships for you.
> * When you react to review feedback, you change your history locally, and
> run an `arc upload-changes`, that automatically updates all Diffs
> accordingly.
>
> Niklas
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Phabricator workflow vs. GitHub

2018-10-05 Thread Simon Marlow
I think the article is assuming the base for `arc diff` is always the
parent revision, i.e. `arc diff HEAD^`, which is how the workflow works
best. Strangely I don't think the open source Phabricator is set up to do
this by default so you have to actually type `arc diff HEAD^` (there's
probably some setting somewhere so that you can make this the default).

On the diff in Phabricator you can enter the dependencies manually. Really
the tooling ought to do this for you (and at Facebook our internal tooling
does do this) but for now manually specifying the dependencies is not
terrible. Then Phabricator shows you the nice dependency tree in the UI, so
you can see the state of all of your diffs in the stack.

Cheers
Simon

On Fri, 5 Oct 2018 at 04:30, Niklas Hambüchen  wrote:

> There are some things in these argumentations that I don't get.
>
> When you have a stack of commits on top of master, like:
>
> * C
> |
> * B
> |
> * A
> |
> * master
>
> What do you use as base for `arc diff` for each of them?
>
> If B depends on A (the patch expressed by B doesn't apply if A was applied
> first),
> do you still use master as a base for B, or do you use Phabricator's
> feature to have diffs depend on other diffs?
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: nofib oldest GHC to support?

2018-10-04 Thread Simon Marlow
Typically I never remove any support for older compilers in nofib and the
nofib-analyze tool, I just add support for new things. I realise we don't
continuously test any of those old versions and thus they can bitrot, but
in my experience so far it doesn't happen very often, and it's sometimes
really useful to be able to use older versions.

Why did it break with 7.10.3? Can that be fixed?

I guess we could remove the Gofer support though :)

In the list of regrexes you pointed to, don't you just need to add one more
to support the new format? It would be nice if those regexes had comments
to explain which version they were added for, I guess we could start doing
that from now on.

Cheers
Simon


On Mon, 1 Oct 2018 at 09:05, Ömer Sinan Ağacan  wrote:

> We currently claim to support GOFER and GHC 4.02! Surely we can drop some
> of
> those support.
>
> I just tried booting nofib with GHC 7.10.3 and it failed. We don't even
> support
> 7.10.3, but we still have code to support ... 4.02!
>
> The desire to cleanup is not because removing code is fun, it's because it
> makes it easier to maintain. Currently I need to parse another variant of
> `+RTS
> -t` output, and I have to deal with this mess for it:
>
>
> https://github.com/ghc/nofib/blob/a80baacfc29cc2e7ed50e94f3cd2648d11b1d7d5/nofib-analyse/Slurp.hs#L153-L207
>
> (note that all of these need to be updated to add one more field)
>
> If we decide on what versions to support we could remove most of those (I
> doubt
> `+RTS -t` output changes too much, so maybe we can even remove all but
> one).
>
> There are also other code with CPP macros for GOFER etc.
>
> I suggest supporting HEAD + 3 major releases. In this plan currently we
> should
> be able to run nofib with GHC HEAD, 8.6, 8.4, and 8.2. Then setting up a
> CI to
> test nofib with these configurations should be trivial (except for GHC HEAD
> maybe, I don't know if we're publishing GHC HEAD bindists for CI servers to
> use).
>
> Ömer
> Joachim Breitner , 1 Eki 2018 Pzt, 03:33
> tarihinde şunu yazdı:
> >
> > Hi,
> >
> > there is no policy that I am aware of, but being able to run nofib on
> > old (or even ancient) versions of GHC is likely to make someone happy
> > in the future, so I’d say that the (valid!) desire to cleanup is not a
> > good reason to drop support – only if it would require unreasonable
> > efforts should we drop old versions there.
> >
> > Cheers,
> > Joachim
> >
> > Am Sonntag, den 30.09.2018, 14:18 +0300 schrieb Ömer Sinan Ağacan:
> > > Do we have a policy on the oldest GHC to support in nofib? I'm
> currently doing
> > > some hacking on nofib to parse some new info printed by a modified
> GHC, and I
> > > think we can do a lot of cleaning (at the very least remove some
> regexes and
> > > parsers) if we decide on which GHCs to support.
> > >
> > > I checked the README and RunningNoFib wiki page but couldn't see
> anything
> > > relevant.
> > >
> > > Thanks
> > >
> > > Ömer
> > > ___
> > > ghc-devs mailing list
> > > ghc-devs@haskell.org
> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> > --
> > Joachim Breitner
> >   m...@joachim-breitner.de
> >   http://www.joachim-breitner.de/
> >
> > ___
> > ghc-devs mailing list
> > ghc-devs@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Phabricator workflow vs. GitHub

2018-10-03 Thread Simon Marlow
Here's an interesting blog post relevant to previous discussions about
Phabricator / GitHub:
https://jg.gg/2018/09/29/stacked-diffs-versus-pull-requests/?fbclid=IwAR3JyQP5uCn6ENiHOTWd41y5D-U0_CCJ55_23nzKeUYTjgLASHu2dq5QCc0

Yes it's a decidedly pro-Phabricator rant, but it does go into a lot of
details about why the Phabricator workflow is productive, and might be
useful to those who struggle to get to grips with it coming from GitHub.

Cheers
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Stable name allocation

2018-09-27 Thread Simon Marlow
On Wed, 26 Sep 2018 at 10:54, David Feuer  wrote:

> Simon seems a bit busy right now. Can anyone else advise me on the
> basics of heap allocation in primops?
>
> On Tue, Sep 25, 2018 at 1:42 PM, David Feuer 
> wrote:
> > Let's forget about allocate(). I can definitely handle this part in
> > C--. But I'm still lost in the macros and such. For example, I'm very
> > unclear on the differences among the ALLOC, HP_CHK, and MAYBE_GC
> > classes of macro. I can't find anything in the commentary, and the
> > source code documentation is very sparse. I'm okay with either of the
> > following approaches, but either way I need a bit more info.
>

The best way to understand these macros is to look at their implementations
and see how they're used in other parts of the RTS.  MAYBE_GC doesn't bump
Hp, it is used to ensure that we don't indefinitely call allocate() in
primops that use it.  The ALLOC family are wrappers around the lower level
HP_CHK functions, these bump Hp. Some of the variations are optimisations
to generate less verbose code - again, see the other primops for examples.
It's always safe to use HP_CHK_GEN_TICKY(), but there might be better
alternatives depending on the type of your primitive.

Cheers
Simon


> > 1. First see if we need to allocate a StableName#. If so, check
> > whether GC would be required to allocate the StableName# (how?). If
> > so, drop the lock, run GC (how?) and start over. This looks cleanest
> > to me if it can be done easily.
> >
> > 2. First run the GC if we're low on memory (how?). Then if we need to
> > allocate a StableName#, we'll be sure to have room.
> >
> >
> > On Tue, Sep 25, 2018 at 6:25 AM, Simon Marlow 
> wrote:
> >> You can do it unconditionally before taking the lock, or you can do it
> >> conditionally as long as you release the lock if the heap check fails. I
> >> think in the latter case there might not be a macro that allows this,
> but
> >> you could use the `allocate()` method for allocating memory (like
> >> newByteArray#) and then you could write a heap check like the MAYBE_GC()
> >> macro. Doing it unconditionally is easier and probably not a big
> performance
> >> hit, but note that you'll have to retreat Hp if you don't use the
> memory.
> >>
> >> Cheers
> >> Simon
> >>
> >> On Sat, 22 Sep 2018 at 13:08, David Feuer 
> wrote:
> >>>
> >>> How do I check if GC will be required, and how do I trigger it? Should
> I
> >>> perform the check unconditionally at the beginning of the operation so
> I
> >>> don't have to drop the lock, GC, then retake? I don't know the right
> ways to
> >>> deal with this stuff, and the macros are mostly undocumented.
> >>>
> >>> On Sep 22, 2018 3:53 AM, "Simon Marlow"  wrote:
> >>>
> >>> Yes, the current implementation looks like it creates the object after
> >>> adding the entry to the StableName table and releasing the lock, which
> is
> >>> unsafe because another thread could read that same entry before the
> object
> >>> has been created.  The easiest solution to that is to take and release
> the
> >>> lock in C-- in the right places instead of in the C lookupStableName()
> >>> function (you might need to make a separate version of
> lookupStableName()
> >>> that doesn't take the lock).
> >>>
> >>> Cheers
> >>> Simon
> >>>
> >>>
> >>> On Fri, 21 Sep 2018 at 12:53, David Feuer 
> wrote:
> >>>>
> >>>> It seems awkward to do it in C--, but maybe you can help me work out
> how.
> >>>> The allocation facilities definitely seem much nicer there, and
> allocating a
> >>>> small heap object in C feels like an abuse of the facilities we have
> there.
> >>>> The essential challenge, as I see it, is that we need the key to
> point to a
> >>>> valid stable name object by the time we drop the hash table lock. The
> >>>> process, as I imagine it:
> >>>>
> >>>> 1. Follow indirections, untag, choose the right generation. (All this
> is
> >>>> in C)
> >>>> 2. Take the appropriate hash table lock. (C)
> >>>> 3. Look up the key in the hash table (C).
> >>>>
> >>>> Now there's a branch. If we found the key, then we don't need to
> allocate
> >>>> an SNO. We just drop the lock and return. Otherwise
> >>>>
> >>>> 4. Allocate an SNO and set its info pointer 

Re: isAlive() too conservative -- does it cause leaks?

2018-07-19 Thread Simon Marlow
On 19 July 2018 at 11:09, Ömer Sinan Ağacan  wrote:

> Hi Simon,
>
> Currently isAlive considers all static closures as being alive. The code:
>
> // ignore static closures
> //
> // ToDo: This means we never look through IND_STATIC, which means
> // isRetainer needs to handle the IND_STATIC case rather than
> // raising an error.
> //
> // ToDo: for static closures, check the static link field.
> // Problem here is that we sometimes don't set the link field, eg.
> // for static closures with an empty SRT or CONSTR_NOCAFs.
> //
> if (!HEAP_ALLOCED_GC(q)) {
> return p;
> }
>
> I'd expect this to cause leaks when e.g. key of a WEAK is a static object.
> Is
> this not the case?


Correct, I believe weak pointers to static objects don't work (not sure if
there's a ticket for this, but if not there should be).

I think this is easy to fix but I may be missing something
> and wanted to ask before investing into it. The idea:
>
> - Evacuate all static objects in evacuate() (including the ones with no
> SRTs)
>   (assuming all static objects have a STATIC_FIELD, is this really the
> case?)
>

This would be expensive. We deliberately don't touch the static objects in
a minor GC because it adds potentially tens of ms to the GC time, and the
optimisation to avoid evacuating the static objects with no SRTs is an
important one.

Cheers
Simon

- In isAlive() check if (STATIC_FIELD & static_flag) != 0. If it is then the
>   object is alive.
>
> Am I missing anything?
>
> Thanks,
>
> Ömer
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Write barrier for stack updates?

2018-07-18 Thread Simon Marlow
Hi Ömer,

The write barrier is the function `dirty_STACK()` here:
https://phabricator.haskell.org/diffusion/GHC/browse/master/rts%2Fsm%2FStorage.c$1133-1140

If you grep for `dirty_STACK` you'll see it being called everywhere we
mutate a STACK, in particular in the scheduler just before running a
thread:
https://phabricator.haskell.org/diffusion/GHC/browse/master/rts%2FSchedule.c$412

We don't call the write barrier in the code generator or from primops,
because at that point the thread is already running and has already been
marked dirty. If we GC and mark the stack clean, then it will be marked
dirty again by the scheduler before we start running it.

Cheers
Simon

On 17 July 2018 at 20:45, Ömer Sinan Ağacan  wrote:

> Hi Simon,
>
> I'm a bit confused about stack updates in generated code and write
> barriers.
> Because stacks are mutable (we push new stuff or maybe even update existing
> frames?) it seems to me that we need one these two, similar to other
> mutable
> objects:
>
> - Always keep all stacks in mut_lists
> - Add write barriers before updates
>
> However looking at some of the primops like catch# and the code generator
> that
> generates code that pushes update frames I can't see any write barriers
> and the
> GC doesn't always add stacks to mut_lists (unlike e.g. MUT_ARR_PTRS). I
> also
> thought maybe we add a stack to a mut_list when we switch to the TSO that
> owns
> it or we park the TSO, but I don't see anything relevant in Schedule.c or
> ThreadPaused.c. So I'm lost. Could you say a few words about how we deal
> with
> mutated stacks in the GC, so that if an old stack points to a young object
> we
> don't collect the young object in a minor GC?
>
> Thanks,
>
> Ömer
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Scavenging SRTs in scavenge_one

2018-06-21 Thread Simon Marlow
When scavenge_one() sees a STACK, it calls scavenge_stack() which traverses
the stack frames, including their SRTs.

So I don't understand what's going wrong for you - how are the SRTs not
being traversed?

Cheers
Simon

On 21 June 2018 at 11:58, Ömer Sinan Ağacan  wrote:

> Here's an example where we allocate a large (4K) stack:
>
> >>> bt
> #0  allocateMightFail (cap=0x7f366808cfc0 ,
> n=4096) at rts/sm/Storage.c:876
> #1  0x7f3667e4a85d in allocate (cap=0x7f366808cfc0
> , n=4096) at rts/sm/Storage.c:849
> #2  0x7f3667e16f46 in threadStackOverflow (cap=0x7f366808cfc0
> , tso=0x4200152a68) at rts/Threads.c:600
> #3  0x7f3667e12a64 in schedule
> (initialCapability=0x7f366808cfc0 , task=0x78c970) at
> rts/Schedule.c:520
> #4  0x7f3667e1215f in scheduleWaitThread (tso=0x4200105388,
> ret=0x0, pcap=0x7ffef40dce78) at rts/Schedule.c:2533
> #5  0x7f3667e25685 in rts_evalLazyIO (cap=0x7ffef40dce78,
> p=0x736ef8, ret=0x0) at rts/RtsAPI.c:530
> #6  0x7f3667e25f7a in hs_main (argc=16, argv=0x7ffef40dd0a8,
> main_closure=0x736ef8, rts_config=...) t rts/RtsMain.c:72
> #7  0x004f738f in main ()
>
> This is based on an old tree so source locations may not be correct, it's
> this
> code in threadStackOverflow():
>
> // Charge the current thread for allocating stack.  Stack usage is
> // non-deterministic, because the chunk boundaries might vary from
> // run to run, but accounting for this is better than not
> // accounting for it, since a deep recursion will otherwise not be
> // subject to allocation limits.
> cap->r.rCurrentTSO = tso;
> new_stack = (StgStack*) allocate(cap, chunk_size);
> cap->r.rCurrentTSO = NULL;
>
> SET_HDR(new_stack, _STACK_info, old_stack->header.prof.ccs);
> TICK_ALLOC_STACK(chunk_size);
>
> Ömer
> Ömer Sinan Ağacan , 21 Haz 2018 Per, 13:42
> tarihinde şunu yazdı:
> >
> > > Large objects can only be primitive objects, like MUT_ARR_PTRS,
> allocated by
> > > the RTS, and none of these have SRTs.
> >
> > Is is not possible to allocate a large STACK? I'm currently observing
> this in
> > gdb:
> >
> > >>> call *Bdescr(0x4200ec9000)
> > $2 = {
> >   start = 0x4200ec9000,
> >   free = 0x4200ed1000,
> >   link = 0x4200100e80,
> >   u = {
> > back = 0x4200103980,
> > bitmap = 0x4200103980,
> > scan = 0x4200103980
> >   },
> >   gen = 0x77b4b8,
> >   gen_no = 1,
> >   dest_no = 1,
> >   node = 0,
> >   flags = 1027, <-- BF_LARGE | BF_EVACUTED | ...
> >   blocks = 8,
> >   _padding = {[0] = 0, [1] = 0, [2] = 0}
> > }
> >
> > >>> call printClosure(0x4200ec9000)
> > 0x4200ec9000: STACK
> >
> > >>> call checkClosure(0x4200ec9000)
> > $3 = 4096 -- makes sense, larger than 3277 bytes
> >
> > So I have a large STACK object, and STACKs can refer to static objects.
> But
> > when we scavenge this object we don't scavenge its SRTs because we use
> > scavenge_one(). This seems wrong to me.
> >
> > Ömer
> >
> > Simon Marlow , 20 Haz 2018 Çar, 14:32 tarihinde
> şunu yazdı:
> > >
> > > Interesting point. I don't think there are any large objects with
> SRTs, but we should document the invariant because we're relying on it.
> > >
> > > Large objects can only be primitive objects, like MUT_ARR_PTRS,
> allocated by the RTS, and none of these have SRTs.
> > >
> > > We did have plans to allocate memory for large dynamic objects using
> `allocate()` from compiled code, in which case we could have large objects
> that could be THUNK, FUN, etc. and could have an SRT, in which case we
> would need to revisit this.  You might want to take a look at Note [big
> objects] in GCUtils.c, which is relevant here.
> > >
> > > Cheers
> > > Simon
> > >
> > >
> > > On 20 June 2018 at 09:20, Ömer Sinan Ağacan 
> wrote:
> > >>
> > >> Hi Simon,
> > >>
> > >> I'm confused about this code again. You said
> > >>
> > >> > scavenge_one() is only used for a non-major collection, where we
> aren't
> > >> > traversing SRTs.
> > >>
> > >> But I think this is not true; scavenge_one() is also used to scavenge
> large
> > >> objects (in scavenge_large()), which are scavenged even in major GCs.
> So it
> > >> seems like we never really scavenge SRTs of large object

Re: Loading GHC into GHCi (and ghcid)

2018-06-08 Thread Simon Marlow
On 8 June 2018 at 19:18, Evan Laforge  wrote:

> On Fri, Jun 8, 2018 at 12:29 AM, Simon Marlow  wrote:
> > heap profiler for a while. However, I imagine at some point loading
> > everything into GHCi will become unsustainable and we'll have to explore
> > other strategies. There are a couple of options here:
> > - pre-compile modules so that GHCi is loading the .o instead of
> interpreted
> > code
>
> This is what I do, which is why I was complaining about GHC tending to
> break it.  But when it's working, it works well, I load 500+ modules
> in under a second.
>
> > - move some of the code into pre-compiled packages, as you mentioned
>
> I was wondering about the tradeoffs between these two approaches,
> compiled modules vs. packages. Compiled modules have the advantage
> that you can reload without restarting ghci and relinking a large
> library, but no one seems to notice when they break.  Whereas if ghc
> broke package loading it would get noticed right away.  Could they be
> unified so that, say, -package xyz is equivalent to adding the package
> root (with all the .hi and .o files) to the -i list?  I guess the low
> level loading mechanism of loading a .so vs. a bunch of individual .o
> files is different.
>

I'm slightly surprised that it keeps breaking for you, given that this is a
core feature of GHCi and we have multiple tests for it.  You'll need to
remind me - what were the bugs specifically? Maybe we need more tests.

There really are fundamental differences in how the compiler treats these
two methods though, and I don't see an easy way to reconcile them. Loading
object files happens as part of the compilation manager that manages the
compilations for all the modules in the current package, whereas packages
are assumed to be pre-compiled and are linked on-demand after all the
compilation is done.

Cheers
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Loading GHC into GHCi (and ghcid)

2018-06-08 Thread Simon Marlow
On 7 June 2018 at 22:25, Evan Laforge  wrote:

> On Thu, Jun 7, 2018 at 1:47 PM, Simon Marlow  wrote:
> > For loading large amounts of code into GHCi, you want to add -j +RTS
> > -A128m where  is the number of cores on your machine. We've found that
> > parallel compilation works really well in GHCi provided you use a nice
> large
> > allocation area for the GC. This dramatically speeds up working with
> large
> > numbers of modules in GHCi. (500 is small!)
>
> This is a bit of a thread hijack (feel free to change the subject),
> but I also have a workflow that involves loading a lot of modules in
> ghci (500-700).  As long as I can coax ghci to load them, things are
> fast and work well, but my impression is that this isn't a common
> workflow, and specifically ghc developers don't do this, because just
> about every ghc release will break it in one way or another (e.g. by
> putting more flags in the recompile check hash), and no one seems to
> understand what I'm talking about when I suggest features to improve
> it (e.g. the recent msg about modtime and recompilation avoidance).
>
> Given the uphill battle, I've been thinking that linking most of those
> modules into a package and loading much fewer will be a better
> supported workflow.  It's actually less convenient, because now it's
> divided between package level (which require a restart and relink if
> they change) and ghci level (which don't), but is maybe less likely to
> be broken by ghc changes.  Also, all those loaded module consume a
> huge amount of memory, which I haven't tracked down yet, but maybe
> packages will load more efficiently.
>
> But ideally I would prefer to continue to not use packages, and in
> fact do per-module more aggressively for larger codebases, because the
> need to restart ghci (or the ghc API-using program) and do a lengthy
> relink every time a module in the "wrong place" changed seems like it
> could get annoying (in fact it already is, for a cabal-oriented
> workflow).
>
> Does the workflow at Facebook involve loading tons of individual
> modules as I do?


Yes, our workflow involves loading a large number of modules into GHCi.
However, we have run into memory issues, which was the reason for the
recent work on fixing this space leak: https://phabricator.haskell.org/D4659

As it is, this workflow is OK thanks to Bartosz' work on speedups for large
numbers of modules, tweaking the RTS flags as I mentioned and some other
fixes we've made in GHCi to avoid performance issues. (all of this is
upstream, incidentally).  There is probably low-hanging fruit to be had in
reducing the memory usage of GHCi, nobody has really attacked this with the
heap profiler for a while. However, I imagine at some point loading
everything into GHCi will become unsustainable and we'll have to explore
other strategies. There are a couple of options here:
- pre-compile modules so that GHCi is loading the .o instead of interpreted
code
- move some of the code into pre-compiled packages, as you mentioned

Cheers
Simon


>
> Or do they get packed into packages?  If it's the
> many modules, do you have recommendations making that work well and
> keeping it working?  If packages are the way you're "supposed" to do
> things, then is there any idea about how hard it would be to reload
> packages at runtime?  If both modules and packages can be reloaded, is
> there an intended conceptual difference between a package and an
> unpackaged collection of modules?  To illustrate, I would put packages
> purely as a way to organize builds and distribution, and have no
> meaning at the compiler level, which is how I gather C compilers
> traditionally work (e.g. 'cc a.o b.o c.o' is the same as 'ar abc.a a.o
> b.o c.o; cc abc.a').  But that's clearly not how ghc sees it!
>
>
> thanks!
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Loading GHC into GHCi (and ghcid)

2018-06-08 Thread Simon Marlow
On 8 June 2018 at 00:33, Evan Laforge  wrote:

> On Thu, Jun 7, 2018 at 2:48 PM, Bartosz Nitka  wrote:
> > What version of GHC are you using?
> > There have been some significant improvements like
> > https://phabricator.haskell.org/rGHCb8fec6950ad99cbf11cd22698b
> 8d5ab35afb828f,
> > that only just made it into GHC 8.4.
>
> I did in fact notice a very nice speedup in 8.4, this explains it.
> Finally I know who to thank for it!  Thank you very much for that fix,
> it really makes a difference.
>
> Are there more goodies in the 8.0.2 facebook branch, or have they all
> made it into 8.4?
>
> As loaded modules seem to consume a lot of memory, I've considered
> trying GHC.Compact on them, but haven't looked into what that would
> entail.  Have you considered something like that?
>

I think I looked into this and found that it wasn't going to be easy, but I
forget exactly why. Off the top of my head:
- you can't compact mutable things: perhaps the FastString table would give
us problems here
- there is lots of deliberate laziness to support demand-loading of
interface files, compaction would force all of it
- you can't compact functions, so if there are any functions in ModIface or
ModDetails we would have to avoid compacting those parts of the structure
somehow
- there are cycles and sharing in these structures so we would need to use
the more expensive compaction method that keeps a hash table, which is 10x
slower than cheap compaction

Probably worth looking into to find out exactly what the problems are
though.

Cheers
Simon





> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Why do we prevent static archives from being loaded when DYNAMIC_GHC_PROGRAMS=YES?

2018-06-07 Thread Simon Marlow
There's a technical restriction. The static code would be compiled with the
small memory model, so it would have 32-bit relocations for external
references, assuming that those references would resolve to something in
the low 2GB of the address space. But we would be trying to link it against
shared libraries which could be loaded anywhere in the address space.

If the static code was compiled with -fPIC then it might be possible, but
there's also the restriction that we wouldn't be able to dlopen() a shared
library that depends on the statically linked code, because the system
linker can't see the symbols that the RTS linker has loaded. GHC doesn't
currently know about this restriction, so it would probably go ahead and
try, and things would break.

Cheers
Simon


On 29 May 2018 at 04:05, Moritz Angermann  wrote:

> Dear friends,
>
> when we build GHC with DYNAMIC_GHC_PROGRAMS=YES, we essentially prevent
> ghc/ghci
> from using archives (.a).  Is there a technical reason behind this?  The
> only
> only reasoning so far I've came across was: insist on using dynamic/shared
> objects,
> because the user said so when building GHC.
>
> In that case, we don't however prevent GHC from building archive (static)
> only
> libraries.  And as a consequence when we later try to build another
> archive of
> a different library, that depends via TH on the former library, GHC will
> bail
> and complain that we don't have the relevant dynamic/shared object.  Of
> course we
> don't we explicitly didn't build it.  But the linker code we have in GHC is
> perfectly capable of loading archives.  So why don't we want to fall back
> to
> archives?
>
> Similarly, as @deech asked on twitter[1], why we prevent GHCi from loading
> static
> libraries?
>
> I'd like to understand the technical reason/rational for this behavior.
> Can
> someone help me out here?  If there is no fundamental reason for this
> behavior,
> I'd like to go ahead and try to lift it.
>
> Thank you!
>
> Cheers,
>  Moritz
>
> ---
> [1]: https://twitter.com/deech/status/1001182709555908608
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Loading GHC into GHCi (and ghcid)

2018-06-07 Thread Simon Marlow
For loading large amounts of code into GHCi, you want to add -j +RTS
-A128m where  is the number of cores on your machine. We've found that
parallel compilation works really well in GHCi provided you use a nice
large allocation area for the GC. This dramatically speeds up working with
large numbers of modules in GHCi. (500 is small!)

Cheers
Simon

On 30 May 2018 at 21:43, Matthew Pickering 
wrote:

> Hi all,
>
> Csongor has informed me that he has worked out how to load GHC into
> GHCi which can then be used with ghcid for a more interactive
> development experience.
>
> 1. Put this .ghci file in compiler/
>
> https://gist.github.com/mpickering/73749e7783f40cc762fec171b879704c
>
> 2. Run "../inplace/bin/ghc-stage2 --interactive -odir tmp -hidir tmp"
> from inside compiler/
>
> It may take a while and require a little bit of memory but in the end
> all 500 or so modules will be loaded.
>
> It can also be used with ghcid.
>
> ghcid -c "../inplace/bin/ghc-stage2 --interactive -odir tmp -hidir tmp"
>
> Hopefully someone who has more RAM than I.
>
> Can anyone suggest the suitable place on the wiki for this information?
>
> Cheers,
>
> Matt
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: revertCAFs and -fexternal-interpreter

2018-06-07 Thread Simon Marlow
Yes, very probably this is a bug.  Please file a ticket and assign to me
(or better still send a diff!).

Cheers
Simon

On 6 June 2018 at 08:58, Rahul Muttineni  wrote:

> Hello devs,
>
> I noticed that in ghc/GHCi/UI.hs, the calls to 'revertCAFs' are made in
> the compiler's RTS instead of the interpreter's RTS. When
> -fexternal-interpreter is on this distinction is visible, otherwise they
> are one and the same so it works as intended.
>
> Shouldn't there be a RevertCAFs data constructor in
> `libraries/ghci/GHCi/Message.hs` to tell the interpreter process to
> revert the CAFs in its heap?
>
> Thanks,
> Rahul Muttineni
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: -fghci-leak-check apparently causes many tests to fail

2018-06-07 Thread Simon Marlow
Sorry, only just saw this. -fghci-leak-check is a new flag I added to
prevent regressions of the space leak that was fixed in
https://phabricator.haskell.org/D4659

If you're seeing errors from this, then we should fix them.  Could you open
a ticket and assign to me please?

Cheers
Simon

On 1 June 2018 at 11:57, Ryan Scott  wrote:

> One thing I forgot to mention is that these test failures only seem to
> occur with the `quick` build flavor, and I couldn't reproduce them with
> ./validate. Is -fghci-leak-check expected to have different behavior if
> stage-2 GHC is built without optimization?
>
> Ryan S.
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Scavenging SRTs in scavenge_one

2018-05-01 Thread Simon Marlow
Your explanation is basically right. scavenge_one() is only used for a
non-major collection, where we aren't traversing SRTs. Admittedly this is a
subtle point that could almost certainly be documented better, I probably
just overlooked it.

More inline:

On 1 May 2018 at 10:26, Ömer Sinan Ağacan  wrote:

> I have an idea but it doesn't explain everything;
>
> SRTs are used to collect CAFs, and CAFs are always added to the oldest
> generation's mut_list when allocated [1].
>
> When we're scavenging a mut_list we know we're not doing a major GC, and
> because mut_list of oldest generation has all the newly allocated CAFs,
> which
> will be scavenged anyway, no need to scavenge SRTs for those.
>
> Also, static objects are always evacuated to the oldest gen [2], so any
> CAFs
> that are alive but not in the mut_list of the oldest gen will stay alive
> after
> a non-major GC, again no need to scavenge SRTs to keep these alive.
>
> This also explains why it's OK to not collect static objects (and not treat
> them as roots) in non-major GCs.
>
> However this doesn't explain
>
> - Why it's OK to scavenge large objects with scavenge_one().
>

I don't understand - perhaps you could elaborate on why you think it might
not be OK? Large objects are treated exactly the same as small objects with
respect to their lifetimes.


> - Why we scavenge SRTs in non-major collections in other places (e.g.
>   scavenge_block()).
>

If you look at scavenge_fun_srt() and co, you'll see that they return
immediately if !major_gc.


> Simon, could you say a few words about this?
>

Was that enough words? I have more if necessary :)

Cheers
Simon



>
> [1]: https://github.com/ghc/ghc/blob/master/rts/sm/Storage.c#L445-L449
> [2]: https://github.com/ghc/ghc/blob/master/rts/sm/Scav.c#L1761-L1763
>
> Ömer
>
> 2018-03-28 17:49 GMT+03:00 Ben Gamari :
> > Hi Simon,
> >
> > I'm a bit confused by scavenge_one; namely it doesn't scavenge SRTs. It
> > appears that it is primarily used for remembered set entries but it's
> > not at all clear why this means that we can safely ignore SRTs (e.g. in
> > the FUN and THUNK cases).
> >
> > Can you shed some light on this?
> >
> > Cheers,
> >
> > - Ben
> >
> > ___
> > ghc-devs mailing list
> > ghc-devs@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Question about indirectees of BLACKHOLE closures

2018-03-26 Thread Simon Marlow
The raise closure is declared to be a THUNK:

https://phabricator.haskell.org/diffusion/GHC/browse/master/rts/Exception.cmm;60e29dc2611f5c1a01cfd9a870841927847a7b74$424

Another example of this is when an asynchronous exception is thrown, and we
update all the thunks/BLACKHOLEs pointed to by the update frames to point
to new thunks (actually AP_STACK closures) representing the frozen state of
evaluation of those thunks.  For this, see rts/RaiseAsync.c.

Cheers
Simon

On 24 March 2018 at 19:27, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:

> Hi Rahul,
>
> I'm still confused. The code that walks the stack and updates UPDATE_FRAMEs
> only makes indirections point to the "raise" closure, not to thunks or
> anything
> else (I also don't understand why this is needed but I guess that's another
> topic). I still don't see how can a BLACKHOLE point to a THUNK.
>
> Ömer
>
> 2018-03-23 18:51 GMT+03:00 Rahul Muttineni <rahulm...@gmail.com>:
> > Hi Omer,
> >
> > As per my understanding, a BLACKHOLE can point to a THUNK when an
> exception
> > is thrown. An exception walks up the stack and overwrites the blackholes
> > pointed to by the update frames as it walks with an stg_raise closure.
> That
> > way, if any concurrent thread happens to evaluate a thunk that was
> walked,
> > it'll evaluate the thunk which will blow up as well thereby throwing the
> > exception on the other thread(s) too.
> >
> > Definition of stg_raise:
> > https://github.com/ghc/ghc/blob/ba5797937e575ce6119de6c07703e9
> 0dda2557e8/rts/Exception.cmm#L424-L427
> >
> > raiseExceptionHelper dealing with update frames:
> > https://github.com/ghc/ghc/blob/d9d463289fe20316cff12a8f0dbf41
> 4db678fa72/rts/Schedule.c#L2864-L2875
> >
> > In general, yes, you can think that a BLACKHOLE will point to a non-THUNK
> > object assuming that everything went right.
> >
> > Hope that helps,
> > Rahul
> >
> > On Fri, Mar 23, 2018 at 5:48 PM, Ömer Sinan Ağacan <omeraga...@gmail.com
> >
> > wrote:
> >>
> >> Thanks Simon, that's really helpful.
> >>
> >> A few more questions:
> >>
> >> As far as I understand the difference between
> >>
> >> - BLACKHOLE pointing to a TSO
> >> - BLACKHOLE pointing to a BLOCKING_QUEUE
> >>
> >> is that in the former we don't yet have any threads blocked by the
> >> BLACKHOLE
> >> whereas in the latter we have and the blocking queue holds all those
> >> blocked
> >> threads. Did I get this right?
> >>
> >> Secondly, can a BLACKHOLE point to a THUNK? I'd expect no, because we
> >> BLACKHOLE
> >> a closure when we're done evaluating it (assuming no eager blackholing),
> >> and
> >> evaluation usually happens up to WHNF.
> >>
> >> Thanks,
> >>
> >> Ömer
> >>
> >> 2018-03-20 18:27 GMT+03:00 Simon Marlow <marlo...@gmail.com>:
> >> > Added comments: https://phabricator.haskell.org/D4517
> >> >
> >> > On 20 March 2018 at 14:58, Simon Marlow <marlo...@gmail.com> wrote:
> >> >>
> >> >> Hi Omer,
> >> >>
> >> >> On 20 March 2018 at 13:05, Ömer Sinan Ağacan <omeraga...@gmail.com>
> >> >> wrote:
> >> >>>
> >> >>> Hi,
> >> >>>
> >> >>> I've been looking at BLACKHOLE closures and how the indirectee field
> >> >>> is
> >> >>> used
> >> >>> and I have a few questions:
> >> >>>
> >> >>> Looking at evacuate for BLACKHOLE closures:
> >> >>>
> >> >>> case BLACKHOLE:
> >> >>> {
> >> >>> StgClosure *r;
> >> >>> const StgInfoTable *i;
> >> >>> r = ((StgInd*)q)->indirectee;
> >> >>> if (GET_CLOSURE_TAG(r) == 0) {
> >> >>> i = r->header.info;
> >> >>> if (IS_FORWARDING_PTR(i)) {
> >> >>> r = (StgClosure *)UN_FORWARDING_PTR(i);
> >> >>> i = r->header.info;
> >> >>> }
> >> >>> if (i == _TSO_info
> >> >>> || i == _WHITEHOLE_info
> >> >>> || i == _BLOCKING_QUEUE_CLEAN_info
> >> >>> || i == _BLOCKING_QUEUE_DIRTY_info) {
> >> >>> copy

Re: Question about indirectees of BLACKHOLE closures

2018-03-20 Thread Simon Marlow
Added comments: https://phabricator.haskell.org/D4517

On 20 March 2018 at 14:58, Simon Marlow <marlo...@gmail.com> wrote:

> Hi Omer,
>
> On 20 March 2018 at 13:05, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>
>> Hi,
>>
>> I've been looking at BLACKHOLE closures and how the indirectee field is
>> used
>> and I have a few questions:
>>
>> Looking at evacuate for BLACKHOLE closures:
>>
>> case BLACKHOLE:
>> {
>> StgClosure *r;
>> const StgInfoTable *i;
>> r = ((StgInd*)q)->indirectee;
>> if (GET_CLOSURE_TAG(r) == 0) {
>> i = r->header.info;
>> if (IS_FORWARDING_PTR(i)) {
>> r = (StgClosure *)UN_FORWARDING_PTR(i);
>> i = r->header.info;
>> }
>> if (i == _TSO_info
>> || i == _WHITEHOLE_info
>> || i == _BLOCKING_QUEUE_CLEAN_info
>> || i == _BLOCKING_QUEUE_DIRTY_info) {
>> copy(p,info,q,sizeofW(StgInd),gen_no);
>> return;
>> }
>> ASSERT(i != _IND_info);
>> }
>> q = r;
>> *p = r;
>> goto loop;
>> }
>>
>> It seems like indirectee can be a TSO, WHITEHOLE, BLOCKING_QUEUE_CLEAN,
>> BLOCKING_QUEUE_DIRTY, and it can't be IND. I'm wondering what does it
>> mean for
>> a BLACKHOLE to point to a
>>
>> - TSO
>> - WHITEHOLE
>> - BLOCKING_QUEUE_CLEAN
>> - BLOCKING_QUEUE_DIRTY
>>
>
> That sounds right to me.
>
>
>> Is this documented somewhere or otherwise could someone give a few
>> pointers on
>> where to look in the code?
>>
>
> Unfortunately I don't think we have good documentation for this, but you
> should look at the comments around messageBlackHole in Messages.c.
>
>
>> Secondly, I also looked at the BLACKHOLE entry code, and it seems like it
>> has a
>> different assumption about what can indirectee field point to:
>>
>> INFO_TABLE(stg_BLACKHOLE,1,0,BLACKHOLE,"BLACKHOLE","BLACKHOLE")
>> (P_ node)
>> {
>> W_ r, info, owner, bd;
>> P_ p, bq, msg;
>>
>> TICK_ENT_DYN_IND(); /* tick */
>>
>> retry:
>> p = StgInd_indirectee(node);
>> if (GETTAG(p) != 0) {
>> return (p);
>> }
>>
>> info = StgHeader_info(p);
>> if (info == stg_IND_info) {
>> // This could happen, if e.g. we got a BLOCKING_QUEUE that has
>> // just been replaced with an IND by another thread in
>> // wakeBlockingQueue().
>> goto retry;
>> }
>>
>> if (info == stg_TSO_info ||
>> info == stg_BLOCKING_QUEUE_CLEAN_info ||
>> info == stg_BLOCKING_QUEUE_DIRTY_info)
>> {
>> ("ptr" msg) = ccall allocate(MyCapability() "ptr",
>>  BYTES_TO_WDS(SIZEOF_MessageBl
>> ackHole));
>>
>> SET_HDR(msg, stg_MSG_BLACKHOLE_info, CCS_SYSTEM);
>> MessageBlackHole_tso(msg) = CurrentTSO;
>> MessageBlackHole_bh(msg) = node;
>>
>> (r) = ccall messageBlackHole(MyCapability() "ptr", msg
>> "ptr");
>>
>> if (r == 0) {
>> goto retry;
>> } else {
>> StgTSO_why_blocked(CurrentTSO) = BlockedOnBlackHole::I16;
>> StgTSO_block_info(CurrentTSO) = msg;
>> jump stg_block_blackhole(node);
>> }
>> }
>> else
>> {
>> ENTER(p);
>> }
>> }
>>
>> The difference is, when the tag of indirectee is 0, evacuate assumes that
>> indirectee can't point to an IND, but BLACKHOLE entry code thinks it's
>> possible
>> and there's even a comment about why. (I don't understand the comment
>> yet) I'm
>> wondering if this code is correct, and why. Again any pointers would be
>> appreciated.
>>
>
> Taking a quick look at the code, my guess is that:
> - a BLOCKING_QUEUE gets overwritten by an IND in wakeBlockingQueue()
> - but when this happens, the indirectee of the BLACKHOLE will also be
> overwritten to point to the value
>
> At runtime a thread might see an intermediate state because these
> mutations are happening in another thread, so we might follow the
> indirectee and see the IND. But this state can't be observed by the GC,
> because all mutator threads have stopped at a safe point.
>
> Cheers
> Simon
>
>
>
>> Thanks,
>>
>> Ömer
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Question about indirectees of BLACKHOLE closures

2018-03-20 Thread Simon Marlow
Hi Omer,

On 20 March 2018 at 13:05, Ömer Sinan Ağacan  wrote:

> Hi,
>
> I've been looking at BLACKHOLE closures and how the indirectee field is
> used
> and I have a few questions:
>
> Looking at evacuate for BLACKHOLE closures:
>
> case BLACKHOLE:
> {
> StgClosure *r;
> const StgInfoTable *i;
> r = ((StgInd*)q)->indirectee;
> if (GET_CLOSURE_TAG(r) == 0) {
> i = r->header.info;
> if (IS_FORWARDING_PTR(i)) {
> r = (StgClosure *)UN_FORWARDING_PTR(i);
> i = r->header.info;
> }
> if (i == _TSO_info
> || i == _WHITEHOLE_info
> || i == _BLOCKING_QUEUE_CLEAN_info
> || i == _BLOCKING_QUEUE_DIRTY_info) {
> copy(p,info,q,sizeofW(StgInd),gen_no);
> return;
> }
> ASSERT(i != _IND_info);
> }
> q = r;
> *p = r;
> goto loop;
> }
>
> It seems like indirectee can be a TSO, WHITEHOLE, BLOCKING_QUEUE_CLEAN,
> BLOCKING_QUEUE_DIRTY, and it can't be IND. I'm wondering what does it mean
> for
> a BLACKHOLE to point to a
>
> - TSO
> - WHITEHOLE
> - BLOCKING_QUEUE_CLEAN
> - BLOCKING_QUEUE_DIRTY
>

That sounds right to me.


> Is this documented somewhere or otherwise could someone give a few
> pointers on
> where to look in the code?
>

Unfortunately I don't think we have good documentation for this, but you
should look at the comments around messageBlackHole in Messages.c.


> Secondly, I also looked at the BLACKHOLE entry code, and it seems like it
> has a
> different assumption about what can indirectee field point to:
>
> INFO_TABLE(stg_BLACKHOLE,1,0,BLACKHOLE,"BLACKHOLE","BLACKHOLE")
> (P_ node)
> {
> W_ r, info, owner, bd;
> P_ p, bq, msg;
>
> TICK_ENT_DYN_IND(); /* tick */
>
> retry:
> p = StgInd_indirectee(node);
> if (GETTAG(p) != 0) {
> return (p);
> }
>
> info = StgHeader_info(p);
> if (info == stg_IND_info) {
> // This could happen, if e.g. we got a BLOCKING_QUEUE that has
> // just been replaced with an IND by another thread in
> // wakeBlockingQueue().
> goto retry;
> }
>
> if (info == stg_TSO_info ||
> info == stg_BLOCKING_QUEUE_CLEAN_info ||
> info == stg_BLOCKING_QUEUE_DIRTY_info)
> {
> ("ptr" msg) = ccall allocate(MyCapability() "ptr",
>  BYTES_TO_WDS(SIZEOF_
> MessageBlackHole));
>
> SET_HDR(msg, stg_MSG_BLACKHOLE_info, CCS_SYSTEM);
> MessageBlackHole_tso(msg) = CurrentTSO;
> MessageBlackHole_bh(msg) = node;
>
> (r) = ccall messageBlackHole(MyCapability() "ptr", msg "ptr");
>
> if (r == 0) {
> goto retry;
> } else {
> StgTSO_why_blocked(CurrentTSO) = BlockedOnBlackHole::I16;
> StgTSO_block_info(CurrentTSO) = msg;
> jump stg_block_blackhole(node);
> }
> }
> else
> {
> ENTER(p);
> }
> }
>
> The difference is, when the tag of indirectee is 0, evacuate assumes that
> indirectee can't point to an IND, but BLACKHOLE entry code thinks it's
> possible
> and there's even a comment about why. (I don't understand the comment yet)
> I'm
> wondering if this code is correct, and why. Again any pointers would be
> appreciated.
>

Taking a quick look at the code, my guess is that:
- a BLOCKING_QUEUE gets overwritten by an IND in wakeBlockingQueue()
- but when this happens, the indirectee of the BLACKHOLE will also be
overwritten to point to the value

At runtime a thread might see an intermediate state because these mutations
are happening in another thread, so we might follow the indirectee and see
the IND. But this state can't be observed by the GC, because all mutator
threads have stopped at a safe point.

Cheers
Simon



> Thanks,
>
> Ömer
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: What does "return" keyword mean in INFO_TABLE_RET declarations?

2018-03-19 Thread Simon Marlow
On 19 March 2018 at 00:53, Rahul Muttineni  wrote:

> Hi Omer,
>
> An INFO_TABLE_RET is a frame that "can be returned to" and the return
> keyword allows you to provide a name for the value(s) that was(were)
> returned to this frame and do something with it if you wish. If you didn't
> have this keyword, you would have to do low-level stack manipulations
> yourself to get a handle on the return value and it's easy to mess up.
>
> You can think of INFO_TABLE_RET as a traditional stack frame in languages
> like C, except it's powerful because you can specify custom logic on how
> you deal with the returned value. In some cases, like stg_atomically_frame,
> you may not even return the value further down into the stack until certain
> conditions are met (the transaction is valid).
>

This is correct.  The "documentation" for this is in the CmmParse.y module:
https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/cmm/CmmParse.y;b3b394b44e42f19ab7c23668a4008e4f728b51ba$151-165

It wouldn't hurt to move all that to the wiki and leave a link behind, if
anyone wants to do that.

Cheers
Simon




> Hope that helps,
> Rahul
>
> On Sun, Mar 18, 2018 at 8:18 PM, Ömer Sinan Ağacan 
> wrote:
>
>> Hi,
>>
>> I'm trying to understand what a "return" list in INFO_TABLE_RET
>> declaration
>> line specifies. As far as I understand a "return" in the declaration line
>> is
>> something different than a "return" in the body. For example, in this
>> definition: (in HeapStackCheck.cmm)
>>
>> INFO_TABLE_RET ( stg_ret_p, RET_SMALL, W_ info_ptr, P_ ptr )
>> return (/* no return values */)
>> {
>> return (ptr);
>> }
>>
>> The return list is empty and it even says "no return values" explicitly,
>> yet it
>> returns something.
>>
>> My guess is that the "return" list in the header is actually for
>> arguments. I
>> found this info table which has an argument: (in StgMiscClosures.cmm)
>>
>> INFO_TABLE_RET (stg_restore_cccs_eval, RET_SMALL, W_ info_ptr, W_
>> cccs)
>> return (P_ ret)
>> {
>> unwind Sp = Sp + WDS(2);
>> #if defined(PROFILING)
>> CCCS = cccs;
>> #endif
>> jump stg_ap_0_fast(ret);
>> }
>>
>> This is the use site: (in Interpreter.c)
>>
>> #if defined(PROFILING)
>> // restore the CCCS after evaluating the closure
>> Sp_subW(2);
>> SpW(1) = (W_)cap->r.rCCCS;
>> SpW(0) = (W_)_restore_cccs_eval_info;
>> #endif
>> Sp_subW(2);
>> SpW(1) = (W_)tagged_obj;
>> SpW(0) = (W_)_enter_info;
>> RETURN_TO_SCHEDULER_NO_PAUSE(ThreadRunGHC, ThreadYielding);
>>
>> If I understand this correctly, the "tagged_obj" code will put the return
>> value
>> in R1, pop the stack (which will have stg_restore_ccs_eval_info at the
>> bottom)
>> and jump to this the info table code shown above. So `P_ ret` is the
>> value of
>> `tagged_obj`, and the "return" list is actually for parameters.
>>
>> Did I get this right? If I did, I'm curious why it's called "return" and
>> not
>> "args" or something like that.
>>
>> Thanks,
>>
>> Ömer
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
>
>
> --
> Rahul Muttineni
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: GHCi recompilation avoidance UI

2017-11-22 Thread Simon Marlow
David,

Perhaps it would be good to defer changing the behaviour of :load *M (I
believe you that it's hard, that code is quite convoluted) and for now just
focus on making GHCi able to load compiled object code again, which I think
is a much simpler problem?

Cheers
Simon


On 21 November 2017 at 21:49, David Feuer <da...@well-typed.com> wrote:

> I started digging back into this today, particularly considering Simon
> PJ's view
> that it's a bit odd for optimization flags to imply -fobject-code
> (specifically
> because we could potentially support optimization for the bytecode
> interpreter some day). I'm left even more lost about exactly what we want.
> I believe it's fairly clear that, as Simon M wrote,
>
> > [W]e'll want at least -fignore-optim-changes to be the default, so that
> GHCi
> > does the expected thing when you have compiled object files.
>
> Based on Simon PJ's comment, I believe we want to *continue* to discard
> optimization flags when -fobject-code is not enabled. As for my suggestion
> in (2),
> I spent the last couple hours attempting to figure out what would be
> necessary
> to allow :load *M to load a module  interpreted even when using
> -fobject-code,
> but found myself utterly lost in the module loading logic. I see that the
> IIModule
> constructor is deeply involved in this, but I haven't been able to figure
> out
> where/how that interacts with -fobject-code to determine whether the module
> will actually be loaded interpreted or compiled. Can someone give me a
> clue?
>
> On Thursday, November 2, 2017 10:21:07 AM EST Simon Marlow wrote:
> > On 31 October 2017 at 15:42, David Feuer <da...@well-typed.com> wrote:
> >
> > > Changes in GHC 8.2.1 lead to a lot of recompilation, because GHCi now
> > > refuses to load optimized
> > > code unless -fobject-code (and optimization flags) are enabled. I
> propose
> > > the following slight
> > > modification to https://ghc.haskell.org/trac/
> ghc/ticket/13604#comment:48
> > >
> > > 1. Optimization flags (except -O0) imply -fobject-code. This ensures
> that
> > > GHC respects optimization flags regardless of --interactive.
> > >
> > > 2. Even when -fobject-code is on, :load *M will load M as bytecode.
> This
> > > provides the "escape hatch" from -fobject-code that you need to use
> > > debugging features, etc.
> > >
> >
> > Yes, I think this is probably what we want. I'm not sure how smooth it
> will
> > be to implement though.
> >
> >
> > > 3. New -fignore-optim-changes and -fignore-hpc-changes (​​Phab:D4123)
> > > flags should enable users to put together object code and bytecode with
> > > diverse optimization levels/options and HPC options while still
> updating
> > > automatically based on source changes and whether profiling is enabled.
> > >
> >
> > As I mentioned on the diff, I think we'll want at least
> > -fignore-optim-changes to be the default, so that GHCi does the expected
> > thing when you have compiled object files.
> >
> > Cheers
> > Simon
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Bringing some observable sharing to GHCi

2017-11-02 Thread Simon Marlow
Not being able to :print an exception would be quite annoying. Do TypeReps
need to be cyclic?

Observable sharing can be done with StableName, but that would be a bit
pile of hassle in the printer. Maybe exceptions warrant a special case.

Cheers
Simon

On 29 October 2017 at 20:40, David Feuer  wrote:

> The :sprint, :print, and :force commands in GHCi fall into infinite
> loops when confronted by cyclical data. This bit me hard in
> https://phabricator.haskell.org/D4085 because that produces cyclical
> TypeReps, which is trouble for (e.g.) the test break011 which tries to
> :force a SomeException (which wraps an Exception dictionary, which has
> a Typeable constraint). I could try coming up with a fix myself, but
> I'm rather curious whether some of the work you (or others) have
> already done on observing GHC data graphs could be yanked into GHCi
> itself for this purpose. We want
>
> 1. To be able to display cyclical data in some sensible way.
>
> > x = "hi" : x
> > x `seq` ()
> > :print x
>
> should print some useful representation of x.
>
> 2. To be able to force cyclical data without looping.
>
> > x = "hi" : x
> > :force x
>
> should print a useful representation of x.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: GHCi recompilation avoidance UI

2017-11-02 Thread Simon Marlow
On 31 October 2017 at 15:42, David Feuer  wrote:

> Changes in GHC 8.2.1 lead to a lot of recompilation, because GHCi now
> refuses to load optimized
> code unless -fobject-code (and optimization flags) are enabled. I propose
> the following slight
> modification to https://ghc.haskell.org/trac/ghc/ticket/13604#comment:48
>
> 1. Optimization flags (except -O0) imply -fobject-code. This ensures that
> GHC respects optimization flags regardless of --interactive.
>
> 2. Even when -fobject-code is on, :load *M will load M as bytecode. This
> provides the "escape hatch" from -fobject-code that you need to use
> debugging features, etc.
>

Yes, I think this is probably what we want. I'm not sure how smooth it will
be to implement though.


> 3. New -fignore-optim-changes and -fignore-hpc-changes (​​Phab:D4123)
> flags should enable users to put together object code and bytecode with
> diverse optimization levels/options and HPC options while still updating
> automatically based on source changes and whether profiling is enabled.
>

As I mentioned on the diff, I think we'll want at least
-fignore-optim-changes to be the default, so that GHCi does the expected
thing when you have compiled object files.

Cheers
Simon



>
> Does this seem like a reasonable way forward?
>
> David Feuer
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Phab: conditional approval

2017-09-12 Thread Simon Marlow
On 19 August 2017 at 03:56, Richard Eisenberg  wrote:

> Hi devs,
>
> When reviewing a diff on Phab, I can "accept" or "request changes".
> Sometimes, though, I want to do both: I suggest very minor (e.g., typo)
> changes, but then when these changes are made, I accept. I'm leery of
> making the suggestions and saying "accept", because then someone working
> quickly may merge without noticing the typos. Does Phab have such an option?
>

"Accept with nits" is standard practice, but you're right it can go wrong
when someone else is merging accepted diffs.  We could adopt a standard
comment keyword, e.g. "NITS" that indicates you'd like the nits to be fixed
before committing, perhaps?

Also, I don't think it's a good idea to merge commits when the author is a
committer, they can land themselves.

Cheers
Simon


> Thanks,
> Richard
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: GHC Threads affinity

2017-09-11 Thread Simon Marlow
On 10 September 2017 at 04:03, Michael Baikov  wrote:

> Greetings
>
>
> Currently GHC supports two kinds of threads - pinned to a specific
> capability (bound threads) and those it can migrate between any
> capabilities (unbound threads). For purposes of achieving lower latency in
> Haskell applications it would be nice to have something in between -
> threads GHC can migrate but within a certain subset of capabilities only.
>

That's not correct actually: a bound thread is associated with a particular
OS thread, but it can migrate between capabilities just like unbound
threads.


> I'm developing a program that contains several kinds of threads - those
> that do little work and sensitive to latency and those that can spend more
> CPU time and less latency sensitive. I looked into several cases of
> increased latency in those sensitive threads (using GHC eventlog) and in
> all cases sensitive threads were waiting for non-sensitive threads to
> finish working. I was able to reduce worst case latency by factor of 10 by
> pinning all the threads in the program to specific capability but manually
> distributing threads (60+ of them) between capabilities (several different
> machines with different numbers of cores available) seems very fragile.
> World stopping GC is still a problem but at least in my case is much less
> frequently so.
>

If you have a fixed set of threads you might just want to use -N
-qn, and then pin every thread to a different capability.  This
gives you 1:1 scheduling at the GHC level, delegating the scheduling job to
the OS.  You will also want to use nursery chunks with something like -n2m,
so you don't waste too much nursery space on the idle capabilities.

Even if your set of threads isn't fixed you might be able to use a hybrid
scheme with -N -qn and pin the high-priority threads on their
own capability, while putting all the low-priority threads on a single
capability, or a few separate ones.

It would be nice to be able to allow GHC runtime to migrate a thread
> between a subset of capabilities using interface similar to this one:
>
> -- creates a thread that is allowed to migrate between capabilities
> according to following rule: ghc is allowed to run this thread on Nth
> capability if Nth `mod` size_of_word bit in mask is set.
> forkOn' :: Int -> IO () -> IO ThreadId
> forkOn' mask act = undefined
>
> This should allow to define up to 64 (32) distinct groups and allow user
> to break down their threads into bigger number of potentially intersecting
> groups by specifying things like capability 0 does latency sensitive
> things, caps 1..5 - less  sensitive things, caps 6-7 bulk things.
>

We could do this, but it would add some complexity to the scheduler and
load balancer (which has already been quite hard to get right, I fixed a
handful of bugs there recently). I'd be happy review a patch if you want to
try it though.

Cheers
Simon


Anything obvious I'm missing? Any recommendations to how to implement this?
>



>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: GHC staus

2017-09-04 Thread Simon Marlow
One thing for 8.4: there have been a series of performance improvements in
ghc --make and GHCi, with some quite dramatic improvements on very large
programs (1K+ modules). Bartosz can supply more details.

On 3 September 2017 at 14:15, Simon Peyton Jones 
wrote:

> Ben, Simon, and ghc-devs
>
> I have to write slides for the GHC status talk in the Haskell
> Implementor’s meeting.
>
> Usually we have
>
>1. Current status (current release)
>2. What’s cooking for the next release
>3. GHC community comments
>
> As background we have
>
>- Our Apr 17 status page
>
>- Our 8.2 release notes
>
> 
>- Our 8.4 status page
>
>
> What would you put under (1-3)?  Anything you’d like to see highlighted?
>
> Simon
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: GHC staus

2017-09-04 Thread Simon Marlow
I have a vested interest in the cross-compilation story because it's very
related to Remote GHCi, so I'd love to join in if you have a discussion
about that :)

On 4 September 2017 at 11:16, Manuel M T Chakravarty 
wrote:

> +1 for a lighting talk on that! (You can tell the organisers that ;)
>
> Also, we should make sure to meet and talk about cross-compilation and GHC
> for iOS :)
>
> Manuel
>
> Moritz Angermann :
>
> Hi,
>
> not sure if this is noteworthy:
>
> The following is or will hopefully make(*) it
> into 8.4 as well
>
> - (1) iserv-remote (run iserv on a remote device over the network)
> - (2) arm / aarch64 linker for elf and mach-o
> - (3*) `-staticlib` support for Linux and BSD derivatives (was darwin
> only):
> - (4*) `-llvmng` new llvm bitcode code gen
> - (5*) refactored llvm pipeline
>
> This essentially is all part of making GHC natively
> support cross compiling (including support for Template Haskell) to
> android/iOS/RaspberryPi.
>
> I hope to give a lighting talk around those, if I get a slot.
>
> Cheers,
>  Moritz
>
> Sent from my iPhone
>
> On 4 Sep 2017, at 8:01 AM, Iavor Diatchki 
> wrote:
>
> Hello,
>
> Trevor Elliott and I have been slowly working on implementing Simon M's
>  "Mutable Constructor Fields" proposal [1].
>
> The current state of the code is here:
> https://github.com/yav/ghc/tree/wip/mutable-fields
>
> I am not sure if this would be ready in time for 8.4 as I don't know what
> the time-line looks like, and also, the actual proposal is still in the
> process of being reviewed by the GHC committee.
>
> -Iavor
>
> [1] https://github.com/simonmar/ghc-proposals/blob/
> mutable-fields/proposals/-mutable-fields.rst
>
>
>
> On Sun, Sep 3, 2017 at 2:15 PM Simon Peyton Jones via ghc-devs <
> ghc-devs@haskell.org> wrote:
>
>> Ben, Simon, and ghc-devs
>>
>> I have to write slides for the GHC status talk in the Haskell
>> Implementor’s meeting.
>>
>> Usually we have
>>
>>1. Current status (current release)
>>2. What’s cooking for the next release
>>3. GHC community comments
>>
>> As background we have
>>
>>- Our Apr 17 status page
>>
>>- Our 8.2 release notes
>>
>> 
>>- Our 8.4 status page
>>
>>
>> What would you put under (1-3)?  Anything you’d like to see highlighted?
>>
>> Simon
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: WordX/IntX wrap Word#/Int#?

2017-06-15 Thread Simon Marlow
On 11 June 2017 at 22:44, Joachim Breitner  wrote:

> Hi,
>
> Am Sonntag, den 11.06.2017, 10:44 -0400 schrieb Ben Gamari:
> > This is certainly one consideration. Another is that you would also
> > need to teach the garbage collector to understand closures with sub-
> > word-size fields. Currently we can encode whether each field of a
> > closure is a pointer or not with a simple bitmap. If we naively
> > allowed smaller fields we would need to increase the granularity of
> > this representation to encode bytes.
> >
> > Of course, one way to work around this would be to impose an
> > invariant that guarantees that pointers are always word-aligned. Then
> > we would probably want to shuffle sub-word sized fields, allowing two
> > Word16s to inhabit a single word.
>
> that is not an issue; we already sort field into pointers first, and
> non-pointers later. So all pointers are at the beginning and nicely
> aligned, and all the non-pointer data can follow in whatever weird
> format. The GC only needs to know how many words in total are used by
> the non-pointer data.
>

But the compiler has no support for sub-word-sized fields yet.  I made a
partial patch to support it a while ago: https://phabricator.haskell.org/D38


Cheers
Simon


Greetings,
> Joachim
> --
> Joachim “nomeata” Breitner
>   m...@joachim-breitner.de • https://www.joachim-breitner.de/
>   XMPP: nome...@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F
>   Debian Developer: nome...@debian.org
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: external interpreter failing on Mac

2017-06-15 Thread Simon Marlow
No idea what this is, but just to point out that the continuous build
succeeded on OS X at the same revision that you have:
https://phabricator.haskell.org/B16186, so this is at least not a universal
failure.  Something specific to the version of GMP, or some other external
tool/library?

On 14 June 2017 at 14:55, Richard Eisenberg  wrote:

> Hi devs,
>
> It seems every test run through the external interpreter is failing for me
> on a Mac:
>
> => TH_mkName(ext-interp) 1 of 1 [0, 0, 0]
> cd "./TH_mkName.run" &&  "/Users/rae/ghc/ghc/inplace/test
> spaces/ghc-stage2" -c TH_mkName.hs -dcore-lint -dcmm-lint
> -no-user-package-db -rtsopts -fno-warn-missed-specialisations
> -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret
> -dno-debug-output -XTemplateHaskell -package template-haskell
> -fexternal-interpreter -v0
> Compile failed (exit code 1) errors were:
> ghc-iserv.bin:
> lookupSymbol failed in relocateSection (RELOC_GOT)
> /Users/rae/ghc/ghc/libraries/integer-gmp/dist-install/build/HSinteger-gmp-1.0.0.1.o:
> unknown symbol `___gmp_rands'
> ghc-stage2: unable to load package `integer-gmp-1.0.0.1'
>
> *** unexpected failure for TH_mkName(ext-interp)
>
> Any advice? My most recent commit from master is
> ef07010cf4f480d9f595a71cf5b009884522a75e from Wed Jun 7.
>
> I'm on IRC today if you want to iterate that way.
>
> Thanks!
> Richard
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Where do I start if I would like help improve GHC compilation times?

2017-04-18 Thread Simon Marlow
Pretty-printing the asm is a likely contender for optimisation, however the
problem is not the pretty-printing per se.  We don't actually use any of
the backtracking stuff when printing asm, since there's no point nicely
indenting things or wrapping lines.  The overhead is probably all in the
layer of data structure that we generate in Pretty before it gets dumped
into raw bytes.  Using a ByteString Builder instead might yield some
improvement.

Cheers
Simon

On 17 April 2017 at 18:44, Alfredo Di Napoli 
wrote:

> Dear all,
>
> after sprinkling (ehm, littering) GHC source code with cost centres, I was
> not surprised to see that roughly 20% of the compilation time (as in .prof)
> was spent in the core gen/simplification process (10% of the total time)
> and on the asm code gen (another 10%).
>
> I have almost immediately abandoned the idea of try optimising some
> modules in simplCore (considering my 0-knowledge of GHC internals anyway..)
> but I have been dwelling on the following: Outputable.hs and Pretty.hs
> seems to be have been implemented making deliberate use of lists and
> concatenations between them, which left me wondering if there was room for
> optimisation there. I have found this interesting paper on the topic:
>
> https://www.cs.kent.ac.uk/pubs/2005/2062/content.pdf
>
> Now, it’s totally possible that this has been already tried (with no
> success) but judging from the original copyright of Pretty.hs (dated 2001),
> it seems it was written prior to the work of Olaf Chitil (the author of the
> paper).
>
> TL;DR I was thinking (even just as a fun exercise to learn more about GHC
> internals) to leverage the ideas of that paper and switch to a different
> implementation for `Doc` coupled with the use of lazy dequeues, which
> *might* increase the performances of the codegen and thus of the compiler
> overall. Am I fighting a strawman (or flogging a dead horse, pick your
> rethorical figure :D ) or is there even a tiny chance of this being
> actually useful?
>
> Have a nice evening,
>
> Alfredo
>
> On 11 April 2017 at 00:47, Ben Gamari  wrote:
>
>> Alfredo Di Napoli  writes:
>>
>> > Hey Ben,
>> >
>> Hi Alfredo,
>>
>> Sorry for the late response! The email queue from the weekend was a bit
>> longer than I would like.
>>
>> > as promised I’m back to you with something more articulated and
>> hopefully
>> > meaningful. I do hear you perfectly — probably trying to dive head-first
>> > into this without at least a rough understanding of the performance
>> > hotspots or the GHC overall architecture is going to do me more harm
>> than
>> > good (I get the overall picture and I’m aware of the different stages of
>> > the GHC compilation pipeline, but it’s far from saying I’m proficient
>> with
>> > the architecture as whole). I have also read a couple of years ago the
>> GHC
>> > chapter on the “Architeture of Open Source Applications” book, but I
>> don’t
>> > know how much that is still relevant. If it is, I guess I should
>> refresh my
>> > memory.
>> >
>> It sounds like you have done a good amount of reading. That's great.
>> Perhaps skimming the AOSA chapter again wouldn't hurt, but otherwise
>> it's likely worthwhile diving in.
>>
>> > I’m currently trying to move on 2 fronts — please advice if I’m a fool
>> > flogging a dead horse or if I have any hope of getting anything done ;)
>> >
>> > 1. I’m trying to treat indeed the compiler as a black block (as you
>> > adviced) trying to build a sufficiently large program where GHC is not
>> “as
>> > fast as I would like” (I know that’s a very lame definition of “slow”,
>> > hehe). In particular, I have built the stage2 compiler with the “prof”
>> > flavour as you suggested, and I have chosen 2 examples as a reference
>> > “benchmark” for performance; DynFlags.hs (which seems to have been
>> > mentioned multiple times as a GHC perf killer) and the highlighting-kate
>> > package as posted here: https://ghc.haskell.org/trac/ghc/ticket/9221 .
>>
>> Indeed, #9221 would be a very interesting ticket to look at. The
>> highlighting-kate package is interesting in the context of that ticket
>> as it has a very large amount of parallelism available.
>>
>> If you do want to look at #9221, note that the cost centre profiler may
>> not provide the whole story. In particular, it has been speculated that
>> the scaling issues may be due to either,
>>
>>  * threads hitting a blackhole, resulting in blocking
>>
>>  * the usual scaling limitations of GHC's stop-the-world GC
>>
>> The eventlog may be quite useful for characterising these.
>>
>> > The idea would be to compile those with -v +RTS -p -hc -RTS enabled,
>> > look at the output from the .prof file AND the `-v` flag, find any
>> > hotspot, try to change something, recompile, observe diff, rinse and
>> > repeat. Do you think I have any hope of making progress this way? In
>> > particular, I think compiling DynFlags.hs is a bit of a 

Re: Lazy ST vs concurrency

2017-02-01 Thread Simon Marlow
On 31 January 2017 at 10:02, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> Huh. You are right.  That’s horrible.
>

Horrible indeed!


>
>
> OK, here’s another idea.  Provide,
>
> applyOnce# :: (a->b) -> a -> b
>
>
>
> which behaves like
>
> applyOnce f x = f x
>
>
>
> but guarantees that any thunk  (applyOnce# f x) will be evaluated with
> atomic eager black-holing.
>
>
>
> \(s :: State# s) ->
>
>let unsafePerformIO = \g -> g s
>
> thunk = applyOnce# unsafePerformIO (\s -> ... )
>
>in
>
>   ...
>
>
But what if GHC decided to add another thunk, e.g.

let
  thunk =
let x = applyOnce# unsafePerformIO (\s -> ...)
in x

now we need atomicity on both thunks, but there's no way to tell. (of
course GHC probably wouldn't do this particularly transformation, but there
are a whole range of other things that it might correctly do that would
subvert the programmer's intention to make a single atomic thunk).

noDuplicate# avoids this problem because it walks the whole stack, claiming
the whole chain of thunks currently under evaluation.  But this is a messy
solution, I don't like it either.

Cheers
Simon


> Of course this does not guarantee safety.  But I think it’d give a
> per-thunk way to specify it.
>
>
>
> Simon
>
>
>
> *From:* Simon Marlow [mailto:marlo...@gmail.com]
> *Sent:* 31 January 2017 09:25
>
> *To:* Simon Peyton Jones <simo...@microsoft.com>
> *Cc:* David Feuer <da...@well-typed.com>; ghc-devs@haskell.org
> *Subject:* Re: Lazy ST vs concurrency
>
>
>
> On 31 January 2017 at 09:11, Simon Peyton Jones <simo...@microsoft.com>
> wrote:
>
> If we could identify exactly the thunks we wanted to be atomic, then yes,
> that would be better than a whole-module solution.  However I'm not sure
> how to do that - doing it on the basis of a free variable with State# type
> doesn't work if the State# is buried in a data structure or a function
> closure, for instance.
>
>
>
> I disagree.  Having a free State# variable is precisely necessary and
> sufficient, I claim.  Can you provide a counter-example?
>
>
>
> Sure, what I had in mind is something like this, defining a local
> unsafePerformIO:
>
>
>
> \(s :: State# s) ->
>
>let unsafePerformIO = \g -> g s
>
> thunk = unsafePerformIO (\s -> ... )
>
>in
>
>   ...
>
>
>
> and "thunk" doesn't have a free variable of type State#.
>
>
>
> Cheers
>
> Simon
>
>
>
>
>
> Informal proof:
>
> · The model is that a value of type (State# t) is a linear value
> that we mutate in-place.  We must not consume it twice.
>
> · Evaluating a thunk that has a free (State# t) variable is
> precisely “consuming” it.  So we should only do that once
>
>
>
>
>
> I think -fatomic-eager-blackholing might "fix" it with less overhead,
> though
>
>
>
> But precisely where would you have to use that flag?  Inlining could meant
> that the code appears anywhere!  Once we have the ability to
> atomically-blackhole a thunk, we can just use my criterion above, I claim.
>
>
>
> Stopgap story for 8.2.   I am far from convinced that putting
> unsafePerformIO in the impl of (>>=) for the ST monad will be correct; but
> if you tell me it is, and if it is surrounded with huge banners saying that
> this is the wrong solution, and pointing to a new ticket to fix it, then OK.
>
>
>
> Arguably this isn't all that urgent, given that it's been broken for 8
> years or so.
>
>
>
>
>
> Simon
>
>
>
> *From:* Simon Marlow [mailto:marlo...@gmail.com]
> *Sent:* 31 January 2017 08:59
> *To:* Simon Peyton Jones <simo...@microsoft.com>
> *Cc:* David Feuer <da...@well-typed.com>; ghc-devs@haskell.org
>
>
> *Subject:* Re: Lazy ST vs concurrency
>
>
>
> On 30 January 2017 at 22:56, Simon Peyton Jones <simo...@microsoft.com>
> wrote:
>
> We don’t want to do this on a per-module basis do we, as
> -fatomic-eager-blackholing would suggest.  Rather, on per-thunk basis, no?
> Which thunks, precisely?   I think perhaps *precisely thunks one of whose
> free variables has type (Sttate# s) for some s.*  These are thunks that
> consume a state token, and must do so no more than once.
>
>
>
> If we could identify exactly the thunks we wanted to be atomic, then yes,
> that would be better than a whole-module solution.  However I'm not sure
> how to do that - doing it on the basis of a free variable with State# type
> doesn't work if the State# is buried in a data structu

Re: Lazy ST vs concurrency

2017-01-31 Thread Simon Marlow
On 31 January 2017 at 09:11, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> If we could identify exactly the thunks we wanted to be atomic, then yes,
> that would be better than a whole-module solution.  However I'm not sure
> how to do that - doing it on the basis of a free variable with State# type
> doesn't work if the State# is buried in a data structure or a function
> closure, for instance.
>
>
>
> I disagree.  Having a free State# variable is precisely necessary and
> sufficient, I claim.  Can you provide a counter-example?
>
>
Sure, what I had in mind is something like this, defining a local
unsafePerformIO:

\(s :: State# s) ->
   let unsafePerformIO = \g -> g s
thunk = unsafePerformIO (\s -> ... )
   in
  ...

and "thunk" doesn't have a free variable of type State#.

Cheers
Simon


>
> Informal proof:
>
> · The model is that a value of type (State# t) is a linear value
> that we mutate in-place.  We must not consume it twice.
>
> · Evaluating a thunk that has a free (State# t) variable is
> precisely “consuming” it.  So we should only do that once
>

>
>
>
> I think -fatomic-eager-blackholing might "fix" it with less overhead,
> though
>
>
>
> But precisely where would you have to use that flag?  Inlining could meant
> that the code appears anywhere!  Once we have the ability to
> atomically-blackhole a thunk, we can just use my criterion above, I claim.
>
>
>
> Stopgap story for 8.2.   I am far from convinced that putting
> unsafePerformIO in the impl of (>>=) for the ST monad will be correct; but
> if you tell me it is, and if it is surrounded with huge banners saying that
> this is the wrong solution, and pointing to a new ticket to fix it, then OK.
>

Arguably this isn't all that urgent, given that it's been broken for 8
years or so.


>
>
> Simon
>
>
>
> *From:* Simon Marlow [mailto:marlo...@gmail.com]
> *Sent:* 31 January 2017 08:59
> *To:* Simon Peyton Jones <simo...@microsoft.com>
> *Cc:* David Feuer <da...@well-typed.com>; ghc-devs@haskell.org
>
> *Subject:* Re: Lazy ST vs concurrency
>
>
>
> On 30 January 2017 at 22:56, Simon Peyton Jones <simo...@microsoft.com>
> wrote:
>
> We don’t want to do this on a per-module basis do we, as
> -fatomic-eager-blackholing would suggest.  Rather, on per-thunk basis, no?
> Which thunks, precisely?   I think perhaps *precisely thunks one of whose
> free variables has type (Sttate# s) for some s.*  These are thunks that
> consume a state token, and must do so no more than once.
>
>
>
> If we could identify exactly the thunks we wanted to be atomic, then yes,
> that would be better than a whole-module solution.  However I'm not sure
> how to do that - doing it on the basis of a free variable with State# type
> doesn't work if the State# is buried in a data structure or a function
> closure, for instance.
>
>
>
> If entering such thunks was atomic, could we kill off noDuplicate#?
>
>
>
> I still don’t understand exactly what noDuplicate# does, what problem it
> solves, and how the problem it solves relates to this LazyST problem.
>
>
>
> Back in our "Haskell on a Shared Memory Multiprocessor" paper (
> http://simonmar.github.io/bib/papers/multiproc.pdf
> <https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fsimonmar.github.io%2Fbib%2Fpapers%2Fmultiproc.pdf=02%7C01%7Csimonpj%40microsoft.com%7C49b93aee78394d54fcab08d449b76706%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C1%7C636214499439419212=81aU2TCVDxdNFl7CIHd8GxWUUdmUn%2FdRO4bOi2ScpVw%3D=0>)
> we described a scheme to try to avoid duplication of work when multiple
> cores evaluate the same thunk.  This is normally applied lazily, because it
> involves walking the stack and atomically black-holing thunks pointed to by
> update frames.  The noDuplicate# primop just invokes the stack walk
> immediately; the idea is to try to prevent multiple threads from evaluating
> a thunk containing unsafePerformIO.
>
>
>
> It's expensive.  It's also not foolproof, because if you already happened
> to create two copies of the unsafePerformIO thunk then noDuplicate# can't
> help. I've never really liked it for these reasons, but I don't know a
> better way.  We have unsafeDupablePerformIO that doesn't call noDuplicate#,
> and the programmer can use when the unsafePerformIO can safely be executed
> multiple times.
>
>
>
>
>
> We need some kind of fix for 8.2.  Simon what do you suggest?
>
>
>
> David's current fix would be OK (along with a clear notice in the release
> notes etc. to note that the implementation got slower).  I think
> -fatomic-eager-blackholing might &quo

Re: Lazy ST vs concurrency

2017-01-31 Thread Simon Marlow
On 30 January 2017 at 22:56, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> We don’t want to do this on a per-module basis do we, as
> -fatomic-eager-blackholing would suggest.  Rather, on per-thunk basis, no?
> Which thunks, precisely?   I think perhaps *precisely thunks one of whose
> free variables has type (Sttate# s) for some s.*  These are thunks that
> consume a state token, and must do so no more than once.
>

If we could identify exactly the thunks we wanted to be atomic, then yes,
that would be better than a whole-module solution.  However I'm not sure
how to do that - doing it on the basis of a free variable with State# type
doesn't work if the State# is buried in a data structure or a function
closure, for instance.


> If entering such thunks was atomic, could we kill off noDuplicate#?
>
>
>
> I still don’t understand exactly what noDuplicate# does, what problem it
> solves, and how the problem it solves relates to this LazyST problem.
>
>
Back in our "Haskell on a Shared Memory Multiprocessor" paper (
http://simonmar.github.io/bib/papers/multiproc.pdf) we described a scheme
to try to avoid duplication of work when multiple cores evaluate the same
thunk.  This is normally applied lazily, because it involves walking the
stack and atomically black-holing thunks pointed to by update frames.  The
noDuplicate# primop just invokes the stack walk immediately; the idea is to
try to prevent multiple threads from evaluating a thunk containing
unsafePerformIO.

It's expensive.  It's also not foolproof, because if you already happened
to create two copies of the unsafePerformIO thunk then noDuplicate# can't
help. I've never really liked it for these reasons, but I don't know a
better way.  We have unsafeDupablePerformIO that doesn't call noDuplicate#,
and the programmer can use when the unsafePerformIO can safely be executed
multiple times.


>
>
> We need some kind of fix for 8.2.  Simon what do you suggest?
>

David's current fix would be OK (along with a clear notice in the release
notes etc. to note that the implementation got slower).  I think
-fatomic-eager-blackholing might "fix" it with less overhead, though.

Ben's suggestion:

> eagerlyBlackhole :: a -> a

is likely to be unreliable I think.  We lack the control in the source
language to tie it to a particular thunk.

Cheers
Simon


>
> Simon
>
>
>
> *From:* Simon Marlow [mailto:marlo...@gmail.com]
> *Sent:* 30 January 2017 21:51
> *To:* David Feuer <da...@well-typed.com>
> *Cc:* Simon Peyton Jones <simo...@microsoft.com>; ghc-devs@haskell.org
> *Subject:* Re: Lazy ST vs concurrency
>
>
>
> On 30 January 2017 at 16:18, David Feuer <da...@well-typed.com> wrote:
>
> I forgot to CC ghc-devs the first time, so here's another copy.
>
>
> I was working on #11760 this weekend, which has to do with concurrency
> breaking lazy ST. I came up with what I thought was a pretty decent
> solution (
> https://phabricator.haskell.org/D3038 ). Simon Peyton Jones, however, is
> quite
> unhappy about the idea of sticking this weird unsafePerformIO-like code
> (noDup, which I originally implemented as (unsafePerformIO . evaluate), but
> which he finds ugly regardless of the details) into fmap and (>>=).  He's
> also
> concerned that the noDuplicate# applications will kill performance in the
> multi-threaded case, and suggests he would rather leave lazy ST broken, or
> even remove it altogether, than use a fix that will make it slow sometimes,
> particularly since there haven't been a lot of reports of problems in the
> wild.
>
>
>
> In a nutshell, I think we have to fix this despite the cost - the
> implementation is incorrect and unsafe.
>
>
>
> Unfortunately the mechanisms we have right now to fix it aren't ideal -
> noDuplicate# is a bigger hammer than we need.  All we really need is some
> way to make a thunk atomic, it would require some special entry code to the
> thunk which did atomic eager-blackholing.  Hmm, now that I think about it,
> perhaps we could just have a flag, -fatomic-eager-blackholing.  We already
> do this for CAFs, incidentally. The idea is to compare-and-swap the
> blackhole info pointer into the thunk, and if we didn't win the race, just
> re-enter the thunk (which is now a blackhole).  We already have the cmpxchg
> MachOp, so It shouldn't be more than a few lines in the code generator to
> implement it.  It would be too expensive to do by default, but doing it
> just for Control.Monad.ST.Lazy should be ok and would fix the unsafety.
>
>
>
> (I haven't really thought this through, just an idea off the top of my
> head, so there could well be something I'm overlooking here...)
>
>
>
> Cheers
>
> Simon
>
>
>
>
>
> My

Re: Lazy ST vs concurrency

2017-01-30 Thread Simon Marlow
On 30 January 2017 at 16:18, David Feuer  wrote:

> I forgot to CC ghc-devs the first time, so here's another copy.
>
> I was working on #11760 this weekend, which has to do with concurrency
> breaking lazy ST. I came up with what I thought was a pretty decent
> solution (
> https://phabricator.haskell.org/D3038 ). Simon Peyton Jones, however, is
> quite
> unhappy about the idea of sticking this weird unsafePerformIO-like code
> (noDup, which I originally implemented as (unsafePerformIO . evaluate), but
> which he finds ugly regardless of the details) into fmap and (>>=).  He's
> also
> concerned that the noDuplicate# applications will kill performance in the
> multi-threaded case, and suggests he would rather leave lazy ST broken, or
> even remove it altogether, than use a fix that will make it slow sometimes,
> particularly since there haven't been a lot of reports of problems in the
> wild.
>

In a nutshell, I think we have to fix this despite the cost - the
implementation is incorrect and unsafe.

Unfortunately the mechanisms we have right now to fix it aren't ideal -
noDuplicate# is a bigger hammer than we need.  All we really need is some
way to make a thunk atomic, it would require some special entry code to the
thunk which did atomic eager-blackholing.  Hmm, now that I think about it,
perhaps we could just have a flag, -fatomic-eager-blackholing.  We already
do this for CAFs, incidentally. The idea is to compare-and-swap the
blackhole info pointer into the thunk, and if we didn't win the race, just
re-enter the thunk (which is now a blackhole).  We already have the cmpxchg
MachOp, so It shouldn't be more than a few lines in the code generator to
implement it.  It would be too expensive to do by default, but doing it
just for Control.Monad.ST.Lazy should be ok and would fix the unsafety.

(I haven't really thought this through, just an idea off the top of my
head, so there could well be something I'm overlooking here...)

Cheers
Simon



> My view is that leaving it broken, even if it only causes trouble
> occasionally, is simply not an option. If users can't rely on it to always
> give correct answers, then it's effectively useless. And for the sake of
> backwards compatibility, I think it's a lot better to keep it around, even
> if
> it runs slowly multithreaded, than to remove it altogether.
>
> Note to Simon PJ: Yes, it's ugly to stick that noDup in there. But lazy ST
> has
> always been a bit of deep magic. You can't *really* carry a moment of time
> around in your pocket and make its history happen only if necessary. We can
> make it work in GHC because its execution model is entirely based around
> graph
> reduction, so evaluation is capable of driving execution. Whereas lazy IO
> is
> extremely tricky because it causes effects observable in the real world,
> lazy
> ST is only *moderately* tricky, causing effects that we have to make sure
> don't lead to weird interactions between threads. I don't think it's
> terribly
> surprising that it needs to do a few more weird things to work properly.
>
> David
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Next steps of the trac-to-maniphest migration?

2017-01-24 Thread Simon Marlow
On 24 January 2017 at 14:09, Matthew Pickering <matthewtpicker...@gmail.com>
wrote:

> On Tue, Jan 24, 2017 at 1:26 PM, Simon Marlow <marlo...@gmail.com> wrote:
>
> > Can we have custom fields with Maniphest?  I like the rich metadata we
> have
> > with OS / Architecture / Component / Failure types.  It's true that we
> don't
> > use it consistently, but at least when we do use it there's an obvious
> and
> > standard way to do it.  When I search for RTS bugs I know that at least
> all
> > the bugs I'm seeing are RTS bugs, even if I'm not seeing all the RTS
> bugs.
> > People responsible for particular architectures can keep their metadata
> up
> > to date to make it easier to manage their ticket lists.
>
> There was a long discussion about this on the original thread with
> people echoing this sentiment. I am of the opinion that projects would
> be a better fit as
>
> 1. They integrate better with the rest of phabricator
> 2. They are not relevant to every ticket. There are tickets about
> infrastructure matters for which the concept of OS is irrelevant for
> example.
>
> I like to think of projects as structured unstructured metadata.
> The structure is that you
> can group different project tags together as subprojects of a parent
> project but adding projects to a ticket is unstructured.
> This is how "architecture" is implemented currently -
> http://ec2-52-214-147-146.eu-west-1.compute.amazonaws.com/pr
> oject/view/101/
> On trac, keywords are not very useful as they are completely
> unstructured and not discoverable. I think projects greatly improve on
> this.
>

I think the problem here is that it's not obvious which projects should be
added to tickets.  As a ticket submitter, if I have metadata I'm not likely
to add it, and as developers we'll probably forget which fields we could
add.

Yes, Trac keywords are even more useless.  But we don't generally use
keywords; the point here is about the other metadata fields (OS,
Architecture, etc.).  Just having some text on the ticket creation page to
suggest adding OS / Architecture would help a lot.

Cheers
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Next steps of the trac-to-maniphest migration?

2017-01-24 Thread Simon Marlow
On 24 January 2017 at 10:37, Matthew Pickering <matthewtpicker...@gmail.com>
wrote:

> Thank you Simon.
>
> If you have any example queries that you run often or queries which
> you have embedded into wikipages then it would be useful to share them
> so I can investigate.
>

The 8.2.1 status page has queries embedded:
https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-8.2.1

Personally I do queries like "all open bugs where Component = RuntimeSystem
ordered by priority".  It looks like we can probably do that with Maniphest.

I couldn't take a look at the interface for creating a ticket because I
have to create an account, and it says my account is pending approval.

Does Maniphest have a concept of ticket dependencies? i.e. ticket X is
blocked by Y.

Can we have custom fields with Maniphest?  I like the rich metadata we have
with OS / Architecture / Component / Failure types.  It's true that we
don't use it consistently, but at least when we do use it there's an
obvious and standard way to do it.  When I search for RTS bugs I know that
at least all the bugs I'm seeing are RTS bugs, even if I'm not seeing all
the RTS bugs. People responsible for particular architectures can keep
their metadata up to date to make it easier to manage their ticket lists.

With regards to the last point. This is possible in a more structured
> way. You can create a dashboard with a single query embedded and then
> embed this using standard remarkup syntax.
>
> For example on a project page, I embedded a query which matched
> tickets with "PatternSynonyms" and "newcomer".
>
> http://ec2-52-214-147-146.eu-west-1.compute.amazonaws.com/
> project/profile/165/
>
> You can embed this panel anywhere where remarkup is accepted. For
> example, in a wiki page -
> http://ec2-52-214-147-146.eu-west-1.compute.amazonaws.com/w/ or
> tickets http://ec2-52-214-147-146.eu-west-1.compute.amazonaws.com/T12548
>

Ok, it's good to know that Phabricator can embed queries, but we're not
planning to move the wiki, correct?


> It is a bit more heavyweight to setup but much easier to get right due
> to the structured editing interface which trac doesn't provide for
> these kinds of queries.
>
> Matt
>
> On Tue, Jan 24, 2017 at 9:41 AM, Simon Marlow <marlo...@gmail.com> wrote:
> > On 21 January 2017 at 22:21, Matthew Pickering <
> matthewtpicker...@gmail.com>
> > wrote:
> >>
> >> Hello devs,
> >>
> >> Thanks to everyone so far who has looked at and commented on the
> >> prototype. It seems that the response is generally positive so I would
> >> like to drive the process forwards.
> >>
> >> In order for that to happen, someone needs to decide whether we as a
> >> community think it is a good idea. It seems to make sense if those who
> >> use the tracker most make this decision so I propose that Simon and
> >> Ben should ultimately be the ones to do this.
> >>
> >> Therefore, I propose this timeline
> >>
> >> 1. Before 11th Feb (3 weeks from today) we decide whether we want to
> >> migrate the issue tracker.
> >> 2. A working group is established who will work through the details of
> >> the migration with the minimum of a final prototype built from a clone
> >> of the actual installation.
> >> 3. Migration would happen before the end of March.
> >
> >
> > Sounds good to me.  I personally have only glanced at it so far, but I'll
> > give it some attention.  I'm pretty attached to Trac's ability to do
> complex
> > queries on tickets and the ability to embed ticket queries into wiki
> pages,
> > so the gains would have to be compelling to outweigh the losses for me.
> But
> > I'll give it a closer look.
> >
> > Cheers
> > Simon
> >
> >>
> >> I think Ben summarised the discussions quite well on the wiki page -
> >> https://ghc.haskell.org/trac/ghc/wiki/Phabricator/Maniphest
> >>
> >> And the prototype continues to exist here.
> >> http://ec2-52-214-147-146.eu-west-1.compute.amazonaws.com/
> >>
> >> As always, any comments welcome.
> >>
> >> Matt
> >> ___
> >> ghc-devs mailing list
> >> ghc-devs@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >
> >
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Next steps of the trac-to-maniphest migration?

2017-01-24 Thread Simon Marlow
On 21 January 2017 at 22:21, Matthew Pickering 
wrote:

> Hello devs,
>
> Thanks to everyone so far who has looked at and commented on the
> prototype. It seems that the response is generally positive so I would
> like to drive the process forwards.
>
> In order for that to happen, someone needs to decide whether we as a
> community think it is a good idea. It seems to make sense if those who
> use the tracker most make this decision so I propose that Simon and
> Ben should ultimately be the ones to do this.
>
> Therefore, I propose this timeline
>
> 1. Before 11th Feb (3 weeks from today) we decide whether we want to
> migrate the issue tracker.
> 2. A working group is established who will work through the details of
> the migration with the minimum of a final prototype built from a clone
> of the actual installation.
> 3. Migration would happen before the end of March.
>

Sounds good to me.  I personally have only glanced at it so far, but I'll
give it some attention.  I'm pretty attached to Trac's ability to do
complex queries on tickets and the ability to embed ticket queries into
wiki pages, so the gains would have to be compelling to outweigh the losses
for me.  But I'll give it a closer look.

Cheers
Simon


> I think Ben summarised the discussions quite well on the wiki page -
> https://ghc.haskell.org/trac/ghc/wiki/Phabricator/Maniphest
>
> And the prototype continues to exist here.
> http://ec2-52-214-147-146.eu-west-1.compute.amazonaws.com/
>
> As always, any comments welcome.
>
> Matt
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: StablePtr / StableName ?

2017-01-24 Thread Simon Marlow
StableNames do use the RTS hash table implementation, but StablePtr does
*not*, the ticket is incorrect.  But to be clear, nothing has changed -
StableName has always used this hash table implementation.  No doubt it
could be faster if we used a better hash table, but whether it matters to
you or not depends on what else your application is doing - is StableName
in the inner loop? You'd have to measure it.

Cheers
Simon

On 22 January 2017 at 16:09, Johannes Waldmann <
johannes.waldm...@htwk-leipzig.de> wrote:

> Dear ghc devs,
>
> would the StablePtr performance issue (slow hash table)
> https://ghc.haskell.org/trac/ghc/ticket/13165
> also affect StableNames?
> Cf. https://github.com/ekmett/ersatz/issues/30
>
> Could making 10^5 stable names, and accessing each just once,
> take noticeable time? Where would this show up in a profile?
>
> I guess there's no easy way to change the ersatz library
> (StableName this is the fundamental mechanism for detecting sharing)
> but if these issues are related, then ersatz provides a
> performance test case.
>
> Thanks, Johannes.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Including remote-iserv upstream?

2017-01-16 Thread Simon Marlow
Absolutely, let's get this code upstream.  Just put it up on Phabricator
and I'll be happy to review.

I recall that we wanted to split up the ghci lib into modules that are
compiled with stage0 (the client) and modules compiled with stage1 (the
server).  Is that a part of your plans?  I think it would be a good cleanup.

Cheers
Simon

On 14 January 2017 at 15:34, Shea Levy  wrote:

> Hi Simon, devs,
>
> As part of my work to get TH working when cross-compiling to iOS, I've
> developed remote-iserv [1] (not yet on hackage), a set of libraries for
> letting GHC communicate with an external interpreter that may be on
> another machine. So far, there are only three additions of note on top
> of what the ghci library offers:
>
> 1. The remote-iserv protocol has facilities for the host sending
>archives and object files the target doesn't have (dynlibs not yet
>implemented but there's no reason they can't be). This works by
>having the server send back a Bool after a loadObj or loadArchive
>indicating whether it needs the object sent, and then just reading it
>off the Pipe.
> 2. The remote-iserv lib abstracts over how the Pipe it communicates over
>is obtained. One could imagine e.g. an ssh-based implementation that
>just uses stdin and stdout* for the communication, the implementation
>I've actually tested on is a TCP server advertised over bonjour.
> 3. There is a protocol version included to address forwards
>compatibility concerns.
>
> As the library currently stands, it works for my use case. However,
> there would be a number of benefits if it were included with ghc (and
> used for local iserv as well):
>
> 1. Reduced code duplication (the server side copies iserv/src/Main.hs
>pretty heavily)
> 2. Reduced overhead keeping up to date with iserv protocol changes
> 3. No need for an extra client-side process, GHC can just open the Pipe
>itself
> 4. Proper library distribution in the cross-compiling case. The client
>needs to be linked with the ghci lib built by the stage0 compiler, as
>it runs on the build machine, while the server needs to be linked
>with the ghci lib built by the stage1 compiler. With a distribution
>created by 'make install', we only get the ghci lib for the
>target. Currently, I'm working around this by just using the ghci lib
>of the bootstrap compiler, which in my case is built from the same
>source checkout, but of course this isn't correct. If these libs were
>upstream, we'd only need one version of the client lib exposed and
>one version of the server lib exposed and could have them be for the
>build machine and the target, respectively
> 5. Better haskell hackers than I invested in the code ;)
>
> Thoughts on this? Would this be welcome upstream in some form?
>
> Thanks,
> Shea
>
> * Note that, in the general case, having the server process's stdio be
>   the same as the compiler's (as we have in the local-iserv case) is not
>   possible. Future work includes adding something to the protocol to
>   allow forwarding stdio over the protocol pipe, to make GHCi usable
>   without watching the *server*'s console.
>
> [1]: https://github.com/obsidiansystems/remote-iserv
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Navigating GHC proposals

2017-01-09 Thread Simon Marlow
Well, you can go to the history of the file, and from there to the first
commit ("Rename proposal file"), and from there you'll see a link to the
pull request in the blue box next to the name of the branch (the link looks
like "#32" in this case).

But really, I wouldn't recommend sending the rendered link to someone, send
the link to the pull request.



On 9 January 2017 at 16:05, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> I don't think there is a way to go from the rendered proposal to the pull
> request, other than the "back" button in your browser.
>
>
>
> Seriously?  But the rendered proposal is the useful link to send to
> people.  There _*must_ *be a way, even if its indirect.
>
>
>
> Simon
>
>
>
> *From:* Simon Marlow [mailto:marlo...@gmail.com]
> *Sent:* 09 January 2017 16:03
> *To:* Simon Peyton Jones <simo...@microsoft.com>
> *Cc:* ghc-devs@haskell.org; Richard Eisenberg <r...@cs.brynmawr.edu>
> *Subject:* Re: Navigating GHC proposals
>
>
>
> I don't think there is a way to go from the rendered proposal to the pull
> request, other than the "back" button in your browser.
>
>
>
> The constraint-vs-type proposal seems a little bit weird in that it
> actually has a branch in the ghc-proposals repository itself, rather than
> being a pull request from a fork in @goldfire's account.  Richard, was that
> intentional?
>
>
>
> On 9 January 2017 at 13:55, Simon Peyton Jones via ghc-devs <
> ghc-devs@haskell.org> wrote:
>
> Once I am looking the rendered form of a GHC proposal, eg
>
> https://github.com/ghc-proposals/ghc-proposals/blob/
> rae/constraint-vs-type/proposals/-constraint-vs-type.rst
> <https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc-proposals%2Fghc-proposals%2Fblob%2Frae%2Fconstraint-vs-type%2Fproposals%2F-constraint-vs-type.rst=02%7C01%7Csimonpj%40microsoft.com%7C79cf69fc14654d88648e08d438a90a1c%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636195746098640774=vFOdPskyztyhQRRDIUHq0KMipo62WuWHc6NR0PTXLEY%3D=0>
>
> how can I find my way to the “conversation” for that proposal, so I can
> comment on it?
>
> https://github.com/ghc-proposals/ghc-proposals/pull/32
> <https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com%2Fghc-proposals%2Fghc-proposals%2Fpull%2F32=02%7C01%7Csimonpj%40microsoft.com%7C79cf69fc14654d88648e08d438a90a1c%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636195746098640774=WIDk8KnNJ6dpm4q3K%2BUyGt4E8LuSmS%2F29cYpCv7GZnk%3D=0>
>
>
>
> Once more, I am lost in a maze of twisty little Githup passages.  I
> clearly have not yet internalised an accurate model of what Github is
> thinking
>
> Thanks
>
> Simon
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> <https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs=02%7C01%7Csimonpj%40microsoft.com%7C79cf69fc14654d88648e08d438a90a1c%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636195746098640774=FMTamv6wS3PdKU1yOSfTnnQfPOlU03EfNx%2B%2BvhWZN4w%3D=0>
>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Debugging GHC with GHCi

2017-01-09 Thread Simon Marlow
On 9 January 2017 at 04:51, Ben Gamari  wrote:

> Thomas Jakway  writes:
>
> > I want to be able to load certain GHC modules in interpreted mode in
> > ghci so I can set breakpoints in them.  I have tests in the testsuite
> > that are compiled by inplace/bin/ghc-stage2 with -package ghc.  I can
> > load the tests with ghc-stage2 --interactive -package ghc but since ghc
> > is compiled I can only set breakpoints in the tests themselves.  Loading
> > the relevant files by passing them as absolute paths to :l loads them
> > but ghci doesn't stop at the breakpoints placed in them (I'm guessing
> > because ghci doesn't realize that the module I just loaded is meant to
> > replace the compiled version in -package ghc).
> >
> > So if I use
> >
> > inplace/bin/ghc-stage2 --interactive -package ghc mytest.hs
> > then
> > :l abs/path/to/AsmCodeGen.hs
> >
> > and set breakpoints, nothing happens.
> >
> Many of us would love to be able to load GHC into GHCi. Unfortunately,
> we aren't currently in a position where this is possible. The only thing
> standing in our way is the inability of GHC's interpreter to run modules
> which use unboxed tuples. While there are a few modules within GHC which
> use unboxed tuples, none of them are particularly interesting for
> debugging purposes, so compiling them with -fobject-code should be fine.
> In principle this could be accomplished by,
>
> {-# OPTIONS_GHC -fobject-code #-}
>
> However, as explained in #10965, GHC sadly does not allow this. I spent
> a bit of time tonight trying to see if I could convince GHC to first
> manually build object code for the needed modules, and then load
> bytecode for the rest. Unfortunately recompilation checking fought me at
> every turn.
>
> The current state of my attempt can be found here [1]. It would be great
> if someone could pick it up. This will involve,
>
>  * Working out how to convince the GHC to use the object code for
>utils/Encoding.o instead of recompiling
>
>  * Identifying all of the modules which can't be byte-code compiled and
>add them to $obj_modules
>
>  * Chassing down whatever other issues that might pop up along the way
>
> I also wouldn't be surprised if you would need this GHC patch [2].
>

I would have thought that something like

:set -fobject-code
:load Main  -- or whatever
-- modify some source file
:set -fbyte-code
:load Main

should do the right thing, loading object code when it can, up to the first
module that has been modified more recently.  Of course you can't have any
object code modules that depend on byte-code modules, so if you modify
something too low down in the dependency graph then you'll have a lot of
interpreted modules, and you may end up trying to interpret something that
can't be interpreted because it has an unboxed tuple.  But for simple tests
it ought to work.  (I haven't tried this so I'm probably forgetting
something...)

Cheers
Simon



>
> Cheers,
>
> - Ben
>
>
> [1] https://gist.github.com/bgamari/bd53e4fd6f3323599387ffc7b11d1a1e
> [2] http://git.haskell.org/ghc.git/commit/326931db9cdc26f2d47657c1f084b9
> 903fd46246
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Navigating GHC proposals

2017-01-09 Thread Simon Marlow
I don't think there is a way to go from the rendered proposal to the pull
request, other than the "back" button in your browser.

The constraint-vs-type proposal seems a little bit weird in that it
actually has a branch in the ghc-proposals repository itself, rather than
being a pull request from a fork in @goldfire's account.  Richard, was that
intentional?

On 9 January 2017 at 13:55, Simon Peyton Jones via ghc-devs <
ghc-devs@haskell.org> wrote:

> Once I am looking the rendered form of a GHC proposal, eg
>
> https://github.com/ghc-proposals/ghc-proposals/blob/
> rae/constraint-vs-type/proposals/-constraint-vs-type.rst
>
> how can I find my way to the “conversation” for that proposal, so I can
> comment on it?
>
> https://github.com/ghc-proposals/ghc-proposals/pull/32
>
>
>
> Once more, I am lost in a maze of twisty little Githup passages.  I
> clearly have not yet internalised an accurate model of what Github is
> thinking
>
> Thanks
>
> Simon
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Compile GHC with -prof to get a stack trace on panic

2016-12-15 Thread Simon Marlow
I think this has been mentioned before but it's probably not widely known:
if you compile GHC profiled (that is, enable GhcProfiled=YES in your mk/
build.mk), then every panic comes with a stack trace.  Here's one I just
saw:

ghc-stage2: panic! (the 'impossible' happened)
  (GHC version 8.1.20161206 for x86_64-unknown-linux):
Ix{Int}.index: Index (65536) out of range ((0,28))
CallStack (from -prof):
  HscTypes.bin_fixities (compiler/main/HscTypes.hs:1050:51-56)
  HscMain.checkOldIface (compiler/main/HscMain.hs:(586,20)-(587,60))
  HscMain.hscIncrementalFrontend (compiler/main/HscMain.hs:(556,1)-(618,81))
  HscMain.hscIncrementalCompile (compiler/main/HscMain.hs:(644,1)-(699,32))
  GHC.withCleanupSession (compiler/main/GHC.hs:(464,1)-(473,27))
  GHC.runGhc (compiler/main/GHC.hs:(439,1)-(444,26))
  GHC.defaultErrorHandler (compiler/main/GHC.hs:(379,1)-(411,7))

To get more detail in the stack trace you need to add

  GhcStage2HcOpts += -fprof-auto-top

Or -fprof-auto, depending on how much detail you want.

Cheers
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Making (useful subsets of) bytecode portable between targets

2016-11-25 Thread Simon Marlow
On 25 November 2016 at 07:23, Moritz Angermann <mor...@lichtzwerge.de>
wrote:

[snip]


> To get this back on topic, if we have a architecture independent
> interpretable bytecode,
> for ghc, could we sidestep the runner solution altogether and have TH for
> the target
> be evaluated on the host?  Is this what Shea initially wanted to go after?
>

Yes, but architecture-independent bytecode is the least of the problems.
Doing this properly is a really big change.

We basically have two worlds: first, the compile-time world. In this world,
we need all the packages and modules of the current package built for the
host platform. Secondly, we need the runtime world, with all the packages
and modules of the current package cross-compiled for the target platform.

When compiling a module that uses TH, we need to
- compile it as if we were compiling for the host platform, reading .hi
files from the host world
- run the TH code in the host world
- restart the compilation, using the .hi files from the target world, and
the results of running the splices

But even this isn't going to be enough.  What if your code imports some
modules that are only available on the runtime platform? iOS APIs, for
example.  The right thing is to have a clean separation between runtime
imports and compile-time imports.  Perhaps we just annotate some imports to
say they aren't needed at compile-time for running the TH code.  but then
we also need compile-time vs. runtime build-depends in our .cabal files,
and so on.

This is just off the top of my head, I'm sure there are more complexities I
haven't thought about.

Its a big project, but ultimately we do have to tackle it, because it's the
right thing to do.  Anyone interested in working on this?  Maybe start a
new proposal to flesh out the details.

Cheers
Simon



> cheers,
>  moritz
>
> > On Nov 25, 2016, at 2:38 PM, Manuel M T Chakravarty <
> c...@justtesting.org> wrote:
> >
> > Ok, I am not saying that it is technical impossible. I am saying that it
> is *impractical*.
> >
> > Imagine Travis CI needing to run stuff on my phone that is attached to
> my Mac (if we are lucky), which is behind NAT somewhere in Australia.
> >
> > Running stuff in the simulator during a build would be pretty awkward,
> but running it on the device is not practical.
> >
> > Manuel
> >
> > PS: BTW, shipping binary code to the device means it has to be code
> signed using a distribution profile of a registered developer. That is one
> thing if Xcode does all the magic behind the scenes, but do you really want
> to make that part of the GHC build process?
> >
> >> Edward Z. Yang <ezy...@mit.edu>:
> >>
> >> At least for Travis, you can generate a private key that only Travis
> >> has access to, and use this to authenticate access to the runner.
> >> See https://docs.travis-ci.com/user/encryption-keys/
> >>
> >> Edward
> >>
> >> Excerpts from Manuel M T Chakravarty's message of 2016-11-24 16:38:34
> +1100:
> >>> If you use Travis CI or such, do you really want to have a runner
> accessible from an arbitrary host on the Internet?
> >>>
> >>>> Moritz Angermann <mor...@lichtzwerge.de>:
> >>>>
> >>>> It's certainly far from ideal, but for CI, what obstacles are there
> besides needing a runner accessible from cross compiling machine?
> >>>>
> >>>> E.g. Start the runner app on an iPhone plugged in into a USB power
> source and leave it there?
> >>>>
> >>>> Sent from my iPhone
> >>>>
> >>>>> On 24 Nov 2016, at 12:42 PM, Manuel M T Chakravarty <
> c...@justtesting.org> wrote:
> >>>>>
> >>>>> Sorry, but I don’t think running on the device is practical. How do
> you want to do CI, for example?
> >>>>>
> >>>>> Manuel
> >>>>>
> >>>>>> Moritz Angermann <mor...@lichtzwerge.de>:
> >>>>>>
> >>>>>>
> >>>>>>> On Nov 23, 2016, at 7:50 PM, Simon Marlow <marlo...@gmail.com>
> wrote:
> >>>>>>>
> >>>>>>> […]
> >>>>>>>
> >>>>>>> My question would be: are you *sure* you can't run target code at
> compile time?  Not even with an iphone simulator?
> >>>>>>
> >>>>>> This should be possible. However for proper development one would
> need to run on the
> >>>>>> device (iPhone, iPad, …) for armv7 or arm64, as the Simulator is
> i386 or x86_64.
> >>>>>>
>

Re: DWARF patches for 8.2

2016-11-23 Thread Simon Marlow
Awesome stuff Ben.  I'll try to find some time to review these.

On 22 November 2016 at 06:18, Ben Gamari  wrote:

> Hello fellow DWARF enthusiasts,
>
> Tonight I finally made something of a breakthrough on the DWARF front;
> after finding a small logic error in one of my patches I was able to get
> a full stack trace into and out of Haskell using the runtime system's
> native stack unwinder. This is quite exciting!
>
> Recall that up until now there have been a few issues which can lead to
> problems with unwinding,
>
>  * #11353: Unsafe foreign calls can require the NCG to make stack
>pointer adjustments to accomodate native calling conventions. These
>adjustments need to be taken into account when we generate unwinding
>information.
>
>  * #11337: Stack fixups produced by CmmStackLayout aren't reflected in
>unwinding information. Essentially this was a result of the fact that
>our current unwinding implementation assumes that stack layout is
>fixed over the course of a block.
>
>  * #11338: The region surrounding safe foreign calls doesn't get proper
>unwinding information.
>
> I've solved all three of these in my branch, which I've rebased, split
> up, and posted to Phabricator. The result is quite a stack of
> differentials,
>
>  * D2740: OrdList: Add Foldable, Traversable instances
>
>Some throat-clearing.
>
>  * D2735: Use newBlockId instead of newLabelC
>
>Just some refactoring.
>
>  * D2737: NCGMonad: Add MonadUnique NatM instance
>
>This will come in handy later.
>
>  * D2736: AsmCodeGen: Refactor worker in cmmNativeGens
>
>More refactoring I did while trying to understand the dataflow in the
>NCG.
>
>  * D2739: CmmCommonBlockElim: Ignore CmmUnwind nodes
>
>This is a fix to what I believe is a bug which I noticed while
>reading through the implementation.
>
>  * D2741: Generalize CmmUnwind and pass unwind information through NCG
>
>This is the bulk of the change. Here we refactor the treatment of
>unwinding information to provide the flexibility we will need to
>address the issues described above and fix #11353. Review is badly
>needed here.
>
>  * D2742: CmmLayoutStack: Add unwind information on stack fixups
>
>Here we use the infrastructure provided in D2741 to fix #11337.
>
>  * D2743: StgCmmForeign: Emit debug information for safe foreign calls
>
>Here we fix #11338 by adding unwind information to the safe foreign
>call prologue/epilogue code.
>
>  * D2738: Cmm: Add support for undefined unwinding statements
>
>Fix unwinding information for stg_stack_underflow_frames, which we
>have no means of unwinding out of. For this we need to add support
>for unwinding declarations which tell the underwinder to "forget"
>about the value of a register.
>
> Reviews would be greatly appreciated.
>
> Cheers,
>
>  - Ben
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: T12041 failing?

2016-11-14 Thread Simon Marlow
Ok, so I think we should mark the test as expect_broken, because the Travis
builds use -DDEBUG and this is causing them to fail currently (see e.g.
https://travis-ci.org/simonmar/ghc/builds/174768018)

Cheers
Simon

On 11 November 2016 at 17:39, Simon Peyton Jones <simo...@microsoft.com>
wrote:

> Hmm.  Yes, this is an (actually harmless) assertion failure if your build
> has -DDEBUG on.  I think it’s just a fluke that it’s only just started
> failing.
>
>
>
> I’ll make a ticket for it; I don’t think it’s super-urgent.
>
>
>
> Simon
>
>
>
> *From:* ghc-devs [mailto:ghc-devs-boun...@haskell.org] *On Behalf Of *Simon
> Marlow
> *Sent:* 09 November 2016 13:03
> *To:* ghc-devs@haskell.org
> *Subject:* T12041 failing?
>
>
>
> I just saw the error below in a validate with -DDEBUG.  Anyone know about 
> this?
>
> --- /tmp/ghctest-uhJ8rt/test   
> spaces/./indexed-types/should_fail/T12041.run/T12041.stderr.normalised   
> 2016-11-09 12:13:38.206501840 +
>
> +++ /tmp/ghctest-uhJ8rt/test   
> spaces/./indexed-types/should_fail/T12041.run/T12041.comp.stderr.normalised  
> 2016-11-09 12:13:38.206501840 +
>
> @@ -1,7 +1,17 @@
>
> +ghc: panic! (the 'impossible' happened)
>
> +  (GHC version 8.1.20161109 for x86_64-unknown-linux):
>
> +  ASSERT failed!
>
> +  i_axb
>
> +  Call stack:
>
> +  CallStack (from HasCallStack):
>
> +prettyCurrentCallStack, called at 
> compiler/utils/Outputable.hs:: in :Outputable
>
> +callStackDoc, called at compiler/utils/Outputable.hs:: 
> in :Outputable
>
> +assertPprPanic, called at 
> compiler/typecheck/TcType.hs:: in :TcType
>
> +  Call stack:
>
> +  CallStack (from HasCallStack):
>
> +prettyCurrentCallStack, called at 
> compiler/utils/Outputable.hs:: in :Outputable
>
> +callStackDoc, called at compiler/utils/Outputable.hs:: 
> in :Outputable
>
> +pprPanic, called at compiler/utils/Outputable.hs:: in 
> :Outputable
>
> +assertPprPanic, called at 
> compiler/typecheck/TcType.hs:: in :TcType
>
>  -T12041.hs:12:15:
>
> - Expected kind ‘i -> Constraint’,
>
> -but ‘(~) Int’ has kind ‘* -> Constraint’
>
> - In the type ‘(~) Int’
>
> -  In the type instance declaration for ‘Ob’
>
> -  In the instance declaration for ‘Category I’
>
> +Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug 
> <https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fwww.haskell.org%2Fghc%2Freportabug=02%7C01%7Csimonpj%40microsoft.com%7C8af7a5deff5f49d2ab9808d408a0bd62%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636142933860965747=BUkCjhjy1GhK9SVcws2TAYIVD5FzdsYrXKciuyD6MzM%3D=0>
>
> *** unexpected failure for T12041(normal)
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


T12041 failing?

2016-11-09 Thread Simon Marlow
I just saw the error below in a validate with -DDEBUG.  Anyone know about this?

--- /tmp/ghctest-uhJ8rt/test
spaces/./indexed-types/should_fail/T12041.run/T12041.stderr.normalised  
2016-11-09
12:13:38.206501840 +
+++ /tmp/ghctest-uhJ8rt/test
spaces/./indexed-types/should_fail/T12041.run/T12041.comp.stderr.normalised 
2016-11-09
12:13:38.206501840 +
@@ -1,7 +1,17 @@
+ghc: panic! (the 'impossible' happened)
+  (GHC version 8.1.20161109 for x86_64-unknown-linux):
+   ASSERT failed!
+  i_axb
+  Call stack:
+  CallStack (from HasCallStack):
+prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:: in
:Outputable
+callStackDoc, called at
compiler/utils/Outputable.hs:: in
:Outputable
+assertPprPanic, called at
compiler/typecheck/TcType.hs:: in :TcType
+  Call stack:
+  CallStack (from HasCallStack):
+prettyCurrentCallStack, called at
compiler/utils/Outputable.hs:: in
:Outputable
+callStackDoc, called at
compiler/utils/Outputable.hs:: in
:Outputable
+pprPanic, called at
compiler/utils/Outputable.hs:: in
:Outputable
+assertPprPanic, called at
compiler/typecheck/TcType.hs:: in :TcType

-T12041.hs:12:15:
- Expected kind ‘i -> Constraint’,
-but ‘(~) Int’ has kind ‘* -> Constraint’
- In the type ‘(~) Int’
-  In the type instance declaration for ‘Ob’
-  In the instance declaration for ‘Category I’
+Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
*** unexpected failure for T12041(normal)
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: setnumcapabilities001 failure

2016-10-28 Thread Simon Marlow
I see, but the compiler has no business caching things across
requestSync(), which can in principle change anything: even if the compiler
could see all the code, it would find a pthread_condwait() in there.

Anyway I've found the problem - it was caused by a subsequent GC
overwriting the values of gc_threads[].idle before the previous GC had
finished releaseGCThreads() which reads those values.  Diff on the way...

Cheers
Simon

On 28 October 2016 at 11:58, Ryan Yates <fryguy...@gmail.com> wrote:

> Right, it is compiler effects at this boundary that I'm worried about,
> values that are not read from memory after the changes have been made, not
> memory effects or data races.
>
> On Fri, Oct 28, 2016 at 3:02 AM, Simon Marlow <marlo...@gmail.com> wrote:
>
>> Hi Ryan, I don't think that's the issue.  Those variables can only be
>> modified in setNumCapabilities, which acquires *all* the capabilities
>> before it makes any changes.  There should be no other threads running RTS
>> code(*) while we change the number of capabilities.  In particular we
>> shouldn't be in releaseGCThreads while enabled_capabilities is being
>> changed.
>>
>> (*) well except for the parts at the boundary with the external world
>> which run without a capability, such as rts_lock() which acquires a
>> capability.
>>
>> Cheers
>> Simon
>>
>> On 27 Oct 2016 17:10, "Ryan Yates" <fryguy...@gmail.com> wrote:
>>
>>> Briefly looking at the code it seems like several global variables
>>> involved should be volatile: n_capabilities, enabled_capabilities, and
>>> capabilities.  Perhaps in a loop like in scheduleDoGC the compiler moves
>>> the reads of n_capabilites or capabilites outside the loop.  A failed
>>> requestSync in that loop would not get updated values for those global
>>> pointers.  That particular loop isn't doing that optimization for me, but I
>>> think it could happen without volatile.
>>>
>>> Ryan
>>>
>>> On Thu, Oct 27, 2016 at 9:18 AM, Ben Gamari <b...@smart-cactus.org>
>>> wrote:
>>>
>>>> Simon Marlow <marlo...@gmail.com> writes:
>>>>
>>>> > I haven't been able to reproduce the failure yet. :(
>>>> >
>>>> Indeed I've also not seen it in my own local builds. It's quite an
>>>> fragile failure.
>>>>
>>>> Cheers,
>>>>
>>>> - Ben
>>>>
>>>>
>>>> ___
>>>> ghc-devs mailing list
>>>> ghc-devs@haskell.org
>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>>
>>>>
>>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: setnumcapabilities001 failure

2016-10-28 Thread Simon Marlow
Hi Ryan, I don't think that's the issue.  Those variables can only be
modified in setNumCapabilities, which acquires *all* the capabilities
before it makes any changes.  There should be no other threads running RTS
code(*) while we change the number of capabilities.  In particular we
shouldn't be in releaseGCThreads while enabled_capabilities is being
changed.

(*) well except for the parts at the boundary with the external world which
run without a capability, such as rts_lock() which acquires a capability.

Cheers
Simon

On 27 Oct 2016 17:10, "Ryan Yates" <fryguy...@gmail.com> wrote:

> Briefly looking at the code it seems like several global variables
> involved should be volatile: n_capabilities, enabled_capabilities, and
> capabilities.  Perhaps in a loop like in scheduleDoGC the compiler moves
> the reads of n_capabilites or capabilites outside the loop.  A failed
> requestSync in that loop would not get updated values for those global
> pointers.  That particular loop isn't doing that optimization for me, but I
> think it could happen without volatile.
>
> Ryan
>
> On Thu, Oct 27, 2016 at 9:18 AM, Ben Gamari <b...@smart-cactus.org> wrote:
>
>> Simon Marlow <marlo...@gmail.com> writes:
>>
>> > I haven't been able to reproduce the failure yet. :(
>> >
>> Indeed I've also not seen it in my own local builds. It's quite an
>> fragile failure.
>>
>> Cheers,
>>
>> - Ben
>>
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Linker reorganization

2016-10-28 Thread Simon Marlow
On 28 October 2016 at 02:33, Ben Gamari  wrote:

> Hello RTS people,
>
> Today I finally grew frustrated enough with my constant battle with the
> 7000 line tangle of CPP that is rts/Linker.c to do something about it.
> The result is D2643 through D2650. In short, I took the file and chopped
> it into more managable pieces:
>
>  * linker/PEi386.[ch]:   PE loading
>  * linker/MachO.[ch]:MachO loading
>  * linker/Elf.[ch]:  ELF loading
>  * linker/CacheFlush.[ch]:   Platform-specific icache flushing logic
>  * linker/SymbolExtras.[ch]: Symbol extras support logic
>  * Linker.c: Everything necessary to glue all of the above
> together
>  * LinkerInternals.h:Declarations shared by the above and
>  declarations for Linker.c
>
> For the most part this involved just shuffling code around since there
> was some rough platform abstraction already in place. In fact, I tried
> quite hard to avoid performing any more intricate refactoring to keep
> the scope of the project in check. Consequently, this is only a start
> and the design is in places a bit awkward; there is still certainly no
> shortage of work remaining to be done. Regardless, I think this change
> an improvement over the current state of affairs.
>
>
I haven't looked through all the patches, but this is a great step
forwards, thanks Ben!


> One concern that I have is that the RTS's header file structure (where
> everything is #include'd via Rts.h) doesn't work very well for this
> particular use, where we have a group of headers specific to a
> particular subsystem (e.g. linker/*.h). Consequently, these header files
> currently lack enclosing `extern "C"` blocks (as well as
> Begin/EndPrivate blocks). It would be easy to add these, but I was
> curious to hear if others had any better ideas.
>
>
Not sure I understand the problem.  Rts.h is for *public* APIs, those that
are accessible outside the RTS, but these APIs are mostly *internal*.  The
public-facing linker API is in includes/rts/Linker.h.

We don't need extern "C" in the internal header files because we're never
going to include these from C++ (we do in the external ones though). But we
should have BeginPrivate.h/EndPrivate.h in the internal headers.

Cheers
Simon



> The refactoring was performed over several small-ish commits, so review
> shouldn't be so bad. I expect to rebase the LoadArchive.c refactoring
> performed in D2642 on top of this set once it has been merged. I will
> also offer to rebase DemiMarie's recent error-handling patch (D2652).
>
> I have tested the set on a variety of platforms,
>
>  * x86-64 Linux
>  * x86-64 Darwin
>  * x86-64 FreeBSD
>  * x86-64 Windows
>  * ARM Linux
>
> What do you think?
>
> Cheers,
>
> - Ben
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Default options for -threaded

2016-10-21 Thread Simon Marlow
On 8 October 2016 at 17:55, Ben Gamari  wrote:

> loneti...@gmail.com writes:
>
> > Hi All,
> >
> > A user on https://ghc.haskell.org/trac/ghc/ticket/11054 has asked why
> > -N -qa isn’t the default for -threaded.
> >
> I'm not sure that scheduling on all of the cores on the user's machine by
> default is a good idea, especially given that our users have
> learned to expect the existing default. Enabling affinity by default
> seems reasonable if we have evidence that it helps the majority of
> applications, but we would first need to introduce an additional
> flag to disable it.
>

Affinity is almost always a bad idea in my experience.


> In general I think -N1 is a reasonable default as it acknowledges the
> fact that deploying parallelism is not something that can be done
> blindly in many (most?) applications. To make effective use of
> parallelism the user needs to understand their hardware, their
> application, and its interaction with the runtime system and configure
> the RTS appropriately.
>
>
Agree on keeping -N1.

Related to this, I think it's about time we made -threaded the default.  We
could add a -single-threaded option to get back the old behaviour.

There is a small overhead to using -threaded, but -threaded is also
required to make a lot of things work (e.g. waitForProcess in a
multithreaded program, not to mention parallelism).

Anyone interested in doing this?

Cheers
Simon



> Of course, this is just my two-cents.
>
> Cheers,
>
> - Ben
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Better X87

2016-10-21 Thread Simon Marlow
I believe that comment goes even further back - it was probably Julian
Seward who worked on the x86 code generator around 1999, if I recall
correctly.

​
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Compact regions in users guide

2016-10-21 Thread Simon Marlow
Yes we need some docs.  But I expect the API to change before we're done
with the implementation (it isn't really usable in its current state), so
I'm deferring the docs until things settle down.

Cheers
Simon

On 17 October 2016 at 18:32, Ben Gamari  wrote:

> Hello Compact Regions authors,
>
> It occurs to me that the compact regions support that is due to be
> included in GHC 8.2 is lacking any discussion in the users guide. At
> very least we should have a mention in the release notes (this is one of
> the major features of 8.2, afterall) and a brief overview of the feature
> elsewhere. It's a bit hard saying where the overview would fit
> (parallel.rst is an option, albeit imperfect; glasgow_exts.rst is
> another). I'll leave this up to you.
>
> I've opened #12413 [1] to track this task. Do you suppose one of you
> could take a few minutes to finish this off?
>
> Thanks!
>
> Cheers,
>
> - Ben
>
>
> [1] https://ghc.haskell.org/trac/ghc/ticket/12413
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Dataflow analysis for Cmm

2016-10-21 Thread Simon Marlow
On 16 October 2016 at 14:03, Michal Terepeta 
wrote:

> Hi,
>
> I was looking at cleaning up a bit the situation with dataflow analysis
> for Cmm.
> In particular, I was experimenting with rewriting the current
> `cmm.Hoopl.Dataflow` module:
> - To only include the functionality to do analysis (since GHC doesn’t seem
> to use
>   the rewriting part).
>   Benefits:
>   - Code simplification (we could remove a lot of unused code).
>   - Makes it clear what we’re actually using from Hoopl.
> - To have an interface that works with transfer functions operating on a
> whole
>   basic block (`Block CmmNode C C`).
>   This means that it would be up to the user of the algorithm to traverse
> the
>   whole block.
>

Ah! This is actually something I wanted to do but didn't get around to.
When I was working on the code generator I found that using Hoopl for
rewriting was prohibitively slow, which is why we're not using it for
anything right now, but I think that pulling out the basic block
transformation is possibly a way forwards that would let us use Hoopl.

A lot of the code you're removing is my attempt at "optimising" the Hoopl
dataflow algorithm to make it usable in GHC.  (I don't mind removing this,
it was a failed experiment really)


>   Benefits:
>   - Further simplifications.
>   - We could remove `analyzeFwdBlocks` hack, which AFAICS is just a
> copy
> of `analyzeFwd` but ignores the middle nodes (probably for efficiency
> of
> analyses that only look at the blocks).
>

Aren't we using this in dataflowAnalFwdBlocks, that's used by
procpointAnalysis?

Cheers
Simon

  - More flexible (e.g., the clients could know which block they’re
> processing;
> we could consider memoizing some per block information, etc.).
>
> What do you think about this?
>
> I have a branch that implements the above:
> https://github.com/michalt/ghc/tree/dataflow2/1
> It’s introducing a second parallel implementation (`cmm.Hoopl.Dataflow2`
> module), so that it's possible to run ./validate while comparing the
> results of
> the old implementation with the new one.
>
> Second question: how could we merge this? (assuming that people are
> generally
> ok with the approach) Some ideas:
> - Change cmm/Hoopl/Dataflow module itself along with the three analyses
> that use
>   it in one step.
> - Introduce the Dataflow2 module first, then switch the analyses, then
> remove
>   any unused code that still depends on the old Dataflow module, finally
> remove
>   the old Dataflow module itself.
> (Personally I'd prefer the second option, but I'm also ok with the first
> one)
>
> I’m happy to export the code to Phab if you prefer - I wasn’t sure what’s
> the
> recommended workflow for code that’s not ready for review…
>
> Thanks,
> Michal
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Master recently broke on OS X

2016-10-19 Thread Simon Marlow
It appears to be passing now.  I did commit a sequence of 3 patches, 2 of
which should have been squashed together (my bad) and the intermediate
builds were broken, but the final state was OK except for a failure in
setnumcapabilities001.  I'll try to reproduce that one today.

Cheers
Simon

On 18 October 2016 at 23:08, Ben Gamari  wrote:

> Hello Simon,
>
> It looks like one of the patches that you pushed to master today may
> have broken the build on OS X. According to Harbormaster something in
> the range of f148513ccd93..7129861397f8 caused T5611 to fail on the OS X
> build bot [1]. Could you have a look?
>
> Cheers,
>
> - Ben
>
>
> [1] https://phabricator.haskell.org/harbormaster/build/14220/?l=100
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Improving GHC GC for latency-sensitive networked services

2016-10-18 Thread Simon Marlow
Chris,

There are a few things here.

- There are different levels of latency-sensitivity.  The system I work on
at Facebook is latency sensitive and we have no problem with the GC (after
we implemented a few optimisations and did some tuning).  But we're ok with
pauses up to 100ms or so, and our average pause time is <50ms with 100MB
live data on large multicore machines.  There's probably still scope to
reduce that some more.

- Thread-local heaps don't fix the pause-time issue.  They reduce the pause
time for a local collection but have no impact on the global collection,
which is still unbounded in size.

- I absolutely agree we should have incremental or concurrent collection.
It's a big project though.  Most of the technology is fairly well
understood (just read
https://www.amazon.co.uk/gp/product/1420082795/ref=pd_bxgy_14_img_2?ie=UTF8=1=P08F0WS4W6Q6Q6K8CSCF)
and I have some vague plans for what direction to take.

- The issue is not so much maintaining multiple GCs.  We already have 3 GCs
(one of which is experimental and unsupported).  The issue is more that a
new kind of GC has non-local implications because it affects read- and
write-barriers, and making a bad tradeoff can penalize the performance of
all code.  Perhaps you're willing to give up 10% of performance to get
guaranteed 10ms pause times, but can we impose that 10% on everyone?  If
not, are you willing to recompile GHC and all your libraries?

Cheers
Simon


On 17 October 2016 at 18:08, Christopher Allen  wrote:

> It'd be unfortunate if more companies trying out Haskell came to the
> same result: https://blog.pusher.com/latency-working-set-ghc-gc-
> pick-two/#comment-2866985345
> (They gave up and rewrote the service in Golang)
>
> Most of the state of the art I'm aware of (such as from Azul Systems)
> is from when I was using a JVM language, which isn't necessarily
> applicable for GHC.
>
> I understand Marlow's thread-local heaps experiment circa 7.2/7.4 was
> abandoned because it penalized performance too much. Does the
> impression that there isn't the labor to maintain two GCs still hold?
> It seems like thread-local heaps would be pervasive.
>
> Does anyone know what could be done in GHC itself to improve this
> situation? Stop-the-world is pretty painful when the otherwise
> excellent concurrency primitives are much of why you're using Haskell.
>
> --- Chris Allen
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: qualified module export

2016-10-13 Thread Simon Marlow
On 11 October 2016 at 18:04, Iavor Diatchki 
wrote:

> Hello,
>
> There may be some more thinking to be done on the design of this feature.
> In particular, if a module `M` has en export declaration `module T`, this
> is not at all the same as adding `import T` in modules exporting `M`.  The
> reason is that meaning of `module T` depends on what is in scope in `M` and
> with what names.For example:
>* `module T` may export only some of the names from `T` (e.g. if `M`
> contains `import T(onlyThisName)`); or,
>* `module T` may export the names from an entirely different module
> (e.g., if `M` contains `import S as T`); or,
>* `module T` may export a combination of multiple modules (e.g., if `M`
> contains `import S1 as T` and `import S2 as T`).
>
> So, I would expect an export of the form `qualified module T as X` to work
> in a similar fashion (for the full details on the current semantics you
> could have a look at [1]).
>
> The next issue would be that, currently, entities exported by a module are
> only identified by an unqualified name, and the imports introduce qualified
> names as necessary.  It might make sense to allow modules to also export
> qualified names instead, but then we'd have to decide what happens on the
> importing end.  Presumably, a simple `import M` would now bring both some
> qualified and some unqualified names.  This means that the explicit import
> and hiding lists would have to support qualified names, seems doable.
> However, we'd also have to decide how `import M as X` works, in particular
> how does it affect imported qualified names.  One option would be to have
> `X` replace the qualifier, so if `A.b` is imported via `import M as X`, the
> resulting name would be `X.b`.  Another option would be to have `X` extend
> the qualifier, so `A.b` would become `X.A.b` locally.  Neither seems
> perfect:  the first one is somewhat surprising, where you might
> accidentally "overwrite" a qualifier and introduce name conflicts; the
> second does not allow exported qualified names to ever get shorter.
>
>
Yes, I think this is an important consideration.  It's much simpler if we
can think of the set of names that a module exports as just strings
(possibly containing dots), and an import brings those names into scope,
possibly prepending a qualifier.

That's a simple story, but it doesn't let you change the qualifier at
import time.  The question is, do we think it's important to allow that?

Suppose Data.Text exported the Text type and everything else qualified by
Text: Text.null, Text.concat, etc.

Now you wouldn't be able to rename the qualifier to T if you wanted to.
Many people do this.  Perhaps people would lobby to have
Data.Text.Unqualified so that they could do "import qualified
Data.Text.Unqualified as T", but then we haven't really made anything
better.

Cheers
Simon

I hope this is helpful,
> -Iavor
>
> [1] http://yav.github.io/publications/modules98.pdf
>
>
> On Tue, Oct 11, 2016 at 8:54 AM, Karl Cronburg  wrote:
>
>> Hello,
>>
>> I'm attempting to add support for export of qualified modules (feature
>> request #8043), and any guidance would be greatly appreciated. Namely I'm
>> very familiar with languages / grammars / happy and was easily able to add
>> an appropriate production alternative to Parser.y to construct a new AST
>> node when 'qualified module' is seen in the export list, i.e.:
>>
>> |  'module' modid {% amsu (sLL $1 $> (IEModuleContents $2))
>>   [mj AnnModule $1] }
>> |  'qualified' 'module' qconid --maybeas
>>   {% amsu (sLL $2 $> (IEModuleQualified $3))
>>   [mj AnnQualified $1] }
>>
>> But now I'm lost in the compiler internals. Where should I be looking /
>> focusing on? In particular:
>>
>> - Where do exported identifiers get added to the list of "[LIE Name]" in
>> ExportAccum (in TcRnExports.hs)?
>>
>> Thanks,
>> -Karl Cronburg-
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Create a ghc-simple-patch-propose list? Re: Notes from Ben's "contribute to ghc" discussion

2016-10-05 Thread Simon Marlow
I added a description of the workflow for multiple dependent diffs here:
https://ghc.haskell.org/trac/ghc/wiki/Phabricator#Workingwithmultipledependentdiffs

Please let me know if anything doesn't make sense.  Note that I never let
arc squash my commits, keeping commits 1:1 with diffs makes things a lot
simpler.


On 1 October 2016 at 21:49, Brandon Allbery <allber...@gmail.com> wrote:

> On Sat, Oct 1, 2016 at 4:47 PM, Simon Marlow <marlo...@gmail.com> wrote:
>
>> A nice trick for dealing with stacked diffs in Phabricator is to use "git
>> rebase -i" to modify diffs in the middle of the stack.  You can also insert
>> "x arc diff" between lines to automatically update later diffs on
>> Phabricator after a rebase lower down the stack.
>>
>> You only need a single branch for the whole stack, and continually rebase
>> it.  I also push the whole branch to github to get Travis to build it, but
>> that's optional.
>>
>
> Perhaps someone could put a sample workflow on (one of...) the wiki(s).
>
> --
> brandon s allbery kf8nh   sine nomine
> associates
> allber...@gmail.com
> ballb...@sinenomine.net
> unix, openafs, kerberos, infrastructure, xmonad
> http://sinenomine.net
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Create a ghc-simple-patch-propose list? Re: Notes from Ben's "contribute to ghc" discussion

2016-10-01 Thread Simon Marlow
A nice trick for dealing with stacked diffs in Phabricator is to use "git
rebase -i" to modify diffs in the middle of the stack.  You can also insert
"x arc diff" between lines to automatically update later diffs on
Phabricator after a rebase lower down the stack.

You only need a single branch for the whole stack, and continually rebase
it.  I also push the whole branch to github to get Travis to build it, but
that's optional.

Cheers
Simon

On 29 September 2016 at 03:27, Moritz Angermann 
wrote:

>
> >> Hence you can go wild on your local branches (use what ever
> >> development model suites your needs) and get one final squashed commit
> >> with an extensive summary.
> >>
> > Sure, but this leads to generally unreviewable patches IMHO. In order to
> > stay sane I generally split up my work into a set of standalone patches
> > with git rebase and then create a Diff of each of these commits.
> > Phabricator supports this by having a notion of dependencies between
> > Diffs, but arcanist has no sensible scheme for taking a branch and
> > conveniently producing a series of Diffs.
>
> Yes, this has been a constant source of frustration for us as well. Dealing
> with dependent diffs is just plain painful with arc :( What I usually end
> up
> doing, and I assume that’s what you are describing is:
>
> Turning
>
> A -- B -- C -- D -- E -- F -- origin/master
> ^
> HEAD
>
> into:
>
> branch B1:  E -- F -- origin/master
>   /
> branch B2:  C -- D
>   /
> branch B3: A -- B
>
> and producing three diffs:
>
> $ git checkout E
> $ arc diff origin/master # producing D1
>
> $ git checkout C
> $ arc diff B1 # adding “depends on D1" into the summary field
>
> $ git checkout A
> $ git diff B2 # adding “depends on D2” into the summary field
>
> and then rebase B2 and B3 when changes to D1 on B1 are necessary.
>
> Running `arc patch` with dependent diffs often resulted in trouble;
> this seems to be getting better with the staging areas though.
>
> So clearly we can see there are drawbacks.  All I wanted to say in
> the previous email was essentially that from my experience frustration
> with arc often came from trying to make arc be git.
>
> Cheers,
>  Moritz
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Create a ghc-simple-patch-propose list? Re: Notes from Ben's "contribute to ghc" discussion

2016-09-28 Thread Simon Marlow
Well, let's be careful here.  I like the idea, but it's not a complete
solution for people who don't want to use arc, because you can't revise a
patch after submission in response to reviews, you would have to open a new
PR.

Perhaps you could build something that would allow revisions to PRs too...
that would be cool.

Cheers
Simon

On 28 September 2016 at 03:22, Michael Sloan  wrote:

> Exactly!  So we will be using Phabricator for the review process, but
> with the github PRs you can use plain git.  This means that new
> contributors will only need to learn about phabricator, and arc will
> be non-mandatory though probably recommended.
>
> Glad you like the idea :)
>
> -Michael
>
> On Tue, Sep 27, 2016 at 6:47 PM, Richard Eisenberg 
> wrote:
> > So you're suggesting that GitHub would function as a sort of alternate
> front-end to Phab. While I've grown to enjoy Phab quite a bit, I still
> strongly dislike arc, which tries to be too clever for my tastes. Provided
> the integration works smoothly, I quite like this idea.
> >
> > Richard
> >
> >> On Sep 27, 2016, at 5:32 PM, Michael Sloan  wrote:
> >>
> >> You're welcome Richard!  I look forward to helping make it happen.  In
> >> the other thread, Alexander Vershilov mentioned that we might instead
> >> consider the following more straightforward workflow:
> >>
> >> 0) Have a bot that watches github for PRs.
> >> 1) Submit whatever you want to github as a PR.
> >> 2) It will be automatically closed and migrated to Phabricator.  I
> >> would like it to automatically create a Phabricator account if you do
> >> not already have one.  The message from the bot will tell you about
> >> this action, and explain how to log in, perhaps even linking to
> >> resources about Phabricator.
> >>
> >> Is this worth it?  I think it is for the one-off cases.  However, you
> >> will have to be prepared that this means that people won't have
> >> arcanist setup, and therefore are less likely to actually iterate on
> >> their PR.  Perhaps we should extend this to the following:
> >>
> >> 3) Subsequent pushes to the branch for the PR will update the
> >> Phabricator differential as if you had pushed via Arcanist.  I think
> >> with this in place, we would have a fully streamlined system that
> >> allows people to use their familiar GitHub workflows, without needing
> >> to learn Arcanist.  Interactions would then still occur on , of
> >> course.
> >>
> >> This way, GHC HQ doesn't even need to learn to use this new "ghc-hub"
> >> tool!  Could name the bot that, though!
> >>
> >> Thoughts?  I think it would be great for this to be proposed formally
> >> soon so that we can make it happen.  I am eager to be able to use my
> >> normal git workflows, as my little experience with Arcanist induced
> >> some head-scratching.  Not the fault of the tool, just a result of
> >> lack of familiarity.
> >>
> >> -Michael
> >>
> >> On Tue, Sep 27, 2016 at 8:46 AM, Richard Eisenberg 
> wrote:
> >>> To sum up, this proposes the following:
> >>>
> >>> 1. Allow PRs on GitHub.
> >>>
> >>> 2. Michael Sloan to write a new utility, ghc-hub, which automates
> tasks interfacing between GitHub and Phab. This utility would be used only
> by GHC HQ and not by contributors.
> >>>
> >>> 3. Small GitHub PRs can be merged directly, by ghc-hub.
> >>>
> >>> 4. Larger GitHub PRs can be migrated to Phab by ghc-hub. The
> contributor would be issued a polite email explaining how to set up a Phab
> account to continue to follow their contribution.
> >>>
> >>> Have I captured this accurately? If so, a resounding +1 from me. I’ve
> wanted exactly this for a while.
> >>>
> >>> Is this worth sending through ghc-proposals?
> >>>
> >>> Thanks for volunteering item (2), Michael!
> >>>
> >>> Richard
> >>>
> >>> -=-=-=-=-=-=-=-=-=-=-
> >>> Richard A. Eisenberg
> >>> Asst. Prof. of Computer Science
> >>> Bryn Mawr College
> >>> Bryn Mawr, PA, USA
> >>> cs.brynmawr.edu/~rae
> >>>
>  On Sep 26, 2016, at 11:09 PM, Manuel M T Chakravarty <
> c...@justtesting.org> wrote:
> 
>  Sounds like a great idea to me and might alleviate SimonM’s concerns
> about fragmentation of dev attention.
> 
>  Manuel
> 
> > Michael Sloan :
> >
> > Argh, sent too soon.  The first paragraph, revised:
> >
> > This sounds like an ideal solution, Ben!  As has been discussed many
> > times before, GitHub has many users familiar with its interface.  By
> > allowing GitHub PRs, the initial contribution barrier will be
> lowered. If
> > there is an easy and straightforward process for shifting big patches
> > to Phabricator, then people who are regularly contributing via GitHub
> > PRs can be incrementally on-boarded to the Phabricator / Arcanist
> > workflow.
> >
> > On Mon, Sep 26, 2016 at 12:07 PM, Michael Sloan 
> wrote:
> >> This sounds like an ideal 

  1   2   3   4   5   >