~jaro/balkon

e2944b4d2ba4dce2e447dc32505597c0cd0519b6 — Jaro 1 year, 7 months ago 993ff05
Fix style: white space in exports and imports.
M lib/Data/Text/ParagraphLayout.hs => lib/Data/Text/ParagraphLayout.hs +21 -21
@@ 13,29 13,29 @@
--
-- Y coordinates increase from bottom to top.
module Data.Text.ParagraphLayout
    (Fragment(Fragment, fragmentPen, fragmentRect, fragmentGlyphs)
    ,LineHeight(Absolute, Normal)
    ,PageContinuity(Break, Continue)
    ,PageOptions
        (PageOptions
        ,pageCurrentHeight
        ,pageNextHeight
        ,pageOrphans
        ,pageWidows
    ( Fragment (Fragment, fragmentPen, fragmentRect, fragmentGlyphs)
    , LineHeight (Absolute, Normal)
    , PageContinuity (Break, Continue)
    , PageOptions
        ( PageOptions
        , pageCurrentHeight
        , pageNextHeight
        , pageOrphans
        , pageWidows
        )
    ,Paragraph(Paragraph)
    ,ParagraphLayout(ParagraphLayout, paragraphRect, spanLayouts)
    ,ParagraphOptions
        (ParagraphOptions
        ,paragraphFont
        ,paragraphLineHeight
        ,paragraphMaxWidth
    , Paragraph (Paragraph)
    , ParagraphLayout (ParagraphLayout, paragraphRect, spanLayouts)
    , ParagraphOptions
        ( ParagraphOptions
        , paragraphFont
        , paragraphLineHeight
        , paragraphMaxWidth
        )
    ,Span(Span, spanLength, spanOptions)
    ,SpanLayout(SpanLayout)
    ,SpanOptions(SpanOptions, spanLanguage)
    ,layoutPlain
    ,paginate
    , Span (Span, spanLength, spanOptions)
    , SpanLayout (SpanLayout)
    , SpanOptions (SpanOptions, spanLanguage)
    , layoutPlain
    , paginate
    )
where


M lib/Data/Text/ParagraphLayout/ParagraphConstruction.hs => lib/Data/Text/ParagraphLayout/ParagraphConstruction.hs +4 -4
@@ 10,10 10,10 @@
--
-- > "ignored prefix" |<>| "ignored suffix"
module Data.Text.ParagraphLayout.ParagraphConstruction
    ((>|)
    ,(>|<)
    ,(|<)
    ,(|<>|)
    ( (>|)
    , (>|<)
    , (|<)
    , (|<>|)
    )
where


M lib/Data/Text/ParagraphLayout/Rect.hs => lib/Data/Text/ParagraphLayout/Rect.hs +9 -9
@@ 1,15 1,15 @@
-- | 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, x_origin, y_origin, x_size, y_size)
    ,height
    ,width
    ,x_max
    ,x_min
    ,x_terminus
    ,y_max
    ,y_min
    ,y_terminus
    ( Rect (Rect, x_origin, y_origin, x_size, y_size)
    , height
    , width
    , x_max
    , x_min
    , x_terminus
    , y_max
    , y_min
    , y_terminus
    )
where


M src/Data/Text/ParagraphLayout/Internal/Break.hs => src/Data/Text/ParagraphLayout/Internal/Break.hs +10 -10
@@ 6,22 6,22 @@
-- `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.Internal.Break
    (LineBreak(..)
    ,locale
    ,breaksDesc
    ,subOffsetsDesc
    ( LineBreak (..)
    , locale
    , breaksDesc
    , subOffsetsDesc
    )
where

import Data.Text (Text)
import Data.Text.Foreign (lengthWord8)
import Data.Text.ICU
    (Break
    ,Breaker
    ,LocaleName(Locale)
    ,breaksRight
    ,brkPrefix
    ,brkStatus
    ( Break
    , Breaker
    , LocaleName (Locale)
    , breaksRight
    , brkPrefix
    , brkStatus
    )

-- | Strictness levels of line-breaking rules,

M src/Data/Text/ParagraphLayout/Internal/Fragment.hs => src/Data/Text/ParagraphLayout/Internal/Fragment.hs +3 -3
@@ 1,7 1,7 @@
module Data.Text.ParagraphLayout.Internal.Fragment
    (Fragment(..)
    ,ShapedRun
    ,shapedRun)
    ( Fragment (..)
    , ShapedRun
    , shapedRun)
where

import Data.Int (Int32)

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

import Data.Int (Int32)

M src/Data/Text/ParagraphLayout/Internal/LinePagination.hs => src/Data/Text/ParagraphLayout/Internal/LinePagination.hs +6 -6
@@ 12,17 12,17 @@
--   (Preceding context may limit the space available on the given page, but it
--   is assumed that the space on every following page can be used in full.)
module Data.Text.ParagraphLayout.Internal.LinePagination
    (Line
    ,lineHeight
    ,PageContinuity(Break, Continue)
    ,bestSplit
    ,paginateLines
    ( Line
    , lineHeight
    , PageContinuity (Break, Continue)
    , bestSplit
    , paginateLines
    )
where

import Data.Int (Int32)
import Data.List (dropWhileEnd, genericLength)
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.List.NonEmpty (NonEmpty ((:|)))
import qualified Data.List.NonEmpty as NonEmpty

-- | Representation of a line of text with a known height.

M src/Data/Text/ParagraphLayout/Internal/Paginable.hs => src/Data/Text/ParagraphLayout/Internal/Paginable.hs +3 -3
@@ 1,7 1,7 @@
module Data.Text.ParagraphLayout.Internal.Paginable
    (PageOptions(..)
    ,Paginable
    ,paginate
    ( PageOptions (..)
    , Paginable
    , paginate
    )
where


M src/Data/Text/ParagraphLayout/Internal/Paragraph.hs => src/Data/Text/ParagraphLayout/Internal/Paragraph.hs +2 -2
@@ 1,6 1,6 @@
module Data.Text.ParagraphLayout.Internal.Paragraph
    (Paragraph(..)
    ,ParagraphOptions(..)
    ( Paragraph (..)
    , ParagraphOptions (..)
    )
where


M src/Data/Text/ParagraphLayout/Internal/ParagraphConstruction.hs => src/Data/Text/ParagraphLayout/Internal/ParagraphConstruction.hs +8 -8
@@ 1,22 1,22 @@
module Data.Text.ParagraphLayout.Internal.ParagraphConstruction
    ((>|)
    ,(>|<)
    ,(|<)
    ,(|<>|)
    ( (>|)
    , (>|<)
    , (|<)
    , (|<>|)
    )
where

import Data.Text (pack)
import Data.Text.Foreign (lengthWord8)
import Data.Text.Internal (Text(Text))
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.Internal.Plain
    (Paragraph(Paragraph)
    ,ParagraphOptions
    ( Paragraph (Paragraph)
    , ParagraphOptions
    )
import Data.Text.ParagraphLayout.Internal.Span (Span(Span), SpanOptions)
import Data.Text.ParagraphLayout.Internal.Span (Span (Span), SpanOptions)

-- | Create first span with optional ignored suffix.
infixr 5 >|

M src/Data/Text/ParagraphLayout/Internal/ParagraphLayout.hs => src/Data/Text/ParagraphLayout/Internal/ParagraphLayout.hs +11 -11
@@ 1,15 1,15 @@
module Data.Text.ParagraphLayout.Internal.ParagraphLayout
    (ParagraphLayout(..)
    ,appendFragments
    ,emptyParagraphLayout
    ,filterFragments
    ,mapFragments
    ,paragraphFragments
    ,paragraphLayout
    ,paragraphOriginX
    ,paragraphOriginY
    ,paragraphSpanBounds
    ,shapedRuns
    ( ParagraphLayout (..)
    , appendFragments
    , emptyParagraphLayout
    , filterFragments
    , mapFragments
    , paragraphFragments
    , paragraphLayout
    , paragraphOriginX
    , paragraphOriginY
    , paragraphSpanBounds
    , shapedRuns
    )
where


M src/Data/Text/ParagraphLayout/Internal/Plain.hs => src/Data/Text/ParagraphLayout/Internal/Plain.hs +19 -19
@@ 1,32 1,32 @@
module Data.Text.ParagraphLayout.Internal.Plain
    (Paragraph(..)
    ,ParagraphLayout(..)
    ,ParagraphOptions(..)
    ,SpanLayout(..)
    ,layoutPlain
    ( Paragraph (..)
    , ParagraphLayout (..)
    , ParagraphOptions (..)
    , SpanLayout (..)
    , layoutPlain
    )
where

import Control.Applicative (ZipList(ZipList), getZipList)
import Control.Applicative (ZipList (ZipList), getZipList)
import Data.Int (Int32)
import Data.List (mapAccumL)
import Data.List.NonEmpty (NonEmpty((:|)), nonEmpty, (<|))
import Data.List.NonEmpty (NonEmpty ((:|)), nonEmpty, (<|))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Text.Foreign (lengthWord8)
import Data.Text.Glyphize
    (Buffer(..)
    ,ContentType(ContentTypeUnicode)
    ,Direction(..)
    ,FontExtents(..)
    ,GlyphInfo
    ,GlyphPos
    ,defaultBuffer
    ,fontExtentsForDir
    ,shape
    ( Buffer (..)
    , ContentType (ContentTypeUnicode)
    , Direction (..)
    , FontExtents (..)
    , GlyphInfo
    , GlyphPos
    , defaultBuffer
    , fontExtentsForDir
    , shape
    )
import Data.Text.ICU (Breaker, LocaleName, breakCharacter, breakLine)
import qualified Data.Text.ICU as BreakStatus (Line(Hard))
import Data.Text.Internal (Text(Text))
import qualified Data.Text.ICU as BreakStatus (Line (Hard))
import Data.Text.Internal (Text (Text))
import qualified Data.Text.Lazy as Lazy

import Data.Text.ParagraphLayout.Internal.Break


@@ 36,7 36,7 @@ import Data.Text.ParagraphLayout.Internal.Paragraph
import Data.Text.ParagraphLayout.Internal.ParagraphLayout
import qualified Data.Text.ParagraphLayout.Internal.ProtoFragment as PF
import Data.Text.ParagraphLayout.Internal.Rect
import Data.Text.ParagraphLayout.Internal.ResolvedSpan (WithSpan(WithSpan))
import Data.Text.ParagraphLayout.Internal.ResolvedSpan (WithSpan (WithSpan))
import qualified Data.Text.ParagraphLayout.Internal.ResolvedSpan as RS
import Data.Text.ParagraphLayout.Internal.Run
import Data.Text.ParagraphLayout.Internal.Span

M src/Data/Text/ParagraphLayout/Internal/ProtoFragment.hs => src/Data/Text/ParagraphLayout/Internal/ProtoFragment.hs +3 -3
@@ 1,11 1,11 @@
module Data.Text.ParagraphLayout.Internal.ProtoFragment
    (ProtoFragment(direction, advance, glyphs)
    ,protoFragmentH
    ( ProtoFragment (direction, advance, glyphs)
    , protoFragmentH
    )
where

import Data.Int (Int32)
import Data.Text.Glyphize (Direction, GlyphInfo, GlyphPos(x_advance))
import Data.Text.Glyphize (Direction, GlyphInfo, GlyphPos (x_advance))

-- | A box fragment which has not been positioned yet.
data ProtoFragment = ProtoFragment

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


M src/Data/Text/ParagraphLayout/Internal/ResolvedSpan.hs => src/Data/Text/ParagraphLayout/Internal/ResolvedSpan.hs +3 -3
@@ 1,7 1,7 @@
module Data.Text.ParagraphLayout.Internal.ResolvedSpan
    (ResolvedSpan(..)
    ,WithSpan(WithSpan)
    ,splitBySpanIndex
    ( ResolvedSpan (..)
    , WithSpan (WithSpan)
    , splitBySpanIndex
    )
where


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

import Data.List (mapAccumL)
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Text.Foreign (dropWord8, lengthWord8, takeWord8)
import Data.Text.Glyphize (Direction(..))
import Data.Text.Glyphize (Direction (..))
import qualified Data.Text.ICU.Char as ICUChar

import Data.Text.ParagraphLayout.Internal.ResolvedSpan

M src/Data/Text/ParagraphLayout/Internal/Span.hs => src/Data/Text/ParagraphLayout/Internal/Span.hs +5 -5
@@ 1,9 1,9 @@
module Data.Text.ParagraphLayout.Internal.Span
    (Span(..)
    ,SpanLayout(..)
    ,SpanOptions(..)
    ,spanFragments
    ,spanRects
    ( Span (..)
    , SpanLayout (..)
    , SpanOptions (..)
    , spanFragments
    , spanRects
    )
where


M src/Data/Text/ParagraphLayout/Internal/TextContainer.hs => src/Data/Text/ParagraphLayout/Internal/TextContainer.hs +12 -12
@@ 1,20 1,20 @@
module Data.Text.ParagraphLayout.Internal.TextContainer
    (SeparableTextContainer
    ,TextContainer
    ,dropWhileEnd
    ,dropWhileStart
    ,getText
    ,splitTextAt8
    ,splitTextsBy
    ,trimTextsEnd
    ,trimTextsEndPreserve
    ,trimTextsStart
    ,trimTextsStartPreserve
    ( SeparableTextContainer
    , TextContainer
    , dropWhileEnd
    , dropWhileStart
    , getText
    , splitTextAt8
    , splitTextsBy
    , trimTextsEnd
    , trimTextsEndPreserve
    , trimTextsStart
    , trimTextsStartPreserve
    )
where

import Data.Foldable (toList)
import Data.List.NonEmpty (NonEmpty((:|)), nonEmpty)
import Data.List.NonEmpty (NonEmpty ((:|)), nonEmpty)
import qualified Data.List.NonEmpty as NonEmpty
import Data.Maybe (catMaybes)
import Data.Text (Text)

M src/Data/Text/ParagraphLayout/Internal/Zipper.hs => src/Data/Text/ParagraphLayout/Internal/Zipper.hs +24 -24
@@ 3,35 3,35 @@
-- All measurements are in UTF-8 code points, each of which can be between
-- 1 and 4 bytes long (inclusive).
module Data.Text.ParagraphLayout.Internal.Zipper
    (Zipper(preceding, following)
    ,advanceBy
    ,atEnd
    ,atStart
    ,next
    ,recombine
    ,splitAt
    ,start
    ,step
    ( Zipper (preceding, following)
    , advanceBy
    , atEnd
    , atStart
    , next
    , recombine
    , splitAt
    , start
    , step
    )
where

import Data.Text (measureOff, null, uncons)
import Data.Text.Internal (Text(Text), empty)
import Data.Text.Internal (Text (Text), empty)
import Prelude
    (Bool
    ,Char
    ,Eq
    ,Int
    ,Maybe(Just, Nothing)
    ,Show
    ,fmap
    ,fst
    ,otherwise
    ,(+)
    ,(-)
    ,(.)
    ,(<=)
    ,(>=)
    ( Bool
    , Char
    , Eq
    , Int
    , Maybe (Just, Nothing)
    , Show
    , fmap
    , fst
    , otherwise
    , (+)
    , (-)
    , (.)
    , (<=)
    , (>=)
    )

-- | Represents a body of text with a read cursor which can be moved forward.

M test/Data/Text/ParagraphLayout/FontLoader.hs => test/Data/Text/ParagraphLayout/FontLoader.hs +13 -13
@@ 1,22 1,22 @@
module Data.Text.ParagraphLayout.FontLoader
    (arabicFont
    ,devanagariFont
    ,latinFont
    ,loadFont
    ,writeFontInfo
    ( arabicFont
    , devanagariFont
    , latinFont
    , loadFont
    , writeFontInfo
    )
where

import Data.ByteString (readFile)
import Data.Text.Glyphize
    (Font
    ,FontOptions
    ,createFace
    ,createFontWithOptions
    ,faceIndex
    ,fontFace
    ,fontPPEm
    ,fontScale
    ( Font
    , FontOptions
    , createFace
    , createFontWithOptions
    , faceIndex
    , fontFace
    , fontPPEm
    , fontScale
    )
import Data.Word (Word)
import Prelude (concat, return, show, ($), (++))

M test/Data/Text/ParagraphLayout/Internal/BreakSpec.hs => test/Data/Text/ParagraphLayout/Internal/BreakSpec.hs +6 -6
@@ 3,13 3,13 @@ module Data.Text.ParagraphLayout.Internal.BreakSpec (spec) where
import Control.Monad (forM_)
import Data.Text (empty, pack, singleton)
import Data.Text.ICU
    (LocaleName(Locale)
    ,breakCharacter
    ,breakLine
    ,breakSentence
    ,breakWord
    ( LocaleName (Locale)
    , breakCharacter
    , breakLine
    , breakSentence
    , breakWord
    )
import qualified Data.Text.ICU as BreakStatus (Line(..), Word(..))
import qualified Data.Text.ICU as BreakStatus (Line (..), Word (..))

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

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

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

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

M test/Data/Text/ParagraphLayout/ParagraphData.hs => test/Data/Text/ParagraphLayout/ParagraphData.hs +19 -19
@@ 1,26 1,26 @@
module Data.Text.ParagraphLayout.ParagraphData
    (arabicFillerParagraph
    ,czechHelloParagraph
    ,devanagariAccentParagraph
    ,devanagariParagraph
    ,devanagariPrefixedAccentParagraph
    ,emptyParagraph
    ,emptySpanParagraph
    ,hardBreaksLTRParagraph
    ,hardBreaksRTLParagraph
    ,ligatureParagraph
    ,loremIpsumParagraph
    ,manySpacesParagraph
    ,mixedLanguageLTRParagraph
    ,mixedScriptSerbianParagraph
    ,mixedScriptWordsParagraph
    ,spannedArabicFillerParagraph
    ,spannedLoremIpsumParagraph
    ,trivialParagraph
    ( arabicFillerParagraph
    , czechHelloParagraph
    , devanagariAccentParagraph
    , devanagariParagraph
    , devanagariPrefixedAccentParagraph
    , emptyParagraph
    , emptySpanParagraph
    , hardBreaksLTRParagraph
    , hardBreaksRTLParagraph
    , ligatureParagraph
    , loremIpsumParagraph
    , manySpacesParagraph
    , mixedLanguageLTRParagraph
    , mixedScriptSerbianParagraph
    , mixedScriptWordsParagraph
    , spannedArabicFillerParagraph
    , spannedLoremIpsumParagraph
    , trivialParagraph
    )
where

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

-- | Span with text in the Czech language.

M test/Data/Text/ParagraphLayout/SpanData.hs => test/Data/Text/ParagraphLayout/SpanData.hs +5 -5
@@ 1,14 1,14 @@
module Data.Text.ParagraphLayout.SpanData
    (emptySpan
    ,czechHello
    ,serbianMixedScript
    ( emptySpan
    , czechHello
    , serbianMixedScript
    )
where

import Data.Text (pack)
import Data.Text.Glyphize (Font)
import Data.Text.ParagraphLayout (LineHeight(Normal))
import Data.Text.ParagraphLayout.Internal.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 +3 -3
@@ 1,9 1,9 @@
module Data.Text.ParagraphLayoutSpec (spec) where

import Data.Text.Glyphize
    (Font
    ,FontOptions(optionPPEm, optionScale)
    ,defaultFontOptions
    ( Font
    , FontOptions (optionPPEm, optionScale)
    , defaultFontOptions
    )

import Test.Hspec