Re: How to build Haddock documentation quickly?

2021-11-20 Thread Andrey Mokhov
Hi Norman,

> I'm more than willing to dive into Hadrian and figure out how it works.
> I could even add a new target to build just what I'm interested in.
> But I would need help.  I've spent some time poking around the `doc` 
> directory, and I've read
> the Shake papers (and some of Andrei's work) but I've never used these tools 
> myself.

I would be delighted to help you (or anyone else!) navigate Hadrian source 
code. Please feel free to get in touch directly.

(Alas, in the last couple of years I couldn't contribute to improving Hadrian 
but that's not for the lack of desire - just due to some life changes. 
Hopefully I can at least help by helping others!)

Cheers,
Andrey

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


RE: Use of forall as a sigil

2020-11-22 Thread Andrey Mokhov
Hi John,

> - We are already getting `forall {a}.`, so it fits nicely with that.

Interesting, I wasn't aware of this. Could you point me to the relevant 
proposal?

> - However, it would have to be `forall @a ->`, 

Oh, that seems even worse than `forall a ->` to me.

> because `forall a.` is already an invisible quantification,
> unless one wants to just change the meaning of `forall a.`!

I'm confused. I wasn't suggesting to change the meaning of `forall a.`.

My suggestion was pretty incremental:

* `forall a.` stays as is: it allows for both invisible and visible type 
arguments.
* `forall @a.` requires a visible type argument.

Cheers,
Andrey

-Original Message-
From: John Ericson [mailto:john.ericson@obsidian.systems] 
Sent: 22 November 2020 16:41
To: Andrey Mokhov ; Richard Eisenberg 

Cc: ghc-devs@haskell.org
Subject: Re: Use of forall as a sigil


I have thought about this too, and don't believe it has been widely
discussed.

- We are already getting `forall {a}.`, so it fits nicely with that.

- However, it would have to be `forall @a ->`, because `forall a.` is
already an invisible quantification, unless one wants to just change the
meaning of `forall a.`!

John

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


Re: Use of forall as a sigil

2020-11-22 Thread Andrey Mokhov
Hi Richard,

> In the end, I've never loved the forall ... -> syntax, but I've never seen
> anything better.

What about the forall @a. syntax?

For example:

  sizeOf :: forall @a. Sized a => Int

We already use @ to explicitly specify types, so it seems natural mark type 
parameters that must be explicitly specified with @ too.

Here's how one would read it: "for all explicitly specified a, ..."

Apologies if this has been discussed and I missed it. It doesn't seem to be 
mentioned in the Alternatives section of the proposal but perhaps it will just 
never work for some reason.

Cheers,
Andrey

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


Re: More failure

2019-12-10 Thread Andrey Mokhov
Hi Tamar,

I think the difficulty here is more with dynamic *outputs* rather than dynamic 
inputs/dependencies.

We do not statically know which of the following three alternatives holds:

  *   `*.dyn_o/hi` files are not built at all.
  *   `*.dyn_o/hi` files are built via a separate execution of GHC.
  *   `*.dyn_o/hi` files are built together with `*.o/hi` files, in a single 
execution of GHC with `-dynamic-too`.

Here is the current implementation:

https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/src/Rules/Compile.hs#L51-69

I believe the last person looking into this was James Foster, so CC-ing to him 
in case he has any insights.

Cheers,
Andrey


From: Phyx 
Sent: 10 December 2019 07:47
To: Andrey Mokhov 
Cc: Simon Peyton-Jones (simo...@microsoft.com) ; Ben 
Gamari ; ghc-devs@haskell.org 
Subject: Re: More failure

Hi Andrey,

I'm not sure what the original issue here is (should probably find the original 
message) but

> The Make build system happens to do the right thing, somehow. I believe we 
> should be able to express the same logic in Shake, but it's not easy.

I believe this typically works because GCC and GHC support dumping the 
dependencies that a command would have caused to a file. So your dynamic 
dependencies don't matter as their static to the build system after this 
invocation.

See
https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/separate_compilation.html#dependency-generation

These Compilers are able to dump out make rules which enabled better dependency 
handling..

Kind regards,
Tamar

Sent from my Mobile

On Tue, Dec 10, 2019, 00:58 Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>> wrote:

Hi Simon,



(Re-sending from the email address that’s allowed on the mailing list.)



> Ugh.  That's not a very happy state of affairs, is it?  It didn't happen with 
> 'make'.

> Is it a fundamental problem, or just not yet fixed?



I think this is not a fundamental problem, but the problem of getting 
dependencies right.



In this case, the complexity comes from the fact that a single invocation of 
GHC produces a set of files, and which set depends on the command line flags, 
which are in turn determined dynamically by reading environment settings 
(specifically, `platformSupportsSharedLibs`).



Such rules are hard to describe precisely, because build systems are tuned to 
the typical case where we statically know, for every output file, which rule 
produces it -- recall the Tasks = k -> Maybe Task function from our paper. In 
this case, we deal with something like k -> f (Maybe Task) instead, i.e. with 
`f` around the Maybe.



The Make build system happens to do the right thing, somehow. I believe we 
should be able to express the same logic in Shake, but it's not easy.



(I never really had a chance to look at dynamic builds, since they are not 
supported on Windows. I guess I should finally find a Linux box for Hadrian.)



Cheers,

Andrey

___
ghc-devs mailing list
ghc-devs@haskell.org<mailto: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: More failure

2019-12-09 Thread Andrey Mokhov
Hi Simon,

