-- | Defines operator precedence.
module Language.Drasil.Expr.Precedence where

import Language.Drasil.Expr.Lang (Expr(..),
  ArithBinOp(..), BoolBinOp, EqBinOp(..), LABinOp, OrdBinOp, VVNBinOp,
  UFunc(..), UFuncB(..), UFuncVV(..), UFuncVN(..),
  AssocBoolOper(..), AssocArithOper(..), VVVBinOp, NVVBinOp)

-- These precedences are inspired from Haskell/F# 
-- as documented at http://kevincantu.org/code/operators.html
-- They are all multiplied by 10, to leave room to weave things in between

-- | prec2Arith - precedence for arithmetic-related binary operations.
prec2Arith :: ArithBinOp -> Int
prec2Arith :: ArithBinOp -> Int
prec2Arith ArithBinOp
Frac = Int
190
prec2Arith ArithBinOp
Pow = Int
200
prec2Arith ArithBinOp
Subt = Int
180

-- | prec2Bool - precedence for boolean-related binary operations.
prec2Bool :: BoolBinOp -> Int
prec2Bool :: BoolBinOp -> Int
prec2Bool BoolBinOp
_ = Int
130

-- | prec2Eq - precedence for equality-related binary operations.
prec2Eq :: EqBinOp -> Int
prec2Eq :: EqBinOp -> Int
prec2Eq EqBinOp
_  = Int
130

-- | prec2LA - precedence for access-related binary operations.
prec2LA :: LABinOp -> Int
prec2LA :: LABinOp -> Int
prec2LA LABinOp
_ = Int
250

-- | prec2Ord - precedence for order-related binary operations.
prec2Ord :: OrdBinOp -> Int
prec2Ord :: OrdBinOp -> Int
prec2Ord OrdBinOp
_  = Int
130

-- | prec2VVV - precedence for Vec->Vec->Vec-related binary operations.
prec2VVV :: VVVBinOp -> Int
prec2VVV :: VVVBinOp -> Int
prec2VVV VVVBinOp
_ = Int
190

-- | prec2VVN - precedence for Vec->Vec->Num-related binary operations.
prec2VVN :: VVNBinOp -> Int
prec2VVN :: VVNBinOp -> Int
prec2VVN VVNBinOp
_ = Int
190

-- | prec2NVV - precedence for Num->Vec->Vec-related binary operations.
prec2NVV :: NVVBinOp -> Int
prec2NVV :: NVVBinOp -> Int
prec2NVV NVVBinOp
_ = Int
190

-- | precA - precedence for arithmetic-related Binary-Associative (Commutative) operators.
precA :: AssocArithOper -> Int
precA :: AssocArithOper -> Int
precA AssocArithOper
MulI = Int
190
precA AssocArithOper
MulRe = Int
190
precA AssocArithOper
AddI = Int
180
precA AssocArithOper
AddRe = Int
180

-- | precB - precedence for boolean-related Binary-Associative (Commutative) operators.
precB :: AssocBoolOper -> Int
precB :: AssocBoolOper -> Int
precB AssocBoolOper
And = Int
120
precB AssocBoolOper
Or = Int
110

-- | prec1 - precedence of unary operators.
prec1 :: UFunc -> Int
prec1 :: UFunc -> Int
prec1 UFunc
Neg = Int
230
prec1 UFunc
Exp = Int
200
prec1 UFunc
_ = Int
250

-- | prec1B - precedence of boolean-related unary operators.
prec1B :: UFuncB -> Int
prec1B :: UFuncB -> Int
prec1B UFuncB
Not = Int
230

-- | prec1VV - precedence of vector-vector-related unary operators.
prec1VV :: UFuncVV -> Int
prec1VV :: UFuncVV -> Int
prec1VV UFuncVV
_ = Int
250

-- | prec1Vec - precedence of vector-number-related unary operators.
prec1VN :: UFuncVN -> Int
prec1VN :: UFuncVN -> Int
prec1VN UFuncVN
_ = Int
230

-- | eprec - "Expression" precedence.
eprec :: Expr -> Int
eprec :: Expr -> Int
eprec Lit{}                  = Int
500
eprec (AssocA AssocArithOper
op [Expr]
_)          = AssocArithOper -> Int
precA AssocArithOper
op
eprec (AssocB AssocBoolOper
op [Expr]
_)          = AssocBoolOper -> Int
precB AssocBoolOper
op
eprec C{}                    = Int
500
eprec FCall{}                = Int
210
eprec Case{}                 = Int
200
eprec Matrix{}               = Int
220
eprec (UnaryOp UFunc
fn Expr
_)         = UFunc -> Int
prec1 UFunc
fn
eprec (UnaryOpB UFuncB
fn Expr
_)        = UFuncB -> Int
prec1B UFuncB
fn
eprec (UnaryOpVV UFuncVV
fn Expr
_)       = UFuncVV -> Int
prec1VV UFuncVV
fn
eprec (UnaryOpVN UFuncVN
fn Expr
_)       = UFuncVN -> Int
prec1VN UFuncVN
fn
eprec (Operator AssocArithOper
o DiscreteDomainDesc Expr Expr
_ Expr
_)       = AssocArithOper -> Int
precA AssocArithOper
o
eprec (ArithBinaryOp ArithBinOp
bo Expr
_ Expr
_) = ArithBinOp -> Int
prec2Arith ArithBinOp
bo
eprec (BoolBinaryOp BoolBinOp
bo Expr
_ Expr
_)  = BoolBinOp -> Int
prec2Bool BoolBinOp
bo
eprec (EqBinaryOp EqBinOp
bo Expr
_ Expr
_)    = EqBinOp -> Int
prec2Eq EqBinOp
bo
eprec (LABinaryOp LABinOp
bo Expr
_ Expr
_)    = LABinOp -> Int
prec2LA LABinOp
bo
eprec (OrdBinaryOp OrdBinOp
bo Expr
_ Expr
_)   = OrdBinOp -> Int
prec2Ord OrdBinOp
bo
eprec (VVVBinaryOp VVVBinOp
bo Expr
_ Expr
_)   = VVVBinOp -> Int
prec2VVV VVVBinOp
bo
eprec (VVNBinaryOp VVNBinOp
bo Expr
_ Expr
_)   = VVNBinOp -> Int
prec2VVN VVNBinOp
bo
eprec (NVVBinaryOp NVVBinOp
bo Expr
_ Expr
_)   = NVVBinOp -> Int
prec2NVV NVVBinOp
bo
eprec RealI{}                = Int
170