RE: Recognizing default method implementations

2021-12-01 Thread Simon Peyton Jones via ghc-devs
Is there a way to recognize that an Id / Var refers to a default method 
implementation, e.g. $dm/= in the following?

I'm afraid not.  There has never been a reason to do so.  And it might not be 
robust e.g. it might be inlined.

What is the problem you are trying to solve?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Erdi, Gergo via 
ghc-devs
Sent: 01 December 2021 05:22
To: 'GHC' 
Subject: [EXTERNAL] Recognizing default method implementations


PUBLIC

Hi,

Is there a way to recognize that an Id / Var refers to a default method 
implementation, e.g. $dm/= in the following?

$dm/= :: forall a. Eq a => a -> a -> Bool
[GblId, Arity=3, Unf=OtherCon []]
$dm/=
  = \ (@a_ahz)
  ($dEq_sI6 [Occ=Once1] :: Eq a_ahz)
  (x_sI7 [Occ=Once1] :: a_ahz)
  (y_sI8 [Occ=Once1] :: a_ahz) ->
  case == @a_ahz $dEq_sI6 x_sI7 y_sI8 of {
False -> True;
True -> False
  }


Thanks,
Gergo

This email and any attachments are confidential and may also be privileged. If 
you are not the intended recipient, please delete all copies and notify the 
sender immediately. You may wish to refer to the incorporation details of 
Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at 
https: //www.sc.com/en/our-locations

Where you have a Financial Markets relationship with Standard Chartered PLC, 
Standard Chartered Bank and their subsidiaries (the "Group"), information on 
the regulatory standards we adhere to and how it may affect you can be found in 
our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory 
Compliance Disclosures at http: //www.sc.com/rcs/fm

Insofar as this communication is not sent by the Global Research team and 
contains any market commentary, the market commentary has been prepared by the 
sales and/or trading desk of Standard Chartered Bank or its affiliate. It is 
not and does not constitute research material, independent research, 
recommendation or financial advice. Any market commentary is for information 
purpose only and shall not be relied on for any other purpose and is subject to 
the relevant disclaimers available at https: 
//www.sc.com/en/regulatory-disclosures/#market-disclaimer.

Insofar as this communication is sent by the Global Research team and contains 
any research materials prepared by members of the team, the research material 
is for information purpose only and shall not be relied on for any other 
purpose, and is subject to the relevant disclaimers available at https: 
//research.sc.com/research/api/application/static/terms-and-conditions.

Insofar as this e-mail contains the term sheet for a proposed transaction, by 
responding affirmatively to this e-mail, you agree that you have understood the 
terms and conditions in the attached term sheet and evaluated the merits and 
risks of the transaction. We may at times also request you to sign the term 
sheet to acknowledge the same.

Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for 
important information with respect to derivative products.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: [EXTERNAL] Unexpected duplicate join points in "Core" output?

2021-11-24 Thread Simon Peyton Jones via ghc-devs
| For two join points to be duplicates they need to not only be alpha
| equivalent but to also have the same continuation.  

Yes exactly. And it would not be hard to adapt the existing CSE pass to support 
this.  Just needs doing.

A ticket and a repo case would be really helpful.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

| -Original Message-
| From: ghc-devs  On Behalf Of Viktor
| Dukhovni
| Sent: 24 November 2021 21:27
| To: ghc-devs@haskell.org
| Subject: Re: [EXTERNAL] Unexpected duplicate join points in "Core"
| output?
| 
| On Sun, Nov 21, 2021 at 06:53:53AM -0500, Carter Schonwald wrote:
| 
| > On Sat, Nov 20, 2021 at 4:17 PM Simon Peyton Jones via ghc-devs <
| > ghc-devs@haskell.org> wrote:
| >
| > > There is absolutely no reason not to common-up those to join
| points.
| > > But we can't common up some join points when we could if they were
| let's.
| > > Consider
| > >
| > > join j1 x = x+1
| > > in case v of
| > >   A -> f (join j2 x = x+1 in ...j2...)
| > >   B -> j1...
| > >   C -> j1...
| > >
| > > Even though j2 is identical to j1's, we can't eliminate j2 in
| favour
| > > of j1 because then j1 wouldn't be a join point any more.
| >
| > In this example: why would it stop being a join point ?
| >
| > Admittedly, my intuition might be skewed by my own ideas about how
| > join points are sortah a semantic special case of other constructs.
| 
| I think the point is that join points are tail calls that don't return
| to the caller.  But here even though `j1` and `j2` have the same body
| j1's continuation is not the same as j2's continuation.
| 
| Rather the result of `j2` is the input to `f`, but the result of j1 is
| a possible output of the whole `case` block in the B and C branches.
| For two join points to be duplicates they need to not only be alpha
| equivalent but to also have the same continuation.  Something like
| 
| join j1 x = x + 1 in
| join j2 y = y + 1 in
| ... j1 ...
| ... j2 ...
| 
| where eliminating j2 in favour of j1 should be correct.
| 
| --
| VIktor.
| ___
| ghc-devs mailing list
| ghc-devs@haskell.org
| https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.h
| askell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
| devsdata=04%7C01%7Csimonpj%40microsoft.com%7Cc5bef423b62e469b382d0
| 8d9af9156f4%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63773386151737
| 6728%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTi
| I6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=nWOBjpnIGGX2RbwIT%2BofdqfGJYq
| xY%2FvKKExGB%2B2Vi3k%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: [EXTERNAL] can GHC generate an irreducible control-flow graph? If so, how?

2021-11-22 Thread Simon Peyton Jones via ghc-devs
GHC breaks strongly connected components with a so-called loop-breaker. In this 
case, maybe countA is the loop-breaker; then countB can inline at all its call 
sites, and it'll look very reducible.  See "Secrets of the GHC inliner".

If you make countA and countB each call themselves, as well as the other, that 
will defeat this plan, and you may get closer to your goal.

I'm guessing a bit, but hope this helps.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

| -Original Message-
| From: ghc-devs  On Behalf Of Norman
| Ramsey
| Sent: 22 November 2021 19:52
| To: ghc-devs@haskell.org
| Subject: [EXTERNAL] can GHC generate an irreducible control-flow graph?
| If so, how?
| 
| I'm trying to figure out how to persuade GHC to generate an irreducible
| control-flow graph (so I can test an algorithm to convert it to
| structured control flow).
| 
| The attached image shows (on the left) the classic simple irreducible
| CFG: there is a loop between nodes A and B, but neither one dominates
| the other, so there is no loop header.  I tried to get GHC to generate
| this CFG using the following source code:
| 
|   length'' :: Bool -> List a -> Int
|   length'' trigger xs = if trigger then countA 0 xs else countB 0 xs
| where countA n Nil = case n of m -> m
|   countA n (Cons _ as) = case n + 1 of m -> countB m as
|   countB n Nil = case n of m -> m
|   countB n (Cons _ as) = case n + 2 of m -> countA m as
| 
| Unfortunately (for my purposes), GHC generates a perfectly lovely
| reducible flow graph with a single header node.
| 
| It is even possible for GHC to generate an irreducible control-flow
| graph?  If so, how can it be done?
| 
| 
| Norman

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


RE: [EXTERNAL] Unexpected duplicate join points in "Core" output?

2021-11-20 Thread Simon Peyton Jones via ghc-devs
There is absolutely no reason not to common-up those to join points.  But we 
can't common up some join points when we could if they were let's.  Consider

join j1 x = x+1
in case v of
  A -> f (join j2 x = x+1 in ...j2...)
  B -> j1...
  C -> j1...

Even though j2 is identical to j1's, we can't eliminate j2 in favour of j1 
because then j1 wouldn't be a join point any more.

GHC.Core.Opt.CSE is conservative at the moment, and never CSE's *any* join 
point.  It would not be hard to make it clever enough to CSE join points, but 
no one has yet done it.

Do open a ticket!

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

| -Original Message-
| From: ghc-devs  On Behalf Of Viktor
| Dukhovni
| Sent: 20 November 2021 00:57
| To: ghc-devs@haskell.org
| Subject: [EXTERNAL] Unexpected duplicate join points in "Core" output?
| 
| The below "Core" output from "ghc -O2" (9.2/8.10) for the attached
| program shows seemingly rendundant join points:
| 
|   join {
| exit :: State# RealWorld -> (# State# RealWorld, () #)
| exit (ipv :: State# RealWorld) = jump $s$j ipv } in
| 
|   join {
| exit1 :: State# RealWorld -> (# State# RealWorld, () #)
| exit1 (ipv :: State# RealWorld) = jump $s$j ipv } in
| 
| that are identical in all but name.  These correspond to fallthrough to
| the "otherwise" case in:
| 
|...
|| acc < q || (acc == q && d <= 5)
|  -> loop (ptr `plusPtr` 1) (acc * 10 + d)
|| otherwise -> return Nothing
| 
| but it seems that the generated X86_64 code (also below) ultimately
| consolidates these into a single target... Is that why it is harmless
| to leave these duplicated in the generated "Core"?
| 
| [ Separately, in the generated machine code, it'd also be nice to avoid
|   comparing the same "q" with the accumulator twice.  A single load and
|   compare should I think be enough, as I'd expect the status flags to
|   persist across the jump the second test.
| 
|   This happens to not be performance critical in my case, because most
|   calls should satisfy the first test, but generally I think that 3-way
|   "a < b", "a == b", "a > b" branches ideally avoid comparing twice...
| ]
| 
|  Associated Core output
| 
| -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
| main2 :: Addr#
| main2 = "12345678901234567890 junk"#
| 
| -- RHS size: {terms: 129, types: 114, coercions: 0, joins: 6/8}
| main1 :: State# RealWorld -> (# State# RealWorld, () #)
| main1
|   = \ (eta :: State# RealWorld) ->
|   let {
| end :: Addr#
| end = plusAddr# main2 25# } in
|   join {
| $s$j :: State# RealWorld -> (# State# RealWorld, () #)
| $s$j _ = hPutStr2 stdout $fShowMaybe4 True eta } in
|   join {
| exit :: State# RealWorld -> (# State# RealWorld, () #)
| exit (ipv :: State# RealWorld) = jump $s$j ipv } in
|   join {
| exit1 :: State# RealWorld -> (# State# RealWorld, () #)
| exit1 (ipv :: State# RealWorld) = jump $s$j ipv } in
|   join {
| exit2
|   :: Addr# -> Word# -> State# RealWorld -> (# State#
| RealWorld, () #)
| exit2 (ww :: Addr#) (ww1 :: Word#) (ipv :: State#
| RealWorld)
|   = case eqAddr# ww main2 of {
|   __DEFAULT ->
| hPutStr2
|   stdout
|   (++
|  $fShowMaybe1
|  (case $w$cshowsPrec3 11# (integerFromWord#
| ww1) [] of
|   { (# ww3, ww4 #) ->
|   : ww3 ww4
|   }))
|   True
|   eta;
|   1# -> jump $s$j ipv
| } } in
|   joinrec {
| $wloop
|   :: Addr# -> Word# -> State# RealWorld -> (# State#
| RealWorld, () #)
| $wloop (ww :: Addr#) (ww1 :: Word#) (w :: State# RealWorld)
|   = join {
|   getDigit :: State# RealWorld -> (# State# RealWorld,
| () #)
|   getDigit (eta1 :: State# RealWorld)
| = case eqAddr# ww end of {
| __DEFAULT ->
|   case readWord8OffAddr# ww 0# eta1 of { (#
| ipv, ipv1 #) ->
|   let {
| ipv2 :: Word#
| ipv2 = minusWord# (word8ToWord# ipv1) 48##
| } in
|   case gtWord# ipv2 9## of {
| __DEFAULT ->
|   case ltWord# ww1 1844674407370955161## of
| {
| __DEFAULT ->
|  

Defaulting design choices

2021-11-15 Thread Simon Peyton Jones via ghc-devs
Sam, Richard, Adam, Vlad, Ryan, and other people interested in GHC's type 
system.
Following discussion with Richard, I have created a new ticket #20686 for Make 
the design of defaulting 
explicit.  This should 
inform !6851 which is trying to finish up Concrete# constraints.
Please have a look - we 'd love your views on The Choice.
Richard especially, but everyone really: feel free to edit the Description to 
make it more clear/accurate.  I propose to treat it as our master design 
document.
Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

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


RE: Output language of typechecking pass?

2021-11-08 Thread Simon Peyton Jones via ghc-devs
Is there anywhere on the GHC wiki that explains how to interpret this output, 
and says that the type and dictionary applications ARE there, just not shown by 
'-ddump-tc'?

Perhaps it would be helpful to add some basic description of what comes out of 
the typechecker to a page like this one? (below)


https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/hsc-main
Yes it would!  Would you care to start such a wiki page (a new one; don't just 
clutter up the one you point to)?You can write down what you know.  Don't 
worry if you aren't 100% sure - we can correct it.  And if you outright don't 
know, leave a "What should I say here?" note.


"This late desugaring is somewhat unusual. It is much more common to desugar 
the program before typechecking, or renaming, because that presents the renamer 
and typechecker with a much smaller language to deal with. However, GHC's 
organisation means that
This note is now slightly out of date.  We are now, very carefully, doing some 
desugaring before typechecking.  See

  *   Note [Handling overloaded and rebindable constructs]  in GHC.Rename.Expr
  *   Note [Rebindable syntax and HsExpansion] in GHC.Hs.Expr

You can and should point to these and similar Notes from the wiki page you 
write.  Indeed there may be some part of what you write that would be better 
framed as Note in GHC's source code.

Thanks!

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Benjamin Redelings
Sent: 08 November 2021 13:12
To: Richard Eisenberg 
Cc: ghc-devs@haskell.org
Subject: Re: Output language of typechecking pass?


Hi,



Questions:



1. It seems like this separation is actually necessary, in order to apply 
generalization only to let arguments written by the programmer, and not to let 
bindings introduced during desugaring. Is that right?



I don't think so. That is, if we did it all in one pass, I still think we could 
get generalization right.

I guess I asked this question wrong.  I mean to say, if we did the two passes 
in the reverse order (desugaring first, followed by typechecking), that would 
not work, right?

As the wiki says:

"This late desugaring is somewhat unusual. It is much more common to desugar 
the program before typechecking, or renaming, because that presents the renamer 
and typechecker with a much smaller language to deal with. However, GHC's 
organisation means that

  *   error messages can display precisely the syntax that the user wrote; and
  *   desugaring is not required to preserve type-inference properties.

"



2. Does the output of type checking contain type lambdas?



Yes. See below.





3. Does the type checking pass determine where to add dictionary arguments?



Yes. See below.





4. Are there any other resources I should be looking at?



Yes. You want to enable -fprint-typechecker-elaboration (and possible 
-fprint-explicit-coercions). With the former, you get to see all this stuff 
you're looking for. It's normally suppressed so that the output resembles the 
user's code.



I hope this helps!

Richard

Hmm... so, I think I see how this works now.  I don't think 
'-fprint-explicit-coercions' does anything here though.

$ ghc -ddump-tc Test2.hs -fprint-typechecker-elaboration

...

AbsBinds [a_a2hp] [$dNum_a2hB]
  {Exports: [g <= g_a2hz
   wrap: <>]
   Exported types: g :: forall a. Num a => a -> a -> a
   [LclId]
   Binds: g x_aYk y_aYl = (y_aYl * x_aYk) + 1
   Evidence: [EvBinds{[W] $dNum_a2hs = $dNum_a2hq
  [W] $dNum_a2hw = $dNum_a2hq
  [W] $dNum_a2hq = $dNum_a2hB}]}

...

The type and dictionary arguments are visible here (along with the evidence 
bindings), but type and dictionary applications are only visible if you use 
-ddump-tc-ast, which is a lot more verbose.  (I don't think there is another 
flag that shows these applications?)  Since I didn't initially know what 
"evidence" was, and there is nothing to say that a_a2hp is a type lambda 
argument, this was pretty opaque until I managed to read the tc-ast and the 
light went on.

I can see now that the type and dictionary arguments are added by annotating 
the AST.

Is there anywhere on the GHC wiki that explains how to interpret this output, 
and says that the type and dictionary applications ARE there, 

RE: Alpha-equivalence for recursive let-bindings

2021-11-08 Thread Simon Peyton Jones via ghc-devs
Huh!  Dead right!

Would you like to:

  *   Open a ticket (you can use the text from this email)
  *   Submit a MR?

On the MR,

  *   Add a Note that again gives your killer example; and mention why we don't 
need the check for NonRec
  *   Worth also pointing out that letrec { x = e1; y = e2 } in b is NOT 
considered equal to letrec { y = e1; x = e1 } in b.   Nor are let x=e1 in let y 
= e2 in b   considered equal to  let y = e1 in let x = e1 in b.   This is fine; 
but worth pointing out.

Thanks for pointing this out!

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Christiaan Baaij
Sent: 07 November 2021 21:08
To: ghc-devs 
Subject: Alpha-equivalence for recursive let-bindings

Hi list,

I was looking at the `Eq (DeBruijn CoreExpr)` instance and I noticed that the 
types of recursive let-bindings aren't checked for alpha-equivalence:

https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Core/Map/Expr.hs#L166-174

go (Let (Rec ps1) e1) (Let (Rec ps2) e2)
  = equalLength ps1 ps2
  && D env1' rs1 == D env2' rs2
  && D env1' e1  == D env2' e2
  where
(bs1,rs1) = unzip ps1
(bs2,rs2) = unzip ps2
env1' = extendCMEs env1 bs1
env2' = extendCMEs env2 bs2

But doesn't that mean that:
let (x :: Int) = x in x
and
let (y :: Bool) = y in y
are considered alpha-equivalent?
If that is the case, then I think that's wrong. Agree?
I understand that you don't have to check types for non-recursive let-bindings: 
when the RHSs match, the types must be the same.

-- Christiaan

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


RE: Exact Print Annotations : Anchor in a SrcSpan

2021-10-29 Thread Simon Peyton Jones via ghc-devs
Alan

I'm way behind with this exact-print stuff and Anchors in particular.

If you and your co-workers on it are confident you know what to do, that's 
great - although as ever, please document the design carefully.   (I volunteer 
as a reader of such a design overview.  I know that a current draft exists.)

If you want a design discussion with others less closely involved then do 
suggest it --  probably a synchronous meeting with a tutorial element would be 
helpful.

thanks for working on this in such a sustained way.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Alan & Kim Zimmerman
Sent: 28 October 2021 22:18
To: ghc-devs 
Subject: Exact Print Annotations : Anchor in a SrcSpan

I have been updating the ghc-exactprint library for real world use cases on the 
about to be released GHC 9.2.1, and realised I need to be able to put an Anchor 
into every SrcSpan in the ParsedSource AST.

I prepared !6854 to sort it out in master and turned to the problem of GHC 
9.2.1, where I had missed the boat.

And then I discovered that we have SrcSpan defined as

data SrcSpan =
RealSrcSpan !RealSrcSpan !(Maybe BufSpan)
  | UnhelpfulSpan !UnhelpfulSpanReason

and the (Maybe BufSpan) is only used for attaching haddock comments after 
parsing.

This means there is an isomorphism between the RealSrcSpan variant and an 
Anchor, which I take advantage of with the code in [1], by using the Maybe to 
encode the AnchorOperation and the BufSpan to encode the DeltaPos.

And it struck me that perhaps we should make this a more official approach.  
The only problem is the detail of the BufSpan, to be able to play both roles 
cleanly.

Alan

[1] 
https://gist.github.com/alanz/5e262599ab79138606cdfcf3792ef635


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


RE: build-system design document: how relevant is it now?

2021-10-22 Thread Simon Peyton Jones via ghc-devs
It's already a sub-tree of "attic" -- ie out of date, retained for archive.

The title index is useful: 
https://gitlab.haskell.org/ghc/ghc/-/wikis/index

Maybe "attic" isn't the best name. Maybe each page should have a header saying 
"Historical value only".  But I hate the idea of outright deletion!

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

|  -Original Message-
|  From: ghc-devs  On Behalf Of Norman
|  Ramsey
|  Sent: 22 October 2021 20:50
|  To: ghc-devs@haskell.org
|  Subject: build-system design document: how relevant is it now?
|  
|  
|  I'm trawling the GHC wiki looking for things that will help me
|  understand how the build system works and what might need to change
|  for cross-compilation.  I stumbled across
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl
|  ab.haskell.org%2Fghc%2Fghc%2F-%2Fwikis%2Fdesign%2Fbuild-
|  systemdata=04%7C01%7Csimonpj%40microsoft.com%7C4c127b6d7e8f4b6008
|  9708d995953f60%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C6377052911
|  25359257%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiL
|  CJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=e3MIn5ElWrtNmCC9u4uOP%2
|  BQGcx4lU%2FFI8QfxQ0%2FbyOM%3Dreserved=0
|  which git helpfully tells me dates from 2008.  I assume that none of
|  it is relevant any longer.
|  
|  In its current form, the page seems only likely to confuse future
|  contributors.  I'd rather not leave things that way.  Does the page
|  have archival value?  Is there a directory of legacy pages to which I
|  should move it?  Or shall I just delete the current text and replace
|  it with a short note?  Or what?
|  
|  
|  Norman
|  
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C4c127b6d7e8f4b600897
|  08d995953f60%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637705291125
|  359257%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=m8dQ5eHD%2Ba0FoK9IFXM7z38
|  ehaAg75I9wj2ESNQZaJM%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-22 Thread Simon Peyton Jones via ghc-devs
I’m out of cycles.  Do please open a ticket. You are more likely to get 
attention that way.

Matthew: maybe you can help with reproducing this?

SImon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo 
Sent: 19 October 2021 09:36
To: Simon Peyton Jones ; 'Matthew Pickering' 

Cc: Montelatici, Raphael Laurent ; 'GHC' 

Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE 
(RE: Instantiation of overloaded definition *in Core*)


PUBLIC


PUBLIC

“settings”? Honestly, I have no idea. GHC looks at these files in the directory 
passed to runGhc, and in my local setup I have some convoluted ghc-lib-based 
system to persist these files and also the base package.db into a 
Stack/cabal-installable package, but these are only needed for environments 
where there’s no bona-fide GHC build directory.

I am sure even without Hadrian, you should have these files somewhere under 
your build directory, since otherwise the same same runGhc function (used 
inside the GHC executable as well…) wouldn’t work. Maybe someone else with 
non-Hadrian knowledge can tell you where these files are put in the non-Hadrian 
build.

From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Tuesday, October 19, 2021 4:08 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>; 'Matthew 
Pickering' mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL 
WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

Yes I have a full build.  No it was not built with Hadrian.  I did not realise 
that your system relied not only on GHC as a library, but also on the build 
system that you use to build GHC.

I guess I can try that, but probably not today.  But what is “settings”?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo mailto:gergo.e...@sc.com>>
Sent: 19 October 2021 09:03
To: Simon Peyton Jones mailto:simo...@microsoft.com>>; 
'Matthew Pickering' 
mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE 
(RE: Instantiation of overloaded definition *in Core*)


PUBLIC


PUBLIC

Do you have a full GHC build there? Are you using Hadrian? Did you set 
`libDir`’s definition in the source file to where you have GHC built? I just 
tried, and if I remove the files from my GHC build, I am able to rebuild them:

mi@localhost[ghc] $ for i in settings llvm-passes llvm-targets; do rm 
~/prog/ghc/_build/stage1/lib/$i; done
mi@localhost[ghc] $ for i in settings llvm-passes llvm-targets; do 
./hadrian/build-stack _build/stage1/lib/$i; done
| Successfully generated _build/stage1/lib/settings.
Build completed in 0.41s

| Copy file: llvm-passes => _build/stage1/lib/llvm-passes
Build completed in 0.40s

| Copy file: llvm-targets => _build/stage1/lib/llvm-targets
Build completed in 0.52s



From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Tuesday, October 19, 2021 3:54 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>; 'Matthew 
Pickering' mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL 
WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

As for opening a ticket – a big part of the problem is that I don’t even know 
yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket 
would even be for – “I’m using the GHC API wrongly” is not a strong bug report 

Plenty of tickets turn out to be non-bugs.  But they are still searchable, and 
form a permanent record that may help others, perhaps in unexpected ways.  So I 
encourage you to do so.

I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ 
as a command line argument.

When I run it I get

simonpj@MSRC-3645512:~/tmp$ ./gergo

Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings

So now I’m stuck again.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to 

RE: Gitlab

2021-10-21 Thread Simon Peyton Jones via ghc-devs
It started working again, a few mins after it stopped working. I was getting 
consistent Error 500, then started being OK.  

Strange.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

|  -Original Message-
|  From: ghc-devs  On Behalf Of Tom Ellis
|  Sent: 21 October 2021 10:07
|  To: ghc-devs@haskell.org
|  Subject: Re: Gitlab
|  
|  On Thu, Oct 21, 2021 at 08:59:48AM +, Simon Peyton Jones via ghc-
|  devs wrote:
|  > Is it just me, or is Gitlab offline again?  I'm getting error code
|  500.
|  
|  I just checked the following, which all work fine:
|  
|  * Navigate to
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl
|  ab.haskell.org%2Fghc%2Fhaddockdata=04%7C01%7Csimonpj%40microsoft.
|  com%7Ca9e47aca8f374f19f98008d994723bf3%7C72f988bf86f141af91ab2d7cd011d
|  b47%7C1%7C0%7C637704041244004412%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wL
|  jAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000sdata
|  =QF5AEHaNFKWepD697Jvtz1pr70%2B4GaK4RuKTBSaFgLI%3Dreserved=0 (in
|  Firefox)
|  
|  * git clone
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl
|  ab.haskell.org%2Fghc%2Fhaddock.gitdata=04%7C01%7Csimonpj%40micros
|  oft.com%7Ca9e47aca8f374f19f98008d994723bf3%7C72f988bf86f141af91ab2d7cd
|  011db47%7C1%7C0%7C637704041244004412%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiM
|  C4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000s
|  data=zPu4532C%2FsdgdIyZu2ExDvFHBTNtsd7IQfMhsmV47EM%3Dreserved=0
|  /tmp/haddock
|  
|  * git clone g...@gitlab.haskell.org:ghc/haddock.git /tmp/haddock-2
|  
|  Simon, can you give more precise details about the problem you are
|  experiencing?
|  
|  Tom
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7Ca9e47aca8f374f19f980
|  08d994723bf3%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637704041244
|  004412%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000sdata=CC%2F0tJSLYXL8A763MtT9%2F
|  Y%2BQG7PL3cSngakqUcFUDes%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Gitlab

2021-10-21 Thread Simon Peyton Jones via ghc-devs
Is it just me, or is Gitlab offline again?  I'm getting error code 500.
Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

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


RE: Cmm comments are not Haddock comments---should this change?

2021-10-20 Thread Simon Peyton Jones via ghc-devs
Sounds like a good idea to me.  I think `foo` works as we as @foo@ in 
Haddock comments, and is a whole lot less obtrusive when looking at the 
comments in their non-typeset form (which is all I ever do).

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

|  -Original Message-
|  From: ghc-devs  On Behalf Of Norman
|  Ramsey
|  Sent: 19 October 2021 19:06
|  To: ghc-devs@haskell.org
|  Subject: Cmm comments are not Haddock comments---should this change?
|  
|  The definitions of the Cmm data structures are richly commented in the
|  source code, but the comments are not Haddock comments, so the
|  information doesn't make it into the Haddock documentation.
|  
|  As I refresh my memory about Cmm, I'm thinking of converting the
|  existing comments to Haddock comments.  The only downside I can think
|  of is that the Haddock pages may appear more cluttered.
|  Is there any reason I should refrain?
|  
|  
|  Norman
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C001a611e1b154df0c32d
|  08d9932b367b%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637702637000
|  557769%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000sdata=lgB5GeTImvl5mMDzgzQy2UD4X
|  %2F3Qf0d1lopgGdiVsxI%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-19 Thread Simon Peyton Jones via ghc-devs
Yes I have a full build.  No it was not built with Hadrian.  I did not realise 
that your system relied not only on GHC as a library, but also on the build 
system that you use to build GHC.

I guess I can try that, but probably not today.  But what is “settings”?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo 
Sent: 19 October 2021 09:03
To: Simon Peyton Jones ; 'Matthew Pickering' 

Cc: Montelatici, Raphael Laurent ; 'GHC' 

Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE 
(RE: Instantiation of overloaded definition *in Core*)


PUBLIC


PUBLIC

Do you have a full GHC build there? Are you using Hadrian? Did you set 
`libDir`’s definition in the source file to where you have GHC built? I just 
tried, and if I remove the files from my GHC build, I am able to rebuild them:

mi@localhost[ghc] $ for i in settings llvm-passes llvm-targets; do rm 
~/prog/ghc/_build/stage1/lib/$i; done
mi@localhost[ghc] $ for i in settings llvm-passes llvm-targets; do 
./hadrian/build-stack _build/stage1/lib/$i; done
| Successfully generated _build/stage1/lib/settings.
Build completed in 0.41s

| Copy file: llvm-passes => _build/stage1/lib/llvm-passes
Build completed in 0.40s

| Copy file: llvm-targets => _build/stage1/lib/llvm-targets
Build completed in 0.52s



From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Tuesday, October 19, 2021 3:54 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>; 'Matthew 
Pickering' mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL 
WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

As for opening a ticket – a big part of the problem is that I don’t even know 
yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket 
would even be for – “I’m using the GHC API wrongly” is not a strong bug report 

Plenty of tickets turn out to be non-bugs.  But they are still searchable, and 
form a permanent record that may help others, perhaps in unexpected ways.  So I 
encourage you to do so.

I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ 
as a command line argument.

When I run it I get

simonpj@MSRC-3645512:~/tmp$ ./gergo

Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings

So now I’m stuck again.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo mailto:gergo.e...@sc.com>>
Sent: 19 October 2021 02:57
To: Simon Peyton Jones mailto:simo...@microsoft.com>>; 
'Matthew Pickering' 
mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE 
(RE: Instantiation of overloaded definition *in Core*)


PUBLIC


PUBLIC

Thanks for looking into this!

`Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can 
of course instead use a local full build of GHC for the libDir. Please find an 
updated version attached that does that – you’ll just have to adapt the 
definition of `libDir` to your environment.

As for opening a ticket – a big part of the problem is that I don’t even know 
yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket 
would even be for – “I’m using the GHC API wrongly” is not a strong bug report 


From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Saturday, October 16, 2021 12:52 AM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>; 'Matthew 
Pickering' mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL 
WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

I could not compile Main.hs:

~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc



Gergo.hs:4:1: error:

Could not find module ‘Paths_ghc_lib’

Use -v (or `:set -v` in ghci) to see a list of the files searched for.

  |

4 | import qualified Paths_ghc_lib as GHC

  | ^

simonpj@MSRC-3645512:~/tmp$

Would you like to open a ticket rather than do this by email?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 

RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-19 Thread Simon Peyton Jones via ghc-devs
As for opening a ticket – a big part of the problem is that I don’t even know 
yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket 
would even be for – “I’m using the GHC API wrongly” is not a strong bug report 

Plenty of tickets turn out to be non-bugs.  But they are still searchable, and 
form a permanent record that may help others, perhaps in unexpected ways.  So I 
encourage you to do so.

I successfully compiled the attached Main.hs with HEAD, passing ‘-package ghc’ 
as a command line argument.

When I run it I get

simonpj@MSRC-3645512:~/tmp$ ./gergo

Missing file: /home/simonpj/code/HEAD-1/compiler/stage1/build/settings

So now I’m stuck again.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo 
Sent: 19 October 2021 02:57
To: Simon Peyton Jones ; 'Matthew Pickering' 

Cc: Montelatici, Raphael Laurent ; 'GHC' 

Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE 
(RE: Instantiation of overloaded definition *in Core*)


PUBLIC


PUBLIC

Thanks for looking into this!

`Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can 
of course instead use a local full build of GHC for the libDir. Please find an 
updated version attached that does that – you’ll just have to adapt the 
definition of `libDir` to your environment.

As for opening a ticket – a big part of the problem is that I don’t even know 
yet if I’m doing something wrong, or GHC is! So it’s not clear what the ticket 
would even be for – “I’m using the GHC API wrongly” is not a strong bug report 


From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Saturday, October 16, 2021 12:52 AM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>; 'Matthew 
Pickering' mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Specialisation doesn't kick in -- NOW WITH MINIMAL 
WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

I could not compile Main.hs:

~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc



Gergo.hs:4:1: error:

Could not find module ‘Paths_ghc_lib’

Use -v (or `:set -v` in ghci) to see a list of the files searched for.

  |

4 | import qualified Paths_ghc_lib as GHC

  | ^

simonpj@MSRC-3645512:~/tmp$

Would you like to open a ticket rather than do this by email?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo mailto:gergo.e...@sc.com>>
Sent: 15 October 2021 05:35
To: Simon Peyton Jones mailto:simo...@microsoft.com>>; 
'Matthew Pickering' 
mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE 
(RE: Instantiation of overloaded definition *in Core*)


PUBLIC


PUBLIC

OK I now have a standalone demonstrator that shows, at least, that the default 
method implementation is not specialized. With the attached input programs, the 
resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as 
follows (only showing the relevant parts):

seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
seq
  = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) ->
  case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV }

$dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
$dmseq
  = \ (@(m :: * -> *))
  ($dMonad [Occ=Once1] :: Monad m)
  (@a)
  (@b)
  (ma [Occ=Once1] :: m a)
  (mb [Occ=OnceL1] :: m b) ->
  let {
sat_ss0 [Occ=Once1] :: a -> m b
[LclId]
sat_ss0 = \ _ [Occ=Dead] -> mb } in
  bind @m $dMonad @a @b ma sat_ss0

$fMonadIO :: Monad IO
$fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq;

$fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b
$fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b;

foo :: IO ()
foo = seq @IO $fMonadIO @() @() ioA ioA

If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just 
doesn’t *do* anything.



This email and any attachments are confidential and may also be privileged. If 
you are not the intended recipient, please delete all copies and notify the 
sender immediately. You may wish to refer to the incorporation details of 
Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at 
https: 

gitlab.haskell.org

2021-10-18 Thread Simon Peyton Jones via ghc-devs
I'm getting "502" from gitlab.haskell.org.   Is it just me?

Thanks

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

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


RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-15 Thread Simon Peyton Jones via ghc-devs
I could not compile Main.hs:

~/code/HEAD-1/inplace/bin/ghc-stage1 -c Gergo.hs -package ghc



Gergo.hs:4:1: error:

Could not find module 'Paths_ghc_lib'

Use -v (or `:set -v` in ghci) to see a list of the files searched for.

  |

4 | import qualified Paths_ghc_lib as GHC

  | ^

simonpj@MSRC-3645512:~/tmp$

Would you like to open a ticket rather than do this by email?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo 
Sent: 15 October 2021 05:35
To: Simon Peyton Jones ; 'Matthew Pickering' 

Cc: Montelatici, Raphael Laurent ; 'GHC' 

Subject: RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE 
(RE: Instantiation of overloaded definition *in Core*)


PUBLIC


PUBLIC

OK I now have a standalone demonstrator that shows, at least, that the default 
method implementation is not specialized. With the attached input programs, the 
resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as 
follows (only showing the relevant parts):

seq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
seq
  = \ (@(m :: * -> *)) (v_srS [Occ=Once1!] :: Monad m) ->
  case v_srS of { C:Monad _ [Occ=Dead] v_srV [Occ=Once1] -> v_srV }

$dmseq :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
$dmseq
  = \ (@(m :: * -> *))
  ($dMonad [Occ=Once1] :: Monad m)
  (@a)
  (@b)
  (ma [Occ=Once1] :: m a)
  (mb [Occ=OnceL1] :: m b) ->
  let {
sat_ss0 [Occ=Once1] :: a -> m b
[LclId]
sat_ss0 = \ _ [Occ=Dead] -> mb } in
  bind @m $dMonad @a @b ma sat_ss0

$fMonadIO :: Monad IO
$fMonadIO = C:Monad @IO bindIO $fMonadIO_$cseq;

$fMonadIO_$cseq :: forall a b. IO a -> IO b -> IO b
$fMonadIO_$cseq = \ (@a) (@b) -> $dmseq @IO $fMonadIO @a @b;

foo :: IO ()
foo = seq @IO $fMonadIO @() @() ioA ioA

If I turn on Opt_D_dump_spec, I can see that specializer *is* running, it just 
doesn't *do* anything.



From: Erdi, Gergo
Sent: Monday, October 11, 2021 4:00 PM
To: Simon Peyton Jones mailto:simo...@microsoft.com>>; 
Matthew Pickering 
mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded 
definition *in Core*)


PUBLIC

Trust me when I say I understand your frustration. It is even more frustrating 
for me not to be able to just send a Github repo link containing my code...

I'll try to make an MWE that demonstrates the problem but it will probably take 
quite some time. I was hoping that maybe there's some known gotcha that I'm not 
aware of - for example (see my other thread), I just discovered that setting 
optimization flags one by one isn't equal to setting them wholesale with -On, 
so I was *not* running specialisation in my normal (per-module) pipeline at 
all! Unfortunately, now that I've discovered this and made sure optLevel is set 
to at least 1, I am still seeing the polymorphic default implementation of >> 
as the only one :/

I also tried to be cheeky about the binding order and put the whole collected 
CoreProgram into a single Rec binder to test your guess, since that should make 
the actual textual order irrelevant. Unfortunately, that sill doesn't change 
anything :/

From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Monday, October 11, 2021 3:33 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>; Matthew 
Pickering mailto:matthewtpicker...@gmail.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of 
overloaded definition *in Core*)


PUBLIC

ATTENTION: This email came from an external source. Do not open attachments or 
click on links from unknown senders or unexpected emails. Always report 
suspicious emails using the Report As Phishing button in Outlook to protect the 
Bank and our clients.

It's incredibly hard to debug this sort of thing remotely, without the ability 
to reproduce it.  First, you are using a variant of GHC, with changes that we 
can only guess at. Second, even with unmodified GHC I often find that 
unexpected things happen - until I dig deeper and it becomes obvious!

There is one odd thing about your dump: it seems to be in reverse dependency 
order, with functions being defined before they are used, rather than after.  
That would certainly stop the specialiser from working.  The occurrence 
analyser would sort this out (literally).   But that's a total guess.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  

RE: how does a CAF become unreachable?

2021-10-12 Thread Simon Peyton Jones via ghc-devs
|  Can anyone show an example?

Sure

xs = [1..1000] :: [Int]
ys = [2..2000] :: [Float]

main = do { print xs; print ys }

After printing xs, the CAF for xs is unreachable and can be GC'd.  No point in 
keeping it around.   Indeed this applies from the moment (print xs) begins 
work.  But it was
main = do { print xs; print xs }
then the CAF for xs remains reachable until the second (print xs) starts.

Simon


PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

|  -Original Message-
|  From: ghc-devs  On Behalf Of Norman
|  Ramsey
|  Sent: 12 October 2021 21:55
|  To: ghc-devs@haskell.org
|  Subject: how does a CAF become unreachable?
|  
|  I spent the afternoon spelunking through some code and the Commentary,
|  and I'm wondering how a CAF becomes unreachable.  I gather it might
|  have to do with GHC floating a static expression out of a context
|  until it becomes a CAF, but I'm still not seeing how a CAF could at
|  one point be reachable, then dynamically become unreachable.
|  
|  Can anyone show an example?
|  
|  
|  Norman
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C788a90f23049467d7636
|  08d98dc2c6ca%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637696690459
|  913210%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=8eSDcyPcNe4gSTnKJc8OQcqQI
|  %2B%2FDf9lSp3OksAV0H%2BU%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: -O* does more than what's in optLevelFlags?

2021-10-11 Thread Simon Peyton Jones via ghc-devs
Oh, now I get it.  I misunderstood you.

But the point is, I do *not* want to set optLevel. I want to turn on individual 
optimizations. But as it stands today, if I turn on any optimizations, that 
doesn’t do anything unless I *also* set optLevel to >= 1.

Yes I agree.   Nothing should consult `optLevel`; indeed maybe we shouldn’t 
even record it permanently.

The place in Pipeline that Sylvain identified is most important.

So when we compute the CoreTodos, instead of looking at the optLevel, we’d 
consult the set of optimizations turned on, and go “yup, at least one of these 
needs core-to-core simpl passes, so we better get on it”, going to the same 
branch that current is gated by optLevel >= 1.

Yes I agree with this.   Another alternative might be to kill off the -O0 
pipeline entirely (in GHC.Core.Opt.Pipeline.getCoreToDo) and just have one 
pipeline that does not-very-much when no optimisations are enabled.  This would 
be more robust (no need to have a list of flags to consult to decide which path 
to follow), but could have unforeseen consequences (what happens in the -0 
pipeline if all optimisations are off?  Same as the -O0 pipeline?).

I’d be happy with either of these changes, if someone wants to offer a patch.   
 Certainly open a ticket with this discussion so it doesn’t get lost.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo 
Sent: 11 October 2021 09:21
To: Simon Peyton Jones 
Cc: Montelatici, Raphael Laurent ; 'GHC' 

Subject: RE: -O* does more than what's in optLevelFlags?


PUBLIC


PUBLIC

But the point is, I do *not* want to set optLevel. I want to turn on individual 
optimizations. But as it stands today, if I turn on any optimizations, that 
doesn’t do anything unless I *also* set optLevel to >= 1.

A nicer design in my mind would be if the semantics of optLevel is fully 
defined in terms of optimization flags. I want “-O1 -fno-strictness” to be 
exactly equivalent to “-fpolynomial-complexity -fremove-space-leaks 
-fstrictness -fno-strictness” which of course is equivalent to 
“-fpolynomial-complexity -fremove-space-leaks -fno-strictness” (assuming that 
the O1 flag is defined to turn on three flags that ensure polynomial 
complexity, remove space leaks, and turn on strictness analysis, just as a way 
of example). So when we compute the CoreTodos, instead of looking at the 
optLevel, we’d consult the set of optimizations turned on, and go “yup, at 
least one of these needs core-to-core simpl passes, so we better get on it”, 
going to the same branch that current is gated by optLevel >= 1.

Would that make sense?

Also, this is NOT just an API documentation issue! The GHC user’s guide itself 
wrongly claims:

The -O* options specify convenient “packages” of optimisation flags; the -f* 
options described later on specify individual optimisations to be turned 
on/off; the -m* options specify machine-specific optimisations to be turned 
on/off.
[…]
There are many options that affect the quality of code produced by GHC. Most 
people only have a general goal, something like “Compile quickly” or “Make my 
program run like greased lightning.” The following “packages” of optimisations 
(or lack thereof) should suffice.

https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/using-optimisation.html#o-convenient-packages-of-optimisation-flags


I’m happy to submit a documentation patch if there is no way to actually 
support this model, but I would prefer much more if we can implement what is 
claimed in the documentation here 


From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Monday, October 11, 2021 4:06 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; 'GHC' 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: -O* does more than what's in optLevelFlags?


Is this a documentation bug, an implementation bug (as in, if any of the 
relevant opts are set, then the CoreToDos should always include the 
optimization steps selected), or a design bug (there is no way to support this 
meaningfully)?

Maybe a documentation bug?  You should update the `optLevel` field of 
`DynFlags` only via calling `setOptLevel`, not by setting it directly.

What other design would make sense?  

RE: -O* does more than what's in optLevelFlags?

2021-10-11 Thread Simon Peyton Jones via ghc-devs
Is this a documentation bug, an implementation bug (as in, if any of the 
relevant opts are set, then the CoreToDos should always include the 
optimization steps selected), or a design bug (there is no way to support this 
meaningfully)?

Maybe a documentation bug?  You should update the `optLevel` field of 
`DynFlags` only via calling `setOptLevel`, not by setting it directly.

What other design would make sense?  We want to support ghc -O -fno-strictness, 
where the -O switches on a bunch of flags, and -fno-strictness turns off 
strictness.  The order matters.

One difficulty is that I'm not even sure where one would look for that 
documentation.  We don't really have a comprehensive GHC User Manual 
description of the GHC API: Section 7.2 "Using GHC as a library" is vestigial.  
I would be Absolutely Fantastic, if someone (Gergo, even) felt able to flesh it 
out.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Erdi, Gergo via 
ghc-devs
Sent: 11 October 2021 08:54
To: 'GHC' 
Cc: Montelatici, Raphael Laurent 
Subject: RE: -O* does more than what's in optLevelFlags?


PUBLIC

I've done some digging into this, and it turns out the DynFlag's `optLevel` 
itself is used at some places, most notably when creating the main [CoreToDo]. 
So turning on all these flags on their own doesn't equal setting -On for the 
right "n"; in fact, currently setting most of these flags does NOTHING on its 
own unless -On with n>=1 is *also* passed on the command line, and there is no 
command line flag to *only* turn on Core optimizations in the abstract, without 
actually turning any specific ones on.

Is this a documentation bug, an implementation bug (as in, if any of the 
relevant opts are set, then the CoreToDos should always include the 
optimization steps selected), or a design bug (there is no way to support this 
meaningfully)?

From: Erdi, Gergo
Sent: Monday, October 11, 2021 12:09 PM
To: 'GHC' mailto:ghc-devs@haskell.org>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>
Subject: -O* does more than what's in optLevelFlags?


PUBLIC

What is set by -O* that is not included in optLevelFlags?

I would have thought that setting all the flags implied by, e.g., -O1, would be 
the same as setting -O1 itself. But this is not the case! Here are all the 
flags for O1 from optLevelFlags:

Opt_DoLambdaEtaExpansion
Opt_DoEtaReduction
Opt_LlvmTBAA
Opt_CallArity
Opt_Exitification
Opt_CaseMerge
Opt_CaseFolding
Opt_CmmElimCommonBlocks
Opt_CmmSink
Opt_CmmStaticPred
Opt_CSE
Opt_StgCSE
Opt_EnableRewriteRules
Opt_FloatIn
Opt_FullLaziness
Opt_IgnoreAsserts
Opt_Loopification
Opt_CfgBlocklayout
Opt_Specialise
Opt_CrossModuleSpecialise
Opt_InlineGenerics
Opt_Strictness
Opt_UnboxSmallStrictFields
Opt_CprAnal
Opt_WorkerWrapper
Opt_SolveConstantDicts
Opt_NumConstantFolding

And here are the ones that are set by O0 (the default) but not by O1:

Opt_IgnoreInterfacePragmas
Opt_OmitInterfacePragmas

So I expected that the following two invocations of GHC would be equivalent:


  1.  ghc -O1
  2.  ghc -fdo-lambda-eta-expansion -fdo-eta-reduction -fllvm-tbaa -fcall-arity 
-fexitification -fcase-merge -fcase-folding -fcmm-elim-common-blocks -fcmm-sink 
-fcmm-static-pred -fcse -fstg-cse -fenable-rewrite-rules -ffloat-in 
-ffull-laziness -fignore-asserts -floopification -fblock-layout-cfg 
-fspecialise -fcross-module-specialise -finline-generics -fstrictness 
-funbox-small-strict-fields -fcpr-anal -fworker-wrapper -fsolve-constant-dicts 
-fnum-constant-folding -fno-ignore-interface-pragmas -fno-omit-interface-pragmas

However, just by observing the output of -dshow-passes, I can see that while 
-O1 applies all these optimizations, the second version does NOT, even though I 
have turned on each and every one of them one by one.

Looking at compiler/GHC/Driver/Session.hs, it is not at all clear that -O* 
should do more than just setting the flags from optLevelFlags. What other flags 
are implied by -O*?

This email and any attachments are confidential and may also be privileged. If 
you are not the intended recipient, please delete all copies and notify the 
sender immediately. You may wish to refer to the incorporation details of 
Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at 
https: //www.sc.com/en/our-locations

Where you have a Financial Markets relationship with Standard Chartered PLC, 
Standard Chartered Bank and their subsidiaries (the "Group"), information on 
the regulatory standards we adhere to and how it may affect you can be found in 
our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory 
Compliance Disclosures at http: //www.sc.com/rcs/fm

Insofar as this communication is not sent by the Global Research 

RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-11 Thread Simon Peyton Jones via ghc-devs
It's incredibly hard to debug this sort of thing remotely, without the ability 
to reproduce it.  First, you are using a variant of GHC, with changes that we 
can only guess at. Second, even with unmodified GHC I often find that 
unexpected things happen - until I dig deeper and it becomes obvious!

There is one odd thing about your dump: it seems to be in reverse dependency 
order, with functions being defined before they are used, rather than after.  
That would certainly stop the specialiser from working.  The occurrence 
analyser would sort this out (literally).   But that's a total guess.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo 
Sent: 11 October 2021 03:58
To: Simon Peyton Jones ; Matthew Pickering 

Cc: Montelatici, Raphael Laurent ; 'GHC' 

Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded 
definition *in Core*)


PUBLIC


PUBLIC

Hi Simon, Matt & others,

It took me until now to be able to try out GHC HEAD, mostly because I had to 
adapt to all the GHC.Unit.* refactorings. However, now I am on 
a466b02492f73a43c6cb9ce69491fc85234b9559 which includes the commit Simon 
pointed out. My original plan was to expose the first half of specProgram, i.e. 
the part that calls `go binds`. I did that because I want to apply 
specialisation on collected whole-program Core, not just whatever would be in 
scope for a Core-to-Core plugin pass, so I am not writing a CoreM and I don't 
even have a ModGuts at hand.

However, I found out from Matt's email on this thread that this is not going to 
be enough and eventually I'll need to figure out how I intend to apply the 
rewrite rules that come out of this. So for now, I am just turning on 
specialization in the normal pipeline by setting Opt_Specialise, 
Opt_SpecialiseAggressively, and Opt_CrossModuleSpecialise. And I'm still not 
seeing $dm>> being specialized.

Is this because I define each of "class Monad", "data IO a", "instance Monad 
IO", and "main", in four distinct modules? In other words, is this something I 
will not be able to try out until I figure out how to make a fake ModGuts and 
run a CoreM from outside the normal compilation pipeline, feeding it the 
whole-program collected CoreBinds? But if so, why is it that when I feed my 
whole program to just specBinds (which I can try easily since it has no 
ModGuts/CoreM dependency other than a uniq supply and the CoreProgram), I get 
back an empty UsageDetails?

Thanks,
Gergo

For reference, the relevant definitions dumped from GHC with specialization 
(supposedly) turned on:

main = $fMonadIO_$c>> @() @() sat_sJg xmain

$fMonadIO_$c>> :: forall a b. IO a -> IO b -> IO b
$fMonadIO_$c>> = \ (@a_aF9) (@b_aFa) -> $dm>> @IO $fMonadIO @a_aF9 @b_aFa;

$dm>> :: forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b
$dm>>
  = \ (@(m_ani :: Type -> Type))
  ($dMonad_sIi [Occ=Once1] :: Monad m_ani)
  (@a_ar4)
  (@b_ar5)
  (ma_sIj [Occ=Once1] :: m_ani a_ar4)
  (mb_sIk [Occ=OnceL1] :: m_ani b_ar5) ->
  let {
sat_sIm [Occ=Once1] :: a_ar4 -> m_ani b_ar5
[LclId]
sat_sIm = \ _ [Occ=Dead] -> mb_sIk } in
  >>= @m_ani $dMonad_sIi @a_ar4 @b_ar5 ma_sIj sat_sIm

From: Erdi, Gergo
Sent: Thursday, October 7, 2021 9:30 AM
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; GHC 
mailto:ghc-devs@haskell.org>>
Subject: RE: Specialisation doesn't kick in (RE: Instantiation of overloaded 
definition *in Core*)


PUBLIC

Indeed, I am using 9.0.1. I'll try upgrading. Thanks!


From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Wednesday, October 6, 2021 6:12 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>
Cc: Montelatici, Raphael Laurent 
mailto:raphael.montelat...@sc.com>>; GHC 
mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of 
overloaded definition *in Core*)

Grego,

Yes I think that should auto-specialise.

Which version of GHC are you using?   Do you have this patch?


commit ef0135934fe32da5b5bb730dbce74262e23e72e8

Author: Simon Peyton Jones simo...@microsoft.com

Date:   Thu Apr 8 22:42:31 2021 +0100



Make the specialiser handle polymorphic specialisation


Here's why I ask.  The call

$fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b

indeed applies $dm>> to $fMonadIO, but it also applies it to a and b.  In the 
version of GHC you have, maybe that stops the call from floating up to the 
definition site, and being used to specialise it.

Can you make a repro case without your plugin?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 

RE: Why can't arguments be levity polymorphic for inline functions?

2021-10-08 Thread Simon Peyton Jones via ghc-devs
We do have a few such functions, and we give them a "compulsory unfolding" 
which means they MUST be inlined at EVERY call site.  But


  *   Usually if a module exports a function, it generates code for that 
function. But for these guys it can't.   We don't have a mechanism for *not* 
generating code for user-defined functions.  We could add an INLINE-COMPULSORY 
pragma perhaps.
  *   Even then we'd have to check that every call of such a function is 
applied to enough arguments to get rid of all levity/representation 
polymorphism; so that when it is inlined all is good. It's not clear how to do 
that in general.

That's the kind of thing Richard means by "templates".

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Clinton Mead
Sent: 08 October 2021 00:37
To: ghc-devs@haskell.org
Subject: Why can't arguments be levity polymorphic for inline functions?

Hi All

Not sure if this belongs in ghc-users or ghc-devs, but it seemed devy enough to 
put it here.

Section 
6.4.12.1
 of the GHC user manual points out, if we allowed levity polymorphic arguments, 
then we would have no way to compile these functions, because the code required 
for different levites is different.

However, if such a function is {-# INLINE #-} or {-# INLINABLE #-} there's no 
need to compile it as it's full definition is in the interface file. Callers 
can just compile it themselves with the levity they require. Indeed callers of 
inline functions already compile their own versions even without levity 
polymorphism (for example, presumably inlining function calls that are known at 
compile time).

The only sticking point to this that I could find was that GHC will only inline 
the function if it is fully 
applied,
 which suggests that the possibility of partial application means we can't 
inline and hence need a compiled version of the code. But this seems like a 
silly restriction, as we have the full RHS of the definition in the interface 
file. The caller can easily create and compile it's own partially applied 
version. It should be able to do this regardless of levity.

It seems to me we're okay as long as the following three things aren't true 
simultaneously:

1. Blah has levity polymorphic arguments
2. Blah is exported
3. Blah is not inline

If a function "Blah" is not exported, we shouldn't care about levity 
polymorphic arguments, because we have it's RHS on hand in the current module 
and compile it as appropriate. And if it's inline, we're exposing it's full RHS 
to other callers so we're still fine also. Only when these three conditions 
combine should we give an error, say like:

"Blah has levity polymorphic arguments, is exported, and is not inline. Please 
either remove levity polymorphic arguments, not export it or add an  {-# INLINE 
#-} or {-# INLINABLE #-} pragma.

I presume however there are some added complications that I don't understand, 
and I'm very interested in what they are as I presume they'll be quite 
interesting.

Thanks,
Clinton

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


RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-06 Thread Simon Peyton Jones via ghc-devs
Grego,

Yes I think that should auto-specialise.

Which version of GHC are you using?   Do you have this patch?


commit ef0135934fe32da5b5bb730dbce74262e23e72e8

Author: Simon Peyton Jones simo...@microsoft.com

Date:   Thu Apr 8 22:42:31 2021 +0100



Make the specialiser handle polymorphic specialisation


Here's why I ask.  The call

$fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b

indeed applies $dm>> to $fMonadIO, but it also applies it to a and b.  In the 
version of GHC you have, maybe that stops the call from floating up to the 
definition site, and being used to specialise it.

Can you make a repro case without your plugin?

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Erdi, Gergo 
Sent: 06 October 2021 03:07
To: Simon Peyton Jones 
Cc: Montelatici, Raphael Laurent ; GHC 

Subject: Specialisation doesn't kick in (RE: Instantiation of overloaded 
definition *in Core*)


PUBLIC


PUBLIC

Hi,

Thanks! Originally I was going to reply to this saying that my transformation 
isn't running in CoreM so where do I get that environment from, but then I 
realized I can just build it from the md_insts field of ModDetails. However, 
after thinking more about it, I also realized that I shouldn't ever really need 
to conjure up dictionaries from thin air: the whole reason I am making a 
specific specialization of an overloaded function is because I found somewhere 
a call at that type. But then, that call also gives me the dictionary!

Of course at this point, this sounds exactly like what GHC already does in 
`specProgram`. So maybe I should be able to just use that?

Unfortunately, my initial testing seems to show that even if I run `specBind` 
manually on my whole-program collected CoreProgram, it doesn't do the work I 
would expect from it!

In the following example, I have only kept the definitions that are relevant. 
Before specialisation, I have the following whole-program Core:

(>>=)
  :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
[GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=]
(>>=)
  = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) ->
  case v_sGm of
  { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] ->
  v_sGp
  }
$dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
[GblId, Arity=3, Unf=OtherCon []]
$dm>>
  = \ (@(m :: * -> *))
  ($dMonad [Occ=Once1] :: Monad m)
 (@a)
  (@b)
  (ma [Occ=Once1] :: m a)
  (mb [Occ=OnceL1] :: m b) ->
  let {
sat_sGQ [Occ=Once1] :: a -> m b
[LclId]
sat_sGQ = \ _ [Occ=Dead] -> mb } in
  >>= @m $dMonad @a @b ma sat_sGQ
C:Monad [InlPrag=NOUSERINLINE CONLIKE]
  :: forall (m :: * -> *).
 Applicative m
 -> (forall a b. m a -> (a -> m b) -> m b)
 -> (forall a b. m a -> m b -> m b)
 -> Monad m
[GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []]
C:Monad
  = \ (@(m :: * -> *))
  (eta_B0 [Occ=Once1] :: Applicative m)
  (eta_B1 [Occ=Once1] :: forall a b. m a -> (a -> m b) -> m b)
  (eta_B2 [Occ=Once1] :: forall a b. m a -> m b -> m b) ->
  C:Monad @m eta_B0 eta_B1 eta_B2
$fMonadIO [InlPrag=NOUSERINLINE CONLIKE] :: Monad IO
[GblId[DFunId]]
$fMonadIO = C:Monad @IO $fApplicativeIO bindIO $fMonadIO_$c>>;
$fMonadIO_$c>> [Occ=LoopBreaker]
  :: forall a b. IO a -> IO b -> IO b
[GblId]
$fMonadIO_$c>> = \ (@a) (@b) -> $dm>> @IO $fMonadIO @a @b;
sat_sHr :: IO ()
[LclId]
sat_sHr = returnIO @() ()
sat_sHq :: IO ()
[LclId]
sat_sHq = returnIO @() ()
main :: IO ()
[GblId]
main = $fMonadIO_$c>> @() @() sat_sHq sat_sHr


Now I pass this to GHC's `specBind`, but the output is exactly the same as the 
input! (or it's close enough that I can't spot the difference).

(>>=)
  :: forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
[GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=]
(>>=)
  = \ (@(m :: * -> *)) (v_sGm [Occ=Once1!] :: Monad m) ->
  case v_sGm of
  { C:Monad _ [Occ=Dead] v_sGp [Occ=Once1] _ [Occ=Dead] ->
  v_sGp
  }
$dm>> :: forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
[GblId, Arity=3, Unf=OtherCon []]
$dm>>
  = \ (@(m :: * -> *))
  ($dMonad [Occ=Once1] :: Monad m)
  (@a)
  (@b)
  (ma [Occ=Once1] :: m a)
  (mb [Occ=OnceL1] :: m b) ->
  let {
sat_MHt [Occ=Once1] :: a -> m b
[LclId]
sat_MHt = \ _ [Occ=Dead] -> mb } in
  >>= @m $dMonad @a @b ma sat_MHt
C:Monad [InlPrag=NOUSERINLINE CONLIKE]
  :: forall (m :: * -> *).
 Applicative m
 -> (forall a b. m a -> (a -> m b) -> m b)
 -> (forall a b. m a -> m b -> m b)
 -> Monad m
[GblId[DataCon], Arity=3, Caf=NoCafRefs, Cpr=m1, Unf=OtherCon []]
C:Monad
  = \ (@(m :: * -> *))
  (eta_B0 [Occ=Once1] :: Applicative m)
   

RE: Instantiation of overloaded definition *in Core*

2021-10-04 Thread Simon Peyton Jones via ghc-devs
You can look it up in the class instance environment, which the Simplifier does 
have access to it.  That's relatively easy when you have a simple dictionary 
like (Monad IO).  But if you want (Eq [Int]) you first of all have to look up 
the (Eq [a]) dictionary, then the Eq Int dictionary, and apply the former to 
the latter.  We don't (yet) have a simple API to do that, although it would not 
be hard to create one.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Erdi, Gergo via 
ghc-devs
Sent: 04 October 2021 10:30
To: 'GHC' 
Cc: Montelatici, Raphael Laurent 
Subject: Instantiation of overloaded definition *in Core*


PUBLIC

Hi,

I'd like to instantiate Core definitions. For example, suppose I have the 
following Core definition:

foo :: forall m a b. Monad m => m a -> m b -> m b
foo = \ @m ($d :: Monad m) @a @b (ma :: m a) (mb :: m b) -> ...

Now let's say I'd like to instantiate it for m ~ IO. It is quite 
straightforward to go from the above to:

foo_IO_0 :: forall a b. Monad IO => IO a -> IO b -> IO b
foo_IO_0 = \ ($d :: Monad IO) @a @b (ma :: IO a) (mb :: IO b) -> ...

However, I would like to go all the way to:

foo_IO :: forall a b. IO a -> IO b -> IO b
foo_IO = \ @a @b (ma :: IO a) (mb :: IO b) -> ...

Because instances are coherent, it should be sound to replace all occurrences 
of $d with "the" dictionary for Monad IO. However, the places I've found for 
this kind of query seem to live in the typechecker. How do I access this 
information while working with Core?

Thanks,
Gergo

This email and any attachments are confidential and may also be privileged. If 
you are not the intended recipient, please delete all copies and notify the 
sender immediately. You may wish to refer to the incorporation details of 
Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at 
https: //www.sc.com/en/our-locations

Where you have a Financial Markets relationship with Standard Chartered PLC, 
Standard Chartered Bank and their subsidiaries (the "Group"), information on 
the regulatory standards we adhere to and how it may affect you can be found in 
our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and Regulatory 
Compliance Disclosures at http: //www.sc.com/rcs/fm

Insofar as this communication is not sent by the Global Research team and 
contains any market commentary, the market commentary has been prepared by the 
sales and/or trading desk of Standard Chartered Bank or its affiliate. It is 
not and does not constitute research material, independent research, 
recommendation or financial advice. Any market commentary is for information 
purpose only and shall not be relied on for any other purpose and is subject to 
the relevant disclaimers available at https: 
//www.sc.com/en/regulatory-disclosures/#market-disclaimer.

Insofar as this communication is sent by the Global Research team and contains 
any research materials prepared by members of the team, the research material 
is for information purpose only and shall not be relied on for any other 
purpose, and is subject to the relevant disclaimers available at https: 
//research.sc.com/research/api/application/static/terms-and-conditions.

Insofar as this e-mail contains the term sheet for a proposed transaction, by 
responding affirmatively to this e-mail, you agree that you have understood the 
terms and conditions in the attached term sheet and evaluated the merits and 
risks of the transaction. We may at times also request you to sign the term 
sheet to acknowledge the same.

Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for 
important information with respect to derivative products.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: SOLVED: GHC 9.3 API panics with "No home unit"

2021-09-29 Thread Simon Peyton Jones via ghc-devs
Norman,

I'm glad you are unstuck.

We badly need a bird's eye view of the GHC API, with chapters about specific 
bits. It shouldn't be a question of trial an error.  But it evolved rather than 
being designed, and since then everyone's shortest path to completion is simply 
to find a way through and execute on it.

If you felt able to write down what you have learned, we could make it part of 
GHC's user manual, and improve it incrementally.   I know that's not on your 
shortest path to completion either, but you have particularly superior writing 
skills, and I think you might find that others join in if you took the lead.

Also then you could say "but why do you need to do getSession not newHscEnv, 
and we might be able to fill in some of the rationale rather than just write 
down cookbook recipes.  And it might lead to design changes too, I hope.

Posting here in the hope that others say "oh yes, I'd love to help with that"! 

Simon


PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use simon.peytonjo...@gmail.com 
instead.  (For now, it just forwards to simo...@microsoft.com.)

|  -Original Message-
|  From: ghc-devs  On Behalf Of Norman
|  Ramsey
|  Sent: 29 September 2021 00:36
|  Cc: ghc-devs@haskell.org
|  Subject: SOLVED: GHC 9.3 API panics with "No home unit"
|  
|   > The code worked in the 9.0 API, but using the 9.3 API causes a
|  panic:
|   >
|   >   sandbox: panic! (the 'impossible' happened)
|   > GHC version 9.3.20210918:
|   >   unsafeGetHomeUnit: No home unit
|  
|  SOLVED: I was getting an `HscEnv` by using `newHscEnv` with a
|  `DynFlags`.
|  Turns out I'm not supposed to do that; using `getSession` instead
|  solved the problem.  Thanks to Cheng Shao for the diagnosis!
|  
|  If there is something I can read to help me avoid similar mistakes in
|  the future, please point me in its direction!
|  
|  
|  Norman
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C96b747b71fd6484be28c
|  08d982d8f526%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637684691082
|  936473%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=A4Mw547%2FzPS1w6WZ%2BkR11
|  f%2F5GMxccIUOqcCPjvIRXVk%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Documenting GHC: blogs, wiki pages, Notes, Haddocks, etc

2021-09-14 Thread Simon Peyton Jones via ghc-devs
te them where Haddock expects you to put 
documentation, and refer to them from the relevant spot in the code?
Viktor (in CC) has done a wonderful work at producing nice layouts for Haddocks 
in base, and we could learn a couple of lessons from his MRs.

---

Now, on the matter of improving Haddock to understand GHC's notes, I'd like to 
remind everyone that Haddock is currently understaffed in terms of feature 
development, and I would like to call to everyone with experience dealing with 
its codebase to give a hand in refactoring, dusting off and improving the code 
so that its maintainability is not jeopardised by people simply going elsewhere.
Our bus factor (or as I like to call it, circus factor), is quite terrifying 
considering the importance of the tool in our ecosystem.


¹ 
https://haskell-haddock.readthedocs.io/en/latest/markup.html#named-chunks<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fhaskell-haddock.readthedocs.io%2Fen%2Flatest%2Fmarkup.html%23named-chunks=04%7C01%7Csimonpj%40microsoft.com%7C1bd0b32d10d941aff47008d977883fda%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637672251247580027%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=34wGCjxKe4A0u9hiIHHG82PN82gxV1MM%2B7w2Kl2RFT0%3D=0>
Le 14/09/2021 à 13:56, Simon Peyton Jones via ghc-devs a écrit :
Alfredo writes (below for full thread)

That is a deceptively simple question you ask there :-) I don't have a strong 
view myself, but I can offer the perspective of somebody who was been for a 
long time on the "other side of the trenches" (i.e. working Haskell programmer, 
not necessarily working GHC programmer):

* Blog post: yes, it's true that is a snapshot, and it's true that is not under 
GHC's gitlab umbrella, so I wouldn't treat it as a reliable source of 
documentation (for the reasons you also explain) but it's surely a good 
testament that "at this point in time, for this particular GHC commit, things 
were this way);

* The wiki page: in the past, when I wanted to learn more about some GHC 
feature, Google would point me to the relevant Wiki page on the GHC repo 
describing such a feature, but I have to say I have almost always dismissed it, 
because everybody knows Wikis are seldomly up-to-date :) In order for a Wiki 
page to work we would have to at least add a banner at the top that states this 
can be trusted as a reliable source of information, and offer in the main 
section the current, up-to-date design. We can still offer the historical 
breakdown of the designs in later sections, as it's still valuable info to keep;

* GHC notes: I have always considered GHC notes a double-edge sword -- from one 
side they are immensely useful when navigating the source code, but these won't 
be rendered in the Hackage's haddocks, and this is not helpful for 
GHC-the-library users willing to understand how to use (or which is the 
semantic of) a particular type (sure, one can click "Show Source" on Hackage 
but it's an annoying extra step to do just to hunt for notes). We already have 
Notes for this work in strategic places -- even better, we have proper Haddock 
comments for things like "Severity vs DiagnosticReason" , e.g. 
https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Types/Error.hs#L279<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fblob%2Fmaster%2Fcompiler%2FGHC%2FTypes%2FError.hs%23L279=04%7C01%7Csimonpj%40microsoft.com%7C1bd0b32d10d941aff47008d977883fda%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637672251247590020%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=wnMtmaZ3aQKLqKgsEXBuq3RiOt5%2FkYcpwrzmNb6Asdw%3D=0>
 .


Yes Haddock doesn’t understand Notes but that’s a deficiency in Haddock!  There 
so much in GHC that simply does not fit well with the Haddocks attached to a 
particular data decl or function.  We need Notes to explain how all the moving 
parts fit together, and to point to them.

Even better, we have proper Haddock comments for things like "Severity vs 
DiagnosticReason"

But I don’t think this is better – I think it is significantly worse!   In the 
case you cite, the Haddock is about DiagnosticReason, and mentions Severity 
only incidentally.  I bet that the Haddock for Severity doesn’t refer to this.  
 Nor is there a clear “Note [Severity vs DiagnosticReason]” title that bits of 
code across GHC can refer to by saying “See Note [Severity vs 
DiagnosticReason]”.   It’s far less satisfactory (to me) than a single Note that
· covers just one topic (the difference between Severity and 
DiagnosticReason, rather than fully describing either
· can be pointed to symmetrically from both Severity and 
DiagnosticReason
· can be pointed to by many other bits of code

The way it is better is that today’s Haddock doesn’t understand Notes.  But we 
could 

RE: More type safety in Core?

2021-09-14 Thread Simon Peyton Jones via ghc-devs
One difficulty is that I think that writing Core-to-Core passes might become a 
lot more challenging.   It gets gnarly writing code that satisfies the type 
checker, depending of course on how strong the invariants are.

I think Typesafe runtime code 
generation
 has some material on this.

TL;DR: by all means give it a try.  I'm not terribly optimistic... but progress 
is made when we find that things we thought weren't possible are possible after 
all.  So I'd be happy to be proved wrong.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: ghc-devs  On Behalf Of Ari Fordsham
Sent: 14 September 2021 13:39
To: ghc-devs@haskell.org
Subject: More type safety in Core?

You don't often get email from 
arifords...@gmail.com. Learn why this is 
important
I don't know if this is the right forum for this, I apologise if I'm 
intruding...

Are there any plans to use the type system to enforce safety in Core, via e.g. 
GADTs? This would replace much of core-lint with static checking.

Conal Eliottt has done something similar in a blog post 
(http://conal.net/blog/posts/overloading-lambda#:~:text=Haskell%20source%20language.-,I,-originally%20intended%20to)
 and it seems relatively straightforward.

This would be especially beneficial to those working at the cutting edge of GHC 
features, statically ensuring their Core manipulations are correct. I would be 
surprised if existing compiler bugs wouldn't be found while implementing this.

What would the performance impact be? would using GADTs incur extra overhead? 
I'd assume you'd save something by lugging around less type information in Core.

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


Documenting GHC: blogs, wiki pages, Notes, Haddocks, etc

2021-09-14 Thread Simon Peyton Jones via ghc-devs
Alfredo writes (below for full thread)

That is a deceptively simple question you ask there :-) I don't have a strong 
view myself, but I can offer the perspective of somebody who was been for a 
long time on the "other side of the trenches" (i.e. working Haskell programmer, 
not necessarily working GHC programmer):

* Blog post: yes, it's true that is a snapshot, and it's true that is not under 
GHC's gitlab umbrella, so I wouldn't treat it as a reliable source of 
documentation (for the reasons you also explain) but it's surely a good 
testament that "at this point in time, for this particular GHC commit, things 
were this way);

* The wiki page: in the past, when I wanted to learn more about some GHC 
feature, Google would point me to the relevant Wiki page on the GHC repo 
describing such a feature, but I have to say I have almost always dismissed it, 
because everybody knows Wikis are seldomly up-to-date :) In order for a Wiki 
page to work we would have to at least add a banner at the top that states this 
can be trusted as a reliable source of information, and offer in the main 
section the current, up-to-date design. We can still offer the historical 
breakdown of the designs in later sections, as it's still valuable info to keep;

* GHC notes: I have always considered GHC notes a double-edge sword -- from one 
side they are immensely useful when navigating the source code, but these won't 
be rendered in the Hackage's haddocks, and this is not helpful for 
GHC-the-library users willing to understand how to use (or which is the 
semantic of) a particular type (sure, one can click "Show Source" on Hackage 
but it's an annoying extra step to do just to hunt for notes). We already have 
Notes for this work in strategic places -- even better, we have proper Haddock 
comments for things like "Severity vs DiagnosticReason" , e.g. 
https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Types/Error.hs#L279
 .


Yes Haddock doesn't understand Notes but that's a deficiency in Haddock!  There 
so much in GHC that simply does not fit well with the Haddocks attached to a 
particular data decl or function.  We need Notes to explain how all the moving 
parts fit together, and to point to them.

Even better, we have proper Haddock comments for things like "Severity vs 
DiagnosticReason"

But I don't think this is better - I think it is significantly worse!   In the 
case you cite, the Haddock is about DiagnosticReason, and mentions Severity 
only incidentally.  I bet that the Haddock for Severity doesn't refer to this.  
 Nor is there a clear "Note [Severity vs DiagnosticReason]" title that bits of 
code across GHC can refer to by saying "See Note [Severity vs 
DiagnosticReason]".   It's far less satisfactory (to me) than a single Note that

  *   covers just one topic (the difference between Severity and 
DiagnosticReason, rather than fully describing either
  *   can be pointed to symmetrically from both Severity and DiagnosticReason
  *   can be pointed to by many other bits of code

The way it is better is that today's Haddock doesn't understand Notes.  But we 
could fix that if we were minded to.

Returning to how to document the error-message architecture, if you'd prefer to 
use a Note than a wiki page, that's fine.  But please write that Overview Note 
that explains all the pieces, points to them one by one.  And then copiously 
refer to that Note from all those places, so people will update it.

Hopefully as the time goes by the new design will "spread" across all the 
different peers working on GHC, and it will become "second nature".

I really don't think that will happen unless there is a Note that explains what 
the new design is!  Lacking this explicit design, everyone will infer their own 
mental model of how it all works from sundry scattered clues - and those mental 
models will differ.   So instead of one thing "spreading"  a dozen subtly 
different things will spread.  And then the next one, confused by these 
slightly different clues, will be even less coherent.

Let's have one, fully-explicit version of The Plan that we constantly refer to.

cc'ing ghc-devs because we must constantly question and refine how we describe 
and document GHC.

Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

From: Alfredo Di Napoli 

Resuming normal service

2021-09-13 Thread Simon Peyton Jones via ghc-devs
Friends
What with the summer holidays and leaving MSR, I've been rather preoccupied and 
have done almost nothing on GHC for the last six weeks.
I'm getting back in action now - I hope.  But my GHC backlog is huge.  If you 
are waiting on some response from me, please feel free to ping me.
Simon

PS: I am leaving Microsoft at the end of November 2021, at which point 
simo...@microsoft.com will cease to work.  Use 
simon.peytonjo...@gmail.com instead.  (For 
now, it just forwards to simo...@microsoft.com.)

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


RE: Question about specialization

2021-09-06 Thread Simon Peyton Jones via ghc-devs
Harendra

That comes as a surprise to me.  Could you possibly make a repo case, and say 
what version of the compiler does, and does not, specialise the function?

File it as a ticket … to me it looks like a bug.

Thanks

Simon

From: ghc-devs  On Behalf Of Harendra Kumar
Sent: 06 September 2021 14:11
To: ghc-devs@haskell.org
Subject: Question about specialization

Hi GHC devs,

I have a simple program using the streamly library, as follows, the whole code 
is in the same module:

{-# INLINE iterateState #-}
{-# SPECIALIZE iterateState :: Int -> SerialT (StateT Int IO) Int #-}
iterateState :: MonadState Int m => Int -> SerialT m Int
iterateState n = do
x <- get
if x > n
then do
put (x - 1)
iterateState n
else return x

main :: IO ()
main = do
State.evalStateT (S.drain (iterateState 0)) 10

Earlier the SPECIALIZE pragma was not required on iterateState, but after some 
refactoring in the library (the monad bind of SerialT changed a bit), this 
program now requires a SPECIALIZE on iterateState to trigger specialization, 
just INLINE also does not help.

My question is whether this may be expected in some conditions or is this 
something which can be considered a bug in the compiler? I am also curious what 
specifically could have made the compiler not specialize this anymore, is it 
the size of the function or some other threshold?

Thanks,
Harendra


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


RE: New implementation for `ImpredicativeTypes`

2021-09-02 Thread Simon Peyton Jones via ghc-devs
Of course not. The same was true for QuickLook, though, wasn't it?
No, not at all.   QuickLook required zero changes to GHC's intermediate 
language - it impacted only the type inference system.   Adding existentials 
will entail a substantial change to the intermediate language, affecting every 
optimisation pass.

Simon

From: Alex Rozenshteyn 
Sent: 02 September 2021 18:13
To: Simon Peyton Jones 
Cc: GHC developers 
Subject: Re: New implementation for `ImpredicativeTypes`

So it's not just a question of saying "just add that paper to GHC and voila job 
done".

Of course not. The same was true for QuickLook, though, wasn't it?

On Thu, Sep 2, 2021 at 12:42 PM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
If I understand correctly, the recent ICFP paper "An Existential Crisis 
Resolved"
 finally enables this; is that right?
It describes one way to include existentials in GHC's intermediate language, 
which is a real contribution. But it is not a small change.  So it's not just a 
question of saying "just add that paper to GHC and voila job done".

Simon

From: Alex Rozenshteyn mailto:rpglove...@gmail.com>>
Sent: 02 September 2021 17:10
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: GHC developers mailto:ghc-devs@haskell.org>>
Subject: Re: New implementation for `ImpredicativeTypes`

If I understand correctly, the recent ICFP paper "An Existential Crisis 
Resolved"
 finally enables this; is that right?

On Mon, Sep 9, 2019 at 12:00 PM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
Suppose Haskell did have existentials;

Yes, I think that's an interesting thing to work on!  I'm not sure what the 
implications would be.  At very least we'd need to extend System FC (GHC's 
intermediate language) with existential types and the corresponding pack and 
unpack syntactic forms.

I don't know of any work studying that question specifically, but others may 
have pointers.

simon

From: Alex Rozenshteyn mailto:rpglove...@gmail.com>>
Sent: 06 September 2019 15:21
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: Alejandro Serrano Mena mailto:trup...@gmail.com>>; GHC 
developers mailto:ghc-devs@haskell.org>>
Subject: Re: New implementation for `ImpredicativeTypes`

Hi Simon,

You're exactly right, of course. My example is confusing, so let me see if I 
can clarify.

What I want in the ideal is map show [1, 'a', "b"]. That is, minimal syntactic 
overhead to mapping a function over multiple values of distinct types that 
results in a homogeneous list. As the reddit thread points out, there are 
workarounds involving TH or wrapping each element in a constructor or using 
bespoke operators, but when it comes down to it, none of them actually allows 
me to say what I mean; the TH one is closest, but I reach for TH only in times 
of desperation.

I had thought that one of the things preventing this was lack of impredicative 
instantiation, but now I'm not sure. Suppose Haskell did have existentials; 
would map show @(exists a. Show a => a) [1, 'a', "b"] work in current Haskell 
and/or in quick-look?

Tangentially, do you have a reference for what difficulties arise in adding 
existentials to Haskell? I have a feeling that it would make working with GADTs 
more ergonomic.

On Fri, Sep 6, 2019 at 12:33 AM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
I'm confused.   Char does not have the type (forall a. Show a =>a), so our 
example is iill-typed in System F, never mind about type inference.  Perhaps 
there's a typo?   I think you may have ment
   exists a. Show a => a
which doesn't exist in Haskell.  You can write existentials with a data type

data Showable where
   S :: forall a. Show a => a -> Showable

Then
   map show [S 1, S 'a', S "b"]
works fine today (without our new stuff), provided you say

   instance Show Showable where
 show (S x) = show x

Our new system can only type programs that can be written in System F.   (The 
tricky bit is inferring the impredicative instantiations.)

Simon

From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> On Behalf 
Of Alex Rozenshteyn
Sent: 06 September 2019 03:31
To: Alejandro Serrano Mena 

RE: New implementation for `ImpredicativeTypes`

2021-09-02 Thread Simon Peyton Jones via ghc-devs
If I understand correctly, the recent ICFP paper "An Existential Crisis 
Resolved"
 finally enables this; is that right?
It describes one way to include existentials in GHC's intermediate language, 
which is a real contribution. But it is not a small change.  So it's not just a 
question of saying "just add that paper to GHC and voila job done".

Simon

From: Alex Rozenshteyn 
Sent: 02 September 2021 17:10
To: Simon Peyton Jones 
Cc: GHC developers 
Subject: Re: New implementation for `ImpredicativeTypes`

If I understand correctly, the recent ICFP paper "An Existential Crisis 
Resolved"
 finally enables this; is that right?

On Mon, Sep 9, 2019 at 12:00 PM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
Suppose Haskell did have existentials;

Yes, I think that's an interesting thing to work on!  I'm not sure what the 
implications would be.  At very least we'd need to extend System FC (GHC's 
intermediate language) with existential types and the corresponding pack and 
unpack syntactic forms.

I don't know of any work studying that question specifically, but others may 
have pointers.

simon

From: Alex Rozenshteyn mailto:rpglove...@gmail.com>>
Sent: 06 September 2019 15:21
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: Alejandro Serrano Mena mailto:trup...@gmail.com>>; GHC 
developers mailto:ghc-devs@haskell.org>>
Subject: Re: New implementation for `ImpredicativeTypes`

Hi Simon,

You're exactly right, of course. My example is confusing, so let me see if I 
can clarify.

What I want in the ideal is map show [1, 'a', "b"]. That is, minimal syntactic 
overhead to mapping a function over multiple values of distinct types that 
results in a homogeneous list. As the reddit thread points out, there are 
workarounds involving TH or wrapping each element in a constructor or using 
bespoke operators, but when it comes down to it, none of them actually allows 
me to say what I mean; the TH one is closest, but I reach for TH only in times 
of desperation.

I had thought that one of the things preventing this was lack of impredicative 
instantiation, but now I'm not sure. Suppose Haskell did have existentials; 
would map show @(exists a. Show a => a) [1, 'a', "b"] work in current Haskell 
and/or in quick-look?

Tangentially, do you have a reference for what difficulties arise in adding 
existentials to Haskell? I have a feeling that it would make working with GADTs 
more ergonomic.

On Fri, Sep 6, 2019 at 12:33 AM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
I'm confused.   Char does not have the type (forall a. Show a =>a), so our 
example is iill-typed in System F, never mind about type inference.  Perhaps 
there's a typo?   I think you may have ment
   exists a. Show a => a
which doesn't exist in Haskell.  You can write existentials with a data type

data Showable where
   S :: forall a. Show a => a -> Showable

Then
   map show [S 1, S 'a', S "b"]
works fine today (without our new stuff), provided you say

   instance Show Showable where
 show (S x) = show x

Our new system can only type programs that can be written in System F.   (The 
tricky bit is inferring the impredicative instantiations.)

Simon

From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> On Behalf 
Of Alex Rozenshteyn
Sent: 06 September 2019 03:31
To: Alejandro Serrano Mena mailto:trup...@gmail.com>>
Cc: GHC developers mailto:ghc-devs@haskell.org>>
Subject: Re: New implementation for `ImpredicativeTypes`

I didn't say anything when you were requesting use cases, so I have no right to 
complain, but I'm still a little disappointed that this doesn't fix my 
(admittedly very minor) issue: 

RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating)

2021-07-16 Thread Simon Peyton Jones via ghc-devs
But then, does that mean that the `ol_witness` field of the `OverLit` is not 
used by the renamer at all?


* In (HsOverLit GhcPs), which is the output of the parser, and the 
input of the renamer, the ol_witness field is garbage.  See 
GHC.Hs.Utils.mkHsIntegral, which fills that field with `noExpr`.

* In (HsOverLit GhcRn), which is the output of the renamer, and the 
input of the typechecker, the ol_witness fiels is (HsVar ), of type 
(HsExpr GhcRn), where  is the Name of the fromX function.

* In (HsOverLit GhcTc), which is the output of the typechecker and the 
input of the desugarer, the ol_witness field is the expression (fromX lit), of 
type (HsExpr GhcTc), the literal value itself.

Some, but not all, of this is stated in Note [Overloaded literal witnesses] in 
Language.Haskell.Syntax.Lit.hs

maybe the intention of `ol_witness` is to be for "entertainment purposes only",

Not exactly. In the parser we have to make a field of type (HsExpr GhcPs), and 
that's what noExpr is.  But no one looks it, ever.

in which case instead of just fixing the docs, we should move `ol_witness` from 
`HsOverLit` to `XOverLit GhcRn` and `XOverLit GhcTc`.

Yes, it would be much better to use the extension field.  That would stop the 
(GHC-independent) Language.Haskell.Syntax needing to talk about "witnesses".

If you tackle this (which would be great) you might want to look at the other 
uses of noExpr too.

OK?  Maybe start by making a ticket for this change.

Simon

From: Erdi, Gergo 
Sent: 12 July 2021 09:59
To: Simon Peyton Jones 
Cc: 'GHC' 
Subject: RE: Using overloaded syntax to avoid `base` dependency (RE: Marking 
ParsedModule fragments as non-user-originating)


PUBLIC

Thanks, this is useful and it is starting to convince myself that there *is* a 
documentation bug here.

It seems the big thing I was missing was the existence of `hsOverLitName`. 
That's what returns `Data.String.fromString` for overloaded string literals. 
But then, does that mean that the `ol_witness` field of the `OverLit` is not 
used by the renamer at all? This contradicts the Note, or maybe I am reading it 
too wishfully - maybe the intention of `ol_witness` is to be for "entertainment 
purposes only",  i.e. something provided by the parser for third-party tools 
but not consumed by the renamer. Or maybe `ol_witness` is only to be used in 
getting information *from* the renamer to the typechecker (note that the code 
you pasted below doesn't use the input's `ol_witness` field for anything at 
all), in which case instead of just fixing the docs, we should move 
`ol_witness` from `HsOverLit` to `XOverLit GhcRn` and `XOverLit GhcTc`. I'm 
happy to prepare a patch for this (code + Note) if you agree this is the 
correct reading of the current code.

Thanks,
Gergo

From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Monday, July 12, 2021 4:37 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>
Cc: 'GHC' mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: 
Marking ParsedModule fragments as non-user-originating)

I don't really understand how my question fits into the 'bug report' bucket. 
The quoted passage is not from the user manual, but rather, from a GHC Note

Only that GHC is doing something that you think is wrong - or at least not as 
documented.  If so, that's a bug. If not, the conversation is illuminating, and 
more easily rediscovered later in the bug tracker.

I am not interested in end-to-end behaviour, but what actually happens GHC 
phase by GHC phase. When is the reference to `fromString` introduced, when is 
it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` 
allo me to replace not just `fromString`, but also `unpackCString#`?

I'm happy to help - but can I ask that when you think you understand, can you 
submit a patch that clarifies the relevant Note(s), or adds one, so that the 
Gergos of the future will find the answer laid out right where you tried to 
find it?

In GHC.Rename.Pat


rnOverLit origLit

  = do  { opt_NumDecimals <- xoptM LangExt.NumDecimals

; let { lit@(OverLit {ol_val=val})

| opt_NumDecimals = origLit {ol_val = generalizeOverLitVal (ol_val 
origLit)}

| otherwise   = origLit

  }

; let std_name = hsOverLitName val

; (from_thing_name, fvs1) <- lookupSyntaxName std_name




  *   hsOverLitName returns Data.String.fromString for string literals. That is 
where fromString first appears.


  *   Then lookupSyntaxName just returns Data.String.fromString when 
RebindableSyntax is off; or looks up "fromString" when RebindableSyntax is on.

When I say "Data.String.fromString" here, I mean the original name i.e. the 
fromString defined in Data.String - not some possibly different entity that 
happens to be in scope with the qualified name  "Data.String.fromString".

Does that help?



From: Erdi, Gergo mailto:gergo.e...@sc.com>>

RE: Potential improvement in compacting GC

2021-07-14 Thread Simon Peyton Jones via ghc-devs
Thanks Omer

I had an interesting conversation with Steve Blackburn, the brains behind
the MMTk memory management toolkit recently
https://www.mmtk.io/

MMTk is designed to be a re-usable, open-source garbage collector, specifically
designed to be usable with lots of languages. In principle this is a great
idea: GC is such a big field that no runtime (GHC's included) can ever devote
enough effort to GC to do a really state of the art job.  It makes sense for
one bunch of people to stellar GC and another bunch to simply reuse their
work.

Of course, the interface between the GC and the mutator, scheduler, etc
is particularly intimate.  Teasing them apart in GHC would be a significant
task, and success would not be guaranteed.

But Steve is interested in working on this, with help from our end, perhaps
initially with a student (or volunteer) project or two.

If it worked, it'd be cool.  

Here's a talk about MMTk: https://www.youtube.com/watch?v=3L6XEVaYAmU

Simon


|  -Original Message-
|  From: ghc-devs  On Behalf Of Ömer Sinan
|  Agacan
|  Sent: 14 July 2021 07:27
|  To: ghc-devs 
|  Subject: Re: Potential improvement in compacting GC
|  
|  Two other ideas that should improve GHC's compacting GC much more
|  significantly. I've implemented both of these in another project and
|  the results were great. In a GC benchmark (mutator does almost no work
|  other than allocating data using a bump allocator), first one reduced
|  Wasm instructions executed by 14%, second one 19.8%.
|  
|  Both of these ideas require pushing object headers to the mark stack
|  with the objects, which means larger mark stacks. This is the only
|  downside of these algorithms.
|  
|  - Instead of marking and then threading in the next pass, mark phase
|  threads
|all fields when pushing the fields to the mark stack. We still need
|  two other
|passes: one to unthread headers, another to move the objects. (we
|  can't do
|both in one pass, let me know if you're curious and I can elaborate)
|  
|This has the same number of passes as the current implementation,
|  but it only
|visits object fields once. Currently, we visit fields once when
|  marking, to
|mark fields, then again in `update_fwd`. This implementation does
|  both in one
|pass over the fields. `update_fwd` does not visit fields.
|  
|This reduced Wasm instructions executed by 14% in my benchmark.
|  
|  - Marking phase threads backwards pointers (ignores forwards
|  pointers). Then we
|do one pass instead of two: for a marked object, unthread it (update
|forwards pointers to the object's new location), move it to its new
|  location,
|then thread its forwards pointers. This completely eliminates one of
|  the 3
|passes, but fields need to be visited twice as before (unlike the
|  algorithm
|above).
|  
|I think this one is originally described in "An Efficient Garbage
|  Compaction
|Algorithm", but I found that paper to be difficult to follow. A
|  short
|description of the same algorithm exists in "High-Performance
|  Garbage
|Collection for Memory-Constrained Environments" in section 5.1.2.
|  
|This reduced Wasm instructions executed by 19.8% in my benchmark.
|  
|In this algorithm, fields that won't be moved can be threaded any
|  time before
|the second pass (pointed objects need to be marked and pushed to the
|  mark
|stack with headers before threading a field). For example, in GHC,
|  mut list
|entries can be threaded before or after marking (but before the
|  second pass)
|as IIRC mut lists are not moved. Same for fields of large objects.
|  
|  As far as I can see, mark-compact GC is still the default when max
|  heap size is specified and the oldest generation size is (by default)
|  more than 30% of the max heap size. I'm not sure if max heap size is
|  specified often (it's off by default), so not sure what would be the
|  impact of these improvements be, but if anyone would be interested in
|  funding me to implement these ideas (second algorithm above, and the
|  bitmap iteration in the previous email) I could try to allocate one or
|  two days a week to finish in a few months.
|  
|  Normally these are simple changes, but it's difficult to test and
|  debug GHC's RTS as we don't have a test suite readily available and
|  the code is not easily testable. In my previous implementations of
|  these algorithms I had unit tests for the GC where I could easily
|  generate arbitrary graphs (with cycles, backwards ptrs, forwards ptrs,
|  ptrs from/to roots etc.) and test GC in isolation. Implementation of
|  (2) took less than a day, and I didn't have to debug it more once the
|  tests passed. It's really unfortunate that GHC's RTS makes this kind
|  of thing difficult..
|  
|  Ömer
|  
|  Ömer Sinan Ağacan , 7 Oca 2021 Per, 20:42
|  tarihinde şunu yazdı:
|  >
|  > Hello,
|  >
|  > I recently implemented the algorithm used by GHC's compacting GC in
|  > another 

RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating)

2021-07-12 Thread Simon Peyton Jones via ghc-devs
I don't really understand how my question fits into the 'bug report' bucket. 
The quoted passage is not from the user manual, but rather, from a GHC Note

Only that GHC is doing something that you think is wrong - or at least not as 
documented.  If so, that's a bug. If not, the conversation is illuminating, and 
more easily rediscovered later in the bug tracker.

I am not interested in end-to-end behaviour, but what actually happens GHC 
phase by GHC phase. When is the reference to `fromString` introduced, when is 
it resolved (by default to `Data.String.fromString`), does `RebindableSyntax` 
allo me to replace not just `fromString`, but also `unpackCString#`?

I'm happy to help - but can I ask that when you think you understand, can you 
submit a patch that clarifies the relevant Note(s), or adds one, so that the 
Gergos of the future will find the answer laid out right where you tried to 
find it?

In GHC.Rename.Pat


rnOverLit origLit

  = do  { opt_NumDecimals <- xoptM LangExt.NumDecimals

; let { lit@(OverLit {ol_val=val})

| opt_NumDecimals = origLit {ol_val = generalizeOverLitVal (ol_val 
origLit)}

| otherwise   = origLit

  }

; let std_name = hsOverLitName val

; (from_thing_name, fvs1) <- lookupSyntaxName std_name




  *   hsOverLitName returns Data.String.fromString for string literals. That is 
where fromString first appears.


  *   Then lookupSyntaxName just returns Data.String.fromString when 
RebindableSyntax is off; or looks up "fromString" when RebindableSyntax is on.

When I say "Data.String.fromString" here, I mean the original name i.e. the 
fromString defined in Data.String - not some possibly different entity that 
happens to be in scope with the qualified name  "Data.String.fromString".

Does that help?



From: Erdi, Gergo 
Sent: 12 July 2021 09:21
To: Simon Peyton Jones 
Cc: 'GHC' 
Subject: RE: Using overloaded syntax to avoid `base` dependency (RE: Marking 
ParsedModule fragments as non-user-originating)


PUBLIC

I don't really understand how my question fits into the 'bug report' bucket. 
The quoted passage is not from the user manual, but rather, from a GHC Note. My 
reading of that note was that if I write a string literal in a Haskell program, 
and compile it with OverloadedStrings, it would parse into `HsLit _ (HsString _ 
fs)` with `HsOverLit _ (OverLit _ (HsIsString _ fs) "Data.String.fromString"`, 
and then the renamer and the type checker would work from that. If this 
understanding were correct, then I could generate parsed (and not yet 
renamed/typechecked) code that is, instead, `HsOverLit _ (OverLit _ (HsIsString 
_ fs) "myStringLitUnpackerFunction"`, and there would be no `fromString` 
dependency. Yet, that's not what seems to happen.

Can you (or anyone else) go into more detail about how rebindable syntax 
resolution and OverloadedStrings interacts in this particular case? I am not 
interested in end-to-end behaviour, but what actually happens GHC phase by GHC 
phase. When is the reference to `fromString` introduced, when is it resolved 
(by default to `Data.String.fromString`), does `RebindableSyntax` allo me to 
replace not just `fromString`, but also `unpackCString#`?


From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Monday, July 12, 2021 3:32 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>
Cc: 'GHC' mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Using overloaded syntax to avoid `base` dependency (RE: 
Marking ParsedModule fragments as non-user-originating)

Gergo,

If you think you have uncovered a bug, could you submit a bug report on the 
issue tracker, with a way to reproduce it? It's a bit hard to decode exactly 
what is happening from what you say.

The user manual documentation doesn't say this in so many words (that's a bug), 
but with OverloadedStrings, the literal "foo" is replaced by 
Data.String.fromString "foo"

Guessing a bit, that is probably why GHC complains that it can't load 
Data.String.fromString.

If in addition you want to use your own fromString, not the built-in one, then 
you need to add RebindableSyntax.

Simon

From: Erdi, Gergo mailto:gergo.e...@sc.com>>
Sent: 12 July 2021 08:13
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: 'GHC' mailto:ghc-devs@haskell.org>>
Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking 
ParsedModule fragments as non-user-originating)


PUBLIC

OK so I tried out OverloadedStrings and it basically went as bad as I expected. 
The documentation on `HsOverLit` is very promising: it points to the Note 
[Overloaded literal witnesses], which states:

Note [Overloaded literal witnesses]
~~~
*Before* type checking, the HsExpr in an HsOverLit is the
name of the coercion function, 'fromInteger' or 'fromRational'.

So that sounds great, right? It sounds like just before renaming, I should be 
able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ 
(HsIsString 

RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating)

2021-07-12 Thread Simon Peyton Jones via ghc-devs
Gergo,

If you think you have uncovered a bug, could you submit a bug report on the 
issue tracker, with a way to reproduce it? It's a bit hard to decode exactly 
what is happening from what you say.

The user manual documentation doesn't say this in so many words (that's a bug), 
but with OverloadedStrings, the literal "foo" is replaced by 
Data.String.fromString "foo"

Guessing a bit, that is probably why GHC complains that it can't load 
Data.String.fromString.

If in addition you want to use your own fromString, not the built-in one, then 
you need to add RebindableSyntax.

Simon

From: Erdi, Gergo 
Sent: 12 July 2021 08:13
To: Simon Peyton Jones 
Cc: 'GHC' 
Subject: Using overloaded syntax to avoid `base` dependency (RE: Marking 
ParsedModule fragments as non-user-originating)


PUBLIC

OK so I tried out OverloadedStrings and it basically went as bad as I expected. 
The documentation on `HsOverLit` is very promising: it points to the Note 
[Overloaded literal witnesses], which states:

Note [Overloaded literal witnesses]
~~~
*Before* type checking, the HsExpr in an HsOverLit is the
name of the coercion function, 'fromInteger' or 'fromRational'.

So that sounds great, right? It sounds like just before renaming, I should be 
able to replace `HsLit _ (HsString _ fs)` with `HsOverLit _ (OverLit _ 
(HsIsString _ fs) unpack` with my own `unpack` function coming from my own 
package, and everything would work out. Unfortunately, this is not what 
happens: if I try getting this through the renamer, I get this error:

Failed to load interface for 'Data.String'
no unit id matching 'base' was found
Can't find interface-file declaration for variable fromString
  Probable cause: bug in .hi-boot file, or inconsistent .hi file
  Use -ddump-if-trace to get an idea of which file caused the error

So even though I am specifying my own coercion function, it is still looking 
for `Data.String.fromString` which is not going to work, since I don't have 
`base`. So either I am misunderstanding that Note, or it is simply out of date, 
but in either case, this isn't going to be a viable route to going base-less.

Gergo

From: Erdi, Gergo
Sent: Tuesday, July 6, 2021 5:39 PM
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: GHC mailto:ghc-devs@haskell.org>>
Subject: RE: Marking ParsedModule fragments as non-user-originating


PUBLIC

Thanks Simon!

Of course, you're right, it's the renamer, not the typechecker - I didn't 
really check, just saw that "it happens during `typecheckModule`.

I'll look at the rebindable syntax stuff in detail, but at least for 
OverloadedStrings, I already know that the problem will be that ultimately they 
do go through the `String` type from `base`, and I need to use GHC baselessly. 
This is a problem for two reasons:


  *   I can't implement `IsString` for `MyString`, because `IsString` is in 
`base`
  *   Even if I made my own fake `base` with a fake `IsString` class, there is 
nothing to put in the codomain of `fromString`: I *only* have `MyString`, not 
`String`. And renaming `MyString to `String` in my fake `base` is not going to 
cut it, since `String` is wired into GHC to be a type synonym for `[Char]` 
(which `MyString` is not).

I foresee similar problems for OverloadedLists :/

Thanks,
Gergo

From: Simon Peyton Jones mailto:simo...@microsoft.com>>
Sent: Tuesday, July 6, 2021 5:08 PM
To: Erdi, Gergo mailto:gergo.e...@sc.com>>
Cc: GHC mailto:ghc-devs@haskell.org>>
Subject: [External] RE: Marking ParsedModule fragments as non-user-originating

The typechecker now complains that the `ViewPatterns` language extension is not 
turned on

I think it's the renamer:


rnPatAndThen mk p@(ViewPat _ expr pat)

  = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns

  ; checkErr vp_flag (badViewPat p) }


More generally, don't you just want OverloadedStrings or OverloadedLists?

You might want to read Note [Handling overloaded and rebindable constructs] in 
GHC.Rename.Expr, and
Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr.  These Notes describe 
how GHC already does something similar to what you want.   Maybe you can use 
the same mechanism in your plugin.

Simon



From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> On Behalf 
Of Erdi, Gergo via ghc-devs
Sent: 06 July 2021 09:08
To: ghc-devs@haskell.org
Subject: Marking ParsedModule fragments as non-user-originating


PUBLIC

Hi,

I'd like to hijack some syntax (like string literals or list patterns) for my 
own use, and I thought a low-tech way of doing that is to transform the 
ParsedModule before typechecking. For example, if I have a function `uncons :: 
Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into 
the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just 
(x3, (uncons -> Nothing)))` and let the normal GHC type checker take over 
from here.

This is working 

RE: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`?

2021-07-06 Thread Simon Peyton Jones via ghc-devs
1. What prevents us from adding `NamedFieldPuns` as a proper constructor for 
the `Extension` type and in principle remove `RecordPuns`? Backward 
compatibility I assume?
You mean, essentially, rename `LangExt.RecordPuns` to `NamedFieldPuns`.

I’d be fine with that.  There might be back-compat issues, but only with other 
plugins, and probably with vanishingly few of them.  Grep in Hackage!

Simon

From: ghc-devs  On Behalf Of Alfredo Di Napoli
Sent: 06 July 2021 10:14
To: Simon Peyton Jones via ghc-devs 
Subject: Can NamedFieldPuns be added to 
`GHC.LanguageExtensions.Types.Extension`?

Dear all,

As some of you might know, for the past few months I have been working on 
changing GHC's diagnostic messages from plain SDocs to richer Haskell types.

As part of this work, I have added a mechanism to embed hints into diagnostics, 
defined in `GHC.Types.Hint` in `HEAD`. One of the main workhorse of this 
`GhcHint` type is the `SuggestExtension LangExt.Extension` constructor, which 
embeds the extension to enable to use a particular feature. The 
`LangExt.Extension` type comes from `GHC.LanguageExtensions.Types`, and up 
until now there has always been a 1:1 mapping between the language pragma for 
the extension and the type itself.

Today I was working on turning this error into a proper Haskell type:

badPun :: Located RdrName -> TcRnMessage
badPun fld = TcRnUnknownMessage $ mkPlainError noHints $
  vcat [text "Illegal use of punning for field" <+> quotes (ppr fld),
text "Use NamedFieldPuns to permit this"]

I was ready to yield a `SuggestExtension LangExt.NamedFieldPuns` when I 
discovered that there is no `NamedFieldPuns` constructor. Rather, there is a 
`RecordPuns` , which refer to a deprecated flag, and we simply map 
`NamedFieldPuns` back to it in `GHC.Driver.Session`:

...
  depFlagSpec' "RecordPuns"   LangExt.RecordPuns
(deprecatedForExtension "NamedFieldPuns"),
...
  flagSpec "NamedFieldPuns"   LangExt.RecordPuns,
...

This is problematic for the `GhcHint` type, because now if I was to yield 
`SuggestExtension LangExt.RecordPuns` to the user, I could still pretty-print 
the suggestion to turn `RecordPuns` into `NamedFieldPuns`, but this means that 
IDEs or third-party library would have access to the
"raw" Haskell datatype, and at that point they will be stuck with a suggestion 
to enable a deprecated extension! (or best case scenario they will have to 
transform the suggestion into something more sensible, which partially defeats 
the point of this refactoring work I have been doing).

I am not sure this behaviour is unique for just `NamedFieldPuns`, but my 
question is:

1. What prevents us from adding `NamedFieldPuns` as a proper constructor for 
the `Extension` type and in principle remove `RecordPuns`? Backward 
compatibility I assume?


Many thanks,

Alfredo








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


RE: Trying to speedup GHC compile times...Help!

2021-07-06 Thread Simon Peyton Jones via ghc-devs
I love "Scrap Your Type Applications" (SYTA) too, although I'm a little biased 
since I'm a co-author.

But SYTA is a change that has a pretty pervasive effect on the way GHC 
manipulates types. Since then we've added TypeInType, from which a lot of 
consequences flowed.  I simply don't know how hard it'd be to do a "scrap your 
type applications" job on GHC today. I agree that the cost/benefit tradeoff 
could have shifted.

We can only find out by trying it.  But trying it would take quite a lot of 
work.  On the other hand, SYTA is the only principled approach that I know of 
that solves the type blow-up we get with deeply-nested data types (notoriously, 
tuples).  It's a problem we have known of for decades, but is still essentially 
unsolved.

Simon

|  -Original Message-
|  From: ghc-devs  On Behalf Of Viktor Dukhovni
|  Sent: 02 July 2021 15:30
|  To: ghc-devs@haskell.org
|  Subject: Re: Trying to speedup GHC compile times...Help!
|  
|  On Fri, Jul 02, 2021 at 08:08:39AM +, Simon Peyton Jones via ghc-devs
|  wrote:
|  
|  > I strongly urge you to keep a constantly-update status wiki page,
|  > which lists the ideas you are working on, and points to relevant
|  > resources and tickets.  An email thread like this is a good way to
|  > gather ideas, but NOT a good way to organise and track them.
|  
|  I remain curious as to whether "Scrap your type applications" is worth a
|  second look.  There are edge cases in which compile time blowup is a result
|  of type blowup (as opposed to code blowup via inlining).  Might GHC have
|  changed enough in the last ~5 years to make it now "another
|  compiler":
|  
|  
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fwww.micros
|  oft.com%2Fen-us%2Fresearch%2Fwp-
|  content%2Fuploads%2F2016%2F07%2Fif.pdfdata=04%7C01%7Csimonpj%40microsof
|  t.com%7C7effa9c7dd004554fdf408d93d6626f0%7C72f988bf86f141af91ab2d7cd011db47%
|  7C1%7C0%7C637608331663562915%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJ
|  QIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=brNlPRnQgHqbTSO
|  AOs9hbZOdC84VZfhfnO8g%2BtwSKOQ%3Dreserved=0
|  
|  (Section 4.4):
|  
|  Overall, allocation decreased by a mere 0.1%. The largest reduction was
|  4%, and the largest increase was 12%, but 120 of the 130 modules showed
|  a
|  change of less than 1%. Presumably, the reduction in work that arises
|  from smaller types is balanced by the additional overheads of SystemIF.
|  On this evidence, the additional complexity introduced by the new
|  reduction rules does not pay its way. Nevertheless, these are matters
|  that are dominated by nitty-gritty representation details, and the
|  balance might well be different in another compiler.
|  
|  Could it be that some of the more compile time intensive packages on hackage
|  (aeson, vector, ...) would benefit more than the various modules in base?
|  
|  Wild speculation aside, of course finding and fixing inefficiencies in the
|  implementation of existing common primitive should be a win across the
|  board, and should not require changing major compiler design features, just
|  leaner code.
|  
|  --
|  Viktor.
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskel
|  l.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C7effa9c7dd004554fdf408d93d
|  6626f0%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608331663562915%7CUnk
|  nown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXV
|  CI6Mn0%3D%7C3000sdata=OYuQV%2FP3Sgly62Ex5m1kwv5ciHLchWEXq7XvvPYJCJ4%3D&
|  amp;reserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Marking ParsedModule fragments as non-user-originating

2021-07-06 Thread Simon Peyton Jones via ghc-devs

The typechecker now complains that the `ViewPatterns` language extension is not 
turned on

I think it's the renamer:


rnPatAndThen mk p@(ViewPat _ expr pat)

  = do { liftCps $ do { vp_flag <- xoptM LangExt.ViewPatterns

  ; checkErr vp_flag (badViewPat p) }


More generally, don't you just want OverloadedStrings or OverloadedLists?

You might want to read Note [Handling overloaded and rebindable constructs] in 
GHC.Rename.Expr, and
Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr.  These Notes describe 
how GHC already does something similar to what you want.   Maybe you can use 
the same mechanism in your plugin.

Simon



From: ghc-devs  On Behalf Of Erdi, Gergo via 
ghc-devs
Sent: 06 July 2021 09:08
To: ghc-devs@haskell.org
Subject: Marking ParsedModule fragments as non-user-originating


PUBLIC

Hi,

I'd like to hijack some syntax (like string literals or list patterns) for my 
own use, and I thought a low-tech way of doing that is to transform the 
ParsedModule before typechecking. For example, if I have a function `uncons :: 
Array a -> Maybe (a, Array a)`, I can rewrite the pattern `[x1, x2, x3]` into 
the view pattern `(uncons -> Just (x1, (uncons -> Just (x2, (uncons -> Just 
(x3, (uncons -> Nothing)))` and let the normal GHC type checker take over 
from here.

This is working for me so far, except for one problem: the typechecker now 
complains that the `ViewPatterns` language extension is not turned on. I would 
like to make the view patterns coming from my ParsedModule rewriter to be 
exempt from this check (but of course still require the `ViewPatterns` 
extension for user-originating code). Is there a way to do that? Or would I be 
better off checking for user-originating view patterns myself before the 
rewrite and then changing the `DynFlags` to always enable view patterns for 
typechecking?

Thanks,
Gergo

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


RE: Trying to speedup GHC compile times...Help!

2021-07-02 Thread Simon Peyton Jones via ghc-devs
GHC precisely use "the rapier".

S

From: Christiaan Baaij 
Sent: 02 July 2021 15:38
To: Simon Peyton Jones 
Cc: Richard Eisenberg ; Young, Jeff ; 
ghc-devs@haskell.org
Subject: Re: Trying to speedup GHC compile times...Help!

Somewhat off-topic: does GHC no longer use "the rapier"? I thought the 
InScopeSet was needed to check that we can safely skip on extending the 
substitution as you go under binders when the binder is not in the InScopeSet 
(naively you would always have to rename binders, and thus extend the 
substitution, in order to avoid capture as you go under binders). i.e. the 
IntMap is not just used to generate new variable names, but to ensure the 
compiler does less work in the form of doing fewer substitutions.

On Fri, 2 Jul 2021 at 16:12, Simon Peyton Jones via ghc-devs 
mailto:ghc-devs@haskell.org>> wrote:
There are lot of places where it would be pretty tiresome to plumb a unique 
supply guaranteed unique from every other.   I think the current setup works 
pretty well - but I bet we can squeeze cycles out of its implementation.

Simon

From: Richard Eisenberg mailto:li...@richarde.dev>>
Sent: 02 July 2021 14:26
To: Simon Peyton Jones mailto:simo...@microsoft.com>>
Cc: Young, Jeff mailto:jeff.yo...@tweag.io>>; 
ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>
Subject: Re: Trying to speedup GHC compile times...Help!

One piece I'm curious about, reading this thread: why do we have so many 
IntMaps and operations on them? Name lookup is a fundamental operation a 
compiler must do, and that would use an IntMap: good. But maybe there are other 
IntMaps used that are less necessary. A key example: whenever we do 
substitution, we track an InScopeSet, which is really just an IntMap. This 
InScopeSet remembers the name of all variables in scope, useful when we need to 
create a new variable name (this is done by uniqAway). Yet perhaps the tracking 
of these in-scope variables is very expensive and comprises much of the IntMap 
time. Might it be better just to always work in a monad capable of giving fresh 
names? We actually don't even need a monad, if that's too annoying. Instead, we 
could just pass around an infinite list of fresh uniques. This would still be 
clutterful, but if it grants us a big speed improvement, the clutter might be 
worth it.

The high-level piece here is that there may be good things that come from 
understanding where these IntMaps arise.

Richard

On Jul 2, 2021, at 4:08 AM, Simon Peyton Jones via ghc-devs 
mailto:ghc-devs@haskell.org>> wrote:

Jeff

Great stuff!  Welcome.

I strongly urge you to keep a constantly-update status wiki page, which lists 
the ideas you are working on, and points to relevant resources and tickets.  An 
email thread like this is a good way to gather ideas, but NOT a good way to 
organise and track them.

Looking carefully at profiles is a good plan.  That's the hard data!

I think that some careful investigation of IntMap (at least the bits that GHC 
uses heavily) would be a good idea.  Clearly we spend a lot of time in these 
maps, so speedups here will yield a lot of benefit.  Look at the heavy hitters 
from the profile, stare at the Core code and see if it's s good as it can be.

For example, Sebastian discovered a strange infelicity in IntMap.lookup, which 
I've documented in a new ticket
https://gitlab.haskell.org/ghc/ghc/-/issues/20069<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fissues%2F20069=04%7C01%7Csimonpj%40microsoft.com%7C022a3006cf304fea267f08d93d6712f3%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608335192973373%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=Thx5296%2FvxiRQrtN7G68Vy9D105bp7xfYgO%2FHyZYwmo%3D=0>

I think it'd also be worth measuring how unbalanced our IntMap trees get.  See
   
https://gitlab.haskell.org/ghc/ghc/-/issues/19820<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fissues%2F19820=04%7C01%7Csimonpj%40microsoft.com%7C022a3006cf304fea267f08d93d6712f3%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608335192983371%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=LIFyRfRa9AYd97hLxVcJw6RWcB1vU8Nsb%2BPq3JohonM%3D=0>
The speculation there is that we are getting very unbalanced trees.  So measure 
it!  If it's true, we could improve matters by using a different IntMap; or 
maybe by scrambling the key a bit --- see the ticket.

Simon

From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> On Behalf 
Of Young, Jeff
Sent: 02 July 2021 02:36
To: ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>
Subject: Trying to speedup GHC compile times...Help!

Hi ghc devs,

I'm a long-time Haskeller but am just getting into GHC development. I started a 
12 week internship at Tweag I/O under Richard Eisenberg this wee

RE: Trying to speedup GHC compile times...Help!

2021-07-02 Thread Simon Peyton Jones via ghc-devs
There are lot of places where it would be pretty tiresome to plumb a unique 
supply guaranteed unique from every other.   I think the current setup works 
pretty well - but I bet we can squeeze cycles out of its implementation.

Simon

From: Richard Eisenberg 
Sent: 02 July 2021 14:26
To: Simon Peyton Jones 
Cc: Young, Jeff ; ghc-devs@haskell.org
Subject: Re: Trying to speedup GHC compile times...Help!

One piece I'm curious about, reading this thread: why do we have so many 
IntMaps and operations on them? Name lookup is a fundamental operation a 
compiler must do, and that would use an IntMap: good. But maybe there are other 
IntMaps used that are less necessary. A key example: whenever we do 
substitution, we track an InScopeSet, which is really just an IntMap. This 
InScopeSet remembers the name of all variables in scope, useful when we need to 
create a new variable name (this is done by uniqAway). Yet perhaps the tracking 
of these in-scope variables is very expensive and comprises much of the IntMap 
time. Might it be better just to always work in a monad capable of giving fresh 
names? We actually don't even need a monad, if that's too annoying. Instead, we 
could just pass around an infinite list of fresh uniques. This would still be 
clutterful, but if it grants us a big speed improvement, the clutter might be 
worth it.

The high-level piece here is that there may be good things that come from 
understanding where these IntMaps arise.

Richard


On Jul 2, 2021, at 4:08 AM, Simon Peyton Jones via ghc-devs 
mailto:ghc-devs@haskell.org>> wrote:

Jeff

Great stuff!  Welcome.

I strongly urge you to keep a constantly-update status wiki page, which lists 
the ideas you are working on, and points to relevant resources and tickets.  An 
email thread like this is a good way to gather ideas, but NOT a good way to 
organise and track them.

Looking carefully at profiles is a good plan.  That's the hard data!

I think that some careful investigation of IntMap (at least the bits that GHC 
uses heavily) would be a good idea.  Clearly we spend a lot of time in these 
maps, so speedups here will yield a lot of benefit.  Look at the heavy hitters 
from the profile, stare at the Core code and see if it's s good as it can be.

For example, Sebastian discovered a strange infelicity in IntMap.lookup, which 
I've documented in a new ticket
https://gitlab.haskell.org/ghc/ghc/-/issues/20069<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fissues%2F20069=04%7C01%7Csimonpj%40microsoft.com%7Cd477d24fb159472b77ab08d93d5cfbb7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608293368167086%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=dSEa4md56IpyMGRPHW%2BVjWtZQGDi7vpVgmOCukyHTIU%3D=0>

I think it'd also be worth measuring how unbalanced our IntMap trees get.  See
   
https://gitlab.haskell.org/ghc/ghc/-/issues/19820<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fissues%2F19820=04%7C01%7Csimonpj%40microsoft.com%7Cd477d24fb159472b77ab08d93d5cfbb7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608293368167086%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=5rgCmwBbb4mZ9NWoT7RtzRPFFND4e13k2XWeQkwgM%2FY%3D=0>
The speculation there is that we are getting very unbalanced trees.  So measure 
it!  If it's true, we could improve matters by using a different IntMap; or 
maybe by scrambling the key a bit --- see the ticket.

Simon

From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> On Behalf 
Of Young, Jeff
Sent: 02 July 2021 02:36
To: ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>
Subject: Trying to speedup GHC compile times...Help!

Hi ghc devs,

I'm a long-time Haskeller but am just getting into GHC development. I started a 
12 week internship at Tweag I/O under Richard Eisenberg this week with the 
singular goal to speedup GHC compile times. I'm specifically looking to 
contribute to ghc issues 
18541<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fissues%2F18541=04%7C01%7Csimonpj%40microsoft.com%7Cd477d24fb159472b77ab08d93d5cfbb7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608293368177079%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=az67TZRzofQayj%2BGsc0aYUibVff1Z%2Fs0%2Bvvt4oD6yaM%3D=0>and
 
18535<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fissues%2F18535=04%7C01%7Csimonpj%40microsoft.com%7Cd477d24fb159472b77ab08d93d5cfbb7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637608293368177079%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=zVUtIY1ux%2BRfHBUsI2BoHM3hOK9O8p0W90F7qqk7TeA%3D=0>.
 So I thought I would reach out to the community to get some direct

RE: Trying to speedup GHC compile times...Help!

2021-07-02 Thread Simon Peyton Jones via ghc-devs
Jeff

Great stuff!  Welcome.

I strongly urge you to keep a constantly-update status wiki page, which lists 
the ideas you are working on, and points to relevant resources and tickets.  An 
email thread like this is a good way to gather ideas, but NOT a good way to 
organise and track them.

Looking carefully at profiles is a good plan.  That's the hard data!

I think that some careful investigation of IntMap (at least the bits that GHC 
uses heavily) would be a good idea.  Clearly we spend a lot of time in these 
maps, so speedups here will yield a lot of benefit.  Look at the heavy hitters 
from the profile, stare at the Core code and see if it's s good as it can be.

For example, Sebastian discovered a strange infelicity in IntMap.lookup, which 
I've documented in a new ticket
https://gitlab.haskell.org/ghc/ghc/-/issues/20069

I think it'd also be worth measuring how unbalanced our IntMap trees get.  See
   https://gitlab.haskell.org/ghc/ghc/-/issues/19820
The speculation there is that we are getting very unbalanced trees.  So measure 
it!  If it's true, we could improve matters by using a different IntMap; or 
maybe by scrambling the key a bit --- see the ticket.

Simon

From: ghc-devs  On Behalf Of Young, Jeff
Sent: 02 July 2021 02:36
To: ghc-devs@haskell.org
Subject: Trying to speedup GHC compile times...Help!

Hi ghc devs,

I'm a long-time Haskeller but am just getting into GHC development. I started a 
12 week internship at Tweag I/O under Richard Eisenberg this week with the 
singular goal to speedup GHC compile times. I'm specifically looking to 
contribute to ghc issues 
18541
 and 
18535.
 So I thought I would reach out to the community to get some direction on 
issues/features/problems to tackle in the pursuit of faster compilation times. 
This is a full time internship and so I think there is a real opportunity to 
nail down a deliverable for the community, but I want to get some guidance from 
the experts (you fine people!) before going down a rabbit hole.

To be specific I'm looking for lingering items such as:
  1. It would be great if we had  but no one has time.
  2. Primop foo is half complete but is the right type for 
.
  3. Swap  to an array-like type non-incrementally, that is, 
establish a patch that rips out the previous type and replaces it with the 
array-like across the entire compiler, rather than module-by-module.

Point 2 is a specific reference to MR 
3571
 but I'm unsure of the status and etiquette around MRs, and I'm unsure exactly 
how fulfilling the todos at the end of that MR would aid in faster compilation 
times (and if there is evidence to that effect somewhere).

Thanks for the help!

- Jeff



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


RE: Is there a way to prevent reboxing in W/W (due to OPAQUE pragma proposal)

2021-06-24 Thread Simon Peyton Jones via ghc-devs
Christiaan

I'm totally paged out on this.  Would you like to do this via a comment on 
!5562, giving a concrete example of a small program that doesn't behave as you 
expect with your patch?

Sebastian may be able to help too.

Simon

From: ghc-devs  On Behalf Of Christiaan Baaij
Sent: 24 June 2021 10:56
To: ghc-devs 
Subject: Is there a way to prevent reboxing in W/W (due to OPAQUE pragma 
proposal)

Hi Ghc-Devs,

I believe I've mostly finished the implementation of GHC proposal 0415 [1], the 
OPAQUE pragma, over at: 
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5562

The only remaining issue is that I'm unsure whether there's a way to prevent 
reboxing of worker arguments as witnessed here: 
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5562/diffs#29ad02619a9f318d67c6cd19648917dbb17354e9_0_134

Note that the reboxing doesn't happen in the worker of the OPAQUE-annotated 
bindings, because OPAQUE-annotated bindings aren't W/W-transformed, but in a 
worker of a function that calls the OPAQUE-annotated binding.
This reboxing was the reason behind the descision to W/W transform 
NOINLINE-annotated bindings in: 
https://gitlab.haskell.org/ghc/ghc/-/commit/b572aadb20c2e41e2f6d7b48401bd0b4239ce9f8

But the whole idea behind OPAQUE is not to change calls to the annotated 
binding f by some call of a name-mangled version of f; so W/W transforming 
OPAQUE-annoted binders is not an option.

Any hints on how to avoid the reboxing (if possible) would be appreciated, like:
* Do I need to change something in GHC.Core.Opt.WorkWrap? or
* Do I need to change the demand/strictness signature of OPAQUE-annoted 
bindings?
* or something else?

Thanks,

Christiaan

[1] 
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0415-opaque-pragma.rst
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Is simplified subsumption really necessary?

2021-06-20 Thread Simon Peyton Jones via ghc-devs
Yes, maybe the seq thing would be possible.   But it feels like a hack, and I'm 
far from convinced that the optimiser would really eliminate the overhead.
If I was convinced that deep subsumption was really better, it might be worth 
investigating the hack more deeply.   But in fact I've become convinced of the 
opposite, that deep subsumption just isn't worth the extra complexity - the 
simpler system allows Quick Look for example.

Simon

From: John Ericson 
Sent: 20 June 2021 18:07
To: ghc-devs ; Simon Peyton Jones 
Subject: Re: Is simplified subsumption really necessary?


I'm sorry, I misunderstood the paper and thought the depth of the instantiation 
and subsumption could be varied more independently.

That said, what about the seq example below? Does forcing any function that is 
eta expanded like that sketchy to you? There is still a runtime cost to the eta 
expansion, but think with more elbow grease that could also be addressed 
(post-type-erasure optimization or new coercions).

John
On 6/18/21 3:56 PM, Simon Peyton Jones wrote:
Richard's paper argues for lazy rather than eager instantiation.

It does not argue for deep rather than shallow subsumption and instantiation; 
on the contrary, it argues for shallow.  (That is, for "simple subsumption".)   
And it is simple subsumption that is the focus of this conversation.

Simon

From: John Ericson 
<mailto:john.ericson@obsidian.systems>
Sent: 18 June 2021 16:56
To: ghc-devs <mailto:ghc-devs@haskell.org>
Cc: Simon Peyton Jones <mailto:simo...@microsoft.com>
Subject: Re: Is simplified subsumption really necessary?


On 6/16/21 12:00 PM, Simon Peyton Jones via ghc-devs wrote:
 I'm sorry to hear that Chris.   It's exactly backwards from what I would 
expect - the typing rules with simple subsumption are, well, simpler than those 
for complicated subsumption, and so one might hope that your intuition had 
fewer complexities to grapple with.

In 
https://richarde.dev/papers/2021/stability/stability.pdf<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fricharde.dev%2Fpapers%2F2021%2Fstability%2Fstability.pdf=04%7C01%7Csimonpj%40microsoft.com%7Cb9916cabe3744e44375008d9340dca51%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637598056497592691%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=SqgQIEVpLIARanGOqvKDNOjG%2FtLFZ6v1XVXzCFD1FQE%3D=0>
 it is written

The analysis around stability in this paper strongly suggests that GHC should 
use the lazy, shallow approach to instantiation. Yet the struggles with lazy 
instantiation above remain. In order to simplify the implementation, GHC has 
recently (for GHC 9.0) switched to use exclusively eager instantiation.This 
choice sacrifices stability for convenience in implementation.

I think the principles outlined in the paper are very good, and explain the 
queasiness some users may feel in 9.0

But wouldn't it be possible to choose a desugaring with seq that doesn't do so?

I just don't know how to do that.  Maybe someone else does.

Is it not

  f `seq` \x -> f x

and similar? I haven't thought about the issue in a while or in very much 
depth, but when I first discussed the proposal years back with some other 
people at work, they spit-balled the same counter-proposal.



Having little "skin in the game" as I haven't yet ported any serious programs 
over to 9.0, I suppose I am glad the experimentation with QuickLook is 
happening, and OK that our accepting on-par fewer programs now opens design 
space for later (i.e. we got the breakage out of the way.) But I certainly 
think there are improvements in the spirit outlined in Richard's paper to be 
done down the road.

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


RE: Is simplified subsumption really necessary?

2021-06-18 Thread Simon Peyton Jones via ghc-devs
Richard's paper argues for lazy rather than eager instantiation.

It does not argue for deep rather than shallow subsumption and instantiation; 
on the contrary, it argues for shallow.  (That is, for "simple subsumption".)   
And it is simple subsumption that is the focus of this conversation.

Simon

From: John Ericson 
Sent: 18 June 2021 16:56
To: ghc-devs 
Cc: Simon Peyton Jones 
Subject: Re: Is simplified subsumption really necessary?


On 6/16/21 12:00 PM, Simon Peyton Jones via ghc-devs wrote:
 I'm sorry to hear that Chris.   It's exactly backwards from what I would 
expect - the typing rules with simple subsumption are, well, simpler than those 
for complicated subsumption, and so one might hope that your intuition had 
fewer complexities to grapple with.

In 
https://richarde.dev/papers/2021/stability/stability.pdf<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fricharde.dev%2Fpapers%2F2021%2Fstability%2Fstability.pdf=04%7C01%7Csimonpj%40microsoft.com%7C7655b09d06a54a4af03508d9327193cd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637596286139778988%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=R1quXKjsnEjusvX%2BSxhPT25t%2B%2Bwqwo7mTPhnulvctQ0%3D=0>
 it is written

The analysis around stability in this paper strongly suggests that GHC should 
use the lazy, shallow approach to instantiation. Yet the struggles with lazy 
instantiation above remain. In order to simplify the implementation, GHC has 
recently (for GHC 9.0) switched to use exclusively eager instantiation.This 
choice sacrifices stability for convenience in implementation.

I think the principles outlined in the paper are very good, and explain the 
queasiness some users may feel in 9.0

But wouldn't it be possible to choose a desugaring with seq that doesn't do so?

I just don't know how to do that.  Maybe someone else does.

Is it not

  f `seq` \x -> f x

and similar? I haven't thought about the issue in a while or in very much 
depth, but when I first discussed the proposal years back with some other 
people at work, they spit-balled the same counter-proposal.



Having little "skin in the game" as I haven't yet ported any serious programs 
over to 9.0, I suppose I am glad the experimentation with QuickLook is 
happening, and OK that our accepting on-par fewer programs now opens design 
space for later (i.e. we got the breakage out of the way.) But I certainly 
think there are improvements in the spirit outlined in Richard's paper to be 
done down the road.

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


RE: Error message degradation for (<= :: Nat -> Nat -> Constraint) in GHC 9.2+

2021-06-17 Thread Simon Peyton Jones via ghc-devs
Christiaan,

Do please submit a bug report on GHC's issue tracker, with a way to reproduce 
it.

Thanks

Simon

From: ghc-devs  On Behalf Of Christiaan Baaij
Sent: 17 June 2021 10:44
To: ghc-devs 
Subject: Error message degradation for (<= :: Nat -> Nat -> Constraint) in GHC 
9.2+

Hi Ghc-Devs,

When upgrading one of our tc plugins 
https://hackage.haskell.org/package/ghc-typelits-natnormalise
 to GHC 9.2, one of our tests, repeated here:

```
{-# LANGUAGE DataKinds, TypeFamilies, TypeOperators #-}
module TestInEq where

import Data.Proxy
import GHC.TypeLits

proxyInEq :: (a <= b) => Proxy a -> Proxy b -> ()
proxyInEq _ _ = ()

proxyInEq1 :: Proxy a -> Proxy (a+1) -> ()
proxyInEq1 = proxyInEq
```

degraded quite badly in terms of the error message.
Where in GHC 9.0.1 we get:

```
TestInEq.hs:11:14: error:
* Couldn't match type 'a <=? (a + 1)' with ''True'
arising from a use of 'proxyInEq'
* In the expression: proxyInEq
  In an equation for 'proxyInEq1': proxyInEq1 = proxyInEq
* Relevant bindings include
proxyInEq1 :: Proxy a -> Proxy (a + 1) -> ()
  (bound at TestInEq.hs:11:1)
   |
11 | proxyInEq1 = proxyInEq
   |
```

with GHC 9.2.0.20210422 we get:

```
TestInEq.hs:11:14: error:
* Couldn't match type 'Data.Type.Ord.OrdCond
 (CmpNat a (a + 1)) 'True 'True 'False'
 with ''True'
arising from a use of 'proxyInEq'
* In the expression: proxyInEq
  In an equation for 'proxyInEq1': proxyInEq1 = proxyInEq
* Relevant bindings include
proxyInEq1 :: Proxy a -> Proxy (a + 1) -> ()
  (bound at TestInEq.hs:11:1)
   |
11 | proxyInEq1 = proxyInEq
   |
```

Errors messages involving type-level naturals and their operations already 
weren't the poster-child of comprehensable GHC error messages, but this change 
has made the situation worse in my opinion.

This change in error message is due to: 
https://gitlab.haskell.org/ghc/ghc/-/commit/eea96042f1e8682605ae68db10f2bcdd7dab923e

Is there a way we can get the nicer pre-9.2.0.2021 error message again before 
the proper 9.2.1 release?
e.g. by doing one of the following:
1. Reinstate `(<=? :: Nat -> Nat -> Bool)` as a builtin type family
2. Somehow add a custom type-error to `Data.Type.Ord.OrdCond`
3. Don't expand type aliases in type errors

What do you think? should this be fixed? should this be fixed before the 9.2.1 
release?

-- Christiaan

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


RE: Is simplified subsumption really necessary?

2021-06-16 Thread Simon Peyton Jones via ghc-devs
rather, it's that it completely screws up my intuition about what should be 
valid Haskell.

I'm sorry to hear that Chris.   It's exactly backwards from what I would expect 
- the typing rules with simple subsumption are, well, simpler than those for 
complicated subsumption, and so one might hope that your intuition had fewer 
complexities to grapple with.

Maybe it's partly a matter of explanation and presentation.  Do you have an 
example of a case in which your intuition was screwed up by the simple 
subsumption rules?  Discussing in the abstract is often un-illuminating.

But wouldn't it be possible to choose a desugaring with seq that doesn't do so?

I just don't know how to do that.  Maybe someone else does.

Meanwhile, Quick 
Look
 depends strongly on simple subsumption.  And I'm very keen on QL.

Simon


From: ghc-devs  On Behalf Of Chris Smith
Sent: 16 June 2021 14:39
To: GHC developers 
Subject: Is simplified subsumption really necessary?

This might be in the "ship has sailed" territory, but I'd like to bring it up 
anyway.  
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0287-simplify-subsumption.rst
 says:

Suppose GHC lacked all four features, and someone proposed adding them. That 
proposal would never leave the launchpad.

Let's test that hypothesis.

I've been spending increasing amounts of time fighting against simplified 
subsumption while porting Haskell code to GHC 9.0.  It's not that any specific 
instance of this problem is hard to fix; rather, it's that it completely screws 
up my intuition about what should be valid Haskell.  It doesn't help that HLS 
still requires 8.10.4, so I usually don't find out I've broken my libraries for 
GHC 9.0 until continuous integration kicks in.  At this point, it's become 
fairly routine that my code that works fine with 8.10.4 is broken with 9.0, and 
this makes me sad.

Understandably, eta expansion reducing the strictness of terms is bad.  But 
wouldn't it be possible to choose a desugaring with seq that doesn't do so?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: abstract interpreter for GHC Core or STG

2021-06-08 Thread Simon Peyton Jones via ghc-devs
I wonder if there was an attempt in the past to create an abstract interpreter 
for GHC Core or STG to approximate the program runtime behaviour?

No, not that I know of.   Because of all the primops, concurrency, STM, etc, it 
would be something of a challenge.  The AAM story could be interesting…

Simon

From: ghc-devs  On Behalf Of Csaba Hruska
Sent: 07 June 2021 15:18
To: GHC developers 
Subject: abstract interpreter for GHC Core or STG

Hello,

I wonder if there was an attempt in the past to create an abstract interpreter 
for GHC Core or STG to approximate the program runtime behaviour?
I'm curious because I'd like to turn my external STG interterpreter to an 
abstract interpreter using the AAM (Abstracting Abstract Machines) method.
This approach seems promising to me because a single Haskell code base (ext STG 
interpreter) could be the specification of the Haskell operational semantics 
and also be a detailed static analyzer that could help optimization 
transformations.
I'm interested in any attempt that happened during GHC/Haskell evolution.

Regards,
Csaba Hruska
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: ghcup failed

2021-06-02 Thread Simon Peyton Jones via ghc-devs
Update: Tom Ellis helped me to discover that I probably had not completed my 
WSL1 -> WSL2 changeover on my laptop, so the error I got below came from WSL1.
Once we’d unravelled that, the error went away.  So it seems that WSL1 is to 
blame, not ghcup, happily.
I wonder if someone might add to this page https://www.haskell.org/ghcup/

  *   a prominent notice saying “Does not work with WLS1”,
  *   explaining how to find out how to know what version you are running (wsl 
-l -v in Powershell)
  *   pointing to the instructions for upgrading to WSL2 
https://docs.microsoft.com/en-us/windows/wsl/install-win10
Thanks
Simon

From: ghc-devs  On Behalf Of Simon Peyton Jones 
via ghc-devs
Sent: 02 June 2021 20:07
To: GHC 
Cc: Julian Ospald 
Subject: ghcup failed

Dear devs
I wanted to install GHC 8.10 on my WSL2 (Windows Subsystem for Linux) computer. 
 So I went here
https://www.haskell.org/ghcup/<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fwww.haskell.org%2Fghcup%2F=04%7C01%7Csimonpj%40microsoft.com%7C941d2a501a8a451f026b08d925f9c287%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637582576926132378%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=Qbhmg5LysvmW2srYmLM2AONWdG5SvZJVOtRFFFlHfNw%3D=0>
and followed the instructions (the curl … command).  There was a long pause then

[ Info  ] verifying digest of: ghc-8.10.4-x86_64-deb9-linux.tar.xz

[ Info  ] Unpacking: ghc-8.10.4-x86_64-deb9-linux.tar.xz to /tmp/ghcup-khiegA

[ Info  ] Installing GHC (this may take a while)

[ Error ] BuildFailed failed in dir "/tmp/ghcup-khiegA": NonZeroExit 2 "make" 
["install"]

Check the logs at "/home/simonpj/.ghcup/logs" and the build directory 
"/tmp/ghcup-khiegA" for more clues.

Make sure to clean up "/tmp/ghcup-khiegA" afterwards.

"_eghcup --cache install ghc recommended" failed!
I looked in the logs as suggested, and found this in the tail of ghc-make.log

Installing library in 
/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/libiserv-8.10.4

"utils/ghc-cabal/dist-install/build/tmp/ghc-cabal-bindist" copy compiler stage2 
"strip" '' '/home/simonpj/.ghcup/ghc/8.10.4' 
'/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4' 
'/home/simonpj/.ghcup/ghc/8.10.4/share/doc/ghc-8.10.4/html/libraries' 'v p dyn'

Installing library in /home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/ghc-8.10.4

"/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/bin/ghc-pkg" --force 
--global-package-db 
"/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/package.conf.d" update 
rts/dist/package.conf.install

ghc-pkg: Couldn't open database 
/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/package.conf.d for modification: 
{handle: 
/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/package.conf.d/package.cache.lock}:
 hLock: invalid argument (Invalid argument)

ghc.mk:967: recipe for target 'install_packages' failed

make[1]: *** [install_packages] Error 1

Makefile:51: recipe for target 'install' failed

make: *** [install] Error 2
So I seem to be stuck.  Any ideas?  I feel embarrassed not to be able to 
install GHC .
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


ghcup failed

2021-06-02 Thread Simon Peyton Jones via ghc-devs
Dear devs
I wanted to install GHC 8.10 on my WSL2 (Windows Subsystem for Linux) computer. 
 So I went here
https://www.haskell.org/ghcup/
and followed the instructions (the curl … command).  There was a long pause then

[ Info  ] verifying digest of: ghc-8.10.4-x86_64-deb9-linux.tar.xz

[ Info  ] Unpacking: ghc-8.10.4-x86_64-deb9-linux.tar.xz to /tmp/ghcup-khiegA

[ Info  ] Installing GHC (this may take a while)

[ Error ] BuildFailed failed in dir "/tmp/ghcup-khiegA": NonZeroExit 2 "make" 
["install"]

Check the logs at "/home/simonpj/.ghcup/logs" and the build directory 
"/tmp/ghcup-khiegA" for more clues.

Make sure to clean up "/tmp/ghcup-khiegA" afterwards.

"_eghcup --cache install ghc recommended" failed!
I looked in the logs as suggested, and found this in the tail of ghc-make.log

Installing library in 
/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/libiserv-8.10.4

"utils/ghc-cabal/dist-install/build/tmp/ghc-cabal-bindist" copy compiler stage2 
"strip" '' '/home/simonpj/.ghcup/ghc/8.10.4' 
'/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4' 
'/home/simonpj/.ghcup/ghc/8.10.4/share/doc/ghc-8.10.4/html/libraries' 'v p dyn'

Installing library in /home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/ghc-8.10.4

"/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/bin/ghc-pkg" --force 
--global-package-db 
"/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/package.conf.d" update 
rts/dist/package.conf.install

ghc-pkg: Couldn't open database 
/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/package.conf.d for modification: 
{handle: 
/home/simonpj/.ghcup/ghc/8.10.4/lib/ghc-8.10.4/package.conf.d/package.cache.lock}:
 hLock: invalid argument (Invalid argument)

ghc.mk:967: recipe for target 'install_packages' failed

make[1]: *** [install_packages] Error 1

Makefile:51: recipe for target 'install' failed

make: *** [install] Error 2
So I seem to be stuck.  Any ideas?  I feel embarrassed not to be able to 
install GHC .
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: value of documenting error messages?

2021-06-02 Thread Simon Peyton Jones via ghc-devs
|  e.g. "conflicting_trait_implementations" seems better than "E0119"

I don't think so.  If the compiler prints "E0119" and I search for that, I know 
I'm going to get exactly that, not similar but subtly different things. (A free 
text search might also throw up illuminating info, but is much less precise.)

Simon

|  -Original Message-
|  From: ghc-devs  On Behalf Of Tom Ellis
|  Sent: 02 June 2021 11:46
|  To: ghc-devs@haskell.org
|  Subject: Re: value of documenting error messages?
|  
|  On Tue, Jun 01, 2021 at 03:40:57PM -0700, Alec Theriault wrote:
|  > Rust has taken an interesting approach for this: every error message
|  > is given a unique number like "E0119"
|  
|  Is there a particularly strong reason to use numbers as codes when we have
|  the entire space human-readable strings available to us?  Even the subset of
|  case-insensitive strings formed from alphanumeric characters plus underscore
|  seems more suitable for the encoding than positive integers.
|  
|  e.g. "conflicting_trait_implementations" seems better than "E0119"
|  
|  Tom
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskel
|  l.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C746c7987d166423f0cf808d925
|  b3da91%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637582277123771646%7CUnk
|  nown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXV
|  CI6Mn0%3D%7C2000sdata=ymgTrD0iPgl7%2Bf%2FOLwOP6r%2BJGfkiR2ej0QQl0oig2Pk
|  %3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: value of documenting error messages?

2021-06-02 Thread Simon Peyton Jones via ghc-devs
Rust has taken an interesting approach for this: every error message is given a 
unique number like "E0119" and there is an error 
index
 generated from simple markdown 
files
 containing explanations and examples for the errors (error codes by themselves 
already massively help searchability). If GHC were to take this approach, I 
think it would be fine to just include the error message identifier in the 
Haddocks.

I think this is a great idea, including that of giving unique numbers.

We should be aware that there are two client groups:

  1.  Users, for whom the error index above is ideal
  2.  Clients of the GHC API (e.g. authors of an IDE) who are consuming the 
data type itself, and need to know what the various fields mean.

For (A) the Rust approach seems terrific.

For (B) adding Haddocks as in the example Richard gave seems better.  But it 
should not repeat (A); rather it should assume you are also looking at (A) for 
that error number, and add any implementation specific info, like what the 
fields mean, and what the test cases are.

Simon

From: ghc-devs  On Behalf Of Alec Theriault
Sent: 01 June 2021 23:41
To: Richard Eisenberg 
Cc: GHC developers 
Subject: Re: value of documenting error messages?

Hello,

If these are the messages that get pretty-printed into errors or warnings, I 
would think detailed documentation is definitely useful. However, since this is 
documentation that users of GHC will want to read (and not just contributors), 
I think it should live primarily in the user's guide and not the Haddocks.

Rust has taken an interesting approach for this: every error message is given a 
unique number like "E0119" and there is an error 
index
 generated from simple markdown 
files
 containing explanations and examples for the errors (error codes by themselves 
already massively help searchability). If GHC were to take this approach, I 
think it would be fine to just include the error message identifier in the 
Haddocks.

Alec

PS: Rust even bundles the documentation for errors into the compiler, so you 
can do something like `rustc --explain E0119` to get the full description of 
the error. It'd be pretty neat if GHC could do this too. Some errors don't have 
much to say about them, but others definitely could be explained!

On Tue, Jun 1, 2021 at 2:36 PM Richard Eisenberg 
mailto:r...@richarde.dev>> wrote:
Hi devs,

Take a quick look at 
https://gitlab.haskell.org/ghc/ghc/-/blob/6db8a0f76ec45d47060e28bb303e9eef60bdb16b/compiler/GHC/Driver/Errors/Types.hs#L107
  You will see a datatype there with constructors describing error messages 
that GHC might produce. These constructors have comments describing the error, 
sometimes giving an example, and sometimes listing test cases. More datatypes 
like this one and more constructors in these datatypes are on 

Errors in haddock git fetch

2021-05-27 Thread Simon Peyton Jones via ghc-devs
I'm getting these errors from `git submodule update`.  Should I worry?
Simon


>From https://gitlab.haskell.org/ghc/haddock

* [new branch]az/T19834 
   -> origin/az/T19834

* [new branch]az/T19834-2   
   -> origin/az/T19834-2

* [new branch]az/T19845 
   -> origin/az/T19845

* [new branch]az/T19845-2   
   -> origin/az/T19845-2

* [new branch]az/T19845-3   
   -> origin/az/T19845-3

* [new branch]
dependabot/npm_and_yarn/haddock-api/resources/html/hosted-git-info-2.8.9 -> 
origin/dependabot/npm_and_yarn/haddock-api/resources/html/hosted-git-info-2.8.9

* [new branch]
dependabot/npm_and_yarn/haddock-api/resources/html/lodash-4.17.21-> 
origin/dependabot/npm_and_yarn/haddock-api/resources/html/lodash-4.17.21

* [new branch]dn/dn-driver-refactor-and-split   
   -> origin/dn/dn-driver-refactor-and-split

   b4e7407b..c7281407  ghc-9.2  
-> origin/ghc-9.2

   dabdee14..4f9088e4  ghc-head 
-> origin/ghc-head

* [new branch]wip/T18389-task-zero  
   -> origin/wip/T18389-task-zero

+ 7d27ea7a...3b6a8774 wip/T19720
   -> origin/wip/T19720  (forced update)

+ fe35fed3...40ba457f wip/adinapoli-align-ps-messages   
   -> origin/wip/adinapoli-align-ps-messages  (forced update)

* [new branch]wip/dn-driver-refactor-and-split  
   -> origin/wip/dn-driver-refactor-and-split

error: cannot lock ref 'refs/remotes/origin/wip/hsyl20/dynflags': 
'refs/remotes/origin/wip/hsyl20/dynflags/exception' exists; cannot create 
'refs/remotes/origin/wip/hsyl20/dynflags'

! [new branch]wip/hsyl20/dynflags   
   -> origin/wip/hsyl20/dynflags  (unable to update local ref)

* [new branch]wip/hsyl20/uncpp  
   -> origin/wip/hsyl20/uncpp

Unable to fetch in submodule path 'utils/haddock'; trying to directly fetch 
4f9088e4b04e52ca510b55a78048c9230537e449:

Submodule path 'utils/haddock': checked out 
'4f9088e4b04e52ca510b55a78048c9230537e449'

simonpj@MSRC-3645512:~/code/HEAD-7$
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Coding style: Using StandaloneKindSignatures in GHC

2021-05-21 Thread Simon Peyton Jones via ghc-devs
I’m good with those rules.

Simon

From: ghc-devs  On Behalf Of Richard Eisenberg
Sent: 21 May 2021 21:21
To: Chris Smith 
Cc: GHC developers 
Subject: Re: Coding style: Using StandaloneKindSignatures in GHC

I agree with Chris here.

Let me expand upon my counter-proposal:

* A datatype declaration gets a standalone kind signature whenever at least one 
of its type arguments has a kind other than Type.
* A class declaration gets a standalone kind signature whenever at least one of 
its type arguments has a kind other than Type.(*)
* A closed type family always gets a standalone kind signature.
* A type synonym gets a standalone kind signature whenever either at least one 
of its arguments has a kind other than Type or its result has a kind other than 
Type.

(*) The class rule has an exception: if a class has a superclass constraint 
using Monad, Functor, Applicative, Foldable, or Traversable (or some other 
class whose name textually includes one of those names, such as MonadIO), we 
understand that the constrained variable must have kind Type -> Type. If that 
type variable is the only one without kind Type -> Type, then the standalone 
kind signature is optional.

In cases other than those covered above, the standalone kind signature is 
optional, at the discretion of the programmer.

This suggests that Dict gets a signature, Eq does not, Fix does, and Either 
does not.

Richard

On May 21, 2021, at 12:37 PM, Chris Smith 
mailto:cdsm...@gmail.com>> wrote:

On Fri, May 21, 2021 at 2:11 AM Baldur Blöndal 
mailto:baldur...@gmail.com>> wrote:
> encouraging the use of a standalone signature for type declarations where at 
> least one parameter of the datatype does not have kind Type.

So Dict, Eq both get a sig but Fix and Either do not?

  type Dict :: Constraint -> Type
  type Eq   :: Type -> Constraint
  type Fix  :: (Type -> Type) -> Type

 That's not how I understand Richard's criteria.  Dict and Fix have non-Type 
parameters (Dict has a Constraint parameter, and Fix has a (Type -> Type) 
parameter.  On the other hand, Eq and Either have only Types as parameters.  
This seems to match my intuition about when a kind signature might be helpful, 
as well as yours as far as I can tell from what you wrote.

That's not to say I am advocating any kind of rule.  As I'm not really involved 
in GHC development, I refrain from having any opinion.  I just think you may 
have misread Richard's suggestion.

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


RE: Coding style: Using StandaloneKindSignatures in GHC

2021-05-18 Thread Simon Peyton Jones via ghc-devs
I'm all for "encourage" but not keen on "require".

Simon

| -Original Message-
| From: ghc-devs  On Behalf Of Hécate
| Sent: 18 May 2021 19:18
| To: ghc-devs@haskell.org
| Subject: Re: Coding style: Using StandaloneKindSignatures in GHC
| 
| After reading this proposal, I agree that StandaloneKindSignatures ought
| to be encouraged in the codebases, and I vote that we mention them in the
| coding style¹.
| 
| Cheers,
| Hécate
| 
| ———
| ¹
| https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.
| haskell.org%2Fghc%2Fghc%2F-%2Fwikis%2Fcommentary%2Fcoding-
| styledata=04%7C01%7Csimonpj%40microsoft.com%7C526d76f0fe6f4bfad5b208
| d91a297bd3%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63756958777303339
| 3%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1
| haWwiLCJXVCI6Mn0%3D%7C3000sdata=xUV24DTEWYImjevJtWxK1hAB6QI0gX9dqvXm
| 81jLOPo%3Dreserved=0
| 
| Cheers,
| Hécate.
| 
| Le 18/05/2021 à 19:58, Baldur Blöndal a écrit :
| > Discussion to permit use of StandaloneKindSignatures in the GHC coding
| > style guide. I believe it increases the clarity of the code,
| > especially as we move to fancier kinds.
| >
| > It is the only way we have for giving full signatures to type
| > synonyms, type classes, type families and others. An example:
| >
| >  type Cat :: Type -> Type
| >  type Cat ob = ob -> ob -> Type
| >
| >  type  Category :: forall ob. Cat ob -> Constraint
| >  class Category cat where
| >id :: cat a a ..
| >
| >  type Proxy :: forall k. k -> Type
| >  data Proxy a = Proxy
| >
| >  type Some :: forall k. (k -> Type) -> Type
| >  data Some f where
| >Some :: f ex -> Some f
| >
| >  -- | The regular function type
| >  type (->) :: forall {rep1 :: RuntimeRep} {rep2 :: RuntimeRep}.
| > TYPE1 rep1 -> TYPE rep2 -> Type
| >  type (->) = FUN 'Many
| >
| > This is in line with function definitions that are always given a
| > top-level, standalone type signature (1) and not like we currently
| > define type families/synonyms (2) by annotating each argument or not
| > at all. Using -XStandaloneKindSignatures (3) matches (1)
| >
| >  -- (1)
| >  curry :: ((a, b) -> c) -> (a -> b -> c)
| >  curry f  x y = f (x, y)
| >
| >  -- (2)
| >  type Curry (f :: (a, b) -> c) (x :: a) (y :: b) =  f '(x, y) :: c
| >
| >  -- (3)
| >  type Curry :: ((a, b) -> c) -> (a -> b -> c)
| >  type Curry f x y = f '(x, y)
| >
| > It covers an edgecase that `KindSignatures` don't. The only way for
| > deriving to reference datatype arguments is if they are quantified by
| > the declaration head -- `newtype Bin a ..`. StandaloneKindSignatures
| > allows us to still provide a full signature. We could write `newtype
| > Bin a :: Type -> Type` without it but not `newtype Bin :: Type -> Type
| > -> Type`
| >
| >  typeBin :: Type -> Type -> Type
| >  newtype Bin a b = Bin (a -> a -> b)
| >deriving (Functor, Applicative)
| >via (->) a `Compose` (->) a
| >
| > Let me know what you think
| > ___
| > ghc-devs mailing list
| > ghc-devs@haskell.org
| > https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
| > haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devsdata=04%7C01
| > %7Csimonpj%40microsoft.com%7C526d76f0fe6f4bfad5b208d91a297bd3%7C72f988
| > bf86f141af91ab2d7cd011db47%7C1%7C0%7C637569587773033393%7CUnknown%7CTW
| > FpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6
| > Mn0%3D%7C3000sdata=Dc5Xbl2YJ%2BWmstt2z289UAzX9s%2BWJ5RuH84V2AbxJY
| > c%3Dreserved=0
| 
| --
| Hécate ✨
| : @TechnoEmpress
| IRC: Uniaika
| WWW:
| https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fglitchb
| ra.in%2Fdata=04%7C01%7Csimonpj%40microsoft.com%7C526d76f0fe6f4bfad5b
| 208d91a297bd3%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63756958777304
| 3386%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6
| Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=KqNL0D9zC%2FiOORPEUqChk%2FTUxkekq
| vxyZuyokFjcxMI%3Dreserved=0
| RUN: BSD
| 
| ___
| ghc-devs mailing list
| ghc-devs@haskell.org
| https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.has
| kell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
| devsdata=04%7C01%7Csimonpj%40microsoft.com%7C526d76f0fe6f4bfad5b208d
| 91a297bd3%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637569587773043386
| %7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1h
| aWwiLCJXVCI6Mn0%3D%7C3000sdata=yuGMW58YP7Grt4TrjtL5dahu0vSOP%2BYmV9I
| zxLvrRxI%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: ZuriHac 2021 - GHC Track - Call for Contributions

2021-05-10 Thread Simon Peyton Jones via ghc-devs
Andreas, Niklas

Would an "ask me anything" slot be useful?  We could get a handful of GHC devs 
(eg me) together and invite participants to ask about GHC specifics.  Not so 
much personal "how long have you worked on GHC?" but more technical "how does 
class instance lookup work?".

I'd be willing.  But it could fall a bit flat if no one asks anything... maybe 
prime the pump with one or two questions...

Simon

From: ghc-devs  On Behalf Of Andreas Herrmann
Sent: 10 May 2021 09:02
To: GHC developers 
Cc: Niklas Hambüchen 
Subject: ZuriHac 2021 - GHC Track - Call for Contributions

Dear GHC developers,

This year's ZuriHac 2021 [1], online Friday 18th June to Sunday 20th June, will
again feature a dedicated GHC track to foster contributions to GHC and teach
newcomers how to participate in GHC's development.

For that we need your help: We would like to invite you to organize a session
in the GHC track. This could be in form of a presentation, a workshop, or a
hack session with topics centered around GHC.

For some inspiration, these are the subjects from last year's track:
- Write a GHC extension in 30 minutes, by Richard Eisenberg
- A tour of linear types and linear base, by Divesh Otwani
- QualifiedDo: customizable 'do' syntax without fuss, by Facundo Dominguez
- On "simple" constraints for typechecker plugins, by Nicolas Frisby

Please let us know if you'd be interested in leading a session or a workshop.
You can contact either Niklas or myself, on this list or by private message.

Best,
Andreas and Niklas
ZuriHac 2021 GHC track coordinators

[1]: 
https://zfoh.ch/zurihac2021/
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Warnings

2021-05-04 Thread Simon Peyton Jones via ghc-devs
If 'transformers' purposely has orphan instances, shouldn't we switch off the 
warnings about them?
Simon


"/opt/ghc/bin/ghc" -hisuf hi -osuf  o -hcsuf hc -static  -O -H64m -Wall   
-package-db libraries/bootstrapping.conf  -this-unit-id transformers-0.5.6.2 
-hide-all-packages -package-env - -i -ilibraries/transformers/. 
-ilibraries/transformers/dist-boot/build 
-Ilibraries/transformers/dist-boot/build 
-ilibraries/transformers/dist-boot/build/./autogen 
-Ilibraries/transformers/dist-boot/build/./autogen -Ilibraries/transformers/.   
 -optP-include 
-optPlibraries/transformers/dist-boot/build/./autogen/cabal_macros.h 
-package-id base-4.14.1.0 -XHaskell98   -no-user-package-db -rtsopts  
-fno-warn-unused-matches -fno-warn-unused-imports -fno-warn-deprecated-flags
  -outputdir libraries/transformers/dist-boot/build   -c 
libraries/transformers/./Control/Applicative/Lift.hs -o 
libraries/transformers/dist-boot/build/Control/Applicative/Lift.o



libraries/transformers/Control/Monad/Trans/Error.hs:98:1: warning: [-Worphans]

Orphan instance: instance [safe] Error e => Alternative (Either e)

To avoid this

move the instance declaration to the module of the class or of the 
type, or

wrap the type with a newtype and declare the instance on the new type.

   |

98 | instance (Error e) => Alternative (Either e) where

   | ^^...



libraries/transformers/Control/Monad/Trans/Error.hs:103:1: warning: [-Worphans]

Orphan instance: instance [safe] Error e => MonadPlus (Either e)

To avoid this

move the instance declaration to the module of the class or of the 
type, or

wrap the type with a newtype and declare the instance on the new type.

|

103 | instance (Error e) => MonadPlus (Either e) where

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


Compiling libraries

2021-04-29 Thread Simon Peyton Jones via ghc-devs
Ben and other friends
What is the approved way to build libraries with (and for) a compiler that I've 
just built?
I tried this:

bash$ cabal v2-install 
--with-ghc=/home/simonpj/code/ghc-9.2-branch/inplace/bin/ghc-stage2 streamly 
--allow-newer
but it failed with

Data/Primitive/Types.hs:273:844: error:

* Couldn't match expected type 'Word#' with actual type 'Word8#'

* In the fourth argument of 'shimmedSetWord8Array#', namely 'x#'
(This was for a compiler built from the ghc-9.2 branch.)
I'd like to be able to do the same for HEAD.
I need to do this to help with the numerous tickets asking about library 
regressions.  For example, I want to be able repoduce @harendra's 
example, but I 
can't because I can't build streamly.
Thanks!
Simon

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


RE: magicDict

2021-04-26 Thread Simon Peyton Jones via ghc-devs
You mean you like 'withDict' with that name,  as well as the argument order K 
suggests?   i.e. not reifyDict?

Simon

From: Edward Kmett 
Sent: 26 April 2021 21:34
To: Simon Peyton Jones 
Cc: Krzysztof Gogolewski ; Spiwack, Arnaud 
; GHC developers ; Ryan Scott 

Subject: Re: magicDict

I like withDict a lot. It is direct, easy to chain/use, avoids fighting about 
direction completely, and even matches the argument order used by reify in the 
reflection library.

+1 from me.

On Mon, Apr 26, 2021 at 7:49 AM Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:
|  I would like to propose one more option:
|
|  withDict :: dt -> (ct => a) -> a

Ah, you mean simply: swap the argument order.   I can see your logic about 
chaining etc.  I'd be fine with this.

Simon

|  -Original Message-
|  From: Krzysztof Gogolewski 
mailto:krz.gogolew...@gmail.com>>
|  Sent: 26 April 2021 15:35
|  To: Simon Peyton Jones mailto:simo...@microsoft.com>>
|  Cc: Spiwack, Arnaud 
mailto:arnaud.spiw...@tweag.io>>; Edward Kmett
|  mailto:ekm...@gmail.com>>; GHC developers 
mailto:ghc-devs@haskell.org>>
|  Subject: Re: magicDict
|
|  I would like to propose one more option:
|
|  withDict :: dt -> (ct => a) -> a
|
|  1. This is less symmetric than '(ct => a) -> dt -> a'
| but in existing applications magicDict gets the arguments
| in the reverse order.
|  2. Easier to chain 'withDict d1 (withDict d2 ...)'.
|  3. The name is similar to 'withTypeable' or 'withFile',
| and avoids arguing which is reify or reflect.
|
|  On Mon, Apr 26, 2021 at 9:41 AM Simon Peyton Jones via ghc-devs mailto:d...@haskell.org>> wrote:
|  >
|  > Can we just agree a name, then?   Please correct me if I'm wrong,
|  but
|  >
|  > I think Ed prefers 'reifyDict',
|  > That is compatible with the existing reflection library Arnaud
|  > disagrees but isn't going to die in the trenches for this one
|  > Virtually anything is better than 'magicDict'.
|  >
|  >
|  >
|  >
|  >
|  > So: reifyDict it is?
|  >
|  >
|  >
|  > Simon
|  >
|  >
|  >
|  > From: Spiwack, Arnaud 
mailto:arnaud.spiw...@tweag.io>>
|  > Sent: 26 April 2021 08:10
|  > To: Edward Kmett mailto:ekm...@gmail.com>>
|  > Cc: Simon Peyton Jones 
mailto:simo...@microsoft.com>>; GHC developers
|  > mailto:ghc-devs@haskell.org>>
|  > Subject: Re: magicDict
|  >
|  >
|  >
|  >
|  >
|  >
|  >
|  > On Sun, Apr 25, 2021 at 2:20 AM Edward Kmett 
mailto:ekm...@gmail.com>>
|  wrote:
|  >
|  > I speak to much this same point in this old stack overflow response,
|  though to exactly the opposite conclusion, and to exactly the opposite
|  pet peeve.
|  >
|  >
|  >
|  >
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fstac
|  >
|  
koverflow.com<https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fkoverflow.com%2F=04%7C01%7Csimonpj%40microsoft.com%7Cbc489a190b534d771e8e08d908f2a2d4%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637550660487039029%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=p1oBeQtmxDH%2BRx%2FDNmIGeshz8PA0BEdiAcOk1faB0xc%3D=0>%2Fa%2F5316014%2F34707data=04%7C01%7Csimonpj%40micro
|  >
|  
soft.com<https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fsoft.com%2F=04%7C01%7Csimonpj%40microsoft.com%7Cbc489a190b534d771e8e08d908f2a2d4%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637550660487049021%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=N6k7M4FOB19jwAJVlx0y5WOxLwv7VUf58iihdwz2mhQ%3D=0>%7C87da21fdcc8e4ed6bef508d908c071fb%7C72f988bf86f141af91ab2d7c
|  >
|  d011db47%7C1%7C0%7C637550444930791696%7CUnknown%7CTWFpbGZsb3d8eyJWIjoi
|  >
|  MC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000
|  >
|  sdata=VlRrIEROGj%2BE6%2FuLXBEdfa%2BPWVlHh50dahgjIrw4tQU%3Dreserve
|  > d=0
|  >
|  >
|  >
|  > :-)
|  >
|  >
|  >
|  > I do not feel that I chose the vocabulary without due consideration
|  of the precise meaning of the words used.
|  >
|  >
|  >
|  > I didn't mean to imply that you did. Sorry if I did so: written
|  communication is hard. For what it's worth, I didn't really think that
|  I would change your mind, either.
|  >
|  >
|  >
|  > Though it still seems to me that the name `ReifiedMonoid` uses the
|  word for a different thing than the `reifyMonoid` function does.
|  >
|  >
|  >
|  > To be explicit:
|  >
|  >
|  >
|  > Viewing a type as a space, 'reify' in the reflection library takes
|  some space 'a' and splits it into individual fibers for each term in
|  'a', finding the appropriate one and handing it back to you as a fresh
|  type 's' that captures just that singular value. The result is
|  significantly 

RE: magicDict

2021-04-26 Thread Simon Peyton Jones via ghc-devs
|  I would like to propose one more option:
|  
|  withDict :: dt -> (ct => a) -> a

Ah, you mean simply: swap the argument order.   I can see your logic about 
chaining etc.  I'd be fine with this.

Simon

|  -Original Message-
|  From: Krzysztof Gogolewski 
|  Sent: 26 April 2021 15:35
|  To: Simon Peyton Jones 
|  Cc: Spiwack, Arnaud ; Edward Kmett
|  ; GHC developers 
|  Subject: Re: magicDict
|  
|  I would like to propose one more option:
|  
|  withDict :: dt -> (ct => a) -> a
|  
|  1. This is less symmetric than '(ct => a) -> dt -> a'
| but in existing applications magicDict gets the arguments
| in the reverse order.
|  2. Easier to chain 'withDict d1 (withDict d2 ...)'.
|  3. The name is similar to 'withTypeable' or 'withFile',
| and avoids arguing which is reify or reflect.
|  
|  On Mon, Apr 26, 2021 at 9:41 AM Simon Peyton Jones via ghc-devs  wrote:
|  >
|  > Can we just agree a name, then?   Please correct me if I'm wrong,
|  but
|  >
|  > I think Ed prefers 'reifyDict',
|  > That is compatible with the existing reflection library Arnaud
|  > disagrees but isn't going to die in the trenches for this one
|  > Virtually anything is better than 'magicDict'.
|  >
|  >
|  >
|  >
|  >
|  > So: reifyDict it is?
|  >
|  >
|  >
|  > Simon
|  >
|  >
|  >
|  > From: Spiwack, Arnaud 
|  > Sent: 26 April 2021 08:10
|  > To: Edward Kmett 
|  > Cc: Simon Peyton Jones ; GHC developers
|  > 
|  > Subject: Re: magicDict
|  >
|  >
|  >
|  >
|  >
|  >
|  >
|  > On Sun, Apr 25, 2021 at 2:20 AM Edward Kmett 
|  wrote:
|  >
|  > I speak to much this same point in this old stack overflow response,
|  though to exactly the opposite conclusion, and to exactly the opposite
|  pet peeve.
|  >
|  >
|  >
|  >
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fstac
|  >
|  koverflow.com%2Fa%2F5316014%2F34707data=04%7C01%7Csimonpj%40micro
|  >
|  soft.com%7C87da21fdcc8e4ed6bef508d908c071fb%7C72f988bf86f141af91ab2d7c
|  >
|  d011db47%7C1%7C0%7C637550444930791696%7CUnknown%7CTWFpbGZsb3d8eyJWIjoi
|  >
|  MC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000
|  >
|  sdata=VlRrIEROGj%2BE6%2FuLXBEdfa%2BPWVlHh50dahgjIrw4tQU%3Dreserve
|  > d=0
|  >
|  >
|  >
|  > :-)
|  >
|  >
|  >
|  > I do not feel that I chose the vocabulary without due consideration
|  of the precise meaning of the words used.
|  >
|  >
|  >
|  > I didn't mean to imply that you did. Sorry if I did so: written
|  communication is hard. For what it's worth, I didn't really think that
|  I would change your mind, either.
|  >
|  >
|  >
|  > Though it still seems to me that the name `ReifiedMonoid` uses the
|  word for a different thing than the `reifyMonoid` function does.
|  >
|  >
|  >
|  > To be explicit:
|  >
|  >
|  >
|  > Viewing a type as a space, 'reify' in the reflection library takes
|  some space 'a' and splits it into individual fibers for each term in
|  'a', finding the appropriate one and handing it back to you as a fresh
|  type 's' that captures just that singular value. The result is
|  significantly less abstract, as we gained detail on the type, now
|  every point in the original space 'a' is a new space. At the type
|  level the fresh 's' in s `Reifies` a now concretely names exactly one
|  inhabitant of 'a'.
|  >
|  >
|  >
|  > On the flip side, 'reflect' in the reflection library forgets this
|  finer fibration / structure on space, losing the information about
|  which fiber the answer came from, being forgetful is precisely the
|  justification of it being the 'reflect' half of the reify -| reflect
|  pairing.
|  >
|  >
|  >
|  > I confess I don't necessarily anticipate this changing your mind but
|  it was not chosen blindly, reflect is the forgetful mapping here,
|  reification is free and left adjoint to it, at least in the context of
|  reflection-the-library, where a quantifier is being injected to track
|  the particular member.
|  >
|  >
|  >
|  > I've got to admit that I have the hardest time seeing the `s` as
|  representing an inhabitant of `a`. I'm probably missing something
|  here.
|  >
|  >
|  >
|  > I also don't think that a free object construction embodies a
|  reify/reflect pair completely. It's probably fair to see `reify` as
|  being the natural mapping from the free object of X to X (the counit
|  of the adjunction). But reification will not be the unit of the
|  adjunction, because it's trivial. So there is still a piece missing in
|  this story.
|  >
|  >
|  >
|  > Anyway... I've made my point, and I am not too willing to spend too
|  much time proving Wadler's law correct. So I think I'll stop here,
|  fascinating a conversation though it is.
|  >
|  >
|  >
|  &g

RE: magicDict

2021-04-26 Thread Simon Peyton Jones via ghc-devs
Can we just agree a name, then?   Please correct me if I'm wrong, but

  *   I think Ed prefers 'reifyDict',
  *   That is compatible with the existing reflection library
  *   Arnaud disagrees but isn't going to die in the trenches for this one
  *   Virtually anything is better than 'magicDict'.


So: reifyDict it is?

Simon

From: Spiwack, Arnaud 
Sent: 26 April 2021 08:10
To: Edward Kmett 
Cc: Simon Peyton Jones ; GHC developers 

Subject: Re: magicDict



On Sun, Apr 25, 2021 at 2:20 AM Edward Kmett 
mailto:ekm...@gmail.com>> wrote:
I speak to much this same point in this old stack overflow response, though to 
exactly the opposite conclusion, and to exactly the opposite pet peeve.

https://stackoverflow.com/a/5316014/34707

:-)

I do not feel that I chose the vocabulary without due consideration of the 
precise meaning of the words used.

I didn't mean to imply that you did. Sorry if I did so: written communication 
is hard. For what it's worth, I didn't really think that I would change your 
mind, either.

Though it still seems to me that the name `ReifiedMonoid` uses the word for a 
different thing than the `reifyMonoid` function does.

To be explicit:

Viewing a type as a space, 'reify' in the reflection library takes some space 
'a' and splits it into individual fibers for each term in 'a', finding the 
appropriate one and handing it back to you as a fresh type 's' that captures 
just that singular value. The result is significantly less abstract, as we 
gained detail on the type, now every point in the original space 'a' is a new 
space. At the type level the fresh 's' in s `Reifies` a now concretely names 
exactly one inhabitant of 'a'.

On the flip side, 'reflect' in the reflection library forgets this finer 
fibration / structure on space, losing the information about which fiber the 
answer came from, being forgetful is precisely the justification of it being 
the 'reflect' half of the reify -| reflect pairing.

I confess I don't necessarily anticipate this changing your mind but it was not 
chosen blindly, reflect is the forgetful mapping here, reification is free and 
left adjoint to it, at least in the context of reflection-the-library, where a 
quantifier is being injected to track the particular member.

I've got to admit that I have the hardest time seeing the `s` as representing 
an inhabitant of `a`. I'm probably missing something here.

I also don't think that a free object construction embodies a reify/reflect 
pair completely. It's probably fair to see `reify` as being the natural mapping 
from the free object of X to X (the counit of the adjunction). But reification 
will not be the unit of the adjunction, because it's trivial. So there is still 
a piece missing in this story.

Anyway... I've made my point, and I am not too willing to spend too much time 
proving Wadler's law correct. So I think I'll stop here, fascinating a 
conversation though it is.

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


RE: magicDict

2021-04-22 Thread Simon Peyton Jones via ghc-devs
Ah, yes... I can never remember which is reify and which is reflect. I'm fine 
either way.  Maybe reifyDict is better.

S

|  -Original Message-
|  From: Krzysztof Gogolewski 
|  Sent: 22 April 2021 20:18
|  To: Spiwack, Arnaud 
|  Cc: Simon Peyton Jones ; GHC developers 
|  Subject: Re: magicDict
|  
|  How about 'reifyDict'? The reflection library uses 'reify' to create a
|  dictionary and 'reflect' to extract a value out of it.
|  
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fhack
|  age.haskell.org%2Fpackage%2Freflection-2.1.6%2Fdocs%2FData-
|  Reflection.html%23v%3Areifydata=04%7C01%7Csimonpj%40microsoft.com
|  %7C4c3a0fe8f1b2459d746308d905c34ed0%7C72f988bf86f141af91ab2d7cd011db47
|  %7C1%7C0%7C637547159883839881%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAw
|  MDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=bQ
|  RNfsZPQQ%2FxqVcJvVpRJSkBIEZojqmKyqhpv7gr9XU%3Dreserved=0
|  
|  On Thu, Apr 22, 2021 at 3:27 PM Spiwack, Arnaud
|   wrote:
|  >
|  > Let me upvote `reflectDict`.
|  >
|  > On Thu, Apr 22, 2021 at 12:41 PM Simon Peyton Jones via ghc-devs
|   wrote:
|  >>
|  >> Ed, and other ghc-devs
|  >>
|  >> We are busy tidying up magicDict, and making it much more type-
|  safe:
|  >> see
|  >>
|  >>
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgit
|  >> lab.haskell.org%2Fghc%2Fghc%2F-
|  %2Fissues%2F16646data=04%7C01%7Cs
|  >>
|  imonpj%40microsoft.com%7C4c3a0fe8f1b2459d746308d905c34ed0%7C72f988bf8
|  >>
|  6f141af91ab2d7cd011db47%7C1%7C0%7C637547159883839881%7CUnknown%7CTWFp
|  >>
|  bGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6M
|  >>
|  n0%3D%7C3000sdata=6OX7dPWC2sVUeMKNaqZVGwH%2FJ9mGSWQRUEWuvUWq8uE%
|  >> 3Dreserved=0
|  >>
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgit
|  >> lab.haskell.org%2Fghc%2Fghc%2F-
|  %2Fmerge_requests%2F5573data=04%7
|  >>
|  C01%7Csimonpj%40microsoft.com%7C4c3a0fe8f1b2459d746308d905c34ed0%7C72
|  >>
|  f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637547159883839881%7CUnknown
|  >>
|  %7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLC
|  >>
|  JXVCI6Mn0%3D%7C3000sdata=D2Q3wq74Y4RVnaAOjXQX6R9EuxuDplwmJ0zdk%2
|  >> BAhN64%3Dreserved=0
|  >>
|  >> As part of that change we're think of changing its currently-
|  rather-obscure name.  I rather favour "reflectDict".  Any other views?
|  >>
|  >> Simon
|  >>
|  >> ___
|  >> ghc-devs mailing list
|  >> ghc-devs@haskell.org
|  >>
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail
|  >> .haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C
|  >>
|  01%7Csimonpj%40microsoft.com%7C4c3a0fe8f1b2459d746308d905c34ed0%7C72f
|  >>
|  988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637547159883839881%7CUnknown%
|  >>
|  7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJ
|  >>
|  XVCI6Mn0%3D%7C3000sdata=%2BQHuwK50UdRQR0AQOuNGstDM%2BtDEv%2F75fs
|  >> Ia3mfqvIw%3Dreserved=0
|  >
|  > ___
|  > ghc-devs mailing list
|  > ghc-devs@haskell.org
|  >
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  > haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01
|  >
|  %7Csimonpj%40microsoft.com%7C4c3a0fe8f1b2459d746308d905c34ed0%7C72f988
|  >
|  bf86f141af91ab2d7cd011db47%7C1%7C0%7C637547159883839881%7CUnknown%7CTW
|  >
|  FpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6
|  >
|  Mn0%3D%7C3000sdata=%2BQHuwK50UdRQR0AQOuNGstDM%2BtDEv%2F75fsIa3mfq
|  > vIw%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


magicDict

2021-04-22 Thread Simon Peyton Jones via ghc-devs
Ed, and other ghc-devs
We are busy tidying up magicDict, and making it much more type-safe: see

  *   https://gitlab.haskell.org/ghc/ghc/-/issues/16646
  *   https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5573
As part of that change we're think of changing its currently-rather-obscure 
name.  I rather favour "reflectDict".  Any other views?
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: External STG Interpreter blog post

2021-04-12 Thread Simon Peyton Jones via ghc-devs
That's extremely impressive, Csaba.

Maybe of interest to folk who have been thinking about "fat interface files".

Simon

From: ghc-devs  On Behalf Of Csaba Hruska
Sent: 10 April 2021 11:49
To: GHC developers 
Subject: External STG Interpreter blog post

Hello,

I've written a blog post about GHC-WPC's external stg interpreter.
https://www.patreon.com/posts/external-stg-49857800
Feedback is welcome.

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


RE: Multiple versions of happy

2021-03-30 Thread Simon Peyton Jones via ghc-devs
That's (2), thanks.  How about (1)?

From: Sebastian Graf 
Sent: 30 March 2021 14:22
To: Simon Peyton Jones 
Cc: ghc-devs@haskell.org
Subject: Re: Multiple versions of happy

Hi Simon,

According to the configure script, you can use the HAPPY env variable. e.g.

$ HAPPY=/full/path/to/happy ./configure

Hope that helps. Cheers,
Sebastian

Am Di., 30. März 2021 um 15:19 Uhr schrieb Simon Peyton Jones via ghc-devs 
mailto:ghc-devs@haskell.org>>:
What's the approved mechanism to install multiple versions of happy/alex etc?  
Eg I tried to build ghc-9.0 and got this:

checking for makeinfo... no

checking for python3... /usr/bin/python3

checking for ghc-pkg matching /opt/ghc/bin/ghc... /opt/ghc/bin/ghc-pkg

checking for happy... /home/simonpj/.cabal/bin/happy

checking for version of happy... 1.20.0

configure: error: Happy version 1.19 is required to compile GHC.


I so I have to

  1.  Install happy-1.19 without overwriting the installed happy-1.20
  2.  Tell configure to use happy-1.19
What's the best way to do those two things?
Thanks
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs<https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs=04%7C01%7Csimonpj%40microsoft.com%7Cb7e07fe78b644f0181be08d8f37ec03c%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637527073028872686%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000=t3W8rl8mUbjPmEXYzcjzDYm1IiSjCDZNb7ATmz%2Fil28%3D=0>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Multiple versions of happy

2021-03-30 Thread Simon Peyton Jones via ghc-devs
What's the approved mechanism to install multiple versions of happy/alex etc?  
Eg I tried to build ghc-9.0 and got this:

checking for makeinfo... no

checking for python3... /usr/bin/python3

checking for ghc-pkg matching /opt/ghc/bin/ghc... /opt/ghc/bin/ghc-pkg

checking for happy... /home/simonpj/.cabal/bin/happy

checking for version of happy... 1.20.0

configure: error: Happy version 1.19 is required to compile GHC.


I so I have to

  1.  Install happy-1.19 without overwriting the installed happy-1.20
  2.  Tell configure to use happy-1.19
What's the best way to do those two things?
Thanks
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Why TcLclEnv and DsGblEnv need to store the same IORef for errors?

2021-03-30 Thread Simon Peyton Jones via ghc-devs
I think the main reason is that for Template Haskell the renamer/type-checker 
need to run the desugarer.  See the call to initDsTc in GHC.Tc.Gen.Splice.

I suppose an alternative is that the TcGblEnv could have a second IORef to use 
for error messages that come from desugaring during TH splices.

Nothing deeper than that I think.

Simon

From: ghc-devs  On Behalf Of Alfredo Di Napoli
Sent: 30 March 2021 08:42
To: Simon Peyton Jones via ghc-devs 
Subject: Why TcLclEnv and DsGblEnv need to store the same IORef for errors?

Hello folks,

as some of you might know me and Richard are reworking how GHC constructs, 
emits and deals with errors and warnings (See 
https://gitlab.haskell.org/ghc/ghc/-/wikis/Errors-as-(structured)-values<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fwikis%2FErrors-as-(structured)-values=04%7C01%7Csimonpj%40microsoft.com%7C49c033aa2865495eb07c08d8f34f70cd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637526870280012102%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=ui4JWOp1gl5Yh%2FOYDqcBLXxTm%2FGnQRi0cDshUVEjwmk%3D=0>
 and #18516).

To summarise very briefly the spirit, we will have (eventually) proper 
domain-specific types instead of SDocs. The idea is to have very precise and 
"focused" types for the different phases of the compilation pipeline, and a 
"catch-all" monomorphic `GhcMessage` type used for the final pretty-printing 
and exception-throwing:

data GhcMessage where
  GhcPsMessage  :: PsMessage -> GhcMessage
  GhcTcRnMessage:: TcRnMessage -> GhcMessage
  GhcDsMessage  :: DsMessage -> GhcMessage
  GhcDriverMessage  :: DriverMessage -> GhcMessage
  GhcUnknownMessage :: forall a. (Diagnostic a, Typeable a) => a -> GhcMessage

While starting to refactor GHC to use these types, I have stepped into 
something bizarre: the `DsGblEnv` and `TcLclEnv` envs both share the same 
`IORef` to store the diagnostics (i.e. warnings and errors) accumulated during 
compilation. More specifically, a function like 
`GHC.HsToCore.Monad.mkDsEnvsFromTcGbl` simply receives as input the `IORef` 
coming straight from the `TcLclEnv`, and stores it into the `DsGblEnv`.

This is unfortunate, because it would force me to change the type of this 
`IORef` to be
`IORef (Messages GhcMessage)` to accommodate both diagnostic types, but this 
would bubble up into top-level functions like `initTc`, which would now return 
a `Messages GhcMessage`. This is once again unfortunate, because is 
"premature": ideally it might still be nice to return `Messages TcRnMessage`, 
so that GHC API users could get a very precise diagnostic type rather than the 
bag `GhcMessage` is. It also violates an implicit contract: we are saying that 
`initTc` might return (potentially) *any* GHC diagnostic message (including, 
for example, driver errors/warnings), which I think is misleading.

Having said all of that, it's also possible that returning `Messages 
GhcMessage` is totally fine here and we don't need to be able to do this 
fine-grained distinction for the GHC API functions. Regardless, I would like to 
ask the audience:

* Why `TcLclEnv` and `DsGblEnv` need to share the same IORef?
* Is this for efficiency reasons?
* Is this because we need the two monads to independently accumulate errors 
into the
  same IORef?

Thanks!

Alfredo












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


RE: Type inference of singular matches on GADTs

2021-03-30 Thread Simon Peyton Jones via ghc-devs
I'm not saying this is a good idea for GHC or that it's implementable. But the 
idea of having type inference account for exhaustivity in this way does not 
seem, a priori, unspecified.

No, but I’m pointing out that specifying it might be tricky, involving some 
highly non-local reasoning.  I can’t yet see how to write a formal 
specification.   Note “yet”  -- growth mindset!

Simon

From: Richard Eisenberg 
Sent: 30 March 2021 04:58
To: Simon Peyton Jones 
Cc: Alexis King ; ghc-devs@haskell.org
Subject: Re: Type inference of singular matches on GADTs

As usual, I want to separate out the specification of a feature from the 
implementation. So let's just focus on specification for now -- with the caveat 
that there might be no possible implementation of these ideas.

The key innovation I see lurking here is the idea of an *exhaustive* function, 
where we know that any pattern-match on an argument is always exhaustive. I 
will write such a thing with @->, in both the type and in the arrow that 
appears after the lambda. The @-> type is a subtype of -> (and perhaps does not 
need to be written differently from ->).

EX1: \x @-> case x of HNil -> blah

This is easy: we can infer HList '[] @-> blah's type, because the pattern match 
is declared to be exhaustive, and no other type grants that property.

EX2: \x @-> (x, case x of HNit -> blah)

Same as EX1.

EX3: \x @-> case x of { HNil1 -> blah; HNil2 -> blah }

Same as EX1. There is still a unique type for which the patten-match is 
exhaustive.

EX4: Reject. There are multiple valid types, and we don't know which one to 
pick. This is like classic untouchable-variables territory.

EX5: This is hard. A declarative spec would probably choose HL2 [a] -> ... as 
you suggest, but there may be no implementation of such an idea.

EX6: Reject. No type leads to exhaustive matches.

I'm not saying this is a good idea for GHC or that it's implementable. But the 
idea of having type inference account for exhaustivity in this way does not 
seem, a priori, unspecified.

Richard




On Mar 29, 2021, at 5:00 AM, Simon Peyton Jones 
mailto:simo...@microsoft.com>> wrote:

I haven't thought about how to implement such a thing. At the least, it would 
probably require some annotation saying that we expect `\HNil -> ()` to be 
exhaustive (as GHC won't, in general, make that assumption). Even with that, 
could we get type inference to behave? Possibly.

As I wrote in another post on this thread, it’s a bit tricky.

What would you expect of (EX1)

   \x -> case x of HNil -> blah

Here the lambda and the case are separated

Now (EX2)

\x -> (x, case x of HNil -> blah)

Here the lambda and the case are separated more, and x is used twice.
What if there are more data constructors that share a common return type? (EX3)

data HL2 a where
HNil1 :: HL2 []
HNil2 :: HL2 []
HCons :: …blah…

\x -> case x of { HNil1 -> blah; HNil 2 -> blah  }

Here HNil1 and HNil2 both return HL2 [].   Is that “singular”?

What if one was a bit more general than the other?   Do we seek the least 
common generalisation of the alternatives given? (EX4)

data HL3 a where
HNil1 :: HL2 [Int]
HNil2 :: HL2 [a]
HCons :: …blah…

\x -> case x of { HNil1 -> blah; HNil 2 -> blah  }

What if the cases were incompatible?  (EX5)

data HL4 a where
HNil1 :: HL2 [Int]
HNil2 :: HL2 [Bool]
HCons :: …blah…

\x -> case x of { HNil1 -> blah; HNil 2 -> blah  }

Would you expect that to somehow generalise to `HL4 [a] -> blah`?

What if x matched multiple times, perhaps on different constructors (EX6)


\x -> (case s of HNil1 -> blah1;  case x of HNil2 -> blah)


The water gets deep quickly here.  I don’t (yet) see an obviously-satisfying 
design point that isn’t massively ad-hoc.

Simon


From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> On Behalf 
Of Richard Eisenberg
Sent: 29 March 2021 03:18
To: Alexis King mailto:lexi.lam...@gmail.com>>
Cc: ghc-devs@haskell.org
Subject: Re: Type inference of singular matches on GADTs





On Mar 26, 2021, at 8:41 PM, Alexis King 
mailto:lexi.lam...@gmail.com>> wrote:

If there’s a single principal type that makes my function well-typed and 
exhaustive, I’d really like GHC to pick it.

I think this is the key part of Alexis's plea: that the type checker take into 
account exhaustivity in choosing how to proceed.

Another way to think about this:

f1 :: HList '[] -> ()
f1 HNil = ()

f2 :: HList as -> ()
f2 HNil = ()

Both f1 and f2 are well typed definitions. In any usage site where both are 
well-typed, they will behave the same. Yet f1 is exhaustive while f2 is not. 
This isn't really about an open-world assumption or the possibility of extra 
cases -- it has to do with what the runtime behaviors of the two functions are. 
f1 never fails, while f2 must check a constructor tag and perhaps throw an 
exception.

If we just see \HNil -> (), Alexis seems to be suggesting we prefer the f1 
interpretation over the f2 interpretation. Why? Because f1 is exhaustive, and 

RE: Type inference of singular matches on GADTs

2021-03-29 Thread Simon Peyton Jones via ghc-devs
I haven't thought about how to implement such a thing. At the least, it would 
probably require some annotation saying that we expect `\HNil -> ()` to be 
exhaustive (as GHC won't, in general, make that assumption). Even with that, 
could we get type inference to behave? Possibly.

As I wrote in another post on this thread, it’s a bit tricky.

What would you expect of (EX1)

   \x -> case x of HNil -> blah

Here the lambda and the case are separated

Now (EX2)

\x -> (x, case x of HNil -> blah)

Here the lambda and the case are separated more, and x is used twice.
What if there are more data constructors that share a common return type? (EX3)


data HL2 a where

HNil1 :: HL2 []

HNil2 :: HL2 []

HCons :: …blah…

\x -> case x of { HNil1 -> blah; HNil 2 -> blah  }

Here HNil1 and HNil2 both return HL2 [].   Is that “singular”?

What if one was a bit more general than the other?   Do we seek the least 
common generalisation of the alternatives given? (EX4)

data HL3 a where

HNil1 :: HL2 [Int]

HNil2 :: HL2 [a]

HCons :: …blah…

\x -> case x of { HNil1 -> blah; HNil 2 -> blah  }

What if the cases were incompatible?  (EX5)

data HL4 a where

HNil1 :: HL2 [Int]

HNil2 :: HL2 [Bool]

HCons :: …blah…

\x -> case x of { HNil1 -> blah; HNil 2 -> blah  }

Would you expect that to somehow generalise to `HL4 [a] -> blah`?

What if x matched multiple times, perhaps on different constructors (EX6)

\x -> (case s of HNil1 -> blah1;  case x of HNil2 -> blah)


The water gets deep quickly here.  I don’t (yet) see an obviously-satisfying 
design point that isn’t massively ad-hoc.

Simon


From: ghc-devs  On Behalf Of Richard Eisenberg
Sent: 29 March 2021 03:18
To: Alexis King 
Cc: ghc-devs@haskell.org
Subject: Re: Type inference of singular matches on GADTs




On Mar 26, 2021, at 8:41 PM, Alexis King 
mailto:lexi.lam...@gmail.com>> wrote:

If there’s a single principal type that makes my function well-typed and 
exhaustive, I’d really like GHC to pick it.

I think this is the key part of Alexis's plea: that the type checker take into 
account exhaustivity in choosing how to proceed.

Another way to think about this:

f1 :: HList '[] -> ()
f1 HNil = ()

f2 :: HList as -> ()
f2 HNil = ()

Both f1 and f2 are well typed definitions. In any usage site where both are 
well-typed, they will behave the same. Yet f1 is exhaustive while f2 is not. 
This isn't really about an open-world assumption or the possibility of extra 
cases -- it has to do with what the runtime behaviors of the two functions are. 
f1 never fails, while f2 must check a constructor tag and perhaps throw an 
exception.

If we just see \HNil -> (), Alexis seems to be suggesting we prefer the f1 
interpretation over the f2 interpretation. Why? Because f1 is exhaustive, and 
when we can choose an exhaustive interpretation, that's probably a good idea to 
pursue.

I haven't thought about how to implement such a thing. At the least, it would 
probably require some annotation saying that we expect `\HNil -> ()` to be 
exhaustive (as GHC won't, in general, make that assumption). Even with that, 
could we get type inference to behave? Possibly.

But first: does this match your understanding?

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


config.sub

2021-03-26 Thread Simon Peyton Jones via ghc-devs
Folks
I'm getting a lot of this

simonpj@MSRC-3645512:~/code/HEAD-3$ git status

On branch wip/T19569

Your branch is up to date with 'origin/wip/T19569'.



Changes not staged for commit:

  (use "git add ..." to update what will be committed)

  (use "git restore ..." to discard changes in working directory)

  (commit or discard the untracked or modified content in submodules)

  modified:   libraries/unix (modified content)



Untracked files:

  (use "git add ..." to include in what will be committed)

  libraries/base/config.sub

  libraries/ghc-bignum/config.sub

What has changed in unix?  Answer:

simonpj@MSRC-3645512:~/code/HEAD-3$ cd libraries/unix

simonpj@MSRC-3645512:~/code/HEAD-3/libraries/unix$ git status

HEAD detached at 21437f2

Changes not staged for commit:

  (use "git add ..." to update what will be committed)

  (use "git restore ..." to discard changes in working directory)

  modified:   config.sub
Ugh.  Why is config.sub modified if it's a repo file?  And should I ignore the 
untracked base/config.sub and ghc-bignum?
What am I doing wrong?
Thanks
Simon

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


RE: Options for targeting Windows XP?

2021-03-26 Thread Simon Peyton Jones via ghc-devs
This link gives some (old) background
https://wiki.haskell.org/GHC/FAQ#Why_isn.27t_GHC_available_for_.NET_or_on_the_JVM.3F
Simon

From: ghc-devs  On Behalf Of Moritz Angermann
Sent: 26 March 2021 08:00
To: Clinton Mead 
Cc: ghc-devs 
Subject: Re: Options for targeting Windows XP?

I believe there is a bit of misconception about what requires a new backend or 
not. GHC is a bunch of different intermediate representations from which one 
can take off to build backends. The STG, or Cmm ones are the most popular. All 
our Native Code Generators and the LLVM code gen take off from the Cmm one. 
Whether or not that is the correct input representation for your target largely 
depends on the target and design of the codegenerator. GHCJS takes off from 
STG, and so does Csaba's GRIN work via the external STG I believe. IIRC 
Asterius takes off from Cmm. I don't remember the details about Eta.

Why fork? Do you want to deal with GHC, and GHC's development? If not, fork. Do 
you want to have to keep up with GHC's development? Maybe not fork. Do you 
think your compiler can stand on it's own and doesn't follow GHC much, except 
for being a haskell compiler? By all means fork.

Eta is a bit special here, Eta forked off, and basically started customising 
their Haskell compiler specifically to the JVM, and this also allowed them to 
make radical changes to GHC, which would not have been permissible in the 
mainline GHC. (Mainline GHC tries to support multiple platforms and 
architectures at all times, breaking any of them isn't really an option that 
can be taken lightheartedly.) Eta also started having Etlas, a custom Cabal, 
... I'd still like to see a lot from Eta and the ecosystem be re-integrated 
into GHC. There have to be good ideas there that can be brought back. It just 
needs someone to go look and do the work.

GHCJS is being aligned more with GHC right now precisely to eventually 
re-integrate it with GHC.

Asterius went down the same path, likely inspired by GHCJS, but I think I was 
able to convince the author that eventual upstreaming should be the goal and 
the project should try to stay as close as possible to GHC for that reason.

Now if you consider adding a codegen backend, this can be done, but again 
depends on your exact target. I'd love to see a CLR target, yet I don't know 
enough about CLR to give informed suggestions here.

If you have a toolchain that functions sufficiently similar to a stock c 
toolchain, (or you can make your toolchain look sufficiently similar to one, 
easily), most of it will just work. If you can separate your building into 
compilation of source to some form of object code, and some form of object code 
aggregates (archives), and some form of linking (objects and archives into 
shared objects, or executables), you can likely plug in your toolchain into GHC 
(and Cabal), and have it work, once you taught GHC how to produce your target 
languages object code.

If your toolchain does stuff differently, a bit more work is involved in 
teaching GHC (and Cabal) about that.

This all only gives you *haskell* though. You still need the Runtime System. If 
you have a C -> Target compiler, you can try to re-use GHC's RTS. This is what 
the WebGHC project did. They re-used GHC's RTS, and implemented a shim for 
linux syscalls, so that they can emulate enough to have the RTS think it's 
running on some musl like linux. You most likely want something proper here 
eventually; but this might be a first stab at it to get something working.

Next you'll have to deal with c-bits. Haskell Packages that link against C 
parts. This is going to be challenging, not impossible but challenging as much 
of the haskell ecosystem expects the ability to compile C files and use those 
for low level system interaction.

You can use hackage overlays to build a set of patched packages, once you have 
your codegen working. At that point you could start patching ecosystem packages 
to work on your target, until your changes are upstreamed, and provide your 
user with a hackage overlay (essentially hackage + patches for specific 
packages).

Hope this helps.

You'll find most of us on 
irc.freenode.net#ghc

On Fri, Mar 26, 2021 at 1:29 PM Clinton Mead 
mailto:clintonm...@gmail.com>> wrote:
Thanks again for the detailed reply Ben.

I guess the other dream of mine is to give GHC a .NET backend. For my problem 
it would be the ideal solution, but it looks like other attempts in this regard 
(e.g. Eta, GHCJS etc) seem to have difficulty keeping up with updates to GHC. 
So I'm sure it's not trivial.

It would be quite lovely though if I could 

RE: Type inference of singular matches on GADTs

2021-03-22 Thread Simon Peyton Jones via ghc-devs
What would you expect of


  1.  \x -> case x of HNil -> blah

Here the lambda and the case are separated.


  1.  \x -> (x, case x of HNil -> blah)

Here the lambda and the case are separated more, and x is used twice.

What if there are more data constructors that share a common return type?



  1.  data HL2 a where

HNil1 :: HL2 []

HNil2 :: HL2 []

HCons :: …blah…

\x -> case x of { HNil1 -> blah; HNil 2 -> blah  }

Here HNil1 and HNil2 both return HL2 [].   Is that “singular”?   What if one 
was a bit more general than the other?   Do we seek the least common 
generalisation of the alternatives given?

The water gets deep quickly here.  I don’t (yet) see an obviously-satisfying 
design point that isn’t massively ad-hoc.

Simon

From: ghc-devs  On Behalf Of Alexis King
Sent: 20 March 2021 09:41
To: ghc-devs@haskell.org
Subject: Type inference of singular matches on GADTs


Hi all,

Today I was writing some code that uses a GADT to represent heterogeneous lists:

data HList as where

  HNil  :: HList '[]

  HCons :: a -> HList as -> HList (a ': as)

This type is used to provide a generic way to manipulate n-ary functions. 
Naturally, I have some functions that accept these n-ary functions as 
arguments, which have types like this:

foo :: Blah as => (HList as -> Widget) -> Whatsit

The idea is that Blah does some type-level induction on as and supplies the 
function with some appropriate values. Correspondingly, my use sites look 
something like this:

bar = foo (\HNil -> ...)

Much to my dismay, I quickly discovered that GHC finds these expressions quite 
unfashionable, and it invariably insults them:

• Ambiguous type variable ‘as0’ arising from a use of ‘foo’

  prevents the constraint ‘(Blah as0)’ from being solved.

The miscommunication is simple enough. I expected that when given an expression 
like

\HNil -> ...

GHC would see a single pattern of type HList '[] and consequently infer a type 
like

HList '[] -> ...

Alas, it was not to be. It seems GHC is reluctant to commit to the choice of 
'[] for as, lest perhaps I add another case to my function in the future. 
Indeed, if I were to do that, the choice of '[] would be premature, as as ~ '[] 
would only be available within one branch. However, I do not in fact have any 
such intention, which makes me quietly wish GHC would get over its anxiety and 
learn to be a bit more of a risk-taker.

I ended up taking a look at the OutsideIn(X) paper, hoping to find some 
commentary on this situation, but in spite of the nice examples toward the 
start about the trickiness of GADTs, I found no discussion of this specific 
scenario: a function with exactly one branch and an utterly unambiguous 
pattern. Most examples come at the problem from precisely the opposite 
direction, trying to tease out a principle type from a collection of branches. 
The case of a function (or perhaps more accurately, a case expression) with 
only a single branch does not seem to be given any special attention.

Of course, fewer special cases is always nice. I have great sympathy for 
generality. Still, I can’t help but feel a little unsatisfied here. 
Theoretically, there is no reason GHC cannot treat

\(a `HCons` b `HCons` c `HCons` HNil) -> ...

and

\a b c -> ...

almost identically, with a well-defined principle type and pleasant type 
inference properties, but there is no way for me to communicate this to the 
typechecker! So, my questions:

  1.  Have people considered this problem before? Is it discussed anywhere 
already?
  2.  Is my desire here reasonable, or is there some deep philosophical 
argument for why my program should be rejected?
  3.  If it is reasonable, are there any obvious situations where a change 
targeted at what I’m describing (vague as that is) would affect programs 
negatively, not positively?

I realize this gets rather at the heart of the typechecker, so I don’t intend 
to imply a change of this sort should be made frivolously. Indeed, I’m not even 
particularly attached to the idea that a change must be made! But I do want to 
understand the tradeoffs better, so any insight would be much appreciated.

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


GitLab is down: urgent

2021-03-19 Thread Simon Peyton Jones via ghc-devs
GHC's GitLab seems to be down.  Ben?
(I just get 502's)
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: On CI

2021-03-17 Thread Simon Peyton Jones via ghc-devs
We need to do something about this, and I'd advocate for just not making stats 
fail with marge.

Generally I agree.   One point you don’t mention is that our perf tests (which 
CI forces us to look at assiduously) are often pretty weird cases.  So there is 
at least a danger that these more exotic cases will stand in the way of (say) a 
perf improvement in the typical case.

But “not making stats fail” is a bit crude.   Instead how about

  *   Always accept stat improvements



  *   We already have per-benchmark windows.  If the stat falls outside the 
window, we fail.  You are effectively saying “widen all windows to infinity”.  
If something makes a stat 10 times worse, I think we *should* fail.  But 10% 
worse?  Maybe we should accept and look later as you suggest.   So I’d argue 
for widening the windows rather than disabling them completely.


  *   If we did that we’d need good instrumentation to spot steps and drift in 
perf, as you say.  An advantage is that since the perf instrumentation runs 
only on committed master patches, not on every CI, it can cost more.  In 
particular , it could run a bunch of “typical” tests, including nofib and 
compiling Cabal or other libraries.

The big danger is that by relieving patch authors from worrying about perf 
drift, it’ll end up in the lap of the GHC HQ team.  If it’s hard for the author 
of a single patch (with which she is intimately familiar) to work out why it’s 
making some test 2% worse, imagine how hard, and demotivating, it’d be for Ben 
to wonder why 50 patches (with which he is unfamiliar) are making some test 5% 
worse.

I’m not sure how to address this problem.   At least we should make it clear 
that patch authors are expected to engage *actively* in a conversation about 
why their patch is making something worse, even after it lands.

Simon

From: ghc-devs  On Behalf Of Moritz Angermann
Sent: 17 March 2021 03:00
To: ghc-devs 
Subject: On CI

Hi there!

Just a quick update on our CI situation. Ben, John, Davean and I have been
discussion on CI yesterday, and what we can do about it, as well as some
minor notes on why we are frustrated with it. This is an open invitation to 
anyone who in earnest wants to work on CI. Please come forward and help!
We'd be glad to have more people involved!

First the good news, over the last few weeks we've seen we *can* improve
CI performance quite substantially. And the goal is now to have MR go through
CI within at most 3hs.  There are some ideas on how to make this even faster,
especially on wide (high core count) machines; however that will take a bit more
time.

Now to the more thorny issue: Stat failures.  We do not want GHC to regress,
and I believe everyone is on board with that mission.  Yet we have just 
witnessed a train of marge trials all fail due to a -2% regression in a few 
tests. Thus we've been blocking getting stuff into master for at least another 
day. This is (in my opinion) not acceptable! We just had five days of nothing 
working because master was broken and subsequently all CI pipelines kept 
failing. We have thus effectively wasted a week. While we can mitigate the 
latter part by enforcing marge for all merges to master (and with faster 
pipeline turnaround times this might be more palatable than with 9-12h 
turnaround times -- when you need to get something done! ha!), but that won't 
help us with issues where marge can't find a set of buildable MRs, because she 
just keeps hitting a combination of MRs that somehow together increase or 
decrease metrics.

We have three knobs to adjust:
- Make GHC build faster / make the testsuite run faster.
  There is some rather interesting work going on about parallelizing (earlier)
  during builds. We've also seen that we've wasted enormous amounts of
  time during darwin builds in the kernel, because of a bug in the testdriver.
- Use faster hardware.
  We've seen that just this can cut windows build times from 220min to 80min.
- Reduce the amount of builds.
  We used to build two pipelines for each marge merge, and if either of both
  (see below) failed, marge's merge would fail as well. So not only did we build
  twice as much as we needed, we also increased our chances to hit bogous
  build failures by 2.

We need to do something about this, and I'd advocate for just not making stats 
fail with marge. Build errors of course, but stat failures, no. And then have a 
separate dashboard (and Ben has some old code lying around for this, which 
someone would need to pick up and polish, ...), that tracks GHC's Performance 
for each commit to master, with easy access from the dashboard to the offending 
commit. We will also need to consider the implications of synthetic micro 
benchmarks, as opposed to say building Cabal or other packages, that reflect 
more real-world experience of users using GHC.

I will try to provide a data driven report on GHC's CI on a bi-weekly or month 
(we will have to see what the costs for writing it up, and the 

RE: Build failure -- missing dependency? Help!

2021-03-15 Thread Simon Peyton Jones via ghc-devs
Thanks Sylvain
So we should add a similar fake import into 
libraries/base/GHC/Exception/Type.hs-boot. I will open a MR.
Thank you! Don't forget to comment it - especially because it is fake.
Make build system doesn't respect package dependencies, only module 
dependencies (afaik)
Does Hadrian suffer from this malady too?  Are the fake imports needed? Or can 
we sweep them away when we sweep away make?
Simon

From: ghc-devs  On Behalf Of Sylvain Henry
Sent: 15 March 2021 08:30
To: ghc-devs@haskell.org
Subject: Re: Build failure -- missing dependency? Help!


Hi Simon,

The issue is that:
1. Make build system doesn't respect package dependencies, only module 
dependencies (afaik)
2. The build system isn't aware that most modules implicitly depend on 
GHC.Num.Integer/Natural (to desugar Integer/Natural literals)

That's why we have several fake imports in `base` that look like:

> import GHC.Num.Integer () -- See Note [Depend on GHC.Num.Integer] in GHC.Base

Note [Depend on GHC.Num.Integer]


The Integer type is special because GHC.Iface.Tidy uses constructors in
GHC.Num.Integer to construct Integer literal values. Currently it reads the
interface file whether or not the current module *has* any Integer literals, so
it's important that GHC.Num.Integer is compiled before any other module.

(There's a hack in GHC to disable this for packages ghc-prim and ghc-bignum
which aren't allowed to contain any Integer literals.)

Likewise we implicitly need Integer when deriving things like Eq instances.

The danger is that if the build system doesn't know about the dependency
on Integer, it'll compile some base module before GHC.Num.Integer,
resulting in:
  Failed to load interface for 'GHC.Num.Integer'
There are files missing in the 'ghc-bignum' package,

Bottom line: we make GHC.Base depend on GHC.Num.Integer; and everything
else either depends on GHC.Base, or does not have NoImplicitPrelude
(and hence depends on Prelude).

Note: this is only a problem with the make-based build system. Hadrian doesn't
seem to interleave compilation of modules from separate packages and respects
the dependency between `base` and `ghc-bignum`.

So we should add a similar fake import into 
libraries/base/GHC/Exception/Type.hs-boot. I will open a MR.

Sylvain




On 14/03/2021 21:53, Simon Peyton Jones via ghc-devs wrote:
I'm getting this (with 'sh validate -legacy').  Oddly

  1.  It does not happen on HEAD
  2.  It does happen on wip/T19495, a tiny patch with one innocuous change to 
GHC.Tc.Gen.HsType
I can't see how my patch could possible cause "missing files" in ghc-bignum!
I'm guessing that there is a missing dependency that someone doesn't show up in 
master, but does in my branch, randomly.
There's something funny about ghc-bignum; it doesn't seem to be a regular 
library
Can anyone help?
Thanks
Simon

"inplace/bin/ghc-stage1" -hisuf hi -osuf  o -hcsuf hc -static  -O -H64m -Wall 
-fllvm-fill-undef-with-garbage-Werror-this-unit-id base-4.16.0.0 
-hide-all-packages -package-env - -i -ilibraries/base/. 
-ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build 
-ilibraries/base/dist-install/build/./autogen 
-Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include 
-Ilibraries/base/dist-install/build/include-optP-include 
-optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package-id 
ghc-bignum-1.0 -package-id ghc-prim-0.8.0 -package-id rts -this-unit-id base 
-Wcompat -Wnoncanonical-monad-instances -XHaskell2010 -O -dcore-lint -ticky 
-Wwarn  -no-user-package-db -rtsopts  -Wno-trustworthy-safe 
-Wno-deprecated-flags -Wnoncanonical-monad-instances  -outputdir 
libraries/base/dist-install/build  -dynamic-too -c 
libraries/base/./GHC/Exception/Type.hs-boot -o 
libraries/base/dist-install/build/GHC/Exception/Type.o-boot -dyno 
libraries/base/dist-install/build/GHC/Exception/Type.dyn_o-boot

Failed to load interface for 'GHC.Num.Integer'

There are files missing in the 'ghc-bignum' package,

try running 'ghc-pkg check'.

Use -v (or `:set -v` in ghci) to see a list of the files searched for.

make[1]: *** [libraries/base/ghc.mk:4: 
libraries/base/dist-install/build/GHC/Exception/Type.o-boot] Error 1

make[1]: *** Waiting for unfinished jobs



___

ghc-devs mailing list

ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>

http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs<https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devs=04%7C01%7Csimonpj%40microsoft.com%7Cc275ff3bbab342f7a26508d8e78c9369%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637513938702730130%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=piDkvXfdWip%2FxOKiYwYUb1G%2FvCpliL9dBuV8ltIdE10%3D=0>
___
ghc-devs mailing list
ghc-devs@hask

Build failure -- missing dependency? Help!

2021-03-14 Thread Simon Peyton Jones via ghc-devs
I'm getting this (with 'sh validate -legacy').  Oddly

  *   It does not happen on HEAD
  *   It does happen on wip/T19495, a tiny patch with one innocuous change to 
GHC.Tc.Gen.HsType
I can't see how my patch could possible cause "missing files" in ghc-bignum!
I'm guessing that there is a missing dependency that someone doesn't show up in 
master, but does in my branch, randomly.
There's something funny about ghc-bignum; it doesn't seem to be a regular 
library
Can anyone help?
Thanks
Simon

"inplace/bin/ghc-stage1" -hisuf hi -osuf  o -hcsuf hc -static  -O -H64m -Wall 
-fllvm-fill-undef-with-garbage-Werror-this-unit-id base-4.16.0.0 
-hide-all-packages -package-env - -i -ilibraries/base/. 
-ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build 
-ilibraries/base/dist-install/build/./autogen 
-Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include 
-Ilibraries/base/dist-install/build/include-optP-include 
-optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package-id 
ghc-bignum-1.0 -package-id ghc-prim-0.8.0 -package-id rts -this-unit-id base 
-Wcompat -Wnoncanonical-monad-instances -XHaskell2010 -O -dcore-lint -ticky 
-Wwarn  -no-user-package-db -rtsopts  -Wno-trustworthy-safe 
-Wno-deprecated-flags -Wnoncanonical-monad-instances  -outputdir 
libraries/base/dist-install/build  -dynamic-too -c 
libraries/base/./GHC/Exception/Type.hs-boot -o 
libraries/base/dist-install/build/GHC/Exception/Type.o-boot -dyno 
libraries/base/dist-install/build/GHC/Exception/Type.dyn_o-boot

Failed to load interface for 'GHC.Num.Integer'

There are files missing in the 'ghc-bignum' package,

try running 'ghc-pkg check'.

Use -v (or `:set -v` in ghci) to see a list of the files searched for.

make[1]: *** [libraries/base/ghc.mk:4: 
libraries/base/dist-install/build/GHC/Exception/Type.o-boot] Error 1

make[1]: *** Waiting for unfinished jobs
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Inlining of `any @[]` vs `elem @[]`

2021-03-12 Thread Simon Peyton Jones via ghc-devs
Ah, sorry, I thought it was just curiosity about what has changed.

I am not sure whether there will be future 8.10 releases; but you can open a 
ticket asking Ben to backport the fix (which you have found) to 8.10, if there 
is to be such a release.

Simon

|  -Original Message-
|  From: ÉRDI Gergő 
|  Sent: 12 March 2021 11:23
|  To: Simon Peyton Jones 
|  Cc: GHC Devs 
|  Subject: RE: Inlining of `any @[]` vs `elem @[]`
|  
|  On Fri, 12 Mar 2021, Simon Peyton Jones wrote:
|  
|  > I'm not sure... you could investigate, but I'm inclined just to
|  declare victory!
|  
|  That's easy for you to say, but here I am stuck with Stack not
|  supporting GHC 9.0...
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith
|  ub.com%2Fcommercialhaskell%2Fstack%2Fissues%2F5486data=04%7C01%7C
|  simonpj%40microsoft.com%7C8ca06575fa2e439f3c9108d8e5494435%7C72f988bf8
|  6f141af91ab2d7cd011db47%7C1%7C0%7C637511450139614984%7CUnknown%7CTWFpb
|  GZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0
|  %3D%7C1000sdata=djhrOesH8Ku%2FnfGynP%2Blx9swLHJ9blzfdMGak27OKbk%3
|  Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Inlining of `any @[]` vs `elem @[]`

2021-03-12 Thread Simon Peyton Jones via ghc-devs
|  I wonder why that is? What changed between GHC 8.10.3 and 9.0.1? Was
|  the definition of `elem` changed in `base`?

I'm not sure... you could investigate, but I'm inclined just to declare victory!

S

|  -Original Message-
|  From: ÉRDI Gergő 
|  Sent: 12 March 2021 10:02
|  To: Simon Peyton Jones 
|  Cc: GHC Devs 
|  Subject: RE: Inlining of `any @[]` vs `elem @[]`
|  
|  On Thu, 11 Mar 2021, Simon Peyton Jones wrote:
|  
|  > With HEAD, and -O, I get the exact same (good code) for these two
|  functions:
|  >
|  >f x = any (x ==) [1, 5, 7::Int]
|  >
|  >g x = elem x [2, 6, 9 :: Int]
|  >
|  > Maybe this is fixed?  If you think not, maybe open a ticket?
|  
|  OK, so initially I tried it on GHC 8.10.3, which is where `elem @[]`
|  is not optimized. I have now tried on GHC 9.0.1, where, just like you
|  see on HEAD, indeed it gets it right.
|  
|  I wonder why that is? What changed between GHC 8.10.3 and 9.0.1? Was
|  the definition of `elem` changed in `base`?
|  
|  Thanks,
|   Gergo
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: WSL2

2021-03-11 Thread Simon Peyton Jones via ghc-devs
OK thanks. Let's pursue this further on this ticket:
https://gitlab.haskell.org/ghc/ghc/-/issues/19525

Simon

|  -Original Message-
|  From: ghc-devs  On Behalf Of Viktor
|  Dukhovni
|  Sent: 11 March 2021 20:36
|  To: ghc-devs@haskell.org
|  Subject: Re: WSL2
|  
|  On Thu, Mar 11, 2021 at 07:53:20PM +, Simon Peyton Jones via ghc-
|  devs wrote:
|  
|  > Voila
|  
|  Thanks!
|  
|  > /etc/nsswitch.conf group entry
|  > group:  files systemd
|  
|  The main "suspicious" thing here (decoded traces below my signature)
|  is that the nsswitch.conf file is configured to try "systemd" as a
|  source of group data, but attempts to contact "systemd" or read the
|  underlying systemd store directly are failing.  This is different from
|  "not found", where systemd might have furnished a negative reply (as
|  is the case on my Fedora 31 system, see below).
|  
|  So a failure return code is not surprising, because the answer is not
|  authoritative, systemd might have answered differently if it had been
|  possible to query it.  It appears the WSL2 systems have a systemically
|  misconfigured "nsswitch.conf" that wants to query "group" (and likely
|  other) data from an unavailable source.
|  
|  [ Bottom line, the "unix" test case in question may need to be
|  prepared
|to encounter such misconfiguration of the test platform and accept
|either type of error.  Perhaps catch the IO expected IO exception,
|  and
|output a fixed "not found" message regardless of the exception
|  details,
|or by specifically checking for either of the two expected forms. ]
|  
|  By way of contrast, on my Fedora system, systemd can actually be
|  reached and appears to respond to the "nss" library's satisfaction:
|  
|  execve("/usr/bin/getent", ["getent", "group", "xyzzy0"],
|  0x7fff3afbcca0 /* 31 vars */) = 0
|  ...
|  openat(AT_FDCWD, "/lib64/libnss_files.so.2", O_RDONLY|O_CLOEXEC) =
|  3
|  openat(AT_FDCWD, "/etc/group", O_RDONLY|O_CLOEXEC) = 3
|  read(3, "root:x:0:\nbin:x:1:\ndaemon:x:2:\ns"..., 4096) = 1161
|  read(3, "", 4096)   = 0
|  ...
|  openat(AT_FDCWD, "/lib64/libnss_systemd.so.2", O_RDONLY|O_CLOEXEC)
|  = 3
|  access("/etc/systemd/dont-synthesize-nobody", F_OK) = -1 ENOENT
|  (No such file or directory)
|  socket(AF_UNIX, SOCK_STREAM|SOCK_CLOEXEC|SOCK_NONBLOCK, 0) = 3
|  connect(3, {sa_family=AF_UNIX,
|  sun_path="/run/dbus/system_bus_socket"}, 30) = 0
|  getsockopt(3, SOL_SOCKET, SO_PEERCRED, {pid=1, uid=0, gid=0},
|  [12]) = 0
|  getsockopt(3, SOL_SOCKET, SO_PEERSEC, 0x5568c64660e0, [64]) = -1
|  ENOPROTOOPT (Protocol not available)
|  getsockopt(3, SOL_SOCKET, SO_PEERGROUPS, 0x5568c6466130, [256->0])
|  = 0
|  sendmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="\0AUTH EXTERNAL\r\nDATA\r\n", iov_len=22},
|  {iov_base="NEGOTIATE_UNIX_FD\r\n", iov_len=19}, {iov_base="BEGIN\r\n",
|  iov_len=7}], msg_iovlen=3, msg_controllen=0, msg_flags=0},
|  MSG_DONTWAIT|MSG_NOSIGNAL) = 48
|  recvmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="DATA\r\nOK 7bc788e33c85b875f6b74a6"...,
|  iov_len=256}], msg_iovlen=1, msg_controllen=0,
|  msg_flags=MSG_CMSG_CLOEXEC}, MSG_DONTWAIT|MSG_CMSG_CLOEXEC) = 58
|  sendmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="l\1\0\1\0\0\0\0\1\0\0\0m\0\0\0\1\1o\0\25\0\0\0/org
|  /fre"..., iov_len=128}], msg_iovlen=1, msg_controllen=0, msg_flags=0},
|  MSG_DONTWAIT|MSG_NOSIGNAL) = 128
|  recvmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="l\2\1\1\16\0\0\0\377\377\377\377G\0\0\0\5\1u\0\1\0
|  \0\0", iov_len=24}], msg_iovlen=1, msg_controllen=0,
|  msg_flags=MSG_CMSG_CLOEXEC}, MSG_DONTWAIT|MSG_CMSG_CLOEXEC) = 24
|  recvmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="\7\1s\0\24\0\0\0org.freedesktop.DBus\0\0\0\0"...,
|  iov_len=78}], msg_iovlen=1, msg_controllen=0,
|  msg_flags=MSG_CMSG_CLOEXEC}, MSG_DONTWAIT|MSG_CMSG_CLOEXEC) = 78
|  sendmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="l\1\0\1\v\0\0\0\2\0\0\0\247\0\0\0\1\1o\0\31\0\0\0/
|  org/fre"..., iov_len=184}, {iov_base="\6\0\0\0xyzzy0\0", iov_len=11}],
|  msg_iovlen=2, msg_controllen=0, msg_flags=0},
|  MSG_DONTWAIT|MSG_NOSIGNAL) = 195
|  recvmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="l\4\1\1\16\0\0\0\377\377\377\377\227\0\0\0\7\1s\0\
|  24\0\0\0", iov_len=24}], msg_iovlen=1, msg_controllen=0,
|  msg_flags=MSG_CMSG_CLOEXEC}, MSG_DONTWAIT|MSG_CMSG_CLOEXEC) = 24
|  recvmsg(3, {msg_name=NULL, msg_namelen=0,
|  msg_iov=[{iov_base="org.freedesktop.DBus\0\0\0\0\6\1s\0\t\0\0\0"...,
|  iov_len=1

RE: WSL2

2021-03-11 Thread Simon Peyton Jones via ghc-devs
@haskell.org
|  Subject: Re: WSL2
|  
|  On Thu, Mar 11, 2021 at 12:21:15PM +, Simon Peyton Jones via ghc-
|  devs wrote:
|  
|  > Like Tom, I'm not following the details, but if you want me to run
|  > some commands and send you the output I can do that.  Just send the
|  > script!
|  
|  See attached.  If any of the prerequisite shell utilities are not
|  installed, the script will exit asking that they be installed.
|  
|  Please email me the output, or post to the list.  (Should be just a
|  couple of hundred lines of mostly hex output).
|  
|  --
|  Viktor.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Inlining of `any @[]` vs `elem @[]`

2021-03-11 Thread Simon Peyton Jones via ghc-devs
Gergo

With HEAD, and -O, I get the exact same (good code) for these two functions:

f x = any (x ==) [1, 5, 7::Int]

g x = elem x [2, 6, 9 :: Int]

namely

f = \ (x_aga :: Int) ->
  case x_aga of { GHC.Types.I# x1_a13b ->
  case x1_a13b of {
__DEFAULT -> GHC.Types.False;
1# -> GHC.Types.True;
5# -> GHC.Types.True;
7# -> GHC.Types.True
  }
  }

g = \ (x_aQu :: Int) ->
  case x_aQu of { GHC.Types.I# x1_a13b ->
  case x1_a13b of {
__DEFAULT -> GHC.Types.False;
2# -> GHC.Types.True;
6# -> GHC.Types.True;
9# -> GHC.Types.True
  }
  }

Maybe this is fixed?  If you think not, maybe open a ticket?

Simon

|  -Original Message-
|  From: ghc-devs  On Behalf Of ÉRDI Gergo
|  Sent: 07 March 2021 02:59
|  To: GHC Devs 
|  Subject: Inlining of `any @[]` vs `elem @[]`
|  
|  Hi,
|  
|  The inlining behaviour of `any @[]` and `elem @[]` differs in a way
|  that I am not sure is intentional, and it is affecting Clash (see
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith
|  ub.com%2Fclash-lang%2Fclash-
|  compiler%2Fissues%2F1691data=04%7C01%7Csimonpj%40microsoft.com%7C
|  e37a9761e8814eada5f208d8e115026d%7C72f988bf86f141af91ab2d7cd011db47%7C
|  1%7C0%7C637506827802688772%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDA
|  iLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000sdata=Kik8v
|  KuwNobr9kiQOcIHuKTn%2BbEmQ7oY8tqP9tFjs6M%3Dreserved=0). I would
|  think that if it is a good idea to inline `any` then inlining `elem`
|  would be just as good an idea, or vice versa.
|  
|  However, `any` is defined polymorphically over `Foldable`, via
|  `foldMap` using `foldr`, with all steps between (and `foldr @[]`!)
|  marked as `INLINE`. The result is that if you use `any (x ==) [1, 5,
|  7]` you get the following beautiful Core:
|  
|  ```
|  topEntity
| = \ (x_agAF :: Int) ->
| case x_agAF of { GHC.Types.I# y_ahao ->
| case y_ahao of {
|   __DEFAULT -> GHC.Types.False;
|   1# -> GHC.Types.True;
|   5# -> GHC.Types.True;
|   7# -> GHC.Types.True
| }
| }
|  ```
|  
|  As the kids these days would say: *chef's kiss*.
|  
|  
|  `elem`, on the other hand, is a typeclass method of `Foldable`, with a
|  default implementation in terms of `any`, but overridden for lists
|  with the following implementation:
|  
|  ```
|  GHC.List.elem :: (Eq a) => a -> [a] -> Bool
|  GHC.List.elem _ []   = False
|  GHC.List.elem x (y:ys)   = x==y || GHC.List.elem x ys
|  {-# NOINLINE [1] elem #-}
|  {-# RULES
|  "elem/build"forall x (g :: forall b . Eq a => (a -> b -> b) -> b -
|  > b)
|  . elem x (build g) = g (\ y r -> (x == y) || r) False
|#-}
|  ```
|  
|  This is marked as non-inlineable until phase 1 (so that `elem/build`
|  has a chance of firing), but it seems that when build fusion doesn't
|  apply (since `[1, 5, 7]` is, of course, not built via `build`), no
|  inlining happens AT ALL, even in later phases, so we end up with this:
|  
|  ```
|  topEntity
| = \ (x_agAF :: Int) ->
| GHC.List.elem
|   @ Int
|   GHC.Classes.$fEqInt
|   x_agAF
|   (GHC.Types.:
|  @ Int
|  (GHC.Types.I# 1#)
|  (GHC.Types.:
| @ Int
| (GHC.Types.I# 5#)
| (GHC.Types.: @ Int (GHC.Types.I# 7#) (GHC.Types.[] @
|  Int ```
|  
|  So not only does it trip up Clash, it would also result in less
|  efficient code in software when using "normal" GHC.
|  
|  Is this all intentional? Wouldn't it make more sense to mark
|  `GHC.List.elem` as `INLINE [1]` instead of `NOINLINE [1]`, so that any
|  calls remaining after build fusion would be inlined?
|  
|  Thanks,
|   Gergo
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7Ce37a9761e8814eada5f2
|  08d8e115026d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637506827802
|  688772%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000sdata=yMXu0XJQU2GmlDTH9ZaHXhl33
|  ZRBjHMe41rr8lKVxkk%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: WSL2

2021-03-11 Thread Simon Peyton Jones via ghc-devs
PS: since this is not, apparently, just my stupidity, it would be good to open 
a ticket and transfer this thread to it.  Would someone like to do that?

|  -Original Message-
|  From: ghc-devs  On Behalf Of Tom Ellis
|  Sent: 11 March 2021 11:41
|  To: ghc-devs@haskell.org
|  Subject: Re: WSL2
|  
|  On Thu, Mar 11, 2021 at 06:19:46AM -0500, Viktor Dukhovni wrote:
|  > On Thu, Mar 11, 2021 at 06:05:04AM -0500, Viktor Dukhovni wrote:
|  > > So the question is why the lookup is failing.  To that end
|  compiling
|  > > a tracing with "strace" the below C program should tell the story:
|  [...]
|  > To experiment with other group names and make sure that at least
|  group
|  > "root" or similar works, a slightly extended version is:
|  [...]
|  
|  I'm not really following the details, but is this useful to you?
|  
|  % cat g.c && cc g.c -o g && ./g
|  #include 
|  #include 
|  #include 
|  #include 
|  
|  int main(int argc, char **argv)
|  {
|  char buf[1024];
|  struct group g, *p;
|  int rc;
|  
|  errno = 0;
|  rc = getgrnam_r(argc > 1 ? argv[1] : "nosuchgrouphere",
|  , buf, sizeof(buf), );
|  printf("%s(%p) %m(%d)\n", p ? g.gr_name : NULL, p, errno);
|  return (rc == 0 && p == NULL);
|  }
|  (null)((nil)) No such process(3)
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C48a10ad0766c4dd6caf4
|  08d8e4829c7d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637510597246
|  441070%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=nQdF9H7BpTqQL%2Bm0URWQmXh
|  1KEQAV1KgfPvG75mOR%2B0%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: WSL2

2021-03-11 Thread Simon Peyton Jones via ghc-devs
Like Tom, I'm not following the details, but if you want me to run some 
commands and send you the output I can do that.  Just send the script!

|  -Original Message-
|  From: ghc-devs  On Behalf Of Tom Ellis
|  Sent: 11 March 2021 11:41
|  To: ghc-devs@haskell.org
|  Subject: Re: WSL2
|  
|  On Thu, Mar 11, 2021 at 06:19:46AM -0500, Viktor Dukhovni wrote:
|  > On Thu, Mar 11, 2021 at 06:05:04AM -0500, Viktor Dukhovni wrote:
|  > > So the question is why the lookup is failing.  To that end
|  compiling
|  > > a tracing with "strace" the below C program should tell the story:
|  [...]
|  > To experiment with other group names and make sure that at least
|  group
|  > "root" or similar works, a slightly extended version is:
|  [...]
|  
|  I'm not really following the details, but is this useful to you?
|  
|  % cat g.c && cc g.c -o g && ./g
|  #include 
|  #include 
|  #include 
|  #include 
|  
|  int main(int argc, char **argv)
|  {
|  char buf[1024];
|  struct group g, *p;
|  int rc;
|  
|  errno = 0;
|  rc = getgrnam_r(argc > 1 ? argv[1] : "nosuchgrouphere",
|  , buf, sizeof(buf), );
|  printf("%s(%p) %m(%d)\n", p ? g.gr_name : NULL, p, errno);
|  return (rc == 0 && p == NULL);
|  }
|  (null)((nil)) No such process(3)
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C48a10ad0766c4dd6caf4
|  08d8e4829c7d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637510597246
|  441070%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=nQdF9H7BpTqQL%2Bm0URWQmXh
|  1KEQAV1KgfPvG75mOR%2B0%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: WSL2

2021-03-10 Thread Simon Peyton Jones via ghc-devs
|  Hmm, this is quite unfortunate. My recollection is that WSL2 by
|  default runs an Ubuntu image, so I'm somewhat surprised that this is
|  failing.

bash$ uname -a
Linux MSRC-3645512 5.4.72-microsoft-standard-WSL2 #1 SMP Wed Oct 28 23:40:43 
UTC 2020 x86_64 x86_64 x86_64 GNU/Linux

bash$ cat /etc/os-release
NAME="Ubuntu"
VERSION="20.04.2 LTS (Focal Fossa)"
ID=ubuntu
ID_LIKE=debian
PRETTY_NAME="Ubuntu 20.04.2 LTS"
VERSION_ID="20.04"
HOME_URL="https://www.ubuntu.com/;
SUPPORT_URL="https://help.ubuntu.com/;
BUG_REPORT_URL="https://bugs.launchpad.net/ubuntu/;
PRIVACY_POLICY_URL="https://www.ubuntu.com/legal/terms-and-policies/privacy-policy;
VERSION_CODENAME=focal
UBUNTU_CODENAME=focal

|  -Original Message-
|  From: Ben Gamari 
|  Sent: 10 March 2021 17:22
|  To: Simon Peyton Jones ; ghc-devs 
|  Subject: Re: WSL2
|  
|  Simon Peyton Jones via ghc-devs  writes:
|  
|  > Friends
|  > I've just installed WSL2 and built GHC.
|  > I get this (single) validation failure in
|  > libraries/unix/tests/getGroupEntryForName. It seems to be just an
|  > error message wibble, but I can't push a change to master because
|  > that'll affect everyone else.
|  
|  Hmm, this is quite unfortunate. My recollection is that WSL2 by
|  default runs an Ubuntu image, so I'm somewhat surprised that this is
|  failing.
|  
|  Can you paste the output of `uname -a` and `cat /etc/os-release`?
|  
|  Cheers,
|  
|  - Ben

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


WSL2

2021-03-09 Thread Simon Peyton Jones via ghc-devs
Friends
I've just installed WSL2 and built GHC.
I get this (single) validation failure in 
libraries/unix/tests/getGroupEntryForName.  It seems to be just an error 
message wibble, but I can't push a change to master because that'll affect 
everyone else.
Any ideas?
Simon


=> 1 of 1 [0, 0, 0]

]0;getGroupEntryForName(normal) 1 of 1 [0, 0, 0]Actual stderr output differs 
from expected:

--- getGroupEntryForName.run/getGroupEntryForName.stderr.normalised 2021-03-09 
22:36:01.300421100 +

+++ getGroupEntryForName.run/getGroupEntryForName.run.stderr.normalised   
2021-03-09 22:36:01.300421100 +

@@ -1 +1 @@

-getGroupEntryForName: getGroupEntryForName: does not exist (no such group)

+getGroupEntryForName: getGroupEntryForName: does not exist (No such process)

*** unexpected failure for getGroupEntryForName(normal)
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: MR template text

2021-02-23 Thread Simon Peyton Jones via ghc-devs
Thanks Julian

I am by definition the wrong person to judge (or even write) text like this.

Could you possibly have a go at editing the draft I sent so that you think it 
has the right tone and content?  The current one is not working well.  Your 
draft will almost certainly be better than mine.

Simon

From: Julian Leviston 
Sent: 23 February 2021 21:59
To: Simon Peyton Jones 
Cc: ghc-devs 
Subject: Re: MR template text


Hi Simon, list et al,

I’ve only contributed a couple of times, but I personally found the checklist 
invaluable to guide me (and remind me of) what needed to be done in total. In 
addition, giving folks a checklist that they can actually check off gives us a 
common set of agreed upon things that’s needed in an MR right in the MR, which 
is nice to folks.

I wonder if we could reword it to say it’s still a work in progress or words to 
that effect at the top, and make the system not allow MRs to be built and/or 
merged unless they edit that text away, as well as have a bot inform them of 
why this is? :) I like the idea of the system guiding us through the process.

Regards,
Julian

Would it be possible to get our tooling (a bot?) to nudge us if we haven’t 
changed it?

On 24 Feb 2021, at 3:14 am, Simon Peyton Jones via ghc-devs 
mailto:ghc-devs@haskell.org>> wrote:

I often see MRs in my inbox that say
Thank you for your contribution to GHC!
Please take a few moments to verify that your commits fulfill the following:
[ ] are either individually buildable or squashed

This is because the author hasn’t changed the Description of the MR, but rather 
has left the template text unchanged.
As a way to “nudge” authors to give reviewers more information, I suggest 
replacing the template text with the draft below.  Does anyone have any views, 
for or against?
Simon

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


MR template text

2021-02-23 Thread Simon Peyton Jones via ghc-devs
I often see MRs in my inbox that say

Thank you for your contribution to GHC!

Please take a few moments to verify that your commits fulfill the following:

[ ] are either individually buildable or squashed

This is because the author hasn't changed the Description of the MR, but rather 
has left the template text unchanged.
As a way to "nudge" authors to give reviewers more information, I suggest 
replacing the template text with the draft below.  Does anyone have any views, 
for or against?
Simon

Proposed new template

PLEASE REPLACE ALL OF THIS TEXT with a description of your merge request, 
including



* A description of what the Merge Request does.  For a single-commit MR, a copy 
of the

  commit message is often perfect.



* A reference (e.g. #19415) to the ticket that led to this MR, and that 
describes the

  problem that this MR solves.  Almost all MRs need a ticket, except the tiniest

  changes (e.g. code formatting)

  - A ticket describes a *problem*

  - A merge request describes a *solution* to that problem.



While you are encouraged to write a good MR Description, it's not compulsory.

You could just be putting up the MR to share with a colleague, for example.



But if you want (a) to get code reviews from others, or

(b) to land the patch in GHC,

please do follow these guidelines.



For general style guidance see

https://gitlab.haskell.org/ghc/ghc/wikis/commentary/coding-style


For completeness, the current template is


Thank you for your contribution to GHC!



Please take a few moments to verify that your commits fulfill the following:



* [ ] are either individually buildable or squashed

* [ ] have commit messages which describe *what they do*

   (referring to [Notes][notes] and tickets using `#` syntax when

   appropriate)

* [ ] have added source comments describing your change. For larger changes you

   likely should add a [Note][notes] and cross-reference it from the relevant

   places.

* [ ] add a [testcase to the

   
testsuite](https://gitlab.haskell.org/ghc/ghc/wikis/building/running-tests/adding).

* [ ] replace this message with a description motivating your change



If you have any questions don't hesitate to open your merge request and inquire

in a comment. If your patch isn't quite done yet please do add prefix your MR

title with `WIP:`.



[notes]: 
https://gitlab.haskell.org/ghc/ghc/wikis/commentary/coding-style#comments-in-the-source-code
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: On CI

2021-02-22 Thread Simon Peyton Jones via ghc-devs
1haWwiLCJXVCI6Mn0%3D%7C3000=9MEWPlRhO2xZK2iu5OqzXS9RZqc9pKNJcGDv7Nj3hyA%3D=0>
They utilise ccache to cache the clang-based C++-backend, so that they only 
have to re-run the front- and middle-end. In effect, they take advantage of the 
fact that the "function" clang, in contrast to the "function" stage1 compiler, 
stays the same.
It's hard to achieve that for GHC, where a complete compiler pipeline comes as 
one big, fused "function": An external tool can never be certain that a change 
to Parser.y could not affect the CodeGen phase.

Inspired by Lean, the following is a bit inconcrete and imaginary, but maybe we 
could make it so that compiler phases "sign" parts of the interface file with 
the binary hash of the respective subcomponents of the phase?
E.g., if all the object files that influence CodeGen (that will later be linked 
into the stage1 compiler) result in a hash of 0xdeadbeef before and after the 
change to Parser.y, we know we can stop recompiling Data.List with the stage1 
compiler when we see that the IR passed to CodeGen didn't change, because the 
last compile did CodeGen with a stage1 compiler with the same hash 0xdeadbeef. 
The 0xdeadbeef hash is a proxy for saying "the function CodeGen stayed the 
same", so we can reuse its cached outputs.
Of course, that is utopic without a tool that does the "taint analysis" of 
which modules in GHC influence CodeGen. Probably just including all the 
transitive dependencies of GHC.CmmToAsm suffices, but probably that's too crude 
already. For another example, a change to GHC.Utils.Unique would probably 
entail a full rebuild of the compiler because it basically affects all compiler 
phases.
There are probably parallels with recompilation avoidance in a language with 
staged meta-programming.

Am Fr., 19. Feb. 2021 um 11:42 Uhr schrieb Josef Svenningsson via ghc-devs 
mailto:ghc-devs@haskell.org>>:
Doing "optimistic caching" like you suggest sounds very promising. A way to 
regain more robustness would be as follows.
If the build fails while building the libraries or the stage2 compiler, this 
might be a false negative due to the optimistic caching. Therefore, evict the 
"optimistic caches" and restart building the libraries. That way we can 
validate that the build failure was a true build failure and not just due to 
the aggressive caching scheme.

Just my 2p

Josef

____________
From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> on behalf 
of Simon Peyton Jones via ghc-devs 
mailto:ghc-devs@haskell.org>>
Sent: Friday, February 19, 2021 8:57 AM
To: John Ericson 
mailto:john.ericson@obsidian.systems>>; ghc-devs 
mailto:ghc-devs@haskell.org>>
Subject: RE: On CI


  1.  Building and testing happen together. When tests failure spuriously, we 
also have to rebuild GHC in addition to re-running the tests. That's pure 
waste. 
https://gitlab.haskell.org/ghc/ghc/-/issues/13897<https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitlab.haskell.org%2Fghc%2Fghc%2F-%2Fissues%2F13897=04%7C01%7Csimonpj%40microsoft.com%7C9d7043627f5042598e5b08d8d6f648c4%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637495701691140326%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000=Nm6vfgGLLlJpiGa8XKxI6kNkBetp8ZZLPZS8hF%2BydrM%3D=0>
 tracks this more or less.
I don't get this.  We have to build GHC before we can test it, don't we?
2 .  We don't cache between jobs.
This is, I think, the big one.   We endlessly build the exact same binaries.
There is a problem, though.  If we make *any* change in GHC, even a trivial 
refactoring, its binary will change slightly.  So now any caching build system 
will assume that anything built by that GHC must be rebuilt - we can't use the 
cached version.  That includes all the libraries and the stage2 compiler.  So 
caching can save all the preliminaries (building the initial Cabal, and large 
chunk of stage1, since they are built with the same bootstrap compiler) but 
after that we are dead.
I don't know any robust way out of this.  That small change in the source code 
of GHC might be trivial refactoring, or it might introduce a critical 
mis-compilation which we really want to see in its build products.
However, for smoke-testing MRs, on every architecture, we could perhaps cut 
corners.  (Leaving Marge to do full diligence.)  For example, we could declare 
that if we have the result of compiling library module X.hs with the stage1 GHC 
in the last full commit in master, then we can re-use that build product rather 
than compiling X.hs with the MR's slightly modified stage1 GHC.  That *might* 
be wrong; but it's usually right.
Anyway, there are big wins to be had here.
Simon



From: ghc-devs 
mailto:ghc-devs-boun...@haskell.org>> On Behalf 
Of John Ericson
Sent: 19 February 2021 03:19
To: ghc-devs mailto:ghc-devs@haskell.org>>
Subject: R

RE: On CI

2021-02-19 Thread Simon Peyton Jones via ghc-devs
  1.  Building and testing happen together. When tests failure spuriously, we 
also have to rebuild GHC in addition to re-running the tests. That's pure 
waste. 
https://gitlab.haskell.org/ghc/ghc/-/issues/13897
 tracks this more or less.
I don't get this.  We have to build GHC before we can test it, don't we?
2 .  We don't cache between jobs.
This is, I think, the big one.   We endlessly build the exact same binaries.
There is a problem, though.  If we make *any* change in GHC, even a trivial 
refactoring, its binary will change slightly.  So now any caching build system 
will assume that anything built by that GHC must be rebuilt - we can't use the 
cached version.  That includes all the libraries and the stage2 compiler.  So 
caching can save all the preliminaries (building the initial Cabal, and large 
chunk of stage1, since they are built with the same bootstrap compiler) but 
after that we are dead.
I don't know any robust way out of this.  That small change in the source code 
of GHC might be trivial refactoring, or it might introduce a critical 
mis-compilation which we really want to see in its build products.
However, for smoke-testing MRs, on every architecture, we could perhaps cut 
corners.  (Leaving Marge to do full diligence.)  For example, we could declare 
that if we have the result of compiling library module X.hs with the stage1 GHC 
in the last full commit in master, then we can re-use that build product rather 
than compiling X.hs with the MR's slightly modified stage1 GHC.  That *might* 
be wrong; but it's usually right.
Anyway, there are big wins to be had here.
Simon



From: ghc-devs  On Behalf Of John Ericson
Sent: 19 February 2021 03:19
To: ghc-devs 
Subject: Re: On CI


I am also wary of us to deferring checking whole platforms and what not. I 
think that's just kicking the can down the road, and will result in more 
variance and uncertainty. It might be alright for those authoring PRs, but it 
will make Ben's job keeping the system running even more grueling.

Before getting into these complex trade-offs, I think we should focus on the 
cornerstone issue that CI isn't incremental.

  1.  Building and testing happen together. When tests failure spuriously, we 
also have to rebuild GHC in addition to re-running the tests. That's pure 
waste. 
https://gitlab.haskell.org/ghc/ghc/-/issues/13897
 tracks this more or less.
  2.  We don't cache between jobs. Shake and Make do not enforce dependency 
soundness, nor cache-correctness when the build plan itself changes, and this 
had made this hard/impossible to do safely. Naively this only helps with stage 
1 and not stage 2, but if we have separate stage 1 and --freeze1 stage 2 
builds, both can be incremental. Yes, this is also lossy, but I only see it 
leading to false failures not false acceptances (if we can also test the stage 
1 one), so I consider it safe. MRs that only work with a slow full build 
because ABI can so indicate.
The second, main part is quite hard to tackle, but I strongly believe 
incrementality is what we need most, and what we should remain focused on.

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


RE: Plan for GHC 9.2

2021-02-15 Thread Simon Peyton Jones via ghc-devs
Ben

Can we get record dot syntax into 9.2?

* Shayne is really nearly there in !4532; he has been working
  hard and recently.
* It depends on my !4981 (was 4722) which fixes some bugs and
  I'm keen to commit.


So, is it ok in principle to pull to trigger on !4981, and hopefully !4532?

Simon

|  -Original Message-
|  From: ghc-devs  On Behalf Of Ben Gamari
|  Sent: 04 February 2021 18:56
|  To: GHC developers 
|  Subject: Plan for GHC 9.2
|  
|  
|  tl;dr. Provisional release schedule for 9.2 enclosed. Please discuss,
| especially if you have something you would like merged for
|  9.2.1.
|  
|  Hello all,
|  
|  With GHC 9.0.1 at long-last out the door, it is time that we start
|  turning attention to GHC 9.2. I would like to avoid making the mistake
|  made in the 9.0 series in starting the fork in a state that required a
|  significant amount of backporting to be releaseable. Consequently, I
|  want to make sure that we have a fork schedule that is realistic given
|  the things that need to be merged for 9.2. These include:
|  
|   * Update haddock submodule in `master` (Ben)
|   * Bumping bytestring to 0.11 (#19091, Ben)
|   * Finishing the rework of sized integer primops (#19026, John
|  Ericson)
|   * Merge of ghc-exactprint into GHC? (Alan Zimmerman, Henry)
|   * Merge BoxedRep (#17526, Ben)
|   * ARM NCG backend and further stabilize Apple ARM support? (Moritz)
|   * Some form of coercion zapping (Ben, Simon, Richard)
|   * Tag inference analysis and tag check elision (Andreas)
|  
|  If you see something that you would like to see in 9.2.1 please do
|  holler. Otherwise, if you see your name in this list it would be great
|  if you could let me know when you think your project may be in a
|  mergeable state.
|  
|  Ideally we would strive for a schedule like the following:
|  
|  4 February 2021:   We are here
| ~4 weeks pass
|  3 March 2021:  Release branch forked
| 1 week passes
|  10 March 2021: Alpha 1 released
| 3 weeks pass
|  31 March 2021: Alpha 2 released
| 2 weeks pass
|  14 April 2021: Alpha 3 released
| 2 weeks pass
|  28 April 2021: Alpha 4 released
| 1 week passes
|  5 May 2021:Beta 1 released
| 1 week passes
|  12 May 2021:   Release candidate 1 released
| 2 weeks pass
|  26 May 2021:   Final release
|  
|  This provides ample time for stabilization while avoiding deviation
|  from the usual May release timeframe. However, this would require that
|  we move aggressively to start getting the tree into shape since the
|  fork would be less than four weeks away. I would appreciate
|  contributors'
|  thoughts on the viability of this timeline.
|  
|  Cheers,
|  
|  - Ben
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


cep_app traces

2021-02-15 Thread Simon Peyton Jones via ghc-devs
Ben
I'm getting a lot of

cpe_app(keepAlive#) 3

cpe_app(keepAlive)
trace messages from HEAD.   Maybe it's a leftover from tracing when you were 
developing?  Remove?
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Plan for GHC 9.2

2021-02-11 Thread Simon Peyton Jones via ghc-devs
Yes I agree, unlifted data types would be terrific.

From: ghc-devs  On Behalf Of Sebastian Graf
Sent: 11 February 2021 10:25
To: Ben Gamari 
Cc: ghc-devs 
Subject: Re: Plan for GHC 9.2

Hi,

Since my hopes of finally merging Nested CPR have recently been crushed again, 
I hope that we can include the implementation of the UnliftedDatatypes 
extension 
(proposal,
 
implementation).
It was on ice since it depends on the BoxedRep proposal, but if BoxedRep is 
going to make it, surely UnliftedDatatypes can make it, too.
I expect quite a few bugs, simply because I don't have much code to test it on 
yet. But I'm very confident that existing code isn't impacted by that, as most 
of the functionality (CodeGen for unlifted types, most importantly) was already 
there and I only had to refine a conditional here and there.

Cheers,
Sebastian

Am Mi., 10. Feb. 2021 um 18:42 Uhr schrieb Ben Gamari 
mailto:b...@well-typed.com>>:
Roland Senn mailto:r...@bluewin.ch>> writes:

> I hope ticket #19157 will make it in the GHC 9.2 release. In the GHCi
> debugger it adds the possibility to set ignore counts to breakpoints.
> The next  times the break point is reached the program's
> execution does not stop. This feature is available in nearly every
> debugger, but until now not yet in the GHCi debugger.
> Merge request !4839 is ready for review  (and it's NOT rocket
> science...)
>
Indeed, this seems quite reasonable. I don't see any reason why we
shouldn't be able to get it in to 9.2.1.

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: Stop holding hadrian back with backwards compatibility

2021-02-10 Thread Simon Peyton Jones via ghc-devs
build with hadrian, and then continue using make with the artifacts (partially) 
built by Hadrian

I agree this is a non-goal.

Simon

From: ghc-devs  On Behalf Of Moritz Angermann
Sent: 10 February 2021 13:32
To: Richard Eisenberg 
Cc: ghc-devs 
Subject: Re: Stop holding hadrian back with backwards compatibility

My understanding of this backwards compat logic is that it's only there to 
allow you to do stuff like:
build with hadrian, and then continue using make with the artifacts (partially) 
built by hadrian.  I think
this is a horrible idea in and onto itself, even if I can somewhat see the 
appeal as a gateway drug; in
which you'd slowly have hadrian take over parts that make used to do, and use 
make for the stuff that
doesn't work (yet) in hadrian.

However, I don't think the benefit of constraining hadrian to work in the make 
framework makes much
sense. We should be permitted to explore new (and better) solutions, that do 
not align with how the
make based build system did things if it allows for a less complex build system 
or faster builds or ...

Cheers,
 Moritz

On Wed, Feb 10, 2021 at 9:28 PM Richard Eisenberg 
mailto:r...@richarde.dev>> wrote:
This sounds very reasonable on the surface, but I don't understand the 
consequences of this proposal. What are these consequences? Will this break 
`make`? (It sounds like it won't, given that the change is to Hadrian.) Does 
this mean horrible things will happen if I use `make` and `hadrian` in the same 
tree? (I have never done this, other than with hadrian/ghci, which seems to 
have its own working directory.) Basically: for someone who uses the build 
system but does not work on it, how does this affect me? (Maybe not at all!)

I would explicitly like to endorse the direction of travel toward Hadrian and 
away from `make`.

Richard

> On Feb 10, 2021, at 8:05 AM, Moritz Angermann 
> mailto:moritz.angerm...@gmail.com>> wrote:
>
> Hi,
>
> so we've finally run into a case where we need to bump the rts version.  This 
> has a great ripple effect.  There is some implicit assumption that rts-1.0 
> will always be true. Of course that was a lie, but a lie we lived with for a 
> long time.
>
> Now, hadrian tries *really* hard to replicate some of the Make based build 
> systems idiosyncrasies, this includes creating versionless symlinks for the 
> rts. E.g. libHSrts -> libHSrts-1.0. There is a great deal of logic just 
> to achieve this, and of course it all crumbles now.
>
> I'd therefore like to float and propose the idea that we agree to *not* 
> bother (too?) much with make based build systems backwards compatibility and 
> warts that grew over the years in the make based build system with hadrian 
> going forward.
>
> Yes, I can probably fix this, and add even more code to this burning pile of 
> complexity, but why?  The next person will assume libHSrts does not need to 
> be versioned and continue with this mess.
>
> Let's have Hadrian be a clean cut in some areas (it already is, it does away 
> with the horrible abomination that ghc-cabal is--which only serves the 
> purpose of translating cabal descriptions into make readable files), and not 
> be bogged down by backwards compatibility.
>
> This is thus my call for voicing concern or the upkeep of legacy support, or 
> I'll take silence as the collective support of making hadrian *not* be held 
> back by backwards compatibility. (This would mean in this case, that I'd just 
> delete the backwards compat code instead of adding even more to it).
>
> I hope we all still want Hadrian to replace Make, if not and we want to keep 
> Make, why are we concerning ourselves with Hadrian in the first place. If we 
> are intending to ditch Make, let's not be held back by it.
>
> Cheers,
>  Moritz
> ___
> 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


Happy version downgrade

2021-02-03 Thread Simon Peyton Jones via ghc-devs
Friends
I can't build ghc-9.0 because of this:

checking for ghc-pkg matching /opt/ghc/bin/ghc... /opt/ghc/bin/ghc-pkg

checking for happy... /home/simonpj/.cabal/bin/happy

checking for version of happy... 1.20.0

configure: error: Happy version 1.19 is required to compile GHC.
What is the easiest way to fix?  I have happy 1.19.8, but it's not called plain 
"happy"

bash$ happy-1.19.8 --version

Happy Version 1.19.8 Copyright (c) 1993-1996 Andy Gill, Simon Marlow (c) 
1997-2005 Simon Marlow

Happy is a Yacc for Haskell, and comes with ABSOLUTELY NO WARRANTY.

This program is free software; you can redistribute it and/or modify

it under the terms given in the file 'LICENSE' distributed with

the Happy sources.
Thanks
Simon

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


RE: Inspecting function arguments in GHCi

2021-01-25 Thread Simon Peyton Jones via ghc-devs
Andrew

We have very poor documentation of the inner workings of the entire breakpoint
and debugging mechanism.   And very few (zero?) people who truly understand it.

You could do a great service by starting a Note or a wiki page or something
that lays out the moving parts.  You may not feel that you are well equipped to
do so, but you'd almost certainly improve matters!

Has anyone else been working in this space.  Matthew P perhaps?

|  So I'm wondering where would be a good place in the pipeline to
|  transform patterns like these into at-patterns, to give them Id's.

I'm not sure what you have in mind. Could you say more about (a) what you'd like
the user experience to be, and (b) how you are considering implementing it.

|  However, the breakpoint logic only looks at the free variables of the
|  right-hand sides and not transitively, which means that e.g. in the
|  following example neither ':print arg1' nor ':print as' works when the
|  interpreter hits a breakpoint in the top level expression on the RHS:
 
Perhaps you are suggesting that each breakpoint should capture bindings for
*all in-scope variables* rather than *all free variable of the sub-expression".
If so, that sounds pretty feasible.  It might risk keeping variables alive
that would otherwise have been garbage-collected, but maybe that's a price
worth paying.

Simon


|  -Original Message-
|  From: ghc-devs  On Behalf Of Andrew
|  Kvapil
|  Sent: 25 January 2021 11:06
|  To: ghc-devs@haskell.org
|  Subject: Inspecting function arguments in GHCi
|  
|  Hello,
|  
|  I'm interested in inspecting the strictness of functions at runtime
|  and the depth of thunks "in the wild." For this reason I'm modifying
|  GHC 8.10.2, essentially to add additional information to breakpoints.
|  I'd like to reuse the logic behind GHCi's :print command
|  (pprintClosureCommand, obtainTermFromId, ...) for which I suppose I
|  need Id's. Those however don't exist for destructuring patterns, such
|  as those in the following equations:
|  
|   last [x] = x
|   last (_:xs) = last xs
|  
|  So I'm wondering where would be a good place in the pipeline to
|  transform patterns like these into at-patterns, to give them Id's.
|  However, the breakpoint logic only looks at the free variables of the
|  right-hand sides and not transitively, which means that e.g. in the
|  following example neither ':print arg1' nor ':print as' works when the
|  interpreter hits a breakpoint in the top level expression on the RHS:
|  
|   qsort arg1@(a:as) = qsort left ++ [a] ++ qsort right
| where (left, right) = (filter (<=a) as, filter (>a) as)
|  
|  Thus I'd also like to know how to extend the free var logic for
|  Tickish that eventually leads to CgBreakInfo and :print's ability to
|  inspect these bindings at runtime. My goal would be to determine to
|  what extent was a thunk evaluated during function application.
|  
|  Any advice would be greatly appreciated!
|  
|  Regards,
|  Andrew Kvapil
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C329b12ba7bb74a2657d2
|  08d8c1213bcc%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637471695782
|  207814%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C1000sdata=uAi4NmjQLj3QG3B7ton5GeFDy
|  IWJecxtXoXiTIP11tE%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: presentation: Next-gen Haskell Compilation Techniques

2021-01-11 Thread Simon Peyton Jones via ghc-devs
I may not emphasize in the talk, but the goal of the grin compiler project is 
to build a compiler pipeline that allows easy experimentation of different 
compilation techniques. Anything between whole program compilation to per 
module incremental codegen. So the whole program compilation is not really a 
requirement but an option.
Right - but some optimisations absolutely require whole-program analysis, don't 
they?  I'm thinking of flow analyses that support defunctionalisation, when you 
must know all the lambdas that could be bound to `f` in the definition of `map` 
for example.

Such optimisations are powerful, but brittle because they are simply 
inapplicable without whole-program analysis.  Or maybe you can find ways to 
make them more resilient.

Simon

From: ghc-devs  On Behalf Of Csaba Hruska
Sent: 11 January 2021 12:19
To: Sebastian Graf 
Cc: GHC developers 
Subject: Re: presentation: Next-gen Haskell Compilation Techniques

Hi Sebastian,

Thanks for your feedback.
I know that CIB and Perceus have issues with cycles, but these systems are 
still in development so who knows what will be the conclusion.
I may not emphasize in the talk, but the goal of the grin compiler project is 
to build a compiler pipeline that allows easy experimentation of different 
compilation techniques. Anything between whole program compilation to per 
module incremental codegen. So the whole program compilation is not really a 
requirement but an option.

Cheers,
Csaba

On Sun, Jan 10, 2021 at 1:58 PM Sebastian Graf 
mailto:sgraf1...@gmail.com>> wrote:
Hi Csaba,

Thanks for your presentation, that's a nice high-level overview of what you're 
up to.

A few thoughts:

  *   Whole-program optimization sounds great, but also very ambitious, given 
the amount of code GHC generates today. I'd be amazed to see advances in that 
area, though, and your >100-module CFA performance incites hope!
  *   I wonder if going through GRIN results in a more efficient mapping to 
hardware. I recently found that the code GHC generates is dominated by 
administrative traffic from and to the heap [1]. I suspect that you can have 
big wins here if you manage to convey better call stack, heap and alias 
information to LLVM.
  *   The Control Analysis+specialisation approach sounds pretty similar to 
doing Constructor Specialisation [2] for Lambdas (cf. 6.2) if you also inline 
the function for which you specialise afterwards. I sunk many hours into making 
that work reliably, fast and without code bloat in the past, to no avail. 
Frankly, if you can do it in GRIN, I don't see why we couldn't do it in Core. 
But maybe we can learn from the GRIN implementation afterwards and maybe 
rethink SpecConstr. Maybe the key is not to inline the function for which we 
specialise? But then you don't gain that much...
  *   I follow the Counting Immutable Beans [3] stuff quite closely (Sebastian 
is a colleague of mine) and hope that it is applicable to Haskell some day. But 
I think using Perceus, like any purely RC-based memory management scheme, means 
that you can't have cycles in your heap, so no loopy thunks (such as 
constant-space `ones = 1:ones`) and mutability. I think that makes a pretty 
huge difference for many use cases. Sebastian also told me that they have to 
adapt their solutions to the cycle restriction from time to time, so far always 
successfully. But it comes at a cost: You have to adapt the code you want to 
write into a form that works.
I only read the slides, apologies if some of my points were invalidated by 
something you said.

Keep up the good work!
Cheers,
Sebastian

[1] 
https://gitlab.haskell.org/ghc/ghc/-/issues/19113
[2] 
https://www.microsoft.com/en-us/research/wp-content/uploads/2016/07/spec-constr.pdf
[3] 

Title index

2021-01-06 Thread Simon Peyton Jones via ghc-devs
Ben
On GHC's wiki home page we 
have Title Index over in the 
right margin.
I thought the title index was auto-generated.  But it doesn't contain this 
page.
What's up?
Thanks
Simon

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


Nominations close Jan 11th for the Haskell Foundation Board

2021-01-04 Thread Simon Peyton Jones via ghc-devs
Friends
Happy new year!
The closing date for self-nominations for membership of the Board of the 
Haskell Foundation is in just under a week:
Monday January 11th 2021

The Haskell Foundation is a new non-profit organisation that seeks to 
articulate the benefits of functional programming to a broader audience, to 
erase barriers to entry, and to support Haskell as a solidly reliable basis for 
mission-critical applications.

The Board provides the strategic leadership for the Foundation, including its 
goals, governance, finances, and staff.  Membership of the Board is a key 
leadership role, not an honorary appointment.

The Call for Nominations gives 
more details.  Please do consider nominating yourself, or encouraging a 
suitable (but perhaps modest) colleague to do so.  The HF needs a strong Board, 
and that means strong nominations.

Thanks!  Please do forward this message on social media or elsewhere.

Simon Peyton Jones



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


HEAD user manual

2020-11-24 Thread Simon Peyton Jones via ghc-devs
Where can I find the GHC user manual for HEAD these days?
I tried https://ghc.gitlab.haskell.org/ghc/doc/, but that takes me to 8.11.
The user documentation page 
https://gitlab.haskell.org/ghc/ghc/-/wikis/ghc-users-guide#ghc-users-documentation
 has the same link.
Thanks
Simon

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


RE: Correct way of extending the context of the typechecker

2020-11-20 Thread Simon Peyton Jones via ghc-devs
Yiyun

You might need to explain in a bit more detail.

The simplest thing may be this.

* Define, say, (==>) in some ordinary Haskell source module,
  say Liquid.Haskell

* Look up "Liquid.Haskell.==>", to get its Name, via
  GHC.Iface.Env.lookupOrig

* Then you can look up that Name, via GHC.Tc.Utils.Env.tcLookupGlobal
  This should load the interface for Liquid.Haskell, if it isn't
  already loaded.

Simon

|  -Original Message-
|  From: ghc-devs  On Behalf Of Yiyun Liu
|  Sent: 19 November 2020 04:06
|  To: ghc-devs@haskell.org
|  Cc: niki.vazou ; James Parker
|  
|  Subject: Correct way of extending the context of the typechecker
|  
|  Hi ghc-devs,
|  
|  Recently we've been trying to merge the typeclass branch of Liquid
|  Haskell into the develop branch (link to the PR:
|  https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith
|  ub.com%2Fucsd-
|  progsys%2Fliquidhaskell%2Fpull%2F1778data=04%7C01%7Csimonpj%40mic
|  rosoft.com%7C8ffb59d6e2534efa91d108d88c408d6c%7C72f988bf86f141af91ab2d
|  7cd011db47%7C1%7C1%7C637413556756006684%7CUnknown%7CTWFpbGZsb3d8eyJWIj
|  oiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000
|  p;sdata=pl2EqO3TwGC6Br1dQJa5Ej3WDQzN1vngy7HG9A7d9dc%3Dreserved=0)
|  . Since we want GHC to typecheck the refinements, we had to add some
|  predefined logic symbols such as ==> to the global environment of GHC.
|  In our branch, we use execStmt to add those extra symbols to the
|  interactive context. This is no longer possible after LH becomes
|  available as a GHC plugin because the plugin lives in TcRn. It seems
|  that the only way is to directly interact with the typechecker and
|  explicitly add the extra symbols to the context. It is not obvious to
|  me how that can be done without accidentally breaking the invariants
|  of the compiler.
|  
|  I wonder if there are examples or certain files that I can look into
|  to learn how to interact with the typechecker?  Adding the extra
|  symbols is probably not that difficult, but I'd also want to acquire
|  some general knowledge of how the typechecker works to further the
|  integration between LH and GHC so we can remove some of the hacks on
|  our end.
|  
|  Thanks,
|  
|  -Yiyun
|  
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
|  haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devsdata=04%7C01%7Csimonpj%40microsoft.com%7C8ffb59d6e2534efa91d1
|  08d88c408d6c%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C1%7C637413556756
|  006684%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJ
|  BTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000sdata=heNWVmVkbhTgW1n9kdoKgXL0K
|  JICoORJOK97uJlEyH0%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


  1   2   3   4   5   6   7   8   9   10   >