{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ViewPatterns #-}

---------------------------------------------------------
-- |
-- Copyright   : (c) 2006-2016, alpheccar.org
-- License     : BSD-style
--
-- Maintainer  : misc@NOSPAMalpheccar.org
-- Stability   : experimental
-- Portability : portable
--
-- Breaking algorithm used to split a paragraph into lines
-- or a text into pages
---------------------------------------------------------
-- #hide
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
--import Debug.Trace

data Justification = FullJustification
                   | Centered
                   | LeftJustification
                   | RightJustification
                   deriving(Justification -> Justification -> Bool
(Justification -> Justification -> Bool)
-> (Justification -> Justification -> Bool) -> Eq Justification
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)

-- | Make a letter from any box
mkLetter :: (Show a, Box a, DisplayableBox a) => BoxDimension -- ^ Dimension of the box
         -> Maybe s -- ^ Text style of the box (can use t)
         -> a  -- ^ Box
         -> Letter s
mkLetter :: BoxDimension -> Maybe s -> a -> Letter s
mkLetter BoxDimension
d Maybe s
s a
a = BoxDimension -> AnyBox -> Maybe s -> Letter s
forall s. BoxDimension -> AnyBox -> Maybe s -> Letter s
Letter BoxDimension
d (a -> AnyBox
forall a. (Show a, Box a, DisplayableBox a) => a -> AnyBox
AnyBox a
a) Maybe s
s

-- | A letter which can be anything. Sizes are widths and for glue the dilation and compression factors
-- For the generic letter, height and descent are also provided
data Letter s = Letter BoxDimension !AnyBox !(Maybe s) -- ^ Any box as a letter
              | Glue !PDFFloat !PDFFloat !PDFFloat !(Maybe s) -- ^ A glue with style to know if it is part of the same sentence
              | FlaggedPenalty !PDFFloat !Int !s -- ^ Hyphen point
              | Penalty !Int -- ^ Penalty
              | AGlyph !s !GlyphCode !PDFFloat -- ^ A glyph
              | Kern !PDFFloat !(Maybe s) -- ^ A kern : non dilatable and non breakable glue
             
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 = Letter s -> PDFFloat -> PDFFloat
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
    
           
-- | Compute glue width with dilation
glueSize :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize PDFFloat
w PDFFloat
y PDFFloat
z PDFFloat
r =   
          if PDFFloat
r PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
>= PDFFloat
0 
              then
                  PDFFloat
rPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
y PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w
              else
                  PDFFloat
rPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
z PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w
                  
letterWidth :: Letter s -- ^ letter
            -> PDFFloat -- ^ Adjustement ratio
            -> PDFFloat -- ^ Width
letterWidth :: Letter s -> PDFFloat -> PDFFloat
letterWidth (AGlyph s
_ GlyphCode
_ PDFFloat
w) PDFFloat
_ = PDFFloat
w
letterWidth (Letter BoxDimension
dim AnyBox
_ Maybe s
_) PDFFloat
_ = BoxDimension -> 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 " String -> ShowS
forall a. [a] -> [a] -> [a]
++ AnyBox -> String
forall a. Show a => a -> String
show AnyBox
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
   show (Glue PDFFloat
a PDFFloat
b PDFFloat
c Maybe s
_) = String
"(Glue " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PDFFloat -> String
forall a. Show a => a -> String
show PDFFloat
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PDFFloat -> String
forall a. Show a => a -> String
show PDFFloat
b String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PDFFloat -> String
forall a. Show a => a -> String
show PDFFloat
c String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
   show (FlaggedPenalty PDFFloat
a Int
b s
_) = String
"(FlaggedPenalty " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PDFFloat -> String
forall a. Show a => a -> String
show PDFFloat
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
b String -> ShowS
forall a. [a] -> [a] -> [a]
++  String
")"
   show (Penalty Int
a) = String
"(Penalty " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
   show (AGlyph s
_ GlyphCode
t PDFFloat
_) = String
"(Glyph " String -> ShowS
forall a. [a] -> [a] -> [a]
++ GlyphCode -> String
forall a. Show a => a -> String
show GlyphCode
t String -> ShowS
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= (-Int
infinity)
    isForcedBreak (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,Penalty Int
p) = Int
p Int -> Int -> Bool
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Bool
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Bool
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> 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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Int
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> PDFFloat
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> PDFFloat
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> PDFFloat
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Int
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]
_) = (PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> Bool
forall s a. PointedBox s a => a -> Bool
isForcedBreak (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
b
    
-- A penalty has no width unless you break on it so it needs a special processing
penaltyWidth :: Letter s -> PDFFloat
penaltyWidth :: 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
(Int -> BreakNode -> ShowS)
-> (BreakNode -> String)
-> ([BreakNode] -> ShowS)
-> Show BreakNode
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 -- ^ Maxw
                -> PDFFloat -- ^ Current w
                -> PDFFloat -- ^ y
                -> PDFFloat -- ^ z
                -> PDFFloat -- ^ Dilatation ratio
dilatationRatio :: PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
dilatationRatio PDFFloat
maxw PDFFloat
w PDFFloat
y PDFFloat
z =                 
                if PDFFloat
w PDFFloat -> PDFFloat -> Bool
forall a. Eq a => a -> a -> Bool
== PDFFloat
maxw 
                    then PDFFloat
0.0
                    else if PDFFloat
w PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
< PDFFloat
maxw
                      then
                          if PDFFloat
y PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
> PDFFloat
0.0 then  ((PDFFloat
maxw PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
w) PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/ PDFFloat
y) else PDFFloat
bigAdjustRatio
                      else
                          if PDFFloat
z PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
> PDFFloat
0.0 then  ((PDFFloat
maxw PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
w) PDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/ PDFFloat
z) else PDFFloat
bigAdjustRatio
               
                            
adjustRatio :: BreakNode
            -> ZList s
            -> PDFFloat
            -> PDFFloat
adjustRatio :: BreakNode -> ZList s -> PDFFloat -> PDFFloat
adjustRatio BreakNode
a ZList s
l PDFFloat
maxw = 
    let w :: PDFFloat
w = ZList s -> PDFFloat
forall s a. PointedBox s a => a -> PDFFloat
cumulatedW ZList s
l PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- BreakNode -> PDFFloat
totalWidth BreakNode
a PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ Letter s -> PDFFloat
forall s. Letter s -> PDFFloat
penaltyWidth (ZList s -> Letter s
forall s a. PointedBox s a => a -> Letter s
letter ZList s
l)
        y :: PDFFloat
y = ZList s -> PDFFloat
forall s a. PointedBox s a => a -> PDFFloat
cumulatedY ZList s
l PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- BreakNode -> PDFFloat
totalDilatation BreakNode
a
        z :: PDFFloat
z = ZList s -> PDFFloat
forall s a. PointedBox s a => a -> PDFFloat
cumulatedZ ZList s
l PDFFloat -> PDFFloat -> PDFFloat
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 PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
< (-PDFFloat
1) then PDFFloat
bigAdjustRatio else PDFFloat
100.0 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
* PDFFloat -> PDFFloat
forall a. Num a => a -> a
abs(PDFFloat
r)PDFFloat -> PDFFloat -> PDFFloat
forall a. Floating a => a -> a -> a
**PDFFloat
3.0

fitness ::  PDFFloat -> Int
fitness :: PDFFloat -> Int
fitness PDFFloat
r = 
 if   PDFFloat
r PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
< (-PDFFloat
0.5)
  then 
      Int
0
  else if PDFFloat
r PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
<= (-PDFFloat
0.5)
      then
          Int
1
      else
          if PDFFloat
r PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
<= PDFFloat
1 
              then
                  Int
2
              else
                  Int
3
                 
-- | Breaking algorithm settings 
data BRState = BRState { BRState -> PDFFloat
firstPassTolerance :: !PDFFloat -- ^ Default value 100
                       , BRState -> PDFFloat
secondPassTolerance :: !PDFFloat -- ^ Default value 100
                       , BRState -> Int
hyphenPenaltyValue :: !Int -- ^ Default value 50
                       , BRState -> PDFFloat
fitness_demerit :: !PDFFloat -- ^ Default value 1000
                       , BRState -> PDFFloat
flagged_demerit :: !PDFFloat -- ^ Default value 1000
                       , BRState -> PDFFloat
line_penalty :: !PDFFloat -- ^ Default value 10
                       , BRState -> Justification
centered :: !Justification -- ^ Default value false
                       , 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 -- ^ adjust ratio
               -> BreakNode -- ^ Flag for previous
               -> ZList s -- ^ Flag for current
               -> Maybe(PDFFloat,Int) -- ^ Demerit for the breakpoint
computeDemerit :: 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 = ZList s -> Int
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 PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
<= PDFFloat
tolerance) Bool -> Bool -> Bool
|| Bool
force -- sndPass
        then 
            let fld :: PDFFloat
fld = if ZList s -> Bool
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' Int -> Int -> Bool
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 = PDFFloat -> PDFFloat -> PDFFloat
forall a. Ord a => a -> a -> a
max PDFFloat
1000.0 (PDFFloat -> PDFFloat) -> PDFFloat -> PDFFloat
forall a b. (a -> b) -> a -> b
$ if Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
                            then
                                PDFFloat
fid PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
fld PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ ((BRState -> PDFFloat
line_penalty BRState
settings) PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
b) PDFFloat -> PDFFloat -> PDFFloat
forall a. Floating a => a -> a -> a
** PDFFloat
2.0 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ (Int -> PDFFloat
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
p) PDFFloat -> PDFFloat -> PDFFloat
forall a. Floating a => a -> a -> a
** PDFFloat
2.0
                            else if Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> (-Int
infinity)
                                then
                                    PDFFloat
fid PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
fld PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ ((BRState -> PDFFloat
line_penalty BRState
settings) PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
b) PDFFloat -> PDFFloat -> PDFFloat
forall a. Floating a => a -> a -> a
** PDFFloat
2.0 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- (Int -> PDFFloat
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
p)PDFFloat -> PDFFloat -> PDFFloat
forall a. Floating a => a -> a -> a
**PDFFloat
2.0
                                else
                                    PDFFloat
fid PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
fld PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ ((BRState -> PDFFloat
line_penalty BRState
settings) PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
b) PDFFloat -> PDFFloat -> PDFFloat
forall a. Floating a => a -> a -> a
** PDFFloat
2.0
            in
               (PDFFloat, Int) -> Maybe (PDFFloat, Int)
forall a. a -> Maybe a
Just (PDFFloat
dem,Int
fitness')
        else
             Maybe (PDFFloat, Int)
forall a. Maybe a
Nothing    

data MaybeCB a = NoCB 
               | OneCB !(CB a)
               deriving(Int -> MaybeCB a -> ShowS
[MaybeCB a] -> ShowS
MaybeCB a -> String
(Int -> MaybeCB a -> ShowS)
-> (MaybeCB a -> String)
-> ([MaybeCB a] -> ShowS)
-> Show (MaybeCB a)
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
[ZList s] -> ShowS
ZList s -> String
(Int -> ZList s -> ShowS)
-> (ZList s -> String) -> ([ZList s] -> ShowS) -> Show (ZList s)
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)

-- Used for debugging only
--currentLetter :: ZList s -> Letter s
--currentLetter (ZList _ (_,_,_,_,a) _) = a

createZList :: [Letter s] -> ZList s
createZList :: [Letter s] -> ZList s
createZList [] = String -> ZList s
forall a. HasCallStack => String -> a
error String
"List cannot be empty to create a zipper"
createZList [Letter s]
l = MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
forall s.
MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
ZList MaybeCB (Letter s)
forall a. MaybeCB a
NoCB (PDFFloat
0,PDFFloat
0,PDFFloat
0,Int
1,[Letter s] -> Letter s
forall a. [a] -> a
head [Letter s]
l) ([Letter s] -> [Letter s]
forall a. [a] -> [a]
tail [Letter s]
l)

theEnd :: ZList s -> Bool
theEnd :: ZList s -> Bool
theEnd (ZList MaybeCB (Letter s)
_ (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
_ []) = Bool
True
theEnd ZList s
_ = Bool
False

-- | We create a new breakpoint but we get the cumulated dimensions only at the next box following the break
-- since glues and penalties are removed at the beginning of a line
createBreaknode :: Maybe (Int,Int,Int,BreakNode) -> ZList s -> BreakNode
createBreaknode :: 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
_) []) = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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
_) []) = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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
_) []) = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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
_) []) = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
infinity = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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]
_) = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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]
_) = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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]
_) = Maybe (Int, Int, Int, BreakNode) -> Bool -> ZList s -> BreakNode
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 = Maybe (Int, Int, Int, BreakNode) -> ZList s -> BreakNode
forall s. Maybe (Int, Int, Int, BreakNode) -> ZList s -> BreakNode
createBreaknode Maybe (Int, Int, Int, BreakNode)
prev (ZList s -> ZList s
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 :: 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) = ZList s -> BoxDimension
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

-- | Get cumulated dimension for following box
getDim :: ZList s -> (PDFFloat,PDFFloat,PDFFloat)
getDim :: 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 ZList s -> Bool
forall s. ZList s -> Bool
theEnd ZList s
a then String -> BoxDimension
forall a. HasCallStack => String -> a
error String
"Can't find end of paragraph" else ZList s -> BoxDimension
forall s. ZList s -> BoxDimension
getDim (ZList s -> ZList s
forall s. ZList s -> ZList s
moveRight ZList s
a)


moveRight :: ZList s -> ZList s
moveRight :: 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 PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w'
        y'' :: PDFFloat
y''=PDFFloat
yPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
y'
        z'' :: PDFFloat
z''=PDFFloat
zPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
z'
    in
    MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
forall s.
MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
ZList ((PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> MaybeCB (Letter s)
forall a. CB a -> MaybeCB a
OneCB (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
c) (PDFFloat
w'',PDFFloat
y'',PDFFloat
z'',Int
pInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,[Letter s] -> Letter s
forall a. [a] -> a
head [Letter s]
r) ([Letter s] -> [Letter s]
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' = Letter s -> PDFFloat -> PDFFloat
forall a. MaybeGlue a => a -> PDFFloat -> PDFFloat
glueSizeWithRatio Letter s
a PDFFloat
0.0
            w'' :: PDFFloat
w'' = PDFFloat
w PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
w'
        in
        MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
forall s.
MaybeCB (Letter s)
-> (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
-> [Letter s]
-> ZList s
ZList ((PDFFloat, PDFFloat, PDFFloat, Int, Letter s) -> MaybeCB (Letter s)
forall a. CB a -> MaybeCB a
OneCB (PDFFloat, PDFFloat, PDFFloat, Int, Letter s)
c) (PDFFloat
w'',PDFFloat
y,PDFFloat
z,Int
pInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1,[Letter s] -> Letter s
forall a. [a] -> a
head [Letter s]
r) ([Letter s] -> [Letter s]
forall a. [a] -> [a]
tail [Letter s]
r)
     

isFeasibleBreakpoint :: Bool -- ^ Second pass
                     -> ZList s -- ^ Current analyzed box
                     -> Bool -- ^ Result
isFeasibleBreakpoint :: Bool -> ZList s -> Bool
isFeasibleBreakpoint Bool
True (ZList MaybeCB (Letter s)
_ (PDFFloat
_,PDFFloat
_,PDFFloat
_,Int
_,FlaggedPenalty PDFFloat
_ Int
p s
_) [Letter s]
_) = Int
p Int -> Int -> Bool
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 Int -> Int -> Bool
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




-- Update a feasible breakpoint remembering only the best one
type PossibleBreak = ActiveNodes -- Line, demerit and break node
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 PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
< BreakNode -> PDFFloat
demerit BreakNode
b then BreakNode
a else BreakNode
b  

-- | Check is a break point is possible
-- otherwise, if none is possible and there is only one remaining active point,
-- we force a breakpoint
updateWithNewRIfNoSolution :: Bool
                           -> PDFFloat -- ^ Old r
                           -> ZList s -- ^ Current
                           -> (Int,Int,Int)
                           -> PossibleBreak
                           -> ActiveNodes-- ^ Actives
                           -> (Bool -> PDFFloat -> ActiveNodes -> (PossibleBreak,ActiveNodes))
                           -> (PossibleBreak,ActiveNodes)
updateWithNewRIfNoSolution :: 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 ZList s -> Bool
forall s a. PointedBox s a => a -> Bool
isForcedBreak ZList s
z
          then
             Bool -> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak)
f Bool
True PDFFloat
r ((Int, Int, Int) -> PossibleBreak -> PossibleBreak
forall k a. Ord k => k -> Map k a -> Map k a
M.delete (Int, Int, Int)
key PossibleBreak
newmap)
          else
             if PDFFloat
r PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
< -PDFFloat
1 
                then let m' :: PossibleBreak
m' = (Int, Int, Int) -> PossibleBreak -> PossibleBreak
forall k a. Ord k => k -> Map k a -> Map k a
M.delete (Int, Int, Int)
key PossibleBreak
newmap 
                     in
                     if PossibleBreak -> Bool
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   
                        
--debug b z = "(" ++
--    show (cumulatedW z - totalWidth b + penaltyWidth (letter z)) ++ " " ++
--    show (cumulatedY z - totalDilatation b) ++ " " ++
--    show (cumulatedZ z - totalCompression b) ++ ")"   
--    
--breakTrace sndPass b z r' p = trace ("SndPass :" ++ show sndPass ++ " " 
--   ++ debug b z ++ " " ++ show r' ++ " " 
--   ++ show (currentLetter z) ++ " " 
--   ++ show (position z) ++ " -> " 
--   ++ show p
--   ++ if isFlagged z then " (Flagged)" else ""
--   )          

getNewActiveBreakpoints ::  BRState -> Bool -> (Int -> PDFFloat) -> ActiveNodes -> ZList s -> (PossibleBreak,ActiveNodes)
getNewActiveBreakpoints :: BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> (PossibleBreak, PossibleBreak)
getNewActiveBreakpoints BRState
settings Bool
sndPass Int -> PDFFloat
fmaxw PossibleBreak
actives ZList s
z = 
    if Bool -> ZList s -> Bool
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' = BreakNode -> ZList s -> PDFFloat -> PDFFloat
forall s. BreakNode -> ZList s -> PDFFloat -> PDFFloat
adjustRatio BreakNode
b ZList s
z (Int -> PDFFloat
fmaxw (Int
lineInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1))
              in -- breakTrace sndPass b z r' p $
              Bool
-> PDFFloat
-> ZList s
-> (Int, Int, Int)
-> PossibleBreak
-> PossibleBreak
-> (Bool
    -> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak))
-> (PossibleBreak, PossibleBreak)
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))
 -> (PossibleBreak, PossibleBreak))
