module Graphics.PDF.Typesetting.Vertical (
mkVboxWithRatio
, vglue
, defaultVerState
, ParagraphStyle(..)
, VerState(..)
, fillContainer
, mkContainer
, VBox(..)
) where
import Graphics.PDF.LowLevel.Types
import Graphics.PDF.Typesetting.Breaking
import Graphics.PDF.Typesetting.Horizontal(horizontalPostProcess,HBox)
import Graphics.PDF.Draw
import Graphics.PDF.Typesetting.Box
import Data.List(foldl')
import Graphics.PDF.Typesetting.Layout
defaultVerState :: s -> VerState s
defaultVerState :: forall s. s -> VerState s
defaultVerState s
s = VerState { baselineskip :: (PDFFloat, PDFFloat, PDFFloat)
baselineskip = (PDFFloat
12,PDFFloat
0.17,PDFFloat
0.0)
, lineskip :: (PDFFloat, PDFFloat, PDFFloat)
lineskip = (PDFFloat
3.0,PDFFloat
0.33,PDFFloat
0.0)
, lineskiplimit :: PDFFloat
lineskiplimit = PDFFloat
2
, currentParagraphStyle :: s
currentParagraphStyle = s
s
}
mkVboxWithRatio :: PDFFloat
-> [VBox ps s]
-> VBox ps s
mkVboxWithRatio :: forall ps s. PDFFloat -> [VBox ps s] -> VBox ps s
mkVboxWithRatio PDFFloat
_ [] = [Char] -> VBox ps s
forall a. HasCallStack => [Char] -> a
error [Char]
"Cannot make an empty vbox"
mkVboxWithRatio PDFFloat
r [VBox ps s]
l =
let w :: PDFFloat
w = (PDFFloat -> VBox ps s -> PDFFloat)
-> PDFFloat -> [VBox ps s] -> PDFFloat
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\PDFFloat
x VBox ps s
y -> PDFFloat
x PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat -> PDFFloat
forall a. MaybeGlue a => a -> PDFFloat -> PDFFloat
glueSizeWithRatio VBox ps s
y PDFFloat
r) PDFFloat
0.0 [VBox ps s]
l
h :: PDFFloat
h = [PDFFloat] -> PDFFloat
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([PDFFloat] -> PDFFloat)
-> ([VBox ps s] -> [PDFFloat]) -> [VBox ps s] -> PDFFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VBox ps s -> PDFFloat) -> [VBox ps s] -> [PDFFloat]
forall a b. (a -> b) -> [a] -> [b]
map VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight ([VBox ps s] -> PDFFloat) -> [VBox ps s] -> PDFFloat
forall a b. (a -> b) -> a -> b
$ [VBox ps s]
l
d :: PDFFloat
d = [PDFFloat] -> PDFFloat
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([PDFFloat] -> PDFFloat)
-> ([VBox ps s] -> [PDFFloat]) -> [VBox ps s] -> PDFFloat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VBox ps s -> PDFFloat) -> [VBox ps s] -> [PDFFloat]
forall a b. (a -> b) -> [a] -> [b]
map VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent ([VBox ps s] -> PDFFloat) -> [VBox ps s] -> PDFFloat
forall a b. (a -> b) -> a -> b
$ [VBox ps s]
l
addBox :: VBox ps s -> VBox ps s -> VBox ps s
addBox (VGlue PDFFloat
gw PDFFloat
gh PDFFloat
gdelta (Just(PDFFloat
y,PDFFloat
z)) Maybe ps
s) (VBox PDFFloat
w' PDFFloat
h' PDFFloat
d' [VBox ps s]
l' Maybe ps
s') = PDFFloat
-> PDFFloat -> PDFFloat -> [VBox ps s] -> Maybe ps -> VBox ps s
forall ps s.
PDFFloat
-> PDFFloat -> PDFFloat -> [VBox ps s] -> Maybe ps -> VBox ps s
VBox PDFFloat
w' PDFFloat
h' PDFFloat
d' (PDFFloat
-> PDFFloat
-> PDFFloat
-> Maybe (PDFFloat, PDFFloat)
-> Maybe ps
-> VBox ps s
forall ps s.
PDFFloat
-> PDFFloat
-> PDFFloat
-> Maybe (PDFFloat, PDFFloat)
-> Maybe ps
-> VBox ps s
VGlue (PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize PDFFloat
gw PDFFloat
y PDFFloat
z PDFFloat
r) PDFFloat
gh PDFFloat
gdelta Maybe (PDFFloat, PDFFloat)
forall a. Maybe a
Nothing Maybe ps
sVBox ps s -> [VBox ps s] -> [VBox ps s]
forall a. a -> [a] -> [a]
:[VBox ps s]
l') Maybe ps
s'
addBox VBox ps s
a (VBox PDFFloat
w' PDFFloat
h' PDFFloat
d' [VBox ps s]
l' Maybe ps
s') = PDFFloat
-> PDFFloat -> PDFFloat -> [VBox ps s] -> Maybe ps -> VBox ps s
forall ps s.
PDFFloat
-> PDFFloat -> PDFFloat -> [VBox ps s] -> Maybe ps -> VBox ps s
VBox PDFFloat
w' PDFFloat
h' PDFFloat
d' (VBox ps s
aVBox ps s -> [VBox ps s] -> [VBox ps s]
forall a. a -> [a] -> [a]
:[VBox ps s]
l') Maybe ps
s'
addBox VBox ps s
_ VBox ps s
_ = [Char] -> VBox ps s
forall a. HasCallStack => [Char] -> a
error [Char]
"We can add boxes only to an horizontal list"
in
(VBox ps s -> VBox ps s -> VBox ps s)
-> VBox ps s -> [VBox ps s] -> VBox ps s
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr VBox ps s -> VBox ps s -> VBox ps s
forall {ps} {s}. VBox ps s -> VBox ps s -> VBox ps s
addBox (PDFFloat
-> PDFFloat -> PDFFloat -> [VBox ps s] -> Maybe ps -> VBox ps s
forall ps s.
PDFFloat
-> PDFFloat -> PDFFloat -> [VBox ps s] -> Maybe ps -> VBox ps s
VBox PDFFloat
w PDFFloat
h PDFFloat
d [] Maybe ps
forall a. Maybe a
Nothing) [VBox ps s]
l
dilateVboxes :: PDFFloat -> VBox ps s -> VBox ps s
dilateVboxes :: forall ps s. PDFFloat -> VBox ps s -> VBox ps s
dilateVboxes PDFFloat
r g :: VBox ps s
g@(VGlue PDFFloat
_ PDFFloat
w PDFFloat
l (Just(PDFFloat
_,PDFFloat
_)) Maybe ps
s) =
let h' :: PDFFloat
h' = VBox ps s -> PDFFloat -> PDFFloat
forall a. MaybeGlue a => a -> PDFFloat -> PDFFloat
glueSizeWithRatio VBox ps s
g PDFFloat
r
in
PDFFloat
-> PDFFloat
-> PDFFloat
-> Maybe (PDFFloat, PDFFloat)
-> Maybe ps
-> VBox ps s
forall ps s.
PDFFloat
-> PDFFloat
-> PDFFloat
-> Maybe (PDFFloat, PDFFloat)
-> Maybe ps
-> VBox ps s
VGlue PDFFloat
h' PDFFloat
w PDFFloat
l Maybe (PDFFloat, PDFFloat)
forall a. Maybe a
Nothing Maybe ps
s
dilateVboxes PDFFloat
_ g :: VBox ps s
g@(VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
Nothing Maybe ps
_) = VBox ps s
g
dilateVboxes PDFFloat
_ VBox ps s
a = VBox ps s
a
drawContainer :: ParagraphStyle ps s => Container ps s
-> Draw ()
drawContainer :: forall ps s. ParagraphStyle ps s => Container ps s -> Draw ()
drawContainer (Container PDFFloat
px PDFFloat
py PDFFloat
_ PDFFloat
maxh PDFFloat
h PDFFloat
y PDFFloat
z PDFFloat
_ [VBox ps s]
oldl) =
let l' :: [VBox ps s]
l' = [VBox ps s] -> [VBox ps s]
forall a. [a] -> [a]
reverse [VBox ps s]
oldl
r :: PDFFloat
r = PDFFloat -> PDFFloat -> PDFFloat
forall a. Ord a => a -> a -> a
min (PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
dilatationRatio PDFFloat
maxh PDFFloat
h PDFFloat
y PDFFloat
z) PDFFloat
2.0
l'' :: [VBox ps s]
l'' = (VBox ps s -> VBox ps s) -> [VBox ps s] -> [VBox ps s]
forall a b. (a -> b) -> [a] -> [b]
map (PDFFloat -> VBox ps s -> VBox ps s
forall ps s. PDFFloat -> VBox ps s -> VBox ps s
dilateVboxes PDFFloat
r) [VBox ps s]
l'
in
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
strokeVBoxes [VBox ps s]
l'' PDFFloat
px PDFFloat
py
createPara :: Int
-> Maybe ps
-> BRState
-> [Letter s]
-> [VBox ps s]
createPara :: forall ps s.
Int -> Maybe ps -> BRState -> [Letter s] -> [VBox ps s]
createPara Int
_ Maybe ps
_ BRState
_ [] = []
createPara Int
lineOffset Maybe ps
style BRState
paraSettings [Letter s]
l = [Int -> [Letter s] -> Maybe ps -> BRState -> VBox ps s
forall ps s. Int -> [Letter s] -> Maybe ps -> BRState -> VBox ps s
Paragraph Int
lineOffset ([Letter s] -> [Letter s]
forall s. [Letter s] -> [Letter s]
simplify [Letter s]
l) Maybe ps
style BRState
paraSettings]
addParaLine :: (ParagraphStyle ps s, ComparableStyle ps) => VerState ps
-> Maybe ps
-> BRState
-> Container ps s
-> [((HBox s,[Letter s]),Int)]
-> Either (Draw (),Container ps s,[VBox ps s]) (Container ps s)
addParaLine :: forall ps s.
(ParagraphStyle ps s, ComparableStyle ps) =>
VerState ps
-> Maybe ps
-> BRState
-> Container ps s
-> [((HBox s, [Letter s]), Int)]
-> Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
addParaLine VerState ps
_ Maybe ps
_ BRState
_ Container ps s
c [] = Container ps s
-> Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
forall a b. b -> Either a b
Right Container ps s
c
addParaLine VerState ps
verstate Maybe ps
style BRState
paraSettings Container ps s
c (((HBox s
line,[Letter s]
remainingPar),Int
lineNb):[((HBox s, [Letter s]), Int)]
l) =
let c' :: Container ps s
c' = VerState ps -> VBox ps s -> Container ps s -> Container ps s
forall ps s.
ComparableStyle ps =>
VerState ps -> VBox ps s -> Container ps s -> Container ps s
addTo VerState ps
verstate (Maybe ps -> PDFFloat -> HBox s -> Int -> VBox ps s
forall ps s.
ParagraphStyle ps s =>
Maybe ps -> PDFFloat -> HBox s -> Int -> VBox ps s
toVBoxes Maybe ps
style (Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerWidth Container ps s
c) HBox s
line Int
lineNb) Container ps s
c
in
if Container ps s -> Bool
forall ps s. Container ps s -> Bool
isOverfull Container ps s
c'
then
(Draw (), Container ps s, [VBox ps s])
-> Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
forall a b. a -> Either a b
Left (Container ps s -> Draw ()
forall ps s. ParagraphStyle ps s => Container ps s -> Draw ()
drawContainer Container ps s
c,Container ps s
c,Int -> Maybe ps -> BRState -> [Letter s] -> [VBox ps s]
forall ps s.
Int -> Maybe ps -> BRState -> [Letter s] -> [VBox ps s]
createPara Int
lineNb Maybe ps
style BRState
paraSettings [Letter s]
remainingPar)
else
VerState ps
-> Maybe ps
-> BRState
-> Container ps s
-> [((HBox s, [Letter s]), Int)]
-> Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
forall ps s.
(ParagraphStyle ps s, ComparableStyle ps) =>
VerState ps
-> Maybe ps
-> BRState
-> Container ps s
-> [((HBox s, [Letter s]), Int)]
-> Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
addParaLine VerState ps
verstate Maybe ps
style BRState
paraSettings Container ps s
c' [((HBox s, [Letter s]), Int)]
l
fillContainer :: (ParagraphStyle ps s, ComparableStyle ps) => VerState ps
-> Container ps s
-> [VBox ps s]
-> (Draw(),Container ps s,[VBox ps s])
fillContainer :: forall ps s.
(ParagraphStyle ps s, ComparableStyle ps) =>
VerState ps
-> Container ps s
-> [VBox ps s]
-> (Draw (), Container ps s, [VBox ps s])
fillContainer VerState ps
_ Container ps s
c [] = (Container ps s -> Draw ()
forall ps s. ParagraphStyle ps s => Container ps s -> Draw ()
drawContainer Container ps s
c,Container ps s
c,[])
fillContainer VerState ps
verstate Container ps s
c para :: [VBox ps s]
para@(Paragraph Int
lineOffset [Letter s]
l Maybe ps
style BRState
paraSettings:[VBox ps s]
l') =
if Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerContentHeight Container ps s
c PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
> Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerHeight Container ps s
c PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerParaTolerance Container ps s
c
then
(Container ps s -> Draw ()
forall ps s. ParagraphStyle ps s => Container ps s -> Draw ()
drawContainer Container ps s
c,Container ps s
c,[VBox ps s]
para)
else
let ([(PDFFloat, [Letter s], [Letter s])]
fl,Maybe ps
newStyle) = case Maybe ps
style of
Maybe ps
Nothing -> (BRState
-> (Int -> PDFFloat)
-> [Letter s]
-> [(PDFFloat, [Letter s], [Letter s])]
forall s.
Style s =>
BRState
-> (Int -> PDFFloat)
-> [Letter s]
-> [(PDFFloat, [Letter s], [Letter s])]
formatList BRState
paraSettings (PDFFloat -> Int -> PDFFloat
forall a b. a -> b -> a
const (PDFFloat -> Int -> PDFFloat) -> PDFFloat -> Int -> PDFFloat
forall a b. (a -> b) -> a -> b
$ Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerWidth Container ps s
c) [Letter s]
l,Maybe ps
forall a. Maybe a
Nothing)
Just ps
aStyle -> let (ps
style',[Letter s]
nl) = ps -> Int -> [Letter s] -> (ps, [Letter s])
forall a s.
ParagraphStyle a s =>
a -> Int -> [Letter s] -> (a, [Letter s])
paragraphChange ps
aStyle Int
lineOffset [Letter s]
l
in
(BRState
-> (Int -> PDFFloat)
-> [Letter s]
-> [(PDFFloat, [Letter s], [Letter s])]
forall s.
Style s =>
BRState
-> (Int -> PDFFloat)
-> [Letter s]
-> [(PDFFloat, [Letter s], [Letter s])]
formatList BRState
paraSettings (\Int
nb -> (ps -> PDFFloat -> Int -> PDFFloat
forall a s. ParagraphStyle a s => a -> PDFFloat -> Int -> PDFFloat
lineWidth ps
style') (Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerWidth Container ps s
c) (Int
nbInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lineOffset) ) [Letter s]
nl,ps -> Maybe ps
forall a. a -> Maybe a
Just ps
style')
newLines :: [(HBox s, [Letter s])]
newLines = [(PDFFloat, [Letter s], [Letter s])] -> [(HBox s, [Letter s])]
forall s.
Style s =>
[(PDFFloat, [Letter s], [Letter s])] -> [(HBox s, [Letter s])]
horizontalPostProcess [(PDFFloat, [Letter s], [Letter s])]
fl
r :: Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
r = VerState ps
-> Maybe ps
-> BRState
-> Container ps s
-> [((HBox s, [Letter s]), Int)]
-> Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
forall ps s.
(ParagraphStyle ps s, ComparableStyle ps) =>
VerState ps
-> Maybe ps
-> BRState
-> Container ps s
-> [((HBox s, [Letter s]), Int)]
-> Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
addParaLine VerState ps
verstate Maybe ps
newStyle BRState
paraSettings Container ps s
c ([(HBox s, [Letter s])] -> [Int] -> [((HBox s, [Letter s]), Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [(HBox s, [Letter s])]
newLines [Int
1..])
in
case Either (Draw (), Container ps s, [VBox ps s]) (Container ps s)
r of
Left (Draw ()
d,Container ps s
c',[VBox ps s]
remPara) -> (Draw ()
d,Container ps s
c',[VBox ps s]
remPara [VBox ps s] -> [VBox ps s] -> [VBox ps s]
forall a. [a] -> [a] -> [a]
++ [VBox ps s]
l')
Right Container ps s
c' -> VerState ps
-> Container ps s
-> [VBox ps s]
-> (Draw (), Container ps s, [VBox ps s])
forall ps s.
(ParagraphStyle ps s, ComparableStyle ps) =>
VerState ps
-> Container ps s
-> [VBox ps s]
-> (Draw (), Container ps s, [VBox ps s])
fillContainer VerState ps
verstate Container ps s
c' [VBox ps s]
l'
fillContainer VerState ps
verstate Container ps s
c oldl :: [VBox ps s]
oldl@(VBox ps s
a:[VBox ps s]
l) =
let c' :: Container ps s
c' = VerState ps -> VBox ps s -> Container ps s -> Container ps s
forall ps s.
ComparableStyle ps =>
VerState ps -> VBox ps s -> Container ps s -> Container ps s
addTo VerState ps
verstate VBox ps s
a Container ps s
c
in
if Container ps s -> Bool
forall ps s. Container ps s -> Bool
isOverfull Container ps s
c'
then
(Container ps s -> Draw ()
forall ps s. ParagraphStyle ps s => Container ps s -> Draw ()
drawContainer Container ps s
c,Container ps s
c,[VBox ps s]
oldl)
else
VerState ps
-> Container ps s
-> [VBox ps s]
-> (Draw (), Container ps s, [VBox ps s])
forall ps s.
(ParagraphStyle ps s, ComparableStyle ps) =>
VerState ps
-> Container ps s
-> [VBox ps s]
-> (Draw (), Container ps s, [VBox ps s])
fillContainer VerState ps
verstate Container ps s
c' [VBox ps s]
l
toVBoxes :: (ParagraphStyle ps s) => Maybe ps
-> PDFFloat
-> HBox s
-> Int
-> VBox ps s
toVBoxes :: forall ps s.
ParagraphStyle ps s =>
Maybe ps -> PDFFloat -> HBox s -> Int -> VBox ps s
toVBoxes Maybe ps
Nothing PDFFloat
_ HBox s
a Int
_ = PDFFloat
-> (PDFFloat, PDFFloat, PDFFloat)
-> AnyBox
-> Maybe ps
-> VBox ps s
forall ps s.
PDFFloat
-> (PDFFloat, PDFFloat, PDFFloat)
-> AnyBox
-> Maybe ps
-> VBox ps s
SomeVBox PDFFloat
0.0 (HBox s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxWidth HBox s
a,HBox s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight HBox s
a,HBox s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent HBox s
a) (HBox s -> AnyBox
forall a. (Show a, Box a, DisplayableBox a) => a -> AnyBox
AnyBox HBox s
a) Maybe ps
forall a. Maybe a
Nothing
toVBoxes s :: Maybe ps
s@(Just ps
style) PDFFloat
w HBox s
a Int
nb =
let delta :: PDFFloat
delta = (ps -> PDFFloat -> Int -> PDFFloat
forall a s. ParagraphStyle a s => a -> PDFFloat -> Int -> PDFFloat
linePosition ps
style) PDFFloat
w Int
nb in
PDFFloat
-> (PDFFloat, PDFFloat, PDFFloat)
-> AnyBox
-> Maybe ps
-> VBox ps s
forall ps s.
PDFFloat
-> (PDFFloat, PDFFloat, PDFFloat)
-> AnyBox
-> Maybe ps
-> VBox ps s
SomeVBox PDFFloat
delta (HBox s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxWidth HBox s
a,HBox s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight HBox s
a,HBox s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent HBox s
a) (HBox s -> AnyBox
forall a. (Show a, Box a, DisplayableBox a) => a -> AnyBox
AnyBox HBox s
a) Maybe ps
s