(Re-sending from the email address that's allowed on the mailing list.)

> Ugh.  That's not a very happy state of affairs, is it?  It didn't happen with 
> 'make'.
> Is it a fundamental problem, or just not yet fixed?

I think this is not a fundamental problem, but the problem of getting 
dependencies right.

In this case, the complexity comes from the fact that a single invocation of 
GHC produces a set of files, and which set depends on the command line flags, 
which are in turn determined dynamically by reading environment settings 
(specifically, `platformSupportsSharedLibs`).

Such rules are hard to describe precisely, because build systems are tuned to 
the typical case where we statically know, for every output file, which rule 
produces it -- recall the Tasks = k -> Maybe Task function from our paper. In 
this case, we deal with something like k -> f (Maybe Task) instead, i.e. with 
`f` around the Maybe.

The Make build system happens to do the right thing, somehow. I believe we 
should be able to express the same logic in Shake, but it's not easy.

(I never really had a chance to look at dynamic builds, since they are not 
supported on Windows. I guess I should finally find a Linux box for Hadrian.)

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


RE: Hadrian: Suddenly a full build fails with: Rules may not be recursive

2019-06-22 Thread Andrey Mokhov
Hi all,

> I think this is because `--configure` is currently broken
> https://gitlab.haskell.org/ghc/ghc/issues/16809. You can work around by
> running bootstrap and configure manually for now.

Here is a merge request with a fix: 
https://gitlab.haskell.org/ghc/ghc/merge_requests/1255

Cheers,
Andrey

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


RE: Container type classes

2019-05-30 Thread Andrey Mokhov
Thanks again Iavor,

Despite the type inference issue, and the fact that this requires a separate 
type class, this is the best solution I've seen so far.

Cheers,
Andrey

-Original Message-
From: Iavor Diatchki [mailto:iavor.diatc...@gmail.com] 
Sent: 30 May 2019 23:16
To: Andrey Mokhov 
Cc: Brandon Allbery ; Andreas Klebinger 
; ghc-devs@haskell.org
Subject: Re: Container type classes

Yeah, there is really no relation between the two parameters of `Fun`,
so you'd have to specify the intermediate type manually. For example:

add3 :: forall s. (Fun s s, Elem s ~ Int) => s -> s
add3 = colMap @s (+1) . colMap (+2)

I wouldn't say that it's a particularly convenient interface to work
with, unless you are working in a setting where most of the containers
have known types.


On Thu, May 30, 2019 at 2:58 PM Andrey Mokhov
 wrote:
>
> Many thanks Iavor,
>
> This looks very promising! I played with your encoding a little, but quickly 
> came across type inference issues. The following doesn't compile:
>
> add3 :: (Fun s s, Elem s ~ Int) => s -> s
> add3 = colMap (+1) . colMap (+2)
>
> I'm getting:
>
> * Could not deduce: Elem a0 ~ Int
>   from the context: (Fun s s, Elem s ~ Int)
> bound by the type signature for:
>add3 :: forall s. (Fun s s, Elem s ~ Int) => s -> s
>   Expected type: Elem a0 -> Elem s
> Actual type: Int -> Int
>   The type variable `a0' is ambiguous
>
> Fun s s is supposed to say that the intermediate type is `s` too, but I guess 
> this is not how type class resolution works.
>
> Cheers,
> Andrey
>
> -Original Message-
> From: Iavor Diatchki [mailto:iavor.diatc...@gmail.com]
> Sent: 30 May 2019 22:38
> To: Brandon Allbery 
> Cc: Andrey Mokhov ; Andreas Klebinger 
> ; ghc-devs@haskell.org
> Subject: Re: Container type classes
>
> This is how you could define `map`.  This is just for fun, and to
> discuss Haskell idioms---I am not suggesting we should do it.  Of
> course, it might be a bit more general than what you'd like---for
> example it allows defining instances like `Fun IntSet (Set Int)` that,
> perhaps?, you'd like to disallow:
>
> {-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}
>
> import Data.Set (Set)
> import qualified Data.Set as Set
> import Data.IntSet (IntSet)
> import qualified Data.IntSet as ISet
>
> class Col t where
>   type Elem t
>   -- ... As in Andreas's example
>
> class (Col a, Col b) => Fun a b where
>   colMap :: (Elem a -> Elem b) -> a -> b
>
> instance Col (Set a) where
>   type Elem (Set a) = a
>
> instance Col IntSet where
>   type Elem IntSet = Int
>
> instance Fun IntSet IntSet where
>   colMap = ISet.map
>
> instance Ord b => Fun (Set a) (Set b) where
>   colMap = Set.map
>
> On Thu, May 30, 2019 at 2:32 PM Brandon Allbery  wrote:
> >
> > They can, with more work. You want indexed monads, so you can describe 
> > types that have e.g. an ordering constraint as well as the Monad constraint.
> >
> > On Thu, May 30, 2019 at 5:26 PM Andrey Mokhov 
> >  wrote:
> >>
> >> Hi Artem,
> >>
> >>
> >>
> >> Thanks for the pointer, but this doesn’t seem to be a solution to my 
> >> challenge: they simply give up on overloading `map` for both Set and 
> >> IntSet. As a result, we can’t write polymorphic functions over Set and 
> >> IntSet if they involve any mapping.
> >>
> >>
> >>
> >> I looked at the prototype by Andreas Klebinger, and it doesn’t include the 
> >> method `setMap` either.
> >>
> >>
> >>
> >> Perhaps, Haskell’s type classes just can’t cope with this problem.
> >>
> >>
> >>
> >> *ducks for cover*
> >>
> >>
> >>
> >> Cheers,
> >>
> >> Andrey
> >>
> >>
> >>
> >> From: Artem Pelenitsyn [mailto:a.pelenit...@gmail.com]
> >> Sent: 30 May 2019 20:56
> >> To: Andrey Mokhov 
> >> Cc: ghc-devs@haskell.org; Andreas Klebinger 
> >> Subject: Re: Container type classes
> >>
> >>
> >>
> >> Hi Andrey,
> >>
> >>
> >>
> >> FWIW, mono-traversable 
> >> (http://hackage.haskell.org/package/mono-traversable) suggests decoupling 
> >> IsSet and Funtor-like.
> >>
> >>
> >>
> >> In a nutshell, they define the IsSet class (in Data.Containers) with 
> >> typical set operations like member and singleton, union and intersection. 
> >> And then they tackle a (seemingly) independent pr

RE: Container type classes

2019-05-30 Thread Andrey Mokhov
Many thanks Iavor,

This looks very promising! I played with your encoding a little, but quickly 
came across type inference issues. The following doesn't compile:

add3 :: (Fun s s, Elem s ~ Int) => s -> s
add3 = colMap (+1) . colMap (+2)

I'm getting:

* Could not deduce: Elem a0 ~ Int
  from the context: (Fun s s, Elem s ~ Int)
bound by the type signature for:
   add3 :: forall s. (Fun s s, Elem s ~ Int) => s -> s
  Expected type: Elem a0 -> Elem s
Actual type: Int -> Int
  The type variable `a0' is ambiguous

Fun s s is supposed to say that the intermediate type is `s` too, but I guess 
this is not how type class resolution works.

Cheers,
Andrey

-Original Message-
From: Iavor Diatchki [mailto:iavor.diatc...@gmail.com] 
Sent: 30 May 2019 22:38
To: Brandon Allbery 
Cc: Andrey Mokhov ; Andreas Klebinger 
; ghc-devs@haskell.org
Subject: Re: Container type classes

This is how you could define `map`.  This is just for fun, and to
discuss Haskell idioms---I am not suggesting we should do it.  Of
course, it might be a bit more general than what you'd like---for
example it allows defining instances like `Fun IntSet (Set Int)` that,
perhaps?, you'd like to disallow:

{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}

import Data.Set (Set)
import qualified Data.Set as Set
import Data.IntSet (IntSet)
import qualified Data.IntSet as ISet

class Col t where
  type Elem t
  -- ... As in Andreas's example

class (Col a, Col b) => Fun a b where
  colMap :: (Elem a -> Elem b) -> a -> b

instance Col (Set a) where
  type Elem (Set a) = a

instance Col IntSet where
  type Elem IntSet = Int

instance Fun IntSet IntSet where
  colMap = ISet.map

instance Ord b => Fun (Set a) (Set b) where
  colMap = Set.map

On Thu, May 30, 2019 at 2:32 PM Brandon Allbery  wrote:
>
> They can, with more work. You want indexed monads, so you can describe types 
> that have e.g. an ordering constraint as well as the Monad constraint.
>
> On Thu, May 30, 2019 at 5:26 PM Andrey Mokhov  
> wrote:
>>
>> Hi Artem,
>>
>>
>>
>> Thanks for the pointer, but this doesn’t seem to be a solution to my 
>> challenge: they simply give up on overloading `map` for both Set and IntSet. 
>> As a result, we can’t write polymorphic functions over Set and IntSet if 
>> they involve any mapping.
>>
>>
>>
>> I looked at the prototype by Andreas Klebinger, and it doesn’t include the 
>> method `setMap` either.
>>
>>
>>
>> Perhaps, Haskell’s type classes just can’t cope with this problem.
>>
>>
>>
>> *ducks for cover*
>>
>>
>>
>> Cheers,
>>
>> Andrey
>>
>>
>>
>> From: Artem Pelenitsyn [mailto:a.pelenit...@gmail.com]
>> Sent: 30 May 2019 20:56
>> To: Andrey Mokhov 
>> Cc: ghc-devs@haskell.org; Andreas Klebinger 
>> Subject: Re: Container type classes
>>
>>
>>
>> Hi Andrey,
>>
>>
>>
>> FWIW, mono-traversable (http://hackage.haskell.org/package/mono-traversable) 
>> suggests decoupling IsSet and Funtor-like.
>>
>>
>>
>> In a nutshell, they define the IsSet class (in Data.Containers) with typical 
>> set operations like member and singleton, union and intersection. And then 
>> they tackle a (seemingly) independent problem of mapping monomorphic 
>> containers (like IntSet, ByteString, etc.) with a separate class MonoFunctor 
>> (in Data.MonoTraversable):
>>
>>
>>
>> class MonoFunctor mono where
>> omap :: (Element mono -> Element mono) -> mono -> mono
>>
>>
>>
>> And gazillion of instances for both polymorphic containers with a fixed type 
>> parameter and monomorphic ones.
>>
>>
>>
>> --
>>
>> Best wishes,
>>
>> Artem
>>
>>
>>
>> On Thu, 30 May 2019 at 20:11, Andrey Mokhov  
>> wrote:
>>
>> Hi all,
>>
>> I tried to use type classes for unifying APIs of several similar data 
>> structures and it didn't work well. (In my case I was working with graphs, 
>> instead of sets or maps.)
>>
>> First, you rarely want to be polymorphic over the set representation, 
>> because you care about performance. You really want to use that 
>> Very.Special.Set.insert because it has the right performance characteristics 
>> for your task at hand. I found only *one* use-case for writing polymorphic 
>> functions operating on something like IsSet: the testsuite. Of course, it is 
>> very nice to write a single property test like
>>
>> memberInsertProperty x set = (member x (insert x set) == True)
>>
>> and then us

RE: Container type classes

2019-05-30 Thread Andrey Mokhov
Hi Brandon,

Could you show the code?

I have no idea how indexed monads could possibly be related here. All I want is 
to have a type class that unifies these two methods:

singleton :: a -> Set a
map :: Ord b => (a -> b) -> Set a -> Set b

singleton :: Int -> IntSet
map :: (Int -> Int) -> IntSet -> IntSet

Cheers,
Andrey

From: Brandon Allbery [mailto:allber...@gmail.com]
Sent: 30 May 2019 22:32
To: Andrey Mokhov 
Cc: Artem Pelenitsyn ; Andreas Klebinger 
; ghc-devs@haskell.org
Subject: Re: Container type classes

They can, with more work. You want indexed monads, so you can describe types 
that have e.g. an ordering constraint as well as the Monad constraint.

On Thu, May 30, 2019 at 5:26 PM Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>> wrote:
Hi Artem,

Thanks for the pointer, but this doesn’t seem to be a solution to my challenge: 
they simply give up on overloading `map` for both Set and IntSet. As a result, 
we can’t write polymorphic functions over Set and IntSet if they involve any 
mapping.

I looked at the prototype by Andreas Klebinger, and it doesn’t include the 
method `setMap` either.

Perhaps, Haskell’s type classes just can’t cope with this problem.

*ducks for cover*

Cheers,
Andrey

From: Artem Pelenitsyn 
[mailto:a.pelenit...@gmail.com<mailto:a.pelenit...@gmail.com>]
Sent: 30 May 2019 20:56
To: Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>>
Cc: ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>; Andreas Klebinger 
mailto:klebinger.andr...@gmx.at>>
Subject: Re: Container type classes

Hi Andrey,

FWIW, mono-traversable (http://hackage.haskell.org/package/mono-traversable) 
suggests decoupling IsSet and Funtor-like.

In a nutshell, they define the IsSet class (in Data.Containers) with typical 
set operations like member and singleton, union and intersection. And then they 
tackle a (seemingly) independent problem of mapping monomorphic containers 
(like IntSet, ByteString, etc.) with a separate class MonoFunctor (in 
Data.MonoTraversable):

class MonoFunctor mono where
omap :: (Element mono -> Element mono) -> mono -> mono

And gazillion of instances for both polymorphic containers with a fixed type 
parameter and monomorphic ones.

--
Best wishes,
Artem

On Thu, 30 May 2019 at 20:11, Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>> wrote:
Hi all,

I tried to use type classes for unifying APIs of several similar data 
structures and it didn't work well. (In my case I was working with graphs, 
instead of sets or maps.)

First, you rarely want to be polymorphic over the set representation, because 
you care about performance. You really want to use that Very.Special.Set.insert 
because it has the right performance characteristics for your task at hand. I 
found only *one* use-case for writing polymorphic functions operating on 
something like IsSet: the testsuite. Of course, it is very nice to write a 
single property test like

memberInsertProperty x set = (member x (insert x set) == True)

and then use it for testing all set data structures that implement `member` and 
`insert`. Here you don't care about performance, only about correctness!

However, this approach leads to problems with type inference, confusing error 
messages, and complexity. I found that it is much nicer to use explicit 
dictionary passing and write something like this instead:

memberInsertProperty SetAPI{..} x set = (member x (insert x set) == True)

where `member` and `insert` come from the SetAPI record via RecordWildCards.

Finally, I'm not even sure how to create a type class covering Set and IntSet 
with the following two methods:

singleton :: a -> Set a
map :: Ord b => (a -> b) -> Set a -> Set b

singleton :: Int -> IntSet
map :: (Int -> Int) -> IntSet -> IntSet

Could anyone please enlighten me about the right way to abstract over this 
using type classes?

I tried a few approaches, for example:

class IsSet s where
type Elem s
singleton :: Elem s -> s
map :: Ord (Elem t) => (Elem s -> Elem t) -> s -> t

Looks nice, but I can't define the IntSet instance:

instance IsSet IntSet where
type Elem IntSet = Int
singleton = IntSet.singleton
map = IntSet.map

This fails with: Couldn't match type `t' with `IntSet' -- and indeed, how do I 
tell the compiler that in the IntSet case s ~ t in the map signature? Shall I 
add more associated types, or "associated constraints" using ConstraintKinds? I 
tried and failed, at various stages, repeatedly.

...And then you discover that there is Set.cartesianProduct :: Set a -> Set b 
-> Set (a, b), but no equivalent in IntSet and things get even more grim.

Cheers,
Andrey

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

RE: Container type classes

2019-05-30 Thread Andrey Mokhov
Hi Artem,

Thanks for the pointer, but this doesn’t seem to be a solution to my challenge: 
they simply give up on overloading `map` for both Set and IntSet. As a result, 
we can’t write polymorphic functions over Set and IntSet if they involve any 
mapping.

I looked at the prototype by Andreas Klebinger, and it doesn’t include the 
method `setMap` either.

Perhaps, Haskell’s type classes just can’t cope with this problem.

*ducks for cover*

Cheers,
Andrey

From: Artem Pelenitsyn [mailto:a.pelenit...@gmail.com]
Sent: 30 May 2019 20:56
To: Andrey Mokhov 
Cc: ghc-devs@haskell.org; Andreas Klebinger 
Subject: Re: Container type classes

Hi Andrey,

FWIW, mono-traversable (http://hackage.haskell.org/package/mono-traversable) 
suggests decoupling IsSet and Funtor-like.

In a nutshell, they define the IsSet class (in Data.Containers) with typical 
set operations like member and singleton, union and intersection. And then they 
tackle a (seemingly) independent problem of mapping monomorphic containers 
(like IntSet, ByteString, etc.) with a separate class MonoFunctor (in 
Data.MonoTraversable):

class MonoFunctor mono where
omap :: (Element mono -> Element mono) -> mono -> mono

And gazillion of instances for both polymorphic containers with a fixed type 
parameter and monomorphic ones.

--
Best wishes,
Artem

On Thu, 30 May 2019 at 20:11, Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>> wrote:
Hi all,

I tried to use type classes for unifying APIs of several similar data 
structures and it didn't work well. (In my case I was working with graphs, 
instead of sets or maps.)

First, you rarely want to be polymorphic over the set representation, because 
you care about performance. You really want to use that Very.Special.Set.insert 
because it has the right performance characteristics for your task at hand. I 
found only *one* use-case for writing polymorphic functions operating on 
something like IsSet: the testsuite. Of course, it is very nice to write a 
single property test like

memberInsertProperty x set = (member x (insert x set) == True)

and then use it for testing all set data structures that implement `member` and 
`insert`. Here you don't care about performance, only about correctness!

However, this approach leads to problems with type inference, confusing error 
messages, and complexity. I found that it is much nicer to use explicit 
dictionary passing and write something like this instead:

memberInsertProperty SetAPI{..} x set = (member x (insert x set) == True)

where `member` and `insert` come from the SetAPI record via RecordWildCards.

Finally, I'm not even sure how to create a type class covering Set and IntSet 
with the following two methods:

singleton :: a -> Set a
map :: Ord b => (a -> b) -> Set a -> Set b

singleton :: Int -> IntSet
map :: (Int -> Int) -> IntSet -> IntSet

Could anyone please enlighten me about the right way to abstract over this 
using type classes?

I tried a few approaches, for example:

class IsSet s where
type Elem s
singleton :: Elem s -> s
map :: Ord (Elem t) => (Elem s -> Elem t) -> s -> t

Looks nice, but I can't define the IntSet instance:

instance IsSet IntSet where
type Elem IntSet = Int
singleton = IntSet.singleton
map = IntSet.map

This fails with: Couldn't match type `t' with `IntSet' -- and indeed, how do I 
tell the compiler that in the IntSet case s ~ t in the map signature? Shall I 
add more associated types, or "associated constraints" using ConstraintKinds? I 
tried and failed, at various stages, repeatedly.

...And then you discover that there is Set.cartesianProduct :: Set a -> Set b 
-> Set (a, b), but no equivalent in IntSet and things get even more grim.

Cheers,
Andrey

___
ghc-devs mailing list
ghc-devs@haskell.org<mailto: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: Container type classes

2019-05-30 Thread Andrey Mokhov
> If you care about performance then explicit dictionary passing is
> going to be worse than using type classes.

Of course! But explicit dictionary passing works great for tests: the code size 
is reduced from O(#modules * #tests) when using the module system to O(#modules 
+ #tests) when using dictionaries.

For example, in the algebraic-graphs library, I have 500+ generic tests and 
around 10 modules. I don't want to write 5000 tests! Here is an example generic 
test which uses explicit dictionary passing: 
https://github.com/snowleopard/alga/blob/master/test/Algebra/Graph/Test/Generic.hs#L303-L319.
 I don't think it would be possible to reuse this test for different graph data 
types by using the module system instead of dictionaries. (Perhaps, Backpack 
could help? I don't know it very well.)

Cheers,
Andrey

-Original Message-
From: Matthew Pickering [mailto:matthewtpicker...@gmail.com] 
Sent: 30 May 2019 18:26
To: Andrey Mokhov 
Cc: ghc-devs@haskell.org; Andreas Klebinger 
Subject: Re: Container type classes

If you care about performance then explicit dictionary passing is
going to be worse than using type classes.

At that point though, what do you gain from using the module system as
you are just going to pass the same dictionaries into every function
and never change them.

So, for me, keep using modules but make the APIs of each module more
consistent if you think it's worthwhile.

On Thu, May 30, 2019 at 6:11 PM Andrey Mokhov
 wrote:
>
> Hi all,
>
> I tried to use type classes for unifying APIs of several similar data 
> structures and it didn't work well. (In my case I was working with graphs, 
> instead of sets or maps.)
>
> First, you rarely want to be polymorphic over the set representation, because 
> you care about performance. You really want to use that 
> Very.Special.Set.insert because it has the right performance characteristics 
> for your task at hand. I found only *one* use-case for writing polymorphic 
> functions operating on something like IsSet: the testsuite. Of course, it is 
> very nice to write a single property test like
>
> memberInsertProperty x set = (member x (insert x set) == True)
>
> and then use it for testing all set data structures that implement `member` 
> and `insert`. Here you don't care about performance, only about correctness!
>
> However, this approach leads to problems with type inference, confusing error 
> messages, and complexity. I found that it is much nicer to use explicit 
> dictionary passing and write something like this instead:
>
> memberInsertProperty SetAPI{..} x set = (member x (insert x set) == True)
>
> where `member` and `insert` come from the SetAPI record via RecordWildCards.
>
> Finally, I'm not even sure how to create a type class covering Set and IntSet 
> with the following two methods:
>
> singleton :: a -> Set a
> map :: Ord b => (a -> b) -> Set a -> Set b
>
> singleton :: Int -> IntSet
> map :: (Int -> Int) -> IntSet -> IntSet
>
> Could anyone please enlighten me about the right way to abstract over this 
> using type classes?
>
> I tried a few approaches, for example:
>
> class IsSet s where
> type Elem s
> singleton :: Elem s -> s
> map :: Ord (Elem t) => (Elem s -> Elem t) -> s -> t
>
> Looks nice, but I can't define the IntSet instance:
>
> instance IsSet IntSet where
> type Elem IntSet = Int
> singleton = IntSet.singleton
> map = IntSet.map
>
> This fails with: Couldn't match type `t' with `IntSet' -- and indeed, how do 
> I tell the compiler that in the IntSet case s ~ t in the map signature? Shall 
> I add more associated types, or "associated constraints" using 
> ConstraintKinds? I tried and failed, at various stages, repeatedly.
>
> ...And then you discover that there is Set.cartesianProduct :: Set a -> Set b 
> -> Set (a, b), but no equivalent in IntSet and things get even more grim.
>
> Cheers,
> Andrey
>
> ___
> 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: Container type classes

2019-05-30 Thread Andrey Mokhov
Hi all,

I tried to use type classes for unifying APIs of several similar data 
structures and it didn't work well. (In my case I was working with graphs, 
instead of sets or maps.)

First, you rarely want to be polymorphic over the set representation, because 
you care about performance. You really want to use that Very.Special.Set.insert 
because it has the right performance characteristics for your task at hand. I 
found only *one* use-case for writing polymorphic functions operating on 
something like IsSet: the testsuite. Of course, it is very nice to write a 
single property test like

memberInsertProperty x set = (member x (insert x set) == True)

and then use it for testing all set data structures that implement `member` and 
`insert`. Here you don't care about performance, only about correctness!

However, this approach leads to problems with type inference, confusing error 
messages, and complexity. I found that it is much nicer to use explicit 
dictionary passing and write something like this instead:

memberInsertProperty SetAPI{..} x set = (member x (insert x set) == True)

where `member` and `insert` come from the SetAPI record via RecordWildCards. 

Finally, I'm not even sure how to create a type class covering Set and IntSet 
with the following two methods:

singleton :: a -> Set a
map :: Ord b => (a -> b) -> Set a -> Set b

singleton :: Int -> IntSet
map :: (Int -> Int) -> IntSet -> IntSet

Could anyone please enlighten me about the right way to abstract over this 
using type classes?

I tried a few approaches, for example:

class IsSet s where
type Elem s
singleton :: Elem s -> s
map :: Ord (Elem t) => (Elem s -> Elem t) -> s -> t

Looks nice, but I can't define the IntSet instance:

instance IsSet IntSet where
type Elem IntSet = Int 
singleton = IntSet.singleton
map = IntSet.map

This fails with: Couldn't match type `t' with `IntSet' -- and indeed, how do I 
tell the compiler that in the IntSet case s ~ t in the map signature? Shall I 
add more associated types, or "associated constraints" using ConstraintKinds? I 
tried and failed, at various stages, repeatedly.

...And then you discover that there is Set.cartesianProduct :: Set a -> Set b 
-> Set (a, b), but no equivalent in IntSet and things get even more grim.

Cheers,
Andrey

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


RE: ZuriHac 2019 - GHC Track

2019-05-01 Thread Andrey Mokhov
Hi all,

I am happy to help with Hadrian, perhaps giving an overview of the codebase and 
a quick demo covering typical use-cases. I'll generally be around to help with 
any build related issues, Hadrian hacking, etc.

Note: I'm attending full days on Friday and Saturday, but on Sunday I may be 
available only in the morning.

Cheers,
Andrey

===

Dear GHC devs,

This year's ZuriHac 2019 [1] will again feature a dedicated GHC track to
foster contributions to GHC and teach newcomers how to participate in GHC's
development. It was a great success last year, and we hope it will be a
great success this year as well.

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

For some inspiration, these are the subjects from last year's track:
- Continuous Integration / DevOps, by Manual Chakravarty
- PrimOps / PrimTypes, by Michal Terepeta
- Performance Regression Tests, by Niklas Hambüchen
- Newcomers Tutorial, by Andreas Herrmann

Other possible subjects could be around:
- Improving documentation
- Extending GHC's test-suite
- General GHC development workflows
- The inner workings of some aspect of GHC

Aside from preparing a session, we are also looking for volunteers to be
around as GHC mentors during hack sessions to help out newcomers.

Please let us know if you'd be interested in leading a session, or being a
mentor, or helping out with this track in any other way. You can contact
either Niklas or myself, on this list or by private message.

Best,
Niklas and Andreas
ZuriHac 2019 GHC track coordinators

[1]: https://zfoh.ch/zurihac2019/

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


RE: Hadrian

2019-04-16 Thread Andrey Mokhov
Hi all, 

Here is a patch for generating wrapper scripts from Hadrian: 

https://gitlab.haskell.org/ghc/ghc/merge_requests/780

While it's being reviewed and merged, you can create script 
`/ghc-stage1` with the following line yourself:

"_build/stage0/bin/ghc.exe" "-package-db _build/stage1/lib/package.conf.d" "$@"

It works for me, e.g. I can do 


$ _build/ghc-stage1 helloWorld.hs
[1 of 1] Compiling Main ( helloWorld.hs, helloWorld.o )
Linking helloWorld.exe ...
$ ./helloWorld.exe
Hello World


Cheers,
Andrey

-Original Message-
From: Simon Peyton Jones [mailto:simo...@microsoft.com] 
Sent: 15 April 2019 14:37
To: Moritz Angermann 
Cc: Matthew Pickering ; Andrey Mokhov 
; ghc-devs@haskell.org
Subject: RE: Hadrian

sounds good to me!

|  -Original Message-
|  From: Moritz Angermann 
|  Sent: 15 April 2019 14:29
|  To: Simon Peyton Jones 
|  Cc: Matthew Pickering ; Andrey Mokhov
|  ; ghc-devs@haskell.org
|  Subject: Re: Hadrian
|  
|  I guess we could add
|  
|  $root/ghc-stage1 (shell script)
|  $root/ghc-stage2 (shell script)
|  
|  As long as we understand that those are just convenience scripts.
|  
|  Why $root? Because we can have multiple build directories for different
|  configurations. Thus putting the scripts into the ghc folder would not
|  know which root you wanted. This for the default root this would be:
|  
|  _build/ghc-stage1
|  _build/ghc-stage2
|  
|  Does that sound like an intermittent solution?
|  
|  Cheers,
|Moritz
|  
|  Sent from my iPhone
|  
|  > On 15 Apr 2019, at 8:47 AM, Simon Peyton Jones via ghc-devs  wrote:
|  >
|  > Ah.  I hadn't even tried the stage2 compiler (in the stage1/ directory).
|  Yes, that works.  But perhaps a script to get to it would be helpful,
|  otherwise invoking stage1 will look entirely different to invoking stage2.
|  Not a bid deal, I grant you!
|  >
|  > S
|  >
|  > |  -Original Message-
|  > |  From: Matthew Pickering 
|  > |  Sent: 15 April 2019 13:40
|  > |  To: Simon Peyton Jones 
|  > |  Cc: Andrey Mokhov ;
|  > | ghc-devs@haskell.org
|  > |  Subject: Re: Hadrian
|  > |
|  > |  Does the stage2 compiler which is found in `stage1/bin/ghc` not
|  > | work for  you? I thought the issue was that the stage1 compiler
|  doesn't work.
|  > |
|  > |  Matt
|  > |
|  > |  On Mon, Apr 15, 2019 at 1:11 PM Simon Peyton Jones via ghc-devs
|  > |  wrote:
|  > |  >
|  > |  > as a temporary workaround we could create a top-level wrapper
|  > | script,  say `ghc-stage1.sh` that will call Stage1 GHC with the
|  > | right arguments,  just like Hadrian itself does during the build.
|  > |  >
|  > |  > That sound fine, thanks.   Same for ghc-stage2.sh?
|  > |  >
|  > |  > My difficulty is that as of today I simply do not know how to
|  > | invoke my  freshly built GHC!
|  > |  >
|  > |  > Simon
|  > |  >
|  > |  >
|  > |  >
|  > |  > From: Andrey Mokhov   > Sent: 15
|  > | April 2019 12:53  > To: Simon Peyton Jones 
|  > | > Cc: ghc-devs@haskell.org  > Subject: RE: Hadrian  >  >  >  > Hi
|  > | Simon,  >  > Apologies it’s taking so long. It’s not obvious how to
|  > | fix this  properly, and as a temporary workaround we could create a
|  > | top-level  wrapper script, say `ghc-stage1.sh` that will call Stage1
|  > | GHC with the  right arguments, just like Hadrian itself does during
|  > | the build.
|  > |  >
|  > |  > Will this work for you?
|  > |  >
|  > |  > Cheers,
|  > |  > Andrey
|  > |  >
|  > |  >
|  > |  >
|  > |  > From: Simon Peyton Jones [mailto:simo...@microsoft.com]  > Sent:
|  > | 15 April 2019 12:28  > To: Andrey Mokhov
|  > |   > Cc: ghc-devs@haskell.org  >
|  > | Subject: Hadrian  >  >  >  > Andrey and other Hadrian heros  >  >
|  > | Just to say that I am 100% stalled on using Hadrian because the  >
|  > | in-tree binary uses the wrong library files.  I reported this a few
|  > | > weeks ago, but it still seems unchanged  >  > Simon  >  >  >  >
|  > | Bash$ ~/code/HEAD/_build/stage0/bin/ghc --version  >  > The Glorious
|  > | Glasgow Haskell Compilation System, version  > 8.9.0.20190414  >  >
|  > | simonpj@MSRC-3645512:~/tmp$ ~/code/HEAD/_build/stage0/bin/ghc -c  >
|  > | T16566.hs  >  >  >  > T16566.hs:1:8: error:
|  > |  >
|  > |  > Bad interface file:
|  > |  > /opt/ghc/8.6.4/lib/ghc-8.6.4/base-4.12.0.0/Prelude.hi
|  > |  >
|  > |  > mismatched interface file versions (wanted "809020190414",
|  got
|  > |  > "8064")
|  > |  >
|  > |  >   |
|  > |  >
|  > |  > 1 | module T16566 where
|  &

RE: Hadrian

2019-04-15 Thread Andrey Mokhov
Hi Simon,
Apologies it's taking so long. It's not obvious how to fix this properly, and 
as a temporary workaround we could create a top-level wrapper script, say 
`ghc-stage1.sh` that will call Stage1 GHC with the right arguments, just like 
Hadrian itself does during the build.
Will this work for you?
Cheers,
Andrey

From: Simon Peyton Jones [mailto:simo...@microsoft.com]
Sent: 15 April 2019 12:28
To: Andrey Mokhov 
Cc: ghc-devs@haskell.org
Subject: Hadrian

Andrey and other Hadrian heros
Just to say that I am 100% stalled on using Hadrian because the in-tree binary 
uses the wrong library files.  I reported this a few weeks ago, but it still 
seems unchanged
Simon


Bash$ ~/code/HEAD/_build/stage0/bin/ghc --version

The Glorious Glasgow Haskell Compilation System, version 8.9.0.20190414

simonpj@MSRC-3645512:~/tmp$ ~/code/HEAD/_build/stage0/bin/ghc -c T16566.hs



T16566.hs:1:8: error:

Bad interface file: /opt/ghc/8.6.4/lib/ghc-8.6.4/base-4.12.0.0/Prelude.hi

mismatched interface file versions (wanted "809020190414", got "8064")

  |

1 | module T16566 where

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


RE: Hadrian Transitive Dependencies

2019-03-27 Thread Andrey Mokhov
Hi David,

We had a discussion about this with Neil some time ago, and I think we had the 
following list of progressively more complex invariants for different types of 
build systems:


·Non-cloud build systems: *all direct inputs must be declared*. If you 
miss a direct input dependency then a build may complete successfully but with 
an incorrect result.



·Cloud build systems: *all direct inputs and direct outputs must be 
declared*. If you miss a direct output then a build may fail because the cloud 
will not be able to restore the corresponding output.


·Cloud build systems with shallow (deferred) materialisation of build 
artefacts: *all transitive inputs and direct outputs must be declared*. Let’s 
say you’d like to download the resulting GHC binary directly, without 
materialising any intermediate artefacts. Then you’ll need to know GHC’s 
ultimate transitive inputs.

I think for now we are really keen to make Hadrian a cloud build system, but 
whether shallow builds are valuable enough is not clear. Maybe not. Therefore, 
I’d say we don’t need to track transitive inputs right now. Furthermore, if we 
were to track all transitive inputs, we would lose the desirable early cutoff 
property, which prevents rebuilding after adding a comment in a file on which a 
lot of other files transitively depend on.

Having said that, if we really access a file during compilation, then I think 
it is *not* a transitive dependency by definition! Any file which is accessed 
during a build rule is a direct dependency.

> GHC is reading *.hi files that are not reported as dependencies by
> `ghc -M  -include-pkg-deps`. This is because they are not direct, but 
> transitive
> dependencies!

So, here I’m confused. If we read a file A when compiling a file B, then it’s 
by definition a direct dependency. Perhaps we just read too much? Maybe the 
solution is to switch to fine-grained `ghc -M` mode, to analyse import 
dependencies for a single module instead of doing it transitively, which I 
believe was discussed in a ticket some time ago? I can’t find this ticket, but 
I think Alp was looking into it at some point. Alp: do you remember it?

Thank you for all your work on Hadrian!

Cheers,
Andrey

From: David Eichmann [mailto:dav...@well-typed.com]
Sent: 27 March 2019 12:54
To: Neil Mitchell ; Andrey Mokhov 
; GHC developers 
Subject: Hadrian Transitive Dependencies


Hello Shake/Hadrian contributors and the like,

Recently I've been putting Hadrian's fsatrace linting feature to good use, 
tracking down missing dependencies in Hadrian. Ultimately, we want to use 
shake's cloud build / shared cache feature and ensure it works across CI 
builds. Unfortunately the feature isn't working smoothly with Hadrian: see 
#16295<https://gitlab.haskell.org/ghc/ghc/issues/16295>. This is very desirable 
to improve CI build times. It is my understanding that in order to get caching 
to work:
1. All accessed files must declared with `need` AND
2. All created files must be declared with `produces` (or be the target of the 
build rule)

Is my understanding correct? Or is there a weaker condition (perhaps only 2 is 
necessary)?

If I'm correct, this amounts to fixing all fsatrace lint errors. See 
here<https://gitlab.haskell.org/ghc/ghc/issues/16400#note_188901> for a 
breakdown of lint errors / missing dependencies. A large portion of these are 
Haskell interface files (i.e. *.hi files). Before building a Haskell object 
file, dependencies are discovered via `ghc` using the `-M  -include-pkg-deps` 
options. Unfortunately, shake's fsatrace linting complains about other *.hi 
files being accessed! For example when building 
`stage1/libraries/mtl/build/Control/Monad/RWS/Class.o` we get the following 
dependencies from ghc:

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
libraries/mtl/Control/Monad/RWS/Class.hs

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
_build/stage1/lib/../lib/x86_64-linux-ghc-8.9.20190325/base-4.13.0.0/Prelude.hi

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
_build/stage1/lib/../lib/x86_64-linux-ghc-8.9.20190325/base-4.13.0.0/Data/Monoid.hi

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
_build/stage1/lib/../lib/x86_64-linux-ghc-8.9.20190325/transformers-0.5.5.0/Control/Monad/Trans/RWS/Strict.hi

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
_build/stage1/lib/../lib/x86_64-linux-ghc-8.9.20190325/transformers-0.5.5.0/Control/Monad/Trans/RWS/Lazy.hi

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
_build/stage1/lib/../lib/x86_64-linux-ghc-8.9.20190325/transformers-0.5.5.0/Control/Monad/Trans/Identity.hi

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
_build/stage1/lib/../lib/x86_64-linux-ghc-8.9.20190325/transformers-0.5.5.0/Control/Monad/Trans/Maybe.hi

_build/stage1/libraries/mtl/build/Control/Monad/RWS/Class.o : 
_build/stage1/lib/../lib/x86_64-linux-ghc-8

Re: Discussion: Hadrian's defaults

2019-03-15 Thread Andrey Mokhov
Hi Arnaud,

Great to hear you've been using Hadrian for a while and like it! 

As others have already pointed, -c used to be default. I personally was always 
inclined to run boot and configure by default, because to me they seem like an 
unnecessary complication on the way to the first GHC build (they confused me a 
lot when I did my first GHC build). On the other hand, people who strongly 
oppose -c being default are all expert users of configure, and should be 
capable of passing --skip-configure when need be (or always).

It's good to discuss this and see what proportion of GHC developers would 
prefer to include -c by default. So far the opponents were much more vocal.

Making --freeze1 default is probably fine. If we go this way, there should be a 
big warning in the documentation saying that this default setting is convenient 
but unsafe, i.e. can produce wrong binaries.

I think --share is not ready to become default. Hopefully, it will be in 1-2 
months!

Cheers,
Andrey


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


RE: --share option for hadrian doesn't work with hs-boot files

2019-02-22 Thread Andrey Mokhov
Hi Matt,

Thanks! Switching branches that add/remove hs-boot files is exactly the kind of 
scenario which is hard to predict :)

This looks like a bug, so please create a ticket. If you manage to reproduce 
this somehow without switching branches, e.g. by just adding or removing an 
hs-boot file, that would make it easier to debug.

> Could you please write down some advice Andrey about
> how to solve issues like this? It seems very fragile making
> sure that every case is covered.

Shake 0.17.6 has the following two commands that may help to partially clean up 
the cache in presence of such bugs:

  --share-listList the shared cache files.
  --share-remove[=SUBSTRING]  Remove the shared cache keys.

By running Hadrian with

--share-remove=_build/stage0/compiler/build/Var*

you should be able to evict the corresponding build rules from the cache and 
hopefully the build will go through. If this does help, please also mention 
this in the ticket.

Cheers,
Andrey

From: Matthew Pickering [mailto:matthewtpicker...@gmail.com]
Sent: 22 February 2019 08:53
To: GHC developers ; Andrey Mokhov 

Subject: --share option for hadrian doesn't work with hs-boot files

I have been trying the new `--share` option implemented in hadrian but I 
haven't actually managed to
complete any builds yet with it enabled after the initial one.

The current error is

```
: error:
‘Var.AnonArgFlag’ is exported by the hs-boot file, but not exported by the 
module
Error when running Shake build system:
  at action, called at src/Rules.hs:35:19 in main:Rules
  at need, called at src/Rules.hs:52:5 in main:Rules
* Depends on: _build/stage0/bin/ghc
  at need, called at src/Utilities.hs:71:18 in main:Utilities
* Depends on: _build/stage0/compiler/build/libHSghc-8.9.a
  at need, called at src/Rules/Library.hs:118:5 in main:Rules.Library
* Depends on: _build/stage0/compiler/build/Var.o
* Raised the exception:
user error (Development.Shake.cmd, system command failed
```

I get this after building Simon's `FunTy` patch which does add this flag and 
the definition to `Var.hs-boot` and then switching back to master with the 
cache enabled.

Could you please write down some advice Andrey about how to solve issues like 
this? It seems very fragile making sure that every case is covered.

Cheers,

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


RE: Distributed local dev builds

2019-02-17 Thread Andrey Mokhov
Hi Julian,

Have a look at this MR: https://gitlab.haskell.org/ghc/ghc/merge_requests/317

As soon as it lands, you'll be able to run Hadrian builds with a local cache as 
follows:

hadrian/build --shared=path/to/cache

In this mode, build rules are cached, and if you happen to rerun a build rule 
with unchanged dependencies the resulting files will be copied from the cache 
instead of executing actual build commands.

This should significantly speed up switching between branches.

Note however that this does not give you a way to run distributed builds: at 
the moment it is not possible to offload any build rules to other machines.

Cheers,
Andrey

--

Message: 1
Date: Sun, 17 Feb 2019 13:36:40 +1100
From: Julian Leviston 
To: GHC developers 
Subject: Distributed local dev builds
Message-ID: <86d5d29a-8839-4d0f-907f-029b626b5...@leviston.net>
Content-Type: text/plain; charset=utf-8

Hi all,

I have several fairly high-spec machines on my network where I usually build 
GHC, and I was wondering if it was easy/trivial/possible to set up a 
distributed build where it farmed out some of the compute work to the other 
machines? I seem to need to build from scratch somewhat often when I switch 
branches I'm working on.

Is this going to be the aim of distributed shake, which hadrian is based on?

Thanks!
Julian


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


RE: Cannot build with Hadrian

2019-02-09 Thread Andrey Mokhov
Hi Eric,

Good to hear you managed to build GHC both with Make and Hadrian.

Best wishes with your first GHC patch!

Cheers,
Andrey

From: Eric Crockett [mailto:ecrocke...@gmail.com]
Sent: 09 February 2019 18:21
To: Andrey Mokhov 
Subject: Re: Cannot build with Hadrian

Andrey,
I had already deleted the folder and tried again with make, which was 
successful. But since I sent the email, I figured I'd try again with hadrian as 
well. I followed exactly what I did above (which is what I did the first time, 
too) and it worked fine. *shrug*

Thanks anyway!
Eric

On Sat, Feb 9, 2019 at 5:03 AM Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>> wrote:
Hi Eric,

Can you show the contents of the "libffi-tarballs" directory in your GHC tree?

This error says it expects exactly one libffi tarball to be there, but it got 
either 0 or more than 1. I guess there is just no tarball there in your case.

Perhaps git clone failed to complete properly?

Cheers,
Andrey

--

Message: 3
Date: Fri, 8 Feb 2019 21:57:03 -0800
From: Eric Crockett mailto:ecrocke...@gmail.com>>
To: ghc-devs mailto:ghc-devs@haskell.org>>
Subject: Cannot build with Hadrian
Message-ID:

mailto:kbdwgb1mlawgicsjok6unvhchy%2bulb...@mail.gmail.com>>
Content-Type: text/plain; charset="utf-8"

GHC newcomer here -- attempting to work on my first patch.

I decided to try Hadrian, but ran into a problem.

I think I obtained the source using
> git clone --recursive https://gitlab.haskell.org/ghc/ghc
Then:
> ./boot && ./configure
> hadrian/build.sh -j --flavour=devel2

This ran for maybe 15 minutes, then showed the error below. Apparently I
ended up with too many tarballs? Any suggestions?

Thanks,
Eric

...

 ...

| Run Ghc CompileCWithGhc Stage1: rts/Inlines.c =>
> _build/stage1/rts/build/c/Inlines.thr_o
> | Run Cc FindCDependencies Stage1: rts/Compact.cmm =>
> _build/stage1/rts/build/cmm/Compact.o.d
> | Run Cc FindCDependencies Stage1: rts/PathUtils.c =>
> _build/stage1/rts/build/c/PathUtils.o.d
> | Run Ghc CompileHs Stage1: rts/Compact.cmm =>
> _build/stage1/rts/build/cmm/Compact.o
> | Run Ghc CompileCWithGhc Stage1: rts/PathUtils.c =>
> _build/stage1/rts/build/c/PathUtils.o
> | Remove file _build/stage1/rts/build/libHSrts-1.0.a
> | Run Ar Pack Stage1: _build/stage1/rts/build/c/Adjustor.o (and 113 more)
> => _build/stage1/rts/build/libHSrts-1.0.a
> /usr/bin/ar: creating _build/stage1/rts/build/libHSrts-1.0.a
> /---\
> | Successfully built library 'rts' (Stage1, way v). |
> | Library: _build/stage1/rts/build/libHSrts-1.0.a   |
> \---/
> | Remove file _build/stage1/rts/build/libHSrts-1.0_thr.a
> | Run Ar Pack Stage1: _build/stage1/rts/build/c/Adjustor.thr_o (and 115
> more) => _build/stage1/rts/build/libHSrts-1.0_thr.a
> /usr/bin/ar: creating _build/stage1/rts/build/libHSrts-1.0_thr.a
> /-\
> | Successfully built library 'rts' (Stage1, way thr). |
> | Library: _build/stage1/rts/build/libHSrts-1.0_thr.a |
> \-/
> | Copy file: _build/generated/ghcplatform.h =>
> _build/stage1/rts/build/ghcplatform.h
> | Copy file: _build/generated/ghcversion.h =>
> _build/stage1/rts/build/ghcversion.h
> | Copy file: _build/generated/DerivedConstants.h =>
> _build/stage1/rts/build/DerivedConstants.h
> | Copy file: _build/generated/ghcautoconf.h =>
> _build/stage1/rts/build/ghcautoconf.h
> | Remove directory _build/stage1/libffi/build
> shakeArgsWith0.000s0%
> Function shake   0.005s0%
> Database read0.000s0%
> With database0.000s0%
> Running rules  548.377s   99%  =
> Total  548.383s  100%
> Error when running Shake build system:
>   at src/Rules.hs:(35,19)-(52,17):
>   at src/Rules.hs:52:5-17:
> * Depends on: _build/stage1/lib/package.conf.d/rts-1.0.conf
>   at src/Rules/Register.hs:(94,9)-(98,34):
> * Depends on: _build/stage1/rts/build/ffi.h
>   at src/Rules/Libffi.hs:(49,7)-(52,48):
> * Depends on: _build/stage1/rts/build/ffi.h
> _build/stage1/rts/build/ffitarget.h
>   at src/Rules/Libffi.hs:52:13-48:
> * Depends on: _build/stage1/libffi/build/inst/lib/libffi.a
>   at src/Hadrian/Builder.hs:70:5-23:
> * Depends on: _build/stage1/libffi/build/Makefile
>   at src/Rules/Libffi.hs:107:9-27:
> * Depends on: _build/stage1/libffi/build/Makefile.in
> * Raised the exception:
> Exactly one LibFFI tarball is expected
> CallStack (from HasCallStack):
>   error, called at src/Hadrian/Utilities.hs:60:27 in main:Hadrian.Utilities
-- next part --
An HTML attachment was scrubbed...
URL: 
<ht

RE: Thoughts on the Contributing page

2019-01-30 Thread Andrey Mokhov
Andreas, Alp:

> > - On windows build.bat defaults to stack which I think has never 
> > worked on my box.
> Andrey? (cc'd him)

Actually `build.bat` calls the Cabal-based build script. This was a relatively 
recent change, and we plan to stick to it in the long term, while still 
providing an alternative `build.stack.bat`.

> There are also a few quality of life issues like ctrl+c not canceling 
> the build on windows.
> Which I hope will be resolved at some point but not sure if these 
> should be showstoppers.

Indeed. I hope it's not difficult to fix this, but I'm not sure where to start. 
Any suggestions are very welcome.

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


Re: Hadrian questions

2019-01-27 Thread Andrey Mokhov
Hi Richard,

First of all, thank you trying Hadrian and generating several new bug reports. 
This is very helpful!

> I think it would be very convenient to make a script we can all install (in 
> our PATH) that will
> search for hadrian's build.sh and run it. Then, we can just say `build` (or 
> whatever we name
> the script) anywhere in a tree. Of course, I could just do this locally, but 
> I doubt I'm the only
> one who would enjoy it.

This sounds like a good feature request to me. Could you please add it on Trac, 
so it's not lost?

> Also, I just had a look at 
> https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/doc/testsuite.md,
> and I don't see a way to run just one directory of the testsuite. I use that 
> ability currently quite
> often (because I know that I've mucked with the typechecker, so I just run 
> the typecheck tests 
> before doing full CI). Is this possible?

Yes, this should be possible. I believe Alp is currently working on the 
testsuite with the goal of fully matching the functionality provided by the 
Make build system. I think this feature is already on his list, but I'm CC-ing 
him just in case.

Cheers,
Andrey


Date: Fri, 25 Jan 2019 08:18:08 -0500
From: Richard Eisenberg 
To: Matthew Pickering 
Cc: GHC 
Subject: Re: Hadrian questions

Maybe I'm just lazy, but would it be possible to shorten these? Specifically, 
could there be a root-level file `build` that triggers Hadrian? That way, I 
could just say ./build instead of hadrian/build.sh.

Actually, even that isn't quite right. It is common, for example, for me to be 
deep in the testsuite, trying to fix a test. I twiddle something (say, the 
output file), and then I want to rerun the test. But now I have to go back out 
to the root of my tree to run the test, no? So: I think it would be very 
convenient to make a script we can all install (in our PATH) that will search 
for hadrian's build.sh and run it. Then, we can just say `build` (or whatever 
we name the script) anywhere in a tree. Of course, I could just do this 
locally, but I doubt I'm the only one who would enjoy it.

