~jaro/balkon

1555a8cc7b5b6ad8c7f365564876dc6f5649f19c — Jaro 1 year, 2 months ago 0552e48
Move non-public modules into Internal namespace.
23 files changed, 215 insertions(+), 208 deletions(-)

M balkon.cabal
M src/Data/Text/ParagraphLayout.hs
R src/Data/Text/ParagraphLayout/{Break.hs => Internal/Break.hs}
R src/Data/Text/ParagraphLayout/{Fragment.hs => Internal/Fragment.hs}
R src/Data/Text/ParagraphLayout/{LineHeight.hs => Internal/LineHeight.hs}
R src/Data/Text/ParagraphLayout/{Plain.hs => Internal/Plain.hs}
R src/Data/Text/ParagraphLayout/{ProtoFragment.hs => Internal/ProtoFragment.hs}
R src/Data/Text/ParagraphLayout/{ResolvedSpan.hs => Internal/ResolvedSpan.hs}
R src/Data/Text/ParagraphLayout/{Run.hs => Internal/Run.hs}
R src/Data/Text/{Script.hs => ParagraphLayout/Internal/Script.hs}
R src/Data/Text/ParagraphLayout/{Span.hs => Internal/Span.hs}
R src/Data/Text/ParagraphLayout/{TextContainer.hs => Internal/TextContainer.hs}
R src/Data/Text/{Zipper.hs => ParagraphLayout/Internal/Zipper.hs}
M src/Data/Text/ParagraphLayout/Rect.hs
R test/Data/Text/ParagraphLayout/{BreakSpec.hs => Internal/BreakSpec.hs}
R test/Data/Text/ParagraphLayout/{RunSpec.hs => Internal/RunSpec.hs}
R test/Data/Text/ParagraphLayout/{TextContainerSpec.hs => Internal/TextContainerSpec.hs}
R test/Data/Text/{ZipperSpec.hs => ParagraphLayout/Internal/ZipperSpec.hs}
M test/Data/Text/ParagraphLayout/ParagraphConstruction.hs
M test/Data/Text/ParagraphLayout/ParagraphData.hs
D test/Data/Text/ParagraphLayout/PlainSpec.hs
M test/Data/Text/ParagraphLayout/SpanData.hs
M test/Data/Text/ParagraphLayoutSpec.hs
M balkon.cabal => balkon.cabal +17 -18
@@ 99,20 99,20 @@ library
    -- Modules exported by the library.
    exposed-modules:
        Data.Text.ParagraphLayout,
        Data.Text.ParagraphLayout.Break,
        Data.Text.ParagraphLayout.Fragment,
        Data.Text.ParagraphLayout.LineHeight,
        Data.Text.ParagraphLayout.Plain,
        Data.Text.ParagraphLayout.ProtoFragment
        Data.Text.ParagraphLayout.Rect,
        Data.Text.ParagraphLayout.ResolvedSpan,
        Data.Text.ParagraphLayout.Run,
        Data.Text.ParagraphLayout.Span,
        Data.Text.ParagraphLayout.TextContainer,
        Data.Text.Zipper
        Data.Text.ParagraphLayout.Internal.Break,
        Data.Text.ParagraphLayout.Internal.Fragment,
        Data.Text.ParagraphLayout.Internal.LineHeight,
        Data.Text.ParagraphLayout.Internal.Plain,
        Data.Text.ParagraphLayout.Internal.ProtoFragment
        Data.Text.ParagraphLayout.Internal.ResolvedSpan,
        Data.Text.ParagraphLayout.Internal.Run,
        Data.Text.ParagraphLayout.Internal.Span,
        Data.Text.ParagraphLayout.Internal.TextContainer,
        Data.Text.ParagraphLayout.Internal.Zipper,
        Data.Text.ParagraphLayout.Rect

    -- Modules included in this library but not exported.
    other-modules:    Data.Text.Script
    other-modules:    Data.Text.ParagraphLayout.Internal.Script

    -- Other library packages from which modules are imported.
    build-depends:


@@ 136,16 136,15 @@ test-suite balkon-test

    other-modules:
        Data.Text.ParagraphLayoutSpec,
        Data.Text.ParagraphLayout.BreakSpec,
        Data.Text.ParagraphLayout.FontLoader,
        Data.Text.ParagraphLayout.Internal.BreakSpec,
        Data.Text.ParagraphLayout.Internal.RunSpec,
        Data.Text.ParagraphLayout.Internal.TextContainerSpec,
        Data.Text.ParagraphLayout.Internal.ZipperSpec,
        Data.Text.ParagraphLayout.ParagraphConstruction,
        Data.Text.ParagraphLayout.ParagraphData,
        Data.Text.ParagraphLayout.PlainSpec,
        Data.Text.ParagraphLayout.RectSpec,
        Data.Text.ParagraphLayout.RunSpec,
        Data.Text.ParagraphLayout.SpanData,
        Data.Text.ParagraphLayout.TextContainerSpec,
        Data.Text.ZipperSpec
        Data.Text.ParagraphLayout.SpanData

    -- Test dependencies.
    build-depends:

M src/Data/Text/ParagraphLayout.hs => src/Data/Text/ParagraphLayout.hs +20 -1
@@ 1,2 1,21 @@
module Data.Text.ParagraphLayout ()
module Data.Text.ParagraphLayout
    (Fragment(Fragment, fragmentPen, fragmentRect, fragmentGlyphs)
    ,LineHeight(Absolute, Normal)
    ,Paragraph(Paragraph)
    ,ParagraphLayout(ParagraphLayout, paragraphRect, spanLayouts)
    ,ParagraphOptions
        (ParagraphOptions
        ,paragraphFont
        ,paragraphLineHeight
        ,paragraphMaxWidth
        )
    ,Span(Span, spanLanguage, spanLength)
    ,SpanLayout(SpanLayout)
    ,layoutPlain
    )
where

import Data.Text.ParagraphLayout.Internal.Fragment
import Data.Text.ParagraphLayout.Internal.LineHeight
import Data.Text.ParagraphLayout.Internal.Plain
import Data.Text.ParagraphLayout.Internal.Span

R src/Data/Text/ParagraphLayout/Break.hs => src/Data/Text/ParagraphLayout/Internal/Break.hs +1 -1
@@ 5,7 5,7 @@
-- (also called UTF-8 code units or bytes) between the start of the input `Text`
-- and the position of the break. The internal offset of the `Text` from the
-- start of its underlying byte array is excluded.
module Data.Text.ParagraphLayout.Break (breaksDesc, subOffsetsDesc)
module Data.Text.ParagraphLayout.Internal.Break (breaksDesc, subOffsetsDesc)
where

import Data.Text (Text)

R src/Data/Text/ParagraphLayout/Fragment.hs => src/Data/Text/ParagraphLayout/Internal/Fragment.hs +1 -1
@@ 1,4 1,4 @@
module Data.Text.ParagraphLayout.Fragment (Fragment(..))
module Data.Text.ParagraphLayout.Internal.Fragment (Fragment(..))
where

import Data.Int (Int32)

R src/Data/Text/ParagraphLayout/LineHeight.hs => src/Data/Text/ParagraphLayout/Internal/LineHeight.hs +1 -1
@@ 1,4 1,4 @@
module Data.Text.ParagraphLayout.LineHeight (LineHeight(..))
module Data.Text.ParagraphLayout.Internal.LineHeight (LineHeight(..))
where

import Data.Int (Int32)

R src/Data/Text/ParagraphLayout/Plain.hs => src/Data/Text/ParagraphLayout/Internal/Plain.hs +10 -13
@@ 8,13 8,10 @@
-- example, if @1em = 20px@, if the output pixels are square, and if the output
-- coordinates are in 1/64ths of a pixel, you should set both the @x_scale@ and
-- the @y_scale@ to @1280@.
module Data.Text.ParagraphLayout.Plain
    (LineHeight(..)
    ,Paragraph(..)
module Data.Text.ParagraphLayout.Internal.Plain
    (Paragraph(..)
    ,ParagraphLayout(..)
    ,ParagraphOptions(..)
    ,Rect(..)
    ,Span(..)
    ,SpanLayout(..)
    ,layoutPlain
    )


@@ 43,15 40,15 @@ import qualified Data.Text.ICU as BreakStatus (Line)
import Data.Text.Internal (Text(Text))
import qualified Data.Text.Lazy as Lazy

import Data.Text.ParagraphLayout.Break
import Data.Text.ParagraphLayout.Fragment
import Data.Text.ParagraphLayout.LineHeight
import qualified Data.Text.ParagraphLayout.ProtoFragment as PF
import Data.Text.ParagraphLayout.Internal.Break
import Data.Text.ParagraphLayout.Internal.Fragment
import Data.Text.ParagraphLayout.Internal.LineHeight
import qualified Data.Text.ParagraphLayout.Internal.ProtoFragment as PF
import qualified Data.Text.ParagraphLayout.Internal.ResolvedSpan as RS
import Data.Text.ParagraphLayout.Internal.Run
import Data.Text.ParagraphLayout.Internal.Span
import Data.Text.ParagraphLayout.Internal.TextContainer
import Data.Text.ParagraphLayout.Rect
import qualified Data.Text.ParagraphLayout.ResolvedSpan as RS
import Data.Text.ParagraphLayout.Run
import Data.Text.ParagraphLayout.Span
import Data.Text.ParagraphLayout.TextContainer

-- | Text to be laid out as a paragraph.
--

R src/Data/Text/ParagraphLayout/ProtoFragment.hs => src/Data/Text/ParagraphLayout/Internal/ProtoFragment.hs +1 -1
@@ 1,4 1,4 @@
module Data.Text.ParagraphLayout.ProtoFragment (ProtoFragment(..))
module Data.Text.ParagraphLayout.Internal.ProtoFragment (ProtoFragment(..))
where

import Data.Int (Int32)

R src/Data/Text/ParagraphLayout/ResolvedSpan.hs => src/Data/Text/ParagraphLayout/Internal/ResolvedSpan.hs +3 -3
@@ 1,12 1,12 @@
module Data.Text.ParagraphLayout.ResolvedSpan (ResolvedSpan(..))
module Data.Text.ParagraphLayout.Internal.ResolvedSpan (ResolvedSpan(..))
where

import Data.Text (Text)
import Data.Text.Glyphize (Font)
import qualified Data.Text.ICU as BreakStatus (Line)

import Data.Text.ParagraphLayout.LineHeight
import Data.Text.ParagraphLayout.TextContainer
import Data.Text.ParagraphLayout.Internal.LineHeight
import Data.Text.ParagraphLayout.Internal.TextContainer

-- | Internal structure containing resolved values that may be shared with
-- other spans across the paragraph.

R src/Data/Text/ParagraphLayout/Run.hs => src/Data/Text/ParagraphLayout/Internal/Run.hs +5 -5
@@ 1,4 1,4 @@
module Data.Text.ParagraphLayout.Run (Run(..), spanToRuns)
module Data.Text.ParagraphLayout.Internal.Run (Run(..), spanToRuns)
where

import Data.List (mapAccumL)


@@ 7,11 7,11 @@ import Data.Text (Text)
import Data.Text.Foreign (dropWord8, lengthWord8, takeWord8)
import Data.Text.Glyphize (Direction(..))
import qualified Data.Text.ICU.Char as ICUChar
import Data.Text.Script (charScript)
import Data.Text.Zipper

import Data.Text.ParagraphLayout.ResolvedSpan
import Data.Text.ParagraphLayout.TextContainer
import Data.Text.ParagraphLayout.Internal.ResolvedSpan
import Data.Text.ParagraphLayout.Internal.Script (charScript)
import Data.Text.ParagraphLayout.Internal.TextContainer
import Data.Text.ParagraphLayout.Internal.Zipper

type ScriptCode = String


R src/Data/Text/Script.hs => src/Data/Text/ParagraphLayout/Internal/Script.hs +1 -1
@@ 1,4 1,4 @@
module Data.Text.Script (charScript)
module Data.Text.ParagraphLayout.Internal.Script (charScript)
where

-- TODO: Use a direct interface to the ICU library, if possible.

R src/Data/Text/ParagraphLayout/Span.hs => src/Data/Text/ParagraphLayout/Internal/Span.hs +1 -1
@@ 1,4 1,4 @@
module Data.Text.ParagraphLayout.Span (Span(..))
module Data.Text.ParagraphLayout.Internal.Span (Span(..))
where

-- Paragraph is broken into spans by the caller.

R src/Data/Text/ParagraphLayout/TextContainer.hs => src/Data/Text/ParagraphLayout/Internal/TextContainer.hs +1 -1
@@ 1,4 1,4 @@
module Data.Text.ParagraphLayout.TextContainer
module Data.Text.ParagraphLayout.Internal.TextContainer
    (SeparableTextContainer
    ,TextContainer
    ,getText

R src/Data/Text/Zipper.hs => src/Data/Text/ParagraphLayout/Internal/Zipper.hs +1 -3
@@ 2,9 2,7 @@
--
-- All measurements are in UTF-8 code points, each of which can be between
-- 1 and 4 bytes long (inclusive).
module Data.Text.Zipper
    -- TODO: Consider renaming the module to avoid conflict with text-zipper
    --       from Hackage.
module Data.Text.ParagraphLayout.Internal.Zipper
    (Zipper(preceding, following)
    ,advanceBy
    ,atEnd

M src/Data/Text/ParagraphLayout/Rect.hs => src/Data/Text/ParagraphLayout/Rect.hs +1 -1
@@ 1,7 1,7 @@
-- | Representation of an axis-aligned rectangle on a 2D plane, with one of its
-- corners being a designated origin point.
module Data.Text.ParagraphLayout.Rect
    (Rect(..)
    (Rect(Rect, x_origin, y_origin, x_size, y_size)
    ,height
    ,union
    ,width

R test/Data/Text/ParagraphLayout/BreakSpec.hs => test/Data/Text/ParagraphLayout/Internal/BreakSpec.hs +2 -2
@@ 1,4 1,4 @@
module Data.Text.ParagraphLayout.BreakSpec (spec) where
module Data.Text.ParagraphLayout.Internal.BreakSpec (spec) where

import Data.Text (empty, pack, singleton)
import Data.Text.ICU


@@ 11,7 11,7 @@ import Data.Text.ICU
import qualified Data.Text.ICU as BreakStatus (Line(..), Word(..))

import Test.Hspec
import Data.Text.ParagraphLayout.Break
import Data.Text.ParagraphLayout.Internal.Break

spec :: Spec
spec = do

R test/Data/Text/ParagraphLayout/RunSpec.hs => test/Data/Text/ParagraphLayout/Internal/RunSpec.hs +3 -3
@@ 1,12 1,12 @@
module Data.Text.ParagraphLayout.RunSpec (spec) where
module Data.Text.ParagraphLayout.Internal.RunSpec (spec) where

import Data.Text (pack)
import Data.Text.Glyphize (Direction(..))

import Test.Hspec
import Data.Text.ParagraphLayout.FontLoader
import Data.Text.ParagraphLayout.ResolvedSpan
import Data.Text.ParagraphLayout.Run
import Data.Text.ParagraphLayout.Internal.ResolvedSpan
import Data.Text.ParagraphLayout.Internal.Run
import Data.Text.ParagraphLayout.SpanData

spec :: Spec

R test/Data/Text/ParagraphLayout/TextContainerSpec.hs => test/Data/Text/ParagraphLayout/Internal/TextContainerSpec.hs +3 -3
@@ 1,11 1,11 @@
module Data.Text.ParagraphLayout.TextContainerSpec (spec) where
module Data.Text.ParagraphLayout.Internal.TextContainerSpec (spec) where

import Data.Text (pack)
import Data.Text.Glyphize (Direction(..))

import Test.Hspec
import Data.Text.ParagraphLayout.Run
import Data.Text.ParagraphLayout.TextContainer
import Data.Text.ParagraphLayout.Internal.Run
import Data.Text.ParagraphLayout.Internal.TextContainer

inputRuns :: [Run]
inputRuns =

R test/Data/Text/ZipperSpec.hs => test/Data/Text/ParagraphLayout/Internal/ZipperSpec.hs +2 -2
@@ 1,11 1,11 @@
module Data.Text.ZipperSpec (spec) where
module Data.Text.ParagraphLayout.Internal.ZipperSpec (spec) where

import Control.Monad (forM_)
import Data.Text (Text, empty, pack)
import qualified Data.Text as Text

import Test.Hspec
import qualified Data.Text.Zipper as Zipper
import qualified Data.Text.ParagraphLayout.Internal.Zipper as Zipper

sampleText :: Text
sampleText =

M test/Data/Text/ParagraphLayout/ParagraphConstruction.hs => test/Data/Text/ParagraphLayout/ParagraphConstruction.hs +1 -1
@@ 20,7 20,7 @@ import Data.Text.Internal (Text(Text))
import Data.Text.Internal.Lazy (chunk, empty)
import qualified Data.Text.Internal.Lazy as Lazy
import Data.Text.Lazy (toStrict)
import Data.Text.ParagraphLayout.Plain
import Data.Text.ParagraphLayout
    (Paragraph(Paragraph)
    ,ParagraphOptions
    ,Span(Span)

M test/Data/Text/ParagraphLayout/ParagraphData.hs => test/Data/Text/ParagraphLayout/ParagraphData.hs +1 -1
@@ 11,8 11,8 @@ module Data.Text.ParagraphLayout.ParagraphData
    )
where

import Data.Text.ParagraphLayout (Paragraph, ParagraphOptions)
import Data.Text.ParagraphLayout.ParagraphConstruction
import Data.Text.ParagraphLayout.Plain (Paragraph, ParagraphOptions)

emptyParagraph :: ParagraphOptions -> Paragraph
emptyParagraph = "x" |<>| "zzzzzzz"

D test/Data/Text/ParagraphLayout/PlainSpec.hs => test/Data/Text/ParagraphLayout/PlainSpec.hs +0 -142
@@ 1,142 0,0 @@
module Data.Text.ParagraphLayout.PlainSpec (spec) where

import Data.List (intersperse)
import Data.Text.Glyphize (Font)

import Test.Hspec
import Test.Hspec.Golden
import System.FilePath ((</>))
import Data.Text.ParagraphLayout.FontLoader
import Data.Text.ParagraphLayout.Fragment
import Data.Text.ParagraphLayout.LineHeight
import Data.Text.ParagraphLayout.ParagraphData
import Data.Text.ParagraphLayout.Plain

prettyShow :: ParagraphLayout -> String
prettyShow (ParagraphLayout pr sls) = showParagraphLayout where
    showParagraphLayout = concat
        [ "ParagraphLayout {paragraphRect = "
        , show pr
        , ", spanLayouts = ["
        , newline
        , showSpanLayouts
        , newline
        , "]}"
        , newline
        ]
    showSpanLayouts = concat $ intersperse commaNewline $ map showSpanLayout sls
    showSpanLayout (SpanLayout frags) = concat
        [ indent1
        , "SpanLayout ["
        , concat $ intersperse ", " $ map showFrag frags
        , "]"
        ]
    showFrag (Fragment r pen glyphs) = concat
        [ "Fragment {fragmentRect = "
        , show r
        , ", "
        , "fragmentPen = "
        , show pen
        , ", "
        , "fragmentGlyphs ="
        , newline
        , indent2
        , "["
        , showGlyphs glyphs
        , "]"
        , newline
        , indent1
        , "}"
        ]
    showGlyphs = concat . intersperse (commaNewline ++ indent2) . map show
    indent1 = "    "
    indent2 = indent1 ++ indent1
    newline = "\n"
    commaNewline = "," ++ newline

shouldBeGolden :: ParagraphLayout -> FilePath -> Golden ParagraphLayout
shouldBeGolden output_ name = Golden
    { output = output_
    , encodePretty = show
    , writeToFile = \path -> writeFile path . prettyShow
    , readFromFile = \path -> readFile path >>= return . read
    , goldenFile = ".golden" </> name </> "golden"
    , actualFile = Just (".golden" </> name </> "actual")
    , failFirstTime = False
    }

emptyLayout :: ParagraphLayout
emptyLayout = ParagraphLayout (Rect 0 0 0 0) []

emptySpanLayout :: ParagraphLayout
emptySpanLayout = ParagraphLayout (Rect 0 0 0 0) [SpanLayout []]

opts :: Font -> ParagraphOptions
opts font = ParagraphOptions font Normal 8000

spec :: Spec
spec = do
    -- Note: This font does not contain Japanese glyphs.
    describe "layoutPlain" $ do
        describe "with Arabic font" $ before loadPlexSansArabicRegular $ do
            it "wraps filler text at 20em" $ \font -> do
                let
                    result = layoutPlain $ arabicFillerParagraph $
                        (opts font)
                        { paragraphMaxWidth = 20000 }
                result `shouldBeGolden` "arabicFiller20em"
        describe "with Latin font" $ before loadUbuntuRegular $ do
            it "handles input with no spans" $ \font -> do
                let result = layoutPlain $ emptyParagraph $ opts font
                result `shouldBe` emptyLayout
            it "handles one span with no text" $ \font -> do
                let result = layoutPlain $ emptySpanParagraph $ opts font
                result `shouldBe` emptySpanLayout
            it "handles Czech hello" $ \font -> do
                let result = layoutPlain $ czechHelloParagraph $ opts font
                result `shouldBeGolden` "czechHelloParagraph"
            it "handles mixed languages in LTR layout" $ \font -> do
                let result = layoutPlain $ mixedLanguageLTRParagraph $ opts font
                result `shouldBeGolden` "mixedLanguageLTRParagraph"
            it "handles normal line height" $ \font -> do
                let
                    result = layoutPlain $ trivialParagraph $
                        (opts font)
                        { paragraphLineHeight = Normal }
                result `shouldBeGolden` "lineHeightNormal"
            it "handles larger line height" $ \font -> do
                let
                    result = layoutPlain $ trivialParagraph $
                        (opts font)
                        { paragraphLineHeight = Absolute 1600 }
                result `shouldBeGolden` "lineHeightLarger"
            it "handles smaller line height" $ \font -> do
                let
                    result = layoutPlain $ trivialParagraph $
                        (opts font)
                        { paragraphLineHeight = Absolute 599 }
                result `shouldBeGolden` "lineHeightSmaller"
            it "wraps by characters when line is ultra narrow" $ \font -> do
                let
                    result = layoutPlain $ czechHelloParagraph $
                        (opts font)
                        { paragraphMaxWidth = 100 }
                result `shouldBeGolden` "czechHelloParagraphUltraNarrow"
            it "wraps lorem ipsum at 20em" $ \font -> do
                let
                    result = layoutPlain $ loremIpsumParagraph $
                        (opts font)
                        { paragraphMaxWidth = 20000 }
                result `shouldBeGolden` "loremIpsum20em"
            it "wraps lorem ipsum at 100em" $ \font -> do
                let
                    result = layoutPlain $ loremIpsumParagraph $
                        (opts font)
                        { paragraphMaxWidth = 100000 }
                result `shouldBeGolden` "loremIpsum100em"
            it "wraps mixed-script words correctly" $ \font -> do
                let
                    result = layoutPlain $ mixedScriptWordsParagraph $
                        (opts font)
                        { paragraphMaxWidth = 6000 }
                result `shouldBeGolden` "mixedScriptWordsParagraph"

M test/Data/Text/ParagraphLayout/SpanData.hs => test/Data/Text/ParagraphLayout/SpanData.hs +2 -2
@@ 7,8 7,8 @@ where

import Data.Text (pack)
import Data.Text.Glyphize (Font)
import Data.Text.ParagraphLayout.LineHeight (LineHeight(Normal))
import Data.Text.ParagraphLayout.ResolvedSpan (ResolvedSpan(..))
import Data.Text.ParagraphLayout (LineHeight(Normal))
import Data.Text.ParagraphLayout.Internal.ResolvedSpan (ResolvedSpan(..))

emptySpan :: Font -> ResolvedSpan
emptySpan font = ResolvedSpan

M test/Data/Text/ParagraphLayoutSpec.hs => test/Data/Text/ParagraphLayoutSpec.hs +137 -1
@@ 1,6 1,142 @@
module Data.Text.ParagraphLayoutSpec (spec) where

import Data.List (intersperse)
import Data.Text.Glyphize (Font)

import Test.Hspec
import Test.Hspec.Golden
import System.FilePath ((</>))
import Data.Text.ParagraphLayout
import Data.Text.ParagraphLayout.FontLoader
import Data.Text.ParagraphLayout.ParagraphData
import Data.Text.ParagraphLayout.Rect


prettyShow :: ParagraphLayout -> String
prettyShow (ParagraphLayout pr sls) = showParagraphLayout where
    showParagraphLayout = concat
        [ "ParagraphLayout {paragraphRect = "
        , show pr
        , ", spanLayouts = ["
        , newline
        , showSpanLayouts
        , newline
        , "]}"
        , newline
        ]
    showSpanLayouts = concat $ intersperse commaNewline $ map showSpanLayout sls
    showSpanLayout (SpanLayout frags) = concat
        [ indent1
        , "SpanLayout ["
        , concat $ intersperse ", " $ map showFrag frags
        , "]"
        ]
    showFrag (Fragment r pen glyphs) = concat
        [ "Fragment {fragmentRect = "
        , show r
        , ", "
        , "fragmentPen = "
        , show pen
        , ", "
        , "fragmentGlyphs ="
        , newline
        , indent2
        , "["
        , showGlyphs glyphs
        , "]"
        , newline
        , indent1
        , "}"
        ]
    showGlyphs = concat . intersperse (commaNewline ++ indent2) . map show
    indent1 = "    "
    indent2 = indent1 ++ indent1
    newline = "\n"
    commaNewline = "," ++ newline

shouldBeGolden :: ParagraphLayout -> FilePath -> Golden ParagraphLayout
shouldBeGolden output_ name = Golden
    { output = output_
    , encodePretty = show
    , writeToFile = \path -> writeFile path . prettyShow
    , readFromFile = \path -> readFile path >>= return . read
    , goldenFile = ".golden" </> name </> "golden"
    , actualFile = Just (".golden" </> name </> "actual")
    , failFirstTime = False
    }

emptyLayout :: ParagraphLayout
emptyLayout = ParagraphLayout (Rect 0 0 0 0) []

emptySpanLayout :: ParagraphLayout
emptySpanLayout = ParagraphLayout (Rect 0 0 0 0) [SpanLayout []]

opts :: Font -> ParagraphOptions
opts font = ParagraphOptions font Normal 8000

spec :: Spec
spec = return ()
spec = do
    -- Note: This font does not contain Japanese glyphs.
    describe "layoutPlain" $ do
        describe "with Arabic font" $ before loadPlexSansArabicRegular $ do
            it "wraps filler text at 20em" $ \font -> do
                let
                    result = layoutPlain $ arabicFillerParagraph $
                        (opts font)
                        { paragraphMaxWidth = 20000 }
                result `shouldBeGolden` "arabicFiller20em"
        describe "with Latin font" $ before loadUbuntuRegular $ do
            it "handles input with no spans" $ \font -> do
                let result = layoutPlain $ emptyParagraph $ opts font
                result `shouldBe` emptyLayout
            it "handles one span with no text" $ \font -> do
                let result = layoutPlain $ emptySpanParagraph $ opts font
                result `shouldBe` emptySpanLayout
            it "handles Czech hello" $ \font -> do
                let result = layoutPlain $ czechHelloParagraph $ opts font
                result `shouldBeGolden` "czechHelloParagraph"
            it "handles mixed languages in LTR layout" $ \font -> do
                let result = layoutPlain $ mixedLanguageLTRParagraph $ opts font
                result `shouldBeGolden` "mixedLanguageLTRParagraph"
            it "handles normal line height" $ \font -> do
                let
                    result = layoutPlain $ trivialParagraph $
                        (opts font)
                        { paragraphLineHeight = Normal }
                result `shouldBeGolden` "lineHeightNormal"
            it "handles larger line height" $ \font -> do
                let
                    result = layoutPlain $ trivialParagraph $
                        (opts font)
                        { paragraphLineHeight = Absolute 1600 }
                result `shouldBeGolden` "lineHeightLarger"
            it "handles smaller line height" $ \font -> do
                let
                    result = layoutPlain $ trivialParagraph $
                        (opts font)
                        { paragraphLineHeight = Absolute 599 }
                result `shouldBeGolden` "lineHeightSmaller"
            it "wraps by characters when line is ultra narrow" $ \font -> do
                let
                    result = layoutPlain $ czechHelloParagraph $
                        (opts font)
                        { paragraphMaxWidth = 100 }
                result `shouldBeGolden` "czechHelloParagraphUltraNarrow"
            it "wraps lorem ipsum at 20em" $ \font -> do
                let
                    result = layoutPlain $ loremIpsumParagraph $
                        (opts font)
                        { paragraphMaxWidth = 20000 }
                result `shouldBeGolden` "loremIpsum20em"
            it "wraps lorem ipsum at 100em" $ \font -> do
                let
                    result = layoutPlain $ loremIpsumParagraph $
                        (opts font)
                        { paragraphMaxWidth = 100000 }
                result `shouldBeGolden` "loremIpsum100em"
            it "wraps mixed-script words correctly" $ \font -> do
                let
                    result = layoutPlain $ mixedScriptWordsParagraph $
                        (opts font)
                        { paragraphMaxWidth = 6000 }
                result `shouldBeGolden` "mixedScriptWordsParagraph"