Re: [Haskell-cafe] Fixity declaration extension

2012-08-14 Thread Евгений Пермяков
Your idea looks _much_ better from code clarity point of view, but it's 
unclear to me, how to deal with it internally and in error messages. I'm 
not a compiler guy, though.


Worse, it does not allow to set up fixity relative to operator that is 
not in scope and it will create unnecessary intermodule dependencies.  
One should fall back to numeric fixities for such cases, if it is needed.


On 08/13/2012 11:26 PM, Ryan Ingram wrote:
When I was implementing a toy functional languages compiler I did away 
with precedence declarations by number and instead allowed the 
programmer to specify a partial order on declarations; this seems to 
be a much cleaner solution and avoids arbitrary precedences between 
otherwise unrelated operators defined in different modules.


You could write statements like

-- define + and - to have the same precedence
infixl + -

-- define * to have higher precedence than +
infixl * above +

-- define / to have the same precedence as *
infixr / equal *

-- $ is right-associative
infixr $
-- you can also separate precedence from fixity declaration
precedence $ below +

-- function application has higher precedence than all operators by 
default, but you can override that

infixl . above APP

-- == is non-associative
infix ==

Here's some parses with this system:

a + b - c   =   (a+b)-c
f.x.y z == g w  = (((f.x).y) z) == (g w)
a == b == c  = parse error (non-associative operator)
a * b / c = parse error (left-associative/right-associative operators 
with same precedence)

a == b $ c = parse error (no ordering known between == and $)
a $ b + c = a $ (b+c)

I think this is a much cleaner way to solve the problem and I hope 
something like it makes it into a future version of Haskell.


  -- ryan

On Sun, Aug 12, 2012 at 11:46 AM, Евгений Пермяков 
permea...@gmail.com mailto:permea...@gmail.com wrote:


fixity declaration has form *infix(l|r)? [Digit]* in haskell. I'm
pretty sure, that this is not enough for complicated cases.
Ideally, fixity declarations should have form *infix(l|r)?
[Digit](\.(+|-)[Digit])** , with implied infinitely long repeated
(.0) tail. This will allow fine tuning of operator priorities and
much easier priority selection. For example, it may be assumed,
that bit operations like (..) operator have hightest priority and
have priorities like 9.0.1 or 9.0.2, anti-lisps like ($) have
lowest priority like 0.0.1, control operators have base priority
1.* and logic operations like () have priority of 2.* and it
will be possibly to add new operators between or above all (for
example) control operators without moving fixity of other ones.

Agda2 language supports wide priority range, but still without
'tails' to my knowledge. Is there any haskell-influenced language
or experimental syntactic extension that address the issue?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto: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


Re: [Haskell-cafe] Fixity declaration extension

2012-08-14 Thread Ryan Ingram
On Tue, Aug 14, 2012 at 1:04 AM, Евгений Пермяков permea...@gmail.comwrote:

  Your idea looks _much_ better from code clarity point of view, but it's
 unclear to me, how to deal with it internally and in error messages. I'm
 not a compiler guy, though.


How to deal with it internally: It's pretty easy, actually.  The hardest
part is implementing an extensible partial order; once you have that and
you can use it to drive comparisons, parsing is not hard.

Basically, at each step when you read an operator token, you need to decide
to shift, that is, put it onto a stack of operations, reduce, that is,
apply the operator at the top of the stack (leaving the current token to
check again at the next step), or give a parse error.  The rules for
deciding which of those to do are pretty simple:

Given X, the operator at the top of the stack, and Y, the operator you just
read:

(1) Compare the precedence of X and Y.  If they are incomparable, it's a
parse error.
(2) If Y is higher precedence than X, shift.
(3) If Y is lower precedence than X, reduce.

(At this point, we know X and Y have equal precedence)

(4) If X or Y is non-associative, it's a parse error.
(5) If X and Y don't have the same associativity, it's a parse error.

(At this point we know X and Y have the same associativity)

(6) If X and Y are left associative, reduce.
(7) Otherwise they are both right associative, shift.

So, for example, reading the expression

x * y + x + g w $ z

Start with stack [empty x].

The empty operator has lower precedence than anything else (that is, it
will never be reduced).  When you finish reading an expression, reduce
until the empty operator is the only thing on the stack and return its
expression.

* is higher precedence than empty, shift.  [empty x, * y]
+ is lower precedence than *, reduce. [empty (x*y)]
+ is higher precedence than empty, shift. [empty (x*y), + x]
+ is the same precedence as +, and is left associative, reduce.  [empty
((x*y)+x)]
+ is higher precedence than empty, shift [empty ((x*y)+x), + g]
function application is higher precedence than +, shift. [empty ((x*y)+x),
+ g, APP w]
$ is lower precedence than function application, reduce. [empty ((x*y)+x),
+ (g w)]
$ is lower precedence than +, reduce. [empty (((x*y)+x) + (g w))]
$ is higher precedence than empty, shift. [empty (((x*y)+x) + (g w)), $ z]
Done, but the stack isn't empty.  Reduce.  [empty x*y)+x) + (g w)) $ z)]
Done, and the stack is empty.
Result: x*y)+x) + (g w)) $ z)

Each operator is shifted exactly once and reduced exactly once, so this
algorithm runs in a number of steps linear in the expression size.
Parentheses start a new sub-stack when parsing the 'thing to apply the
operator to' part of the expression.

Something like this:

simple_exp :: Parser Exp
simple_exp =
(ExpId $ identifier) | (ExpLit $ literal) | (lparen *
expression * rparen)

expression :: Parser Exp
expression = do
first - simple_exp
binops [ (Empty, first) ]

reduceAll [ (Empty, e) ] = return e
reduceAll ((op1, e1) : (op2, e2) : rest) = reduceAll ((op2, (ExpOperator
op1 e1 e2)) : rest)

binops :: Stack - Parser Exp
binops s = handle_binop | handle_application | reduceAll s where
handle_binop = do
op - operator
rhs - simple_exp
reduce_until_shift op rhs s
handle_application = do
rhs - simple_exp
reduce_until_shift FunctionApplication rhs s

reduce_until_shift implements the algorithm above until it eventually
shifts the operator onto the stack.
identifier parses an identifier, operator parses an operator, literal
parses a literal (like 3 or hello)
lparen and rparen parse left and right parentheses.

I haven't considered how difficult it would be to expand this algorithm to
support unary or more-than-binary operators; I suspect it's not
ridiculously difficult, but I don't know.  Haskell's support for both of
those is pretty weak, however; even the lip service paid to unary - is a
source of many problems in parsing Haskell.

Worse, it does not allow to set up fixity relative to operator that is not
 in scope and it will create unnecessary intermodule dependencies.  One
 should fall back to numeric fixities for such cases, if it is needed.


You can get numeric fixity by just declaring precedence equal to some
prelude operator with the desired fixity; this will likely be the common
case.

I would expect modules to declare locally relative fixities between
operators imported from different modules if and only if it was relevant to
that module's implementation.  In most cases I expect the non-ordering to
be resolved by adding parentheses, not by declaring additional precedence
directives; for example, even though (a == b == c) would be a parse error
due to == being non-associative, both ((a == b) == c) and (a == (b == c))
are not.  The same method of 'just add parentheses where you mean it' fixes
any parse error due to incomparable precedences.

  -- ryan
___

Re: [Haskell-cafe] Fixity declaration extension

2012-08-14 Thread Евгений Пермяков

On 08/14/2012 02:52 PM, Ryan Ingram wrote:



On Tue, Aug 14, 2012 at 1:04 AM, Евгений Пермяков permea...@gmail.com 
mailto:permea...@gmail.com wrote:


Your idea looks _much_ better from code clarity point of view, but
it's unclear to me, how to deal with it internally and in error
messages. I'm not a compiler guy, though.


How to deal with it internally: It's pretty easy, actually. The 
hardest part is implementing an extensible partial order; once you 
have that and you can use it to drive comparisons, parsing is not hard.


Basically, at each step when you read an operator token, you need to 
decide to shift, that is, put it onto a stack of operations, 
reduce, that is, apply the operator at the top of the stack (leaving 
the current token to check again at the next step), or give a parse 
error.  The rules for deciding which of those to do are pretty simple:


Yes, I can guess it. This way. however, is linearly dependent in time 
from number of operators in scope. It is clearly much worse then looking 
into Map OperatorName Fixity . But changing numeric fixity in Map when 
adding operator somewhere in between existing stack is also linearly - 
dependent. Of course, associated penalties are small if few operators 
are in scope. It is unclear for me, how heavy associated penalties will 
be for both cases.


I would expect modules to declare locally relative fixities between 
operators imported from different modules if and only if it was 
relevant to that module's implementation.
Noway. Monoid, Monad and Functor are absolutely independent typeclasses 
and defined in different modules. There is, however, type [], which has 
instances for all three typeclasses, so operators for all three of them 
have to play together. Thus, when you create typeclass and 
operator-combinators for it, you should add them to entire set of 
operators on all hackages, as you never know, which typeclass instances 
will give some yet unknown types. So, rules for such cases must exists, 
and leaving priorities undefined is not a good way.


In most cases I expect the non-ordering to be resolved by adding 
parentheses, not by declaring additional precedence directives; for 
example, even though (a == b == c) would be a parse error due to == 
being non-associative, both ((a == b) == c) and (a == (b == c)) are 
not.  The same method of 'just add parentheses where you mean it' 
fixes any parse error due to incomparable precedences.

I hate lisp-like syntax.


  -- ryan



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fixity declaration extension

2012-08-14 Thread Ketil Malde
AntC anthony_clay...@clear.net.nz writes:

 I agree. I don't declare operators very often, and when I do I always 
 struggle 
 to remember which way round the precedence numbers go.
   [...]
 (Anything else we can bikeshed about while we're at it?)

  infixl * before +

Perhaps before and after clearer than higher and lower?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fixity declaration extension

2012-08-14 Thread Twan van Laarhoven

On 14/08/12 13:46, Ketil Malde wrote:

AntC anthony_clay...@clear.net.nz writes:


I agree. I don't declare operators very often, and when I do I always struggle
to remember which way round the precedence numbers go.

[...]

(Anything else we can bikeshed about while we're at it?)


   infixl * before +

Perhaps before and after clearer than higher and lower?


I would pick tighter than and looser than, but I suppose that before and 
after are also clear enough. Or maybe inside and outside?


I don't think that we really need a new keyword for precedence declarations. The 
current infix would suffice if the default was for operators to be non-fix and 
of indeterminate precedence. Multiple fixity declarations for the same operator 
should then be allowed. Or perhaps just require that separate declarations use 
the same infix[lr]? keyword.



Twan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fixity declaration extension

2012-08-13 Thread Ryan Ingram
When I was implementing a toy functional languages compiler I did away with
precedence declarations by number and instead allowed the programmer to
specify a partial order on declarations; this seems to be a much cleaner
solution and avoids arbitrary precedences between otherwise unrelated
operators defined in different modules.

You could write statements like

-- define + and - to have the same precedence
infixl + -

-- define * to have higher precedence than +
infixl * above +

-- define / to have the same precedence as *
infixr / equal *

-- $ is right-associative
infixr $
-- you can also separate precedence from fixity declaration
precedence $ below +

-- function application has higher precedence than all operators by
default, but you can override that
infixl . above APP

-- == is non-associative
infix ==

Here's some parses with this system:

a + b - c   =   (a+b)-c
f.x.y z == g w  = (((f.x).y) z) == (g w)
a == b == c  = parse error (non-associative operator)
a * b / c = parse error (left-associative/right-associative operators with
same precedence)
a == b $ c = parse error (no ordering known between == and $)
a $ b + c = a $ (b+c)

I think this is a much cleaner way to solve the problem and I hope
something like it makes it into a future version of Haskell.

  -- ryan

On Sun, Aug 12, 2012 at 11:46 AM, Евгений Пермяков permea...@gmail.comwrote:

  fixity declaration has form *infix(l|r)? [Digit]* in haskell. I'm pretty
 sure, that this is not enough for complicated cases. Ideally, fixity
 declarations should have form *infix(l|r)? [Digit](\.(+|-)[Digit])** ,
 with implied infinitely long repeated (.0) tail. This will allow fine
 tuning of operator priorities and much easier priority selection. For
 example, it may be assumed, that bit operations like (..) operator have
 hightest priority and have priorities like 9.0.1 or 9.0.2, anti-lisps like
 ($) have lowest priority like 0.0.1, control operators have base priority
 1.* and logic operations like () have priority of 2.* and it will be
 possibly to add new operators between or above all (for example) control
 operators without moving fixity of other ones.

 Agda2 language supports wide priority range, but still without 'tails' to
 my knowledge. Is there any haskell-influenced language or experimental
 syntactic extension that address the issue?

 ___
 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


Re: [Haskell-cafe] Fixity declaration extension

2012-08-13 Thread AntC
Ryan Ingram ryani.spam at gmail.com writes:

 
 
 When I was implementing a toy functional languages compiler I did away with 
precedence declarations by number and instead allowed the programmer to 
specify a partial order on declarations; this seems to be a much cleaner 
solution and avoids arbitrary precedences between otherwise unrelated 
operators defined in different modules.


I agree. I don't declare operators very often, and when I do I always struggle 
to remember which way round the precedence numbers go. I usually end up 
hunting for a Prelude operator that works the way I'm aiming for, then copy 
its definition. It would be much easier to declare the fixity of myop to be 
same as someotherop (which would presumably have to be already declared/fixed 
in an imported module).

[It's also slightly counterintuitive that the thing being defined comes last 
in an infix declaration, and that the stand-alone operator isn't in parens.]

infixAs !! .$-- fixing myop (.$) to be fixed as Preludeop (!!)

If you wanted to define precedence relative to some other operator(s), it 
might be clearer to give some model parsings (grabbing some syntax something 
like Ryan's):

infix .$ (x ** y .$ z .$ w) == (x ** ((y .$  z) .$ w))
-- === infixl 9 .$


OTOH, I think Евгений's proposal is getting too exotic. Do we really need such 
fine shades of binding? Will the reader remember how each operator binds 
relative to the others? Surely a case where explicit parens would be better.

(Anything else we can bikeshed about while we're at it?)

AntC



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fixity declaration extension

2012-08-12 Thread Евгений Пермяков
fixity declaration has form *infix(l|r)? [Digit]* in haskell. I'm pretty 
sure, that this is not enough for complicated cases. Ideally, fixity 
declarations should have form *infix(l|r)? [Digit](\.(+|-)[Digit])** , 
with implied infinitely long repeated (.0) tail. This will allow fine 
tuning of operator priorities and much easier priority selection. For 
example, it may be assumed, that bit operations like (..) operator have 
hightest priority and have priorities like 9.0.1 or 9.0.2, anti-lisps 
like ($) have lowest priority like 0.0.1, control operators have base 
priority 1.* and logic operations like () have priority of 2.* and it 
will be possibly to add new operators between or above all (for example) 
control operators without moving fixity of other ones.


Agda2 language supports wide priority range, but still without 'tails' 
to my knowledge. Is there any haskell-influenced language or 
experimental syntactic extension that address the issue?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe