Re: Unicode, strings, and Show

2016-03-29 Thread Evan Laforge
There was recently a discussion about it, search for subject "Can we
improve Show instance for non-ascii charcters?"

You can read for yourself but my impression was that people were
generally favorable, but had some backward compatibility worries, and
came up with some workarounds, but no one committed to following up on
a ghci patch.

On Tue, Mar 29, 2016 at 7:26 PM, Manuel M T Chakravarty
 wrote:
> Why are we doing this?
>
>   GHCi, version 7.10.3: http://www.haskell.org/ghc/  :? for help
>   Prelude> "文字"
>   "\25991\23383"
>   Prelude>
>
> After all, we don’t print ’a’ as ’\97’.
>
> Manuel
>
> ___
> 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: Unicode, strings, and Show

2016-03-29 Thread Manuel Gómez
On Tue, Mar 29, 2016 at 9:56 PM, Manuel M T Chakravarty
 wrote:
> Why are we doing this?
>
>   GHCi, version 7.10.3: http://www.haskell.org/ghc/  :? for help
>   Prelude> "文字"
>   "\25991\23383"
>   Prelude>
>
> After all, we don’t print ’a’ as ’\97’.
>
> Manuel

Indeed:

• 2016: 
https://mail.haskell.org/pipermail/haskell-cafe/2016-February/122874.html
• 2012: 
http://stackoverflow.com/questions/14039726/how-to-make-haskell-or-ghci-able-to-show-chinese-characters-and-run-chinese-char
• 2012 again: 
https://mail.haskell.org/pipermail/haskell-cafe/2012-July/102569.html
• 2011: 
http://stackoverflow.com/questions/5535512/how-to-hack-ghci-or-hugs-so-that-it-prints-unicode-chars-unescaped
• 2010: https://mail.haskell.org/pipermail/haskell-cafe/2010-August/082823.html

This is a constant source of pain and should be relatively easy to fix.

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


Unicode, strings, and Show

2016-03-29 Thread Manuel M T Chakravarty
Why are we doing this?

  GHCi, version 7.10.3: http://www.haskell.org/ghc/  :? for help
  Prelude> "文字"
  "\25991\23383"
  Prelude> 

After all, we don’t print ’a’ as ’\97’.

Manuel

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


Re: Initial compile time benchmarks

2016-03-29 Thread Edward Z. Yang
This ticket may be of interest:

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

Deriving costs a lot and we just need someone to figure out what's
going on.

Edward

