Re: Can we offer ~ without GADTs or type families?

2016-08-05 Thread Eric Crockett
As a user who frequently uses ~, but doesn't need the rest of GADTs or
TypeFamilies, I'd really like to see a TypeEqualities extension!

Eric

On Fri, Aug 5, 2016 at 3:27 PM, Adam Gundry  wrote:

> On 05/08/16 19:08, David Feuer wrote:
> > It seems to me that equality constraints could potentially be supported
> > by an implementation with neither GADTs nor type families. Type families
> > don't really seem to have much to do with it, and GADTs are strictly
> > heavier (GADTs ~= ExistentialQuantification + TypeEquality).
> >
> > Could we get a separate LANGUAGE pragma just for equality constraints?
>
> I suggested this in #10431 [1], where there is some discussion of the
> implications. I still think it is a good idea, and I don't think the
> implementation would be very difficult.
>
> All the best,
>
> Adam
>
> [1] https://ghc.haskell.org/trac/ghc/ticket/10431
>
>
> --
> Adam Gundry, 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
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [commit: ghc] master: Replace some `length . filter` with `count` (02614fd)

2016-08-05 Thread Joachim Breitner
Hi,

Am Freitag, den 05.08.2016, 22:41 + schrieb g...@git.haskell.org:
> commit 02614fd61f57b599c5e4fd5e85f00a4e1ce37bc7
> Author: Ömer Sinan Ağacan 
> Date:   Fri Aug 5 20:58:02 2016 +
> 
> Replace some `length . filter` with `count`

Well intended!

I wouldn’t be surprised if this is actually making the code worse,
considering that "count" is implemented in the “wrong”, stackeating way
(whereas lenght . filter could, thanks to list fusion, produce the
desired code)

count :: (a -> Bool) -> [a] -> Int
count _ [] = 0
count p (x:xs) | p x   = 1 + count p xs
   | otherwise = count p xs

I would say that the regression reported by 
https://perf.haskell.org/ghc/#revision/02614fd61f57b599c5e4fd5e85f00a4e1ce37bc7
confirms this, but T6048 is simply unreliable. So practically, it does
not seem to matter either way.

I’ll change the implementation of count.

(Although even then it is not clear that the change is a win, as
"length . filter" might fuse with the producer, whereas "count" without
a lot of extra hassle will not.)

Joachim

-- 
Joachim “nomeata” Breitner
  m...@joachim-breitner.de • https://www.joachim-breitner.de/
  XMPP: nome...@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F
  Debian Developer: nome...@debian.org

signature.asc
Description: This is a digitally signed message part
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Can we offer ~ without GADTs or type families?

2016-08-05 Thread Adam Gundry
On 05/08/16 19:08, David Feuer wrote:
> It seems to me that equality constraints could potentially be supported
> by an implementation with neither GADTs nor type families. Type families
> don't really seem to have much to do with it, and GADTs are strictly
> heavier (GADTs ~= ExistentialQuantification + TypeEquality).
> 
> Could we get a separate LANGUAGE pragma just for equality constraints?

I suggested this in #10431 [1], where there is some discussion of the
implications. I still think it is a good idea, and I don't think the
implementation would be very difficult.

All the best,

Adam

[1] https://ghc.haskell.org/trac/ghc/ticket/10431


-- 
Adam Gundry, 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: Can we offer ~ without GADTs or type families?

2016-08-05 Thread Ryan Scott
Good point, I hadn't considered the perspective of other compilers. In
that case, I could be persuaded to introduce a separate pragma like
-XTypeEqualities, and have -XGADTs and -XTypeFamilies imply
-XTypeEqualities for backwards compatibility.

Ryan S.

On Fri, Aug 5, 2016 at 2:27 PM, Edward Kmett  wrote:
> TypeOperators as a language extension doesn't require a whole lot on the
> behalf of implementors today. They basically just have to add fixity
> handling to types. This is a no-brainer for a compiler implementor. It is a
> simple elaboration and some extra cases to deal with in their parser. The
> typechecker changes are obvious.
>
> Asking them to do all the things to support 'some typechecking details' that
> aren't entirely trivial to support that same extension is an awful big ask!
> OutsideIn(X) is a big paper to read, let alone implement, and the only
> compiler to even try handling (~) today is GHC.
>
> -Edward
>
> On Fri, Aug 5, 2016 at 2:15 PM, Ryan Scott  wrote:
>>
>> Hi David,
>>
>> > Could we get a separate LANGUAGE pragma just for equality constraints?
>>
>> I think we should, and I don't think we'd even need to introduce a new
>> pragma, since there's already a perfectly good one: -XTypeOperators!
>> After all, there's nothing really that special about (~) other than
>> some typechecking details. A fix to Trac #9194 [1] would give us this.
>>
>> Ryan S.
>> -
>> [1] https://ghc.haskell.org/trac/ghc/ticket/9194
>> ___
>> 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: Deriving tweaking

2016-08-05 Thread David Feuer
Excellent!

On Aug 5, 2016 2:32 PM, "Edward Kmett"  wrote:

> Done and done! Retroactively. How is that for service? =)
>
> -Edward
>
> On Fri, Aug 5, 2016 at 2:08 PM, David Feuer  wrote:
>
>> I know there's been some discussion about letting users select the
>> deriving mechanism they want, but I'd like to propose a separate tweak to
>> the defaults. Specifically, it's annoying to have to use three pragmas to
>> let me write
>>
>> newtype Foo f a = Foo (f a) deriving (Functor, Foldable, Traversable)
>> data Bar f a = Bar (f a) deriving (Functor, Foldable, Traversable)
>>
>> and more annoying still that I'll end up with Foldable and Functor
>> instances for Foo that may be much worse than GND-derived ones.
>>
>> The tweaks I'm after:
>>
>> 1. Prefer GND to the built-in derivations for Functor and Foldable, and
>> probably also Eq and Ord.
>> 2. Make DeriveTraversable imply DeriveFunctor and DeriveFoldable.
>>
>> ___
>> 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: Deriving tweaking

2016-08-05 Thread Edward Kmett
Done and done! Retroactively. How is that for service? =)

-Edward

On Fri, Aug 5, 2016 at 2:08 PM, David Feuer  wrote:

> I know there's been some discussion about letting users select the
> deriving mechanism they want, but I'd like to propose a separate tweak to
> the defaults. Specifically, it's annoying to have to use three pragmas to
> let me write
>
> newtype Foo f a = Foo (f a) deriving (Functor, Foldable, Traversable)
> data Bar f a = Bar (f a) deriving (Functor, Foldable, Traversable)
>
> and more annoying still that I'll end up with Foldable and Functor
> instances for Foo that may be much worse than GND-derived ones.
>
> The tweaks I'm after:
>
> 1. Prefer GND to the built-in derivations for Functor and Foldable, and
> probably also Eq and Ord.
> 2. Make DeriveTraversable imply DeriveFunctor and DeriveFoldable.
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Can we offer ~ without GADTs or type families?

2016-08-05 Thread Edward Kmett
TypeOperators as a language extension doesn't require a whole lot on the
behalf of implementors today. They basically just have to add fixity
handling to types. This is a no-brainer for a compiler implementor. It is a
simple elaboration and some extra cases to deal with in their parser. The
typechecker changes are obvious.

Asking them to do all the things to support 'some typechecking details'
that aren't entirely trivial to support that same extension is an awful big
ask! OutsideIn(X) is a big paper to read, let alone implement, and the only
compiler to even try handling (~) today is GHC.

-Edward

On Fri, Aug 5, 2016 at 2:15 PM, Ryan Scott  wrote:

> Hi David,
>
> > Could we get a separate LANGUAGE pragma just for equality constraints?
>
> I think we should, and I don't think we'd even need to introduce a new
> pragma, since there's already a perfectly good one: -XTypeOperators!
> After all, there's nothing really that special about (~) other than
> some typechecking details. A fix to Trac #9194 [1] would give us this.
>
> Ryan S.
> -
> [1] https://ghc.haskell.org/trac/ghc/ticket/9194
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Can we offer ~ without GADTs or type families?

2016-08-05 Thread Ryan Scott
Hi David,

> Could we get a separate LANGUAGE pragma just for equality constraints?

I think we should, and I don't think we'd even need to introduce a new
pragma, since there's already a perfectly good one: -XTypeOperators!
After all, there's nothing really that special about (~) other than
some typechecking details. A fix to Trac #9194 [1] would give us this.

Ryan S.
-
[1] https://ghc.haskell.org/trac/ghc/ticket/9194
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Deriving tweaking

2016-08-05 Thread David Feuer
I know there's been some discussion about letting users select the deriving
mechanism they want, but I'd like to propose a separate tweak to the
defaults. Specifically, it's annoying to have to use three pragmas to let
me write

newtype Foo f a = Foo (f a) deriving (Functor, Foldable, Traversable)
data Bar f a = Bar (f a) deriving (Functor, Foldable, Traversable)

and more annoying still that I'll end up with Foldable and Functor
instances for Foo that may be much worse than GND-derived ones.

The tweaks I'm after:

1. Prefer GND to the built-in derivations for Functor and Foldable, and
probably also Eq and Ord.
2. Make DeriveTraversable imply DeriveFunctor and DeriveFoldable.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Can we offer ~ without GADTs or type families?

2016-08-05 Thread David Feuer
It seems to me that equality constraints could potentially be supported by
an implementation with neither GADTs nor type families. Type families don't
really seem to have much to do with it, and GADTs are strictly heavier
(GADTs ~= ExistentialQuantification + TypeEquality).

Could we get a separate LANGUAGE pragma just for equality constraints?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Request for feedback: deriving strategies syntax

2016-08-05 Thread Shayan Najd
Hi all,

Shayan, have you written anything describing how things are going?


Ben,
  thank you for reaching out.

I am not sure about the history and the context of the discussions in this
thread so far, but here is a brief description of what we intend to do and
how far we have come so far.

The idea is simple: allow grand larceny, with a clear conscience!
We are trying to allow metaprograms to directly access and reuse the
"native" machinery inside the compiler. There is no need to have a separate
representation of syntax, and the associated sets of tools, as in Template
Haskell, or even as in third-party libraries like Haskell-Src-Exts (HSE)
and others in Haskell-Suite. GHC has a "native" representation of terms,
with many tools already built on top of that, including the compiler passes
like the renamer, or the typechecker. We would certainly like to unify
these representations and tools as much as possible, and allow metaprograms
to directly access these internal machineries.

The eventual goal is indeed more than sole reuse of the AST in GHC (HsSyn);
metaprograms should also be able to reuse the "infrastructure" like the
different environments and monads used for name resolution or typechecking.
If we are to treat `deriving`, and many other similar constructs in the
language simply as metaprograms, access to types is *sometimes* crucial:
they describe a type-directed elaboration process.
I am a strong advocate of such simplifications for both the front-end
(i.e., how users perceive constructs in the language), and the back-end
(i.e., how the compiler implements them). However, there is a huge, often
underestimated, gap between having these constructs as built-in, and
 having them as yet another metaprogram. The gap is both in theory, e.g.,
the equational and algebraic properties of the constructs, and in practice,
e.g., handling the error messages and maintain the general
macro/metaprogramming system allowing for such definitions. Many
researchers, including me, have worked on these problems; there is still
work to be done. We can discuss some of these related works, if you are
interested.

For now, as the first step, we are focusing on how to reuse GHC AST (HsSyn)
for metaprogramming. The immediate problem with reusing GHC AST is that it
comes with a large set of extra fields and constructors carrying the
information only necessary for the passes inside GHC.
Users (metaprogrammers?) do not want to, and do not need to, deal with
these extra fields and constructors. Moreover, the AST should be,
to some degree, easy to use, and we have no exact metric for the ease of
use.

Our solution is twofold, addressing the two mentioned problems:
  (a) after a rather deep analysis, we have come up with a simple, yet
powerful, encoding of extensible ASTs that allows us to extend a base AST
with new fields and constructors;
  (b) we are updating GHC AST to match HSE AST, hence unifying the two
(based on its popularity, we can say HSE is easy enough to use).

In theory, due to (a), code for GHC passes do not need to change.
In practice, due to (b), we may need to update the code in GHC passes in
some cases.

It is needless to say, that this is all work in progress.
Following Simon's suggestion, I am planning to give a talk on this in
Haskell Implementors' Workshop in Japan. But since then, for further
information, you may be brave enough to read our sketchy notes / pieces of
code:
- An example using the extensible encoding (a bit outdated variant though):

https://github.com/shayan-najd/NativeMetaprogramming/blob/master/HsSyn/Example.hs
- Discussion on why this extensible encoding is suitable:

https://github.com/shayan-najd/NativeMetaprogramming/wiki/Extensions-&-Annotations
- To see progress on unifying HSE AST and GHC AST compare
  the updated GHC AST at

https://github.com/shayan-najd/NativeMetaprogramming/blob/master/HsSyn/SyntaxExtensibleAutoSplitted.hs
  and the updated HSE AST at

https://github.com/shayan-najd/NativeMetaprogramming/blob/master/HSE/SyntaxExtensibleAuto.hs
   They should be line-by-line comparable unless the comments says so
otherwise.

There is much to be done without a doubt, specially to synchronise with and
learn form communities working on similar topics

Yours,
  Shayan

On Fri, Aug 5, 2016 at 11:06 AM, Ben Gamari  wrote:

> Ryan Scott  writes:
>
> > Sorry for not including the full context on that link. It's part of a
> > Summer of Haskell 2016 project called Native Metaprogramming in
> > Haskell [1] (a.k.a. Introspective Template Haskell [2]), aiming to fix
> > Trac #11081 [3].
> >
> On this note, it would be great to hear a bit about the state of this
> project. Shayan, have you written anything describing how things are
> going? It would be great if you could update the Wiki page [2]
> describing a bit about the approach you have taken and the current state
> of your implementation.
>
> Cheers,
>
> - Ben
>

Re: Request for feedback: deriving strategies syntax

2016-08-05 Thread Bardur Arantsson
On 2016-08-05 11:06, Ben Gamari wrote:
> Ryan Scott  writes:
> 
>> Sorry for not including the full context on that link. It's part of a
>> Summer of Haskell 2016 project called Native Metaprogramming in
>> Haskell [1] (a.k.a. Introspective Template Haskell [2]), aiming to fix
>> Trac #11081 [3].
>>
> On this note, it would be great to hear a bit about the state of this
> project. Shayan, have you written anything describing how things are
> going? It would be great if you could update the Wiki page [2]
> describing a bit about the approach you have taken and the current state
> of your implementation.
> 

Just a little aside: AFAICT the idea here was originally to reuse the
compiler's internal AST representation. I'd be really interested to hear
if that's changed.

This compes along with a little cautionary note: The Scala people
originally did this for their macro support and it's being abandoned in
favor of something called TASTY which is a different (simplified?)
representation of the Scala AST. (There were a lot of other problems
with the Scala macro implementation which is caused by simply being
intimately tied to compiler internals in *other* ways.) Obviously, all
of this is AFAIUI and my understanding may not exactly be great, but
regardless I think it's worth looking into Scala/TASTY and why the Scala
people have (apparently) chosen it as the solution over the existing one.

Regards,

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


RdrName and decorations

2016-08-05 Thread Alan & Kim Zimmerman
Hi all

At the moment I am working through ghc-exactprint, adding a feature to add
standard API annotations to any constructed AST so that it can be
(pretty)-printed.

One of the major headaches is the decorations on a RdrName.

What I mean by this is that an item appearing in the AST as a RdrName may
have parens or backquotes around it, and may have a preceding keyword out
of [forall, pattern, type].

I am slowly teasing out the contextual requirements to determine these, but
it seems that they should be captured directly in the AST already.  And not
as API Annotations.

So the question is, does it make sense to do this?  Does it belong in the
OccName or the RdrName if so?


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


Re: Request for feedback: deriving strategies syntax

2016-08-05 Thread Ben Gamari
Ryan Scott  writes:

> Sorry for not including the full context on that link. It's part of a
> Summer of Haskell 2016 project called Native Metaprogramming in
> Haskell [1] (a.k.a. Introspective Template Haskell [2]), aiming to fix
> Trac #11081 [3].
>
On this note, it would be great to hear a bit about the state of this
project. Shayan, have you written anything describing how things are
going? It would be great if you could update the Wiki page [2]
describing a bit about the approach you have taken and the current state
of your implementation.

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