-> (Bool
    -> PDFFloat -> PossibleBreak -> (PossibleBreak, PossibleBreak))
-> (PossibleBreak, PossibleBreak)
forall a b. (a -> b) -> a -> b
$
               \Bool
force PDFFloat
r PossibleBreak
newmap -> let dem' :: Maybe (PDFFloat, Int)
dem' = Bool
-> BRState
-> Bool
-> PDFFloat
-> BreakNode
-> ZList s
-> Maybe (PDFFloat, Int)
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' = Maybe (Int, Int, Int, BreakNode) -> ZList s -> BreakNode
forall s. Maybe (Int, Int, Int, BreakNode) -> ZList s -> BreakNode
createBreaknode ((Int, Int, Int, BreakNode) -> Maybe (Int, Int, Int, BreakNode)
forall a. a -> Maybe a
Just (Int
p,Int
line,Int
f,BreakNode
b)) ZList s
z in
                                      -- We keep only the best new break
                                      ((BreakNode -> BreakNode -> BreakNode)
-> (Int, Int, Int) -> BreakNode -> PossibleBreak -> PossibleBreak
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
M.insertWith BreakNode -> BreakNode -> BreakNode
updateBreak (ZList s -> Int
forall s a. PointedBox s a => a -> Int
position ZList s
z,Int
lineInt -> Int -> Int
forall 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') = ((Int, Int, Int)
 -> BreakNode
 -> (PossibleBreak, PossibleBreak)
 -> (PossibleBreak, PossibleBreak))
-> (PossibleBreak, PossibleBreak)
-> PossibleBreak
-> (PossibleBreak, PossibleBreak)
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
M.foldrWithKey (Int, Int, Int)
-> BreakNode
-> (PossibleBreak, PossibleBreak)
-> (PossibleBreak, PossibleBreak)
analyzeActive (PossibleBreak
forall k a. Map k a
M.empty,PossibleBreak
actives) PossibleBreak
actives
            dmin :: PDFFloat
dmin = [PDFFloat] -> PDFFloat
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum ([PDFFloat] -> PDFFloat)
-> (PossibleBreak -> [PDFFloat]) -> PossibleBreak -> PDFFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BreakNode -> PDFFloat) -> [BreakNode] -> [PDFFloat]
forall a b. (a -> b) -> [a] -> [b]
map BreakNode -> PDFFloat
demerit ([BreakNode] -> [PDFFloat])
-> (PossibleBreak -> [BreakNode]) -> PossibleBreak -> [PDFFloat]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PossibleBreak -> [BreakNode]
forall k a. Map k a -> [a]
M.elems (PossibleBreak -> PDFFloat) -> PossibleBreak -> PDFFloat
forall a b. (a -> b) -> a -> b
$ PossibleBreak
breaks'
            nbreaks :: PossibleBreak
nbreaks = (BreakNode -> Bool) -> PossibleBreak -> PossibleBreak
forall a k. (a -> Bool) -> Map k a -> Map k a
M.filter (\BreakNode
x -> BreakNode -> PDFFloat
demerit BreakNode
x PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
< PDFFloat
dmin PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ (BRState -> PDFFloat
fitness_demerit BRState
settings)) PossibleBreak
breaks'
        in
        if PossibleBreak -> Bool
forall k a. Map k a -> Bool
M.null PossibleBreak
nbreaks
         then
           (PossibleBreak
breaks' , PossibleBreak
actives') 
         else
           (PossibleBreak
nbreaks , PossibleBreak
actives') 
    else
       (PossibleBreak
forall k a. Map k a
M.empty,PossibleBreak
actives )
          
-- (position, line, fitness) -> (adjust ratio, break position)
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)(PDFFloat, Int, Bool)
-> [(PDFFloat, Int, Bool)] -> [(PDFFloat, Int, Bool)]
forall a. a -> [a] -> [a]
:(Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)]
genNodeList (Maybe (Int, Int, Int, BreakNode) -> (Int, Int, Int, BreakNode)
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Int, Int, Int, BreakNode) -> (Int, Int, Int, BreakNode))
-> (BreakNode -> Maybe (Int, Int, Int, BreakNode))
-> BreakNode
-> (Int, Int, Int, BreakNode)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BreakNode -> Maybe (Int, Int, Int, BreakNode)
previous (BreakNode -> (Int, Int, Int, BreakNode))
-> BreakNode -> (Int, Int, Int, BreakNode)
forall a b. (a -> b) -> a -> b
$ BreakNode
b)


