{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Graphics.PDF.Typesetting.Breaking (
Letter(..)
, formatList
, infinity
, createGlyph
, kernBox
, glueBox
, penalty
, spaceGlueBox
, hyphenPenalty
, splitText
, MaybeGlue(..)
, defaultBreakingSettings
, BRState(..)
, glueSize
, mkLetter
, spaceWidth
, centeredDilatationFactor
, leftDilatationFactor
, rightDilatationFactor
, dilatationRatio
, badness
, bigAdjustRatio
, Justification(..)
, simplify
) where
import Graphics.PDF.LowLevel.Types
import Data.List(minimumBy)
import qualified Data.Map.Strict as M
import Graphics.PDF.Text
import Graphics.PDF.Typesetting.Box
import Data.Maybe(fromJust)
import Graphics.PDF.Fonts.Font hiding(fontSize)
import Graphics.PDF.Typesetting.WritingSystem
import qualified Data.Text as T(Text)
import qualified Text.Hyphenation as H
data Justification = FullJustification
| Centered
| LeftJustification
| RightJustification
deriving(Justification -> Justification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Justification -> Justification -> Bool
$c/= :: Justification -> Justification -> Bool
== :: Justification -> Justification -> Bool
$c== :: Justification -> Justification -> Bool
Eq)
mkLetter :: (Show a, Box a, DisplayableBox a) => BoxDimension
-> Maybe s
-> a
-> Letter s
mkLetter :: forall a s.
(Show a, Box a, DisplayableBox a) =>
BoxDimension -> Maybe s -> a -> Letter s
mkLetter BoxDimension
d Maybe s
s a
a = forall s. BoxDimension -> AnyBox -> Maybe s -> Letter s
Letter BoxDimension
d (forall a. (Show a, Box a, DisplayableBox a) => a -> AnyBox
AnyBox a
a) Maybe s
s
data Letter s = Letter BoxDimension !AnyBox !(Maybe s)
| Glue !PDFFloat !PDFFloat !PDFFloat !(Maybe s)
| FlaggedPenalty !PDFFloat !Int !s
| Penalty !Int
| AGlyph !s !GlyphCode !PDFFloat
| Kern !PDFFloat !(Maybe s)
class MaybeGlue a where
glueY :: a -> PDFFloat
glueZ :: a -> PDFFloat
glueSizeWithRatio :: a -> PDFFloat -> PDFFloat
instance MaybeGlue (Letter s) where
glueSizeWithRatio :: Letter s -> PDFFloat -> PDFFloat
glueSizeWithRatio = forall s. Letter s -> PDFFloat -> PDFFloat
letterWidth
glueY :: Letter s -> PDFFloat
glueY (Glue PDFFloat
_ PDFFloat
y PDFFloat
_ Maybe s
_) = PDFFloat
y
glueY Letter s
_ = PDFFloat
0
glueZ :: Letter s -> PDFFloat
glueZ (Glue PDFFloat
_ PDFFloat
_ PDFFloat
z Maybe s
_) = PDFFloat
z
glueZ Letter s
_ = PDFFloat
0
glueSize :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize PDFFloat
w PDFFloat
y PDFFloat
z PDFFloat
r =
if PDFFloat
r forall a. Ord a => a -> a -> Bool
>= PDFFloat
0
then
PDFFloat
rforall a. Num a => a -> a -> a
*PDFFloat
y forall a. Num a => a -> a -> a
+ PDFFloat
w
else
PDFFloat
rforall a. Num a => a -> a -> a
*PDFFloat
z forall a. Num a => a -> a -> a
+ PDFFloat
w
letterWidth :: Letter s
-> PDFFloat
-> PDFFloat
letterWidth :: forall s. Letter s -> PDFFloat -> PDFFloat
letterWidth (AGlyph s
_ GlyphCode
_ PDFFloat
w) PDFFloat
_ = PDFFloat
w
letterWidth (Letter BoxDimension
dim AnyBox
_ Maybe s
_) PDFFloat
_ = forall a. Box a => a -> PDFFloat
boxWidth BoxDimension
dim
letterWidth (Glue PDFFloat
w PDFFloat
yi PDFFloat
zi Maybe s
_) PDFFloat
r = PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize PDFFloat
w PDFFloat
yi PDFFloat
zi PDFFloat
r
letterWidth (FlaggedPenalty PDFFloat
_ Int
_ s
_) PDFFloat
_ = PDFFloat
0
letterWidth (Penalty Int
_) PDFFloat
_ = PDFFloat
0
letterWidth (Kern PDFFloat
w Maybe s
_) PDFFloat
_ = PDFFloat
w
instance Show (Letter s) where
show :: Letter s -> String
show (Letter BoxDimension
_ AnyBox
a Maybe s
_) = String
"(Letter " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show AnyBox
a forall a. [a] -> [a] -> [a]
++ String
")"
show (Glue PDFFloat
a PDFFloat
b PDFFloat
c Maybe s
_) = String
"(Glue " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show PDFFloat
a forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show PDFFloat
b forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show PDFFloat
c forall a. [a] -> [a] -> [a]
++ String
")"
show (FlaggedPenalty PDFFloat
a Int
b s
_) = String
"(FlaggedPenalty " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show PDFFloat
a forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
b forall a. [a] -> [a] -> [a]
++ String
")"
show (Penalty Int
a) = String
"(Penalty " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
a forall a. [a] -> [a] -> [a]
++ String
")"
show (AGlyph s
_ GlyphCode
t PDFFloat
_) = String
"(Glyph " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show GlyphCode
t forall a. [a] -> [a] -> [a]
++ String
")"
show (Kern PDFFloat
_ Maybe s
_) = String
"(Kern)"
type CB a = (PDFFloat,PDFFloat,PDFFloat,Int,a)
class PointedBox s a | a -> s where
isFlagged :: a -> Bool
getPenalty :: a -> Int
isPenalty :: a -> Bool
letter :: a -> Letter s
position :: a -> Int
cumulatedW :: a -> PDFFloat
cumulatedY :: a -> PDFFloat
cumulatedZ :: a -> PDFFloat
isForcedBreak :: a -> Bool
instance PointedBox s (PDFFloat,PDFFloat,PDFFloat,Int,Letter s) where
isFlagged :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Bool
isFlagged (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
_ s
_) = Bool
True
isFlagged (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
_ = Bool
False
isPenalty :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Bool
isPenalty (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
_ s
_) = Bool
True
isPenalty (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Penalty Int
_) = Bool
True
isPenalty (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
_ = Bool
False
getPenalty :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Int
getPenalty (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
p s
_) = Int
p
getPenalty (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Penalty Int
p) = Int
p
getPenalty (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
_ = Int
0
letter :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Letter s
letter (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Letter s
a) = Letter s
a
position :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Int
position (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
p,Letter s
_) = Int
p
cumulatedW :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> PDFFloat
cumulatedW (PDFFloat
w,PDFFloat
_,PDFFloat
_,Int
_,Letter s
_) = PDFFloat
w
cumulatedY :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> PDFFloat
cumulatedY (PDFFloat
_,PDFFloat
y,PDFFloat
_,Int
_,Letter s
_) = PDFFloat
y
cumulatedZ :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> PDFFloat
cumulatedZ (PDFFloat
_,PDFFloat
_,PDFFloat
z,Int
_,Letter s
_) = PDFFloat
z
isForcedBreak :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Bool
isForcedBreak (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
p s
_) = Int
p forall a. Ord a => a -> a -> Bool
<= (-Int
infinity)
isForcedBreak (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Penalty Int
p) = Int
p forall a. Ord a => a -> a -> Bool
<= (-Int
infinity)
isForcedBreak (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
_ = Bool
False
instance PointedBox s (ZList s) where
isPenalty :: ZList s -> Bool
isPenalty (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> Bool
isPenalty (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
isFlagged :: ZList s -> Bool
isFlagged (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> Bool
isFlagged (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
letter :: ZList s -> Letter s
letter (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> Letter s
letter (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
position :: ZList s -> Int
position (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> Int
position (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
cumulatedW :: ZList s -> PDFFloat
cumulatedW (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> PDFFloat
cumulatedW (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
cumulatedY :: ZList s -> PDFFloat
cumulatedY (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> PDFFloat
cumulatedY (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
cumulatedZ :: ZList s -> PDFFloat
cumulatedZ (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> PDFFloat
cumulatedZ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
getPenalty :: ZList s -> Int
getPenalty (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> Int
getPenalty (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
isForcedBreak :: ZList s -> Bool
isForcedBreak (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b [Letter s]
_) = forall s a. PointedBox s a => a -> Bool
isForcedBreak (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
penaltyWidth :: Letter s -> PDFFloat
penaltyWidth :: forall s. Letter s -> PDFFloat
penaltyWidth (FlaggedPenalty PDFFloat
w Int
_ s
_) = PDFFloat
w
penaltyWidth Letter s
_ = PDFFloat
0
data BreakNode =
BreakNode { BreakNode -> PDFFloat
totalWidth :: !PDFFloat
, BreakNode -> PDFFloat
totalDilatation :: !PDFFloat
, BreakNode -> PDFFloat
totalCompression :: !PDFFloat
, BreakNode -> PDFFloat
demerit :: !PDFFloat
, BreakNode -> Bool
flagged :: !Bool
, BreakNode -> Int
fitnessValue :: !Int
, BreakNode -> PDFFloat
ratio :: !PDFFloat
, BreakNode -> Maybe (Int, Int, Int, BreakNode)
previous :: Maybe (Int,Int,Int,BreakNode)
}
deriving(Int -> BreakNode -> ShowS
[BreakNode] -> ShowS
BreakNode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BreakNode] -> ShowS
$cshowList :: [BreakNode] -> ShowS
show :: BreakNode -> String
$cshow :: BreakNode -> String
showsPrec :: Int -> BreakNode -> ShowS
$cshowsPrec :: Int -> BreakNode -> ShowS
Show)
dilatationRatio :: PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
dilatationRatio :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
dilatationRatio PDFFloat
maxw PDFFloat
w PDFFloat
y PDFFloat
z =
if PDFFloat
w forall a. Eq a => a -> a -> Bool
== PDFFloat
maxw
then PDFFloat
0.0
else if PDFFloat
w forall a. Ord a => a -> a -> Bool
< PDFFloat
maxw
then
if PDFFloat
y forall a. Ord a => a -> a -> Bool
> PDFFloat
0.0 then ((PDFFloat
maxw forall a. Num a => a -> a -> a
- PDFFloat
w) forall a. Fractional a => a -> a -> a
/ PDFFloat
y) else PDFFloat
bigAdjustRatio
else
if PDFFloat
z forall a. Ord a => a -> a -> Bool
> PDFFloat
0.0 then ((PDFFloat
maxw forall a. Num a => a -> a -> a
- PDFFloat
w) forall a. Fractional a => a -> a -> a
/ PDFFloat
z) else PDFFloat
bigAdjustRatio
adjustRatio :: BreakNode
-> ZList s
-> PDFFloat
-> PDFFloat
adjustRatio :: forall s. BreakNode -> ZList s -> PDFFloat -> PDFFloat
adjustRatio BreakNode
a ZList s
l PDFFloat
maxw =
let w :: PDFFloat
w = forall s a. PointedBox s a => a -> PDFFloat
cumulatedW ZList s
l forall a. Num a => a -> a -> a
- BreakNode -> PDFFloat
totalWidth BreakNode
a forall a. Num a => a -> a -> a
+ forall s. Letter s -> PDFFloat
penaltyWidth (forall s a. PointedBox s a => a -> Letter s
letter ZList s
l)
y :: PDFFloat
y = forall s a. PointedBox s a => a -> PDFFloat
cumulatedY ZList s
l forall a. Num a => a -> a -> a
- BreakNode -> PDFFloat
totalDilatation BreakNode
a
z :: PDFFloat
z = forall s a. PointedBox s a => a -> PDFFloat
cumulatedZ ZList s
l forall a. Num a => a -> a -> a
- BreakNode -> PDFFloat
totalCompression BreakNode
a
in
PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
dilatationRatio PDFFloat
maxw PDFFloat
w PDFFloat
y PDFFloat
z
badness :: PDFFloat -> PDFFloat
badness :: PDFFloat -> PDFFloat
badness PDFFloat
r = if PDFFloat
r forall a. Ord a => a -> a -> Bool
< (-PDFFloat
1) then PDFFloat
bigAdjustRatio else PDFFloat
100.0 forall a. Num a => a -> a -> a
* forall a. Num a => a -> a
abs(PDFFloat
r)forall a. Floating a => a -> a -> a
**PDFFloat
3.0
fitness :: PDFFloat -> Int
fitness :: PDFFloat -> Int
fitness PDFFloat
r =
if PDFFloat
r forall a. Ord a => a -> a -> Bool
< (-PDFFloat
0.5)
then
Int
0
else if PDFFloat
r forall a. Ord a => a -> a -> Bool
<= (-PDFFloat
0.5)
then
Int
1
else
if PDFFloat
r forall a. Ord a => a -> a -> Bool
<= PDFFloat
1
then
Int
2
else
Int
3
data BRState = BRState { BRState -> PDFFloat
firstPassTolerance :: !PDFFloat
, BRState -> PDFFloat
secondPassTolerance :: !PDFFloat
, BRState -> Int
hyphenPenaltyValue :: !Int
, BRState -> PDFFloat
fitness_demerit :: !PDFFloat
, BRState -> PDFFloat
flagged_demerit :: !PDFFloat
, BRState -> PDFFloat
line_penalty :: !PDFFloat
, BRState -> Justification
centered :: !Justification
, BRState -> WritingSystem
writingSystem :: !WritingSystem
}
defaultBreakingSettings :: BRState
defaultBreakingSettings :: BRState
defaultBreakingSettings = PDFFloat
-> PDFFloat
-> Int
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Justification
-> WritingSystem
-> BRState
BRState PDFFloat
100 PDFFloat
100 Int
50 PDFFloat
1000 PDFFloat
1000 PDFFloat
10 Justification
FullJustification (Hyphenator -> WritingSystem
Latin Hyphenator
H.english_US)
computeDemerit :: Bool
-> BRState
-> Bool
-> PDFFloat
-> BreakNode
-> ZList s
-> Maybe(PDFFloat,Int)
computeDemerit :: forall s.
Bool
-> BRState
-> Bool
-> PDFFloat
-> BreakNode
-> ZList s
-> Maybe (PDFFloat, Int)
computeDemerit Bool
force BRState
settings Bool
sndPass PDFFloat
r BreakNode
a ZList s
z =
let b :: PDFFloat
b = PDFFloat -> PDFFloat
badness PDFFloat
r
p :: Int
p = forall s a. PointedBox s a => a -> Int
getPenalty ZList s
z
fitness' :: Int
fitness' = PDFFloat -> Int
fitness PDFFloat
r
tolerance :: PDFFloat
tolerance = if Bool
sndPass then (BRState -> PDFFloat
secondPassTolerance BRState
settings) else (BRState -> PDFFloat
firstPassTolerance BRState
settings)
in
if (PDFFloat
b forall a. Ord a => a -> a -> Bool
<= PDFFloat
tolerance) Bool -> Bool -> Bool
|| Bool
force
then
let fld :: PDFFloat
fld = if forall s a. PointedBox s a => a -> Bool
isFlagged ZList s
z Bool -> Bool -> Bool
&& (BreakNode -> Bool
flagged BreakNode
a) then (BRState -> PDFFloat
flagged_demerit BRState
settings) else PDFFloat
0.0
fid :: PDFFloat
fid = if Int
fitness' forall a. Eq a => a -> a -> Bool
/= (BreakNode -> Int
fitnessValue BreakNode
a) then (BRState -> PDFFloat
fitness_demerit BRState
settings) else PDFFloat
0.0
dem :: PDFFloat
dem = forall a. Ord a => a -> a -> a
max PDFFloat
1000.0 forall a b. (a -> b) -> a -> b
$ if Int
p forall a. Ord a => a -> a -> Bool
>= Int
0
then
PDFFloat
fid forall a. Num a => a -> a -> a
+ PDFFloat
fld forall a. Num a => a -> a -> a
+ ((BRState -> PDFFloat
line_penalty BRState
settings) forall a. Num a => a -> a -> a
+ PDFFloat
b) forall a. Floating a => a -> a -> a
** PDFFloat
2.0 forall a. Num a => a -> a -> a
+ (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
p) forall a. Floating a => a -> a -> a
** PDFFloat
2.0
else if Int
p forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
p forall a. Ord a => a -> a -> Bool
> (-Int
infinity)
then
PDFFloat
fid forall a. Num a => a -> a -> a
+ PDFFloat
fld forall a. Num a => a -> a -> a
+ ((BRState -> PDFFloat
line_penalty BRState
settings) forall a. Num a => a -> a -> a
+ PDFFloat
b) forall a. Floating a => a -> a -> a
** PDFFloat
2.0 forall a. Num a => a -> a -> a
- (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
p)forall a. Floating a => a -> a -> a
**PDFFloat
2.0
else
PDFFloat
fid forall a. Num a => a -> a -> a
+ PDFFloat
fld forall a. Num a => a -> a -> a
+ ((BRState -> PDFFloat
line_penalty BRState
settings) forall a. Num a => a -> a -> a
+ PDFFloat
b) forall a. Floating a => a -> a -> a
** PDFFloat
2.0
in
forall a. a -> Maybe a
Just (PDFFloat
dem,Int
fitness')
else
forall a. Maybe a
Nothing
data MaybeCB a = NoCB
| OneCB !(CB a)
deriving(Int -> MaybeCB a -> ShowS
forall a. Show a => Int -> MaybeCB a -> ShowS
forall a. Show a => [MaybeCB a] -> ShowS
forall a. Show a => MaybeCB a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaybeCB a] -> ShowS
$cshowList :: forall a. Show a => [MaybeCB a] -> ShowS
show :: MaybeCB a -> String
$cshow :: forall a. Show a => MaybeCB a -> String
showsPrec :: Int -> MaybeCB a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> MaybeCB a -> ShowS
Show)
data ZList s = ZList (MaybeCB (Letter s)) (PDFFloat,PDFFloat,PDFFloat,Int,Letter s) [Letter s] deriving(Int -> ZList s -> ShowS
forall s. Int -> ZList s -> ShowS
forall s. [ZList s] -> ShowS
forall s. ZList s -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ZList s] -> ShowS
$cshowList :: forall s. [ZList s] -> ShowS
show :: ZList s -> String
$cshow :: forall s. ZList s -> String
showsPrec :: Int -> ZList s -> ShowS
$cshowsPrec :: forall s. Int -> ZList s -> ShowS
Show)
createZList :: [Letter s] -> ZList s
createZList :: forall s. [Letter s] -> ZList s
createZList [] = forall a. HasCallStack => String -> a
error String
"List cannot be empty to create a zipper"
createZList [Letter s]
l = forall s.
MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
ZList forall a. MaybeCB a
NoCB (PDFFloat
0,PDFFloat
0,PDFFloat
0,Int
1,forall a. [a] -> a
head [Letter s]
l) (forall a. [a] -> [a]
tail [Letter s]
l)
theEnd :: ZList s -> Bool
theEnd :: forall s. ZList s -> Bool
theEnd (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
_ []) = Bool
True
theEnd ZList s
_ = Bool
False
createBreaknode :: Maybe (Int,Int,Int,BreakNode) -> ZList s -> BreakNode
createBreaknode :: forall s. Maybe (Int, Int, Int, BreakNode) -> ZList s -> BreakNode
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
_ s
_) []) = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
True ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Penalty Int
_) []) = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
False ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Glue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe s
_) []) = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
False ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Letter s
_) []) = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
False ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
p s
_) [Letter s]
_) | Int
p forall a. Ord a => a -> a -> Bool
<= Int
infinity = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
True ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Letter BoxDimension
_ AnyBox
_ Maybe s
_) [Letter s]
_) = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
False ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,AGlyph s
_ GlyphCode
_ PDFFloat
_) [Letter s]
_) = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
False ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev a :: ZList s
a@(ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Kern PDFFloat
_ Maybe s
_) [Letter s]
_) = forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
False ZList s
a
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev ZList s
z =
let BreakNode PDFFloat
a PDFFloat
b PDFFloat
c PDFFloat
d Bool
_ Int
e PDFFloat
f Maybe (Int, Int, Int, BreakNode)
g = forall s. Maybe (Int, Int, Int, BreakNode) -> ZList s -> BreakNode
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev (forall s. ZList s -> ZList s
moveRight ZList s
z) in
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Bool
-> Int
-> PDFFloat
-> Maybe (Int, Int, Int, BreakNode)
-> BreakNode
BreakNode PDFFloat
a PDFFloat
b PDFFloat
c PDFFloat
d Bool
False Int
e PDFFloat
f Maybe (Int, Int, Int, BreakNode)
g
breakN :: Maybe (Int,Int,Int,BreakNode) -> Bool -> ZList s -> BreakNode
breakN :: forall s.
Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
breakN Maybe (Int, Int, Int, BreakNode)
prev Bool
t ZList s
a = let (PDFFloat
w,PDFFloat
y,PDFFloat
z) = forall s. ZList s -> BoxDimension
getDim ZList s
a in PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Bool
-> Int
-> PDFFloat
-> Maybe (Int, Int, Int, BreakNode)
-> BreakNode
BreakNode PDFFloat
w PDFFloat
y PDFFloat
z PDFFloat
0.0 Bool
t Int
0 PDFFloat
0.0 Maybe (Int, Int, Int, BreakNode)
prev
getDim :: ZList s -> (PDFFloat,PDFFloat,PDFFloat)
getDim :: forall s. ZList s -> BoxDimension
getDim (ZList MaybeCB (Letter s)
_ (PDFFloat
w,PDFFloat
y,PDFFloat
z,Int
_,Letter BoxDimension
_ AnyBox
_ Maybe s
_) [Letter s]
_) = (PDFFloat
w,PDFFloat
y,PDFFloat
z)
getDim (ZList MaybeCB (Letter s)
_ (PDFFloat
w,PDFFloat
y,PDFFloat
z,Int
_,AGlyph s
_ GlyphCode
_ PDFFloat
_) [Letter s]
_) = (PDFFloat
w,PDFFloat
y,PDFFloat
z)
getDim (ZList MaybeCB (Letter s)
_ (PDFFloat
w,PDFFloat
y,PDFFloat
z,Int
_,Kern PDFFloat
_ Maybe s
_) [Letter s]
_) = (PDFFloat
w,PDFFloat
y,PDFFloat
z)
getDim (ZList MaybeCB (Letter s)
_ (PDFFloat
w,PDFFloat
y,PDFFloat
z,Int
_,Letter s
_) []) = (PDFFloat
w,PDFFloat
y,PDFFloat
z)
getDim ZList s
a = if forall s. ZList s -> Bool
theEnd ZList s
a then forall a. HasCallStack => String -> a
error String
"Can't find end of paragraph" else forall s. ZList s -> BoxDimension
getDim (forall s. ZList s -> ZList s
moveRight ZList s
a)
moveRight :: ZList s -> ZList s
moveRight :: forall s. ZList s -> ZList s
moveRight (ZList MaybeCB (Letter s)
_ c :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
c@(PDFFloat
w,PDFFloat
y,PDFFloat
z,Int
p,Glue PDFFloat
w' PDFFloat
y' PDFFloat
z' Maybe s
_) [Letter s]
r) =
let w'' :: PDFFloat
w'' = PDFFloat
w forall a. Num a => a -> a -> a
+ PDFFloat
w'
y'' :: PDFFloat
y''=PDFFloat
yforall a. Num a => a -> a -> a
+PDFFloat
y'
z'' :: PDFFloat
z''=PDFFloat
zforall a. Num a => a -> a -> a
+PDFFloat
z'
in
forall s.
MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
ZList (forall a. CB a -> MaybeCB a
OneCB (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
c) (PDFFloat
w'',PDFFloat
y'',PDFFloat
z'',Int
pforall a. Num a => a -> a -> a
+Int
1,forall a. [a] -> a
head [Letter s]
r) (forall a. [a] -> [a]
tail [Letter s]
r)
moveRight (ZList MaybeCB (Letter s)
_ c :: (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
c@(PDFFloat
w,PDFFloat
y,PDFFloat
z,Int
p,Letter s
a) [Letter s]
r) =
let w' :: PDFFloat
w' = forall a. MaybeGlue a => a -> PDFFloat -> PDFFloat
glueSizeWithRatio Letter s
a PDFFloat
0.0
w'' :: PDFFloat
w'' = PDFFloat
w forall a. Num a => a -> a -> a
+ PDFFloat
w'
in
forall s.
MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
ZList (forall a. CB a -> MaybeCB a
OneCB (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
c) (PDFFloat
w'',PDFFloat
y,PDFFloat
z,Int
pforall a. Num a => a -> a -> a
+Int
1,forall a. [a] -> a
head [Letter s]
r) (forall a. [a] -> [a]
tail [Letter s]
r)
isFeasibleBreakpoint :: Bool
-> ZList s
-> Bool
isFeasibleBreakpoint :: forall s. Bool -> ZList s -> Bool
isFeasibleBreakpoint Bool
True (ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
p s
_) [Letter s]
_) = Int
p forall a. Ord a => a -> a -> Bool
< Int
infinity
isFeasibleBreakpoint Bool
False (ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
_ s
_) [Letter s]
_) = Bool
False
isFeasibleBreakpoint Bool
_ (ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Penalty Int
p) [Letter s]
_) = Int
p forall a. Ord a => a -> a -> Bool
< Int
infinity
isFeasibleBreakpoint Bool
_ (ZList MaybeCB (Letter s)
NoCB (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
_ [Letter s]
_) = Bool
False
isFeasibleBreakpoint Bool
_ (ZList (OneCB (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Letter BoxDimension
_ AnyBox
_ Maybe s
_)) (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Glue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe s
_) [Letter s]
_) = Bool
True
isFeasibleBreakpoint Bool
_ (ZList (OneCB (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,AGlyph s
_ GlyphCode
_ PDFFloat
_)) (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Glue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe s
_) [Letter s]
_) = Bool
True
isFeasibleBreakpoint Bool
_ ZList s
_ = Bool
False
type PossibleBreak = ActiveNodes
type ActiveNodes = M.Map (Int,Int,Int) BreakNode
updateBreak :: BreakNode
-> BreakNode
-> BreakNode
updateBreak :: BreakNode -> BreakNode -> BreakNode
updateBreak BreakNode
a BreakNode
b = if BreakNode -> PDFFloat
demerit BreakNode
a forall a. Ord a => a -> a -> Bool
< BreakNode -> PDFFloat
demerit BreakNode
b then BreakNode
a else BreakNode
b
updateWithNewRIfNoSolution :: Bool
-> PDFFloat
-> ZList s
-> (Int,Int,Int)
-> PossibleBreak
-> ActiveNodes
-> (Bool -> PDFFloat -> ActiveNodes -> (PossibleBreak,ActiveNodes))
-> (PossibleBreak,ActiveNodes)
updateWithNewRIfNoSolution :: forall s.
Bool
-> PDFFloat
-> ZList s
-> (Int, Int, Int)
-> PossibleBreak
-> PossibleBreak
-> (Bool
-> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak))
-> (PossibleBreak, PossibleBreak)
updateWithNewRIfNoSolution Bool
sndPass PDFFloat
r ZList s
z (Int, Int, Int)
key PossibleBreak
newbreak PossibleBreak
newmap Bool -> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak)
f =
if forall s a. PointedBox s a => a -> Bool
isForcedBreak ZList s
z
then
Bool -> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak)
f Bool
True PDFFloat
r (forall k a. Ord k => k -> Map k a -> Map k a
M.delete (Int, Int, Int)
key PossibleBreak
newmap)
else
if PDFFloat
r forall a. Ord a => a -> a -> Bool
< -PDFFloat
1
then let m' :: PossibleBreak
m' = forall k a. Ord k => k -> Map k a -> Map k a
M.delete (Int, Int, Int)
key PossibleBreak
newmap
in
if forall k a. Map k a -> Bool
M.null PossibleBreak
m' Bool -> Bool -> Bool
&& Bool
sndPass then Bool -> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak)
f Bool
True (-PDFFloat
0.99) PossibleBreak
m' else (PossibleBreak
newbreak,PossibleBreak
m')
else
Bool -> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak)
f Bool
False PDFFloat
r PossibleBreak
newmap
getNewActiveBreakpoints :: BRState -> Bool -> (Int -> PDFFloat) -> ActiveNodes -> ZList s -> (PossibleBreak,ActiveNodes)
getNewActiveBreakpoints :: forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> (PossibleBreak, PossibleBreak)
getNewActiveBreakpoints BRState
settings Bool
sndPass Int -> PDFFloat
fmaxw PossibleBreak
actives ZList s
z =
if forall s. Bool -> ZList s -> Bool
isFeasibleBreakpoint Bool
sndPass ZList s
z
then
let analyzeActive :: (Int, Int, Int)
-> BreakNode
-> (PossibleBreak, PossibleBreak)
-> (PossibleBreak, PossibleBreak)
analyzeActive key :: (Int, Int, Int)
key@(Int
p,Int
line,Int
f) BreakNode
b (PossibleBreak
newbreak,PossibleBreak
newmap') =
let r' :: PDFFloat
r' = forall s. BreakNode -> ZList s -> PDFFloat -> PDFFloat
adjustRatio BreakNode
b ZList s
z (Int -> PDFFloat
fmaxw (Int
lineforall a. Num a => a -> a -> a
+Int
1))
in
forall s.
Bool
-> PDFFloat
-> ZList s
-> (Int, Int, Int)
-> PossibleBreak
-> PossibleBreak
-> (Bool
-> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak))
-> (PossibleBreak, PossibleBreak)
updateWithNewRIfNoSolution Bool
sndPass PDFFloat
r' ZList s
z (Int, Int, Int)
key PossibleBreak
newbreak PossibleBreak
newmap' forall a b. (a -> b) -> a -> b
$
\Bool
force PDFFloat
r PossibleBreak
newmap -> let dem' :: Maybe (PDFFloat, Int)
dem' = forall s.
Bool
-> BRState
-> Bool
-> PDFFloat
-> BreakNode
-> ZList s
-> Maybe (PDFFloat, Int)
computeDemerit Bool
force BRState
settings Bool
sndPass PDFFloat
r BreakNode
b ZList s
z in
case Maybe (PDFFloat, Int)
dem' of
Maybe (PDFFloat, Int)
Nothing -> (PossibleBreak
newbreak,PossibleBreak
newmap)
Just (PDFFloat
d',Int
f') ->
let b' :: BreakNode
b' = forall s. Maybe (Int, Int, Int, BreakNode) -> ZList s -> BreakNode
createBreaknode (forall a. a -> Maybe a
Just (Int
p,Int
line,Int
f,BreakNode
b)) ZList s
z in
(forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
M.insertWith BreakNode -> BreakNode -> BreakNode
updateBreak (forall s a. PointedBox s a => a -> Int
position ZList s
z,Int
lineforall a. Num a => a -> a -> a
+Int
1,Int
f') (BreakNode
b' {demerit :: PDFFloat
demerit = PDFFloat
d',fitnessValue :: Int
fitnessValue = Int
f', ratio :: PDFFloat
ratio = PDFFloat
r}) PossibleBreak
newbreak ,PossibleBreak
newmap)
in
let (PossibleBreak
breaks',PossibleBreak
actives') = forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
M.foldrWithKey (Int, Int, Int)
-> BreakNode
-> (PossibleBreak, PossibleBreak)
-> (PossibleBreak, PossibleBreak)
analyzeActive (forall k a. Map k a
M.empty,PossibleBreak
actives) PossibleBreak
actives
dmin :: PDFFloat
dmin = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map BreakNode -> PDFFloat
demerit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [a]
M.elems forall a b. (a -> b) -> a -> b
$ PossibleBreak
breaks'
nbreaks :: PossibleBreak
nbreaks = forall a k. (a -> Bool) -> Map k a -> Map k a
M.filter (\BreakNode
x -> BreakNode -> PDFFloat
demerit BreakNode
x forall a. Ord a => a -> a -> Bool
< PDFFloat
dmin forall a. Num a => a -> a -> a
+ (BRState -> PDFFloat
fitness_demerit BRState
settings)) PossibleBreak
breaks'
in
if forall k a. Map k a -> Bool
M.null PossibleBreak
nbreaks
then
(PossibleBreak
breaks' , PossibleBreak
actives')
else
(PossibleBreak
nbreaks , PossibleBreak
actives')
else
(forall k a. Map k a
M.empty,PossibleBreak
actives )
genNodeList :: (Int,Int,Int,BreakNode) -> [(PDFFloat,Int,Bool)]
genNodeList :: (Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)]
genNodeList (Int
p,Int
_,Int
_,b :: BreakNode
b@(BreakNode PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ Bool
f Int
_ PDFFloat
_ Maybe (Int, Int, Int, BreakNode)
Nothing)) = [(BreakNode -> PDFFloat
ratio BreakNode
b,Int
p,Bool
f)]
genNodeList (Int
p,Int
_,Int
_,b :: BreakNode
b@(BreakNode PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ Bool
f Int
_ PDFFloat
_ (Just (Int, Int, Int, BreakNode)
_))) = (BreakNode -> PDFFloat
ratio BreakNode
b,Int
p,Bool
f)forall a. a -> [a] -> [a]
:(Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)]
genNodeList (forall a. HasCallStack => Maybe a -> a
fromJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. BreakNode -> Maybe (Int, Int, Int, BreakNode)
previous forall a b. (a -> b) -> a -> b
$ BreakNode
b)
analyzeBoxes :: BRState -> Bool -> (Int -> PDFFloat) -> ActiveNodes -> ZList s -> ZList s -> [(PDFFloat,Int,Bool)]
analyzeBoxes :: forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
analyzeBoxes BRState
settings Bool
pass Int -> PDFFloat
fmaxw PossibleBreak
actives ZList s
lastz ZList s
z =
let getMinBreak :: Map (a, b, c) BreakNode -> (a, b, c, BreakNode)
getMinBreak Map (a, b, c) BreakNode
b' = (\((a
xc,b
yc,c
zc),BreakNode
w) -> (a
xc,b
yc,c
zc,BreakNode
w)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
minimumBy (\((a, b, c)
_,BreakNode
a) ((a, b, c)
_,BreakNode
b) -> forall a. Ord a => a -> a -> Ordering
compare (BreakNode -> PDFFloat
demerit BreakNode
a) (BreakNode -> PDFFloat
demerit BreakNode
b)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
M.toList forall a b. (a -> b) -> a -> b
$ Map (a, b, c) BreakNode
b'
(PossibleBreak
breaks',PossibleBreak
actives') = forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> (PossibleBreak, PossibleBreak)
getNewActiveBreakpoints BRState
settings Bool
pass Int -> PDFFloat
fmaxw PossibleBreak
actives ZList s
z
newActives :: PossibleBreak
newActives = forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union (PossibleBreak
breaks') (PossibleBreak
actives')
getRightOrderNodeList :: (Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)]
getRightOrderNodeList = forall a. [a] -> [a]
tail forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)]
genNodeList
getKey :: (a, b, c, d) -> (a, b, c)
getKey (a
a,b
b,c
c,d
_) = (a
a,b
b,c
c)
getNode :: (a, b, c, BreakNode) -> BreakNode
getNode (a
_,b
_,c
_,BreakNode PDFFloat
a PDFFloat
b PDFFloat
c PDFFloat
d Bool
e Int
f PDFFloat
r Maybe (Int, Int, Int, BreakNode)
_) = PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Bool
-> Int
-> PDFFloat
-> Maybe (Int, Int, Int, BreakNode)
-> BreakNode
BreakNode PDFFloat
a PDFFloat
b PDFFloat
c PDFFloat
d Bool
e Int
f PDFFloat
r forall a. Maybe a
Nothing
in
if forall k a. Map k a -> Bool
M.null PossibleBreak
actives'
then
if forall k a. Map k a -> Bool
M.null PossibleBreak
breaks'
then
if Bool -> Bool
not Bool
pass
then
forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
analyzeBoxes BRState
settings Bool
True Int -> PDFFloat
fmaxw PossibleBreak
actives ZList s
lastz ZList s
lastz
else
forall a. HasCallStack => String -> a
error String
"Second pass analysis failed ! Generally due to wrong width in the text area or an end of text before end of paragraph detected"
else
let minBreak :: (Int, Int, Int, BreakNode)
minBreak = forall {a} {b} {c}. Map (a, b, c) BreakNode -> (a, b, c, BreakNode)
getMinBreak PossibleBreak
breaks'
someNewBreaks :: [(PDFFloat, Int, Bool)]
someNewBreaks = (Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)]
getRightOrderNodeList (Int, Int, Int, BreakNode)
minBreak
in
if forall s. ZList s -> Bool
theEnd ZList s
z
then
[(PDFFloat, Int, Bool)]
someNewBreaks
else
let z' :: ZList s
z' = forall s. ZList s -> ZList s
moveRight ZList s
z in
[(PDFFloat, Int, Bool)]
someNewBreaks forall a. [a] -> [a] -> [a]
++ forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
analyzeBoxes BRState
settings Bool
pass Int -> PDFFloat
fmaxw (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (forall {a} {b} {c} {d}. (a, b, c, d) -> (a, b, c)
getKey (Int, Int, Int, BreakNode)
minBreak) (forall {a} {b} {c}. (a, b, c, BreakNode) -> BreakNode
getNode (Int, Int, Int, BreakNode)
minBreak) forall k a. Map k a
M.empty) ZList s
z' ZList s
z'
else
if forall k a. Map k a -> Bool
M.null PossibleBreak
breaks'
then
if forall s. ZList s -> Bool
theEnd ZList s
z
then
forall a. HasCallStack => String -> a
error String
"End of text found but no paragraph end detected"
else
forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
analyzeBoxes BRState
settings Bool
pass Int -> PDFFloat
fmaxw PossibleBreak
actives' ZList s
lastz (forall s. ZList s -> ZList s
moveRight ZList s
z)
else
if forall s. ZList s -> Bool
theEnd ZList s
z
then
let minBreak :: (Int, Int, Int, BreakNode)
minBreak = forall {a} {b} {c}. Map (a, b, c) BreakNode -> (a, b, c, BreakNode)
getMinBreak PossibleBreak
breaks' in
(Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)]
getRightOrderNodeList (Int, Int, Int, BreakNode)
minBreak
else
forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
analyzeBoxes BRState
settings Bool
pass Int -> PDFFloat
fmaxw PossibleBreak
newActives ZList s
lastz (forall s. ZList s -> ZList s
moveRight ZList s
z)
hyphenBox :: Style s => s -> Letter s
hyphenBox :: forall s. Style s => s -> Letter s
hyphenBox s
s =
let PDFFont AnyFont
f Int
fontSize = TextStyle -> PDFFont
textFont forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s
maybeHyphen :: Maybe GlyphCode
maybeHyphen = forall f. IsFont f => f -> Maybe GlyphCode
hyphenGlyph AnyFont
f
in
case Maybe GlyphCode
maybeHyphen of
Just GlyphCode
h -> forall s. s -> GlyphCode -> PDFFloat -> Letter s
AGlyph s
s GlyphCode
h (forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
h)
Maybe GlyphCode
Nothing -> forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
0 forall a. Maybe a
Nothing
cutList :: Style s => Justification -> [Letter s] -> Int -> [(PDFFloat,Int,Bool)] -> [(PDFFloat,[Letter s],[Letter s])]
cutList :: forall s.
Style s =>
Justification
-> [Letter s]
-> Int
-> [(PDFFloat, Int, Bool)]
-> [(PDFFloat, [Letter s], [Letter s])]
cutList Justification
_ [] Int
_ [(PDFFloat, Int, Bool)]
_ = []
cutList Justification
_ [Letter s]
t Int
_ [] = [(PDFFloat
0.0,[],[Letter s]
t)]
cutList Justification
j [Letter s]
t Int
c ((PDFFloat
ra,Int
ba,Bool
fa):[(PDFFloat, Int, Bool)]
l) =
let ([Letter s]
theLine,[Letter s]
t') = forall a. Int -> [a] -> ([a], [a])
splitAt (Int
baforall a. Num a => a -> a -> a
-Int
c) [Letter s]
t
in
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Letter s]
theLine
then
[]
else
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Letter s]
t'
then
[(PDFFloat
ra,[Letter s]
theLine,[Letter s]
t)]
else
case forall a. [a] -> a
head [Letter s]
t' of
FlaggedPenalty PDFFloat
_ Int
_ s
s -> if Bool -> Bool
not Bool
fa
then
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Breakpoint marked as not flagged but detected as flagged ! Send a bug report ! " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (PDFFloat
ra,Int
ba,Bool
fa)
else
(PDFFloat
ra,[Letter s]
theLine forall a. [a] -> [a] -> [a]
++ forall s. Style s => Justification -> s -> [Letter s]
hyphenForJustification Justification
j s
s,[Letter s]
t) forall a. a -> [a] -> [a]
: forall s.
Style s =>
Justification
-> [Letter s]
-> Int
-> [(PDFFloat, Int, Bool)]
-> [(PDFFloat, [Letter s], [Letter s])]
cutList Justification
j [Letter s]
t' Int
ba [(PDFFloat, Int, Bool)]
l
Letter s
_ -> if Bool
fa
then
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Breakpoint marked as flagged but detected as not flagged ! Send a bug report ! " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (PDFFloat
ra,Int
ba,Bool
fa) forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show [Letter s]
theLine forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show [Letter s]
t'
else
(PDFFloat
ra,[Letter s]
theLine,[Letter s]
t) forall a. a -> [a] -> [a]
: forall s.
Style s =>
Justification
-> [Letter s]
-> Int
-> [(PDFFloat, Int, Bool)]
-> [(PDFFloat, [Letter s], [Letter s])]
cutList Justification
j [Letter s]
t' Int
ba [(PDFFloat, Int, Bool)]
l
formatList :: Style s => BRState -> (Int -> PDFFloat) -> [Letter s] -> [(PDFFloat,[Letter s],[Letter s])]
formatList :: forall s.
Style s =>
BRState
-> (Int -> PDFFloat)
-> [Letter s]
-> [(PDFFloat, [Letter s], [Letter s])]
formatList BRState
settings Int -> PDFFloat
maxw [Letter s]
boxes =
let active :: PossibleBreak
active = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Int
0,Int
0,Int
1) (PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Bool
-> Int
-> PDFFloat
-> Maybe (Int, Int, Int, BreakNode)
-> BreakNode
BreakNode PDFFloat
0 PDFFloat
0 PDFFloat
0 PDFFloat
0 Bool
False Int
0 PDFFloat
0.0 forall a. Maybe a
Nothing) forall k a. Map k a
M.empty
z :: ZList s
z = forall s. [Letter s] -> ZList s
createZList [Letter s]
boxes
theBreaks :: [(PDFFloat, Int, Bool)]
theBreaks = forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
analyzeBoxes BRState
settings Bool
False Int -> PDFFloat
maxw PossibleBreak
active ZList s
z ZList s
z
in
forall s.
Style s =>
Justification
-> [Letter s]
-> Int
-> [(PDFFloat, Int, Bool)]
-> [(PDFFloat, [Letter s], [Letter s])]
cutList (BRState -> Justification
centered BRState
settings) [Letter s]
boxes Int
1 [(PDFFloat, Int, Bool)]
theBreaks
infinity :: Int
infinity :: Int
infinity = Int
10000
bigAdjustRatio :: PDFFloat
bigAdjustRatio :: PDFFloat
bigAdjustRatio = PDFFloat
10000.0
glueBox :: Maybe s
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Letter s
glueBox :: forall s. Maybe s -> PDFFloat -> PDFFloat -> PDFFloat -> Letter s
glueBox Maybe s
s PDFFloat
w PDFFloat
y PDFFloat
z = forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
w PDFFloat
y PDFFloat
z Maybe s
s
spaceWidth :: Style s => s
-> PDFFloat
spaceWidth :: forall s. Style s => s -> PDFFloat
spaceWidth s
s =
let PDFFont AnyFont
f Int
fontSize = (TextStyle -> PDFFont
textFont forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s)
ws :: PDFFloat
ws = forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize (forall f. IsFont f => f -> GlyphCode
spaceGlyph AnyFont
f)
h :: PDFFloat
h = TextStyle -> PDFFloat
scaleSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s
in
PDFFloat
ws forall a. Num a => a -> a -> a
* PDFFloat
h
centeredDilatationFactor :: PDFFloat
centeredDilatationFactor :: PDFFloat
centeredDilatationFactor = PDFFloat
10.0
leftDilatationFactor :: PDFFloat
leftDilatationFactor :: PDFFloat
leftDilatationFactor = PDFFloat
20.0
rightDilatationFactor :: PDFFloat
rightDilatationFactor :: PDFFloat
rightDilatationFactor = PDFFloat
20.0
spaceGlueBox :: Style s => BRState
-> s
-> PDFFloat
-> [Letter s]
spaceGlueBox :: forall s. Style s => BRState -> s -> PDFFloat -> [Letter s]
spaceGlueBox BRState
settings s
s PDFFloat
f =
let ws :: PDFFloat
ws = forall s. Style s => s -> PDFFloat
spaceWidth s
s
h :: PDFFloat
h = TextStyle -> PDFFloat
scaleSpace forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s
sy :: PDFFloat
sy = TextStyle -> PDFFloat
scaleDilatation forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s
sz :: PDFFloat
sz = TextStyle -> PDFFloat
scaleCompression forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s
normalW :: PDFFloat
normalW = PDFFloat
ws forall a. Num a => a -> a -> a
* PDFFloat
h
in
case (BRState -> Justification
centered BRState
settings) of
Justification
FullJustification -> [forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue (PDFFloat
normalW) (PDFFloat
normalWforall a. Num a => a -> a -> a
*PDFFloat
syforall a. Fractional a => a -> a -> a
/PDFFloat
2.0forall a. Num a => a -> a -> a
*PDFFloat
f) (PDFFloat
normalWforall a. Num a => a -> a -> a
*PDFFloat
szforall a. Fractional a => a -> a -> a
/PDFFloat
3.0) (forall a. a -> Maybe a
Just s
s)]
Justification
Centered -> [ forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
centeredDilatationFactorforall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
, forall s. Int -> Letter s
Penalty Int
0
, forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue (PDFFloat
normalW) (-PDFFloat
2forall a. Num a => a -> a -> a
*PDFFloat
centeredDilatationFactorforall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
, forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
, forall s. Int -> Letter s
Penalty Int
infinity
, forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
centeredDilatationFactorforall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
]
Justification
LeftJustification -> [ forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
leftDilatationFactorforall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
, forall s. Int -> Letter s
Penalty Int
0
, forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
normalW (-PDFFloat
leftDilatationFactorforall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
]
Justification
RightJustification -> [ forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
normalW (-PDFFloat
rightDilatationFactorforall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
, forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
, forall s. Int -> Letter s
Penalty Int
infinity
, forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
rightDilatationFactorforall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)
]
simplify :: [Letter s]
-> [Letter s]
simplify :: forall s. [Letter s] -> [Letter s]
simplify [] = []
simplify ((Glue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe s
_):[Letter s]
l) = forall s. [Letter s] -> [Letter s]
simplify [Letter s]
l
simplify ((FlaggedPenalty PDFFloat
_ Int
_ s
_):[Letter s]
l) = forall s. [Letter s] -> [Letter s]
simplify [Letter s]
l
simplify ((Penalty Int
_):[Letter s]
l) = forall s. [Letter s] -> [Letter s]
simplify [Letter s]
l
simplify [Letter s]
l = [Letter s]
l
hyphenForJustification :: Style s => Justification -> s -> [Letter s]
hyphenForJustification :: forall s. Style s => Justification -> s -> [Letter s]
hyphenForJustification Justification
Centered s
s = [forall s. Style s => s -> Letter s
hyphenBox s
s,forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
centeredDilatationFactorforall a. Num a => a -> a -> a
*forall s. Style s => s -> PDFFloat
spaceWidth s
s) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)]
hyphenForJustification Justification
LeftJustification s
s = [forall s. Style s => s -> Letter s
hyphenBox s
s,forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
leftDilatationFactorforall a. Num a => a -> a -> a
*forall s. Style s => s -> PDFFloat
spaceWidth s
s) PDFFloat
0 (forall a. a -> Maybe a
Just s
s)]
hyphenForJustification Justification
_ s
s = [forall s. Style s => s -> Letter s
hyphenBox s
s]
penalty :: Int
-> Letter s
penalty :: forall s. Int -> Letter s
penalty Int
p = forall s. Int -> Letter s
Penalty Int
p
createGlyph :: s
-> GlyphCode
-> PDFFloat
-> Letter s
createGlyph :: forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
c PDFFloat
w = forall s. s -> GlyphCode -> PDFFloat -> Letter s
AGlyph s
s GlyphCode
c PDFFloat
w
ripText :: Style s
=> s
-> BRState
-> [SpecialChar]
-> [Letter s]
ripText :: forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
_ BRState
_ [] = []
ripText s
s BRState
settings (NormalChar Char
ca:SpecialChar
BreakingHyphen:NormalChar Char
cb:[SpecialChar]
l) =
let PDFFont AnyFont
f Int
fontSize = (TextStyle -> PDFFont
textFont forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s)
ga :: GlyphCode
ga = forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
ca
gb :: GlyphCode
gb = forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
cb
oldKerning :: PDFFloat
oldKerning = forall f.
IsFont f =>
f -> Int -> GlyphCode -> GlyphCode -> PDFFloat
getKern AnyFont
f Int
fontSize GlyphCode
ga GlyphCode
gb
la :: Letter s
la = forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
ga ((forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
ga) forall a. Num a => a -> a -> a
+ PDFFloat
oldKerning)
lb :: Letter s
lb = forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
gb (forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
gb)
maybeH :: Maybe GlyphCode
maybeH = forall f. IsFont f => f -> Maybe GlyphCode
hyphenGlyph AnyFont
f
in
case Maybe GlyphCode
maybeH of
Maybe GlyphCode
Nothing -> Letter s
laforall a. a -> [a] -> [a]
:Letter s
lbforall a. a -> [a] -> [a]
:forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
Just GlyphCode
h ->
let newKerning :: PDFFloat
newKerning = forall f.
IsFont f =>
f -> Int -> GlyphCode -> GlyphCode -> PDFFloat
getKern AnyFont
f Int
fontSize GlyphCode
ga GlyphCode
h
w :: PDFFloat
w = forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
h forall a. Num a => a -> a -> a
- PDFFloat
oldKerning forall a. Num a => a -> a -> a
+ PDFFloat
newKerning
in
Letter s
laforall a. a -> [a] -> [a]
:forall s. BRState -> s -> PDFFloat -> Letter s
hyphenPenalty BRState
settings s
s PDFFloat
wforall a. a -> [a] -> [a]
:Letter s
lbforall a. a -> [a] -> [a]
:forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
ripText s
s BRState
settings (NormalChar Char
ca:NormalChar Char
cb:[SpecialChar]
l) =
let PDFFont AnyFont
f Int
fontSize = (TextStyle -> PDFFont
textFont forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s)
ga :: GlyphCode
ga = forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
ca
gb :: GlyphCode
gb = forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
cb
k :: PDFFloat
k = forall f.
IsFont f =>
f -> Int -> GlyphCode -> GlyphCode -> PDFFloat
getKern AnyFont
f Int
fontSize GlyphCode
ga GlyphCode
gb
la :: Letter s
la = forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
ga ((forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
ga) forall a. Num a => a -> a -> a
+ PDFFloat
k)
lb :: Letter s
lb = forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
gb (forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
gb)
in
Letter s
laforall a. a -> [a] -> [a]
:Letter s
lbforall a. a -> [a] -> [a]
:forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
ripText s
s BRState
settings (SpecialChar
NormalSpace:[SpecialChar]
l) = (forall s. Style s => BRState -> s -> PDFFloat -> [Letter s]
spaceGlueBox BRState
settings s
s PDFFloat
1.0) forall a. [a] -> [a] -> [a]
++ forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
ripText s
s BRState
settings (SpecialChar
BiggerSpace:[SpecialChar]
l) = (forall s. Style s => BRState -> s -> PDFFloat -> [Letter s]
spaceGlueBox BRState
settings s
s PDFFloat
2.0) forall a. [a] -> [a] -> [a]
++ forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
ripText s
s BRState
settings (SpecialChar
BreakingHyphen:[SpecialChar]
l) = forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
ripText s
s BRState
settings (NormalChar Char
c:[SpecialChar]
l) =
let PDFFont AnyFont
f Int
fontSize = (TextStyle -> PDFFont
textFont forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Style a => a -> TextStyle
textStyle forall a b. (a -> b) -> a -> b
$ s
s)
g :: GlyphCode
g = forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
c
in
forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
g (forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
g) forall a. a -> [a] -> [a]
:forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
splitText :: Style s => BRState -> s -> T.Text -> [Letter s]
splitText :: forall s. Style s => BRState -> s -> Text -> [Letter s]
splitText BRState
settings s
f Text
t =
let w :: WritingSystem
w = BRState -> WritingSystem
writingSystem BRState
settings
special :: [SpecialChar]
special = WritingSystem -> Text -> [SpecialChar]
mapToSpecialGlyphs WritingSystem
w Text
t
in
forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
f BRState
settings [SpecialChar]
special
hyphenPenalty :: BRState
-> s
-> PDFFloat
-> Letter s
hyphenPenalty :: forall s. BRState -> s -> PDFFloat -> Letter s
hyphenPenalty BRState
settings s
s PDFFloat
w = forall s. PDFFloat -> Int -> s -> Letter s
FlaggedPenalty PDFFloat
w (BRState -> Int
hyphenPenaltyValue BRState
settings) s
s
kernBox :: s -> PDFFloat -> Letter s
kernBox :: forall s. s -> PDFFloat -> Letter s
kernBox s
s PDFFloat
w = forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
w (forall a. a -> Maybe a
Just s
s)