tmux-mate/test/Spec.hs

80 lines
2.7 KiB
Haskell
Raw Permalink Normal View History

2020-02-17 05:55:24 +03:00
{-# LANGUAGE ScopedTypeVariables #-}
2020-02-23 12:59:55 +03:00
{-# LANGUAGE TypeApplications #-}
2020-02-17 05:55:24 +03:00
import Control.Monad (when)
2020-02-22 14:20:49 +03:00
import qualified Data.List.NonEmpty as NE
2020-02-23 12:59:55 +03:00
import qualified Data.Text as Text
import qualified Data.Text.IO as Text.IO
2020-02-17 05:55:24 +03:00
import Dhall
import Dhall.Core (pretty)
import Test.Hspec
import Test.QuickCheck
import Test.QuickCheck.Monadic
2020-02-22 14:20:49 +03:00
import qualified Tests.TmuxMate.TmuxCommands as TmuxCommands
2020-02-17 05:55:24 +03:00
import Tests.TmuxMate.Types (Session)
2020-02-22 11:52:02 +03:00
import qualified Tests.TmuxMate.Validate as Validate
2020-02-17 05:55:24 +03:00
import TmuxMate.Running
2020-02-17 21:42:29 +03:00
import TmuxMate.Types
2020-02-17 05:55:24 +03:00
main :: IO ()
main = hspec $ do
2020-02-22 11:52:02 +03:00
Validate.spec
2020-02-22 14:20:49 +03:00
TmuxCommands.spec
2020-02-17 05:55:24 +03:00
describe "ParseRunning" $ do
it "Rejects nonsense" $ do
parseSingle "sdfdsf" `shouldBe` Nothing
it "Accepts goodness" $ do
2020-02-17 21:42:29 +03:00
parseSingle "foo:bar:1:yes Pane 1"
`shouldBe` Just
( Running
2020-02-22 14:20:49 +03:00
(VSessionName (NE.fromList "foo"))
(VWindowName (NE.fromList "bar"))
2020-02-17 21:42:29 +03:00
(PaneCommand "yes Pane 1")
1
)
2020-02-17 05:55:24 +03:00
it "Accepts goodness with double colons inside" $ do
2020-02-17 21:42:29 +03:00
parseSingle "foo:bar:1:yes Pane 1:2"
`shouldBe` Just
( Running
2020-02-22 14:20:49 +03:00
(VSessionName (NE.fromList "foo"))
(VWindowName (NE.fromList "bar"))
2020-02-17 21:42:29 +03:00
(PaneCommand "yes Pane 1:2")
1
)
2020-02-17 05:55:24 +03:00
it "returns the original number when given a positive input" $
2020-02-22 14:20:49 +03:00
parseRunning
"0:0:\nfoo:bar:0:yes Pane 2\nfoo:bar:1:yes Pane 1\n"
2020-02-17 21:42:29 +03:00
`shouldBe` [ Running
2020-02-22 14:20:49 +03:00
(VSessionName (NE.fromList "foo"))
(VWindowName (NE.fromList "bar"))
2020-02-17 21:42:29 +03:00
(PaneCommand "yes Pane 2")
0,
Running
2020-02-22 14:20:49 +03:00
(VSessionName (NE.fromList "foo"))
(VWindowName (NE.fromList "bar"))
2020-02-17 21:42:29 +03:00
(PaneCommand "yes Pane 1")
1
]
2020-02-23 12:59:55 +03:00
describe "Dhall" $ do
it "Round trips Dhall encoding" $ do
property dhallSessionRoundtrip
it "Generates a Dhall schema that matches our advertised one" $ do
let schema = (Dhall.Core.pretty (Dhall.expected (Dhall.auto @Session)))
savedSchema <- Text.IO.readFile "./samples/Schema.dhall"
when
(Text.stripEnd schema /= Text.stripEnd savedSchema)
( do
putStrLn "Generated schema:"
Text.IO.putStrLn schema
)
2020-02-23 12:59:55 +03:00
Text.stripEnd schema `shouldBe` Text.stripEnd savedSchema
2020-02-17 05:55:24 +03:00
dhallSessionRoundtrip :: Property
dhallSessionRoundtrip =
monadicIO $ do
(sesh :: Session) <- pick arbitrary
let dhallVal = pretty (embed inject sesh)
let (decoder :: Decoder Session) = auto
decoded <- run $ input decoder dhallVal
assert $ decoded == sesh