Also, I just had a look at 
https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/doc/testsuite.md, and I 
don't see a way to run just one directory of the testsuite. I use that ability 
currently quite often (because I know that I've mucked with the typechecker, so 
I just run the typecheck tests before doing full CI). Is this possible?

Thanks for all the work on this!
Richard

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


RE: [ANNOUNCE] You should try Hadrian

2019-01-27 Thread Andrey Mokhov
Hi Tamar,

Here is the relevant bullet point from the README:

> On Windows, if you do not want to install MSYS, you can
> use the Stack-based build script (Stack provides a managed
> MSYS environment), as described in these instructions.
> If you don't mind installing MSYS yourself or already have it,
> you can use the Cabal-based build script.

As you can see, `doc/windows.md` is recommended for people who “do not want to 
install MSYS”. Perhaps, the wording is not clear enough – please feel free to 
suggest improvements.

> In order for ./boot and configure to work already you need to
> be in an msys2 environment.

Yes, and Stack provides it. This means, if you follow instructions in this 
file, you don’t need to install MSYS yourself.

> There's a dubious claim there that using stack is
> "more robust", what is this claim based on?

This claim is based on my experience. Installing the MSYS environment has never 
worked out smoothly for me. Doing this via Stack was indeed more robust 
(especially, when struggling with building GHC on Windows CI!). Has this been 
different in your experience?

> I'm just confused when it was decided to switch the defaults,
> and why, without any consultation.

I’m not sure what you mean. Could you clarify? The file `doc/windows.md` is 3 
years old and hasn’t changed much since creation. The default build script 
`build.bat` currently uses Cabal:

```
rem By default on Windows we build Hadrian using Cabal
hadrian/build.cabal.bat %*
```

P.S.: I’ve just noticed that `doc/windows.md` hasn’t been updated when moving 
to GitLab, and created this MR to fix this:

https://gitlab.haskell.org/ghc/ghc/merge_requests/239

Please jump into the comments there if you’d like me to fix/clarify anything.

Thanks for reaching out!

Cheers,
Andrey

From: Phyx [mailto:loneti...@gmail.com]
Sent: 27 January 2019 21:11
To: Andrey Mokhov ; Ben Gamari 

Cc: GHC developers 
Subject: Re: [ANNOUNCE] You should try Hadrian

Hi Andrey,

I'm looking at https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/README.md 
and https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/doc/windows.md
wondering why the default instructions for Windows are using stack, this isn't 
currently the case.

In order for ./boot and configure to work already you need to be in an msys2 
environment. So having stack install its own, un-updated msys2 is not a 
workflow I would recommend.

There's a dubious claim there that using stack is "more robust", what is this 
claim based on?
I'm just confused when it was decided to switch the defaults, and why, without 
any consultation.

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


[ANNOUNCE] You should try Hadrian

2019-01-24 Thread Andrey Mokhov
Dear GHC developers,

Summary: You should try to use Hadrian as the GHC build system, because it will 
(hopefully!) become the default around GHC 8.8.

What is Hadrian and how can I try it?
=

Hadrian is a new build system for GHC written in Haskell. It lives in the 
directory "hadrian" in the GHC tree, and we have been actively developing it in 
the past year to reach feature and correctness parity with the existing 
Make-based build system. While we haven't quite reached this goal (more on this 
below), Hadrian is already working well and we run Hadrian jobs alongside the 
Make ones in our CI pipelines since the recent move to GitLab.

At this point, we would like to encourage everyone to try using Hadrian for 
their usual GHC development tasks. Hadrian's documentation resides in GHC's 
source tree, and below are the documents you will be most interested in:


*https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/README.md: The 
root of Hadrian's documentation. It explains the basics and points to more 
specific documents where appropriate.



*https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/doc/make.md: A 
cheatsheet-style document for GHC developers used to the Make build system 
(that is, most/all of you), showing equivalent Make/Hadrian commands for many 
tasks.


*
https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/doc/user-settings.md: A 
description of the "user settings" mechanism in Hadrian, which is where you can 
customise the build flavour, choose the packages to build, add 
file/package/platform-specific command line flags, etc.


*
https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/doc/testsuite.md: A 
description of the "test" rule and all the options it supports.

The documentation can surely be improved, so please do not hesitate to send us 
feedback and suggestions here, or even better on Trac: make sure you choose the 
component "Build System (Hadrian)" when creating a new ticket.

You need Hadrian


Hadrian is new, requires time to learn, and still has rough edges, but it has 
been developed to make your lives better. Here are a few advantages of Hadrian 
over the Make-based build system:

1) Hadrian is more reliable.

Hadrian can capture build dependencies more accurately, which means you rarely 
(if ever) need to do a clean rebuild.

2) Hadrian is faster.

Hadrian is faster for two reasons: (i) more accurate build dependencies, (ii) 
tracking of file contents instead of file modification times. Both allow you to 
avoid a lot of unnecessary rebuilds. Building Hadrian itself may take a while 
but needs to be done only once.

3) Hadrian is easier to understand and modify.

You no longer need to deal with Make's global namespace of mutable string 
variables. Hadrian is written in the language you love; it has modules, types 
and pure functions.


If you come across a situation where Hadrian is worse than the Make build 
system in any of the above aspects, this is a bug and you should report it.

Helping Hadrian
===

The best way to help is to try Hadrian, and let us know how it goes, what 
doesn't work, what's missing for you, what you think should be easier, and so 
on. Below is a list of known issues that we are in the process of fixing or 
that we will be tackling soon:


*Stage 2 GHC should be dynamically linked most of the time, but it 
never is, currently. See https://ghc.haskell.org/trac/ghc/ticket/15837

*There are about a dozen of failing tests in the GHC testsuite, some 
related to #15837.

*Binary distributions haven't been thoroughly tested on many platforms 
(only some Linux flavours). There will definitely be some issues here. For 
example, the binary distribution rule currently fails on Windows: 
https://ghc.haskell.org/trac/ghc/ticket/16073.

*There is no "validate" rule yet, only "test", but we have all the 
pieces to make this happen and it has a very high priority.

*There are issues with building cross compilers: see 
https://ghc.haskell.org/trac/ghc/ticket/16051.

We are likely missing some features compared to the Make build system, but none 
of them should take a lot of time to implement at this point. If you spot one, 
let us know! We'll do our best to implement it (or help you do it) as soon as 
we can. It is useful to look at the existing Hadrian tickets before submitting 
new ones, to make sure that the issue or idea that you would like to talk about 
hasn't been brought up yet: 
https://ghc.haskell.org/trac/ghc/query?status=!closed=Build+System+(Hadrian).

Of course, we welcome your code contributions too! Several GHC developers have 
a good understanding of Hadrian codebase and will be able to help you. To find 
their names, have a look at the list of recent Hadrian commits: 
https://gitlab.haskell.org/ghc/ghc/commits/master/hadrian. As you can see, 
Hadrian is actively developed by many people, and we hope 

RE: Hadrian build failed

2018-11-01 Thread Andrey Mokhov
Hello Yotam,

Could you please report this as a bug on GHC Trac?

https://ghc.haskell.org/trac/ghc/wiki/ReportABug

I couldn’t quickly reproduce your issue, however, I run into another seemingly 
unrelated problem.

P.S.: Note that build instructions in my blog post got slightly out of date 
after the Hadrian move – I’ve fixed this.

Cheers,
Andrey

 Forwarded Message 
Subject:

Hadrian build failed

Date:

Thu, 1 Nov 2018 20:33:14 +0200

From:

Yotam Ohad 

To:

ghc-devs@haskell.org


Hi,
I'm trying to build with hadrian 
(https://blogs.ncl.ac.uk/andreymokhov/building-ghc-on-windows/)
I get an error when running: stack exec hadrian -- --directory ".." -j 
--flavour=quickest --configure

md5sum: 'standard input': no properly formatted MD5 checksum lines found

ERROR: mingw-w64-x86_64-crt-git-5.0.0.4795.e3d96cb1-1-any.pkg.tar.xz appears to 
be corrupted, please delete it and try again.
)
Deleting and trying again results in the same error. Any idea on how to solve 
this?

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


RE: Coordinating the Hadrian merge

2018-10-16 Thread Andrey Mokhov
Thanks Alp and Ben!

I fully agree with you. Let's go ahead.

Ben: I guess you'll do the actual merge -- feel free to do this whenever you 
like.

> How should we handle ticket tracking post-merge? The easiest option
> would probably be to keep the existing tickets on GitHub and ask that
> new tickets be reported via Trac.

Yes, this sounds good. 

Cheers,
Andrey

-Original Message-
From: Ben Gamari [mailto:b...@well-typed.com] 
Sent: 16 October 2018 02:33
To: Andrey Mokhov ; Alp Mestanogullari 

