{-# LANGUAGE OverloadedStrings #-} module Boilerplate.DocTests where import Boilerplate.Doc import Data.Text (Text) import HsInspect.Types (Pos(..)) import Test.Tasty.Hspec upsert' :: Text -> (Int, Int) -> Maybe (Int, Int) -> Text -> Text upsert' orig start end new = unDoc $ upsert (mkDoc orig) (mkPos start) (mkPos <$> end) new where mkPos (l, c) = Pos l c spec_doc :: Spec spec_doc = do it "should upsert text at the start" $ do upsert' "foo\nbar\nbaz" (0, 0) Nothing "gaz\n" `shouldBe` "gaz\nfoo\nbar\nbaz\n" it "should upsert text at the end" $ do upsert' "foo\nbar\nbaz" (4, 0) Nothing "gaz\n" `shouldBe` "foo\nbar\nbaz\ngaz\n\n" upsert' "foo\nbar\nbaz" (4, 1) Nothing "gaz\n" `shouldBe` "foo\nbar\nbaz\ngaz\n\n" it "should upsert text in the center" $ do upsert' "foo\nbar\nbaz" (2, 0) Nothing "gaz\n" `shouldBe` "foo\ngaz\nbar\nbaz\n" it "should upsert text in the middle of a line" $ do upsert' "foo\nbar\nbaz" (2, 1) Nothing "gaz" `shouldBe` "foo\nbgazar\nbaz\n" upsert' "foo\nbar\nbaz" (2, 2) Nothing "gaz" `shouldBe` "foo\nbagazr\nbaz\n" it "should upsert and replace text beyond the region" $ do upsert' "foo\nbar\nbaz" (2, 1) (Just (4, 0)) "ozo" `shouldBe` "foo\nbozo\n" it "should upsert and replace text in the middle of a line" $ do upsert' "foo\nbar\nbaz" (2, 1) (Just (2, 3)) "ozo" `shouldBe` "foo\nbozor\nbaz\n" it "should upsert and replace text beyond a line" $ do upsert' "foo\nbar\nbaz" (2, 1) (Just (2, 5)) "ozo" `shouldBe` "foo\nbozo\nbaz\n" it "should upsert and replace text across multiple lines" $ do upsert' "foo\nbar\nbaz" (2, 1) (Just (3, 3)) "uz" `shouldBe` "foo\nbuzz\n"