
data Exp = ... | InfixE (Maybe Exp) Exp (Maybe Exp) to something like type Op = Exp --- because TH doesn't distinguish operators from expressions data Exp = ... | InfixE [Exp] [Op] --- length [Exp] == 1 + length [Op], always | LeftSection Exp Op | RightSection Op Exp Apart from splitting of the sections, the important difference is that
This post follows on from a discussion about a month ago, called "Haskell Syntax Inside Quasiquote". To summarise, suppose I want to create a Haskell quasiquoter for lists, eg [$list|1,x^2,y,3|] (representing the list [1,x^2,y,3]) Ideally, this would allow arbitrary Haskell expressions for each element of the list (provided, of course, that the types are correct). To write this list quasiquoter, I would need to parse Haskell expressions. This is doable[1], but is necessarily buggy when infix operators are concerned. For instance, a user of the list quasiquoter may define two new operators, (+*) and (+^), and then write [$list|1+*2+^3|] Being able to correctly parse such an expression depends on known the two operator's fixities, which is currently impossible. The problem is that potentially non-local fixity declarations affect parsing. As far as I can see, the correct solution is to change the Template Haskell AST representation of fixity expressions from the expressions are parsed as a list of expressions separated by operators. So, my example above would be parsed as something like InfixE [parseExp "1", parseExp "2", parseExp "3"] ["+*", "+^"] Then, when Template Haskell performs the splice, it could correctly resolve the fixities. Of course, this would require a change to Template Haskell, so a second-best solution would be to forbid unparenthesised expressions in my quasiquoter. Then, parsing can proceed correctly without knowing the fixities. This would be easiest to do if haskell-src-exts changed its AST in a similar way to described above for Template Haskell. Any thoughts? Cheers, Reiner Pope [1] For instance, see haskell-src-meta, which uses haskell-src-exts as a parser, and then converts the AST into a form that Template Haskell recognises.

It occurs to me that changing the Template Haskell representation to a
less-information representation is disadvantageous when code has been
reified for examination by a Template Haskell-using library. In that
case, the library would want maximum knowledge about the fixities.
Perhaps the best solution is just to forbid unparenthesised infix
expressions in the quasiquote language.
Cheers,
Reiner
On Fri, Nov 21, 2008 at 11:59 PM, Reiner Pope
This post follows on from a discussion about a month ago, called "Haskell Syntax Inside Quasiquote".
To summarise, suppose I want to create a Haskell quasiquoter for lists, eg [$list|1,x^2,y,3|] (representing the list [1,x^2,y,3]) Ideally, this would allow arbitrary Haskell expressions for each element of the list (provided, of course, that the types are correct).
To write this list quasiquoter, I would need to parse Haskell expressions. This is doable[1], but is necessarily buggy when infix operators are concerned. For instance, a user of the list quasiquoter may define two new operators, (+*) and (+^), and then write [$list|1+*2+^3|] Being able to correctly parse such an expression depends on known the two operator's fixities, which is currently impossible. The problem is that potentially non-local fixity declarations affect parsing.
data Exp = ... | InfixE (Maybe Exp) Exp (Maybe Exp) to something like type Op = Exp --- because TH doesn't distinguish operators from expressions data Exp = ... | InfixE [Exp] [Op] --- length [Exp] == 1 + length [Op], always | LeftSection Exp Op | RightSection Op Exp Apart from splitting of the sections, the important difference is that
As far as I can see, the correct solution is to change the Template Haskell AST representation of fixity expressions from the expressions are parsed as a list of expressions separated by operators. So, my example above would be parsed as something like
InfixE [parseExp "1", parseExp "2", parseExp "3"] ["+*", "+^"]
Then, when Template Haskell performs the splice, it could correctly resolve the fixities.
Of course, this would require a change to Template Haskell, so a second-best solution would be to forbid unparenthesised expressions in my quasiquoter. Then, parsing can proceed correctly without knowing the fixities. This would be easiest to do if haskell-src-exts changed its AST in a similar way to described above for Template Haskell.
Any thoughts?
Cheers, Reiner Pope
[1] For instance, see haskell-src-meta, which uses haskell-src-exts as a parser, and then converts the AST into a form that Template Haskell recognises.

Of course, this would require a change to Template Haskell, so a second-best solution would be to forbid unparenthesised expressions in my quasiquoter. Then, parsing can proceed correctly without knowing the fixities. This would be easiest to do if haskell-src-exts changed its AST in a similar way to described above for Template Haskell.
I'm not sure I follow you here. In what way would it be simpler if HSE changes its AST to a less-information constructor? I won't do that, for the same reason you point out with TH and disadvantages when using it as a library, though I'm still curious what uses you envision and how it would be made easier. I'm still in the process of designing the fixity support for HSE, and all input is valuable. :-) Cheers, /Niklas

It seems to me that fixity information behaves more like semantics
than like syntax. For instance, fixities may be imported, and obey
namespacing rules. Knowing and correctly handling these rules seems
beyond the scope of a mere parser: I would hope that a single Haskell
file could be parsed without reference to any files, and fixity
declarations seem to be just about the only thing which prevent this
-- hence my suggestion to change the AST in order to regain this
property.
The use I envision of it is as I described: writing a quasiquoter
using HSE to parse the user's Haskell expressions. The problem is
that, for such a case, HSE (or any other parser) is forced to parse
infix expressions for which it cannot possibly know the correct
fixities. Any result with more information than the list form I gave
would be a lie.
I realise that I don't know how fixities are implemented in Haskell
compilers, so perhaps I'm misunderstanding how they are treated.
Cheers,
Reiner
On Sat, Nov 22, 2008 at 11:54 PM, Niklas Broberg
Of course, this would require a change to Template Haskell, so a second-best solution would be to forbid unparenthesised expressions in my quasiquoter. Then, parsing can proceed correctly without knowing the fixities. This would be easiest to do if haskell-src-exts changed its AST in a similar way to described above for Template Haskell.
I'm not sure I follow you here. In what way would it be simpler if HSE changes its AST to a less-information constructor? I won't do that, for the same reason you point out with TH and disadvantages when using it as a library, though I'm still curious what uses you envision and how it would be made easier. I'm still in the process of designing the fixity support for HSE, and all input is valuable. :-)
Cheers,
/Niklas

Though many see it as "losing" information, I agree wholeheartedly with your proposal to change the AST. It's better to have an AST that conveys less information, but truthfully, than to have an AST that purports to convey more information, when in fact that information is false. In most languages, some things just can't be known at parse time. They need to be resolved later. In this case, the most important thing is following the principle of least surprise: A Haskell expression inside a quasiquote should work the same as a Haskell expression outside a quasiquote. Violating the "principle of least surprise" is one of the most grievous mistakes language (and interface) designers make. Regards, John A. De Goes N-BRAIN, Inc. http://www.n-brain.net [n minds are better than n-1] On Nov 22, 2008, at 9:02 AM, Reiner Pope wrote:
It seems to me that fixity information behaves more like semantics than like syntax. For instance, fixities may be imported, and obey namespacing rules. Knowing and correctly handling these rules seems beyond the scope of a mere parser: I would hope that a single Haskell file could be parsed without reference to any files, and fixity declarations seem to be just about the only thing which prevent this -- hence my suggestion to change the AST in order to regain this property.
The use I envision of it is as I described: writing a quasiquoter using HSE to parse the user's Haskell expressions. The problem is that, for such a case, HSE (or any other parser) is forced to parse infix expressions for which it cannot possibly know the correct fixities. Any result with more information than the list form I gave would be a lie.
I realise that I don't know how fixities are implemented in Haskell compilers, so perhaps I'm misunderstanding how they are treated.
Cheers,
Reiner
On Sat, Nov 22, 2008 at 11:54 PM, Niklas Broberg
wrote: Of course, this would require a change to Template Haskell, so a second-best solution would be to forbid unparenthesised expressions in my quasiquoter. Then, parsing can proceed correctly without knowing the fixities. This would be easiest to do if haskell-src-exts changed its AST in a similar way to described above for Template Haskell.
I'm not sure I follow you here. In what way would it be simpler if HSE changes its AST to a less-information constructor? I won't do that, for the same reason you point out with TH and disadvantages when using it as a library, though I'm still curious what uses you envision and how it would be made easier. I'm still in the process of designing the fixity support for HSE, and all input is valuable. :-)
Cheers,
/Niklas
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

It turns out that there is at least a (partial) solution to my
quasiquote problem. Template Haskell's "reify" function can be used to
find an operator's fixity, although it seems not for all cases.
However, for the purposes of this discussion, suppose I can write a
function
userFixity :: String -> Q Fixity
which takes a operator used in user code and returns its fixity, in
the Q monad (Template Haskell's monad).
I want this information to be used somehow when creating the Template
Haskell AST, so that the operators used have the correct fixities. If
I use HSE for parsing Haskell expressions, then I want it to tell me
where it unsure of the fixities, so that I can insert the correct ones
there. For this use case, I would want HSE to use an AST like I
suggested, because it allows the parser to say, "I'm not sure what the
correct fixity is".
Cheers,
Reiner
On Sun, Nov 23, 2008 at 8:23 AM, John A. De Goes
Though many see it as "losing" information, I agree wholeheartedly with your proposal to change the AST.
It's better to have an AST that conveys less information, but truthfully, than to have an AST that purports to convey more information, when in fact that information is false.
In most languages, some things just can't be known at parse time. They need to be resolved later.
In this case, the most important thing is following the principle of least surprise: A Haskell expression inside a quasiquote should work the same as a Haskell expression outside a quasiquote.
Violating the "principle of least surprise" is one of the most grievous mistakes language (and interface) designers make.
Regards,
John A. De Goes N-BRAIN, Inc. http://www.n-brain.net [n minds are better than n-1]
On Nov 22, 2008, at 9:02 AM, Reiner Pope wrote:
It seems to me that fixity information behaves more like semantics than like syntax. For instance, fixities may be imported, and obey namespacing rules. Knowing and correctly handling these rules seems beyond the scope of a mere parser: I would hope that a single Haskell file could be parsed without reference to any files, and fixity declarations seem to be just about the only thing which prevent this -- hence my suggestion to change the AST in order to regain this property.
The use I envision of it is as I described: writing a quasiquoter using HSE to parse the user's Haskell expressions. The problem is that, for such a case, HSE (or any other parser) is forced to parse infix expressions for which it cannot possibly know the correct fixities. Any result with more information than the list form I gave would be a lie.
I realise that I don't know how fixities are implemented in Haskell compilers, so perhaps I'm misunderstanding how they are treated.
Cheers,
Reiner
On Sat, Nov 22, 2008 at 11:54 PM, Niklas Broberg
wrote: Of course, this would require a change to Template Haskell, so a second-best solution would be to forbid unparenthesised expressions in my quasiquoter. Then, parsing can proceed correctly without knowing the fixities. This would be easiest to do if haskell-src-exts changed its AST in a similar way to described above for Template Haskell.
I'm not sure I follow you here. In what way would it be simpler if HSE changes its AST to a less-information constructor? I won't do that, for the same reason you point out with TH and disadvantages when using it as a library, though I'm still curious what uses you envision and how it would be made easier. I'm still in the process of designing the fixity support for HSE, and all input is valuable. :-)
Cheers,
/Niklas
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Nov 23, 2008 at 8:23 AM, John A. De Goes
wrote: Though many see it as "losing" information, I agree wholeheartedly with your proposal to change the AST.
It's better to have an AST that conveys less information, but truthfully, than to have an AST that purports to convey more information, when in fact that information is false.
In most languages, some things just can't be known at parse time. They need to be resolved later.
While I agree with you in principle, that the rule of least surprise should be adhered to, I don't agree in this instance. You are assuming that the AST is only used by the parser, and if that was true I would agree with you. But HSE is just as much a library for *building* an AST using combinators. If I changed the AST to one carrying less information, it would be impossible to *ever* get the fixities right in the AST, even for those use cases where the information is known and possible to use.
I want this information to be used somehow when creating the Template Haskell AST, so that the operators used have the correct fixities. If I use HSE for parsing Haskell expressions, then I want it to tell me where it unsure of the fixities, so that I can insert the correct ones there. For this use case, I would want HSE to use an AST like I suggested, because it allows the parser to say, "I'm not sure what the correct fixity is".
As noted above, I really don't like that change. If you use HSE for parsing expressions, it would *never* know the correct fixities, and you would always get a completely left-biased tree. Why would that be harder to work with? I understand the argument about least surprise, and that this feature must be strongly documented (which it currently isn't), but for practical purposes I don't see why the current state would be problematic. It should even be trivial to convert the left-biased tree into an intermediate structure exactly like the one you suggest, no? Cheers, /Niklas

On Mon, Nov 24, 2008 at 12:39 AM, Niklas Broberg
I want this information to be used somehow when creating the Template Haskell AST, so that the operators used have the correct fixities. If I use HSE for parsing Haskell expressions, then I want it to tell me where it unsure of the fixities, so that I can insert the correct ones there. For this use case, I would want HSE to use an AST like I suggested, because it allows the parser to say, "I'm not sure what the correct fixity is".
As noted above, I really don't like that change. If you use HSE for parsing expressions, it would *never* know the correct fixities, and you would always get a completely left-biased tree. Why would that be harder to work with? I understand the argument about least surprise, and that this feature must be strongly documented (which it currently isn't), but for practical purposes I don't see why the current state would be problematic. It should even be trivial to convert the left-biased tree into an intermediate structure exactly like the one you suggest, no?
No, I believe it wouldn't. The left-biased tree cannot distinguish where parentheses have been used from where HSE inserted its own left fixities. For instance, if we have the expressions xs ++ ys ++ zs (xs ++ ys) ++ zs Then HSE will return something like (I'm using strings for the subexpression parses, for simplicity) InfixE (InfixE "xs" "++" "ys") "++" "zs" for both the first and second parses. However, if I then use the knowledge that ++ is right infix, I will want to convert the first, but not the second parses into right infix. I can't do this, because they are both parsed the same way. I would also like to point out that a list representation as I suggested can in fact encode the correct fixities if they are known to HSE. This is true simply because the list constructor is isomorphic to the current constructor in the special case where the list of operators has length 1. For instance, in the first example above, if HSE somehow knew that ++ is right infix, it should return a parse result of InfixE ["xs", InfixE ["ys", "zs"] ["++"]] ["++"] rather than just InfixE ["xs", "ys", "zs"] ["++", "++"] Cheers, Reiner
Cheers,
/Niklas

No, I believe it wouldn't. The left-biased tree cannot distinguish where parentheses have been used from where HSE inserted its own left fixities. For instance, if we have the expressions
xs ++ ys ++ zs (xs ++ ys) ++ zs
Then HSE will return something like (I'm using strings for the subexpression parses, for simplicity) InfixE (InfixE "xs" "++" "ys") "++" "zs" for both the first and second parses. However, if I then use the knowledge that ++ is right infix, I will want to convert the first, but not the second parses into right infix. I can't do this, because they are both parsed the same way.
No, this is not correct, they are parsed differently. HSE will return (the equivalent of) InfixApp (Paren (InfixApp "xs" "++" "ys")) "++" "zs" for the second case, i.e. with explicit parenthesizing of the subexpression. So they can be and are distinguished, and there would be no problem with the fixity fixing. However...
I would also like to point out that a list representation as I suggested can in fact encode the correct fixities if they are known to HSE. This is true simply because the list constructor is isomorphic to the current constructor in the special case where the list of operators has length 1. For instance, in the first example above, if HSE somehow knew that ++ is right infix, it should return a parse result of InfixE ["xs", InfixE ["ys", "zs"] ["++"]] ["++"] rather than just InfixE ["xs", "ys", "zs"] ["++", "++"]
Indeed, I did not realize that. So that means that this representation carries strictly *more* knowledge than that binary constructor, which is of course nice. That certainly makes me somewhat less antagonistic towards a change along these lines. Hmm... Cheers, /Niklas
participants (3)
-
John A. De Goes
-
Niklas Broberg
-
Reiner Pope