Cc: GHC developers 
Subject: RE: Coordinating the Hadrian merge

Andrey Mokhov  writes:

> Hi Ben,
>
> Yes, I'm fine to merge, but we should make it clear that Hadrian
> should not be used just yet:
>
> 1) It is currently broken due to some recent changes in GHC.
>
> 2) Alp made tremendous progress with fixing the testsuite failures, but there 
> are still some failures left.
>
> 3) There are a few usability requests by Simon Marlow that we need to address.
>
>> In the past we discussed squashing the project's early history
>> however I've had very little luck doing this cleanly
>
Sure, I'm happy to make it clear that things are still in flux and that
there are known weaknesses. That being said, I'm not sure it helps to
active discourage use. Afterall, there will be little incentive for
others to help find and fix the remaining issues unless there are users.

> Ouch, it would be a bit grim to merge all those early commits. On the
> other hand, I looked at commits at the middle of Hadrian's history and
> they look quite sensible, just overly fine-grained. So, even if we
> could somehow squash the early history, that probably wouldn't give us
> much saving in terms of the commit count -- it would still be more
> than 1K.
>
Right; given that GHC itself has more than 50k commits I'm not terribly
concerned about Hadrian's contribution.

How should we handle ticket tracking post-merge? The easiest option
would probably be to keep the existing tickets on GitHub and ask that
new tickets be reported via Trac.

Cheers,

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


RE: Coordinating the Hadrian merge

2018-10-15 Thread Andrey Mokhov
Hi Ben,

Yes, I'm fine to merge, but we should make it clear that Hadrian should not be 
used just yet:

1) It is currently broken due to some recent changes in GHC.

2) Alp made tremendous progress with fixing the testsuite failures, but there 
are still some failures left.

3) There are a few usability requests by Simon Marlow that we need to address.

> In the past we discussed squashing the project's early history
> however I've had very little luck doing this cleanly

Ouch, it would be a bit grim to merge all those early commits. On the other 
hand, I looked at commits at the middle of Hadrian's history and they look 
quite sensible, just overly fine-grained. So, even if we could somehow squash 
the early history, that probably wouldn't give us much saving in terms of the 
commit count -- it would still be more than 1K. 

P.S.: Don't forget to switch off commit notifications when you do the merge ;-)

Cheers,
Andrey

-Original Message-
From: Ben Gamari [mailto:b...@well-typed.com] 
Sent: 15 October 2018 23:14
To: Andrey Mokhov ; Alp Mestanogullari 

Cc: GHC developers 
Subject: Coordinating the Hadrian merge

Hi Andrey and Alp,

Before ICFP we concluded that we will merge Hadrian into the GHC tree.
This unfortunately took a back-seat priority-wise while I sorted out
various release things but I think we are now in a position to make this
happen.

Andrey, would you be okay with my merging Hadrian as-is into the GHC
tree? In the past we discussed squashing the project's early history
however I've had very little luck doing this cleanly (primarily due to
the difficulty of rebasing in the presence of merge commits)

After merging there will be a period where we flush the pull request
queue but I don't anticipate this causing much trouble.

Cheers,

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


RE: Hadrian

2018-09-04 Thread Andrey Mokhov
Thanks Simon,

I fixed the "verboseCommands" typo.

Regarding various available predicates: indeed, we don't currently have a 
comprehensive description -- I've opened an issue for this and will hopefully 
fix it soon.

In the meanwhile, there are a few examples of predicates in the rest of the 
doc/user-settings.md document, for example here: 
https://github.com/snowleopard/hadrian/blob/master/doc/user-settings.md#command-line-arguments.

The `input` and `output` predicates accept Shake's `FilePattern` as parameters 
-- see the documentation for it here: 

https://hackage.haskell.org/package/shake-0.16.4/docs/Development-Shake.html#v:-63--61--61-

Cheers,
Andrey

-Original Message-
From: Simon Peyton Jones [mailto:simo...@microsoft.com] 
Sent: 04 September 2018 16:49
To: Andrey Mokhov ; Alp Mestanogullari 

Cc: ghc-devs 
Subject: RE: Hadrian

Very confusingly
https://github.com/snowleopard/hadrian/blob/master/doc/user-settings.md#verbose-command-lines

speaks about verboseCommmands PLURAL, whereas it should say verboseCommand 
SINGLUAR.

Moreover, what is the language things you can say (i.e. where is it 
documented).  The "//" business, and what patterns can occur. What things other 
than "//" can you have?  What about 'input' etc?

Simon

|  -Original Message-
|  From: Andrey Mokhov 
|  Sent: 30 August 2018 12:26
|  To: Simon Peyton Jones ; Alp Mestanogullari
|  
|  Cc: ghc-devs 
|  Subject: RE: Hadrian
|  
|  Simon,
|  
|  If you want to see all command lines, you can pass '--verbose' or '-V'
|  flag to Hadrian and it will then print out everything it does.
|  
|  But you can also choose which particular command lines to print in
|  UserSettings, see:
|  
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2Fdoc%2Fuser-
|  settings.md%23verbose-command-
|  linesdata=02%7C01%7Csimonpj%40microsoft.com%7C0c6118a504f74269efd508
|  d60e6b4fe7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63671225140342623
|  1sdata=tMYhmIGMeVbBYjAtxWQTY5%2F4Kyfc4m981N4OTowGkbQ%3Dreserved
|  =0
|  
|  So, you can do:
|  
|  verboseCommand = input "//GHC/Real.hs"
|  
|  Or, alternatively,
|  
|  verboseCommand = output "//GHC/Real.hi"
|  
|  Both should produce the same result (in theory).
|  
|  In general, we have the following documents on Hadrian:
|  
|  The README:
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2FREADME.mddata=02%7C01%7
|  Csimonpj%40microsoft.com%7C0c6118a504f74269efd508d60e6b4fe7%7C72f988bf86f
|  141af91ab2d7cd011db47%7C1%7C0%7C636712251403426231sdata=7WigmQG7lbDd
|  eyhYCSaKOQEb0eeZcn0iXAbAKdwZ5A4%3Dreserved=0
|  How to use UserSettings:
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2Fdoc%2Fuser-
|  settings.mddata=02%7C01%7Csimonpj%40microsoft.com%7C0c6118a504f74269
|  efd508d60e6b4fe7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63671225140
|  3426231sdata=tRu2lO%2F6TNV3ao5tzNKO%2FAHJMWsxKX%2BqExHn78nuCvU%3D
|  p;reserved=0
|  An overview of build flavours:
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2Fdoc%2Fflavours.mddata=0
|  2%7C01%7Csimonpj%40microsoft.com%7C0c6118a504f74269efd508d60e6b4fe7%7C72f
|  988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636712251403426231sdata=Esye
|  DdAKLV9DC3PUwkqsuQ4zGoOYKcaJeEov1BAH8lU%3Dreserved=0
|  
|  I hope the more Hadrian gets used, the more complete the documentation
|  will become.
|  
|  Cheers,
|  Andrey
|  
|  From: Simon Peyton Jones [mailto:simo...@microsoft.com]
|  Sent: 30 August 2018 12:19
|  To: Simon Peyton Jones ; Alp Mestanogullari
|  ; Andrey Mokhov 
|  Cc: ghc-devs 
|  Subject: RE: Hadrian
|  
|  Sigh.  As an inconvenient workaround, I tried adding {-# OPTIONS_GHC -
|  dverbose-core2core #-} to GHC.Real, and then doing
|      cabal new-run hadrian -- -c -j4 --flavour=quick --directory=".."
|  in hadrian/
|  That did recompile GHC.Real - but all the debug output disappeared!
|  I tried adding {-# OPTIONS_GHC -ddebug-output #-} as well, but that
|  didn't work.
|  I'm stuck - any ideas?
|  Simon
|  
|  From: ghc-devs  On Behalf Of Simon Peyton
|  Jones via ghc-devs
|  Sent: 30 August 2018 12:12
|  To: Alp Mestanogullari ; Andrey Mokhov
|  
|  Cc: ghc-devs 
|  Subject: Hadrian
|  
|  Alp, Andrey
|  The old build system printed out every command line; and I often copy-
|  paste that info to build single modules.
|  Eg currently, when trying to understand #15570 I see a suspicious
|  GHC.Real.hi.  So I want to manually recompile GHC.Real (from base),
|  adding some debug flags.  How can I get the right command line to do that
|  from the build log?
|  Where is the "how to use Hadrian" wiki page?  I know you've been writing
|  one.
|  Simon
_

RE: Hadrian

2018-08-30 Thread Andrey Mokhov
> How do I "pass --verbose to Hadrian"?

Like this:

cabal new-run hadrian -- -c -j4 --flavour=quick --directory=".." -V

Everything after "--" in this command line are flags passed to Hadrian. 
Everything before are flags passed to Cabal. (I hope we'll fix the "build.sh" 
script for you soon, so you don't need to go via Cabal.)

I just tried this with {-# OPTIONS_GHC -dverbose-core2core #-} and this did 
also print out a lot of Core. And a lot more stuff (somehow this seems to cause 
further recompilation).


> https://ghc.haskell.org/trac/ghc/wiki/Building/Hadrian/QuickStart

Artem -- thanks! I forgot to mention this wiki page, which indeed looks 


Cheers,
Andrey

-Original Message-
From: Simon Peyton Jones [mailto:simo...@microsoft.com] 
Sent: 30 August 2018 13:00
To: Andrey Mokhov ; Alp Mestanogullari 

Cc: ghc-devs 
Subject: RE: Hadrian

|  If you want to see all command lines, you can pass '--verbose' or '-V'
|  flag to Hadrian and it will then print out everything it does.

But I am not invoking Hadrian.  I am saying (on your instructions)

cabal new-run hadrian -- -c -j4 --flavour=quick --directory=".."

How do I "pass --verbose to Hadrian"?


|  -Original Message-
|  From: Andrey Mokhov 
|  Sent: 30 August 2018 12:26
|  To: Simon Peyton Jones ; Alp Mestanogullari
|  
|  Cc: ghc-devs 
|  Subject: RE: Hadrian
|  
|  Simon,
|  
|  If you want to see all command lines, you can pass '--verbose' or '-V'
|  flag to Hadrian and it will then print out everything it does.
|  
|  But you can also choose which particular command lines to print in
|  UserSettings, see:
|  
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2Fdoc%2Fuser-
|  settings.md%23verbose-command-
|  linesdata=02%7C01%7Csimonpj%40microsoft.com%7C0c6118a504f74269efd508
|  d60e6b4fe7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63671225140342623
|  1sdata=tMYhmIGMeVbBYjAtxWQTY5%2F4Kyfc4m981N4OTowGkbQ%3Dreserved
|  =0
|  
|  So, you can do:
|  
|  verboseCommand = input "//GHC/Real.hs"
|  
|  Or, alternatively,
|  
|  verboseCommand = output "//GHC/Real.hi"
|  
|  Both should produce the same result (in theory).
|  
|  In general, we have the following documents on Hadrian:
|  
|  The README:
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2FREADME.mddata=02%7C01%7
|  Csimonpj%40microsoft.com%7C0c6118a504f74269efd508d60e6b4fe7%7C72f988bf86f
|  141af91ab2d7cd011db47%7C1%7C0%7C636712251403426231sdata=7WigmQG7lbDd
|  eyhYCSaKOQEb0eeZcn0iXAbAKdwZ5A4%3Dreserved=0
|  How to use UserSettings:
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2Fdoc%2Fuser-
|  settings.mddata=02%7C01%7Csimonpj%40microsoft.com%7C0c6118a504f74269
|  efd508d60e6b4fe7%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C63671225140
|  3426231sdata=tRu2lO%2F6TNV3ao5tzNKO%2FAHJMWsxKX%2BqExHn78nuCvU%3D
|  p;reserved=0
|  An overview of build flavours:
|  https://na01.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.c
|  om%2Fsnowleopard%2Fhadrian%2Fblob%2Fmaster%2Fdoc%2Fflavours.mddata=0
|  2%7C01%7Csimonpj%40microsoft.com%7C0c6118a504f74269efd508d60e6b4fe7%7C72f
|  988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636712251403426231sdata=Esye
|  DdAKLV9DC3PUwkqsuQ4zGoOYKcaJeEov1BAH8lU%3Dreserved=0
|  
|  I hope the more Hadrian gets used, the more complete the documentation
|  will become.
|  
|  Cheers,
|  Andrey
|  
|  From: Simon Peyton Jones [mailto:simo...@microsoft.com]
|  Sent: 30 August 2018 12:19
|  To: Simon Peyton Jones ; Alp Mestanogullari
|  ; Andrey Mokhov 
|  Cc: ghc-devs 
|  Subject: RE: Hadrian
|  
|  Sigh.  As an inconvenient workaround, I tried adding {-# OPTIONS_GHC -
|  dverbose-core2core #-} to GHC.Real, and then doing
|      cabal new-run hadrian -- -c -j4 --flavour=quick --directory=".."
|  in hadrian/
|  That did recompile GHC.Real - but all the debug output disappeared!
|  I tried adding {-# OPTIONS_GHC -ddebug-output #-} as well, but that
|  didn't work.
|  I'm stuck - any ideas?
|  Simon
|  
|  From: ghc-devs  On Behalf Of Simon Peyton
|  Jones via ghc-devs
|  Sent: 30 August 2018 12:12
|  To: Alp Mestanogullari ; Andrey Mokhov
|  
|  Cc: ghc-devs 
|  Subject: Hadrian
|  
|  Alp, Andrey
|  The old build system printed out every command line; and I often copy-
|  paste that info to build single modules.
|  Eg currently, when trying to understand #15570 I see a suspicious
|  GHC.Real.hi.  So I want to manually recompile GHC.Real (from base),
|  adding some debug flags.  How can I get the right command line to do that
|  from the build log?
|  Where is the "how to use Hadrian" wiki page?  I know you've been writing
|  one.
|  Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Hadrian

2018-08-30 Thread Andrey Mokhov
Simon,

If you want to see all command lines, you can pass '--verbose' or '-V' flag to 
Hadrian and it will then print out everything it does.

But you can also choose which particular command lines to print in 
UserSettings, see:

https://github.com/snowleopard/hadrian/blob/master/doc/user-settings.md#verbose-command-lines
 

So, you can do:

verboseCommand = input "//GHC/Real.hs"

Or, alternatively, 

verboseCommand = output "//GHC/Real.hi"

Both should produce the same result (in theory).

In general, we have the following documents on Hadrian: 

The README: https://github.com/snowleopard/hadrian/blob/master/README.md 
How to use UserSettings: 
https://github.com/snowleopard/hadrian/blob/master/doc/user-settings.md 
An overview of build flavours: 
https://github.com/snowleopard/hadrian/blob/master/doc/flavours.md 

I hope the more Hadrian gets used, the more complete the documentation will 
become.

Cheers,
Andrey

From: Simon Peyton Jones [mailto:simo...@microsoft.com] 
Sent: 30 August 2018 12:19
To: Simon Peyton Jones ; Alp Mestanogullari 
; Andrey Mokhov 
Cc: ghc-devs 
Subject: RE: Hadrian

Sigh.  As an inconvenient workaround, I tried adding {-# OPTIONS_GHC 
-dverbose-core2core #-} to GHC.Real, and then doing
    cabal new-run hadrian -- -c -j4 --flavour=quick --directory=".."
in hadrian/
That did recompile GHC.Real - but all the debug output disappeared!
I tried adding {-# OPTIONS_GHC -ddebug-output #-} as well, but that didn't work.
I'm stuck - any ideas?
Simon

From: ghc-devs  On Behalf Of Simon Peyton Jones 
via ghc-devs
Sent: 30 August 2018 12:12
To: Alp Mestanogullari ; Andrey Mokhov 

Cc: ghc-devs 
Subject: Hadrian

Alp, Andrey
The old build system printed out every command line; and I often copy-paste 
that info to build single modules.
Eg currently, when trying to understand #15570 I see a suspicious GHC.Real.hi.  
So I want to manually recompile GHC.Real (from base), adding some debug flags.  
How can I get the right command line to do that from the build log?
Where is the "how to use Hadrian" wiki page?  I know you've been writing one.
Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: Observation on Hadrian's relative performance re current

2017-11-17 Thread Andrey Mokhov
Hi Herbert,

Thanks for the careful performance experiment! Can you please put all the 
details into the issue tracker so they don't get lost?

We have a couple of performance issues open, and we know that there are 
performance bugs in Hadrian leading to too sequential build (a recent example 
is #464), but we haven't had time to optimise Hadrian yet.

In any case it's good to know where we stand right now. I hope you'll be 
willing to repeat your experiment once these bugs are fixed.

Cheers,
Andrey

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


[ANNOUNCE] Hadrian update

2017-11-15 Thread Andrey Mokhov
Dear GHC developers,

As some of you might have already noticed, Hadrian has finally been merged into 
the GHC tree. However it's not yet time to celebrate - there are still many 
issues that need to be addressed before the Make-based build system may retire.

Have a look at the README if you'd like a quick try: 
https://github.com/ghc/ghc/tree/master/hadrian.

Here is a quick update on the on-going development:

1) Hadrian can build GHC and can already be used as part of the CI 
infrastructure. However, the resulting binary does not pass the validation. 
Zhen Zhang is looking into this, but more help is needed. See 
https://github.com/snowleopard/hadrian/issues/299.

2) A major refactoring by Moritz Angermann is on the way. Moritz is primarily 
interested in cross compilation, but to make it work he had to get rid of the 
ghc-cabal utility, reorganise the build tree, and make numerous other 
improvements to Hadrian. See https://github.com/snowleopard/hadrian/pull/445.

3) There is currently no support for binary distribution. Ben Gamari is looking 
into this issue: https://github.com/snowleopard/hadrian/issues/219.

4) Dynamic linking on Windows is not implemented. Tamar Christina has kindly 
offered help with this: https://github.com/snowleopard/hadrian/issues/343.

5) Hadrian source code is still not fully documented and tested, and generally 
requires some polishing. I am currently taking care of this when not distracted 
by urgent bug fixes and will appreciate your help in making Hadrian easier to 
understand and use.

I can't believe that we seem to approach the finish line! It's been a long, 
tedious but also interesting project. Thank you all for helping us get this 
far, and I hope we'll celebrate the switch from Make to Hadrian soon.

Cheers,
Andrey

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


RE: Building the docs, again

2017-11-01 Thread Andrey Mokhov
> Maybe Hadrian will help here?

Hadrian can build documentation in various formats but the current 
implementation is very coarse-grain: we either build all possible docs or no 
docs at all. It would be relatively easy to add more fine-grain documentation 
targets and modes. If someone could design/describe the requirements in a 
ticket that would be great.

Cheers,
Andrey


From: Simon Peyton Jones [mailto:simo...@microsoft.com]
Sent: 01 November 2017 08:28
To: Iavor Diatchki <iavor.diatc...@gmail.com>; ghc-devs@haskell.org; Andrey 
Mokhov <andrey.mok...@newcastle.ac.uk>
Subject: RE: Building the docs, again

It is quite confusing that we can be setting the same variable to different 
values in different places.   It would also be quite helpful if we modified the 
Makefile to say `documentation build target is disabled` or some such, rather 
then going ahead and building the whole of GHC, only at the end to inform me 
that it doesn't know what is `html`.
Maybe Hadrian will help here?

Simon

From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Iavor Diatchki
Sent: 31 October 2017 21:49
To: ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>
Subject: Re: Building the docs, again

Hello,

never mind, I figured it out---apparently the build targets were disabled for 
the `quick` flavor, which I was using.

It is quite confusing that we can be setting the same variable to different 
values in different places.   It would also be quite helpful if we modified the 
Makefile to say `documentation build target is disabled` or some such, rather 
then going ahead and building the whole of GHC, only at the end to inform me 
that it doesn't know what is `html`.

-Iavor



On Tue, Oct 31, 2017 at 2:26 PM Iavor Diatchki 
<iavor.diatc...@gmail.com<mailto:iavor.diatc...@gmail.com>> wrote:
Hello,

sometime ago, I asked if it is possible to build just the GHC docs, without 
building the compiler.  I was told to just run `make html`.  This does not 
appear to work, the command seems to just start building GHC.  What am I doing 
wrong?

Here is the output I see, running the command from the root of the GHC tree.

> make html V=0
===--- building phase 0
make --no-print-directory -f 
ghc.mk<https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fghc.mk=02%7C01%7Csimonpj%40microsoft.com%7Cf681d88b258e48157e2008d520a95302%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636450833981966485=qPWSl5FMtQ%2FRzTI8PYxHfkK%2B%2FltgBh2z1VRr8dJleok%3D=0>
 phase=0 phase_0_builds
make[1]: Nothing to be done for 'phase_0_builds'.
===--- building phase 1
make --no-print-directory -f 
ghc.mk<https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fghc.mk=02%7C01%7Csimonpj%40microsoft.com%7Cf681d88b258e48157e2008d520a95302%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636450833981966485=qPWSl5FMtQ%2FRzTI8PYxHfkK%2B%2FltgBh2z1VRr8dJleok%3D=0>
 phase=1 phase_1_builds
  HC [stage 0] compiler/stage1/build/BufWrite.o
  HC [stage 0] compiler/stage1/build/Pretty.o
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/PprColour.o
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/Outputable.o
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/Json.o
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/SrcLoc.o
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/BasicTypes.o
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/Unique.o
  HC [stage 0] compiler/stage1/build/Packages.o-boot
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/FiniteMap.o
compilation IS NOT required
  HC [stage 0] compiler/stage1/build/Name.o-boot

(then I interrupted it).

Also, in 
`mk/config.mk<https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fconfig.mk=02%7C01%7Csimonpj%40microsoft.com%7Cf681d88b258e48157e2008d520a95302%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636450833981966485=F9gkJnWKkFVjF0ZgraTEyQXPnOA4Id2lL7jhppN1mrc%3D=0>`
 I see this:
BUILD_SPHINX_HTML= YES

-Iavor



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


RE: Hadrian

2017-10-20 Thread Andrey Mokhov
Hi Moritz and Herbert,

Thank you for detailed comments! We clearly need to carefully think through our 
options for merging Hadrian.

Can I invite you both and everyone else to continue the discussion in 
https://github.com/snowleopard/hadrian/issues/440? Long email threads tend to 
become hard to read/follow and get lost. 

In my view, the two most important requirements in the long term are:

1) Preserving the commit/issue/pull-request history. A GHC developer fighting a 
strange build failure should be able to find a relevant discussion not only now 
but in 5 years from now. This may be solved via documentation, i.e. gradually 
moving all discussions from GitHub to docs/comments. That's a lot of hard work.

2) Making it convenient for GHC developers to work on Hadrian. To me, git 
submodules are not convenient at all, but maybe there is just no other option 
given the requirement (1). Is git subtree a solution? 

Cheers,
Andrey

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


RE: Hadrian

2017-10-19 Thread Andrey Mokhov
Hi Ben,

> Well, the GitHub repo will still exist. Is that enough?

Yes, but I think I'll need to do some clean up in the code so that it's obvious 
where to look for answers. For example, here is a random comment from a Hadrian 
source file:

-- Objdump is only required on OpenBSD and AIX, as mentioned in #211.

The reader might confuse this with GHC ticket #211, so I guess this should be 
replaced with a full link https://github.com/snowleopard/hadrian/issues/211. 
There may be other potential pitfalls, but hopefully nothing difficult to 
handle.

I've created an issue to discuss and prepare for the merge: 
https://github.com/snowleopard/hadrian/issues/440. 

Cheers,
Andrey

-Original Message-
From: Ben Gamari [mailto:b...@well-typed.com] 
Sent: 19 October 2017 21:50
To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>; Boespflug, Mathieu 
<m...@tweag.io>
Cc: Jonas Pfenniger Chevalier <jonas.cheval...@tweag.io>; Manuel M T 
Chakravarty <manuel.chakrava...@tweag.io>; ghc-devs <ghc-devs@haskell.org>
Subject: RE: Hadrian

Andrey Mokhov <andrey.mok...@newcastle.ac.uk> writes:

> Thanks Ben,
>
> Just to clarify: By history I mean not just commits, but GitHub issues
> and PRs as well -- together they contain a lot of valuable interlinked
> information for GHC/Hadrian developers.
>
Well, the GitHub repo will still exist. Is that enough?

Cheers,

- Ben

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


RE: Hadrian

2017-10-19 Thread Andrey Mokhov
Thanks Ben,

Just to clarify: By history I mean not just commits, but GitHub issues and PRs 
as well -- together they contain a lot of valuable interlinked information for 
GHC/Hadrian developers. 

> That is pretty much precisely the use-case which
> git subtree was designed to address. This will allow us to have Hadrian,
> with history, in the GHC tree and you can continue to develop it on
> GitHub until things have stabilized.

Sounds great. I haven't used git subtrees before, so I'll need to do some 
reading, but if everyone is happy with merging Hadrian as is, I can prepare a 
patch over the weekend!

Cheers,
Andrey

-Original Message-
From: Ben Gamari [mailto:b...@well-typed.com] 
Sent: 19 October 2017 20:50
To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>; Boespflug, Mathieu 
<m...@tweag.io>
Cc: Manuel M T Chakravarty <manuel.chakrava...@tweag.io>; Moritz Angermann 
<moritz.angerm...@gmail.com>; Jonas Pfenniger Chevalier 
<jonas.cheval...@tweag.io>; ghc-devs <ghc-devs@haskell.org>
Subject: RE: Hadrian

Andrey Mokhov <andrey.mok...@newcastle.ac.uk> writes:

> Hi Mathieu,
>
> Yes, in principle we can merge right now, as long as it's clear that Hadrian 
> still requires more work before taking over.
>
> My only concern is that merging will make it more difficult for us to
> quickly iterate on Hadrian: the GitHub workflow is more convenient (at
> least for me) than the Phabricator one. Perhaps, we can keep Hadrian
> on GitHub as a submodule? This also has the advantage that we can keep
> all existing references to GitHub issues/PRs without migrating
> everything to GHC Trac. It would be very unfortunate to lose all
> history during the merge.
>
Okay, so if we want to preserve history then I would suggest that we go
the subtree route. That is pretty much precisely the use-case which
git subtree was designed to address. This will allow us to have Hadrian,
with history, in the GHC tree and you can continue to develop it on
GitHub until things have stabilized. The only question is how to ensure
that the subtree remains up-to-date.

Cheers,

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


RE: Hadrian

2017-10-19 Thread Andrey Mokhov
Hi Mathieu,

Yes, in principle we can merge right now, as long as it's clear that Hadrian 
still requires more work before taking over.

My only concern is that merging will make it more difficult for us to quickly 
iterate on Hadrian: the GitHub workflow is more convenient (at least for me) 
than the Phabricator one. Perhaps, we can keep Hadrian on GitHub as a 
submodule? This also has the advantage that we can keep all existing references 
to GitHub issues/PRs without migrating everything to GHC Trac. It would be very 
unfortunate to lose all history during the merge.

Cheers,
Andrey

-Original Message-
From: Boespflug, Mathieu [mailto:m...@tweag.io] 
Sent: 19 October 2017 19:21
To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>
Cc: Ben Gamari <b...@well-typed.com>; Manuel M T Chakravarty 
<manuel.chakrava...@tweag.io>; Moritz Angermann <moritz.angerm...@gmail.com>; 
Jonas Pfenniger Chevalier <jonas.cheval...@tweag.io>; ghc-devs 
<ghc-devs@haskell.org>
Subject: Re: Hadrian

Hi all,

As a user who tried to be an early adopter of Hadrian, I can attest to
Andrey's remarks about GHC progress sometimes (frequently?) breaking
Hadrian.

Ben, Andrey - how about this strawman proposal:

we merge Hadrian into GHC *now*, not because ./validate with Hadrian
works (it doesn't yet), but because the build of GHC succeeds with
Hadrian. The resulting compiler might well be garbage. But that's fine
- we can iterate in the official ghc repo, all the while knowing that
CI has our back if ever some change makes Hadrian no longer even build
a compiler. Once ./validate passes with Hadrian, the guarantee that CI
gives will become stronger still: we'll know if any change would make
the Hadrian-produced compiler garbage again.

Maybe that does sound totally bonkers to you? :) Maybe it's radical,
but sounds to me like the best way to get the benefit *now* of
ensuring Make and Hadrian move forward in lock step thanks to CI.

The above all assumes that we're committed to Hadrian being the future
of GHC's build system. But I take it that's a given by now.

Best,

Mathieu


On 19 October 2017 at 19:05, Andrey Mokhov
<andrey.mok...@newcastle.ac.uk> wrote:
> Hi Ben, Manuel and all,
>
> Ben has already covered most questions in his answer, but let me add a couple 
> of comments.
>
>> So, Mathieu had the clever idea that having the two build system in
>> GHC side-by-side and then build in CI both ways might be a good way of
>> making sure that keep constant tabs on Hadian and get a clear (and
>> continuous picture) of where it is and what is missing.
>
> It would be great to build every GHC commit both by Make and Hadrian. Not 
> only this would allow to monitor the readiness of Hadrian, it would also make 
> it easier for us to catch up with changes in GHC and the Make build system. 
> At the moment, Hadrian is frequently broken by changes in GHC/Make and we 
> need to do detective work of figuring out which commit broke what and fix 
> Hadrian accordingly. These fixes are trivial in many cases (e.g. adding a new 
> flag to one of the builders) so GHC developers would probably be able to 
> easily mirror these changes in Hadrian if only their commits were marked as 
> Hadrian-breaking by the common CI.
>
>> In other words, why can’t we have Hadrian *today*?
>
> I'd say the biggest issue is #299 -- i.e. making sure that the GHC built by 
> Hadrian passes validation. At the moment we still have 100-200 unexpected 
> failures, most of which probably have to do with outdated command line flags 
> (GHC's build system continuously evolves and it wasn't possible to keep track 
> of all flag changes over time, so there are certainly some differences in 
> Hadrian that lead to validation failures). This is where help is currently 
> needed.
>
> Cheers,
> Andrey
>
> -Original Message-
> From: Ben Gamari [mailto:b...@well-typed.com]
> Sent: 19 October 2017 15:08
> To: Manuel M T Chakravarty <manuel.chakrava...@tweag.io>
> Cc: Mathieu Boespflug <m...@tweag.io>; Moritz Angermann 
> <moritz.angerm...@gmail.com>; Jonas Pfenniger Chevalier 
> <jonas.cheval...@tweag.io>; Andrey Mokhov <andrey.mok...@newcastle.ac.uk>
> Subject: Re: Hadrian
>
> CCing Andrey and Zhen, who are the principle authors of Hadrian.
>
> Manuel M T Chakravarty <manuel.chakrava...@tweag.io> writes:
>
>> Hi Ben,
>>
>> I our exploration of cross-compilation for GHC and the CI integration,
>> we talked with Moritz and got to the topic of Hadrian. It seems that
>> there are few interdependent issues here, and I am really interested
>> in getting your take on them.
>>
>> * Hadrian is slated for inclusion for 8.4, but I couldn’t find any
>> tickets except #12599. Is this because Hadrian

RE: Hadrian status

2017-05-09 Thread Andrey Mokhov
Hi Ben and all,

I'm strongly in favour of switching GHC to Hadrian as soon as possible, because 
just keeping up with changes in GHC takes substantial effort. Zhen Zhang (in 
CC) has been recently helping me, and I hope he could make good progress 
towards this goal as part of his Summer of Haskell project (I believe he 
submitted an application).

Switching will likely be a painful process for GHC developers, because some of 
the usual workflows will inevitably break. We could keep both Make and Hadrian 
in the tree for some period of time, but maintaining two completely different 
build systems is only feasible for a short period of time.

Ben,

Could I ask you to go through the open issues 
(https://github.com/snowleopard/hadrian/issues) and tag them with the 
'tree-tremble' milestone if you think they must be implemented before the 
merge? I don't hack on GHC myself, so it's often difficult for me to judge the 
relative importance of features; it would be great if you could also tag the 
issues with priorities (I've just created tags high-/medium-/low-priority).

Everyone:

Please contribute to the discussions on the minimum set of features that 
Hadrian should support before it can replace Make in this thread: 
https://github.com/snowleopard/hadrian/issues/239. 
 
Cheers,
Andrey

-Original Message-
From: Ben Gamari [mailto:b...@well-typed.com] 
Sent: 09 May 2017 21:37
To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>
Cc: GHC developers <ghc-devs@haskell.org>
Subject: Hadrian status

Hi Andrey,

Given that 8.2.1 is finally starting to come together, now is probably a
good time to start reflecting on what will come in 8.4. I think it would
be great if we could finally get Hadrian into the tree for the 8.4
release. It would be even better if we could flip over to Hadrian as the
primary build system. However, if we are to do this then I think we
should leave plenty of time to iron out the inevitable bugs that will
arise.

Have you given much thought to the schedule post-8.2? Do you think a
complete switch-over will be feasible?

Cheers,

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


RE: Build time over travis time limit again

2017-02-09 Thread Andrey Mokhov
Joachim, Ben,

I gave it a try on my machine. 

First of all, we currently need "--flavour=quick" instead of "quickest" because 
the latter builds only vanilla RTS.

If I do:

./build.bat -j --flavour=quick
./build.bat -j --flavour=quick validate

Then the testsuite completes, but I get a lot of errors, particularly in 
"ghci/", "perf/" and "th/". Most of them can probably be fixed relatively 
easily in Hadrian, but this requires a good understanding of which GHC features 
these tests actually depend on. I'll create an issue in the Hadrian repo to 
track down these testsuite failures and will CC you.

Cheers,
Andrey


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


RE: Build time over travis time limit again

2017-02-08 Thread Andrey Mokhov
Hi Joachim,

> Does Hadrian speed up a build from scratch?

Hadrian can build GHC on Windows (AppVeyor) and Linux (Travis) CI instances in 
about 40 mins using the 'quickest' build flavour (no optimisation/docs). 

https://ci.appveyor.com/project/snowleopard/hadrian
https://travis-ci.org/snowleopard/hadrian

On Travis OSX we recently started to time out (jobs are terminated at 48 mins), 
even though I'm using another trick to save build time on OSX: building with 
the --integer-simple flag, which skips building the GMP library.

Cheers,
Andrey

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


Hadrian update

2017-02-05 Thread Andrey Mokhov
Hello everyone,

This is a quick update on the current state of Hadrian, the new build system 
for GHC (https://github.com/snowleopard/hadrian).

Current status


We've been slowly but steadily fixing issues, and are getting close to the 
stage where GHC-devs can start using Hadrian in their everyday development, 
perhaps at first alongside Make as a fallback option.

Here are key remaining issues and what we plan to do about them:

* Build rules for distribution and installation are not fully implemented. I 
don't understand very well the requirements for these build rules and plan to 
spend some time with Simon Marlow to complete the implementation in March. If 
anyone can do this earlier, feel free to volunteer, I'm happy to help.

* Ability to build stage1 GHC only. This is a quick fix on Hadrian's side but 
is currently blocked by Shake refactoring. Neil Mitchell is working on this.

* Hadrian can't build GHC in the dynamic way. Jose Calderon has bravely taken 
up the challenge to fix this oldest surviving ticket (#4).

There are a lot of other minor issues and continuous refactoring, but I think 
the above three are most important. If I missed anything, please let me know.

How to help
==

1) One of the simplest way to help the project is to try Hadrian and report any 
issues you encounter. To try it, clone it into your GHC tree and run it using 
"hadrian/build.sh" or "hadrian/build.bat", adding "-j --flavour=quickest" to 
speed things up. See the README for more details:

https://github.com/snowleopard/hadrian

2) Whenever you are doing any changes in the GHC that affect the build system, 
please CC me (@snowleopard) to the corresponding Phab differential. This can 
save me a lot of time when Hadrian breaks because of changes in GHC.

3) Email me if you have time to write some code or docs for Hadrian - I'll find 
a good place to start with.

Cheers,
Andrey

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


Build GHC on Windows using Hadrian and Stack

2016-09-01 Thread Andrey Mokhov
Hi all,

Summary: Building GHC on Windows using Hadrian and Stack got even simpler - see 
https://github.com/snowleopard/hadrian/blob/master/doc/windows.md.


To build GHC on Windows you usually need to jump through a lot of hoops [1], 
which may be confusing even for experienced GHC developers [2].

Hadrian to the rescue!

Hadrian, a new build system for GHC that I've been developing [3], is written 
in Haskell and can therefore be built and run via Stack that can install 
appropriate bootstrapping GHC and MSYS2 environment in an automated and robust 
way. This was first pointed out by Neil Mitchell [4], and I've recently 
simplified build instructions even further. Here are all the steps:

git clone --recursive git://git.haskell.org/ghc.git
cd ghc
git clone git://github.com/snowleopard/hadrian
cd hadrian
stack setup
stack exec -- pacman -S autoconf automake-wrapper make patch tar --noconfirm
stack build
stack exec hadrian -- --directory ".." -j --flavour=quickest

See more details here: 
https://github.com/snowleopard/hadrian/blob/master/doc/windows.md.

NB: Hadrian can build Stage2 GHC, but there are still many limitations [5]. 
Help make it better!

[1] https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows
[2] https://mail.haskell.org/pipermail/ghc-devs/2016-June/012340.html
[3] https://github.com/snowleopard/hadrian
[4] http://neilmitchell.blogspot.co.uk/2016/03/compiling-ghc-on-windows.html
[5] https://github.com/snowleopard/hadrian#current-limitations

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


RE: msys2 64 bit: help help!

2016-06-27 Thread Andrey Mokhov
Hi Simon,

> 3. After this step, starting a shell failed altogether with 
> "c:/msys64/mingw64_shell.bat is
> not recognised as an internal or external command". And sure enough, there is 
> no such file.
> Presumably it existed in step 1.  So perhaps step 2 deleted it?
> [...]
> 4. As you mention, I then tried msys2_shell.cmd.  It worked -- with a 
> noticeable delay of 5
> seconds or so.

I've also just got a new Win10 laptop and had the same issue with missing 
mingw64_shell.bat during msys2 install. I solved it by creating mingw64.bat 
with the following contents:

msys2_shell.cmd -mingw64 -mintty

I deleted all old shortcuts and use this script instead. Everything seems to 
work fine -- can build GHC.

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


RE: Fwd: Is anything being done to remedy the soul crushing compile times of GHC?

2016-02-18 Thread Andrey Mokhov
Thomas Tuegel  writes:

> I think what Andrey meant was, the first time we run the pre-processors,
> cache the locations of all the files that need to be pre-processed. On
> subsequent runs, we only need to check pre-processors the files in the cache.

Yes, something along the lines. Although I don't fully understand Herbert's 
comment, so I decided to open an issue about this so we could discuss this 
without spamming the ghc-devs mailing list:

https://github.com/snowleopard/shaking-up-ghc/issues/210

Herbert, Thomas, and all -- I'd appreciate your input!

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


Re: Fwd: Is anything being done to remedy the soul crushing compile times of GHC?

2016-02-18 Thread Andrey Mokhov
Thomas Tuegel  writes:

> > What exactly does the pre-process phase do, anyways?

> It runs the appropriate pre-processor (Alex, Happy, c2hs, etc.) for modules
> that require it. It's slow because of the way the process is carried out: For
> each module in the package description, Cabal tries to find an associated .hs
> source file in the hs-source-dirs. If it cannot, it looks for a file with an
> extension matching one of the pre-processors it knows about. If it finds one,
> it runs the corresponding program if the output files are missing or outdated.

Interesting! In the new Shake-based build system we also need to automagically 
generate .hs files using Alex et al. My first implementation was slow but then 
I realised that it is possible to scan the source tree only once and remember 
where all .hs/.x/etc files are. This brought down the complexity from quadratic 
to linear in my case -- maybe this could be reused in cabal too?

By the way, there seem to be a fair amount of code & functionality overlap in 
cabal and the new build system. We might want to look into this once the build 
system becomes more stable.

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


RE: [ANNOUNCE] Shaking up GHC

2016-01-30 Thread Andrey Mokhov
Simon & all,

> Why not just make the 'validate' script invoke the shake build system
> (instead of 'make') when you say 'sh validate --shake'?  That would be
> simple, wouldn't it? So shake builds GHC, and then 'validate' invokes
> 'make test' (or whatever) to run the testsuite.
>   
> Little things like this would significantly increase uptake I think!

We can now run:

shake-build/build.sh validate

This will rebuild stage2 GHC, ghc-pkg and hpc if need be, and will then run GHC 
tests by executing `make fast` in `testsuite/tests` folder 
(https://github.com/snowleopard/shaking-up-ghc#testing). 

There is still a lot of work to add proper support for various useful command 
line settings like `TEST=abc` or `TEST_HC=xyz`.

It would be great if someone could add support for `--shake` command line flag 
to the `validate` script, as Simon suggested. This would be a better solution, 
but I'm not confident enough to edit the validate script myself.

Thanks to Thomas Miedema for his patient guidance on how GHC test suite works.

Cheers,
Andrey

> -Original Message-
> From: Simon Peyton Jones [mailto:simo...@microsoft.com]
> Sent: 26 January 2016 08:55
> To: Andrey Mokhov; Ben Gamari
> Cc: ghc-devs@haskell.org
> Subject: RE: [ANNOUNCE] Shaking up GHC
> 
> |  That's correct. Note though that the two build systems put (some)
> |  build results in the same directories, e.g. inplace/bin/ghc-stage1,
> so
> |  there is some interaction between them. In future it would be
> possible
> |  to decouple them completely (if need be).
> 
> Documenting this side-by-side possibility on the home page would be
> very helpful to up-take.
> 
> |  > How can I do that using Shake to build?  Maybe
> |  >  sh validate --shake --fast --no-clean
> |  > or something?  Just modifying the validate script to make it
> |  >convenient to use shake for the build part would be great.
> |
> |  This may be possible precisely because binaries are where validate
> |  expects them to be. I tried to pull this off, but unsuccessfully so
> |  far (validate starts rebuilding everything from scratch with make).
> I
> |  think the reason is that we changed some naming conventions for
> |  directories (using stageN instead of dist, dist-boot, dist-install),
> |  so validate can't find some utils. I'll let you know if I find a
> |  workaround.
> 
> Why not just make the 'validate' script invoke the shake build system
> (instead of 'make') when you say 'sh validate --shake'?  That would be
> simple, wouldn't it?  So shake builds GHC, and then 'validate' invokes
> 'make test' (or whatever) to run the testsuite.
>   
> Little things like this would significantly increase uptake I think!
> 
> Simon
> 
> 
> 
> |
> |  Ben,
> |
> |  > > But User.hs is a source file, which we shouldn't normally modify
> |  > > lest we accidentally commit it. Could we have a non-source file
> to
> |  > > modify (rather like
> |  > >
> |  https://na01.safelinks.protection.outlook.com/?url=build.mk=01%
> |  > >
> |  7c01%7csimonpj%40064d.mgd.microsoft.com%7c7f0edcff3c78490bd0e808d325
> |  > >
> |  be4774%7c72f988bf86f141af91ab2d7cd011db47%7c1=8L%2b7QWlhbAwUnY
> |  > > fAfCEwTXTC2PUMd17m1ceCcD2TE%2fU%3d being based on
> build.mk.sample)
> |  > >
> |  > One way around this would be to add User.hs to .gitignore. That
> way
> |  > git will ignore changes to this files when you `git commit -a`.
> You
> |  > can still, however, commit changes to it if you ask git
> explicitly.
> |
> |  Yes, I was thinking about the same idea.
> |
> |  Cheers,
> |  Andrey
> |
> |  -Original Message-
> |  From: Simon Peyton Jones [mailto:simo...@microsoft.com]
> |  Sent: 25 January 2016 12:14
> |  To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>; ghc-
> |  d...@haskell.org
> |  Cc: Neil Mitchell <ndmitch...@gmail.com>; Simon Marlow
> |  <marlo...@gmail.com>
> |  Subject: RE: [ANNOUNCE] Shaking up GHC
> |
> |  Very good.
> |
> |  As I understand it, it can work side-by-side with the existing build
> |  system, correct?  That means we don't need to make an either/or
> |  choice, which is very helpful.
> |
> |  Every day I do
> | sh validate --fast --no-clean
> |  How can I do that using Shake to build?  Maybe
> | sh validate --shake --fast --no-clean
> |  or something?  Just modifying the validate script to make it
> |  convenient to use shake for the build part would be great.
> |
> |  You say: The make-based build system uses mk/build.mk to specify
> user
> |  build settings. We use src/Settings/User.hs for the same purpose.
> Feel
> |  free to experiment following the Haddock comme

RE: [ANNOUNCE] Shaking up GHC

2016-01-27 Thread Andrey Mokhov
Simon,

> Documenting this side-by-side possibility on the home page
> would be very helpful to up-take.

Indeed. I added a note on this at the very top of the README.

> Why not just make the 'validate' script invoke the shake build
> system (instead of 'make') when you say 'sh validate --shake'? 
> That would be simple, wouldn't it?  So shake builds GHC, and
> then 'validate' invokes 'make test' (or whatever) to run the testsuite.

Several quick attempts to reuse the validate script have failed, so I decided 
to start implementing a proper test rule in the new build system. (Note, I 
still rely on the old Python scripts for testing -- rewriting them seems to be 
a major undertaking.) The test rule does work for me on Windows, but the 
functionality is very limited at the moment. You can give it a try by running:

shake-build/build.sh test

This should run (some) tests. It shouldn't take long to make it more useful. I 
added a section on testing to the README: 
https://github.com/snowleopard/shaking-up-ghc#testing.

Cheers,
Andrey

-Original Message-
From: Simon Peyton Jones [mailto:simo...@microsoft.com] 
Sent: 26 January 2016 08:55
To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>; Ben Gamari 
<b...@smart-cactus.org>
Cc: ghc-devs@haskell.org
Subject: RE: [ANNOUNCE] Shaking up GHC

|  That's correct. Note though that the two build systems put (some)  
| build results in the same directories, e.g. inplace/bin/ghc-stage1, so  
| there is some interaction between them. In future it would be possible  
| to decouple them completely (if need be).

Documenting this side-by-side possibility on the home page would be very 
helpful to up-take.

|  > How can I do that using Shake to build?  Maybe
|  >sh validate --shake --fast --no-clean
|  > or something?  Just modifying the validate script to make it  
| >convenient to use shake for the build part would be great.
|  
|  This may be possible precisely because binaries are where validate  
| expects them to be. I tried to pull this off, but unsuccessfully so  
| far (validate starts rebuilding everything from scratch with make). I  
| think the reason is that we changed some naming conventions for  
| directories (using stageN instead of dist, dist-boot, dist-install),  
| so validate can't find some utils. I'll let you know if I find a  
| workaround.

Why not just make the 'validate' script invoke the shake build system (instead 
of 'make') when you say 'sh validate --shake'?  That would be simple, wouldn't 
it?  So shake builds GHC, and then 'validate' invokes 'make test' (or whatever) 
to run the testsuite.

Little things like this would significantly increase uptake I think!

Simon



|  
|  Ben,
|  
|  > > But User.hs is a source file, which we shouldn't normally modify  
| > > lest we accidentally commit it. Could we have a non-source file to  
| > > modify (rather like  > >  
| https://na01.safelinks.protection.outlook.com/?url=build.mk=01%
|  > >
|  7c01%7csimonpj%40064d.mgd.microsoft.com%7c7f0edcff3c78490bd0e808d325
|  > >
|  be4774%7c72f988bf86f141af91ab2d7cd011db47%7c1=8L%2b7QWlhbAwUnY
|  > > fAfCEwTXTC2PUMd17m1ceCcD2TE%2fU%3d being based on 
| build.mk.sample)  > >  > One way around this would be to add User.hs 
| to .gitignore. That way  > git will ignore changes to this files when 
| you `git commit -a`. You  > can still, however, commit changes to it 
| if you ask git explicitly.
|  
|  Yes, I was thinking about the same idea.
|  
|  Cheers,
|  Andrey
|  
|  -Original Message-
|  From: Simon Peyton Jones [mailto:simo...@microsoft.com]
|  Sent: 25 January 2016 12:14
|  To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>; ghc-  
| d...@haskell.org
|  Cc: Neil Mitchell <ndmitch...@gmail.com>; Simon Marlow  
| <marlo...@gmail.com>
|  Subject: RE: [ANNOUNCE] Shaking up GHC
|  
|  Very good.
|  
|  As I understand it, it can work side-by-side with the existing build  
| system, correct?  That means we don't need to make an either/or  
| choice, which is very helpful.
|  
|  Every day I do
|   sh validate --fast --no-clean
|  How can I do that using Shake to build?  Maybe
|   sh validate --shake --fast --no-clean  or something?  Just modifying 
| the validate script to make it  convenient to use shake for the build 
| part would be great.
|  
|  You say: The make-based build system uses mk/build.mk to specify user  
| build settings. We use src/Settings/User.hs for the same purpose. Feel  
| free to experiment following the Haddock comments.
|  
|  But User.hs is a source file, which we shouldn't normally modify lest  
| we accidentally commit it.  Could we have a non-source file to modify  
| (rather like  
| https://na01.safelinks.protection.outlook.com/?url=build.mk=01%7c
|  
| 01%7csimonpj%40064d.mgd.microsoft.com%7c7f0edcff3c78490bd0e808d325be47
|  
| 74%7c72f988bf86f141af91ab2d7cd011db47%7c1=8L%2b7QWlhbAwU

RE: [ANNOUNCE] Shaking up GHC

2016-01-25 Thread Andrey Mokhov
Simon,

> As I understand it, it can work side-by-side with the existing build
> system, correct?  That means we don't need to make an either/or
> choice, which is very helpful.

That's correct. Note though that the two build systems put (some) build results 
in the same directories, e.g. inplace/bin/ghc-stage1, so there is some 
interaction between them. In future it would be possible to decouple them 
completely (if need be).

> How can I do that using Shake to build?  Maybe
>   sh validate --shake --fast --no-clean
> or something?  Just modifying the validate script to make it
> convenient to use shake for the build part would be great.

This may be possible precisely because binaries are where validate expects them 
to be. I tried to pull this off, but unsuccessfully so far (validate starts 
rebuilding everything from scratch with make). I think the reason is that we 
changed some naming conventions for directories (using stageN instead of dist, 
dist-boot, dist-install), so validate can't find some utils. I'll let you know 
if I find a workaround. Otherwise we'll just have to wait for the proper 
implementation of the "test" target in the new build system. Maybe it's not too 
difficult to implement.

Ben,

> > But User.hs is a source file, which we shouldn't normally modify lest 
> > we accidentally commit it. Could we have a non-source file to modify 
> > (rather like build.mk being based on build.mk.sample)
> >
> One way around this would be to add User.hs to .gitignore. That way git
> will ignore changes to this files when you `git commit -a`. You can still,
> however, commit changes to it if you ask git explicitly.

Yes, I was thinking about the same idea. 

Cheers,
Andrey

-Original Message-
From: Simon Peyton Jones [mailto:simo...@microsoft.com] 
Sent: 25 January 2016 12:14
To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>; ghc-devs@haskell.org
Cc: Neil Mitchell <ndmitch...@gmail.com>; Simon Marlow <marlo...@gmail.com>
Subject: RE: [ANNOUNCE] Shaking up GHC

Very good.

As I understand it, it can work side-by-side with the existing build system, 
correct?  That means we don't need to make an either/or choice, which is very 
helpful.

Every day I do
sh validate --fast --no-clean
How can I do that using Shake to build?  Maybe
sh validate --shake --fast --no-clean
or something?  Just modifying the validate script to make it convenient to use 
shake for the build part would be great.

You say: The make-based build system uses mk/build.mk to specify user build 
settings. We use src/Settings/User.hs for the same purpose. Feel free to 
experiment following the Haddock comments.

But User.hs is a source file, which we shouldn't normally modify lest we 
accidentally commit it.  Could we have a non-source file to modify (rather like 
build.mk being based on build.mk.sample)

Simon

|  -Original Message-
|  From: Andrey Mokhov [mailto:andrey.mok...@newcastle.ac.uk]
|  Sent: 22 January 2016 14:27
|  To: ghc-devs@haskell.org
|  Cc: Simon Peyton Jones <simo...@microsoft.com>; Neil Mitchell  
| <ndmitch...@gmail.com>; Simon Marlow <marlo...@gmail.com>
|  Subject: [ANNOUNCE] Shaking up GHC
|  
|  Dear GHC developers,
|  
|  I am happy to announce that the Shaking up GHC project has finally  
| reached the first milestone. The goal of the project is to design a  
| new GHC build system based on Shake that will eventually replace the  
| current make-based one. See the project page for more details:
|  https://github.com/snowleopard/shaking-up-ghc.
|  
|  There is still a long way until we can match the capabilities of the  
| current build system. At the moment we only build vanilla way.
|  Validation, documentation, build flavours and cross-compilation are  
| not yet implemented. Known limitations are listed here:
|  https://github.com/snowleopard/shaking-up-ghc#current-limitations.
|  
|  The purpose of this announcement is to attract alpha testers and  
| collect early feedback across multiple platforms and build  
| configurations. We already have several success reports on Linux, OS  
| X, Solaris and Windows. However, things will inevitably break and we  
| hope to catch and fix as many of these cases as possible with your  
| help. The instructions on how to try the new build system can be found
|  here: https://github.com/snowleopard/shaking-up-ghc#your-first-build.
|  
|  We plan to be ready to become a part of the GHC tree around 1 March  
| 2016, and catch up with the make build system around 1 June 2016. The  
| dates are tentative and depend on how much time it takes us to resolve  
| the remaining issues: https://github.com/snowleopard/shaking-up-
|  ghc/milestones.
|  
|  I would like thank everyone who contributed to this project so far:
|  Simon Peyton Jones, Neil Mitchell and Simon Marlow came up with the  
| idea and guided me throughout the project; Mo

RE: [ANNOUNCE] Shaking up GHC

2016-01-23 Thread Andrey Mokhov
Thanks David!

> Are there any plans as to how to include it in the GHC tree? Does it
> ship with all the libraries required to build the build system, will we
> have a mini-build system to bootstrap it? If I recall correctly, we rely
> on Cabal sandboxes on Linux/OSX and global Cabal library
> installations on Windows in order to run it.

The simplest way is to add the 'shake-build' folder to the GHC tree and
ask first adopters of the new build system to globally install the
dependencies (ansi-terminal, mtl, shake, QuickCheck). Then 'build.sh'
and 'build.bat' scripts should work.

I am open to suggestions on how to make this more convenient and
robust. I've never used anything more advanced than a global cabal
installation, so I'd appreciate input from more experienced users.

Could you create a ticket on github suggesting possible approaches?
I'm afraid our discussion may get lost in ghc-devs mailing list.

Many thanks!
Andrey

> From: David Luposchainsky 
> To: ghc-devs@haskell.org
> Subject: Re: [ANNOUNCE] Shaking up GHC
> Message-ID: <56a27eb1.1080...@gmail.com>
> Content-Type: text/plain; charset=windows-1252
>
> Great work Andrey!
>
> I'm actually (pleasantly) surprised this is becoming part of the GHC
> tree so soon
> .
>
> Are there any plans as to how to include it in the GHC tree? Does it
> ship with
> all the libraries required to build the build system, will we have a
> mini-build
> system to bootstrap it? If I recall correctly, we rely on Cabal
> sandboxes on
> Linux/OSX and global Cabal library installations on Windows in order to
> run it.
>
> Greetings,
> David
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: [ANNOUNCE] Shaking up GHC

2016-01-23 Thread Andrey Mokhov
Hi George,

I think you are hitting this bug: https://ghc.haskell.org/trac/ghc/ticket/11379.

Note, you don't have to use GHC HEAD as a bootstrapping compiler. I'm 
bootstrapping with GHC 7.10.1, for example.

Cheers,
Andrey

From: George Colpitts [mailto:george.colpi...@gmail.com]
Sent: 23 January 2016 13:36
To: Andrey Mokhov
Cc: dluposchain...@googlemail.com; GHC developers
Subject: Re: [ANNOUNCE] Shaking up GHC

with ghc 8.0.0.20160111, cabal install shake fails with
[43 of 47] Compiling Development.Shake.Args ( src/Development/Shake/Args.hs, 
dist/build/Development/Shake/Args.o )

src/Development/Shake/Args.hs:1:1: error:
solveWanteds: too many iterations (limit = 4)
  Unsolved: WC {wc_simple =
  [D] _ :: Eq a (CDictCan)
  [D] _ :: Ord a (CDictCan)
  [D] _ :: Read a (CDictCan)
  [D] _ :: Show a (CDictCan)
  [W] hole{a4gTO} :: a ~ a (CNonCanonical)
  [D] _ :: Eq a (CDictCan)}
  New superclasses found
  Set limit with -fconstraint-solver-iterations=n; n=0 for no limit

Is this a known problem?
Thanks

On Sat, Jan 23, 2016 at 9:05 AM, Andrey Mokhov 
<andrey.mok...@newcastle.ac.uk<mailto:andrey.mok...@newcastle.ac.uk>> wrote:
Thanks David!

> Are there any plans as to how to include it in the GHC tree? Does it
> ship with all the libraries required to build the build system, will we
> have a mini-build system to bootstrap it? If I recall correctly, we rely
> on Cabal sandboxes on Linux/OSX and global Cabal library
> installations on Windows in order to run it.

The simplest way is to add the 'shake-build' folder to the GHC tree and
ask first adopters of the new build system to globally install the
dependencies (ansi-terminal, mtl, shake, QuickCheck). Then 'build.sh'
and 'build.bat' scripts should work.

I am open to suggestions on how to make this more convenient and
robust. I've never used anything more advanced than a global cabal
installation, so I'd appreciate input from more experienced users.

Could you create a ticket on github suggesting possible approaches?
I'm afraid our discussion may get lost in ghc-devs mailing list.

Many thanks!
Andrey

> From: David Luposchainsky 
> <dluposchain...@googlemail.com<mailto:dluposchain...@googlemail.com>>
> To: ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>
> Subject: Re: [ANNOUNCE] Shaking up GHC
> Message-ID: <56a27eb1.1080...@gmail.com<mailto:56a27eb1.1080...@gmail.com>>
> Content-Type: text/plain; charset=windows-1252
>
> Great work Andrey!
>
> I'm actually (pleasantly) surprised this is becoming part of the GHC
> tree so soon
> .
>
> Are there any plans as to how to include it in the GHC tree? Does it
> ship with
> all the libraries required to build the build system, will we have a
> mini-build
> system to bootstrap it? If I recall correctly, we rely on Cabal
> sandboxes on
> Linux/OSX and global Cabal library installations on Windows in order to
> run it.
>
> Greetings,
> David

___
ghc-devs mailing list
ghc-devs@haskell.org<mailto: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: [ANNOUNCE] Shaking up GHC

2016-01-23 Thread Andrey Mokhov
Herbert,

> I think it's already quite convenient. After all, you're expected to
> have a minimum GHC bootstrapping environment anyway. So having the
> tools installed (as already do now, e.g. you need alex, happy, and
> ghc to be able to work on GHC).

I agree. Roughly, we are talking about going from:

cabal install alex happy

to:

cabal install alex happy ansi-terminal mtl shake QuickCheck

This doesn't look too onerous (although one could also consider
somehow packaging these dependencies together). And hopefully
upcoming cabal features will make this more robust.

Tuncer,

> My suggestion, and what I'd expect, is to make Shake part of
> GHC's included lib, just like process or xhtml.

This sounds like a very big decision which is beyond the Shaking
up GHC project. (I wouldn't want to shake up GHC too much!)

Cheers,
Andrey

> -Original Message-
> From: Herbert Valerio Riedel [mailto:hvrie...@gmail.com]
> Sent: 23 January 2016 17:14
> To: Andrey Mokhov
> Cc: dluposchain...@googlemail.com; GHC developers
> Subject: Re: [ANNOUNCE] Shaking up GHC
> 
> On 2016-01-23 at 14:05:56 +0100, Andrey Mokhov wrote:
> >> Are there any plans as to how to include it in the GHC tree? Does it
> >> ship with all the libraries required to build the build system, will
> we
> >> have a mini-build system to bootstrap it? If I recall correctly, we
> rely
> >> on Cabal sandboxes on Linux/OSX and global Cabal library
> >> installations on Windows in order to run it.
> >
> > The simplest way is to add the 'shake-build' folder to the GHC tree
> and
> > ask first adopters of the new build system to globally install the
> > dependencies (ansi-terminal, mtl, shake, QuickCheck). Then 'build.sh'
> > and 'build.bat' scripts should work.
> >
> > I am open to suggestions on how to make this more convenient and
> > robust. I've never used anything more advanced than a global cabal
> > installation, so I'd appreciate input from more experienced users.
> 
> I think it's already quite convenient. After all, you're expected to
> have a minimum GHC bootstrapping environment anyway. So having the
> tools
> installed (as already do now, e.g. you need alex, happy, and ghc to be
> able to work on GHC).
> 
> And the new cabal nix-store feature to show-case as tech-preview
> together with GHC 8.0 makes this even more robust by avoiding pkg-db
> breakages due to reinstalls, which would be the main reason not to
> rely on "global installed dependency".
> 
> The shake-build.sh script simply needs to invoke `cabal new-build` to
> generate the ghc shake build-tool executable.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: [ANNOUNCE] Shaking up GHC

2016-01-23 Thread Andrey Mokhov
Ben,

> Wouldn't
>   
> git clone git://github.com/snowleopard/shaking-up-ghc shake-build
> cabal install shake-build/
> 
> be sufficient?

As I understand, this will not take care of alex and happy? Although if
we list them as dependencies in shaking-up-ghc.cabal, that will indeed
be sufficient... I think it's a good idea :)

Cheers,
Andrey

> -Original Message-
> From: Ben Gamari [mailto:b...@smart-cactus.org]
> Sent: 23 January 2016 21:22
> To: Andrey Mokhov; Herbert Valerio Riedel; Tuncer Ayaz
> Cc: GHC developers
> Subject: RE: [ANNOUNCE] Shaking up GHC
> 
> Andrey Mokhov <andrey.mok...@newcastle.ac.uk> writes:
> 
> > Herbert,
> >
> >> I think it's already quite convenient. After all, you're expected to
> >> have a minimum GHC bootstrapping environment anyway. So having the
> >> tools installed (as already do now, e.g. you need alex, happy, and
> >> ghc to be able to work on GHC).
> >
> > I agree. Roughly, we are talking about going from:
> >
> > cabal install alex happy
> >
> > to:
> >
> > cabal install alex happy ansi-terminal mtl shake QuickCheck
> >
> Wouldn't
>   
> git clone git://github.com/snowleopard/shaking-up-ghc shake-build
> cabal install shake-build/
> 
> be sufficient?
> 
> Cheers,
> 
> - Ben

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


Re: FW: Shaking up GHC

2016-01-12 Thread Andrey Mokhov
Many thanks Eric,

I think you solved the mystery! I changed my address on the ghc-devs mailing 
list from andrey.mok...@ncl.ac.uk to andrey.mok...@newcastle.ac.uk (it's the 
same mailbox really). Hopefully this will go through this time.

Cheers,
Andrey

From: Eric Seidel 
To: ghc-devs@haskell.org
Subject: Re: FW: Shaking up GHC

I'm pretty sure you can only post to the list with the address you used
to subscribe.

According to https://mail.haskell.org/cgi-bin/mailman/roster/ghc-devs it
looks like Andrey is subscribed with

  andrey.mokhov at ncl.ac.uk

but the email you forwarded is from

  andrey.mokhov at newcastle.ac.uk

So that may be the issue.

Eric

On Tue, Jan 12, 2016, at 08:20, Simon Peyton Jones wrote:
> Dear ghc devs
> Can someone figure out how to help Andrey be able to post to this mailing
> list (ghc-devs)?  I thought anyone subscribed can post, but perhaps not.
> Thanks!
> Simon
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs