Re: Another hadrian option you might want to use

2021-10-20 Thread Alfredo Di Napoli
Hello Matthew,

Perhaps it would be too niche of a resource, but what about collecting
these options either in a Wiki page in GHC or maybe a short blog post on
your website (if that's not the case already)? I personally use
`--flavour=default+no_profiled_libs+omit_pragmas` all the time with Hadrian
these days once you made me discover that magic incantation, but I am
essentially relying on my bash history or my search capabilities within
this mailing list.

I could imagine how other people might have missed your original email, and
it would be great if we could have this shared somewhere in a more
discoverable way.

Alfredo


On Wed, 20 Oct 2021 at 12:59, Matthew Pickering 
wrote:

> Hi,
>
> A recent change in the testsuite meant that we now running the haddock
> tests with hadrian, this means that haddocks for ghc/base get rebuilt
> if you modify anything in the compiler.
>
> This can decrease interaction speed. To disable the documentation
> tests from running use
>
> --docs=none
>
> This is similar to the flag which already skips performance tests:
>
> --skip-perf
>
> Cheers,
>
> Matt
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: help needed configuring GHC API client

2021-09-23 Thread Alfredo Di Napoli
Hi Norman,

in addition to what Ben already said: is there any particular reason you
wanted to use the stage0 compiler? I have written a small program against
HEAD which used the GHC API fairly recently, and I have simply used the
`stage1` compiler. An excerpt from my little code snippet:

```
-- This is just the output of '_build/stage1/bin/ghc --print-libdir'
myGhcLibDir :: FilePath
myGhcLibDir = "./_build/stage1/lib"

playground :: FilePath -> IO ()
playground fn = do
  res <- runGhc (Just myGhcLibDir) $ do
  ...
```

As you can see that's exactly what you are doing, modulo the fact I was
using the `stage1` (where _build is the default directory for Hadrian
builds).

Hope this helps in some way!

A.




On Fri, 24 Sept 2021 at 03:37, Ben Gamari  wrote:

> Norman Ramsey  writes:
>
> > I'm writing client code against the GHC API in HEAD (version 9.3),
> > using 9.0.1 as my bootstrap compiler.  To make it possible to build
> > this code, I've set up cabal using
> >
> >cabal v1-configure \
> >   --package-db clear \
> >   --package-db $STAGE0/lib/package.conf.d/  # stage0 libraries
> >
> > In my Haskell code I'm invoking `runGhc (Just thelibdir)` where
> >
> >thelibir = "/home/nr/asterius/ghc/_build/stage0/lib"
> >
> > which is my `$STAGE0/lib`.
> >
> > Unfortunuately, when I launch my app, `setSessionDynFlags` panics.
> > The output, along with some diagnostic information about some dflags
> > that seemed relevant, looks like this:
> >
> >   libdir = /home/nr/asterius/ghc/_build/stage0/lib
> >   includePaths = IncludeSpecs {includePathsQuote = [],
> includePathsGlobal = [], includePathsQuoteImplicit = []}
> >   libraryPaths = []
> >   packageDBFlags = []
> >   packageEnv = Nothing
> >   panic! (the 'impossible' happened)
> > GHC version 9.3.20210918:
> >   GHC couldn't find the RTS constants (#define HS_CONSTANTS ")
> in /home/nr/.ghcup/ghc/9.0.1/lib/ghc-9.0.1/include/DerivedConstants.h: the
> RTS package you are trying to use is perhaps for another GHC version(e.g.
> you are using the wrong package database) or the package database is broken.
> >
> >   CallStack (from HasCallStack):
> > error, called at
> _build/stage0/compiler/build/GHC/Platform/Constants.hs:143:20 in
> ghc:GHC.Platform.Constants
> >
> >   Please report this as a GHC bug:
> https://www.haskell.org/ghc/reportabug
> >
> > I'm a little suprprised that my app is hunting for 9.3 information in
> > the tree that belongs to the bootstrap compiler.
> >
> I suspect that the stages are getting mixed up here. Would it be
> possible to post a full reproducer? I'd be happy to investigate further,
> but without being able to reproduce locally it's a bit hard to say
> anything useful. My recollection is that we look for DerivedConstants.h
> in the usual include paths, so there are many ways in which things could
> go wrong.
>
> 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: Can NamedFieldPuns be added to `GHC.LanguageExtensions.Types.Extension`?

2021-07-13 Thread Alfredo Di Napoli
Hello all,

I am happy to see engagement on this issue. I didn't read Ed's and
Richard's replies until now, but I have indeed explored the pattern synonym
solution, which I have materialised in a MR here:

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/6156

As I say in the MR description, the only small downside is the beefy
`COMPLETE` pragma, but we gain the possibility of deprecating the extension
a bit more explicitly, which is nice. Feedback welcome! :)

Thanks,

Alfredo



On Mon, 12 Jul 2021 at 17:08, Edward Kmett  wrote:

> There's always pattern synonyms as an option for cases like this, free of
> backwards compat issues.
>
> -Edward
>
> On Tue, Jul 6, 2021 at 3:00 AM Alfredo Di Napoli <
> alfredo.dinap...@gmail.com> wrote:
>
>>
>> Hello Simon,
>>
>> Yes, renaming and perhaps keeping `RecordPuns` as a pattern synonym to
>> not break backward-compat, if that's feasible to define as we are in
>> `ghc-boot-th` here. Not sure if `PatternSynonyms` and `COMPLETE` would be
>> available there.
>>
>> I am not sure how many libs that depend on the ghc API would break (I
>> haven't grepped on Hackage yet), but that might tip the benefits/troubles
>> ratio towards keeping the status quo.
>>
>> This is not a "problem" I have to solve today, and it might not be
>> considered a problem by others (just an inconsistency I guess): as a
>> colleague of mine pointed out, GHC is not necessarily "lying" here. It's
>> still the same underlying extension, it just happens that there are two
>> names that refer to it.
>>
>> Perhaps I could think about adding to `GhcHint` some kind of mapping
>> which would give to IDEs or third-party libs the correct extension name
>> given an input `LangExt.Extension`, the problem then becomes making sure
>> that we keep this mapping in sync with the information contained in
>> `GHC.Driver.Session`.
>>
>> I will let it simmer.
>>
>> Thanks!
>>
>> A.
>>
>> On Tue, 6 Jul 2021 at 11:19, Simon Peyton Jones 
>> wrote:
>>
>>> 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`:
>>>
>>>
>>>
>>> ...
>>&

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

2021-07-06 Thread Alfredo Di Napoli
Hello Simon,

Yes, renaming and perhaps keeping `RecordPuns` as a pattern synonym to not
break backward-compat, if that's feasible to define as we are in
`ghc-boot-th` here. Not sure if `PatternSynonyms` and `COMPLETE` would be
available there.

I am not sure how many libs that depend on the ghc API would break (I
haven't grepped on Hackage yet), but that might tip the benefits/troubles
ratio towards keeping the status quo.

This is not a "problem" I have to solve today, and it might not be
considered a problem by others (just an inconsistency I guess): as a
colleague of mine pointed out, GHC is not necessarily "lying" here. It's
still the same underlying extension, it just happens that there are two
names that refer to it.

Perhaps I could think about adding to `GhcHint` some kind of mapping which
would give to IDEs or third-party libs the correct extension name given an
input `LangExt.Extension`, the problem then becomes making sure that we
keep this mapping in sync with the information contained in
`GHC.Driver.Session`.

I will let it simmer.

Thanks!

A.

On Tue, 6 Jul 2021 at 11:19, Simon Peyton Jones 
wrote:

> 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


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

2021-07-06 Thread Alfredo Di Napoli
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: instance {Semigroup, Monoid} (Bag a) ?

2021-04-14 Thread Alfredo Di Napoli
Good morning all,

I have now split Richard's commit in two, so that it's explicit in the
commit history that we are adding those instances:

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5509/diffs?commit_id=2cbad0e7ced9de896eb9a1732631786a6adb676a

*Ben*: I have briefly tried to add the Hlint annotations, but it turned out
to be trickier than anticipated. I couldn't find any easy way in HLint to
add a custom hint on a *typeclass instance*, and adding something like this
into `compiler/.hlint.yaml` didn't change anything:

- modules:
  - {name: GHC.Data.Bag, badidents: [mempty], message: "Use emptyBag as
it's more descriptive"}
  - {name: GHC.Data.Bag, badidents: [(<>)], message: "Use unionBags as it's
more descriptive"}

(I suspect that's not what's the badidents syntax is for). I have also
tried to add two `ANN` to the definitions, like this:

{-# ANN (<>) ("HLint: use unionBags as it's more descriptive" :: String) #-}
instance Semigroup (Bag a) where
  (<>) = unionBags

However, this won't work as (<>) is imported qualified and there is no way
in the ANN syntax to specify a fully qualified identifier. However, I
suspect this is not the correct syntax either, as `(<>)` is really the
*typeclass* method, but we want to target the particular instance
implementation.

*Having said that*, Richard carefully defined `(<>) = unionBags` and
`mempty = emptyBag`, so I agree that using `(<>)` and `mempty` would be
more opaque but at the end of the day it should have the asymptotic
complexity than using `unionBags` and `emptyBag` (modulo dictionary
passing, but I hope that won't each our lunch).

A.


On Thu, 15 Apr 2021 at 02:20, Ben Gamari  wrote:

> Richard Eisenberg  writes:
>
> > Hi devs,
> >
> > In the work on simplifying the error-message infrastructure (heavy
> lifting by Alfredo, in cc), I've been tempted (twice!) to add
> >
> >> instance Semigroup (Bag a) where
> >>   (<>) = unionBags
> >>
> >> instance Monoid (Bag a) where
> >>   mempty = emptyBag
> >
> > to GHC.Data.Bag.
> >
> > The downside to writing these is that users might be tempted to write
> > e.g. mempty instead of emptyBag, while the latter gives more
> > information to readers and induces less manual type inference (to a
> > human reader). The upside is that it means Bags work well with
> > Monoid-oriented functions, like foldMap.
> >
> > I favor adding them, and slipped them into !5509 (a big commit with
> > lots of other stuff). Alfredo rightly wondered whether this decision
> > deserved more scrutiny, and so I'm asking the question here.
> >
> My sense is that adding the instances is a Good Thing. However, I do
> think that we probably ought to refrain from using (<>) and mempty where
> more specific functions would do. Adding a lint would be one way to
> accomplish this. Hiding the functions from GhcPrelude would be another.
>
> 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


Error and Warning Messages practical migration guidelines

2021-04-03 Thread Alfredo Di Napoli
*TL;DR If you recently had merge conflicts related to error and
messages in GHC, here I give migration guidelines. Otherwise,
feel free to ignore this email.*


Good morning all,

If you had some work-in-progress branch that was emitting errors or
warnings (either adding new ones or modifying existing
ones), chances are you noticed that now the API and types changed
slightly and you had to deal with the conflicts. What
you noticed was the initial chunk of work for [#18516]. See the [Wiki]
for more info.

Our work is not done yet, but the API changed enough to warrant me
writing this little email to help folks out
with their rebasing (because we are *all* rebasing at least daily,
aren't we? :) ).

First of all, sorry for all the churning! I am trying to stabilise the
external interfaces (i.e the type signatures
of the GHC API functions) so things will become a bit more stable in the future.

In the meantime, I wanted to give you some practical guidelines on how
to migrate your code:

* Rather than "errors" or "warnings", we are trying to shift our
vocabulary to talk about "diagnostics". In
  GHC this distinction is not so "strict", in the sense warnings can
become errors and errors can become warnings
  if deferred. Rather we talk about diagnostics, i.e. facts about the
compiled program, that can be, at the very end,
  classified as errors or warnings based on their `Severity`;

* *If you skip this whole email, read just this:* the key insight is
that there is a clear separation between the *reason*
  this diagnostic was created and the final `Severity`! Example: we
emit a diagnostic because `Opt_WarnMonomorphism` is
  on. That's the raison d'être of this diagnostic. Therefore, we would
create a new message (more on this later) with
  reason `WarningWithFlag Opt_WarnMonomorphism`;

* A `Severity` of a diagnostic is computed using the `DynFlags`,
because that's the only way to correctly classify
  a diagnostic. Back to our little example above, if
`Opt_WarnMonomorphism` was set as fatal (or -Werror enabled), now
  the final `Severity` of the diagnostic above would be `SevError`.
That's why it's important to keep them separate;

* We separated out the logging messages with the diagnostics proper,
this is why we now have a new [MessageClass]
  type which can be used to log all sort of messages (debug ones,
informational etc) *and* diagnostics, which has
  a dedicated type constructor;

* If you want to emit something which is not an error or a warning,
use [putLogMsg].
  Here is an example:
https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Core/Lint.hs#L402
(we could
  argue if the example shouldn't be a diagnostic, but we didn't go
that far in the refactoring yet, this is just
  to give you an idea of the usage);

* The most general function which can be used to produce a diagnostic
is [mkMsgEnvelope], which takes as
  input the `DynFlags` to compute the `Severity` under the hood.

* You can't just pass a random `DynFlags` to `mkMsgEnvelope`, but the
former should be acquired as close as possible
  to the construction/emission site of the diagnostics. This is
because `DynFlags` evolves and are mangled all the time
  inside GHC, and we want to produce the `Severity` using the most
faithful "snapshot" of the state of the world at the
  time the diagnostic was produced.

* Most of the times you don't have to worry about all of this; if you
know for sure a diagnostic is an error and is
  not recoverable, then you can use `mkMsgErrorEnvelope` that doesn't
need the `DynFlags` and always produces a diagnostic
  with `SevError` and `ErrorWithoutFlags`.

* Once #18516 will be completed, this will require a bit less
cognitive overhead. We will have proper types (not SDocs
  or generic `DecoratedMessage`s), and all the working GHC hacker will
have to worry about would be to create a brand new
  Haskell type for the diagnostic, give it a `Diagnostic` instance (or
extend the instance declaration if that's an
  existing type) and then just call whichever high-level API we will
have available.


Hope this helps!


Alfredo


[#18516]: https://gitlab.haskell.org/ghc/ghc/-/issues/18516
[Wiki]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Errors-as-(structured)-values
[MessageClass]:
https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Types/Error.hs#L209
[putLogMsg]: 
https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Utils/Logger.hs#L128
[mkMsgEnvelope]:
https://gitlab.haskell.org/ghc/ghc/-/blob/master/compiler/GHC/Utils/Error.hs#L116
___
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-31 Thread Alfredo Di Napoli
Hello all,

John: right, I am not opposed to what you describe, but at the end of the
day we need to add all these messages to a single IORef (unless we go with
the two IORef idea that Richard is not fond of), and for that we need a
single monomorphic type, which could be, initially, even something like:

type TcRnDsMessage = Either DsMessage TcRnMessage

I guess I'll have to iterate on this until we get something meaningful and
that passes the full testsuite :)

A.



On Wed, 31 Mar 2021 at 16:36, John Ericson 
wrote:

> I might still be tempted to do:
> data DsMessage =
> ...
>   | DsLiftedTcRnMessage !TcRnMessage
>   -- ^ A diagnostic coming straight from the Typecheck-renamer.
>
> data TcRnMessage =
> ...
>   | TcRnLiftedDsMessage !DsMessage
>   -- ^ A diagnostic coming straight from the Desugarer.
>
> tying them together with hs-boot. Yes, that means one can do some silly
> `TcRnLiftedDsMessage . DsLiftedTcRnMessage . TcRnLiftedDsMessage ...`, but
> that could even show up in a render as "while desugaring a splice during
> type checking, while typechecking during desguaring, ..." so arguably the
> information the wrapping isn't purely superfluous.
>
> I think this would pose no practical problem today, while still "soft
> enforcing" the abstraction boundaries we want.
>
> On 3/31/21 3:45 AM, Alfredo Di Napoli wrote:
>
> Follow up:
>
> Argh! I have just seen that I have a bunch of test failures related to my
> MR (which, needless to say, it's still WIP).
>
> For example:
>
> run/T9140.run.stdout.normalised 2021-03-31 09:35:48.0 +0200
> @@ -1,12 +1,4 @@
>
> -:2:5:
> -You can't mix polymorphic and unlifted bindings: a = (# 1 #)
> -Probable fix: add a type signature
> -
> -:3:5:
> -You can't mix polymorphic and unlifted bindings: a = (# 1, 3 #)
> -Probable fix: add a type signature
> -
>
> So it looks like some diagnostic is now not being reported and, surprise
> surprise, this was emitted from the DsM monad.
>
> I have the suspect that indeed Richard was right (like he always is :) )
> -- when we go from a DsM to a TcM monad (See `initDsTc`) for example, I
> think we also need to carry into the new monad all the diagnostics we
> collected so far.
>
> This implies indeed a mutual dependency (as Simon pointed out, heh).
>
>
> So I think my cunning plan of embedding is crumbling -- I suspect we would
> end up with a type `TcRnDsMessage` which captures the dependency.
>
> Sorry for not seeing it sooner!
>
>
>
>
>
>
>
>
> On Wed, 31 Mar 2021 at 08:05, Alfredo Di Napoli <
> alfredo.dinap...@gmail.com> wrote:
>
>> Morning all,
>>
>> *Richard*: sorry! Unfortunately MR !4798 is the cornerstone of this
>> refactoring work but it's also gargantuan. Let's discuss a plan to attack
>> it, but fundamentally there is a critical mass of changes that needs to
>> happen atomically or it wouldn't make much sense, and alas this doesn't
>> play in our favour when it comes to MR size and ease of review. However, to
>> quickly reply to your remak: currently (for the sake of the
>> "minimum-viable-product") I am trying to stabilise the external interfaces,
>> by which I mean giving functions their final type signature while I do
>> what's easiest to make things typecheck. In this phase what I think is the
>> easiest is to wrap the majority of diagnostics into the `xxUnknownxx`
>> constructor, and change them gradually later. A fair warning, though: you
>> say "I would think that a DsMessage would later be wrapped in an
>> envelope." This might be true for Ds messages (didn't actually invest any
>> brain cycles to check that) but in general we have to turn a message into
>> an envelope as soon as we have a chance to do so, because we need to grab
>> the `SrcSpan` and the `DynFlags` *at the point of creation* of the
>> diagnostics. Carrying around a message and make it bubble up at some random
>> point won't be a good plan (even for Ds messages). Having said that, I
>> clearly have very little knowledge about this area of GHC, so feel free to
>> disagree :)
>>
>> *John*: Although it's a bit hard to predict how well this is going to
>> evolve, my current embedding, to refresh everyone's memory, is the
>> following:
>>
>> data DsMessage =
>>
>> DsUnknownMessage !DiagnosticMessage
>>
>>   -- ^ Stop-gap constructor to ease the migration.
>>
>>   | DsLiftedTcRnMessage !TcRnMessage
>>
>>   -- ^ A diagnostic coming straight from the Typecheck-renamer.
>>
>>   -- More

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

2021-03-31 Thread Alfredo Di Napoli
Follow up:

Argh! I have just seen that I have a bunch of test failures related to my
MR (which, needless to say, it's still WIP).

For example:

run/T9140.run.stdout.normalised 2021-03-31 09:35:48.0 +0200
@@ -1,12 +1,4 @@

-:2:5:
-You can't mix polymorphic and unlifted bindings: a = (# 1 #)
-Probable fix: add a type signature
-
-:3:5:
-You can't mix polymorphic and unlifted bindings: a = (# 1, 3 #)
-Probable fix: add a type signature
-

So it looks like some diagnostic is now not being reported and, surprise
surprise, this was emitted from the DsM monad.

I have the suspect that indeed Richard was right (like he always is :) ) --
when we go from a DsM to a TcM monad (See `initDsTc`) for example, I think
we also need to carry into the new monad all the diagnostics we collected
so far.

This implies indeed a mutual dependency (as Simon pointed out, heh).


So I think my cunning plan of embedding is crumbling -- I suspect we would
end up with a type `TcRnDsMessage` which captures the dependency.

Sorry for not seeing it sooner!








On Wed, 31 Mar 2021 at 08:05, Alfredo Di Napoli 
wrote:

> Morning all,
>
> *Richard*: sorry! Unfortunately MR !4798 is the cornerstone of this
> refactoring work but it's also gargantuan. Let's discuss a plan to attack
> it, but fundamentally there is a critical mass of changes that needs to
> happen atomically or it wouldn't make much sense, and alas this doesn't
> play in our favour when it comes to MR size and ease of review. However, to
> quickly reply to your remak: currently (for the sake of the
> "minimum-viable-product") I am trying to stabilise the external interfaces,
> by which I mean giving functions their final type signature while I do
> what's easiest to make things typecheck. In this phase what I think is the
> easiest is to wrap the majority of diagnostics into the `xxUnknownxx`
> constructor, and change them gradually later. A fair warning, though: you
> say "I would think that a DsMessage would later be wrapped in an
> envelope." This might be true for Ds messages (didn't actually invest any
> brain cycles to check that) but in general we have to turn a message into
> an envelope as soon as we have a chance to do so, because we need to grab
> the `SrcSpan` and the `DynFlags` *at the point of creation* of the
> diagnostics. Carrying around a message and make it bubble up at some random
> point won't be a good plan (even for Ds messages). Having said that, I
> clearly have very little knowledge about this area of GHC, so feel free to
> disagree :)
>
> *John*: Although it's a bit hard to predict how well this is going to
> evolve, my current embedding, to refresh everyone's memory, is the
> following:
>
> data DsMessage =
>
> DsUnknownMessage !DiagnosticMessage
>
>   -- ^ Stop-gap constructor to ease the migration.
>
>   | DsLiftedTcRnMessage !TcRnMessage
>
>   -- ^ A diagnostic coming straight from the Typecheck-renamer.
>
>   -- More messages added in the future, of course
>
>
> At first I thought this was the wrong way around, due to Simon's comment,
> but this actually creates pleasant external interfaces. To give you a bunch
> of examples from MR !4798:
>
>
> deSugar :: HscEnv -> ModLocation -> TcGblEnv -> IO (Messages DsMessage,
> Maybe ModGuts)
> deSugarExpr :: HscEnv -> LHsExpr GhcTc -> IO (Messages DsMessage, Maybe
> CoreExpr)
>
> Note something interesting: the second function actually calls
> `runTcInteractive` inside the body, but thanks to the `DsLiftedTcRnMessage`
> we can still expose to the consumer an opaque `DsMessage` , which is what I
> would expect to see from a function called "deSugarExpr". Conversely, I
> would be puzzled to find those functions returning a `TcRnDsMessage`.
>
>
> Having said all of that, I am not advocating this design is "the best". I
> am sure we will iterate on it. I am just reporting that even this baseline
> seems to be decent from an API perspective :)
>
>
> On Wed, 31 Mar 2021 at 05:45, John Ericson 
> wrote:
>
>> Alfredo also replied to this pointing his embedding plan. I also prefer
>> that, because I really wish TH didn't smear together the phases so much.
>> Moreover, I hope with
>>
>>  - GHC proposals https://github.com/ghc-proposals/ghc-proposals/pull/412
>> / https://github.com/ghc-proposals/ghc-proposals/pull/243
>>
>>  - The parallelism work currently be planned in
>> https://gitlab.haskell.org/ghc/ghc/-/wikis/Plan-for-increased-parallelism-and-more-detailed-intermediate-output
>>
>> we might actually have an opportunity/extra motivation to do that.
>> Splices and quotes will still induce

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

2021-03-30 Thread Alfredo Di Napoli
Morning all,

*Richard*: sorry! Unfortunately MR !4798 is the cornerstone of this
refactoring work but it's also gargantuan. Let's discuss a plan to attack
it, but fundamentally there is a critical mass of changes that needs to
happen atomically or it wouldn't make much sense, and alas this doesn't
play in our favour when it comes to MR size and ease of review. However, to
quickly reply to your remak: currently (for the sake of the
"minimum-viable-product") I am trying to stabilise the external interfaces,
by which I mean giving functions their final type signature while I do
what's easiest to make things typecheck. In this phase what I think is the
easiest is to wrap the majority of diagnostics into the `xxUnknownxx`
constructor, and change them gradually later. A fair warning, though: you
say "I would think that a DsMessage would later be wrapped in an envelope."
This might be true for Ds messages (didn't actually invest any brain cycles
to check that) but in general we have to turn a message into an envelope as
soon as we have a chance to do so, because we need to grab the `SrcSpan`
and the `DynFlags` *at the point of creation* of the diagnostics. Carrying
around a message and make it bubble up at some random point won't be a good
plan (even for Ds messages). Having said that, I clearly have very little
knowledge about this area of GHC, so feel free to disagree :)

*John*: Although it's a bit hard to predict how well this is going to
evolve, my current embedding, to refresh everyone's memory, is the
following:

data DsMessage =

DsUnknownMessage !DiagnosticMessage

  -- ^ Stop-gap constructor to ease the migration.

  | DsLiftedTcRnMessage !TcRnMessage

  -- ^ A diagnostic coming straight from the Typecheck-renamer.

  -- More messages added in the future, of course


At first I thought this was the wrong way around, due to Simon's comment,
but this actually creates pleasant external interfaces. To give you a bunch
of examples from MR !4798:


deSugar :: HscEnv -> ModLocation -> TcGblEnv -> IO (Messages DsMessage,
Maybe ModGuts)
deSugarExpr :: HscEnv -> LHsExpr GhcTc -> IO (Messages DsMessage, Maybe
CoreExpr)

Note something interesting: the second function actually calls
`runTcInteractive` inside the body, but thanks to the `DsLiftedTcRnMessage`
we can still expose to the consumer an opaque `DsMessage` , which is what I
would expect to see from a function called "deSugarExpr". Conversely, I
would be puzzled to find those functions returning a `TcRnDsMessage`.


Having said all of that, I am not advocating this design is "the best". I
am sure we will iterate on it. I am just reporting that even this baseline
seems to be decent from an API perspective :)


On Wed, 31 Mar 2021 at 05:45, John Ericson 
wrote:

> Alfredo also replied to this pointing his embedding plan. I also prefer
> that, because I really wish TH didn't smear together the phases so much.
> Moreover, I hope with
>
>  - GHC proposals https://github.com/ghc-proposals/ghc-proposals/pull/412
> / https://github.com/ghc-proposals/ghc-proposals/pull/243
>
>  - The parallelism work currently be planned in
> https://gitlab.haskell.org/ghc/ghc/-/wikis/Plan-for-increased-parallelism-and-more-detailed-intermediate-output
>
> we might actually have an opportunity/extra motivation to do that. Splices
> and quotes will still induce intricate inter-phase dependencies, but I hope
> that could be mediated by the driver rather than just baked into each phase.
>
> (One final step would be the "stuck macros" technique of
> https://www.youtube.com/watch?v=nUvKoG_V_U0 /
> https://github.com/gelisam/klister, where TH splices would be able to
> making "blocking queries" of the the compiler in ways that induce more of
> these fine-grained dependencies.)
>
> Anyways, while we could also do a "RnTsDsError" and split later, I hope
> Alfredo's alternative of embedding won't be too much harder and prepare us
> for these exciting areas of exploration.
>
> John
> On 3/30/21 10:14 AM, Richard Eisenberg wrote:
>
>
>
> On Mar 30, 2021, at 4:57 AM, Alfredo Di Napoli 
> wrote:
>
> I'll explore the idea of adding a second IORef.
>
>
> Renaming/type-checking is already mutually recursive. (The renamer must
> call the type-checker in order to rename -- that is, evaluate -- untyped
> splices. I actually can't recall why the type-checker needs to call the
> renamer.) So we will have a TcRnError. Now we see that the desugarer ends
> up mixed in, too. We could proceed how Alfredo suggests, by adding a second
> IORef. Or we could just make TcRnDsError (maybe renaming that).
>
> What's the disadvantage? Clients will have to potentially know about all
> the different error forms with either

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

2021-03-30 Thread Alfredo Di Napoli
Hello folks,

Richard: as I was in the middle of some other refactoring by the time Simon
replied, you can see a potential refactoring that *doesn't* use the double
IORef, but rather this idea of having a `DsMessage` embed `TcRnMessage`(s)
via a new costructor:

https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4798/diffs#6eaba7424490cb26d74e0dab0f6fd7bc3537dca7

(Just grep for "DsMessage", "DsUnknownMessage", and `DsLiftedTcRnMessage`
to see the call sites).

The end result is not bad, I have to say. Or, at least, it doesn't
strike me as totally horrid :)

A.



On Tue, 30 Mar 2021 at 16:14, Richard Eisenberg  wrote:

>
>
> On Mar 30, 2021, at 4:57 AM, Alfredo Di Napoli 
> wrote:
>
> I'll explore the idea of adding a second IORef.
>
>
> Renaming/type-checking is already mutually recursive. (The renamer must
> call the type-checker in order to rename -- that is, evaluate -- untyped
> splices. I actually can't recall why the type-checker needs to call the
> renamer.) So we will have a TcRnError. Now we see that the desugarer ends
> up mixed in, too. We could proceed how Alfredo suggests, by adding a second
> IORef. Or we could just make TcRnDsError (maybe renaming that).
>
> What's the disadvantage? Clients will have to potentially know about all
> the different error forms with either approach (that is, using my combined
> type or using multiple IORefs). The big advantage to separating is maybe
> module dependencies? But my guess is that the dependencies won't be an
> issue here, due to the fact that these components are already leaning on
> each other. Maybe the advantage is just in having smaller types? Maybe.
>
> I don't have a great sense as to what to do here, but I would want a clear
> reason that e.g. the TcRn monad would have two IORefs, while other monads
> will work with GhcMessage (instead of a whole bunch of IORefs).
>
> Richard
>
___
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 Alfredo Di Napoli
Right, I see, thanks.

This is what I was attempting so far:

data DsMessage =
DsUnknownMessage !DiagnosticMessage
  | DsLiftedTcRnMessage !TcRnMessage
  -- ^ A diagnostic coming straight from the Typecheck-renamer.

and later:

liftTcRnMessages :: MonadIO m => IORef (Messages TcRnMessage) -> m (IORef
(Messages DsMessage))
liftTcRnMessages ref = liftIO $ do
  oldContent <- readIORef ref
  newIORef (DsLiftedTcRnMessage <$> oldContent)

...

mkDsEnvsFromTcGbl :: MonadIO m
  => HscEnv -> IORef (Messages TcRnMessage) -> TcGblEnv
  -> m (DsGblEnv, DsLclEnv)
mkDsEnvsFromTcGbl hsc_env msg_var tcg_env
  = do { cc_st_var   <- liftIO $ newIORef newCostCentreState
   ...
   ; msg_var' <- liftTcRnMessages msg_var
   ; return $ mkDsEnvs unit_env this_mod rdr_env type_env fam_inst_env
   msg_var' cc_st_var complete_matches
   }


While this typechecks, I wonder if that's the right way to think about it
-- from your reply, it seems like the dependency is in the opposite
direction -- we need to store desugaring diagnostics in the TcM due to TH
splicing, not the other way around.

I'll explore the idea of adding a second IORef.

Thanks!


On Tue, 30 Mar 2021 at 10:51, Simon Peyton Jones 
wrote:

> 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&data=04%7C01%7Csimonpj%40microsoft.com%7C49c033aa2865495eb07c08d8f34f70cd%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637526870280012102%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C3000&sdata=ui4JWOp1gl5Yh%2FOYDqcBLXxTm%2FGnQRi0cDshUVEjwmk%3D&reserved=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 wou

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

2021-03-30 Thread Alfredo Di Napoli
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
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: safe to upgrade my Mac?

2021-01-27 Thread Alfredo Di Napoli
Hi Richard,

I am running 10.15.7 and I think I upgraded to Catalina months ago (but I
don't exactly recall when). From my experience, everything works just fine,
at least for my current workflow (clients' projects, GHC development etc).
At work I have successfully used GHC 8.6.5 and 8.10.2 for various projects,
both with Cabal and Stack and didn't experience any major problems.

In terms of performance, I cannot judge. If it got slower, I certainly
didn't notice.

I hope it helps! :)

A.

On Wed, 27 Jan 2021 at 22:29, Merijn Verstraaten 
wrote:

>
> > On 27 Jan 2021, at 21:56, Richard Eisenberg  wrote:
> > I'm currently running MacOS High Sierra, 10.13.6. Things are fine, but
> I'd like to upgrade to get Dark Mode and (hopefully) to speed up Mail.
> (That is, upgrading is nice, but not at all necessary.)
>
> I just (finally) upgraded to Catalina last week and the 8.10.2 bindist
> works just fine (you have to fiddle with xattr after unzipping, there's an
> issue on gitlab that has the right command in there). If you're going to
> Mojave then there's 0 issues. Big Sur I haven't tried yet.
>
> > If I upgrade, will GHC hate me? That is, will GHC 8.10 continue to work?
> Will I continue to be able to compile GHC? Will it be as performant? (A few
> years ago, I had a strange issue on a secondary computer where any binary
> built by GHC was horribly slow; we never got to the bottom of it.)
>
> I didn't notice any performance regressions, but I also haven't paid close
> attention.
>
> - Merijn
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Parser depends on DynFlags, depends on Hooks, depends on TcM, DsM, ...

2020-09-15 Thread Alfredo Di Napoli
> Do you happen to know of DynFlagPlugins, Adam?

Alas the newly release LiquidHaskell plugin relies on the `dynflagsPlugin`
action, so it would be nice if this was not removed:

https://github.com/ucsd-progsys/liquidhaskell/blob/develop/src/Language/Haskell/Liquid/GHC/Plugin.hs#L146

Ignoring the other options, we rely on `Opt_KeepRawTokenStreams` which is
*key* for the correct behaviour of the plugin. If we were not intercepting
the `DynFlags` at this stage, the lexer would drop any block comments from
the parsed sources and we wouldn't have the chance of parsing the LH
annotations contained within.

Now, truth to be told, due to the fact we ended up re-parsing each module
anyway (for unfortunate reasons) we *could* survive without it by tweaking
the `DynFlags` inside the `ModSummary` before we call `parseModule`, but in
an ideal world we wouldn't need this, and we would be using directly the
parsed source that the `parsedResultAction` would give us. Without the
`dynflagsPlugin` I don't think we would be able to do that anymore.




On Mon, 14 Sep 2020 at 23:20, Alp Mestanogullari  wrote:

> My original motivation for !1580 and !1827 (the latter of which ended up
> getting merged) would be equally well supported by an interface with more
> limited scope. My only requirement there was to be able to override the
> meta hook. I therefore would not mind going back to the approach I
> initially took, in !1580, which I preferred back then already. As long as
> we leave a way for plugins to override hooks, my use case will not suffer.
> On 14/09/2020 21:20, Ben Gamari wrote:
>
> Moritz Angermann   
> writes:
>
>
> I believe this to already be broken in HEAD. DynFlags already got quite an
> overhaul/break. I'd rather we drop supporting DynFlagPlugins. And
> offer alternative stable interfaces. Though to be honest, I believe our
> Plugin story is rather poor so far.
>
>
> To fill in a bit of history here, DynFlags plugins were introduced in
> !1827, which arose as an alternative to !1580. The latter proposed a
> much more specialised interface specifically allowing plugins to
> introduce Hooks. Personally, I far prefer the approach taken in !1580. To
> quote my comment on !1580:
>
>
> I agree that overriding DynFlags is excessive and, moreover, it
> entrenches the structure of DynFlags as a semi-stable interface. In my
> opinion the current state of DynFlags is a very uneasy compromise and
> really should be refactored (at very least split up into smaller
> records). While it's true that the Hsc capability given to parser
> plugins allows DynFlags to be modified, I would consider this to be
> very much a backdoor and not a supported use.
>
> Hooks, on the other hand, are intended to be extension points for the
> compiler. Consequently it is quite natural for them to be set by
> plugins.
>
> In light of how quickly DynFlags is now changing, I somewhat regret not
> pushing back more vigorously against the DynFlags-centric approach. I
> tend to agree that we should remove the interface and revert to a more
> limited interface that simply deals in Hooks.
>
> Cheers,
>
> - Ben
>
>
>
> ___
> ghc-devs mailing 
> listghc-devs@haskell.orghttp://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


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

2017-04-18 Thread Alfredo Di Napoli
Hey Ben,

thanks for that. I didn’t realise I opened pretty much the Pandora’s box,
hehe. I have now found (whilst reading Bartosz’s notes) the numerous
tickets & discussions around the library, but what you say in this email
neatly summarise the crux of the problem, as far as I could see. Rather
than saying silly things, I would rather spend a bit of time reading
everything that has been written by folks way smarter than me on the
subject and get back to you folks later ;)

Alfredo

On 18 April 2017 at 14:21, Ben Gamari  wrote:

> Alfredo Di Napoli  writes:
>
> > Hey Simon,
> >
> > thanks for chiming in. I had the same suspect as well, and in fact my
> first
> > temptation was to use dlists to avoid costly concatenation (I guess a
> > Builder shares pretty much the same idea, which is avoid right-appends).
> I
> > eventually bailed out as that Pretty module had some functions like sepX
> or
> > fillNBE (I might be wrong, going by memory only here) which needed to
> > *inspect* the current [Doc] we were carrying around, and thus dlists
> > couldn’t accomplish this in O(1), but forcing it back to a list was
> > necessary. Am I right in thinking that using a Builder here will suffer
> the
> > same malady? Ideally I would like constant time for both appends, left
> > concat & inspection (as in pattern-matching inspection) but I don’t think
> > what I’m asking exists, at least not in its functional declination
> anyway ;)
> >
> > That’s why I was thinking to give Deques (or more generally, Sequences) a
> > go: they don’t have O(1) appends but at least can be inspected in O(1).
> > Question has to be answered whether this will yield improvement or not,
> > which I guess depends upon the ratio of inspection / appending we do in
> the
> > pretty printing. In that case using dlists or builders might be better.
> > Last but not least, although the current implementation doesn’t backtrack
> > anyway, I’m wondering wether switching to a different representation for
> a
> > Doc (namely a huge function composition of Token(s), as described in the
> > paper) could be beneficial as well.
> >
> > Do you guys have any opinions? Yesterday I extracted Pretty.hs from the
> > sourcetree and I’m now planning to produce a criterion benchmark and
> > compare different implementations, althought it’s a bit hard to predict
> the
> > real world usage as I don’t have access to a representative Doc document
> as
> > produced by GHC, so my benchs could be all ill-founded.
> >
> Note that GHC's `Pretty` module is just a slightly modified version of
> the `pretty` package. The differences are fairly minimal (although
> important for performance):
>
>  * It uses FastString in place of String, giving us fast `length` (in
>https://ghc.haskell.org/trac/ghc/ticket/8809#comment:60
>I propose that we extend `pretty` with a typeclass for string types)
>
>  * GHC's variant still has a known stack overflow bug that was fixed
>upstream. Unfortunately, compiler performance regressed when we
>attempted to port upstream's patch (#10735)
>
> Ideally we would fix these and just use the `pretty` library itself.
>
> In addition to these issues, it would be quite helpful if `pretty`
> gained a special-case for the infinite band-width case (which is what we
> use in the code generator). The point here is that we should need to do
> no layout computation in the infinite band case: merely place line
> breaks precisely where the user asks. This should result in a noticeable
> improvement in code generation performance (IIRC Bartosz noted rather
> significant amounts of time spent pretty-printing assembler).
>
> Cheers,
>
> - Ben
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


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

2017-04-18 Thread Alfredo Di Napoli
Hey Bartosz,

thanks for that, looks like I won the jackpot today ;)

Sounds like your notes are an excellent starting point. Will try to get a
better understanding of that module myself, to see if we can reap some perf
win here, but the fact you “have been there before” looks like this is a
promising path to take.

Cheers!

Alfredo

On 18 April 2017 at 13:01, Bartosz Nitka  wrote:

> Hey Alfredo,
>
> Thanks for taking a look at this. I've taken a look at this before and
> collected some notes here: https://github.com/niteria/notes/blob/master/
> PrettyPrintingGHC.md#problems
> Based on my investigations I concluded that there are places where
> pretty-printing Asm and Cmm gets accidentally quadratic.
> If I remember correctly the core of the problem was that even in the
> "fast" mode the pretty printer was computing the lengths of subtrees in
> `reduceDoc`, which in some cases made the operations quadratic.
> I've tried implementing a "just append bytes"-mode without `reduceDoc`,
> but what stopped me was my lack of understanding of different semantics for
> 3 kinds of empty Doc's.
> I think if you took the time to understand it, you could implement it in a
> way that's not quadratic, reaping a substantial performance win.
>
> Cheers,
> Bartosz
>
> 2017-04-18 11:17 GMT+01:00 Alfredo Di Napoli :
>
>> Hey Simon,
>>
>> thanks for chiming in. I had the same suspect as well, and in fact my
>> first temptation was to use dlists to avoid costly concatenation (I guess a
>> Builder shares pretty much the same idea, which is avoid right-appends). I
>> eventually bailed out as that Pretty module had some functions like sepX or
>> fillNBE (I might be wrong, going by memory only here) which needed to
>> *inspect* the current [Doc] we were carrying around, and thus dlists
>> couldn’t accomplish this in O(1), but forcing it back to a list was
>> necessary. Am I right in thinking that using a Builder here will suffer the
>> same malady? Ideally I would like constant time for both appends, left
>> concat & inspection (as in pattern-matching inspection) but I don’t think
>> what I’m asking exists, at least not in its functional declination anyway ;)
>>
>> That’s why I was thinking to give Deques (or more generally, Sequences) a
>> go: they don’t have O(1) appends but at least can be inspected in O(1).
>> Question has to be answered whether this will yield improvement or not,
>> which I guess depends upon the ratio of inspection / appending we do in the
>> pretty printing. In that case using dlists or builders might be better.
>> Last but not least, although the current implementation doesn’t backtrack
>> anyway, I’m wondering wether switching to a different representation for a
>> Doc (namely a huge function composition of Token(s), as described in the
>> paper) could be beneficial as well.
>>
>> Do you guys have any opinions? Yesterday I extracted Pretty.hs from the
>> sourcetree and I’m now planning to produce a criterion benchmark and
>> compare different implementations, althought it’s a bit hard to predict the
>> real world usage as I don’t have access to a representative Doc document as
>> produced by GHC, so my benchs could be all ill-founded.
>>
>> Alfredo
>>
>> On 18 April 2017 at 12:01, Simon Marlow  wrote:
>>
>>> Pretty-printing the asm is a likely contender for optimisation, however
>>> the problem is not the pretty-printing per se.  We don't actually use any
>>> of the backtracking stuff when printing asm, since there's no point nicely
>>> indenting things or wrapping lines.  The overhead is probably all in the
>>> layer of data structure that we generate in Pretty before it gets dumped
>>> into raw bytes.  Using a ByteString Builder instead might yield some
>>> improvement.
>>>
>>> Cheers
>>> Simon
>>>
>>> On 17 April 2017 at 18:44, Alfredo Di Napoli >> > wrote:
>>>
>>>> Dear all,
>>>>
>>>> after sprinkling (ehm, littering) GHC source code with cost centres, I
>>>> was not surprised to see that roughly 20% of the compilation time (as in
>>>> .prof) was spent in the core gen/simplification process (10% of the total
>>>> time) and on the asm code gen (another 10%).
>>>>
>>>> I have almost immediately abandoned the idea of try optimising some
>>>> modules in simplCore (considering my 0-knowledge of GHC internals anyway..)
>>>> but I have been dwelling on the following: Outputable.hs and Pretty.hs
>>>> seems to be have been implemented making 

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

2017-04-18 Thread Alfredo Di Napoli
Hey Simon,

thanks for chiming in. I had the same suspect as well, and in fact my first
temptation was to use dlists to avoid costly concatenation (I guess a
Builder shares pretty much the same idea, which is avoid right-appends). I
eventually bailed out as that Pretty module had some functions like sepX or
fillNBE (I might be wrong, going by memory only here) which needed to
*inspect* the current [Doc] we were carrying around, and thus dlists
couldn’t accomplish this in O(1), but forcing it back to a list was
necessary. Am I right in thinking that using a Builder here will suffer the
same malady? Ideally I would like constant time for both appends, left
concat & inspection (as in pattern-matching inspection) but I don’t think
what I’m asking exists, at least not in its functional declination anyway ;)

That’s why I was thinking to give Deques (or more generally, Sequences) a
go: they don’t have O(1) appends but at least can be inspected in O(1).
Question has to be answered whether this will yield improvement or not,
which I guess depends upon the ratio of inspection / appending we do in the
pretty printing. In that case using dlists or builders might be better.
Last but not least, although the current implementation doesn’t backtrack
anyway, I’m wondering wether switching to a different representation for a
Doc (namely a huge function composition of Token(s), as described in the
paper) could be beneficial as well.

Do you guys have any opinions? Yesterday I extracted Pretty.hs from the
sourcetree and I’m now planning to produce a criterion benchmark and
compare different implementations, althought it’s a bit hard to predict the
real world usage as I don’t have access to a representative Doc document as
produced by GHC, so my benchs could be all ill-founded.

Alfredo

On 18 April 2017 at 12:01, Simon Marlow  wrote:

> Pretty-printing the asm is a likely contender for optimisation, however
> the problem is not the pretty-printing per se.  We don't actually use any
> of the backtracking stuff when printing asm, since there's no point nicely
> indenting things or wrapping lines.  The overhead is probably all in the
> layer of data structure that we generate in Pretty before it gets dumped
> into raw bytes.  Using a ByteString Builder instead might yield some
> improvement.
>
> Cheers
> Simon
>
> On 17 April 2017 at 18:44, Alfredo Di Napoli 
> wrote:
>
>> Dear all,
>>
>> after sprinkling (ehm, littering) GHC source code with cost centres, I
>> was not surprised to see that roughly 20% of the compilation time (as in
>> .prof) was spent in the core gen/simplification process (10% of the total
>> time) and on the asm code gen (another 10%).
>>
>> I have almost immediately abandoned the idea of try optimising some
>> modules in simplCore (considering my 0-knowledge of GHC internals anyway..)
>> but I have been dwelling on the following: Outputable.hs and Pretty.hs
>> seems to be have been implemented making deliberate use of lists and
>> concatenations between them, which left me wondering if there was room for
>> optimisation there. I have found this interesting paper on the topic:
>>
>> https://www.cs.kent.ac.uk/pubs/2005/2062/content.pdf
>>
>> Now, it’s totally possible that this has been already tried (with no
>> success) but judging from the original copyright of Pretty.hs (dated 2001),
>> it seems it was written prior to the work of Olaf Chitil (the author of the
>> paper).
>>
>> TL;DR I was thinking (even just as a fun exercise to learn more about GHC
>> internals) to leverage the ideas of that paper and switch to a different
>> implementation for `Doc` coupled with the use of lazy dequeues, which
>> *might* increase the performances of the codegen and thus of the compiler
>> overall. Am I fighting a strawman (or flogging a dead horse, pick your
>> rethorical figure :D ) or is there even a tiny chance of this being
>> actually useful?
>>
>> Have a nice evening,
>>
>> Alfredo
>>
>> On 11 April 2017 at 00:47, Ben Gamari  wrote:
>>
>>> Alfredo Di Napoli  writes:
>>>
>>> > Hey Ben,
>>> >
>>> Hi Alfredo,
>>>
>>> Sorry for the late response! The email queue from the weekend was a bit
>>> longer than I would like.
>>>
>>> > as promised I’m back to you with something more articulated and
>>> hopefully
>>> > meaningful. I do hear you perfectly — probably trying to dive
>>> head-first
>>> > into this without at least a rough understanding of the performance
>>> > hotspots or the GHC overall architecture is going to do me more harm
>>> than
>>> > good (I get the overall picture and I

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

2017-04-17 Thread Alfredo Di Napoli
Dear all,

after sprinkling (ehm, littering) GHC source code with cost centres, I was
not surprised to see that roughly 20% of the compilation time (as in .prof)
was spent in the core gen/simplification process (10% of the total time)
and on the asm code gen (another 10%).

I have almost immediately abandoned the idea of try optimising some modules
in simplCore (considering my 0-knowledge of GHC internals anyway..) but I
have been dwelling on the following: Outputable.hs and Pretty.hs seems to
be have been implemented making deliberate use of lists and concatenations
between them, which left me wondering if there was room for optimisation
there. I have found this interesting paper on the topic:

https://www.cs.kent.ac.uk/pubs/2005/2062/content.pdf

Now, it’s totally possible that this has been already tried (with no
success) but judging from the original copyright of Pretty.hs (dated 2001),
it seems it was written prior to the work of Olaf Chitil (the author of the
paper).

TL;DR I was thinking (even just as a fun exercise to learn more about GHC
internals) to leverage the ideas of that paper and switch to a different
implementation for `Doc` coupled with the use of lazy dequeues, which
*might* increase the performances of the codegen and thus of the compiler
overall. Am I fighting a strawman (or flogging a dead horse, pick your
rethorical figure :D ) or is there even a tiny chance of this being
actually useful?

Have a nice evening,

Alfredo

On 11 April 2017 at 00:47, Ben Gamari  wrote:

> Alfredo Di Napoli  writes:
>
> > Hey Ben,
> >
> Hi Alfredo,
>
> Sorry for the late response! The email queue from the weekend was a bit
> longer than I would like.
>
> > as promised I’m back to you with something more articulated and hopefully
> > meaningful. I do hear you perfectly — probably trying to dive head-first
> > into this without at least a rough understanding of the performance
> > hotspots or the GHC overall architecture is going to do me more harm than
> > good (I get the overall picture and I’m aware of the different stages of
> > the GHC compilation pipeline, but it’s far from saying I’m proficient
> with
> > the architecture as whole). I have also read a couple of years ago the
> GHC
> > chapter on the “Architeture of Open Source Applications” book, but I
> don’t
> > know how much that is still relevant. If it is, I guess I should refresh
> my
> > memory.
> >
> It sounds like you have done a good amount of reading. That's great.
> Perhaps skimming the AOSA chapter again wouldn't hurt, but otherwise
> it's likely worthwhile diving in.
>
> > I’m currently trying to move on 2 fronts — please advice if I’m a fool
> > flogging a dead horse or if I have any hope of getting anything done ;)
> >
> > 1. I’m trying to treat indeed the compiler as a black block (as you
> > adviced) trying to build a sufficiently large program where GHC is not
> “as
> > fast as I would like” (I know that’s a very lame definition of “slow”,
> > hehe). In particular, I have built the stage2 compiler with the “prof”
> > flavour as you suggested, and I have chosen 2 examples as a reference
> > “benchmark” for performance; DynFlags.hs (which seems to have been
> > mentioned multiple times as a GHC perf killer) and the highlighting-kate
> > package as posted here: https://ghc.haskell.org/trac/ghc/ticket/9221 .
>
> Indeed, #9221 would be a very interesting ticket to look at. The
> highlighting-kate package is interesting in the context of that ticket
> as it has a very large amount of parallelism available.
>
> If you do want to look at #9221, note that the cost centre profiler may
> not provide the whole story. In particular, it has been speculated that
> the scaling issues may be due to either,
>
>  * threads hitting a blackhole, resulting in blocking
>
>  * the usual scaling limitations of GHC's stop-the-world GC
>
> The eventlog may be quite useful for characterising these.
>
> > The idea would be to compile those with -v +RTS -p -hc -RTS enabled,
> > look at the output from the .prof file AND the `-v` flag, find any
> > hotspot, try to change something, recompile, observe diff, rinse and
> > repeat. Do you think I have any hope of making progress this way? In
> > particular, I think compiling DynFlags.hs is a bit of a dead-end; I
> > whipped up this buggy script which
> > escalated into a Behemoth which is compiling pretty much half of the
> > compiler once again :D
> >
> > ```
> > #!/usr/bin/env bash
> >
> > ../ghc/inplace/bin/ghc-stage2 --make -j8 -v +RTS -A256M -qb0 -p -h \
> > -RTS -DSTAGE=2 -I../ghc/includes -I../ghc/compiler
> -I../ghc/compiler/stage2
> > \
> > -I../ghc/c

Re: ghc-stage2 —interactive segfaults on Mac OS X 10.11.6 (build flavour = prof)

2017-04-14 Thread Alfredo Di Napoli
Ok, I had success by removing “-debug” in favour of “-DDEBUG”. After
compiling GHC I fired GDB and this is the output:

Starting program:
/Users/adinapoli/programming/haskell/ghc/inplace/lib/bin/ghc-stage2
-B/Users/adinapoli/programming/haskell/ghc/inplace/lib --interactive
GHCi, version 8.3.20170413: http://www.haskell.org/ghc/  :? for help
[New Thread 0x120f of process 19786]
[New Thread 0x1403 of process 19786]
[New Thread 0x1503 of process 19786]
[New Thread 0x1603 of process 19786]

Thread 1 received signal SIGSEGV, Segmentation fault.
0x000104cdd81a in ocInit_MachO () at rts/linker/MachO.c:141
141 if(NULL != oc->info->nlist) {

Maybe it does ring a bell to any of you. In case not, I’m happy to continue
digging.

A.

On 14 April 2017 at 21:19, Alfredo Di Napoli 
wrote:

> Hey Ben,
>
> yes, it’s consistently reproducible. I have tried compiling GHC from
> scratch by adding `-dcore-lint` and `-debug` to GhcStage2HcOpts in my mk/
> build.mk, but eventually the build process failed with:
>
> ld: library not found for -lHSrts_thr_debug_p
>
> Any idea what am I doing wrong? Next I’m going to try enabling `-DDEBUG`
> only as described here:
>
> https://ghc.haskell.org/trac/ghc/wiki/Debugging/Compiler
>
> To see if I get any further.
>
> Thanks!
>
> A.
>
>
> On 13 April 2017 at 19:01, Ben Gamari  wrote:
>
>> Alfredo Di Napoli  writes:
>>
>> > Hey all,
>> >
>> > I’m trying to compile GHC HEAD (cloning from master) with the `prof`
>> build
>> > flavour on a Mac OS X 10.11.6 machine and I have noticed that, despite
>> > ghc-stage2 works as expected, when invoked with —interactive it starts
>> > before crashing with a segmentation fault:
>> >
>> > ```
>> > ☁  compiler [master] ⚡ ../inplace/bin/ghc-stage2 --interactive
>> > GHCi, version 8.3.20170413: http://www.haskell.org/ghc/  :? for help
>> > [1]79176 segmentation fault  ../inplace/bin/ghc-stage2 --interactive
>> > ```
>> >
>> > Did it happen to somebody else or it’s just me? Shall I try throwing
>> gdb at
>> > it to try and see what’s going on?
>>
>> Hmm, interesting. I've not seen crashes like this locally nor in CI. It
>> would be great if you could try to get some insight. Is this crash
>> perfectly reproducible?
>>
>> It may be worth adding -dcore-lint to GhcStage2HcOpts to ensure the code
>> we are producing is sane.
>>
>> Cheers,
>>
>> - Ben
>>
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


ghc-stage2 —interactive segfaults on Mac OS X 10.11.6 (build flavour = prof)

2017-04-13 Thread Alfredo Di Napoli
Hey all,

I’m trying to compile GHC HEAD (cloning from master) with the `prof` build
flavour on a Mac OS X 10.11.6 machine and I have noticed that, despite
ghc-stage2 works as expected, when invoked with —interactive it starts
before crashing with a segmentation fault:

```
☁  compiler [master] ⚡ ../inplace/bin/ghc-stage2 --interactive
GHCi, version 8.3.20170413: http://www.haskell.org/ghc/  :? for help
[1]79176 segmentation fault  ../inplace/bin/ghc-stage2 --interactive
```

Did it happen to somebody else or it’s just me? Shall I try throwing gdb at
it to try and see what’s going on?

Thanks,

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


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

2017-04-10 Thread Alfredo Di Napoli
Hey all,

thanks a ton for the invaluable pointers. I’m now in the
“I-dunno-what-I-am-doing” mode banging SCC annotations like there is no
tomorrow, trying to spot any chance for some low-hanging-fruit algorithmic
improvement (like using a sequence instead of a list, etc), and will come
back to your suggestions as I will face the inevitable dead-end wall :D

Alfredo

On 10 April 2017 at 01:54, Niklas Hambüchen  wrote:

> I have some suggestions for low hanging fruits in this effort.
>
> 1. Make ghc print more statistics on what it spending time on
>
> When I did the linking investigation recently
> (https://www.reddit.com/r/haskell/comments/63y43y/liked_
> linking_3x_faster_with_gold_link_10x_faster/)
> I noticed (with strace) that there are lots of interesting syscalls
> being made that you might not expect. For example, each time TH is used,
> shared libraries are loaded, and to determine the shared library paths,
> ghc shells out to `gcc --print-file-name`. Each such invocation takes 20
> ms on my system, and I have 1000 invocations in my build. That's 20
> seconds (out of 2 minutes build time) just asking gcc for paths.
>
> I recommend that for every call to an external GHC measures how long
> that call took, so that it can be asked to print a summary when it's done.
>
> That might give us lots of interesting things to optimize. For example,
> This would have made the long linker times totally obvious.
>
> At the end, I would love to know for each compilation (both one-shot as
> used in ghc's build system, and `ghc --make`):
>
> * What programs did it invoke and how long did they take
> * What files did it read and how long did that take
> * How long did it take to read all the `.hi` files in `ghc --make`
> * High level time summary (parsing, typechecking, codegen, .hi files, etc)
>
> That way we'll know at least what is slow, and don't have to resort to
> strace every time in order to obtain this basic answer.
>
> 2. Investigate if idiotic syscalls are being done and how much
>
> There's this concept I call "idiotic syscalls", which are syscalls of
> which you know from before that they won't contribute anything
> productive. For example, if you give a linker N many `-L` flags (library
> dirs) and M many `-l` flags (library names to link), it will try to
> `stat()` or `open()` N*M many files, out of which most are total
> rubbish, because we typically know what library is in what dir.
> Example: You pass `-L/usr/lib/opencv -L/usr/lib/imagemagick
> -L/usr/lib/blas -lopencv -limagemagick -lblas`. Then you you will get
> things like `open("/usr/lib/opencv/libimagemagick.so") = ENOENT` which
> makes no sense and obviously that file doesn't exist. This is a problem
> with the general "search path" concept; same happens for running
> executables searching through $PATH. Yes, nonexistent file opens fail
> fast, but in my typical ghc invocation I get millions of them (and we
> should at least measure how much time is wasted on them), and they
> clutter the strace output and make the real problems harder to investigate.
> We should check if we can create ways to give pass those files that do
> exist.
>
> 3. Add pure TemplateHaskell
>
> It is well known that TH is a problem for incremental compilation
> because it can have side effects and we must therefore be more
> conservative about when to recompile; when you see a `[TH]` in your `ghc
> --make` output, it's likely that time again.
>
> I believe this could be avoided by adding a variant of TH that forbids
> the use of the `runIO` function, and can thus not have side effects.
>
> Most TH does not need side effects, for example any form of code
> generation based on other data types (lenses, instances for whatever).
> If that was made "pure TH", we would not have to recompile when inputs
> to our TH functions change.
>
> Potentially this could even be determined automatically instead of
> adding a new variant of TH like was done for typed TH `$$()`, simply by
> inspecting what's in the TH and if we can decide there's no `runIO` in
> there, mark it as clean, otherwise as tainted.
>
> 4. Build ghc with `ghc --make` if possible
>
> This one might be controversial or impossible (others can likely tell
> us). Most Haskell code is built with `ghc --make`, not with the one-shot
> compilation system + make or Hadrian as as done in GHC's build system.
> Weirdly, often `ghc --make` scales much worse and has much worse
> incremental recompilation times than the one-shot mode, which doesn't
> make sense given that it has no process creation overhead, can do much
> better caching etc. I believe that if ghc or large parts of it (e.g.
> stage2) itself was built with `--make`, we would magically see --make
> become very good, simply we make the right people (GHC devs) suffer
> through it daily :D. I expect from this the solution of the `-j`
> slowness, GHC overhead reduction, faster interface file loads and so on.
>
> These are some ideas.
>
> Niklas
>
___

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

2017-04-09 Thread Alfredo Di Napoli
Hey Ben,

as promised I’m back to you with something more articulated and hopefully
meaningful. I do hear you perfectly — probably trying to dive head-first
into this without at least a rough understanding of the performance
hotspots or the GHC overall architecture is going to do me more harm than
good (I get the overall picture and I’m aware of the different stages of
the GHC compilation pipeline, but it’s far from saying I’m proficient with
the architecture as whole). I have also read a couple of years ago the GHC
chapter on the “Architeture of Open Source Applications” book, but I don’t
know how much that is still relevant. If it is, I guess I should refresh my
memory.

I’m currently trying to move on 2 fronts — please advice if I’m a fool
flogging a dead horse or if I have any hope of getting anything done ;)

1. I’m trying to treat indeed the compiler as a black block (as you
adviced) trying to build a sufficiently large program where GHC is not “as
fast as I would like” (I know that’s a very lame definition of “slow”,
hehe). In particular, I have built the stage2 compiler with the “prof”
flavour as you suggested, and I have chosen 2 examples as a reference
“benchmark” for performance; DynFlags.hs (which seems to have been
mentioned multiple times as a GHC perf killer) and the highlighting-kate
package as posted here: https://ghc.haskell.org/trac/ghc/ticket/9221 . The
idea would be to compile those with -v +RTS -p -hc -RTS enabled, look at
the output from the .prof file AND the `-v` flag, find any hotspot, try to
change something, recompile, observe diff, rinse and repeat. Do you think I
have any hope of making progress this way? In particular, I think compiling
DynFlags.hs is a bit of a dead-end; I whipped up this buggy script which
escalated into a Behemoth which is compiling pretty much half of the
compiler once again :D

```
#!/usr/bin/env bash

../ghc/inplace/bin/ghc-stage2 --make -j8 -v +RTS -A256M -qb0 -p -h \
-RTS -DSTAGE=2 -I../ghc/includes -I../ghc/compiler -I../ghc/compiler/stage2
\
-I../ghc/compiler/stage2/build \
-i../ghc/compiler/utils:../ghc/compiler/types:../ghc/compiler/typecheck:../ghc/compiler/basicTypes
\
-i../ghc/compiler/main:../ghc/compiler/profiling:../ghc/compiler/coreSyn:../ghc/compiler/iface:../ghc/compiler/prelude
\
-i../ghc/compiler/stage2/build:../ghc/compiler/simplStg:../ghc/compiler/cmm:../ghc/compiler/parser:../ghc/compiler/hsSyn
\
-i../ghc/compiler/ghci:../ghc/compiler/deSugar:../ghc/compiler/simplCore:../ghc/compile/specialise
\
-fforce-recomp -c $@
```

I’m running it with `./dynflags.sh ../ghc/compiler/main/DynFlags.hs` but
it’s taking a lot to compile (20+ mins on my 2014 mac Pro) because it’s
pulling in half of the compiler anyway :D I tried to reuse the .hi files
from my stage2 compilation but I failed (GHC was complaining about
interface file mismatch). Short story short, I don’t think it will be a
very agile way to proceed. Am I right? Do you have any recommendation in
such sense? Do I have any hope to compile DynFlags.hs in a way which would
make this perf investigation feasible?

The second example (the highlighting-kate package) seems much more
promising. It takes maybe 1-2 mins on my machine, which is enough to take a
look at the perf output. Do you think I should follow this second lead? In
principle any 50+ modules package I think would do (better if with a lot of
TH ;) ) but this seems like a low-entry barrier start.

2. The second path I’m exploring is simply to take a less holistic approach
and try to dive in into a performance ticket like the ones listed here:
https://www.reddit.com/r/haskell/comments/45q90s/is_anything_being_done_to_remedy_the_soul/czzq6an/
Maybe some are very specific, but it seems like fixing small things and
move forward could help giving me understanding of different sub-parts of
GHC, which seems less intimidating than the black-box approach.

In conclusion, what do you think is the best approach, 1 or 2, both or
none? ;)

Thank you!

Alfredo

On 7 April 2017 at 18:30, Alfredo Di Napoli 
wrote:

> Hey Ben,
>
> thanks for the quite exhaustive reply! I’m on the go right now, but I
> promise to get back to you with a meaningful reply later this weekend ;)
>
> Alfredo
>
> On 7 April 2017 at 18:22, Ben Gamari  wrote:
>
>> Alfredo Di Napoli  writes:
>>
>> > Hey folks,
>> >
>> Hi Alfredo!
>>
>> First, thanks for writing. More eyes looking at GHC's compiler
>> performance is badly needed.
>>
>> > maybe I’m setting up for something too ambitious for me, but I would
>> like
>> > to take an active stance to the overlasting “GHC compilation times are
>> > terrible” matter, instead of simply stare at the screen with despair
>> > whenever GHC compiles a sufficiently large Haskell program ;)
>> >
>> > To make this even more interesting, I have never contributed to GHC
>> either!
&

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

2017-04-07 Thread Alfredo Di Napoli
Hey Ben,

thanks for the quite exhaustive reply! I’m on the go right now, but I
promise to get back to you with a meaningful reply later this weekend ;)

Alfredo

On 7 April 2017 at 18:22, Ben Gamari  wrote:

> Alfredo Di Napoli  writes:
>
> > Hey folks,
> >
> Hi Alfredo!
>
> First, thanks for writing. More eyes looking at GHC's compiler
> performance is badly needed.
>
> > maybe I’m setting up for something too ambitious for me, but I would like
> > to take an active stance to the overlasting “GHC compilation times are
> > terrible” matter, instead of simply stare at the screen with despair
> > whenever GHC compiles a sufficiently large Haskell program ;)
> >
> > To make this even more interesting, I have never contributed to GHC
> either!
> > The max I have pushed myself into was 2 years ago when I successfully
> built
> > GHC head from source and tried to fix an Haddock “easy” ticket I don’t
> even
> > recall (full disclosure, eventually I didn’t :D ).
> >
> > Specifically, I would love community recommendations & guidance about:
> >
> > 1. Is this simply too daunting for somebody like me? Maybe is better to
> > first start contributing more regularly, take confidence with the code
> base
> > AND then move forward?
> >
> As with any software project, it is possible to treat the compiler as a
> black box, throw a profiler at it and see what hotspots show up. This
> gives you a place to focus your effort, allowing you to learn a small
> area and broaden your knowledge as necessary.
>
> However, I think it's fair to say that you will be significantly more
> productive if you first develop a basic understanding of the compilation
> pipeline. I'd recommend having a look at the GHC Commentary [1] for a
> start.
>
> I think it also helps to have a rough idea of what "slow" means to you.
> I find it is quite helpful if you have a particular program which you
> feel compiles more slowly than you would like (especially if it even
> compiles slowly with -O0, since then much less of the compiler is
> involved in compilation). Another approach is to look for programs whose
> compilation time has regressed over the course of GHC releases. It is
> not hard to find these examples and it is often possible to bisect your
> way back to the regressing commit.
>
> Also, note that I have collected some notes pertaining to compiler
> performance on the Wiki [2]. Here you will find a number of tickets of
> interest (as well a some rough themes which I've noticed), some nofib
> results which might guide your efforts, as well as a list of some
> fixes which have been committed in the past.
>
> [1] https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler
> [2] https://ghc.haskell.org/trac/ghc/wiki/Performance/Compiler
>
> > 2. Are compilation times largely dependant from the target platform (I’m
> on
> > Darwin) or there is something which can be done “globally” so that the
> > benefits can be experienced by everybody?
> >
> There are some external considerations (e.g. the platform's compiler and
> linking toolchain) which contribute to GHC's runtime. For instance, it
> is known that the BFD ld linker implementation that many Linux
> distributions use by default is a great deal slower than it could be.
> This particular issue has come up recently and I'm currently working on
> allowing us to use the more performant gold linker when available.
>
> However, I think it's fair to say that for most programs GHC's runtime
> is largely independent of platform. I would invite you to try compiling
> a package which you consider GHC to compile "slowly" with GHC's -v flag
> (and GHC 8.0.1 or newer). This will give you a rough breakdown of where
> time is spent. For many packages you will find that the simplifier
> and/or typechecker dominate, followed (often distantly) by native code
> generation. Of these steps native code generation is the only one with a
> strong platform dependence.
>
> > 3. Is there any recommended workflow to profile GHC compilation times? Is
> > there any build flavour one should prefer when doing so? (Maybe the full,
> > slowest one?)
> >
> There are a few options here:
>
>  * As of GHC 8.0 the compiler will output timing and allocation
>information for its various stages if run with -v. This can be
>extremely helpful to get a high-level picture of where the compiler
>is spending its time while compiling your program. This is almost
>always the right place to start.
>
>  * As with any Haskell program, the cost centre profiler can be used to
>characterize the memory and C

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

2017-04-07 Thread Alfredo Di Napoli
Hey folks,

maybe I’m setting up for something too ambitious for me, but I would like
to take an active stance to the overlasting “GHC compilation times are
terrible” matter, instead of simply stare at the screen with despair
whenever GHC compiles a sufficiently large Haskell program ;)

To make this even more interesting, I have never contributed to GHC either!
The max I have pushed myself into was 2 years ago when I successfully built
GHC head from source and tried to fix an Haddock “easy” ticket I don’t even
recall (full disclosure, eventually I didn’t :D ).

Specifically, I would love community recommendations & guidance about:

1. Is this simply too daunting for somebody like me? Maybe is better to
first start contributing more regularly, take confidence with the code base
AND then move forward?

2. Are compilation times largely dependant from the target platform (I’m on
Darwin) or there is
something which can be done “globally” so that the benefits can be
experienced by everybody?

3. Is there any recommended workflow to profile GHC compilation times? Is
there any build flavour one should prefer when doing so? (Maybe the full,
slowest one?)

Thanks in advance for taking the time reading this mail, and have a nice
weekend!

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


Re: ANNOUNCE: GHC version 7.8.4

2014-12-29 Thread Alfredo Di Napoli
Hi Carter,

I finally had the chance to test this on my personal laptop, where I was
pretty much free on which version of Cabal/haddock to use.
Installing a fresh haddock, and using Cabal-1.20.0.3 (but I suspect it
doesn’t matter), “cabal haddock” worked just fine on one of my
libraries.

A.

On Wednesday, 24 December 2014, Carter Schonwald 
wrote:
> or worse case, just cabal install haddock and that will work fine
> On Wed, Dec 24, 2014 at 12:56 PM, Carter Schonwald <
carter.schonw...@gmail.com> wrote:
>
> try rm ~/.cabal/bin/haddock
> and then type which haddock and you should be getting the
/usr/local/bin/haddock or whatever, then stuff should work fine
> On Wed, Dec 24, 2014 at 11:40 AM, Alfredo Di Napoli <
alfredo.dinap...@gmail.com> wrote:
>
> The installation succeedeed and GHC is working correctly.
> But yes, "cabal haddock" seems to have some difficulty in the new
version, but I can't judge if it's my sandboxed environment (we use "hub"
at work) or the failure you mentioned.
>
> Calling "haddock" alone works (using the previously installed on my
system), "cabal haddock" does not:
>
> ☁  mandrill [master] ⚡ haddock src/Network/API/Mandrill.hs
> Haddock coverage:
> Warning: main:Network.API.Mandrill: Could not find documentation for
exported module: M
> Warning: Couldn't find .haddock for export Control.Monad.IO.Class.liftIO
>  88% (  7 /  8) in 'Network.API.Mandrill'
> Warning: Network.API.Mandrill: could not find link destinations for:
>Control.Monad.IO.Class.MonadIO
Network.API.Mandrill.Types.MandrillMessage
Network.API.Mandrill.Trans.MandrillT
Network.API.Mandrill.Types.MandrillResponse
Network.API.Mandrill.Messages.Types.MessagesResponse
Text.Email.Parser.EmailAddress Data.Text.Internal.Text Text.Blaze.Html.Html
GHC.Types.IO
>
> ☁  mandrill [master] ⚡ cabal haddock
> cabal-1.20.0.0: You need to re-run the 'configure' command. The version of
> Cabal being used has changed (was Cabal-1.18.1.5, now Cabal-1.20.0.0).
> cabal haddock: /usr/hs/tools/cabal-1.20.0.0 failure (return code=1)
>
> On Wednesday, 24 December 2014, Carter Schonwald <
carter.schonw...@gmail.com> wrote:
>> sure, please verify first.  (also make sure haddock etc works for you, i
had to remove a haddock binary from ~/.cabal/bin before haddocks were
building correctly for me)
>> On Wed, Dec 24, 2014 at 10:52 AM, Alfredo Di Napoli <
alfredo.dinap...@gmail.com> wrote:
>>
>> Thanks Carter!
>>
>> I have just asked basically about it on Reddit, in the announce thread.
>> I'll give it a spin, and if it works I will share the link (if you are
ok with that!) on the
>> same Reddit post.
>>
>> Alfredo
>>
>> On Tuesday, 23 December 2014, Carter Schonwald <
carter.schonw...@gmail.com> wrote:
>>> Heres a OS X build that should work with >= 10.7
>>>
http://www.wellposed.com/opensource/ghc/releasebuild-unofficial/ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>>>
>>> and the sha 512
>>> shasum -a512 ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>>>
c6e76a2cd7ec7820d071ef1f417981845bb86c4c8337a57431136a375cbd0695fe810ec10963109ab1971d1a0ab80318c62d71b95eddb5657800cac296a260bd
 ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>>> On Tue, Dec 23, 2014 at 8:12 AM, Austin Seipp 
wrote:
>>>
>>> ==
>>> The (Interactive) Glasgow Haskell Compiler -- version 7.8.4
>>> ==
>>>
>>> The GHC Team is pleased to announce a new patchlevel release of GHC,
7.8.4.
>>>
>>> This is an important bugfix release relative to 7.8.3 (with over 30
>>> defects fixed), so we highly recommend upgrading from the previous 7.8
>>> releases.
>>>
>>> The full release notes are here:
>>>
>>>   https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_gui
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: ANNOUNCE: GHC version 7.8.4

2014-12-24 Thread Alfredo Di Napoli
The installation succeedeed and GHC is working correctly.
But yes, "cabal haddock" seems to have some difficulty in the new version,
but I can't judge if it's my sandboxed environment (we use "hub" at work)
or the failure you mentioned.

Calling "haddock" alone works (using the previously installed on my
system), "cabal haddock" does not:

☁  mandrill [master] ⚡ haddock src/Network/API/Mandrill.hs
Haddock coverage:
Warning: main:Network.API.Mandrill: Could not find documentation for
exported module: M
Warning: Couldn't find .haddock for export Control.Monad.IO.Class.liftIO
 88% (  7 /  8) in 'Network.API.Mandrill'
Warning: Network.API.Mandrill: could not find link destinations for:
   Control.Monad.IO.Class.MonadIO
