~jaro/balkon

ba3f061d271830dda274348ca469e0187cf4039f — Jaro 11 months ago 8067edb
Generalise text from SpanData for other tests.
4 files changed, 85 insertions(+), 69 deletions(-)

M balkon.cabal
M test/Data/Text/ParagraphLayout/Internal/RunSpec.hs
D test/Data/Text/ParagraphLayout/SpanData.hs
A test/Data/Text/ParagraphLayout/TextData.hs
M balkon.cabal => balkon.cabal +1 -1
@@ 197,7 197,7 @@ test-suite balkon-test
        Data.Text.ParagraphLayout.RectSpec,
        Data.Text.ParagraphLayout.Rich.ParagraphData,
        Data.Text.ParagraphLayout.RichSpec,
        Data.Text.ParagraphLayout.SpanData
        Data.Text.ParagraphLayout.TextData

    -- Test dependencies.
    build-depends:

M test/Data/Text/ParagraphLayout/Internal/RunSpec.hs => test/Data/Text/ParagraphLayout/Internal/RunSpec.hs +33 -8
@@ 1,20 1,45 @@
module Data.Text.ParagraphLayout.Internal.RunSpec (spec) where

import Data.Text (pack)
import Data.Text.Glyphize (Direction (..), emptyFont)
import Data.Text (Text, pack)
import Data.Text.Glyphize (Direction (..), Font, emptyFont)

import Test.Hspec
import Data.Text.ParagraphLayout.Internal.BoxOptions
import Data.Text.ParagraphLayout.Internal.LineHeight
import Data.Text.ParagraphLayout.Internal.ResolvedBox
import Data.Text.ParagraphLayout.Internal.ResolvedSpan
import Data.Text.ParagraphLayout.Internal.Run
import Data.Text.ParagraphLayout.SpanData
import Data.Text.ParagraphLayout.Internal.TextOptions
import Data.Text.ParagraphLayout.TextData

defaultBox :: Direction -> ResolvedBox ()
defaultBox dir = ResolvedBox () 0 defaultBoxOptions dir

sampleSpan :: (Direction, String, Text) -> Font -> ResolvedSpan ()
sampleSpan (dir, lang, text) font = ResolvedSpan
    { spanUserData = ()
    , spanIndex = 0
    , spanOffsetInParagraph = 0
    , spanText = text
    , spanTextOptions = (defaultTextOptions dir)
        { textFont = font
        , textLineHeight = Normal
        , textLanguage = lang
        }
    , spanBoxes = [defaultBox dir]
    , spanLineBreaks = []
    , spanCharacterBreaks = []
    }

spec :: Spec
spec = do
    describe "spanToRuns" $ do
        it "handles span with no text" $ do
            spanToRuns (emptySpan emptyFont) `shouldBe` []
            let inputSpan = sampleSpan englishEmpty emptyFont
            let runs = spanToRuns inputSpan
            runs `shouldBe` []
        it "handles Czech hello" $ do
            let inputSpan = czechHello emptyFont
            let inputSpan = sampleSpan czechHello emptyFont
            let runs = spanToRuns inputSpan
            runs `shouldBe`
                [ Run


@@ 25,7 50,7 @@ spec = do
                    }
                ]
        it "handles Arabic hello" $ do
            let inputSpan = arabicHello emptyFont
            let inputSpan = sampleSpan arabicHello emptyFont
            let runs = spanToRuns inputSpan
            runs `shouldBe`
                [ Run


@@ 36,7 61,7 @@ spec = do
                    }
                ]
        it "handles Serbian with mixed script" $ do
            let inputSpan = serbianMixedScript emptyFont
            let inputSpan = sampleSpan serbianMixedScript emptyFont
            let runs = spanToRuns inputSpan
            runs `shouldBe`
                [ Run


@@ 54,7 79,7 @@ spec = do
                    }
                ]
        it "handles English text with Arabic inside" $ do
            let inputSpan = englishAroundArabic emptyFont
            let inputSpan = sampleSpan englishAroundArabic emptyFont
            let runs = spanToRuns inputSpan
            runs `shouldBe`
                [ Run

D test/Data/Text/ParagraphLayout/SpanData.hs => test/Data/Text/ParagraphLayout/SpanData.hs +0 -60
@@ 1,60 0,0 @@
module Data.Text.ParagraphLayout.SpanData
    ( emptySpan
    , czechHello
    , arabicHello
    , serbianMixedScript
    , englishAroundArabic
    )
where

import Data.Text (pack)
import Data.Text.Glyphize (Direction (DirLTR, DirRTL), Font)

import Data.Text.ParagraphLayout.Internal.BoxOptions
import Data.Text.ParagraphLayout.Internal.LineHeight
import Data.Text.ParagraphLayout.Internal.ResolvedBox
import Data.Text.ParagraphLayout.Internal.ResolvedSpan
import Data.Text.ParagraphLayout.Internal.TextOptions

defaultBox :: Direction -> ResolvedBox ()
defaultBox dir = ResolvedBox () 0 defaultBoxOptions dir

sampleSpan :: Direction -> String -> String -> Font -> ResolvedSpan ()
sampleSpan dir lang str font = ResolvedSpan
    { spanUserData = ()
    , spanIndex = 0
    , spanOffsetInParagraph = 0
    , spanText = text
    , spanTextOptions = (defaultTextOptions dir)
        { textFont = font
        , textLineHeight = Normal
        , textLanguage = lang
        }
    , spanBoxes = [defaultBox dir]
    , spanLineBreaks = []
    , spanCharacterBreaks = []
    }
    where
        text = pack str

emptySpan :: Font -> ResolvedSpan ()
emptySpan = sampleSpan DirLTR "en"
    ""

czechHello :: Font -> ResolvedSpan ()
czechHello = sampleSpan DirLTR "cs"
    "Ahoj, světe!"

arabicHello :: Font -> ResolvedSpan ()
arabicHello = sampleSpan DirRTL "ar"
    "سلام"

serbianMixedScript :: Font -> ResolvedSpan ()
serbianMixedScript = sampleSpan DirLTR "sr"
    "Vikipedija (Википедија)"

-- | Source:
-- <https://www.w3.org/International/articles/inline-bidi-markup/uba-basics>
englishAroundArabic :: Font -> ResolvedSpan ()
englishAroundArabic = sampleSpan DirLTR "en"
    "The title is مفتاح معايير الويب in Arabic."

A test/Data/Text/ParagraphLayout/TextData.hs => test/Data/Text/ParagraphLayout/TextData.hs +51 -0
@@ 0,0 1,51 @@
module Data.Text.ParagraphLayout.TextData
    ( englishEmpty
    , czechHello
    , arabicHello
    , serbianMixedScript
    , englishAroundArabic
    )
where

import Data.Text (Text, empty, pack)
import Data.Text.Glyphize (Direction (DirLTR, DirRTL))

type Language = String
type Sample = (Direction, Language, Text)

englishEmpty :: Sample
englishEmpty =
    ( DirLTR
    , "en"
    , empty
    )

czechHello :: Sample
czechHello =
    ( DirLTR
    , "cs"
    , pack "Ahoj, světe!"
    )

arabicHello :: Sample
arabicHello =
    ( DirRTL
    , "ar"
    , pack "سلام"
    )

serbianMixedScript :: Sample
serbianMixedScript =
    ( DirLTR
    , "sr"
    , pack "Vikipedija (Википедија)"
    )

-- | Source:
-- <https://www.w3.org/International/articles/inline-bidi-markup/uba-basics>
englishAroundArabic :: Sample
englishAroundArabic =
    ( DirLTR
    , "en"
    , pack "The title is مفتاح معايير الويب in Arabic."
    )