Re: Trees that Grow and constraints

2017-11-13 Thread Alan & Kim Zimmerman
I have updated the page, with a bit more detail and an additional plan


> OK.  It’s hard to keep this straight in email. Take a look at
>>
>> https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/Instances
>>
>>
>>
>> Please edit and improve it.
>>
>>
Alan
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Trees that Grow and constraints

2017-11-13 Thread Alan & Kim Zimmerman
Will do

Alan

On 13 November 2017 at 19:08, Simon Peyton Jones 
wrote:

> Alan (adding Shayan and ghc-devs)
>
>
>
> OK.  It’s hard to keep this straight in email. Take a look at
>
> https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/Instances
>
>
>
> Please edit and improve it.
>
>
>
> Simon
>
>
>
>
>
> *From:* Alan & Kim Zimmerman [mailto:alan.z...@gmail.com]
> *Sent:* 13 November 2017 13:30
>
> *To:* Simon Peyton Jones 
> *Subject:* Re: Trees that Grow and constraints
>
>
>
> At the moment, in GHC master, we have
>
> data HsOverLit p
>
>   = OverLit {
>
>   ol_ext :: (XOverLit p),
>
>   ol_val :: OverLitVal,
>
>   ol_witness :: HsExpr p} -- Note [Overloaded literal witnesses]
>
>
>
>   | XOverLit
>
>   (XXOverLit p)
>
> deriving instance (DataIdLR p p) => Data (HsOverLit p)
>
>
>
> And in HsExtension.hs we have an ever-growing constraint type defining 
> DataIdLR
>
> I am trying to remove the need for that.
>
> In the Experiment.hs file, I found that using
>
> data Experiment p
>   = Experiment {
>   e_ext :: (XEOverLit p),
>   e_val :: Int }
>   | XExperiment (XXOverLit p)
> deriving instance Data (GhcPass 'Parsed ) => Data (Experiment (GhcPass 
> 'Parsed ))
> deriving instance Data (GhcPass 'Renamed) => Data (Experiment (GhcPass 
> 'Renamed))
> deriving instance Data (GhcPass 'Typechecked) => Data (Experiment (GhcPass 
> 'Typechecked))
>
> will compile using GHC 8.2.1, but not with GHC 8.0.2
>
>
>
> Alan
>
>
>
> On 13 November 2017 at 15:13, Simon Peyton Jones 
> wrote:
>
> And it looks like it could work, when bootstrapping from GHC 8.2.1, but
> this is still a long time away.
>
>
>
> I’m sorry, I still don’t know what “it” is that “could work”.  Can you be
> more precise.  I think you must be suggesting some alternative to my code
> below?
>
>
>
> Simon
>
>
>
> *From:* Alan & Kim Zimmerman [mailto:alan.z...@gmail.com]
> *Sent:* 13 November 2017 13:09
>
>
> *To:* Simon Peyton Jones 
> *Subject:* Re: Trees that Grow and constraints
>
>
>
> Yes.
>
>
>
> If we can solve this, it means we can get rid of the DataId and ForallXXX
> constraints defined in hsSyn/HsExtension.hs
>
>
>
> And also move the type family definitions to the files where they are used.
>
>
>
> I suspect that typechecking those constraint sets is adding to the GHC
> compilation time, significantly
>
>
>
> And it looks like it could work, when bootstrapping from GHC 8.2.1, but
> this is still a long time away.
>
>
>
> Alan
>
>
>
> On 13 November 2017 at 15:05, Simon Peyton Jones 
> wrote:
>
> That’s not a problem you are trying to solve – it’s just some code .
>
>
>
> Let me hazard a guess.  You want a derived instance for
>
>
>
> Data (OverLit (GhcPass p))
>
>
>
> But to do that of course we’ll need  Data (XEOverLit (GhcPass p)).
>
>
>
> We can’t possibly have that at the time of writing the instance
> declaration, because p is universally quantified.  So we are stuck with
>
>
>
> instance (Data (XEOverLit (GhcPass p))) => Data (OverLit
> (GhcPass p)) where…
>
>
>
> and the context gets a constraint for every extension field in OverLit,
> which is painful.
>
>
>
> So we have a solution bit contexts, but it’s painful.
>
>
>
> Is that the problem you are trying to solve?
>
>
>
> Simon
>
>
>
> *From:* Alan & Kim Zimmerman [mailto:alan.z...@gmail.com]
> *Sent:* 13 November 2017 13:01
> *To:* Simon Peyton Jones 
>
> *Subject:* Re: Trees that Grow and constraints
>
>
>
> Sorry, I simplified the problem.
>
> The actual one I am trying to solve will be the general case, so e.g.
>
>  type instance XEOverLit (GhcPass 'Parsed ) = RdrName
>  type instance XEOverLit (GhcPass 'Renamed) = Name
>  type instance XEOverLit (GhcPass 'Typechecked) = Id
>
> or more likely, modelling the existing PostTc and PostRn usages.
>
> And I suppose looking into using them in a single definition might work
>
> Alan
>
>
>
>
>
> On 13 November 2017 at 14:55, Simon Peyton Jones 
> wrote:
>
> Or do I misunderstand your advice?
>
>
>
> Well, you said
>
> Where specifying the type instance with a wild card keeps GHC happy (the
> XXOverLit case), but specifying for each of the three constructors for pass
> does not (the XEOverLit case)
>
> My question is: why not just use the wildcard, in that case?
>
> Do you want to re-state the problem you are trying to solve?
>
>
>
> Simon
>
>
>
>
>
> *From:* Alan & Kim Zimmerman [mailto:alan.z...@gmail.com]
> *Sent:* 13 November 2017 12:49
> *To:* Simon Peyton Jones 
> *Cc:* ghc-devs@haskell.org
> *Subject:* Re: Trees that Grow and constraints
>
>
>
>
>
> So why not use one?
>
>
>
> Simon
>
>
>
> If I do
>
> instance (Data p) => Data (Experiment p)
>
> then GHC does not know that the type instances for
>
>
>  type instance XEOverLit (GhcPass 

RE: Trees that Grow and constraints

2017-11-13 Thread Simon Peyton Jones via ghc-devs
Alan (adding Shayan and ghc-devs)

OK.  It’s hard to keep this straight in email. Take a look at
https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/Instances

Please edit and improve it.

Simon


From: Alan & Kim Zimmerman [mailto:alan.z...@gmail.com]
Sent: 13 November 2017 13:30
To: Simon Peyton Jones 
Subject: Re: Trees that Grow and constraints

At the moment, in GHC master, we have

data HsOverLit p

  = OverLit {

  ol_ext :: (XOverLit p),

  ol_val :: OverLitVal,

  ol_witness :: HsExpr p} -- Note [Overloaded literal witnesses]



  | XOverLit

  (XXOverLit p)

deriving instance (DataIdLR p p) => Data (HsOverLit p)


And in HsExtension.hs we have an ever-growing constraint type defining DataIdLR

I am trying to remove the need for that.

In the Experiment.hs file, I found that using

data Experiment p
  = Experiment {
  e_ext :: (XEOverLit p),
  e_val :: Int }
  | XExperiment (XXOverLit p)
deriving instance Data (GhcPass 'Parsed ) => Data (Experiment (GhcPass 
'Parsed ))
deriving instance Data (GhcPass 'Renamed) => Data (Experiment (GhcPass 
'Renamed))
deriving instance Data (GhcPass 'Typechecked) => Data (Experiment (GhcPass 
'Typechecked))

will compile using GHC 8.2.1, but not with GHC 8.0.2



Alan

On 13 November 2017 at 15:13, Simon Peyton Jones 
> wrote:
And it looks like it could work, when bootstrapping from GHC 8.2.1, but this is 
still a long time away.

I’m sorry, I still don’t know what “it” is that “could work”.  Can you be more 
precise.  I think you must be suggesting some alternative to my code below?

Simon

From: Alan & Kim Zimmerman 
[mailto:alan.z...@gmail.com]
Sent: 13 November 2017 13:09

To: Simon Peyton Jones >
Subject: Re: Trees that Grow and constraints

Yes.

If we can solve this, it means we can get rid of the DataId and ForallXXX 
constraints defined in hsSyn/HsExtension.hs

And also move the type family definitions to the files where they are used.

I suspect that typechecking those constraint sets is adding to the GHC 
compilation time, significantly

And it looks like it could work, when bootstrapping from GHC 8.2.1, but this is 
still a long time away.

Alan

On 13 November 2017 at 15:05, Simon Peyton Jones 
> wrote:
That’s not a problem you are trying to solve – it’s just some code .

Let me hazard a guess.  You want a derived instance for

Data (OverLit (GhcPass p))

But to do that of course we’ll need  Data (XEOverLit (GhcPass p)).

We can’t possibly have that at the time of writing the instance declaration, 
because p is universally quantified.  So we are stuck with

instance (Data (XEOverLit (GhcPass p))) => Data (OverLit (GhcPass 
p)) where…

and the context gets a constraint for every extension field in OverLit, which 
is painful.

So we have a solution bit contexts, but it’s painful.

Is that the problem you are trying to solve?

Simon

From: Alan & Kim Zimmerman 
[mailto:alan.z...@gmail.com]
Sent: 13 November 2017 13:01
To: Simon Peyton Jones >
Subject: Re: Trees that Grow and constraints

Sorry, I simplified the problem.
The actual one I am trying to solve will be the general case, so e.g.

 type instance XEOverLit (GhcPass 'Parsed ) = RdrName
 type instance XEOverLit (GhcPass 'Renamed) = Name
 type instance XEOverLit (GhcPass 'Typechecked) = Id
or more likely, modelling the existing PostTc and PostRn usages.
And I suppose looking into using them in a single definition might work
Alan


On 13 November 2017 at 14:55, Simon Peyton Jones 
> wrote:
Or do I misunderstand your advice?

Well, you said
Where specifying the type instance with a wild card keeps GHC happy (the 
XXOverLit case), but specifying for each of the three constructors for pass 
does not (the XEOverLit case)
My question is: why not just use the wildcard, in that case?
Do you want to re-state the problem you are trying to solve?

Simon


From: Alan & Kim Zimmerman 
[mailto:alan.z...@gmail.com]
Sent: 13 November 2017 12:49
To: Simon Peyton Jones >
Cc: ghc-devs@haskell.org
Subject: Re: Trees that Grow and constraints


So why not use one?

Simon

If I do

instance (Data p) => Data (Experiment p)
then GHC does not know that the type instances for


 type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
 type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
 type instance XEOverLit (GhcPass 'Typechecked) = PlaceHolder
apply.

Or do I misunderstand your advice?

Alan



___
ghc-devs 

Re: Trees that Grow and constraints

2017-11-13 Thread Shayan Najd
Isn't the solution always
  if generic programming makes things complicated, avoid it!

Here generic programming is where you define instances parametric on the
phase index.
Why not defining three instances of the type class, one per each phase?
Yes, we get code duplication (which in this case is still not much as we
use automatic deriving), but the compilation gets faster (which is the
motivation), like [2].

[2] http://lpaste.net/360019

/Shayan



On Mon, Nov 13, 2017 at 2:05 PM, Alan & Kim Zimmerman 
wrote:

> Just to clarify, this example is a simplification, in practice we would be
> applying different type for each type instance
>
> e.g.
>
> type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
> type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
> type instance XEOverLit (GhcPass 'Typechecked) = Type
>
> (modelling existing PostTc)
>
> Alan
>
> On 13 November 2017 at 11:23, Alan & Kim Zimmerman 
> wrote:
>
>> At the moment the Trees that Grow implementation in GHC master makes use
>> of massive constraint types to provide Data instances for the hsSyn AST.
>>
>> I am trying to remove the need for this, and have hit a problem.
>>
>> The example I have reduced it to is here [1]
>>
>> The essence of the problem is
>>
>> ---
>> data Experiment p
>>   = Experiment {
>>   e_ext :: (XEOverLit p),
>>   e_val :: Int }
>>   | XExperiment (XXOverLit p)
>> deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
>>
>> type family XEOverLit  x
>> type family XXOverLit x
>>
>> -- The following line works
>> -- type instance XEOverLit (GhcPass _) = PlaceHolder
>>
>> -- The following 3 lines do noe
>> type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
>> type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
>> type instance XEOverLit (GhcPass 'Typechecked) = PlaceHolder
>>
>> type instance XXOverLit (GhcPass _) = PlaceHolder
>> ---
>>
>> Where specifying the type instance with a wild card keeps GHC happy (the
>> XXOverLit case), but specifying for each of the three constructors for pass
>> does not (the XEOverLit case)
>>
>> The exact error message is
>>
>> --
>> Experiment.hs:34:1: error:
>> • Could not deduce (Data (XEOverLit (GhcPass p)))
>> arising from a use of ‘k’
>>   from the context: Data (GhcPass p)
>> bound by the instance declaration at Experiment.hs:34:1-69
>> • In the first argument of ‘k’, namely ‘(z Experiment `k` a1)’
>>   In the expression: ((z Experiment `k` a1) `k` a2)
>>   In an equation for ‘gfoldl’:
>>   gfoldl k z Experiment a1 a2 = ((z Experiment `k` a1) `k` a2)
>>   When typechecking the code for ‘gfoldl’
>> in a derived instance for ‘Data (Experiment (GhcPass p))’:
>> To see the code I am typechecking, use -ddump-deriv
>>|
>> 34 | deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
>>| 
>> ^
>> --
>>
>> Alan
>>
>> [1] http://lpaste.net/360017
>>
>>
>>
>
> ___
> 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: Dynamically choosing the main function

2017-11-13 Thread Brandon Allbery
On Mon, Nov 13, 2017 at 2:46 AM, Harendra Kumar 
wrote:

> Also, the symbols are anyway exposed to the users, we just ask the users
> to not look at those.
>

Only if you built a dynamic executable, or built for debugging. Default
static executables are stripped.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: [commit: ghc] master: WIP on combined Step 1 and 3 for Trees That Grow, HsExpr (e3ec2e7)

2017-11-13 Thread Ben Gamari
Manuel M T Chakravarty  writes:

>> I noted this on D4177 and discussed the effect with Alan. Indeed there is 
>> quite a sizeable regression in compilation time but thankfully this is not 
>> because GHC itself is slower. Rather, it simply requires more work to 
>> compile. I did a set of nofib runs with and without the first TTG patch and 
>> found that compiler allocations remained essentially unchanged.
>> 
>> A 15% regression in the compilation time of GHC is indeed hard to stomach 
>> but Alan had said that much of this will likely disappear in the future. If 
>> this is the case then a temporary regression is in my opinion acceptable.
>
> Hmm, on what grounds does he think that this is going to disappear and how 
> likely is likely? This doesn’t sound convincing TBH.
>
As Alan has pointed out elsewhere, currently the TTG involves some
unnecessarily large constraints which very likely inflate typechecking
time. This is almost certainly why we are seeing such increases in 
compilation time of the compiler (and, as importantly, no changes in the
performance characteristics of the resulting compiler).

Given how consistent the story seems to be, a reduction after the
constraints are simplified sounds very likely.

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


Re: Trees that Grow and constraints

2017-11-13 Thread Alan & Kim Zimmerman
Just to clarify, this example is a simplification, in practice we would be
applying different type for each type instance

e.g.

type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
type instance XEOverLit (GhcPass 'Typechecked) = Type

(modelling existing PostTc)

Alan

On 13 November 2017 at 11:23, Alan & Kim Zimmerman 
wrote:

> At the moment the Trees that Grow implementation in GHC master makes use
> of massive constraint types to provide Data instances for the hsSyn AST.
>
> I am trying to remove the need for this, and have hit a problem.
>
> The example I have reduced it to is here [1]
>
> The essence of the problem is
>
> ---
> data Experiment p
>   = Experiment {
>   e_ext :: (XEOverLit p),
>   e_val :: Int }
>   | XExperiment (XXOverLit p)
> deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
>
> type family XEOverLit  x
> type family XXOverLit x
>
> -- The following line works
> -- type instance XEOverLit (GhcPass _) = PlaceHolder
>
> -- The following 3 lines do noe
> type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
> type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
> type instance XEOverLit (GhcPass 'Typechecked) = PlaceHolder
>
> type instance XXOverLit (GhcPass _) = PlaceHolder
> ---
>
> Where specifying the type instance with a wild card keeps GHC happy (the
> XXOverLit case), but specifying for each of the three constructors for pass
> does not (the XEOverLit case)
>
> The exact error message is
>
> --
> Experiment.hs:34:1: error:
> • Could not deduce (Data (XEOverLit (GhcPass p)))
> arising from a use of ‘k’
>   from the context: Data (GhcPass p)
> bound by the instance declaration at Experiment.hs:34:1-69
> • In the first argument of ‘k’, namely ‘(z Experiment `k` a1)’
>   In the expression: ((z Experiment `k` a1) `k` a2)
>   In an equation for ‘gfoldl’:
>   gfoldl k z Experiment a1 a2 = ((z Experiment `k` a1) `k` a2)
>   When typechecking the code for ‘gfoldl’
> in a derived instance for ‘Data (Experiment (GhcPass p))’:
> To see the code I am typechecking, use -ddump-deriv
>|
> 34 | deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
>| ^
> --
>
> Alan
>
> [1] http://lpaste.net/360017
>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Trees that Grow and constraints

2017-11-13 Thread Alan & Kim Zimmerman
> So why not use one?
>
>
>
> Simon
>
>
If I do

instance (Data p) => Data (Experiment p)

then GHC does not know that the type instances for


 type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
 type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
 type instance XEOverLit (GhcPass 'Typechecked) = PlaceHolder

apply.

Or do I misunderstand your advice?

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


RE: Trees that Grow and constraints

2017-11-13 Thread Simon Peyton Jones via ghc-devs
Where specifying the type instance with a wild card keeps GHC happy (the 
XXOverLit case), but specifying for each of the three constructors for pass 
does not (the XEOverLit case)
Well, of course!  The derived data instance looks something like

instance (Data (GhcPass p)) => Data (Experiment (GhcPass p)) where
   gfoldl = ….Needs (Data (XEOverLit (GhcPass p)))…

How can GHC solve the wanted constraint
Data (XEOverlit (GhcPass p))

With three equations, it can’t. With one, it can.

So why not use one?

Simon

From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Alan & Kim 
Zimmerman
Sent: 13 November 2017 09:24
To: ghc-devs@haskell.org
Subject: Trees that Grow and constraints

At the moment the Trees that Grow implementation in GHC master makes use of 
massive constraint types to provide Data instances for the hsSyn AST.
I am trying to remove the need for this, and have hit a problem.
The example I have reduced it to is here [1]
The essence of the problem is

---
data Experiment p
  = Experiment {
  e_ext :: (XEOverLit p),
  e_val :: Int }
  | XExperiment (XXOverLit p)
deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))

type family XEOverLit  x
type family XXOverLit x

-- The following line works
-- type instance XEOverLit (GhcPass _) = PlaceHolder

-- The following 3 lines do noe
type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
type instance XEOverLit (GhcPass 'Typechecked) = PlaceHolder

type instance XXOverLit (GhcPass _) = PlaceHolder
---

Where specifying the type instance with a wild card keeps GHC happy (the 
XXOverLit case), but specifying for each of the three constructors for pass 
does not (the XEOverLit case)

The exact error message is

--
Experiment.hs:34:1: error:
• Could not deduce (Data (XEOverLit (GhcPass p)))
arising from a use of ‘k’
  from the context: Data (GhcPass p)
bound by the instance declaration at Experiment.hs:34:1-69
• In the first argument of ‘k’, namely ‘(z Experiment `k` a1)’
  In the expression: ((z Experiment `k` a1) `k` a2)
  In an equation for ‘gfoldl’:
  gfoldl k z Experiment a1 a2 = ((z Experiment `k` a1) `k` a2)
  When typechecking the code for ‘gfoldl’
in a derived instance for ‘Data (Experiment (GhcPass p))’:
To see the code I am typechecking, use -ddump-deriv
   |
34 | deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
   | ^
--

Alan

[1] 
http://lpaste.net/360017


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


Re: Trees that Grow and constraints

2017-11-13 Thread Alan & Kim Zimmerman
And it seems that

--
data Experiment p
  = Experiment {
  e_ext :: (XEOverLit p),
  e_val :: Int }
  | XExperiment (XXOverLit p)
deriving instance (Data GhcPs) => Data (Experiment GhcPs)
deriving instance (Data GhcRn) => Data (Experiment GhcRn)
deriving instance (Data GhcTc) => Data (Experiment GhcTc)


works, but only for GHC 8.2.1, not GHC 8.0.2

Alan

On 13 November 2017 at 11:23, Alan & Kim Zimmerman 
wrote:

> At the moment the Trees that Grow implementation in GHC master makes use
> of massive constraint types to provide Data instances for the hsSyn AST.
>
> I am trying to remove the need for this, and have hit a problem.
>
> The example I have reduced it to is here [1]
>
> The essence of the problem is
>
> ---
> data Experiment p
>   = Experiment {
>   e_ext :: (XEOverLit p),
>   e_val :: Int }
>   | XExperiment (XXOverLit p)
> deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
>
> type family XEOverLit  x
> type family XXOverLit x
>
> -- The following line works
> -- type instance XEOverLit (GhcPass _) = PlaceHolder
>
> -- The following 3 lines do noe
> type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
> type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
> type instance XEOverLit (GhcPass 'Typechecked) = PlaceHolder
>
> type instance XXOverLit (GhcPass _) = PlaceHolder
> ---
>
> Where specifying the type instance with a wild card keeps GHC happy (the
> XXOverLit case), but specifying for each of the three constructors for pass
> does not (the XEOverLit case)
>
> The exact error message is
>
> --
> Experiment.hs:34:1: error:
> • Could not deduce (Data (XEOverLit (GhcPass p)))
> arising from a use of ‘k’
>   from the context: Data (GhcPass p)
> bound by the instance declaration at Experiment.hs:34:1-69
> • In the first argument of ‘k’, namely ‘(z Experiment `k` a1)’
>   In the expression: ((z Experiment `k` a1) `k` a2)
>   In an equation for ‘gfoldl’:
>   gfoldl k z Experiment a1 a2 = ((z Experiment `k` a1) `k` a2)
>   When typechecking the code for ‘gfoldl’
> in a derived instance for ‘Data (Experiment (GhcPass p))’:
> To see the code I am typechecking, use -ddump-deriv
>|
> 34 | deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
>| ^
> --
>
> Alan
>
> [1] http://lpaste.net/360017
>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Trees that Grow and constraints

2017-11-13 Thread Alan & Kim Zimmerman
At the moment the Trees that Grow implementation in GHC master makes use of
massive constraint types to provide Data instances for the hsSyn AST.

I am trying to remove the need for this, and have hit a problem.

The example I have reduced it to is here [1]

The essence of the problem is

---
data Experiment p
  = Experiment {
  e_ext :: (XEOverLit p),
  e_val :: Int }
  | XExperiment (XXOverLit p)
deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))

type family XEOverLit  x
type family XXOverLit x

-- The following line works
-- type instance XEOverLit (GhcPass _) = PlaceHolder

-- The following 3 lines do noe
type instance XEOverLit (GhcPass 'Parsed ) = PlaceHolder
type instance XEOverLit (GhcPass 'Renamed) = PlaceHolder
type instance XEOverLit (GhcPass 'Typechecked) = PlaceHolder

type instance XXOverLit (GhcPass _) = PlaceHolder
---

Where specifying the type instance with a wild card keeps GHC happy (the
XXOverLit case), but specifying for each of the three constructors for pass
does not (the XEOverLit case)

The exact error message is

--
Experiment.hs:34:1: error:
• Could not deduce (Data (XEOverLit (GhcPass p)))
arising from a use of ‘k’
  from the context: Data (GhcPass p)
bound by the instance declaration at Experiment.hs:34:1-69
• In the first argument of ‘k’, namely ‘(z Experiment `k` a1)’
  In the expression: ((z Experiment `k` a1) `k` a2)
  In an equation for ‘gfoldl’:
  gfoldl k z Experiment a1 a2 = ((z Experiment `k` a1) `k` a2)
  When typechecking the code for ‘gfoldl’
in a derived instance for ‘Data (Experiment (GhcPass p))’:
To see the code I am typechecking, use -ddump-deriv
   |
34 | deriving instance (Data (GhcPass p)) => Data (Experiment (GhcPass p))
   | ^
--

Alan

[1] http://lpaste.net/360017
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs