Skip to content

Commit

Permalink
Add tests for JSON encoding
Browse files Browse the repository at this point in the history
  • Loading branch information
luc-tielen committed Sep 17, 2023
1 parent d8b3f13 commit 2c497be
Show file tree
Hide file tree
Showing 2 changed files with 42 additions and 1 deletion.
3 changes: 2 additions & 1 deletion eclair-lang.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -255,6 +255,7 @@ test-suite eclair-test
other-modules:
Paths_eclair_lang
Test.Eclair.ArgParserSpec
Test.Eclair.JSONSpec
Test.Eclair.LLVM.HashSpec
Test.Eclair.LSP.JSONSpec
Test.Eclair.RA.IndexSelectionSpec
Expand Down Expand Up @@ -302,10 +303,10 @@ test-suite eclair-test
, extra >=1 && <2
, filepath >=1 && <2
, hedgehog >=1 && <2
, hermes-json <1
, hspec >=2.6.1 && <3.0.0
, hspec-hedgehog <1
, llvm-codegen
, hermes-json <1
, megaparsec >=9 && <10
, mmorph >=1 && <2
, mtl >=2 && <3
Expand Down
40 changes: 40 additions & 0 deletions tests/eclair/Test/Eclair/JSONSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
{-# LANGUAGE QuasiQuotes #-}

module Test.Eclair.JSONSpec
( module Test.Eclair.JSONSpec
) where

import Eclair.JSON
import Test.Hspec
import NeatInterpolation

spec :: Spec
spec = describe "JSON encoding" $ parallel $ do
it "can encode null" $ do
encodeJSON Null `shouldBe` "null"

it "can encode booleans" $ do
encodeJSON (Boolean True) `shouldBe` "true"
encodeJSON (Boolean False) `shouldBe` "false"

it "can encode strings" $ do
encodeJSON (String "abcdef") `shouldBe` [text|"abcdef"|]
encodeJSON (String "123") `shouldBe` [text|"123"|]

it "can encode integers" $ do
encodeJSON (Number 42) `shouldBe` "42"
encodeJSON (Number 123) `shouldBe` "123"

it "can encode objects" $ do
encodeJSON (Object [("line", Number 10), ("column", Number 33)]) `shouldBe` [text|
{"line":10,"column":33}
|]
encodeJSON (Object [("a", Null), ("b", Boolean True)]) `shouldBe` [text|
{"a":null,"b":true}
|]

it "can encode arrays" $ do
encodeJSON (Array []) `shouldBe` "[]"
encodeJSON (Array [Number 123, String "abc", Null]) `shouldBe` [text|
[123,"abc",null]
|]

0 comments on commit 2c497be

Please sign in to comment.