module Data.Text.ParagraphLayout.Internal.TextContainerSpec (spec) where import Data.Text (Text, empty, pack) import Data.Text.Foreign (lengthWord8) import Test.Hspec import Data.Text.ParagraphLayout.Internal.TextContainer 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 only generate a split for end-biased breaks. 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 only generate a split for start-biased breaks. 10, -- Out of bounds. Should not generate any splits. 5, 0, -1 ] -- | Bound `exampleBreaks` to the given text container and adjust offsets, -- including start of text but excluding end of text. -- -- Container boundaries should therefore only generate one split, -- and all splits should have a non-empty prefix. startBiasedBreakPoints :: ExampleContainer -> [Int] startBiasedBreakPoints c = dropWhile (>= l) $ takeWhile (>= 0) $ map (subtract d) $ exampleBreaks where l = lengthWord8 $ cText c d = cOffset c -- | Bound `exampleBreaks` to the given text container and adjust offsets, -- excluding start of text but including end of text. -- -- Container boundaries should therefore only generate one split, -- and all splits should have a non-empty prefix. endBiasedBreakPoints :: ExampleContainer -> [Int] endBiasedBreakPoints 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 (start bias)" $ do splitTextsBy startBiasedBreakPoints exampleContainers `shouldBe` [ ( [ contain "Vikipedija " 10, contain "(Википеди" 21 ] , [ contain "ја)" 38 ] ) , ( [ contain "Vikipedija " 10, contain "(Википе" 21 ] , [ contain "дија)" 34 ] ) , ( [ contain "Vikipedija " 10, contain "(Вики" 21 ] , [ contain "педија)" 30 ] ) , ( [ contain "Vikipedija " 10, contain "(Ви" 21 ] , [ contain "кипедија)" 26 ] ) , ( [ contain "Vikipedija " 10 ] , [ contain "(Википедија)" 21 ] ) , ( [ contain "Vikipedi" 10 ] , [ contain "ja " 18, contain "(Википедија)" 21 ] ) , ( [ contain "Vikipe" 10 ] , [ contain "dija " 16, contain "(Википедија)" 21 ] ) , ( [ contain "Viki" 10 ] , [ contain "pedija " 14, contain "(Википедија)" 21 ] ) , ( [ contain "Vi" 10 ] , [ contain "kipedija " 12, contain "(Википедија)" 21 ] ) , ( [] , [ contain "Vikipedija " 10, contain "(Википедија)" 21 ] ) ] it "splits example text containers (end bias)" $ do splitTextsBy endBiasedBreakPoints exampleContainers `shouldBe` [ ( [ contain "Vikipedija " 10, contain "(Википедија)" 21 ] , [] ) , ( [ contain "Vikipedija " 10, contain "(Википеди" 21 ] , [ contain "ја)" 38 ] ) , ( [ contain "Vikipedija " 10, contain "(Википе" 21 ] , [ contain "дија)" 34 ] ) , ( [ contain "Vikipedija " 10, contain "(Вики" 21 ] , [ contain "педија)" 30 ] ) , ( [ contain "Vikipedija " 10, contain "(Ви" 21 ] , [ contain "кипедија)" 26 ] ) , ( [ contain "Vikipedija " 10 ] , [ contain "(Википедија)" 21 ] ) , ( [ contain "Vikipedi" 10 ] , [ contain "ja " 18, contain "(Википедија)" 21 ] ) , ( [ contain "Vikipe" 10 ] , [ contain "dija " 16, contain "(Википедија)" 21 ] ) , ( [ contain "Viki" 10 ] , [ contain "pedija " 14, contain "(Википедија)" 21 ] ) , ( [ contain "Vi" 10 ] , [ contain "kipedija " 12, contain "(Википедија)" 21 ] ) ] describe "dropWhileStartCascade" $ do describe "isSpace" $ do it "does nothing on an empty list" $ do let inputTexts = [] :: [Text] dropWhileStartCascade isSpace inputTexts `shouldBe` inputTexts it "does nothing on list of empty texts" $ do let inputTexts = [empty, empty, empty] dropWhileStartCascade isSpace inputTexts `shouldBe` inputTexts it "does nothing when first run does not start with space" $ do let inputTexts = [pack "some ", pack "text"] dropWhileStartCascade isSpace inputTexts `shouldBe` inputTexts it "does nothing when first non-empty run does not start with space" $ do let inputTexts = [empty, empty, pack "some ", pack "text"] dropWhileStartCascade isSpace inputTexts `shouldBe` inputTexts it "trims spaces from first text" $ do let inputTexts = [pack " some ", pack "text"] dropWhileStartCascade isSpace inputTexts `shouldBe` [pack "some ", pack "text"] it "trims texts containing only spaces to empty" $ do let inputTexts = [pack " ", pack "some ", pack "text"] dropWhileStartCascade isSpace inputTexts `shouldBe` [empty, pack "some ", pack "text"] it "trims first text that contains non-spaces" $ do let inputTexts = [pack " ", pack " some ", pack "text "] dropWhileStartCascade isSpace inputTexts `shouldBe` [empty, pack "some ", pack "text "] it "trims space-only input down to empty texts" $ do let inputTexts = [pack " ", pack " ", pack " "] dropWhileStartCascade isSpace inputTexts `shouldBe` [empty, empty, empty] describe "dropWhileEndCascade" $ do describe "isSpace" $ do it "does nothing on an empty list" $ do let inputTexts = [] :: [Text] dropWhileEndCascade isSpace inputTexts `shouldBe` inputTexts it "does nothing on list of empty texts" $ do let inputTexts = [empty, empty, empty] dropWhileEndCascade isSpace inputTexts `shouldBe` inputTexts it "does nothing when last run does not end with space" $ do let inputTexts = [pack "some ", pack "text"] dropWhileEndCascade isSpace inputTexts `shouldBe` inputTexts it "does nothing when last non-empty run does not end with space" $ do let inputTexts = [pack "some ", pack "text", empty, empty] dropWhileEndCascade isSpace inputTexts `shouldBe` inputTexts it "trims spaces from last text" $ do let inputTexts = [pack "some ", pack "text "] dropWhileEndCascade isSpace inputTexts `shouldBe` [pack "some ", pack "text"] it "trims texts containing only spaces to empty" $ do let inputTexts = [pack "some ", pack "text", pack " "] dropWhileEndCascade isSpace inputTexts `shouldBe` [pack "some ", pack "text", empty] it "trims last text that contains non-spaces" $ do let inputTexts = [pack "some ", pack "text ", pack " "] dropWhileEndCascade isSpace inputTexts `shouldBe` [pack "some ", pack "text", empty] it "trims space-only input down to empty texts" $ do let inputTexts = [pack " ", pack " ", pack " "] dropWhileEndCascade isSpace inputTexts `shouldBe` [empty, empty, empty]