{-# LANGUAGE OverloadedStrings #-} module Main (main) where import System.IO import System.IO.LineIndexedCursor import Data.Foldable import Test.Hspec main :: IO () main = hspec $ do let mkCursor capacity = do h <- openFile "test/testdata" ReadMode c <- mkLineIndexedCursorWithCapacity h capacity pure (h, c) forM_ [0 :: Integer ..20] $ \capacity -> do before (mkCursor capacity) . after (\(h, _) -> hClose h) $ describe ("System.IO.LineIndexedCursor with list capacity " ++ show capacity) $ do it "getCurrentLine works" $ \(_, c) -> do l <- getCurrentLine c l `shouldBe` Just "Lorem ipsum dolor sit amet, consectetur adipiscing elit." ln <- goToLine c 3 ln `shouldBe` 3 l' <- getCurrentLine c l' `shouldBe` Just "Curabitur nec mi sit amet justo condimentum gravida." l'' <- getCurrentLine c l'' `shouldBe` Just "Pellentesque accumsan dolor at nisl pulvinar, ut bibendum diam egestas." it "goToLine works" $ \(_, c) -> do ln <- goToLine c 10 ln `shouldBe` 10 l <- getCurrentLine c l `shouldBe` Just "Sed elementum velit sit amet orci mollis tincidunt." it "goToLine is negative" $ \(_, c) -> do ln <- goToLine c (-10) ln `shouldBe` 0 l <- getCurrentLine c l `shouldBe` Just "Lorem ipsum dolor sit amet, consectetur adipiscing elit." it "goToLine is too big" $ \(_, c) -> do l <- getCurrentLine c l `shouldBe` Just "Lorem ipsum dolor sit amet, consectetur adipiscing elit." ln <- goToLine c 30 ln `shouldBe` 20 l' <- getCurrentLine c l' `shouldBe` Nothing it "fullScan works" $ \(_, c) -> do l <- getCurrentLine c l `shouldBe` Just "Lorem ipsum dolor sit amet, consectetur adipiscing elit." doFullScan c cln <- getCurrentLineNumber c cln `shouldBe` 20 l' <- getCurrentLine c l' `shouldBe` Nothing s <- getCursorState c s `shouldBe` [0,57,117,191,244,316,384,429,511,561,616,668,715,761,799,851,907,941,981,1024,1068] it "read line, then go to the beginning and forth" $ \(_, c) -> do cln <- getCurrentLineNumber c cln `shouldBe` 0 l <- getCurrentLine c l `shouldBe` Just "Lorem ipsum dolor sit amet, consectetur adipiscing elit." cln' <- getCurrentLineNumber c cln' `shouldBe` 1 _ <- getCurrentLine c _ <- getCurrentLine c _ <- getCurrentLine c _ <- getCurrentLine c _ <- getCurrentLine c cln'' <- getCurrentLineNumber c cln'' `shouldBe` 6 ln <- goToLine c 0 ln `shouldBe` 0 cln''' <- getCurrentLineNumber c cln''' `shouldBe` 0 l' <- getCurrentLine c l' `shouldBe` Just "Lorem ipsum dolor sit amet, consectetur adipiscing elit." ln' <- goToLine c 5 ln' `shouldBe` 5 l'' <- getCurrentLine c l'' `shouldBe` Just "Curabitur nec dui posuere, tincidunt turpis vitae, tincidunt magna." ln'' <- goToLine c 6 ln'' `shouldBe` 6 ln''' <- goToLine c 7 ln''' `shouldBe` 7 ln'''' <- goToLine c 10 ln'''' `shouldBe` 10 ln''''' <- goToLine c 3 ln''''' `shouldBe` 3 ln'''''' <- goToLine c 2 ln'''''' `shouldBe` 2 ln''''''' <- goToLine c 1 ln''''''' `shouldBe` 1 ln'''''''' <- goToLine c 0 ln'''''''' `shouldBe` 0