Operating on HsSyn

Shayan Najd sh.najd at gmail.com
Mon Jul 31 00:19:01 UTC 2017


Simon,

Back to your original questions:

1. I think we should probably use a superclass instead of a type synonym
>
> class (Data p, ForallX Data p, ....) => DataId p where {}
>
> Why?  Only one argument to pass, and to pass on to successive calls.  I
> see no downside.


Sounds good to me. I have not experimented with it yet, but I see no
downside as well.

Shall we treat Outputable like Data?  (I.e. make an abbreviation for a long
> list of Outputable instances and use it everywhere)


Besides, the above point about semantics and reusing it as classical
pretty-printer, I suggest a bit more fine-grained abbreviations, if we are
going along this path:
 we define the abbreviations per datatype (as opposed to all), we define
`ForallXNAME :: constraint -> *` (as in Section 3.7 of the paper) where
`NAME` is name of the datatype.

However, we do NOT need Trees that Grow in its full generality: as far as I
understand, we do not have GADTs or existentials in GHC ASTs.
This means we can use the simpler design of Trees that Grow that all
extension families had the same arity and kind, then we could factor them
all into one type family dispatching on some unique identifier.
(we used type-level strings, or promoted datatypes for annotations.)

For example, the following in absence of existentials

> type family XVar x a
> type family XApp x a
> type family XAbs x a
> data Exp x a
>  = Var (XVar x a) a
>  | Abs (XAbs x a) a (Exp x a)
>  | App (XApp x a) (Exp x a) (Exp x a)

is as good as (one of our very first extensible encodings)

> type family XDispatch name x a
> data Lbl = VarL | AbsL | AppL
> data Exp x a
>  = Var (XDispatch VarL x a) a
>  | Abs (XDispatch AbsL x a) a (Exp x a)
>  | App (XDispatch AppL x a) (Exp x a) (Exp x a)

We could do the same with promoted datatypes as annotations (instead of
type-level strings).

The advantage of the simpler encoding is that now, in theory, we can define

> ForallXExp (c :: Constraint) x a = forall l. c (XDispatch l x a)

Which gives us for example `ForallXExp Outputable x a `.

Is this encoding faster, in comparison? Does it help?

/Shayan









On Fri, Jul 28, 2017 at 10:11 PM, Shayan Najd <sh.najd at gmail.com> wrote:

> MarLinn,
>    Thanks for correcting me, and spelling this out.
>    I did mean what Alan mentioned: "re-parsing a pretty printed parse tree
> gives you back a parse tree identical to the original (ignoring SrcSpans)".
>    As I recall, we had to go a bit further to give 'Something' some more
> structure to take into account things like "(ignoring SrcSpans)" (e.g., to
> define exact-printers, etc).
>    Provided I have failed twice to properly recall the invariant, I
> refrain from trying to recall the rest tonight :)
>
> Not diverging from my point above, as far as I understand, an ideal
> `Outputable` machinery is going to be a bit different from the traditional
> pretty printers.
> I believe with a proper design we can even reuse `Outputable` machinery
> and provide it as a pretty printer for Haskell terms.
> It resembles the scenario in Section 3.7 compared to Section 3.6 of Trees
> that Grow [1].
>
> Having said all these, we ARE diverging from the original thread, and
> Simon's questions.
>
> How about taking printer-design related discussion to the following wiki
> page (and/or a new ghc-dev thread if needed):
>   https://ghc.haskell.org/trac/ghc/wiki/HaskellSyntaxPrinters
>
> Cheers,
>   Shayan
>
> [1] http://www.jucs.org/jucs_23_1/trees_that_grow/jucs_23_
> 01_0042_0062_najd.pdf
>
> On Fri, Jul 28, 2017 at 8:43 PM, Alan & Kim Zimmerman <alan.zimm at gmail.com
> > wrote:
>
>> I agree. 4 is the current GHC invariant.
>>
>> i.e., re-parsing a pretty printed parse tree gives you back a parse tree
>> identical to the original (ignoring SrcSpans)
>>
>> Alan
>>
>> On 28 July 2017 at 20:34, MarLinn <monkleyon at gmail.com> wrote:
>>
>>> by
>>>
>>>  (parser . prettyPrint . parser) = id
>>>
>>> I meant
>>>
>>> (prettyPrint . parser . prettyPrint) = id
>>>
>>> for a valid input.
>>>
>>> Simplifying, (parser ∷ String → something), and (prettyPrint ∷
>>> something → String).
>>>
>>> Therefore, (parser . prettyPrint . parser ∷ String → something) and (prettyPrint
>>> . parser . prettyPrint ∷ something → String).
>>>
>>> Therefore, both criteria could only apply for (something ~ String). But
>>> as pretty printing adds quotation marks, not even that is true.
>>>
>>> There are four formulations that might be applicable:
>>>
>>>    1.
>>>
>>>    parser . prettyPrint ≍ id
>>>    2.
>>>
>>>    prettyPrint . parser ≍ id -- ∷ String → String, useless here
>>>    3.
>>>
>>>    prettyPrint . parser . prettyPrint ≍ prettyPrint
>>>    4.
>>>
>>>    parser . prettyPrint . parser ≍ parser
>>>    5. Well, you could go beyond to (prettyPrint . parser . prettyPrint
>>>    . parser ≍ prettyPrint . parser) etc…
>>>
>>> I don't think 1 (or 2) follow from one of the last two. But 1 does imply
>>> them. So it is a stronger criterion than both, and therefore probably not
>>> the one to choose. Assuming the parser is internally consistent, 3 just
>>> says something about the internal consistency of the pretty printer, while
>>> 4 says something about the relationship of the pretty printer to the
>>> parser. Thus 4 looks like the best candidate for a criterion. Possibly with
>>> 3 as a secondary target.
>>>
>>> Cheers,
>>> MarLinn
>>>
>>> _______________________________________________
>>> ghc-devs mailing list
>>> ghc-devs at haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>
>>>
>>
>> _______________________________________________
>> ghc-devs mailing list
>> ghc-devs at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20170731/346450d2/attachment.html>


More information about the ghc-devs mailing list