Network.API.Mandrill.Types.MandrillMessage
Network.API.Mandrill.Trans.MandrillT
Network.API.Mandrill.Types.MandrillResponse
Network.API.Mandrill.Messages.Types.MessagesResponse
Text.Email.Parser.EmailAddress Data.Text.Internal.Text Text.Blaze.Html.Html
GHC.Types.IO

☁  mandrill [master] ⚡ cabal haddock
cabal-1.20.0.0: You need to re-run the 'configure' command. The version of
Cabal being used has changed (was Cabal-1.18.1.5, now Cabal-1.20.0.0).
cabal haddock: /usr/hs/tools/cabal-1.20.0.0 failure (return code=1)

On Wednesday, 24 December 2014, Carter Schonwald 
wrote:
> sure, please verify first.  (also make sure haddock etc works for you, i
had to remove a haddock binary from ~/.cabal/bin before haddocks were
building correctly for me)
> On Wed, Dec 24, 2014 at 10:52 AM, Alfredo Di Napoli <
alfredo.dinap...@gmail.com> wrote:
>
> Thanks Carter!
>
> I have just asked basically about it on Reddit, in the announce thread.
> I'll give it a spin, and if it works I will share the link (if you are ok
with that!) on the
> same Reddit post.
>
> Alfredo
>
> On Tuesday, 23 December 2014, Carter Schonwald 
wrote:
>> Heres a OS X build that should work with >= 10.7
>>
http://www.wellposed.com/opensource/ghc/releasebuild-unofficial/ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>>
>> and the sha 512
>> shasum -a512 ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>>
c6e76a2cd7ec7820d071ef1f417981845bb86c4c8337a57431136a375cbd0695fe810ec10963109ab1971d1a0ab80318c62d71b95eddb5657800cac296a260bd
 ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>> On Tue, Dec 23, 2014 at 8:12 AM, Austin Seipp 
wrote:
>>
>> ==
>> The (Interactive) Glasgow Haskell Compiler -- version 7.8.4
>> ==
>>
>> The GHC Team is pleased to announce a new patchlevel release of GHC,
7.8.4.
>>
>> This is an important bugfix release relative to 7.8.3 (with over 30
>> defects fixed), so we highly recommend upgrading from the previous 7.8
>> releases.
>>
>> The full release notes are here:
>>
>>
https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_guide/release-7-8-4.html
>>
>> How to get it
>> ~
>>
>> The easy way is to go to the web page, which should be self-explanatory:
>>
>> https://www.haskell.org/ghc/
>>
>> We supply binary builds in the native package format for many
>> platforms, and the source distribution is available from the same
>> place.
>>
>> Packages will appear as they are built - if the package for your
>> system isn't available yet, please try again later.
>>
>>
>> Background
>> ~~
>>
>> Haskell is a standard lazy functional programming language.
>>
>> GHC is a state-of-the-art programming suite for Haskell.  Included is
>> an optimising compiler generating good code for a variety of
>> platforms, together with an interactive system for convenient, quick
>> development.  The distribution includes space and time profiling
>> facilities, a large collection of libraries, and support for various
>> language extensions, including concurrency, exceptions, and foreign
>> language interfaces (C, whatever).  GHC is distributed under a
>> BSD-style open source license.
>>
>> A wide variety of Haskell related resources (tutorials, libraries,
>> specifications, documentation, compilers, interpreters, references,
>> contact information, links to research groups) are available from the
>> Haskell home page (see below).
>>
>>
>> On-line GHC-related resources
>> ~~
>>
>> Relevant URLs on the World-Wide Web:
>>
>> GHC home page  http://www.haskell.org/ghc/
>> GHC developers' home page  http://ghc.haskell.org/trac/ghc/
>> Haskell home page  http://www.haskell.org/
>>
>>
>> Supported Platforms
>> ~~~
>>
>> The list of platforms we support, and the people responsible for them,
>> is here:
>>
>>http://ghc.haskell.org/trac/ghc/wiki/Platforms
>>http://ghc.haskell.org/trac/ghc/wiki/CodeOwners
>>
>> Ports to other platforms are possible with varying degrees of
>> difficulty.  The Building Guide describes how
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: ANNOUNCE: GHC version 7.8.4

2014-12-24 Thread Alfredo Di Napoli
Thanks Carter!

I have just asked basically about it on Reddit, in the announce thread.
I'll give it a spin, and if it works I will share the link (if you are ok
with that!) on the
same Reddit post.

Alfredo

On Tuesday, 23 December 2014, Carter Schonwald 
wrote:
> Heres a OS X build that should work with >= 10.7
>
http://www.wellposed.com/opensource/ghc/releasebuild-unofficial/ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>
> and the sha 512
> shasum -a512 ghc-7.8.4-x86_64-apple-darwin.tar.bz2
>
c6e76a2cd7ec7820d071ef1f417981845bb86c4c8337a57431136a375cbd0695fe810ec10963109ab1971d1a0ab80318c62d71b95eddb5657800cac296a260bd
 ghc-7.8.4-x86_64-apple-darwin.tar.bz2
> On Tue, Dec 23, 2014 at 8:12 AM, Austin Seipp 
wrote:
>
> ==
> The (Interactive) Glasgow Haskell Compiler -- version 7.8.4
> ==
>
> The GHC Team is pleased to announce a new patchlevel release of GHC,
7.8.4.
>
> This is an important bugfix release relative to 7.8.3 (with over 30
> defects fixed), so we highly recommend upgrading from the previous 7.8
> releases.
>
> The full release notes are here:
>
>
https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_guide/release-7-8-4.html
>
> How to get it
> ~
>
> The easy way is to go to the web page, which should be self-explanatory:
>
> https://www.haskell.org/ghc/
>
> We supply binary builds in the native package format for many
> platforms, and the source distribution is available from the same
> place.
>
> Packages will appear as they are built - if the package for your
> system isn't available yet, please try again later.
>
>
> Background
> ~~
>
> Haskell is a standard lazy functional programming language.
>
> GHC is a state-of-the-art programming suite for Haskell.  Included is
> an optimising compiler generating good code for a variety of
> platforms, together with an interactive system for convenient, quick
> development.  The distribution includes space and time profiling
> facilities, a large collection of libraries, and support for various
> language extensions, including concurrency, exceptions, and foreign
> language interfaces (C, whatever).  GHC is distributed under a
> BSD-style open source license.
>
> A wide variety of Haskell related resources (tutorials, libraries,
> specifications, documentation, compilers, interpreters, references,
> contact information, links to research groups) are available from the
> Haskell home page (see below).
>
>
> On-line GHC-related resources
> ~~
>
> Relevant URLs on the World-Wide Web:
>
> GHC home page  http://www.haskell.org/ghc/
> GHC developers' home page  http://ghc.haskell.org/trac/ghc/
> Haskell home page  http://www.haskell.org/
>
>
> Supported Platforms
> ~~~
>
> The list of platforms we support, and the people responsible for them,
> is here:
>
>http://ghc.haskell.org/trac/ghc/wiki/Platforms
>http://ghc.haskell.org/trac/ghc/wiki/CodeOwners
>
> Ports to other platforms are possible with varying degrees of
> difficulty.  The Building Guide describes how to go about porting to a
> new platform:
>
> http://ghc.haskell.org/trac/ghc/wiki/Building
>
>
> Developers
> ~~
>
> We welcome new contributors.  Instructions on accessing our source
> code repository, and getting started with hacking on GHC, are
> available from the GHC's developer's site run by Trac:
>
>   http://ghc.haskell.org/trac/ghc/
>
>
> Mailing lists
> ~
>
> We run mailing lists for GHC users and bug reports; to subscribe, use
> the web interfaces at
>
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
>
> There are several other haskell and ghc-related mailing lists on
> www.haskell.org; for the full list, see
>
> http://www.haskell.org/mailman/listinfo/
>
> Some GHC developers hang out on #haskell on IRC, too:
>
> http://www.haskell.org/haskellwiki/IRC_channel
>
> Please report bu
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Getting error about unused instances during "sh validate"

2014-06-13 Thread Alfredo Di Napoli
I think I have finally understood what's going on.

As Simon pointed out (that was the key insight) mapMaybeFP is referenced
inside the RULE, but I'm working on the Lexer to remove old Haddock 0.x
comments, and I suspect my patch broke the Lexer, so the GHC version on my
branch is interpreting that rule as a normal comment, causing the
aforementioned error.
Well, at least I know the problem is just mine and that my patch needs
improvement :)

Thanks SPJ!
Alfredo

On Thursday, 12 June 2014, Alfredo Di Napoli 
wrote:
> Hi Simon,
> It's strange because I was not getting that before (say 2 weeks ago) and
as far as I know I have not changed my build type (always been "quick").
> I'll try to see if playing around with -O will change things and report
back.
> Thanks!
>
> Alfredo
> On 12/giu/2014, at 16:36, Simon Peyton Jones 
wrote:
>
> Does not happen for me.  Maybe you are compiling without –O (odd, but
possible)?  mapMaybeFB is mentioned only inside a RULE, so perhaps it’s
regarded as un-referenced without –O?
>
>
>
> Simon
>
>
>
> From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Alfredo
Di Napoli
> Sent: 12 June 2014 12:31
> To: ghc-devs@haskell.org
> Subject: Getting error about unused instances during "sh validate"
>
>
>
> Hello guys,
>
> am I the only one to get the following when I run "sh validate"?
>
>
> libraries/base/Data/Maybe.hs:139:1: Warning:
>Defined but not used: ‘mapMaybeFB’
>
> :
> Failing due to -Werror.
> make[1]: *** [libraries/base/dist-install/doc/html/base/base.haddock]
Error 1
> make[1]: *** Waiting for unfinished jobs
> make: *** [all] Error 2
>
>
> I'm working on this ticket, but I can't see how that can be related:
>
> https://ghc.haskell.org/trac/ghc/ticket/8226
>
> Thanks!
> Alfredo
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Getting error about unused instances during "sh validate"

2014-06-12 Thread Alfredo Di Napoli
Hi Simon,

It's strange because I was not getting that before (say 2 weeks ago) and as far 
as I know I have not changed my build type (always been "quick").
I'll try to see if playing around with -O will change things and report back.

Thanks!

Alfredo

> On 12/giu/2014, at 16:36, Simon Peyton Jones  wrote:
> 
> Does not happen for me.  Maybe you are compiling without –O (odd, but 
> possible)?  mapMaybeFB is mentioned only inside a RULE, so perhaps it’s 
> regarded as un-referenced without –O?
>  
> Simon
>  
> From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Alfredo Di 
> Napoli
> Sent: 12 June 2014 12:31
> To: ghc-devs@haskell.org
> Subject: Getting error about unused instances during "sh validate"
>  
> Hello guys,
> 
> am I the only one to get the following when I run "sh validate"?
> 
> 
> libraries/base/Data/Maybe.hs:139:1: Warning:
>Defined but not used: ‘mapMaybeFB’
> 
> :
> Failing due to -Werror.
> make[1]: *** [libraries/base/dist-install/doc/html/base/base.haddock] Error 1
> make[1]: *** Waiting for unfinished jobs
> make: *** [all] Error 2
> 
> 
> I'm working on this ticket, but I can't see how that can be related:
> 
> https://ghc.haskell.org/trac/ghc/ticket/8226
> 
> Thanks!
> Alfredo
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Getting error about unused instances during "sh validate"

2014-06-12 Thread Alfredo Di Napoli
Hello guys,

am I the only one to get the following when I run "sh validate"?


libraries/base/Data/Maybe.hs:139:1: Warning:
   Defined but not used: ‘mapMaybeFB’

:
Failing due to -Werror.
make[1]: *** [libraries/base/dist-install/doc/html/base/base.haddock] Error
1
make[1]: *** Waiting for unfinished jobs
make: *** [all] Error 2


I'm working on this ticket, but I can't see how that can be related:

https://ghc.haskell.org/trac/ghc/ticket/8226

Thanks!
Alfredo
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: [GHC] #8226: Remove the old style -- # Haddock comments.

2014-06-07 Thread Alfredo Di Napoli
Thanks Fuuzetsu,
Tomorrow I'll still be at the ZuriHac, so hopefully I'll able to adjust the 
patch :)
I'll poke you if you'll be around

Thanks!

Alfredo Di Napoli

> On 07/giu/2014, at 07:23, "GHC"  wrote:
> 
> #8226: Remove the old style -- # Haddock comments.
> -+
>Reporter:  Fuuzetsu  |Owner:
>Type:  task  |   Status:  patch
>Priority:  normal|Milestone:  7.10.1
>   Component:  Compiler  |  Version:  7.7
>  Resolution:| Keywords:
> Operating System:  Unknown/Multiple  | Architecture:  Unknown/Multiple
> Type of failure:  None/Unknown  |   Difficulty:  Unknown
>   Test Case:|   Blocked By:
>Blocking:|  Related Tickets:
> -+
> 
> Comment (by Fuuzetsu):
> 
> Sorry I fell behind a bit on reading GHC tickets.
> 
> Yes adinapoli, those should also be removed, we do not use --# for
> anything and it served the same purpose as {-# as far as I know.
> 
> Also the data type used to store that type of comment should be removed:
> 
> https://github.com/ghc/ghc/blob/master/compiler/parser/Lexer.x#L625
> 
> FTR the Haddock ticket is now tracked at
> https://github.com/haskell/haddock/issues/171
> 
> Thanks for looking into this, feel free to poke me on IRC/e-mail if you
> need more immediate review.
> 
> --
> Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8226#comment:5>
> GHC <http://www.haskell.org/ghc/>
> The Glasgow Haskell Compiler
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Was GHC 7.8 RC2 profiled-compiled?

2014-03-21 Thread Alfredo Di Napoli
Interesting, enabling TemplateHaskell in cabal as "default extension" made
the error go away.


On 21 March 2014 21:27, Alfredo Di Napoli wrote:

> Evening guys,
>
> was GHC 7.8 RC2 released with profiling enabled? Trying to use TH yields:
>
> You can't use Template Haskell with a profiled compiler
>
> This message is spit out from ghc mod.
>
> Do you guys know if the plan was releasing the RC2 profile compiled or is
> just a flag forgotten to be disabled?
>
> Furthermore, do you know if is available a non-profiled version available
> for Mavericks ?
>
> Sorry if I'm just being stupid!
>
> Alfredo
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Was GHC 7.8 RC2 profiled-compiled?

2014-03-21 Thread Alfredo Di Napoli
Evening guys,

was GHC 7.8 RC2 released with profiling enabled? Trying to use TH yields:

You can't use Template Haskell with a profiled compiler

This message is spit out from ghc mod.

Do you guys know if the plan was releasing the RC2 profile compiled or is
just a flag forgotten to be disabled?

Furthermore, do you know if is available a non-profiled version available
for Mavericks ?

Sorry if I'm just being stupid!

Alfredo
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Can't "make" ghc on master

2013-08-05 Thread Alfredo Di Napoli
Hi Edsko :)

Hsenv was indeed the murderer. Now make passed that error (and is
byte-crunching as we talk).

Thanks for sharing the blog post, it's pure gold.

A.

On 5 August 2013 10:31, Edsko de Vries  wrote:
> It might well be hsenv, which modifies your environment in a number of
> ways. I recommend using my approach to sandboxes, which works fine
> with ghc (http://www.edsko.net/2013/02/10/comprehensive-haskell-sandboxes/).
>
> -E
>
> On Mon, Aug 5, 2013 at 9:14 AM, Alfredo Di Napoli
>  wrote:
>> Hello guys,
>>
>> I'm trying a fresh compile from master. These are the steps I've taken:
>>
>> $ git clone http://darcs.haskell.org/ghc.git/
>> $ cd ghc
>> $ ./sync-all --testsuite get
>>
>> followed by:
>>
>> cp mk/build.mk.sample mk/build.mk
>> 
>>
>> and finally:
>>
>> $ perl boot
>> $ ./configure
>> $ make
>>
>> But this is what I've got in the middle of make (just posting the
>> relevant section):
>>
>> https://gist.github.com/adinapoli/6154219
>>
>> As you can see I'm sandboxed inside hsenv, but I can't think of any
>> reason this being the cause of the failure. Any ideas?
>>
>> Sorry for the naive question,
>> A.
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://www.haskell.org/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Can't "make" ghc on master

2013-08-05 Thread Alfredo Di Napoli
Hello guys,

I'm trying a fresh compile from master. These are the steps I've taken:

$ git clone http://darcs.haskell.org/ghc.git/
$ cd ghc
$ ./sync-all --testsuite get

followed by:

cp mk/build.mk.sample mk/build.mk


and finally:

$ perl boot
$ ./configure
$ make

But this is what I've got in the middle of make (just posting the
relevant section):

https://gist.github.com/adinapoli/6154219

As you can see I'm sandboxed inside hsenv, but I can't think of any
reason this being the cause of the failure. Any ideas?

Sorry for the naive question,
A.

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Mailing lists

2013-01-24 Thread Alfredo Di Napoli
Thank you! As a ghc-dev-wannabe, for now simply lurking in the shadows, it
was really
overwhelming to receive tons of emails from the build system :)

Cheers,
A.

On 23 January 2013 17:19, Ian Lynagh  wrote:

>
> Hi all,
>
> As you've probably noticed, the mailing list changes have now been made.
>
> The following new lists have been created:
> ghc-devs@   For developer discussions
> ghc-commits@For automated commit messages from the git
> repositories
> ghc-builds@ For automated nightly build reports
> ghc-tickets@For automated messages from trac
>
> These mailing lists no longer exist (but for now they forward to an
> appropriate new list):
> cvs-ghc@
> cvs-libraries@
> cvs-other@
> glasgow-haskell-bugs@
>
> People have been subscribed to the new lists based on which old lists
> they were on.
>
> If you find any web pages etc referring to the old lists, please ask the
> webmaster to update them (or do so yourself if e.g. it's on a wiki).
>
>
> Thanks
> Ian
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://www.haskell.org/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs