Skip to content

Commit

Permalink
Add unit roundtrip tests
Browse files Browse the repository at this point in the history
  • Loading branch information
TristanCacqueray committed Jun 26, 2022
1 parent bacced4 commit ca6c9cd
Show file tree
Hide file tree
Showing 3 changed files with 21 additions and 1 deletion.
5 changes: 4 additions & 1 deletion src/Swarm/Language/Pipeline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ data ProcessedTerm
-- ^ Capabilities required by the term
CapCtx
-- ^ Capability context for any definitions embedded in the term
deriving (Data, Show, Generic, ToJSON)
deriving (Data, Show, Eq, Generic)

instance FromJSON ProcessedTerm where
parseJSON = withText "Term" tryProcess
Expand All @@ -64,6 +64,9 @@ instance FromJSON ProcessedTerm where
Right Nothing -> fail "Term was only whitespace"
Right (Just pt) -> return pt

instance ToJSON ProcessedTerm where
toJSON (ProcessedTerm t _ _ _) = String $ prettyText t

-- | Given a 'Text' value representing a Swarm program,
--
-- 1. Parse it (see "Swarm.Language.Parse")
Expand Down
1 change: 1 addition & 0 deletions swarm.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -154,6 +154,7 @@ test-suite swarm-unit
tasty-hunit >= 0.10 && < 0.11,
tasty-quickcheck >= 0.10 && < 0.11,
-- Imports shared with the library don't need bounds
aeson,
base,
filepath,
hashable,
Expand Down
16 changes: 16 additions & 0 deletions test/unit/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,14 @@ module Main where
import Control.Lens ((&), (.~), (^.))
import Control.Monad.Except
import Control.Monad.State
import Data.Aeson (eitherDecode, encode)
import Data.Either
import Data.Hashable
import Data.Maybe
import Data.String (fromString)
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Encoding qualified as T
import Linear
import Test.Tasty
import Test.Tasty.HUnit
Expand Down Expand Up @@ -139,10 +143,22 @@ parser =
)
)
]
, testGroup
"json encoding"
[ testCase "simple expr" (roundTrip "42 + 43")
, testCase "module def" (roundTrip "def x = 41 end; def y = 42 end")
]
]
where
valid = flip process ""

roundTrip txt = assertEqual "rountrip" term (decodeThrow $ encode term)
where
decodeThrow v = case eitherDecode v of
Left e -> error $ "Decoding of " <> from (T.decodeUtf8 (from v)) <> " failed with: " <> from e
Right x -> x
term = fromMaybe (error "") $ fromRight (error "") $ processTerm txt

process :: Text -> Text -> Assertion
process code expect = case processTerm code of
Left e
Expand Down

0 comments on commit ca6c9cd

Please sign in to comment.