-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge branch '103-parse-expr' of github.com:EpitechPromo2027/B-FUN-50…
…0-BAR-5-2-glados-oriol.linan into 103-parse-expr
- Loading branch information
Showing
1 changed file
with
12 additions
and
13 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,48 +1,47 @@ | ||
module Ast.Parser.UnaryOperationSpec where | ||
|
||
import qualified Ast.Parser.Env as E | ||
import qualified Ast.Parser.UnaryOperation as PO | ||
import qualified Ast.Parser.UnaryOperation as AUO | ||
import qualified Ast.Types as AT | ||
import qualified Control.Monad.State as S | ||
import Data.Either (isLeft) | ||
import Test.Hspec | ||
import qualified Text.Megaparsec as M | ||
import qualified Text.Megaparsec.Char as MC | ||
|
||
spec :: Spec | ||
spec = do | ||
let initialEnv = E.emptyEnv | ||
let parseWithEnv input opType = | ||
fst $ S.runState (M.runParserT (PO.parseUnaryOperation (MC.string "x") opType) "" input) initialEnv | ||
fst $ S.runState (M.runParserT (AUO.parseUnaryOperation opType) "" input) initialEnv | ||
|
||
describe "parseUnaryOperation" $ do | ||
it "parses logical NOT" $ do | ||
parseWithEnv "!x" PO.Pre `shouldBe` Right AT.Not | ||
parseWithEnv "!" AUO.Pre `shouldBe` Right AT.Not | ||
|
||
it "parses 'not' logical unary operator" $ do | ||
parseWithEnv "not x" PO.Pre `shouldBe` Right AT.Not | ||
parseWithEnv "not" AUO.Pre `shouldBe` Right AT.Not | ||
|
||
it "parses bitwise NOT" $ do | ||
parseWithEnv "~x" PO.Pre `shouldBe` Right AT.BitNot | ||
parseWithEnv "~" AUO.Pre `shouldBe` Right AT.BitNot | ||
|
||
it "parses address-of operator" $ do | ||
parseWithEnv "&x" PO.Pre `shouldBe` Right AT.AddrOf | ||
parseWithEnv "&" AUO.Pre `shouldBe` Right AT.AddrOf | ||
|
||
it "parses pre-unary increment" $ do | ||
parseWithEnv "++x" PO.Pre `shouldBe` Right AT.PreInc | ||
parseWithEnv "++" AUO.Pre `shouldBe` Right AT.PreInc | ||
|
||
it "parses pre-unary decrement" $ do | ||
parseWithEnv "--x" PO.Pre `shouldBe` Right AT.PreDec | ||
parseWithEnv "--" AUO.Pre `shouldBe` Right AT.PreDec | ||
|
||
it "parses dereference operator" $ do | ||
parseWithEnv "x." PO.Post `shouldBe` Right AT.Deref | ||
parseWithEnv "." AUO.Post `shouldBe` Right AT.Deref | ||
|
||
it "parses post-unary increment" $ do | ||
parseWithEnv "x++" PO.Post `shouldBe` Right AT.PostInc | ||
parseWithEnv "++" AUO.Post `shouldBe` Right AT.PostInc | ||
|
||
it "parses post-unary decrement" $ do | ||
parseWithEnv "x--" PO.Post `shouldBe` Right AT.PostDec | ||
parseWithEnv "--" AUO.Post `shouldBe` Right AT.PostDec | ||
|
||
it "returns error for invalid operator" $ do | ||
let result = parseWithEnv "invalid" PO.Pre | ||
let result = parseWithEnv "invalid" AUO.Pre | ||
isLeft result `shouldBe` True |