Re: GHC build time graphs

2016-02-13 Thread Karel Gardas

On 02/13/16 07:57 PM, Karel Gardas wrote:

On 02/12/16 09:02 PM, Reid Barton wrote:

btw, just recent experience on ARM64 (X-gene board):

bootstrapping 7.10.1 with 7.6.x took: ~120 minutes
bootstrapping 8.0.1 RC2 with 7.10.1 took: ~446 minutes

both run as: ./configure; time make -j8


It would be interesting to have the time for bootstrapping 7.10.1 with
7.10.1 too, for comparison.


boostrapping 7.10.1 with 7.10.1 took: ~212 minutes -- but this is not
comparable directly with numbers above since for whatever reason haddock
and doc is not build although I've used previous ./configure; time make
-j8.

Anyway, parallel make itself is not good to use here since the build
process may also contain some noise of paralellel make fixes and such.

I think more reliable benchmark may be simple build (single-threaded) of
ghc-cabal here. I'll see what I can do about that.


OK, so not everything is that bad. Benchmarking compilation of GHC 
7.10.1 ghc-cabal tool reveals:


GHC 7.6.3: ~12 minutes
GHC 7.10.1: ~24 minutes
GHC 8.0.1 RC2: ~14 minutes

Please note that GHC 7.6.3 compiles 89 files while GHC 7.10.1 and 8.0.1 
RC2 compile 90 files. Test done on the same x-gene board like the tests 
above for the reference...


Karel

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


Re: GHC build time graphs

2016-02-13 Thread Karel Gardas

On 02/12/16 09:02 PM, Reid Barton wrote:

btw, just recent experience on ARM64 (X-gene board):

bootstrapping 7.10.1 with 7.6.x took: ~120 minutes
bootstrapping 8.0.1 RC2 with 7.10.1 took: ~446 minutes

both run as: ./configure; time make -j8


It would be interesting to have the time for bootstrapping 7.10.1 with
7.10.1 too, for comparison.


boostrapping 7.10.1 with 7.10.1 took: ~212 minutes -- but this is not 
comparable directly with numbers above since for whatever reason haddock 
and doc is not build although I've used previous ./configure; time make -j8.


Anyway, parallel make itself is not good to use here since the build 
process may also contain some noise of paralellel make fixes and such.


I think more reliable benchmark may be simple build (single-threaded) of 
ghc-cabal here. I'll see what I can do about that.


Cheers,
Karel

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


Re: New type of expressions containing (error ...) includes noisy implicit parameter

2016-02-13 Thread Eric Seidel


On Sat, Feb 13, 2016, at 01:25, Ben Gamari wrote:
> Christopher Allen  writes:
> 
> > Prelude> let myList = [1, 2, 3 :: Integer]
> > Prelude> let myList' = myList ++ undefined
> > Prelude> :t myList
> > myList :: [Integer]
> > Prelude> :t myList'
> > myList' :: (?callStack::GHC.Stack.Types.CallStack) => [Integer]
> >
> ...
> > This isn't just a pedagogical problem, this is a UX problem. The users
> > don't _care_ that call stack information is being carried around. Why would
> > they? It happens without any mention in the types in almost every other
> > programming language.
> >
> Well, in the case of implicit call stacks users arguably *need* to care
> whether call stack information is carried around: you only get call
> stack information when you explicit request request one. This is one of
> the limitations of the implicit callstack mechanism.
> 
> That being said, the example that you offer is a bit suspicious to the
> point where I suspect it's a bug. As far as I know, the solver should
> not introduce new callstack constraints: if a CallStack constraint
> doesn't exist in the available context the solver should simply satisfy
> it with an empty callstack and that should be the end of it (Eric,
> correct me if I'm wrong).
> 
> Indeed, 7.10.2, which also had an early version of implicit callstack
> support, did exactly this. I haven't yet looked any further into what
> may have changed, but I have opened #11573 to track this.

The inferred CallStack is not a bug, it was added to fix #10845. The
problem is that in a function like

foo :: HasCallStack => ...
foo x = let bar y = undefined
in bar x

we *need* to infer a CallStack for bar (due to the structure of the
constraint solver) in order to link foo's CallStack to undefined.

Currently, this extends to inferring CallStacks for top-level binders
without explicit type signatures. Pedagogic concerns aside, I don't
think this is a big deal as it's standard practice to provide explicit
signatures. But it wouldn't be hard to make an exception for top-level
binders.

What *is* a bug is that GHC shows the implicit parameter in the inferred
signature. We don't expose those anymore in the CallStack API, instead
we use a type synonym HasCallStack. GHC should infer HasCallStack
constraints instead.

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


Re: New type of ($) operator in GHC 8.0 is problematic

2016-02-13 Thread Yuras Shumovich
On Sat, 2016-02-13 at 13:41 +0100, Ben Gamari wrote:
> Ryan Scott  writes:
> 
> > Hi Chris,
> > 
> > The change to ($)'s type is indeed intentional. The short answer is
> > that ($)'s type prior to GHC 8.0 was lying a little bit. If you
> > defined something like this:
> > 
> > unwrapInt :: Int -> Int#
> > unwrapInt (I# i) = i
> > 
> ...
> 
> Hello everyone,
> 
> While this thread continues to smolder, it seems that the arguments
> relevant to the levity polymorphism change have been sussed out. Now
> seems like a good time to review what we have all learned,
> 
>  * In 7.10 and earlier the type of ($) is a bit of a lie as it did
> not
>    reflect the fact that the result type was open-kinded.
> 
>    ($) also has magic to allow impredicative uses, although this is
>    orthogonal to the present levity discussion.
>    
>  * the type of ($) has changed to become more truthful in 8.0: we now
>    capture lifted-ness in the type system with the notion of Levity.
> 
>  * there is widespread belief that the new type is too noisy and
>    obfuscates the rather simple concept embodied by ($). This is
>    especially concerning for those teaching and learning the
> language.
> 
>  * One approach to fix this would be to specialize ($) for lifted
> types
>    and introduce a new levity polymorphic variant. This carries the
>    potential to break existing users of ($), although it's unclear
> how
>    much code this would affect in practice.
> 
>  * Another approach would be to preserve the current lie with
>    pretty-printer behavior. This would be relatively easy to do and
>    would allow us to avoid breaking existing users of ($). This,
>    however, comes at the expense of some potential confusion when
>    polymorphism is needed.

Thank you for the summary! The thread is too big to find anything in
it.

I'd like to present a bit different approach, kind of a compromise,
without lie and code breakage: introduce a language pragma for levity
polymorphism and default levity polymorphic signatures to "*" when the
pragma is not enabled.

For example, ($) could be defined like it is right now:

($)
  :: forall (w :: GHC.Types.Levity) a (b :: TYPE w).
     (a -> b) -> a -> b

But when it is used in a module without levity polymorphism enabled,
"w" is defaulted to "Lifted", "b" gets kind "*", and ($) gets its old
type:

($)
  :: (a -> b) -> a -> b

So any use of ($) with types on kind "#" is disallowed.

But with levily polymorphism enabled, one will see the full type and
use ($) with unlifted types. To prevent breakage of the existing code,
MagicHash extension should by default imply levity polymorphism.

What do you think? Am I missing something?

Thanks,
Yuras.

>  * There are further questions regarding the appropriate kinds
>    of (->) and (.) [1]
> 
>  * Incidentally, there is a GHC or Haddock bug [2] which causes kind
>    signatures to be unnecessarily shown in documentation for some
> types,
>    exposing levities to the user.
> 
> The current plan to address this situation is as follows,
> 
>  * Introduce [3] a flag, -fshow-runtime-rep, which when disabled will
>    cause the pretty-printer to instantiate levity-polymorphic types
> as
>    lifted (e.g. resulting in *). This flag will be off by default,
>    meaning that users will in most cases see the usual lifted types
>    unless they explicitly request otherwise.
> 
>  * Fix the GHC/Haddock bug, restoring elision of unnecessary kind
>    signatures in documentation.
> 
>  * In the future we should seriously consider introducing an
> alternate
>    Prelude for beginners
>  
> As far as I can tell from the discussion, this was an acceptable
> solution to all involved. If there are any remaining objections or
> concerns let's discuss them in another thread.
> 
> Thanks to everyone who contributed to this effort.
> 
> Cheers,
> 
> - Ben
> 
> 
> [1] https://ghc.haskell.org/trac/ghc/ticket/10343#comment:27
> [2] https://ghc.haskell.org/trac/ghc/ticket/11567
> [3] https://ghc.haskell.org/trac/ghc/ticket/11549
> ___
> 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: New type of ($) operator in GHC 8.0 is problematic

2016-02-13 Thread Ben Gamari
Ryan Scott  writes:

> Hi Chris,
>
> The change to ($)'s type is indeed intentional. The short answer is
> that ($)'s type prior to GHC 8.0 was lying a little bit. If you
> defined something like this:
>
> unwrapInt :: Int -> Int#
> unwrapInt (I# i) = i
>
...

Hello everyone,

While this thread continues to smolder, it seems that the arguments
relevant to the levity polymorphism change have been sussed out. Now
seems like a good time to review what we have all learned,

 * In 7.10 and earlier the type of ($) is a bit of a lie as it did not
   reflect the fact that the result type was open-kinded.

   ($) also has magic to allow impredicative uses, although this is
   orthogonal to the present levity discussion.
   
 * the type of ($) has changed to become more truthful in 8.0: we now
   capture lifted-ness in the type system with the notion of Levity.

 * there is widespread belief that the new type is too noisy and
   obfuscates the rather simple concept embodied by ($). This is
   especially concerning for those teaching and learning the language.

 * One approach to fix this would be to specialize ($) for lifted types
   and introduce a new levity polymorphic variant. This carries the
   potential to break existing users of ($), although it's unclear how
   much code this would affect in practice.

 * Another approach would be to preserve the current lie with
   pretty-printer behavior. This would be relatively easy to do and
   would allow us to avoid breaking existing users of ($). This,
   however, comes at the expense of some potential confusion when
   polymorphism is needed.

 * There are further questions regarding the appropriate kinds
   of (->) and (.) [1]

 * Incidentally, there is a GHC or Haddock bug [2] which causes kind
   signatures to be unnecessarily shown in documentation for some types,
   exposing levities to the user.

The current plan to address this situation is as follows,

 * Introduce [3] a flag, -fshow-runtime-rep, which when disabled will
   cause the pretty-printer to instantiate levity-polymorphic types as
   lifted (e.g. resulting in *). This flag will be off by default,
   meaning that users will in most cases see the usual lifted types
   unless they explicitly request otherwise.

 * Fix the GHC/Haddock bug, restoring elision of unnecessary kind
   signatures in documentation.

 * In the future we should seriously consider introducing an alternate
   Prelude for beginners
 
As far as I can tell from the discussion, this was an acceptable
solution to all involved. If there are any remaining objections or
concerns let's discuss them in another thread.

Thanks to everyone who contributed to this effort.

Cheers,

- Ben


[1] https://ghc.haskell.org/trac/ghc/ticket/10343#comment:27
[2] https://ghc.haskell.org/trac/ghc/ticket/11567
[3] https://ghc.haskell.org/trac/ghc/ticket/11549


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


Potentially confusing syntax for injective type families

2016-02-13 Thread Matthew Pickering
I was updating haskell-src-exts for ghc 8.0 recently and found some of
the syntax for injective type families quite confusing.

Is it a problem that the two following snippets have quite different meanings?

1. With the infectivity annotation, this declares an associated type.

class Hcl a b where
type Ht a b = r | r -> b a

2. Without the infectivity annotation, this declares an associate type
synonym default. This isn't valid because Ht is not declared as an
associated type before hand and r is not mentioned on the LHS.

class Hcl a b where
type Ht a b = r


Has this been considered?

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


Re: New type of expressions containing (error ...) includes noisy implicit parameter

2016-02-13 Thread Ben Gamari
Christopher Allen  writes:

> Prelude> let myList = [1, 2, 3 :: Integer]
> Prelude> let myList' = myList ++ undefined
> Prelude> :t myList
> myList :: [Integer]
> Prelude> :t myList'
> myList' :: (?callStack::GHC.Stack.Types.CallStack) => [Integer]
>
...
> This isn't just a pedagogical problem, this is a UX problem. The users
> don't _care_ that call stack information is being carried around. Why would
> they? It happens without any mention in the types in almost every other
> programming language.
>
Well, in the case of implicit call stacks users arguably *need* to care
whether call stack information is carried around: you only get call
stack information when you explicit request request one. This is one of
the limitations of the implicit callstack mechanism.

That being said, the example that you offer is a bit suspicious to the
point where I suspect it's a bug. As far as I know, the solver should
not introduce new callstack constraints: if a CallStack constraint
doesn't exist in the available context the solver should simply satisfy
it with an empty callstack and that should be the end of it (Eric,
correct me if I'm wrong).

Indeed, 7.10.2, which also had an early version of implicit callstack
support, did exactly this. I haven't yet looked any further into what
may have changed, but I have opened #11573 to track this.

Thanks for pointing this out.

Cheers,

- Ben


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


New type of expressions containing (error ...) includes noisy implicit parameter

2016-02-13 Thread Christopher Allen
Prelude> let myList = [1, 2, 3 :: Integer]
Prelude> let myList' = myList ++ undefined
Prelude> :t myList
myList :: [Integer]
Prelude> :t myList'
myList' :: (?callStack::GHC.Stack.Types.CallStack) => [Integer]

This is on by default and insofar as I've been able to try, it's avoidable
in a default GHCi 8.0 REPL session. I'm glad I caught this before our book
goes to print in a couple months. We'd managed to avoid talking about
implicit parameters in 1,100+ pages of book but now we're forced to
acknowledge their existence in the 4th of 32 chapters.

This slipped past the radar more stealthily than the earlier stages of BBP
did for 7.10. I was hearing about BBP on the GHC Trac pretty early on for
months on end. Was the thinking that people still used implicit parameters
for anything or taught them? On the one hand, this is a nice change and
something I personally attempted (and failed) to make easier in GHC 7.10.
The implementation making the types noisy rankles and didn't seem necessary
when I investigated it between 7.8 and 7.10.

Could you warn us when (educationally relevant?) stuff like this is coming
down the pipe before the RC please? Ideally during the design phase. I
think this was discussed as part of FTP to avoid future debacles.

This isn't just a pedagogical problem, this is a UX problem. The users
don't _care_ that call stack information is being carried around. Why would
they? It happens without any mention in the types in almost every other
programming language.


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