Re: [Haskell-cafe] Operator precedence and associativity with Polyparse

2011-10-26 Thread Christian Maeder

Am 26.10.2011 01:49, schrieb Tom Hawkins:

Can someone provide guidance on how handle operator precedence and
associativity with Polyparse?


Do you mean parsing something like 1 + 2 * 3 ?  I don't think
there's any real difference in using Polyparse vs Parsec for this,
except for doing p `orElse` q rather than try p|  q.


Actually, I was looking for something equivalent to
Text.ParserCombinators.Parsec.Expr.buildExpressionParser.  I suppose I
should learn how Parsec implements this under the hood.


I would do it as described under chainl1 in
http://hackage.haskell.org/packages/archive/parsec2/1.0.0/doc/html/Text-ParserCombinators-Parsec-Combinator.html

I believe Parsec.Expr cannot handle a prefix operator (i.e. unary minus) 
properly, that has lower precedence than an infix operator (i.e. ^ 
power). If it can parse -x^2 as -(x^2) then if cannot parse x^ -2 
as x^(-2).


Cheers Christian



-Tom


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


[Haskell-cafe] Operator precedence and associativity with Polyparse

2011-10-25 Thread Tom Hawkins
Hi,

Can someone provide guidance on how handle operator precedence and
associativity with Polyparse?

Thanks in advance.

-Tom

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


Re: [Haskell-cafe] Operator precedence and associativity with Polyparse

2011-10-25 Thread Ivan Lazar Miljenovic
On 26 October 2011 06:37, Tom Hawkins tomahawk...@gmail.com wrote:
 Hi,

 Can someone provide guidance on how handle operator precedence and
 associativity with Polyparse?

Do you mean parsing something like 1 + 2 * 3 ?  I don't think
there's any real difference in using Polyparse vs Parsec for this,
except for doing p `orElse` q rather than try p | q.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] Operator precedence and associativity with Polyparse

2011-10-25 Thread Tom Hawkins
 Can someone provide guidance on how handle operator precedence and
 associativity with Polyparse?

 Do you mean parsing something like 1 + 2 * 3 ?  I don't think
 there's any real difference in using Polyparse vs Parsec for this,
 except for doing p `orElse` q rather than try p | q.

Actually, I was looking for something equivalent to
Text.ParserCombinators.Parsec.Expr.buildExpressionParser.  I suppose I
should learn how Parsec implements this under the hood.

-Tom

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


Re: [Haskell-cafe] Operator precedence and associativity with Polyparse

2011-10-25 Thread Ivan Lazar Miljenovic
On 26 October 2011 10:49, Tom Hawkins tomahawk...@gmail.com wrote:
 Can someone provide guidance on how handle operator precedence and
 associativity with Polyparse?

 Do you mean parsing something like 1 + 2 * 3 ?  I don't think
 there's any real difference in using Polyparse vs Parsec for this,
 except for doing p `orElse` q rather than try p | q.

 Actually, I was looking for something equivalent to
 Text.ParserCombinators.Parsec.Expr.buildExpressionParser.  I suppose I
 should learn how Parsec implements this under the hood.

There's nothing like that for PolyParse: it has a much smaller set of
combinators than Parsec, which I for one prefer because I don't have
to worry about behaviour of existing combinators being different than
what I want/need (as it stands, I already use a custom version of
bracket from polyparse).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com

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


[Haskell-cafe] Operator precedence

2010-09-06 Thread michael rice
Is there a handy list of operators and their precedence somewhere?

Michael



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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread Daniel Díaz
Take a look to the Haskell Report:

http://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009

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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread michael rice
Thanks, Daniel.

This be all of them?

Michael

infixr 9  .
 
infixr 8  ^, ^^, ⋆⋆
 
infixl 7  ⋆, /, ‘quot‘, ‘rem‘, ‘div‘, ‘mod‘
 
infixl 6  +, -

 

   


   

-- The (:) operator is built-in syntax, and cannot legally be given
 
-- a fixity declaration; but its fixity is given by:
 
--   infixr 5  :
 

 
infix  4  ==, /=, , =, =, 
 
infixr 3  
 
infixr 2  ||
 
infixl 1  , =
 
infixr 1  =
 
infixr 0  $, $!, ‘seq‘


--- On Mon, 9/6/10, Daniel Díaz lazy.dd...@gmail.com wrote:

From: Daniel Díaz lazy.dd...@gmail.com
Subject: Re: [Haskell-cafe] Operator precedence
To: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org
Date: Monday, September 6, 2010, 1:06 PM

Take a look to the Haskell Report:
 
http://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009

-- 
Daniel Díaz




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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread Daniel Díaz
Those are all operators in Prelude. See a concrete library for their
operator precedences.

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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread michael rice
A concrete library?

I'm playing around with Data.Bits. It has .. and .|. which I assume are 
functions (rather than operators) because I don't see and infix statement for 
them. Correct?

Michael

--- On Mon, 9/6/10, Daniel Díaz lazy.dd...@gmail.com wrote:

From: Daniel Díaz lazy.dd...@gmail.com
Subject: Re: [Haskell-cafe] Operator precedence
To: michael rice nowg...@yahoo.com, haskell-cafe@haskell.org
Date: Monday, September 6, 2010, 1:17 PM

Those are all operators in Prelude. See a concrete library for their operator 
precedences.

-- 
Daniel Díaz




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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread Bulat Ziganshin
Hello michael,

Monday, September 6, 2010, 9:00:32 PM, you wrote:

 Is there a handy list of operators and their precedence somewhere?

unlike most languages, operators are user-definable in haskell. so
there is no comprehensive list

any function with two arguments van be used as operator:

a `min` b

any operator may be defined or used as a function:

() a b = ...

main = print (() True False)


-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread David Menendez
On Mon, Sep 6, 2010 at 1:37 PM, michael rice nowg...@yahoo.com wrote:

 A concrete library?

 I'm playing around with Data.Bits. It has .. and .|. which I assume are 
 functions
 (rather than operators) because I don't see and infix statement for them. 
 Correct?

.|. and .. are operators because they are made from symbol
characters. Operators default to infixl 9 unless specified otherwise,
so no infix declaration is needed.
However, Data.Bits does have infix declarations for .. and .|. :

infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
infixl 7 ..
infixl 6 `xor`
infixl 5 .|.

If you want to check the fixity of an operator, use :info in GHCi.
Prelude Data.Bits :i .|.
class (Num a) = Bits a where
  ...
  (.|.) :: a - a - a
  ...
   -- Defined in Data.Bits
infixl 5 .|.

--
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread michael rice
Hi David,

You're right, I keep forgetting to look at the source code.

And I wasn't aware of the info (:i) command. Should come in handy in the future.

Michael

--- On Mon, 9/6/10, David Menendez d...@zednenem.com wrote:

From: David Menendez d...@zednenem.com
Subject: Re: [Haskell-cafe] Operator precedence
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org, Daniel Díaz lazy.dd...@gmail.com
Date: Monday, September 6, 2010, 1:50 PM

On Mon, Sep 6, 2010 at 1:37 PM, michael rice nowg...@yahoo.com wrote:

 A concrete library?

 I'm playing around with Data.Bits. It has .. and .|. which I assume are 
 functions
 (rather than operators) because I don't see and infix statement for them. 
 Correct?

.|. and .. are operators because they are made from symbol
characters. Operators default to infixl 9 unless specified otherwise,
so no infix declaration is needed.
However, Data.Bits does have infix declarations for .. and .|. :

infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
infixl 7 ..
infixl 6 `xor`
infixl 5 .|.

If you want to check the fixity of an operator, use :info in GHCi.
Prelude Data.Bits :i .|.
class (Num a) = Bits a where
  ...
  (.|.) :: a - a - a
  ...
   -- Defined in Data.Bits
infixl 5 .|.

--
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/



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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread Daniel Díaz

El Lun, 6 de Septiembre de 2010, 7:50 pm, David Menendez escribió:
 Operators default to infixl 9 unless specified otherwise,
 so no infix declaration is needed.

Why there is a default infix? Why it is 9?

-- 
Daniel Díaz

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


Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread David Menendez
On Mon, Sep 6, 2010 at 2:21 PM, Daniel Díaz danield...@asofilak.es wrote:

 El Lun, 6 de Septiembre de 2010, 7:50 pm, David Menendez escribió:
 Operators default to infixl 9 unless specified otherwise,
 so no infix declaration is needed.

 Why there is a default infix? Why it is 9?

That's what the Haskell Report says: Any operator lacking a fixity
declaration is assumed to be infixl 9 (section 4.4.2).

Any function with at least two arguments can be used as an operator,
so there has to be a default. Presumably, infixl 9 was considered the
least surprising.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Operator precedence and associativity on happy grammars

2009-05-07 Thread j . romildo
Hello.

I am learning how to use Happy (a LALR(1) parser generator) and I have a
question on a grammar based on an example from the manual. The input
file to Happy is attached to this message.

The grammar is:

   Exp - let var = Exp in Exp
   Exp - Exp + Exp
   Exp - Exp - Exp
   Exp - Exp * Exp
   Exp - Exp / Exp
   Exp - ( Exp )

This grammar is ambiguous, but the conflicts that will appear in the
parser table can be resolved with precedence and associativity
declarations for the operators that surround expressions:

   %right in
   %left + -
   %left * /

giving right associativity to the in token, and left associativity to
the arithmetic operators, and giving lower precedence to in, followed by
+ and -, and then by * and /.

I see that if the token in is not given a precedence declaration, the
grammar still is ambiguous, as can be seen in the example of parsing the
expression:

   let v = e1 in e2 + e3

which could be parsed as

   (let v = e1 in e2) + e3

or

   let v = e1 in (e2 + e3)

Giving the token in a lower precedence makes the parser choose the last
option.

My question is about the associativity of the token in? Does it make any
difference giving it left associativity, right associativity, or making
it non associative?

Regards.

José Romildo
-- calc3.y-*- mode: haskell -*-
{
module Main where

import Data.Char (isSpace, isDigit, isAlpha, isAlphaNum)
import Data.Maybe (fromMaybe)
}

%name calc
%tokentype { Token }
%error { parseError }

%token
let { TokenLet }
in  { TokenIn }
int { TokenInt $$ }
var { TokenVar $$ }
'=' { TokenEq }
'+' { TokenPlus }
'-' { TokenMinus }
'*' { TokenTimes }
'/' { TokenDiv }
'(' { TokenLP }
')' { TokenRP }


%nonassoc in
%left '+' '-'
%left '*' '/'
%left NEG

%%

Exp : let var '=' Exp in Exp { \env - $6 (($2,$4 env) : env)  }
| Exp '+' Exp{ \env - $1 env + $3 env }
| Exp '-' Exp{ \env - $1 env - $3 env }
| Exp '*' Exp{ \env - $1 env * $3 env }
| Exp '/' Exp{ \env - $1 env `div` $3 env }
| '(' Exp ')'{ $2  }
| '-' Exp %prec NEG  { \env - - ($2 env)  }
| int{ \env - $1  }
| var{ \env - fromMaybe 0 (lookup $1 env) }

{
parseError :: [Token] - a
parseError _ = error Parse error

data Token
= TokenLet
| TokenIn
| TokenInt Int
| TokenVar String
| TokenEq
| TokenPlus
| TokenMinus
| TokenTimes
| TokenDiv
| TokenLP
| TokenRP
deriving (Show)

lexer :: String - [Token]
lexer [] = []
lexer (c:cs) | isSpace c = lexer cs
 | isAlpha c = let (name,rest) = span isAlphaNum cs
   tok = case c:name of
   let - TokenLet
   in  - TokenIn
   var   - TokenVar var
   in tok : lexer rest
 | isDigit c = let (num,rest) = span isDigit cs
   in TokenInt (read (c:num)) : lexer rest
lexer ('=':cs) = TokenEq: lexer cs
lexer ('+':cs) = TokenPlus  : lexer cs
lexer ('-':cs) = TokenMinus : lexer cs
lexer ('*':cs) = TokenTimes : lexer cs
lexer ('/':cs) = TokenDiv   : lexer cs
lexer ('(':cs) = TokenLP: lexer cs
lexer (')':cs) = TokenRP: lexer cs

main = do input - getContents
  mapM_ print (map (($ []) . calc . lexer) (lines input))
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe