module ParseSpec where import Test.Hspec import Tile import Parse import Room import Plant import Story import Input import Meeple.Operate import Terminal.Game import Lens.Micro.Platform import qualified Control.Monad.State as S myp :: Parser a -> String -> a myp p c = parseRun "" p c ct :: Char -> Tile ct c = maybe (error "ct - ParseSpec") id (charTile c) spec :: Spec spec = do -- STORY -- describe "pcomment" $ do it "parses a comment" $ myp pcomment "@@ comment\n" `shouldBe` () it "eof is ok too" $ myp pcomment "@@ comment" `shouldBe` () describe "pstoryname" $ do it "parses a story name" $ myp pstoryname "story_name: Proclo\n" `shouldBe` "Proclo" describe "proomsize" $ do it "parses a mandatory room size" $ myp proomsize "room_size: 11 18\n" `shouldBe` (11, 18) describe "pstory" $ do it "parse a story" $ (^. rooms . to length) <$> readStory "stories/a_first-stroll.vns" `shouldReturn` 4 it "can end on EOF" $ let tt = init . unlines $ ["story_name: test", "room_size: 2 2", "start_room: Uno", "", "# Uno", "xx", "xx", ">>> N -> Uno"] in myp (_name <$> pstory) tt `shouldBe` "test" -- SCREEN -- -- ROOM -- describe "ptitle" $ do it "parses a screen title" $ myp ptitle "# alloro\n" `shouldBe` "alloro" describe "ptile" $ do it "parse a single tile" $ tType (myp ltile ".") `shouldBe` Background describe "proom" $ do it "parses a room" $ myp proom "# aaa\n \n>>> E -> bbb" `shouldBe` let p = defaultPlant r = defaultRoom & title .~ "aaa" & plant .~ p & exits .~ [Exit E "bbb"] in r -- PLANT -- describe "pelements" $ do it "parses a plant" $ myp pelements "\n @-" `shouldBe` [Blank, Blank, EMeeple (MSave $ defaultSave (2,2)), ETile (ct '-') (2,3)] it "parses a prop" $ myp pelements " ®-®" `shouldBe` [Blank, Blank, ETile (creaProp '-') (1,3), Blank] it "parses a multichar prop" $ myp pelements "®12®" `shouldBe` [Blank, ETile (creaProp '1') (1,2), ETile (creaProp '2') (1,3), Blank] -- EXITS -- describe "pcard" $ do it "parses a cardinal element" $ myp pcard "N" `shouldBe` N it "it is case unsensitive" $ myp pcard "n" `shouldBe` N describe "pexit" $ do it "parses an exit" $ myp pexit ">>> N -> qoo" `shouldBe` Exit N "qoo" -- ELEM/TILE -- describe "pelem" $ do it "parses a prop, if we are in prop-mode" $ myp (toggleprop >> pelem) "-" `shouldBe` ETile (creaProp '-') (1,1) it "parses a space too" $ myp pelem " " `shouldBe` Blank it "parses a newline too" $ myp pelem "\n" `shouldBe` Blank it "parses a meeple too" $ myp pelem "*" `shouldBe` EMeeple (MStar $ defaultStar (1,1)) describe "etile" $ do it "parse a single tile" $ myp etile ":" `shouldBe` ETile (ct ':') (1,1) describe "pmeeple" $ do it "parses a meeple" $ myp (Just <$> pmeeple) "d" `shouldBe` charMeeple 'd' (1,1) -- ANCILLARIES -- describe "advance" $ do it "advances a col" $ myp (advance ACol >> S.lift S.get) "" `shouldBe` ParseState (1, 2) False it "advances a row" $ myp (advance ARow >> S.lift S.get) "" `shouldBe` ParseState (2, 1) False it "resets column" $ myp (advance ACol >> advance ARow >> S.lift S.get) "" `shouldBe` ParseState (2, 1) False