-- Analyze the boxes to compute breaks
analyzeBoxes :: BRState -> Bool -> (Int -> PDFFloat) -> ActiveNodes -> ZList s -> ZList s -> [(PDFFloat,Int,Bool)]
analyzeBoxes :: 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)) (((a, b, c), BreakNode) -> (a, b, c, BreakNode))
-> (Map (a, b, c) BreakNode -> ((a, b, c), BreakNode))
-> Map (a, b, c) BreakNode
-> (a, b, c, BreakNode)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((a, b, c), BreakNode) -> ((a, b, c), BreakNode) -> Ordering)
-> [((a, b, c), BreakNode)] -> ((a, b, c), BreakNode)
forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
minimumBy (\((a, b, c)
_,BreakNode
a) ((a, b, c)
_,BreakNode
b) -> PDFFloat -> PDFFloat -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (BreakNode -> PDFFloat
demerit BreakNode
a) (BreakNode -> PDFFloat
demerit BreakNode
b)) ([((a, b, c), BreakNode)] -> ((a, b, c), BreakNode))
-> (Map (a, b, c) BreakNode -> [((a, b, c), BreakNode)])
-> Map (a, b, c) BreakNode
-> ((a, b, c), BreakNode)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map (a, b, c) BreakNode -> [((a, b, c), BreakNode)]
forall k a. Map k a -> [(k, a)]
M.toList (Map (a, b, c) BreakNode -> (a, b, c, BreakNode))
-> Map (a, b, c) BreakNode -> (a, b, c, BreakNode)
forall a b. (a -> b) -> a -> b
$ Map (a, b, c) BreakNode
b'
        (PossibleBreak
breaks',PossibleBreak
actives') = BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> (PossibleBreak, PossibleBreak)
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 = PossibleBreak -> PossibleBreak -> PossibleBreak
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 = [(PDFFloat, Int, Bool)] -> [(PDFFloat, Int, Bool)]
forall a. [a] -> [a]
tail ([(PDFFloat, Int, Bool)] -> [(PDFFloat, Int, Bool)])
-> ((Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)])
-> (Int, Int, Int, BreakNode)
-> [(PDFFloat, Int, Bool)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(PDFFloat, Int, Bool)] -> [(PDFFloat, Int, Bool)]
forall a. [a] -> [a]
reverse ([(PDFFloat, Int, Bool)] -> [(PDFFloat, Int, Bool)])
-> ((Int, Int, Int, BreakNode) -> [(PDFFloat, Int, Bool)])
-> (Int, Int, Int, BreakNode)
-> [(PDFFloat, Int, Bool)]
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 Maybe (Int, Int, Int, BreakNode)
forall a. Maybe a
Nothing
    in
    --  If forced breakpoint or no breakpoint found
    if PossibleBreak -> Bool
forall k a. Map k a -> Bool
M.null PossibleBreak
actives'
        then
            -- If no breakpoint found
            if PossibleBreak -> Bool
forall k a. Map k a -> Bool
M.null PossibleBreak
breaks'
                then
                    -- Second pass analysis
                    if Bool -> Bool
not Bool
pass
                     then
                          BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
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
                          String -> [(PDFFloat, Int, Bool)]
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 
                    -- Forced breakpoint then we gen a list from it and continue the analysis
                    let minBreak :: (Int, Int, Int, BreakNode)
minBreak = PossibleBreak -> (Int, Int, Int, BreakNode)
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 ZList s -> Bool
forall s. ZList s -> Bool
theEnd ZList s
z
                      then
                        [(PDFFloat, Int, Bool)]
someNewBreaks
                      else
                        let z' :: ZList s
z' = ZList s -> ZList s
forall s. ZList s -> ZList s
moveRight ZList s
z in
                        [(PDFFloat, Int, Bool)]
someNewBreaks [(PDFFloat, Int, Bool)]
-> [(PDFFloat, Int, Bool)] -> [(PDFFloat, Int, Bool)]
forall a. [a] -> [a] -> [a]
++ BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
forall s.
BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
analyzeBoxes BRState
settings Bool
pass Int -> PDFFloat
fmaxw ((Int, Int, Int) -> BreakNode -> PossibleBreak -> PossibleBreak
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ((Int, Int, Int, BreakNode) -> (Int, Int, Int)
forall a b c d. (a, b, c, d) -> (a, b, c)
getKey (Int, Int, Int, BreakNode)
minBreak) ((Int, Int, Int, BreakNode) -> BreakNode
forall a b c. (a, b, c, BreakNode) -> BreakNode
getNode (Int, Int, Int, BreakNode)
minBreak) PossibleBreak
forall k a. Map k a
M.empty) ZList s
z' ZList s
z'
        -- Normal feasible breakpoint
        else
            if PossibleBreak -> Bool
forall k a. Map k a -> Bool
M.null PossibleBreak
breaks'
             then
                 if ZList s -> Bool
forall s. ZList s -> Bool
theEnd ZList s
z
                    then  
                        String -> [(PDFFloat, Int, Bool)]
forall a. HasCallStack => String -> a
error String
"End of text found but no paragraph end detected"
                    else
                        BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
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 -> ZList s
forall s. ZList s -> ZList s
moveRight ZList s
z)
             else
                -- If the end it must be a possible breakpoint
                -- We should NEVER reach this part. The end should always be a forced breakpoint
                if ZList s -> Bool
forall s. ZList s -> Bool
theEnd ZList s
z
                   then
                     let minBreak :: (Int, Int, Int, BreakNode)
minBreak = PossibleBreak -> (Int, Int, Int, BreakNode)
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
                     -- We continue the analysis
                     BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
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 (ZList s -> ZList s
forall s. ZList s -> ZList s
moveRight ZList s
z)

-- | Create an hyphen box
hyphenBox :: Style s => s -> Letter s
hyphenBox :: s -> Letter s
hyphenBox s
s = 
  let PDFFont AnyFont
f Int
fontSize = TextStyle -> PDFFont
textFont (TextStyle -> PDFFont) -> (s -> TextStyle) -> s -> PDFFont
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFont) -> s -> PDFFont
forall a b. (a -> b) -> a -> b
$ s
s
      maybeHyphen :: Maybe GlyphCode
maybeHyphen = AnyFont -> Maybe GlyphCode
forall f. IsFont f => f -> Maybe GlyphCode
hyphenGlyph AnyFont
f 
  in 
  case Maybe GlyphCode
maybeHyphen of 
  Just GlyphCode
h -> s -> GlyphCode -> PDFFloat -> Letter s
forall s. s -> GlyphCode -> PDFFloat -> Letter s
AGlyph s
s GlyphCode
h (AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
h)
  Maybe GlyphCode
Nothing -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
0 Maybe s
forall a. Maybe a
Nothing

-- Use a list of breakpoint and adjustement ratios to generate a list of lines. Bool means if the break was done on a flagged penalty (hyphen)
cutList :: Style s => Justification -> [Letter s] -> Int -> [(PDFFloat,Int,Bool)] -> [(PDFFloat,[Letter s],[Letter s])]
cutList :: 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') = Int -> [Letter s] -> ([Letter s], [Letter s])
forall a. Int -> [a] -> ([a], [a])
splitAt (Int
baInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
c) [Letter s]
t 
   in
   if [Letter s] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Letter s]
theLine 
      then
         []
      else 
         if [Letter s] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Letter s]
t'
             then
                 [(PDFFloat
ra,[Letter s]
theLine,[Letter s]
t)]
             else
                 case [Letter s] -> Letter s
forall a. [a] -> a
head [Letter s]
t' of
                     FlaggedPenalty PDFFloat
_ Int
_ s
s -> if Bool -> Bool
not Bool
fa 
                                               then
                                                  String -> [(PDFFloat, [Letter s], [Letter s])]
forall a. HasCallStack => String -> a
error (String -> [(PDFFloat, [Letter s], [Letter s])])
-> String -> [(PDFFloat, [Letter s], [Letter s])]
forall a b. (a -> b) -> a -> b
$ String
"Breakpoint marked as not flagged but detected as flagged ! Send a bug report ! " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (PDFFloat, Int, Bool) -> String
forall a. Show a => a -> String
show (PDFFloat
ra,Int
ba,Bool
fa)
                                               else
                                                 (PDFFloat
ra,[Letter s]
theLine [Letter s] -> [Letter s] -> [Letter s]
forall a. [a] -> [a] -> [a]
++ Justification -> s -> [Letter s]
forall s. Style s => Justification -> s -> [Letter s]
hyphenForJustification Justification
j s
s,[Letter s]
t) (PDFFloat, [Letter s], [Letter s])
-> [(PDFFloat, [Letter s], [Letter s])]
-> [(PDFFloat, [Letter s], [Letter s])]
forall a. a -> [a] -> [a]
: Justification
-> [Letter s]
-> Int
-> [(PDFFloat, Int, Bool)]
-> [(PDFFloat, [Letter s], [Letter s])]
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
                                String -> [(PDFFloat, [Letter s], [Letter s])]
forall a. HasCallStack => String -> a
error (String -> [(PDFFloat, [Letter s], [Letter s])])
-> String -> [(PDFFloat, [Letter s], [Letter s])]
forall a b. (a -> b) -> a -> b
$ String
"Breakpoint marked as flagged but detected as not flagged ! Send a bug report ! " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (PDFFloat, Int, Bool) -> String
forall a. Show a => a -> String
show (PDFFloat
ra,Int
ba,Bool
fa) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Letter s] -> String
forall a. Show a => a -> String
show [Letter s]
theLine String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Letter s] -> String
forall a. Show a => a -> String
show [Letter s]
t'
                            else
                                (PDFFloat
ra,[Letter s]
theLine,[Letter s]
t) (PDFFloat, [Letter s], [Letter s])
-> [(PDFFloat, [Letter s], [Letter s])]
-> [(PDFFloat, [Letter s], [Letter s])]
forall a. a -> [a] -> [a]
: Justification
-> [Letter s]
-> Int
-> [(PDFFloat, Int, Bool)]
-> [(PDFFloat, [Letter s], [Letter s])]
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
     
-- Compute the breakpoints and generate a list of lines with the adjustement ratios
-- The line are not interpreted. Some additional postprocessing is required
-- for horizontal lines of vertical boxes
formatList :: Style s => BRState -> (Int -> PDFFloat) -> [Letter s] -> [(PDFFloat,[Letter s],[Letter s])]
formatList :: BRState
-> (Int -> PDFFloat)
-> [Letter s]
-> [(PDFFloat, [Letter s], [Letter s])]
formatList BRState
settings Int -> PDFFloat
maxw [Letter s]
boxes = 
    let active :: PossibleBreak
active = (Int, Int, Int) -> BreakNode -> PossibleBreak -> PossibleBreak
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 Maybe (Int, Int, Int, BreakNode)
forall a. Maybe a
Nothing) PossibleBreak
forall k a. Map k a
M.empty
        z :: ZList s
z = [Letter s] -> ZList s
forall s. [Letter s] -> ZList s
createZList [Letter s]
boxes
        theBreaks :: [(PDFFloat, Int, Bool)]
theBreaks = BRState
-> Bool
-> (Int -> PDFFloat)
-> PossibleBreak
-> ZList s
-> ZList s
-> [(PDFFloat, Int, Bool)]
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
    Justification
-> [Letter s]
-> Int
-> [(PDFFloat, Int, Bool)]
-> [(PDFFloat, [Letter s], [Letter s])]
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
     
-- | Value modeling infinity  
infinity :: Int 
infinity :: Int
infinity = Int
10000

bigAdjustRatio :: PDFFloat
bigAdjustRatio :: PDFFloat
bigAdjustRatio = PDFFloat
10000.0

-- | Add a glue to the stream
glueBox :: Maybe s
        -> PDFFloat -- ^ Glue width
        -> PDFFloat -- ^ Glue dilatation
        -> PDFFloat -- ^ Glue compression
        -> Letter s
glueBox :: Maybe s -> PDFFloat -> PDFFloat -> PDFFloat -> Letter s
glueBox Maybe s
s PDFFloat
w PDFFloat
y PDFFloat
z = PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
w PDFFloat
y PDFFloat
z Maybe s
s

-- | Return the standard space width
spaceWidth :: Style s => s -- ^ The style
           -> PDFFloat
spaceWidth :: s -> PDFFloat
spaceWidth  s
s =  
    let PDFFont AnyFont
f Int
fontSize = (TextStyle -> PDFFont
textFont (TextStyle -> PDFFont) -> (s -> TextStyle) -> s -> PDFFont
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFont) -> s -> PDFFont
forall a b. (a -> b) -> a -> b
$ s
s) 
        ws :: PDFFloat
ws = AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize (AnyFont -> GlyphCode
forall f. IsFont f => f -> GlyphCode
spaceGlyph AnyFont
f)
        h :: PDFFloat
h = TextStyle -> PDFFloat
scaleSpace (TextStyle -> PDFFloat) -> (s -> TextStyle) -> s -> PDFFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFloat) -> s -> PDFFloat
forall a b. (a -> b) -> a -> b
$ s
s
    in
      PDFFloat
ws PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
* PDFFloat
h  
   
-- | How much dilatation is allowed compred to the space width   
centeredDilatationFactor :: PDFFloat
centeredDilatationFactor :: PDFFloat
centeredDilatationFactor = PDFFloat
10.0       

-- | How much dilatation is allowed compared to the space width   
leftDilatationFactor :: PDFFloat
leftDilatationFactor :: PDFFloat
leftDilatationFactor = PDFFloat
20.0

-- | How much dilatation is allowed compared to the space width   
rightDilatationFactor :: PDFFloat
rightDilatationFactor :: PDFFloat
rightDilatationFactor = PDFFloat
20.0

-- | Add a glue to the stream
spaceGlueBox :: Style s => BRState -- ^ Paragraph settings
             -> s -- ^ The style
             -> PDFFloat
             -> [Letter s]
spaceGlueBox :: BRState -> s -> PDFFloat -> [Letter s]
spaceGlueBox BRState
settings s
s PDFFloat
f = 
     let ws :: PDFFloat
ws = s -> PDFFloat
forall s. Style s => s -> PDFFloat
spaceWidth s
s
         h :: PDFFloat
h = TextStyle -> PDFFloat
scaleSpace (TextStyle -> PDFFloat) -> (s -> TextStyle) -> s -> PDFFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFloat) -> s -> PDFFloat
forall a b. (a -> b) -> a -> b
$ s
s
         sy :: PDFFloat
sy = TextStyle -> PDFFloat
scaleDilatation (TextStyle -> PDFFloat) -> (s -> TextStyle) -> s -> PDFFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFloat) -> s -> PDFFloat
forall a b. (a -> b) -> a -> b
$ s
s
         sz :: PDFFloat
sz = TextStyle -> PDFFloat
scaleCompression (TextStyle -> PDFFloat) -> (s -> TextStyle) -> s -> PDFFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFloat) -> s -> PDFFloat
forall a b. (a -> b) -> a -> b
$ s
s
         normalW :: PDFFloat
normalW = PDFFloat
ws PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
* PDFFloat
h
     in
     case (BRState -> Justification
centered BRState
settings) of
        Justification
FullJustification -> [PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue (PDFFloat
normalW) (PDFFloat
normalWPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
syPDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/PDFFloat
2.0PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
f) (PDFFloat
normalWPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
szPDFFloat -> PDFFloat -> PDFFloat
forall a. Fractional a => a -> a -> a
/PDFFloat
3.0) (s -> Maybe s
forall a. a -> Maybe a
Just s
s)]
        Justification
Centered -> [ PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
centeredDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                    , Int -> Letter s
forall s. Int -> Letter s
Penalty Int
0
                    , PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue (PDFFloat
normalW) (-PDFFloat
2PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
centeredDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                    , PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                    , Int -> Letter s
forall s. Int -> Letter s
Penalty Int
infinity
                    , PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
centeredDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                    ]
        Justification
LeftJustification -> [ PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
leftDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                             , Int -> Letter s
forall s. Int -> Letter s
Penalty Int
0
                             , PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
normalW (-PDFFloat
leftDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                             ] 
        Justification
RightJustification -> [ PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
normalW (-PDFFloat
rightDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                              , PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                              , Int -> Letter s
forall s. Int -> Letter s
Penalty Int
infinity
                              , PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
rightDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*PDFFloat
normalW) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)
                              ]                    

     
-- | When a paragraph is full and we start a new one we must clean the beginning paragraph and remove what has been left by the
-- broken space
simplify :: [Letter s]
         -> [Letter s]
simplify :: [Letter s] -> [Letter s]
simplify [] = []
simplify ((Glue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe s
_):[Letter s]
l) = [Letter s] -> [Letter s]
forall s. [Letter s] -> [Letter s]
simplify [Letter s]
l
simplify ((FlaggedPenalty PDFFloat
_ Int
_ s
_):[Letter s]
l) = [Letter s] -> [Letter s]
forall s. [Letter s] -> [Letter s]
simplify [Letter s]
l
simplify ((Penalty Int
_):[Letter s]
l) = [Letter s] -> [Letter s]
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 :: Justification -> s -> [Letter s]
hyphenForJustification Justification
Centered s
s = [s -> Letter s
forall s. Style s => s -> Letter s
hyphenBox s
s,PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
centeredDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*s -> PDFFloat
forall s. Style s => s -> PDFFloat
spaceWidth s
s) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)]
hyphenForJustification Justification
LeftJustification s
s = [s -> Letter s
forall s. Style s => s -> Letter s
hyphenBox s
s,PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> PDFFloat -> PDFFloat -> Maybe s -> Letter s
Glue PDFFloat
0 (PDFFloat
leftDilatationFactorPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
*s -> PDFFloat
forall s. Style s => s -> PDFFloat
spaceWidth s
s) PDFFloat
0 (s -> Maybe s
forall a. a -> Maybe a
Just s
s)]
hyphenForJustification Justification
_ s
s = [s -> Letter s
forall s. Style s => s -> Letter s
hyphenBox s
s]
                        
                          
-- | Add a penalty to the stream
penalty :: Int -- ^ Penalty value
        -> Letter s
penalty :: Int -> Letter s
penalty Int
p = Int -> Letter s
forall s. Int -> Letter s
Penalty Int
p

-- | Create a box containing text
createGlyph :: s -- ^ Char style
            -> GlyphCode
            -> PDFFloat -- ^ Char width
            -> Letter s
createGlyph :: s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
c PDFFloat
w = s -> GlyphCode -> PDFFloat -> Letter s
forall s. s -> GlyphCode -> PDFFloat -> Letter s
AGlyph s
s GlyphCode
c PDFFloat
w



{-
  
Breaking a text with specific hyphen handling if it make sense

-}




ripText :: Style s 
        => s
        -> BRState
        -> [SpecialChar] -- ^ Special meaning glyph
        -> [Letter s] -- ^ List of chars and char width taking into account kerning
ripText :: 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 (TextStyle -> PDFFont) -> (s -> TextStyle) -> s -> PDFFont
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFont) -> s -> PDFFont
forall a b. (a -> b) -> a -> b
$ s
s) 
        ga :: GlyphCode
ga = AnyFont -> Char -> GlyphCode
forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
ca 
        gb :: GlyphCode
gb = AnyFont -> Char -> GlyphCode
forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
cb
        oldKerning :: PDFFloat
oldKerning = AnyFont -> Int -> GlyphCode -> GlyphCode -> PDFFloat
forall f.
IsFont f =>
f -> Int -> GlyphCode -> GlyphCode -> PDFFloat
getKern AnyFont
f Int
fontSize GlyphCode
ga GlyphCode
gb
        la :: Letter s
la = s -> GlyphCode -> PDFFloat -> Letter s
forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
ga ((AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
ga) PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
oldKerning)
        lb :: Letter s
lb = s -> GlyphCode -> PDFFloat -> Letter s
forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
gb (AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
gb)
        maybeH :: Maybe GlyphCode
maybeH = AnyFont -> Maybe GlyphCode
forall f. IsFont f => f -> Maybe GlyphCode
hyphenGlyph AnyFont
f
    in 
    case Maybe GlyphCode
maybeH of 
    Maybe GlyphCode
Nothing -> Letter s
laLetter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:Letter s
lbLetter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:s -> BRState -> [SpecialChar] -> [Letter s]
forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
    Just GlyphCode
h -> 
          let newKerning :: PDFFloat
newKerning = AnyFont -> Int -> GlyphCode -> GlyphCode -> PDFFloat
forall f.
IsFont f =>
f -> Int -> GlyphCode -> GlyphCode -> PDFFloat
getKern AnyFont
f Int
fontSize GlyphCode
ga GlyphCode
h
              w :: PDFFloat
w = AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
h PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
oldKerning PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
newKerning
          in
          Letter s
laLetter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:BRState -> s -> PDFFloat -> Letter s
forall s. BRState -> s -> PDFFloat -> Letter s
hyphenPenalty BRState
settings s
s PDFFloat
wLetter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:Letter s
lbLetter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:s -> BRState -> [SpecialChar] -> [Letter s]
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 (TextStyle -> PDFFont) -> (s -> TextStyle) -> s -> PDFFont
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFont) -> s -> PDFFont
forall a b. (a -> b) -> a -> b
$ s
s) 
        ga :: GlyphCode
ga = AnyFont -> Char -> GlyphCode
forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
ca 
        gb :: GlyphCode
gb = AnyFont -> Char -> GlyphCode
forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
cb
        k :: PDFFloat
k = AnyFont -> Int -> GlyphCode -> GlyphCode -> PDFFloat
forall f.
IsFont f =>
f -> Int -> GlyphCode -> GlyphCode -> PDFFloat
getKern AnyFont
f Int
fontSize GlyphCode
ga GlyphCode
gb
        la :: Letter s
la = s -> GlyphCode -> PDFFloat -> Letter s
forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
ga ((AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
ga) PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
k)
        lb :: Letter s
lb = s -> GlyphCode -> PDFFloat -> Letter s
forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
gb (AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
gb)
    in 
    Letter s
laLetter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:Letter s
lbLetter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:s -> BRState -> [SpecialChar] -> [Letter s]
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) = (BRState -> s -> PDFFloat -> [Letter s]
forall s. Style s => BRState -> s -> PDFFloat -> [Letter s]
spaceGlueBox BRState
settings s
s PDFFloat
1.0) [Letter s] -> [Letter s] -> [Letter s]
forall a. [a] -> [a] -> [a]
++ s -> BRState -> [SpecialChar] -> [Letter s]
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) = (BRState -> s -> PDFFloat -> [Letter s]
forall s. Style s => BRState -> s -> PDFFloat -> [Letter s]
spaceGlueBox BRState
settings s
s PDFFloat
2.0) [Letter s] -> [Letter s] -> [Letter s]
forall a. [a] -> [a] -> [a]
++ s -> BRState -> [SpecialChar] -> [Letter s]
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) = s -> BRState -> [SpecialChar] -> [Letter s]
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 (TextStyle -> PDFFont) -> (s -> TextStyle) -> s -> PDFFont
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (s -> PDFFont) -> s -> PDFFont
forall a b. (a -> b) -> a -> b
$ s
s) 
      g :: GlyphCode
g = AnyFont -> Char -> GlyphCode
forall f. IsFont f => f -> Char -> GlyphCode
charGlyph AnyFont
f Char
c
  in
  s -> GlyphCode -> PDFFloat -> Letter s
forall s. s -> GlyphCode -> PDFFloat -> Letter s
createGlyph s
s GlyphCode
g (AnyFont -> Int -> GlyphCode -> PDFFloat
forall f. IsFont f => f -> Int -> GlyphCode -> PDFFloat
glyphWidth AnyFont
f Int
fontSize GlyphCode
g) Letter s -> [Letter s] -> [Letter s]
forall a. a -> [a] -> [a]
:s -> BRState -> [SpecialChar] -> [Letter s]
forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
s BRState
settings [SpecialChar]
l
             


-- | split a line into boxes and add hyphen where needed
splitText :: Style s => BRState -> s -> T.Text -> [Letter s]
splitText :: 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 
   s -> BRState -> [SpecialChar] -> [Letter s]
forall s. Style s => s -> BRState -> [SpecialChar] -> [Letter s]
ripText s
f BRState
settings [SpecialChar]
special
     
-- | Create an hyphen penalty
hyphenPenalty :: BRState
              -> s -- ^ Style of future hyphen
              -> PDFFloat -- ^ Size of hyphen taking into account the kerning that was perturbed by the hyphen introduction. The char before the hyphen is now bigger
              -> Letter s
hyphenPenalty :: BRState -> s -> PDFFloat -> Letter s
hyphenPenalty BRState
settings s
s PDFFloat
w = PDFFloat -> Int -> s -> Letter s
forall s. PDFFloat -> Int -> s -> Letter s
FlaggedPenalty PDFFloat
w (BRState -> Int
hyphenPenaltyValue BRState
settings) s
s

kernBox :: s -> PDFFloat -> Letter s
kernBox :: s -> PDFFloat -> Letter s
kernBox s
s PDFFloat
w = PDFFloat -> Maybe s -> Letter s
forall s. PDFFloat -> Maybe s -> Letter s
Kern PDFFloat
w (s -> Maybe s
forall a. a -> Maybe a
Just s
s)