Excerpts from Michael Sloan's message of 2016-03-29 15:23:50 -0700:
> Great! Thanks for y'all putting effort towards performance. It really is
> crucial
> for developer productivity.
> 
> In the particular case of haskell-src-exts, I found that removing many of
> the
> more complicated typeclasses from deriving (Data, Generics, etc) brought the
> compilation time way down. IIRC it was pretty drastic, like 40 seconds vs 10
> seconds (that could be just the timing for that one types module though, I
> don't recall).  Could be valuable to investigate exactly what's going on
> there.
> 
> -Michael
> 
> On Tue, Mar 29, 2016 at 2:00 PM, Ömer Sinan Ağacan 
> wrote:
> 
> > Hi all,
> >
> > Using Ben's timing patch [^1], Cabal, and a Haskell program to parse
> > generated
> > logs [^2], I generated some tables that show compile times of modules in
> > hxt,
> > haskell-src-exts, lens, and all of their dependencies:
> >
> >
> > https://gist.githubusercontent.com/osa1/fd82335181a584679c9f3200b7b0a8a5/raw/5d46b0e7006c7ef9fae913f7d6932b74c83835f1/gistfile1.txt
> >
> > Some notes:
> >
> > - Modules and passes in modules are sorted.
> >
> > - At the end of the file you can see the cumulative numbers for the
> > passes. In
> >   fact, that's a small table so I'm just going to paste it here:
> >
> > ==Total==
> > CodeGen41.32%
> > Simplifier 34.83%
> > Renamer/typechecker12.22%
> > Desugar 2.11%
> > CorePrep1.90%
> > Demand analysis 1.44%
> > CoreTidy1.35%
> > Called arity analysis   1.10%
> > Float inwards   0.96%
> > Common sub-expression   0.87%
> > Parser  0.75%
> > SpecConstr  0.57%
> > Specialise  0.30%
> > Worker Wrapper binds0.17%
> > Liberate case   0.12%
> > ByteCodeGen 0.00%
> > Simplify0.00%
> >
> > I don't know how to make use of this yet, but I thought ghc-devs may find
> > it
> > useful.
> >
> > As a next thing I'm hoping to add some more `withTiming` calls. The analyze
> > program can handle nested `withTiming` calls and renders passes as a tree
> > (GHC
> > HEAD doesn't have nested `withTiming`s so we don't see it in the file
> > above),
> > so we can benchmark things in more details. I also want to experiment a
> > little
> > bit with different `force` parameters to `withTiming`. If anyone has any
> > other
> > ideas I can also try those.
> >
> > ---
> >
> > [^1]: https://phabricator.haskell.org/D1959
> > [^2]: https://github.com/osa1/analyze-ghc-timings
> > ___
> > 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: Initial compile time benchmarks

2016-03-29 Thread Michael Sloan
Great! Thanks for y'all putting effort towards performance. It really is
crucial
for developer productivity.

In the particular case of haskell-src-exts, I found that removing many of
the
more complicated typeclasses from deriving (Data, Generics, etc) brought the
compilation time way down. IIRC it was pretty drastic, like 40 seconds vs 10
seconds (that could be just the timing for that one types module though, I
don't recall).  Could be valuable to investigate exactly what's going on
there.

-Michael

On Tue, Mar 29, 2016 at 2:00 PM, Ömer Sinan Ağacan 
wrote:

> Hi all,
>
> Using Ben's timing patch [^1], Cabal, and a Haskell program to parse
> generated
> logs [^2], I generated some tables that show compile times of modules in
> hxt,
> haskell-src-exts, lens, and all of their dependencies:
>
>
> https://gist.githubusercontent.com/osa1/fd82335181a584679c9f3200b7b0a8a5/raw/5d46b0e7006c7ef9fae913f7d6932b74c83835f1/gistfile1.txt
>
> Some notes:
>
> - Modules and passes in modules are sorted.
>
> - At the end of the file you can see the cumulative numbers for the
> passes. In
>   fact, that's a small table so I'm just going to paste it here:
>
> ==Total==
> CodeGen41.32%
> Simplifier 34.83%
> Renamer/typechecker12.22%
> Desugar 2.11%
> CorePrep1.90%
> Demand analysis 1.44%
> CoreTidy1.35%
> Called arity analysis   1.10%
> Float inwards   0.96%
> Common sub-expression   0.87%
> Parser  0.75%
> SpecConstr  0.57%
> Specialise  0.30%
> Worker Wrapper binds0.17%
> Liberate case   0.12%
> ByteCodeGen 0.00%
> Simplify0.00%
>
> I don't know how to make use of this yet, but I thought ghc-devs may find
> it
> useful.
>
> As a next thing I'm hoping to add some more `withTiming` calls. The analyze
> program can handle nested `withTiming` calls and renders passes as a tree
> (GHC
> HEAD doesn't have nested `withTiming`s so we don't see it in the file
> above),
> so we can benchmark things in more details. I also want to experiment a
> little
> bit with different `force` parameters to `withTiming`. If anyone has any
> other
> ideas I can also try those.
>
> ---
>
> [^1]: https://phabricator.haskell.org/D1959
> [^2]: https://github.com/osa1/analyze-ghc-timings
> ___
> 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: Initial compile time benchmarks

2016-03-29 Thread Eric Seidel
Very cool!

It would be nice to add build flags to the table (or at least
optimization levels) as these probably differ across packages, and will
certainly impact the numbers. 

I'd also be really interested to see a comparison of the timing data for
-O0 and -O. I think the biggest impact for performance improvements will
probably come from working on -O0, since that's what people will use for
development.

Thanks!
Eric

On Tue, Mar 29, 2016, at 14:00, Ömer Sinan Ağacan wrote:
> Hi all,
> 
> Using Ben's timing patch [^1], Cabal, and a Haskell program to parse
> generated
> logs [^2], I generated some tables that show compile times of modules in
> hxt,
> haskell-src-exts, lens, and all of their dependencies:
> 
> https://gist.githubusercontent.com/osa1/fd82335181a584679c9f3200b7b0a8a5/raw/5d46b0e7006c7ef9fae913f7d6932b74c83835f1/gistfile1.txt
> 
> Some notes:
> 
> - Modules and passes in modules are sorted.
> 
> - At the end of the file you can see the cumulative numbers for the
> passes. In
>   fact, that's a small table so I'm just going to paste it here:
> 
> ==Total==
> CodeGen41.32%
> Simplifier 34.83%
> Renamer/typechecker12.22%
> Desugar 2.11%
> CorePrep1.90%
> Demand analysis 1.44%
> CoreTidy1.35%
> Called arity analysis   1.10%
> Float inwards   0.96%
> Common sub-expression   0.87%
> Parser  0.75%
> SpecConstr  0.57%
> Specialise  0.30%
> Worker Wrapper binds0.17%
> Liberate case   0.12%
> ByteCodeGen 0.00%
> Simplify0.00%
> 
> I don't know how to make use of this yet, but I thought ghc-devs may find
> it
> useful.
> 
> As a next thing I'm hoping to add some more `withTiming` calls. The
> analyze
> program can handle nested `withTiming` calls and renders passes as a tree
> (GHC
> HEAD doesn't have nested `withTiming`s so we don't see it in the file
> above),
> so we can benchmark things in more details. I also want to experiment a
> little
> bit with different `force` parameters to `withTiming`. If anyone has any
> other
> ideas I can also try those.
> 
> ---
> 
> [^1]: https://phabricator.haskell.org/D1959
> [^2]: https://github.com/osa1/analyze-ghc-timings
> ___
> 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


Initial compile time benchmarks

2016-03-29 Thread Ömer Sinan Ağacan
Hi all,

Using Ben's timing patch [^1], Cabal, and a Haskell program to parse generated
logs [^2], I generated some tables that show compile times of modules in hxt,
haskell-src-exts, lens, and all of their dependencies:

https://gist.githubusercontent.com/osa1/fd82335181a584679c9f3200b7b0a8a5/raw/5d46b0e7006c7ef9fae913f7d6932b74c83835f1/gistfile1.txt

Some notes:

- Modules and passes in modules are sorted.

- At the end of the file you can see the cumulative numbers for the passes. In
  fact, that's a small table so I'm just going to paste it here:

==Total==
CodeGen41.32%
Simplifier 34.83%
Renamer/typechecker12.22%
Desugar 2.11%
CorePrep1.90%
Demand analysis 1.44%
CoreTidy1.35%
Called arity analysis   1.10%
Float inwards   0.96%
Common sub-expression   0.87%
Parser  0.75%
SpecConstr  0.57%
Specialise  0.30%
Worker Wrapper binds0.17%
Liberate case   0.12%
ByteCodeGen 0.00%
Simplify0.00%

I don't know how to make use of this yet, but I thought ghc-devs may find it
useful.

As a next thing I'm hoping to add some more `withTiming` calls. The analyze
program can handle nested `withTiming` calls and renders passes as a tree (GHC
HEAD doesn't have nested `withTiming`s so we don't see it in the file above),
so we can benchmark things in more details. I also want to experiment a little
bit with different `force` parameters to `withTiming`. If anyone has any other
ideas I can also try those.

---

[^1]: https://phabricator.haskell.org/D1959
[^2]: https://github.com/osa1/analyze-ghc-timings
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: instantiating visible parameters in when deriving instances

2016-03-29 Thread Richard Eisenberg

On Mar 29, 2016, at 3:58 PM, Ryan Scott  wrote:

> I hope this is a bug and not a fundamental limitation.

As I posted in the ticket, this is a somewhat fundamental limitation. I qualify 
by "somewhat" because it's a consequence of a design choice, but reversing the 
design choice would be rather difficult and lead to several more tough design 
choices. It's my hope and belief that this restriction will one day be lifted. 
That day will not be soon. The wiki 
(https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Internal#Liftedvs.Unliftedequality)
 has some thoughts on the issue, but those notes may be out of date and/or 
wrong. YMMV.

As for Simon's question about the difference between visible and invisible: 
when the user says `deriving (Cat k)`, the user has written k and presumably 
means k to be universally quantified. When the user days `deriving Category`, 
then no `k` has been written and unification seems appropriate. Of course, if 
we consider that in the `deriving (Cat k)` case, we're just inferring a `k ~ *` 
constraint, perhaps this is OK. But it's certainly a bit odd.

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


Re: GHC 8.0.1 release plan

2016-03-29 Thread Austin Seipp
Hello all,

I just wanted to follow up on this. Yesterday, Ben and I spent some
time and went over the current bug list[1]. If you saw that email
yesterday - please refresh that page, we've trimmed the hedges a
little bit. Please note that, barring any huge bugs in 8.0.1-rc3, we
really aren't intending on putting anything else into the queue.

So, if you're a developer: Please take a look at the tickets! Try to
fix something. If you're a user: if you want something done for 8.0.1
that isn't done already, you better make a *really* good case for it,
email us ASAP, and help us fix it!

Realistically, we're going to be spending most of our time on the
high/highest priority bugs. The remaining 'normal' bugs would be 'nice
to have', and some may even be promoted - so if you can, maybe take a
look. Otherwise we're going to be working on getting the remaining
critical bugs fixed and out of the way and move forward.

Thanks!

[1] https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-8.0.1#Ticketsslatedfor8.0.1

On Mon, Mar 28, 2016 at 2:16 PM, Ben Gamari  wrote:
> Ben Gamari  writes:
>
>> Hello GHCers,
>>
>> After numerous delays, I think we may finally be converging on a
>> (hopefully final) 8.0.1 release candidate. Thanks to the tireless
>> efforts of Richard Eisenberg, Simon PJ, and many others almost all of
>> the release blocking tickets [1] have now been resolved. There are a few
>> patches currently waiting for review that should hopefully be mergeable
>> within the next few days.
>>
>> After these last patches have been merged I'll proceed in cutting
>> the source distribution for GHC 8.0.1 release candidate 3. This release
>> candidate will be made available immediately, although, in accordance
>> with our new release policy [2], binary distributions won't be available
>> until seven days later.
>>
> Oops, forgot the reference here. The new release timing policy was
> described here,
>
> [2] https://mail.haskell.org/pipermail/ghc-devs/2016-March/011546.html
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>



-- 
Regards,

Austin Seipp, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: instantiating visible parameters in when deriving instances

2016-03-29 Thread Ryan Scott
> Why should it make a difference whether it's visible or not.  Can't we behave 
> the same for both?

Oops, I made the wrong distinction. I should have said: we freely
unify eta-reduced type parameters when deriving, but if a type
parameter isn't eta-reduced, then we generate equality constraints
instead of unifying it.

That is, the distinction between

instance Functor P1
-- with -fprint-explicit-kinds, this would be instance Functor * P1

and

instance (k ~ *) => Functor (P2 k)

We can't generate equality constraints for eta-reduced type variables
since there's literally no way to refer to them in an instance.

Ryan S.

On Tue, Mar 29, 2016 at 10:47 AM, Simon Peyton Jones
 wrote:
> |  So I'm starting to lean towards Simon's proposal. That is, we freely
> |  unify non-visible type parameters when deriving, but if a type
> |  parameter is visible, then we generate equality constraints instead of
> |  unifying it.
>
> Why should it make a difference whether it's visible or not.  Can't we behave 
> the same for both?
>
> Simon
>
>
> |  -Original Message-
> |  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ryan
> |  Scott
> |  Sent: 29 March 2016 14:58
> |  To: ghc-devs@haskell.org
> |  Subject: Re: instantiating visible parameters in when deriving
> |  instances
> |
> |  Simon, did you meant P2? (Since you can't write instance (k ~ *) =>
> |  Functor (P1 (a :: k)), as that's ill-kinded). Something like this?
> |
> |  data P2 k (a :: k) = MkP2
> |  instance (k ~ *) => Functor (P2 k)
> |
> |  That's an interesting idea. Be aware that you actually can't compile
> |  that code at the moment, since GHC complains:
> |
> |  * Expected kind ‘* -> *’, but ‘P2 k’ has kind ‘k -> *’
> |  * In the first argument of ‘Functor’, namely ‘P2 k’
> |In the instance declaration for ‘Functor (P2 k)’
> |
> |  I hope this is a bug and not a fundamental limitation.
> |
> |  There's another wrinkle in the design we must consider. Not only can
> |  datatypes have dependent type parameters, but so can typeclasses
> |  themselves. Consider:
> |
> |  {-# LANGUAGE FlexibleInstances #-}
> |  {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> |  {-# LANGUAGE MultiParamTypeClasses #-}
> |  {-# LANGUAGE TypeInType #-}
> |  module Cat where
> |
> |  import Data.Kind
> |
> |  class Cat k (cat :: k -> k -> *) where
> |catId   :: cat a a
> |catComp :: cat b c -> cat a b -> cat a c
> |
> |  instance Cat * (->) where
> |catId   = id
> |catComp = (.)
> |
> |  newtype Fun a b = Fun (a -> b) deriving (Cat k)
> |
> |  I was surprised to find out that this code currently compiles without
> |  issue on GHC 8.0, even though we're deriving (Cat k) instead of (Cat
> |  *). This is an effect of the way GHC currently handles deriving
> |  clauses, since it unifies the kind of the datatype and typeclass
> |  beforehand (therefore, it silently gets unified to Cat * before
> |  generating the instance). [1]
> |
> |  Is this correct? It definitely feels a bit off. We currently allow this
> |  (see Trac #8865 [2]):
> |
> |  newtype T a b = MkT (Either a b) deriving ( Category )
> |
> |  Even though Category :: k -> k -> * (i.e., we silently unify k with *).
> |  The difference here, as is the difference between P1 and P2 in Simon's
> |  email, is that k is not visible, so it's out-of-sight and out-of-mind.
> |  When k is visible, as in Cat, when now must be conscious of how it's
> |  used in a deriving clause.
> |
> |  The Cat code is lying in the sense that we aren't deriving an instance
> |  that begins with (Cat k), but rather:
> |
> |  instance Cat * Fun where ...
> |
> |  Using Simon's advice, we could just as well generate:
> |
> |  instance (k ~ *) => Cat k Fun where ...
> |
> |  (Again, this doesn't currently compile on 8.0. I really hope that's
> |  just a bug.)
> |
> |  So I'm starting to lean towards Simon's proposal. That is, we freely
> |  unify non-visible type parameters when deriving, but if a type
> |  parameter is visible, then we generate equality constraints instead of
> |  unifying it.
> |
> |  Ryan S.
> |  -
> |  [1]
> |  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fgit.has
> |  kell.org%2fghc.git%2fblob%2fb0ab8db61568305f50947058fc5573e2382c84eb%3a
> |  %2fcompiler%2ftypecheck%2fTcDeriv.hs%23l653&data=01%7c01%7csimonpj%4006
> |  4d.mgd.microsoft.com%7cdd343f6279d74b40a30b08d357da348e%7c72f988bf86f14
> |  1af91ab2d7cd011db47%7c1&sdata=I2YgFKCYkZtpSJlN7UzOyawgK2LncTQIlE2PpOAwP
> |  2c%3d
> |  [2] https://ghc.haskell.org/trac/ghc/ticket/8865
> |  ___
> |  ghc-devs mailing list
> |  ghc-devs@haskell.org
> |  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.ha
> |  skell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
> |  devs%0a&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7cdd343f6279d74
> |  b40a30b08d357da348e%7c72f988bf8

RE: instantiating visible parameters in when deriving instances

2016-03-29 Thread Simon Peyton Jones
|  So I'm starting to lean towards Simon's proposal. That is, we freely
|  unify non-visible type parameters when deriving, but if a type
|  parameter is visible, then we generate equality constraints instead of
|  unifying it.

Why should it make a difference whether it's visible or not.  Can't we behave 
the same for both?

Simon


|  -Original Message-
|  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ryan
|  Scott
|  Sent: 29 March 2016 14:58
|  To: ghc-devs@haskell.org
|  Subject: Re: instantiating visible parameters in when deriving
|  instances
|  
|  Simon, did you meant P2? (Since you can't write instance (k ~ *) =>
|  Functor (P1 (a :: k)), as that's ill-kinded). Something like this?
|  
|  data P2 k (a :: k) = MkP2
|  instance (k ~ *) => Functor (P2 k)
|  
|  That's an interesting idea. Be aware that you actually can't compile
|  that code at the moment, since GHC complains:
|  
|  * Expected kind ‘* -> *’, but ‘P2 k’ has kind ‘k -> *’
|  * In the first argument of ‘Functor’, namely ‘P2 k’
|In the instance declaration for ‘Functor (P2 k)’
|  
|  I hope this is a bug and not a fundamental limitation.
|  
|  There's another wrinkle in the design we must consider. Not only can
|  datatypes have dependent type parameters, but so can typeclasses
|  themselves. Consider:
|  
|  {-# LANGUAGE FlexibleInstances #-}
|  {-# LANGUAGE GeneralizedNewtypeDeriving #-}
|  {-# LANGUAGE MultiParamTypeClasses #-}
|  {-# LANGUAGE TypeInType #-}
|  module Cat where
|  
|  import Data.Kind
|  
|  class Cat k (cat :: k -> k -> *) where
|catId   :: cat a a
|catComp :: cat b c -> cat a b -> cat a c
|  
|  instance Cat * (->) where
|catId   = id
|catComp = (.)
|  
|  newtype Fun a b = Fun (a -> b) deriving (Cat k)
|  
|  I was surprised to find out that this code currently compiles without
|  issue on GHC 8.0, even though we're deriving (Cat k) instead of (Cat
|  *). This is an effect of the way GHC currently handles deriving
|  clauses, since it unifies the kind of the datatype and typeclass
|  beforehand (therefore, it silently gets unified to Cat * before
|  generating the instance). [1]
|  
|  Is this correct? It definitely feels a bit off. We currently allow this
|  (see Trac #8865 [2]):
|  
|  newtype T a b = MkT (Either a b) deriving ( Category )
|  
|  Even though Category :: k -> k -> * (i.e., we silently unify k with *).
|  The difference here, as is the difference between P1 and P2 in Simon's
|  email, is that k is not visible, so it's out-of-sight and out-of-mind.
|  When k is visible, as in Cat, when now must be conscious of how it's
|  used in a deriving clause.
|  
|  The Cat code is lying in the sense that we aren't deriving an instance
|  that begins with (Cat k), but rather:
|  
|  instance Cat * Fun where ...
|  
|  Using Simon's advice, we could just as well generate:
|  
|  instance (k ~ *) => Cat k Fun where ...
|  
|  (Again, this doesn't currently compile on 8.0. I really hope that's
|  just a bug.)
|  
|  So I'm starting to lean towards Simon's proposal. That is, we freely
|  unify non-visible type parameters when deriving, but if a type
|  parameter is visible, then we generate equality constraints instead of
|  unifying it.
|  
|  Ryan S.
|  -
|  [1]
|  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fgit.has
|  kell.org%2fghc.git%2fblob%2fb0ab8db61568305f50947058fc5573e2382c84eb%3a
|  %2fcompiler%2ftypecheck%2fTcDeriv.hs%23l653&data=01%7c01%7csimonpj%4006
|  4d.mgd.microsoft.com%7cdd343f6279d74b40a30b08d357da348e%7c72f988bf86f14
|  1af91ab2d7cd011db47%7c1&sdata=I2YgFKCYkZtpSJlN7UzOyawgK2LncTQIlE2PpOAwP
|  2c%3d
|  [2] https://ghc.haskell.org/trac/ghc/ticket/8865
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.ha
|  skell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
|  devs%0a&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7cdd343f6279d74
|  b40a30b08d357da348e%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=19EhLy
|  AsemDkPIdmK08C0XBbLufiKEsEwYuLqWhCH3s%3d
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: More Higher-Kinded Typeclass Instances

2016-03-29 Thread Andrew Martin
Yeah, that is a lot of instances (especially all 62 types of tuples). I
think you're right that it makes more sense to do this with an extension to
the deriving mechanism, especially since even if I wrote them now, it would
probably make sense to redo them with a deriving clause later. At the
moment, I don't really need any of them but Proxy, which is already done,
some I'm happy to wait this one out. Thanks.

-Andrew Martin

On Tue, Mar 29, 2016 at 9:10 AM, Ryan Scott  wrote:

> Well, if we're going to be thorough, we need to also get:
>
> * Tuple types
> * All (* -> *)-kinded datatypes in Data.Monoid
> * Data.Type.Equality.(:~:) and Data.Type.Coercion.Coercion
> * Fixed
> * ST, STRef
> * Chan
> * MVar, IORef, TVar
>
> A lot of these types' existing Eq/Ord/Read/Show instances are
> currently derived, however, and you might find it incredibly tedious
> to type all them out by hand (not to discourage you from going for it
> if you need them now, but we warned). Given that the window for new
> 8.0 features is almost closed, perhaps it would be better to wait
> until I've implemented an extension which derives these classes
> automatically?
>
> (I wanted to get such an extension implemented sooner, but time ran
> out. I'll try to find some time to write a wiki page proposing a
> design so that we can get the ball rolling soon after the 8.0 final
> release.)
>
> Ryan S.
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>



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


Re: instantiating visible parameters in when deriving instances

2016-03-29 Thread Ryan Scott
Simon, did you meant P2? (Since you can't write instance (k ~ *) =>
Functor (P1 (a :: k)), as that's ill-kinded). Something like this?

data P2 k (a :: k) = MkP2
instance (k ~ *) => Functor (P2 k)

That's an interesting idea. Be aware that you actually can't compile
that code at the moment, since GHC complains:

* Expected kind ‘* -> *’, but ‘P2 k’ has kind ‘k -> *’
* In the first argument of ‘Functor’, namely ‘P2 k’
  In the instance declaration for ‘Functor (P2 k)’

I hope this is a bug and not a fundamental limitation.

There's another wrinkle in the design we must consider. Not only can
datatypes have dependent type parameters, but so can typeclasses
themselves. Consider:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeInType #-}
module Cat where

import Data.Kind

class Cat k (cat :: k -> k -> *) where
  catId   :: cat a a
  catComp :: cat b c -> cat a b -> cat a c

instance Cat * (->) where
  catId   = id
  catComp = (.)

newtype Fun a b = Fun (a -> b) deriving (Cat k)

I was surprised to find out that this code currently compiles without
issue on GHC 8.0, even though we're deriving (Cat k) instead of (Cat
*). This is an effect of the way GHC currently handles deriving
clauses, since it unifies the kind of the datatype and typeclass
beforehand (therefore, it silently gets unified to Cat * before
generating the instance). [1]

Is this correct? It definitely feels a bit off. We currently allow
this (see Trac #8865 [2]):

newtype T a b = MkT (Either a b) deriving ( Category )

Even though Category :: k -> k -> * (i.e., we silently unify k with
*). The difference here, as is the difference between P1 and P2 in
Simon's email, is that k is not visible, so it's out-of-sight and
out-of-mind. When k is visible, as in Cat, when now must be conscious
of how it's used in a deriving clause.

The Cat code is lying in the sense that we aren't deriving an instance
that begins with (Cat k), but rather:

instance Cat * Fun where ...

Using Simon's advice, we could just as well generate:

instance (k ~ *) => Cat k Fun where ...

(Again, this doesn't currently compile on 8.0. I really hope that's just a bug.)

So I'm starting to lean towards Simon's proposal. That is, we freely
unify non-visible type parameters when deriving, but if a type
parameter is visible, then we generate equality constraints instead of
unifying it.

Ryan S.
-
[1] 
http://git.haskell.org/ghc.git/blob/b0ab8db61568305f50947058fc5573e2382c84eb:/compiler/typecheck/TcDeriv.hs#l653
[2] https://ghc.haskell.org/trac/ghc/ticket/8865
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: More Higher-Kinded Typeclass Instances

2016-03-29 Thread Ryan Scott
Well, if we're going to be thorough, we need to also get:

* Tuple types
* All (* -> *)-kinded datatypes in Data.Monoid
* Data.Type.Equality.(:~:) and Data.Type.Coercion.Coercion
* Fixed
* ST, STRef
* Chan
* MVar, IORef, TVar

A lot of these types' existing Eq/Ord/Read/Show instances are
currently derived, however, and you might find it incredibly tedious
to type all them out by hand (not to discourage you from going for it
if you need them now, but we warned). Given that the window for new
8.0 features is almost closed, perhaps it would be better to wait
until I've implemented an extension which derives these classes
automatically?

(I wanted to get such an extension implemented sooner, but time ran
out. I'll try to find some time to write a wiki page proposing a
design so that we can get the ball rolling soon after the 8.0 final
release.)

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


RE: instantiating visible parameters in when deriving instances

2016-03-29 Thread Simon Peyton Jones
Just to be clear to everyone else, we are discussing

   data P1   (a :: k) = MkP1 deriving Functor
   data P2 k (a :: k) = MkP2 deriving Functor

Here P2 has an explicit kind arg, which must appear in any use of P2; thus
   f :: P2 * Int -> Bool

Now the question is: what derived instances do we get?  We could get

  instance Functor (P1 (a :: *))
  instance Functor (P2 * (a ::*))

The question before the house is whether to reject either or both 'deriving' 
clauses, on the grounds that both instantiate 'k'; and ask for a stand-alone 
deriving declaration instead.  In principle we could say Yes/Yes, Yes/No, or 
No/No to the two cases.

As Richard points out, a 'deriving' clause attached to a 'data' decl infers 
some instance context.  That context must be written explicitly in a standalone 
deriving declaration. For example:

  data Maybe a = Nothing | Just a deriving( Eq )

we get the derived instance

  instance Eq a => Eq (Maybe a ) where
(==) x y = ...blah...

The "Eq a" context in this instance declaration is magically inferred from the 
form of the data type declaration.  This inference process gets pretty tricky 
for Functor and Traversable. To use the instance declarations you have to 
understand what the inferred instance context is; GHC should really provide a 
way to tell you.

Richard points out (later in the thread) that "instantiating k" is like adding 
a constraint `k ~ *` to the instance, thus
{{{
  instance (k ~ *) => Functor (P1 (a :: k))
}}}
That's not quite true, because this instance will match for any k, and hence 
overlaps with putative instances for k's other than `*`; whereas
{{{
  instance Functor P1 (a :: *)
}}}
matches only for the `*` case.  And that is a subtle distinction indeed!

Humph.  I am rather persuaded by Richard's argument. Proposal: just regard the 
kind constraints as extra inferred constraints, and hence generate
{{{
  instance (k ~ *) => Functor (P1 (a :: k))
}}}
Now the derived instance always has type variables in the head; but those type 
variables may be constrained by the context.  I like that.

It's not quite what happens now, so there would be a little implementation work 
to do.  It might quite possibly actually be simpler.

I'm going to dump this email into the ticket.

Simon

|  -Original Message-
|  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of
|  Richard Eisenberg
|  Sent: 28 March 2016 13:55
|  To: GHC developers 
|  Subject: instantiating visible parameters in when deriving instances
|  
|  Hi devs,
|  
|  Consider the following:
|  
|  > data Proxy k (a :: k) = P
|  >   deriving Functor
|  
|  What should happen when this is compiled?
|   1. Issue an error saying that `deriving` cannot instantiate visible
|  parameters.
|   2. Type error: cannot match `k` with `*`.
|   3. Successfully produce `instance (Proxy *)`.
|  
|  Currently, GHC does #3. But this ends up choosing a value for a visible
|  (i.e. explicit) parameter to Proxy. Is this a good idea? I myself have
|  flip-flopped on this issue; see
|  https://ghc.haskell.org/trac/ghc/ticket/11732, comments 4 and 9.
|  
|  I'd love to get feedback on this point.
|  
|  Thanks!
|  Richard
|  ___
|  ghc-devs mailing list
|  ghc-devs@haskell.org
|  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.ha
|  skell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
|  devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c175b7c5afb594993
|  14e708d357083e9e%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=d6dNjZWCi
|  IeqDBNFVSL13b6ZUG0QREf9UcqrVrqbpEA%3d
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


RE: possible tuple elimination optimization?

2016-03-29 Thread Simon Peyton Jones
Yes: see https://ghc.haskell.org/trac/ghc/wiki/NestedCPR

Simon

| -Original Message-
| From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Dan Doel
| Sent: 26 March 2016 20:41
| To: George Colpitts 
| Cc: ghc-devs@haskell.org
| Subject: Re: possible tuple elimination optimization?
| 
| By the way, in case this helps your mental model, if you modify sumr to be:
| 
| sumr n = snd $ as' 1 0
|   where
|   as' i s
| | i >= n = (i, s)
| | otherwise = ...
| 
| Then it has the same problem as sumh. Your original as' for sumr is
| strict in s, but this modified one isn't.
| 
| This shows another way to fix sumh, too. Create a version of until
| that separates out the part of the state that is only for testing.
| Then the until loop will be strict in the result part of the state,
| and the desired optimizations will happen (in this case):
| 
| until' p step = go
|  where
|  go t r
|| p t = r
|| otherwise = uncurry go $ step (t, r)
| 
| -- Dan
| 
| On Sat, Mar 26, 2016 at 1:50 PM, George Colpitts
|  wrote:
| > The following higher order function, sumh, seems to be 3 to 14 times slower
| > than the equivalent recursive function, sumr:
| >
| > sumh :: Double -> Double
| > sumh n =
| > snd $ until ((>= n) . fst) as' (1, 0)
| > where
| >   as' (i,s) =
| >   (i + 2, s + (-1) / i + 1 / (i + 1))
| >
| > sumr :: Double -> Double
| > sumr n =
| > as' 1 0
| > where
| >   as' i  s
| >   | i >= n= s
| >   | otherwise = as' (i + 2) (s + (-1) / i + 1 / (i + 1))
| >
| > This is true in 7.10.3 as well as 8.0.1 so this is not a regression. From
| > the size usage my guess is that this is due to the allocation of tuples in
| > sumh. Maybe there is a straightforward way to optimize sumh but I couldn't
| > find it. Adding a Strict pragma didn't help nor did use of
| > -funbox-strict-fields -flate-dmd-anal. Have I missed something or should I
| > file a bug?
| >
| > Timings from 8.0.1 rc2:
| >
| > ghc --version
| > The Glorious Glasgow Haskell Compilation System, version 8.0.0.20160204
| > bash-3.2$ ghc -O2 -dynamic sum.hs
| > ghc -O2 -dynamic sum.hs
| > [1 of 1] Compiling Main ( sum.hs, sum.o )
| > Linking sum ...
| > bash-3.2$ ghci
| > Prelude> :load sum
| > Ok, modules loaded: Main.
| > (0.05 secs,)
| > Prelude Main> sumh (10^6)
| > -0.6931466805602525
| > it :: Double
| > (0.14 secs, 40,708,016 bytes)
| > Prelude Main> sumr (10^6)
| > -0.6931466805602525
| > it :: Double
| > (0.01 secs, 92,000 bytes)
| >
| > Thanks
| > George
| >
| > ___
| > ghc-devs mailing list
| > ghc-devs@haskell.org
| >
| https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.
| org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
| devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7cec78251e0f564b23014708
| d355b6ed56%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=7u50FvyHKPpAXiweli%2b
| 0CP1pup15X8Kh9rN8JrIXP78%3d
| >
| ___
| ghc-devs mailing list
| ghc-devs@haskell.org
| https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.
| org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
| devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7cec78251e0f564b23014708
| d355b6ed56%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=7u50FvyHKPpAXiweli%2b
| 0CP1pup15X8Kh9rN8JrIXP78%3d
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs