module Data.Text.ParagraphLayout.Internal.TextContainerSpec (spec) where import qualified Data.List.NonEmpty import Data.Text (Text, empty, pack) import Data.Text.Foreign (lengthWord8) import Test.Hspec import Data.Text.ParagraphLayout.Internal.TextContainer ne :: [a] -> Data.List.NonEmpty.NonEmpty a ne = Data.List.NonEmpty.fromList data ExampleContainer = Contain { cText :: Text, cOffset :: Int } deriving (Show, Eq) contain :: String -> Int -> ExampleContainer contain s o = Contain (pack s) o instance TextContainer ExampleContainer where getText = cText instance SeparableTextContainer ExampleContainer where splitTextAt8 n (Contain t o) = (Contain t1 o1, Contain t2 o2) where (t1, t2) = splitTextAt8 n t o1 = o o2 = o + lengthWord8 t1 dropWhileStart p (Contain t o) = Contain t' o' where l = lengthWord8 t t' = dropWhileStart p t l' = lengthWord8 t o' = o + l - l' dropWhileEnd p (Contain t o) = Contain (dropWhileEnd p t) o exampleContainers :: [ExampleContainer] exampleContainers = [c1, c2] where (c1, c2) = splitTextAt8 11 $ contain "Vikipedija (Википедија)" 10 exampleBreaks :: [Int] exampleBreaks = [ -- Out of bounds. Should not generate any splits. 999, 50, -- End of last text. Should not generate a split. 43, -- Word and syllable bounds in the second text, -- similar to hyphenation rules. Each should generate a corresponding split. 38, 34, 30, 26, -- The exact edge between the two texts. -- Should generate a split, but not any empty containers. 21, -- Word and syllable bounds in the first text. -- Each should generate a corresponding split. 18, 16, 14, 12, -- Start of first text. Should not generate a split. 10, -- Out of bounds. Should not generate any splits. 5, 0, -1 ] exampleBreakPoints :: ExampleContainer -> [Int] exampleBreakPoints c = dropWhile (>= l) $ takeWhile (>= 0) $ map (subtract d) $ exampleBreaks where l = lengthWord8 $ cText c d = cOffset c isSpace :: Char -> Bool isSpace = (== ' ') spec :: Spec spec = do describe "splitTextsBy" $ do it "splits example text containers" $ do splitTextsBy exampleBreakPoints exampleContainers `shouldBe` [ ( ne [ contain "Vikipedija " 10, contain "(Википеди" 21 ] , ne [ contain "ја)" 38 ] ) , ( ne [ contain "Vikipedija " 10, contain "(Википе" 21 ] , ne [ contain "дија)" 34 ] ) , ( ne [ contain "Vikipedija " 10, contain "(Вики" 21 ] , ne [ contain "педија)" 30 ] ) , ( ne [ contain "Vikipedija " 10, contain "(Ви" 21 ] , ne [ contain "кипедија)" 26 ] ) , ( ne [ contain "Vikipedija " 10 ] , ne [ contain "(Википедија)" 21 ] ) , ( ne [ contain "Vikipedi" 10 ] , ne [ contain "ja " 18, contain "(Википедија)" 21 ] ) , ( ne [ contain "Vikipe" 10 ] , ne [ contain "dija " 16, contain "(Википедија)" 21 ] ) , ( ne [ contain "Viki" 10 ] , ne [ contain "pedija " 14, contain "(Википедија)" 21 ] ) , ( ne [ contain "Vi" 10 ] , ne [ contain "kipedija " 12, contain "(Википедија)" 21 ] ) ] describe "trimTextsEnd" $ do describe "isSpace" $ do it "does nothing on an empty list" $ do let inputTexts = [] :: [Text] trimTextsEnd isSpace inputTexts `shouldBe` inputTexts it "does nothing when last run does not end with space" $ do let inputTexts = [pack "some ", pack "text"] trimTextsEnd isSpace inputTexts `shouldBe` inputTexts it "trims empty texts down to an empty list" $ do let inputTexts = [empty, empty, empty] trimTextsEnd isSpace inputTexts `shouldBe` [] it "trims empty texts from a list" $ do let inputTexts = [pack "some ", pack "text", empty, empty] trimTextsEnd isSpace inputTexts `shouldBe` [pack "some ", pack "text"] it "trims spaces from last text" $ do let inputTexts = [pack "some ", pack "text "] trimTextsEnd isSpace inputTexts `shouldBe` [pack "some ", pack "text"] it "trims texts containing only spaces" $ do let inputTexts = [pack "some ", pack "text", pack " "] trimTextsEnd isSpace inputTexts `shouldBe` [pack "some ", pack "text"] it "trims last text that contains non-spaces" $ do let inputTexts = [pack "some ", pack "text ", pack " "] trimTextsEnd isSpace inputTexts `shouldBe` [pack "some ", pack "text"]