Skip to content

Commit

Permalink
[add] tests for Ast/Types
Browse files Browse the repository at this point in the history
  • Loading branch information
RenzoMaggiori committed Dec 9, 2024
1 parent 0309299 commit 9438b8b
Show file tree
Hide file tree
Showing 2 changed files with 72 additions and 0 deletions.
1 change: 1 addition & 0 deletions glados.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@ test-suite glados-test
type: exitcode-stdio-1.0
other-modules:
Ast.ParserSpec
Ast.TypesSpec
Misc.MiscSpec

hs-source-dirs: test
Expand Down
71 changes: 71 additions & 0 deletions test/Ast/TypesSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,71 @@
module Ast.TypesSpec (spec) where

import Ast.Types
( AST (..),
Expr (..),
Literal (..),
Operation (..),
)
import Test.Hspec

spec :: Spec
spec = do
describe "Literal instances" $ do
it "tests the Show instance for Literal" $ do
show (LInt 42) `shouldBe` "LInt 42"
show (LBool True) `shouldBe` "LBool True"
show (LSymbol "x") `shouldBe` "LSymbol \"x\""

it "tests the Eq instance for Literal" $ do
LInt 42 `shouldBe` LInt 42
LBool False `shouldBe` LBool False
LSymbol "x" `shouldBe` LSymbol "x"
LInt 1 `shouldNotBe` LInt 2
LBool True `shouldNotBe` LBool False

it "tests the Ord instance for Literal" $ do
LInt 1 `shouldSatisfy` (< LInt 2)
LBool False `shouldSatisfy` (< LBool True)
LSymbol "a" `shouldSatisfy` (< LSymbol "b")

describe "Expr instances" $ do
it "tests the Show instance for Expr" $ do
show (Lit (LInt 42)) `shouldBe` "Lit (LInt 42)"
show (Var "x") `shouldBe` "Var \"x\""
show (Define "x" (Lit (LInt 10))) `shouldBe` "Define \"x\" (Lit (LInt 10))"

it "tests the Eq instance for Expr" $ do
Lit (LInt 42) `shouldBe` Lit (LInt 42)
Var "x" `shouldBe` Var "x"
Define "x" (Lit (LInt 10)) `shouldBe` Define "x" (Lit (LInt 10))
Lit (LInt 1) `shouldNotBe` Lit (LInt 2)

it "tests the Ord instance for Expr" $ do
Lit (LInt 1) `shouldSatisfy` (< Lit (LInt 2))
Var "a" `shouldSatisfy` (< Var "b")
Define "a" (Lit (LInt 10)) `shouldSatisfy` (< Define "b" (Lit (LInt 20)))

describe "Operation instances" $ do
it "tests the Show instance for Operation" $ do
show Add `shouldBe` "Add"
show Sub `shouldBe` "Sub"
show Mult `shouldBe` "Mult"

it "tests the Eq instance for Operation" $ do
Add `shouldBe` Add
Sub `shouldBe` Sub
Mult `shouldNotBe` Div

it "tests the Ord instance for Operation" $ do
Add `shouldSatisfy` (< Sub)
Sub `shouldSatisfy` (< Mult)
Div `shouldSatisfy` (< Mod)

describe "AST instances" $ do
it "tests the Show instance for AST" $ do
show (AST [Lit (LInt 42)]) `shouldBe` "AST [Lit (LInt 42)]"
show (AST [Var "x", Lit (LBool True)]) `shouldBe` "AST [Var \"x\",Lit (LBool True)]"

it "tests the Eq instance for AST" $ do
AST [Lit (LInt 42)] `shouldBe` AST [Lit (LInt 42)]
AST [Var "x", Lit (LBool True)] `shouldNotBe` AST [Var "x"]

0 comments on commit 9438b8b

Please # to comment.