module Symantic.Fixity where
import Data.Bool
import Data.Eq (Eq(..))
import Data.Function ((.))
import Data.Int (Int)
import Data.Maybe (Maybe(..))
import Data.Ord (Ord(..))
import Data.Semigroup
import Data.String (String, IsString(..))
import Text.Show (Show(..))
data Fixity
= Fixity1 Unifix
| Fixity2 Infix
deriving (Fixity -> Fixity -> Bool
(Fixity -> Fixity -> Bool)
-> (Fixity -> Fixity -> Bool) -> Eq Fixity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Fixity -> Fixity -> Bool
$c/= :: Fixity -> Fixity -> Bool
== :: Fixity -> Fixity -> Bool
$c== :: Fixity -> Fixity -> Bool
Eq, Int -> Fixity -> ShowS
[Fixity] -> ShowS
Fixity -> String
(Int -> Fixity -> ShowS)
-> (Fixity -> String) -> ([Fixity] -> ShowS) -> Show Fixity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Fixity] -> ShowS
$cshowList :: [Fixity] -> ShowS
show :: Fixity -> String
$cshow :: Fixity -> String
showsPrec :: Int -> Fixity -> ShowS
$cshowsPrec :: Int -> Fixity -> ShowS
Show)
data Unifix
= Prefix { Unifix -> Int
unifix_precedence :: Precedence }
| Postfix { unifix_precedence :: Precedence }
deriving (Unifix -> Unifix -> Bool
(Unifix -> Unifix -> Bool)
-> (Unifix -> Unifix -> Bool) -> Eq Unifix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Unifix -> Unifix -> Bool
$c/= :: Unifix -> Unifix -> Bool
== :: Unifix -> Unifix -> Bool
$c== :: Unifix -> Unifix -> Bool
Eq, Int -> Unifix -> ShowS
[Unifix] -> ShowS
Unifix -> String
(Int -> Unifix -> ShowS)
-> (Unifix -> String) -> ([Unifix] -> ShowS) -> Show Unifix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Unifix] -> ShowS
$cshowList :: [Unifix] -> ShowS
show :: Unifix -> String
$cshow :: Unifix -> String
showsPrec :: Int -> Unifix -> ShowS
$cshowsPrec :: Int -> Unifix -> ShowS
Show)
data Infix
= Infix
{ Infix -> Maybe Associativity
infix_associativity :: Maybe Associativity
, Infix -> Int
infix_precedence :: Precedence
} deriving (Infix -> Infix -> Bool
(Infix -> Infix -> Bool) -> (Infix -> Infix -> Bool) -> Eq Infix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Infix -> Infix -> Bool
$c/= :: Infix -> Infix -> Bool
== :: Infix -> Infix -> Bool
$c== :: Infix -> Infix -> Bool
Eq, Int -> Infix -> ShowS
[Infix] -> ShowS
Infix -> String
(Int -> Infix -> ShowS)
-> (Infix -> String) -> ([Infix] -> ShowS) -> Show Infix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Infix] -> ShowS
$cshowList :: [Infix] -> ShowS
show :: Infix -> String
$cshow :: Infix -> String
showsPrec :: Int -> Infix -> ShowS
$cshowsPrec :: Int -> Infix -> ShowS
Show)
infixL :: Precedence -> Infix
infixL :: Int -> Infix
infixL = Maybe Associativity -> Int -> Infix
Infix (Associativity -> Maybe Associativity
forall a. a -> Maybe a
Just Associativity
AssocL)
infixR :: Precedence -> Infix
infixR :: Int -> Infix
infixR = Maybe Associativity -> Int -> Infix
Infix (Associativity -> Maybe Associativity
forall a. a -> Maybe a
Just Associativity
AssocR)
infixB :: Side -> Precedence -> Infix
infixB :: Side -> Int -> Infix
infixB = Maybe Associativity -> Int -> Infix
Infix (Maybe Associativity -> Int -> Infix)
-> (Side -> Maybe Associativity) -> Side -> Int -> Infix
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Associativity -> Maybe Associativity
forall a. a -> Maybe a
Just (Associativity -> Maybe Associativity)
-> (Side -> Associativity) -> Side -> Maybe Associativity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Side -> Associativity
AssocB
infixN :: Precedence -> Infix
infixN :: Int -> Infix
infixN = Maybe Associativity -> Int -> Infix
Infix Maybe Associativity
forall a. Maybe a
Nothing
infixN0 :: Infix
infixN0 :: Infix
infixN0 = Int -> Infix
infixN Int
0
infixN5 :: Infix
infixN5 :: Infix
infixN5 = Int -> Infix
infixN Int
5
isPairNeeded :: (Infix, Side) -> Infix -> Bool
isPairNeeded :: (Infix, Side) -> Infix -> Bool
isPairNeeded (Infix
po, Side
lr) Infix
op =
Infix -> Int
infix_precedence Infix
op Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Infix -> Int
infix_precedence Infix
po
Bool -> Bool -> Bool
|| Infix -> Int
infix_precedence Infix
op Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Infix -> Int
infix_precedence Infix
po
Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
associate
where
associate :: Bool
associate =
case (Side
lr, Infix -> Maybe Associativity
infix_associativity Infix
po) of
(Side
_, Just AssocB{}) -> Bool
True
(Side
SideL, Just Associativity
AssocL) -> Bool
True
(Side
SideR, Just Associativity
AssocR) -> Bool
True
(Side, Maybe Associativity)
_ -> Bool
False
pairIfNeeded ::
Semigroup s => IsString s =>
Pair -> (Infix, Side) -> Infix ->
s -> s
pairIfNeeded :: Pair -> (Infix, Side) -> Infix -> s -> s
pairIfNeeded (String
o,String
c) (Infix, Side)
po Infix
op s
s =
if (Infix, Side) -> Infix -> Bool
isPairNeeded (Infix, Side)
po Infix
op
then String -> s
forall a. IsString a => String -> a
fromString String
o s -> s -> s
forall a. Semigroup a => a -> a -> a
<> s
s s -> s -> s
forall a. Semigroup a => a -> a -> a
<> String -> s
forall a. IsString a => String -> a
fromString String
c
else s
s
type Precedence = Int
class PrecedenceOf a where
precedence :: a -> Precedence
instance PrecedenceOf Fixity where
precedence :: Fixity -> Int
precedence (Fixity1 Unifix
uni) = Unifix -> Int
forall a. PrecedenceOf a => a -> Int
precedence Unifix
uni
precedence (Fixity2 Infix
inf) = Infix -> Int
forall a. PrecedenceOf a => a -> Int
precedence Infix
inf
instance PrecedenceOf Unifix where
precedence :: Unifix -> Int
precedence = Unifix -> Int
unifix_precedence
instance PrecedenceOf Infix where
precedence :: Infix -> Int
precedence = Infix -> Int
infix_precedence
data Associativity
= AssocL
| AssocR
| AssocB Side
deriving (Associativity -> Associativity -> Bool
(Associativity -> Associativity -> Bool)
-> (Associativity -> Associativity -> Bool) -> Eq Associativity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Associativity -> Associativity -> Bool
$c/= :: Associativity -> Associativity -> Bool
== :: Associativity -> Associativity -> Bool
$c== :: Associativity -> Associativity -> Bool
Eq, Int -> Associativity -> ShowS
[Associativity] -> ShowS
Associativity -> String
(Int -> Associativity -> ShowS)
-> (Associativity -> String)
-> ([Associativity] -> ShowS)
-> Show Associativity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Associativity] -> ShowS
$cshowList :: [Associativity] -> ShowS
show :: Associativity -> String
$cshow :: Associativity -> String
showsPrec :: Int -> Associativity -> ShowS
$cshowsPrec :: Int -> Associativity -> ShowS
Show)
data Side
= SideL
| SideR
deriving (Side -> Side -> Bool
(Side -> Side -> Bool) -> (Side -> Side -> Bool) -> Eq Side
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Side -> Side -> Bool
$c/= :: Side -> Side -> Bool
== :: Side -> Side -> Bool
$c== :: Side -> Side -> Bool
Eq, Int -> Side -> ShowS
[Side] -> ShowS
Side -> String
(Int -> Side -> ShowS)
-> (Side -> String) -> ([Side] -> ShowS) -> Show Side
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Side] -> ShowS
$cshowList :: [Side] -> ShowS
show :: Side -> String
$cshow :: Side -> String
showsPrec :: Int -> Side -> ShowS
$cshowsPrec :: Int -> Side -> ShowS
Show)
type Pair = (String, String)
pairAngle :: Pair
pairBrace :: Pair
pairBracket :: Pair
pairParen :: Pair
pairAngle :: Pair
pairAngle = (String
"<",String
">")
pairBrace :: Pair
pairBrace = (String
"{",String
"}")
pairBracket :: Pair
pairBracket = (String
"[",String
"]")
pairParen :: Pair
pairParen = (String
"(",String
")")