{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
module Graphics.PDF.Typesetting.Layout (
Container(..)
, Width
, Height
, VBox(..)
, ParagraphStyle(..)
, VerState(..)
, vglue
, addTo
, isOverfull
, mkContainer
, strokeVBoxes
, containerX
, containerY
, containerWidth
, containerHeight
, containerContentHeight
, containerContentRightBorder
, containerContentLeftBorder
, containerCurrentHeight
, containerContentRectangle
, containerParaTolerance
) where
import Graphics.PDF.LowLevel.Types
import Graphics.PDF.Typesetting.Breaking
import Graphics.PDF.Draw
import Graphics.PDF.Coordinates
import Graphics.PDF.Shapes(Rectangle(..))
import Graphics.PDF.Typesetting.Box
import Data.List(foldl')
import Data.Maybe(isJust,fromJust)
data VerState s = VerState { forall s. VerState s -> (PDFFloat, PDFFloat, PDFFloat)
baselineskip :: !(PDFFloat,PDFFloat,PDFFloat)
, forall s. VerState s -> (PDFFloat, PDFFloat, PDFFloat)
lineskip :: !(PDFFloat,PDFFloat,PDFFloat)
, forall s. VerState s -> PDFFloat
lineskiplimit :: !PDFFloat
, forall s. VerState s -> s
currentParagraphStyle :: !s
}
data VBox ps s = Paragraph Int [Letter s] !(Maybe ps) !BRState
| VBox !PDFFloat !PDFFloat !PDFFloat ![VBox ps s] !(Maybe ps)
| VGlue !PDFFloat !PDFFloat !PDFFloat !(Maybe (PDFFloat,PDFFloat)) !(Maybe ps)
| SomeVBox !PDFFloat !BoxDimension !AnyBox !(Maybe ps)
notGlue :: VBox ps s -> Bool
notGlue :: forall ps s. VBox ps s -> Bool
notGlue (VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_) = Bool
False
notGlue (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_) = Bool
False
notGlue VBox ps s
_ = Bool
True
vglue :: Maybe ps
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> VBox ps s
vglue :: forall ps s.
Maybe ps
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> VBox ps s
vglue Maybe ps
s PDFFloat
h PDFFloat
y PDFFloat
z PDFFloat
width PDFFloat
delta = 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
width PDFFloat
delta ((PDFFloat, PDFFloat) -> Maybe (PDFFloat, PDFFloat)
forall a. a -> Maybe a
Just(PDFFloat
y,PDFFloat
z)) Maybe ps
s
instance Show (VBox ps s) where
show :: VBox ps s -> String
show (VBox PDFFloat
_ PDFFloat
a PDFFloat
_ [VBox ps s]
l Maybe ps
_) = String
"(VBox " 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]
++ [VBox ps s] -> String
forall a. Show a => a -> String
show [VBox ps s]
l String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
show (VGlue PDFFloat
a PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_) = String
"(VGlue " 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
")"
show (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_) = String
"(Paragraph)"
show (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
d AnyBox
t Maybe ps
_) = String
"(SomeVBox " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PDFFloat -> String
forall a. Show a => a -> String
show ((PDFFloat, PDFFloat, PDFFloat) -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight (PDFFloat, PDFFloat, PDFFloat)
d) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ AnyBox -> String
forall a. Show a => a -> String
show AnyBox
t String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
instance MaybeGlue (VBox ps s) where
glueSizeWithRatio :: VBox ps s -> PDFFloat -> PDFFloat
glueSizeWithRatio (VGlue PDFFloat
w PDFFloat
_ PDFFloat
_ (Just(PDFFloat
y,PDFFloat
z)) Maybe ps
_) PDFFloat
r = PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize PDFFloat
w PDFFloat
y PDFFloat
z PDFFloat
r
glueSizeWithRatio VBox ps s
a PDFFloat
_ = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
a
glueY :: VBox ps s -> PDFFloat
glueY (VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ (Just(PDFFloat
y,PDFFloat
_)) Maybe ps
_) = PDFFloat
y
glueY VBox ps s
_ = PDFFloat
0
glueZ :: VBox ps s -> PDFFloat
glueZ (VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ (Just(PDFFloat
_,PDFFloat
z)) Maybe ps
_) = PDFFloat
z
glueZ VBox ps s
_ = PDFFloat
0
instance Box (VBox ps s) where
boxWidth :: VBox ps s -> PDFFloat
boxWidth (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_) = PDFFloat
0
boxWidth (VBox PDFFloat
w PDFFloat
_ PDFFloat
_ [VBox ps s]
_ Maybe ps
_) = PDFFloat
w
boxWidth (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
d AnyBox
_ Maybe ps
_) = (PDFFloat, PDFFloat, PDFFloat) -> PDFFloat
forall a. Box a => a -> PDFFloat
boxWidth (PDFFloat, PDFFloat, PDFFloat)
d
boxWidth (VGlue PDFFloat
_ PDFFloat
w PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_) = PDFFloat
w
boxHeight :: VBox ps s -> PDFFloat
boxHeight (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_) = PDFFloat
0
boxHeight (VBox PDFFloat
_ PDFFloat
h PDFFloat
_ [VBox ps s]
_ Maybe ps
_) = PDFFloat
h
boxHeight (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
d AnyBox
_ Maybe ps
_) = (PDFFloat, PDFFloat, PDFFloat) -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight (PDFFloat, PDFFloat, PDFFloat)
d
boxHeight (VGlue PDFFloat
h PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_) = PDFFloat
h
boxDescent :: VBox ps s -> PDFFloat
boxDescent (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_) = PDFFloat
0
boxDescent (VBox PDFFloat
_ PDFFloat
_ PDFFloat
d [VBox ps s]
_ Maybe ps
_) = PDFFloat
d
boxDescent (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
d AnyBox
_ Maybe ps
_) = (PDFFloat, PDFFloat, PDFFloat) -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent (PDFFloat, PDFFloat, PDFFloat)
d
boxDescent (VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_) = PDFFloat
0
instance (ParagraphStyle ps s) => DisplayableBox (VBox ps s) where
strokeBox :: VBox ps s -> PDFFloat -> PDFFloat -> Draw ()
strokeBox (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_) PDFFloat
_ PDFFloat
_ = () -> Draw ()
forall a. a -> Draw a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
strokeBox b :: VBox ps s
b@(VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
l Maybe ps
_) PDFFloat
x PDFFloat
y'' = [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
strokeVBoxes [VBox ps s]
l PDFFloat
x PDFFloat
y'
where
y' :: PDFFloat
y' = PDFFloat
y'' PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
b
strokeBox (VGlue PDFFloat
h PDFFloat
w PDFFloat
delta Maybe (PDFFloat, PDFFloat)
_ (Just ps
style)) PDFFloat
x PDFFloat
y =
if (Maybe (Rectangle -> Draw ()) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (Rectangle -> Draw ()) -> Bool)
-> (ps -> Maybe (Rectangle -> Draw ())) -> ps -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ps -> Maybe (Rectangle -> Draw ())
forall a s. ParagraphStyle a s => a -> Maybe (Rectangle -> Draw ())
interline (ps -> Bool) -> ps -> Bool
forall a b. (a -> b) -> a -> b
$ ps
style)
then
(Maybe (Rectangle -> Draw ()) -> Rectangle -> Draw ()
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Rectangle -> Draw ()) -> Rectangle -> Draw ())
-> (ps -> Maybe (Rectangle -> Draw ()))
-> ps
-> Rectangle
-> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ps -> Maybe (Rectangle -> Draw ())
forall a s. ParagraphStyle a s => a -> Maybe (Rectangle -> Draw ())
interline (ps -> Rectangle -> Draw ()) -> ps -> Rectangle -> Draw ()
forall a b. (a -> b) -> a -> b
$ ps
style) (Rectangle -> Draw ()) -> Rectangle -> Draw ()
forall a b. (a -> b) -> a -> b
$ Point -> Point -> Rectangle
Rectangle ((PDFFloat
xPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
delta) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
yPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
h)) ((PDFFloat
xPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
wPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
delta) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y)
else
() -> Draw ()
forall a. a -> Draw a
forall (m :: * -> *) a. Monad m => a -> m a
return()
strokeBox (VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_) PDFFloat
_ PDFFloat
_ = () -> Draw ()
forall a. a -> Draw a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
strokeBox (SomeVBox PDFFloat
delta (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
a Maybe ps
_) PDFFloat
x PDFFloat
y = AnyBox -> PDFFloat -> PDFFloat -> Draw ()
forall a. DisplayableBox a => a -> PDFFloat -> PDFFloat -> Draw ()
strokeBox AnyBox
a (PDFFloat
xPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
delta) PDFFloat
y
type Width = PDFFloat
type Height = PDFFloat
data Container ps s = Container PDFFloat PDFFloat Width PDFFloat PDFFloat PDFFloat PDFFloat PDFFloat [VBox ps s]
mkContainer :: PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> Container ps s
mkContainer :: forall ps s.
PDFFloat
-> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> Container ps s
mkContainer PDFFloat
x PDFFloat
y PDFFloat
width PDFFloat
height PDFFloat
tol = PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
forall ps s.
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
Container PDFFloat
x PDFFloat
y PDFFloat
width PDFFloat
height PDFFloat
0 PDFFloat
0 PDFFloat
0 PDFFloat
tol []
containerWidth :: Container ps s -> PDFFloat
containerWidth :: forall ps s. Container ps s -> PDFFloat
containerWidth (Container PDFFloat
_ PDFFloat
_ PDFFloat
w PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_) = PDFFloat
w
containerParaTolerance :: Container ps s -> PDFFloat
containerParaTolerance :: forall ps s. Container ps s -> PDFFloat
containerParaTolerance (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
t [VBox ps s]
_) = PDFFloat
t
containerHeight :: Container ps s -> PDFFloat
containerHeight :: forall ps s. Container ps s -> PDFFloat
containerHeight (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
h PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_) = PDFFloat
h
containerCurrentHeight :: Container ps s -> PDFFloat
containerCurrentHeight :: forall ps s. Container ps s -> PDFFloat
containerCurrentHeight (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
ch PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_) = PDFFloat
ch
containerContentHeight :: Container ps s -> PDFFloat
containerContentHeight :: forall ps s. Container ps s -> PDFFloat
containerContentHeight (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
maxh PDFFloat
h PDFFloat
y PDFFloat
z PDFFloat
_ [VBox ps s]
_) = let 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 in
PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
glueSize PDFFloat
h PDFFloat
y PDFFloat
z PDFFloat
r
containerContentLeftBorder :: Container ps s -> PDFFloat
containerContentLeftBorder :: forall ps s. Container ps s -> PDFFloat
containerContentLeftBorder (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ []) = PDFFloat
0.0
containerContentLeftBorder (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
l) = [PDFFloat] -> PDFFloat
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum ([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 ps s. VBox ps s -> PDFFloat
getBoxDelta ([VBox ps s] -> PDFFloat) -> [VBox ps s] -> PDFFloat
forall a b. (a -> b) -> a -> b
$ [VBox ps s]
l
containerContentRightBorder :: Container ps s -> PDFFloat
containerContentRightBorder :: forall ps s. Container ps s -> PDFFloat
containerContentRightBorder (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ []) = PDFFloat
0.0
containerContentRightBorder (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
l) =
let xmax :: PDFFloat
xmax = [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 ps s. VBox ps s -> PDFFloat
rightBorder ([VBox ps s] -> PDFFloat) -> [VBox ps s] -> PDFFloat
forall a b. (a -> b) -> a -> b
$ [VBox ps s]
l
rightBorder :: VBox ps s -> PDFFloat
rightBorder VBox ps s
x = VBox ps s -> PDFFloat
forall ps s. VBox ps s -> PDFFloat
getBoxDelta VBox ps s
x PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxWidth VBox ps s
x
in
PDFFloat
xmax
containerX :: Container ps s -> PDFFloat
containerX :: forall ps s. Container ps s -> PDFFloat
containerX (Container PDFFloat
x PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_) = PDFFloat
x
containerY :: Container ps s -> PDFFloat
containerY :: forall ps s. Container ps s -> PDFFloat
containerY (Container PDFFloat
_ PDFFloat
y PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_) = PDFFloat
y
containerContentRectangle :: Container ps s -> Rectangle
containerContentRectangle :: forall ps s. Container ps s -> Rectangle
containerContentRectangle Container ps s
c = Point -> Point -> Rectangle
Rectangle ((PDFFloat
xPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
l) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
yPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
th)) ((PDFFloat
xPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
r) PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y)
where
x :: PDFFloat
x = Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerX Container ps s
c
y :: PDFFloat
y = Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerY Container ps s
c
th :: PDFFloat
th = Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerContentHeight Container ps s
c
l :: PDFFloat
l = Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerContentLeftBorder Container ps s
c
r :: PDFFloat
r = Container ps s -> PDFFloat
forall ps s. Container ps s -> PDFFloat
containerContentRightBorder Container ps s
c
getInterlineStyle :: ComparableStyle ps => VBox ps s -> VBox ps s -> Maybe ps
getInterlineStyle :: forall ps s.
ComparableStyle ps =>
VBox ps s -> VBox ps s -> Maybe ps
getInterlineStyle (VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_ (Just ps
s)) (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
_ (Just ps
s')) | ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s' = ps -> Maybe ps
forall a. a -> Maybe a
Just ps
s
| Bool
otherwise = Maybe ps
forall a. Maybe a
Nothing
getInterlineStyle (VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_ (Just ps
s)) (VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_ (Just ps
s')) | ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s' = ps -> Maybe ps
forall a. a -> Maybe a
Just ps
s
| Bool
otherwise = Maybe ps
forall a. Maybe a
Nothing
getInterlineStyle (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
_ (Just ps
s)) (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
_ (Just ps
s')) | ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s' = ps -> Maybe ps
forall a. a -> Maybe a
Just ps
s
| Bool
otherwise = Maybe ps
forall a. Maybe a
Nothing
getInterlineStyle (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
_ (Just ps
s)) (VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_ (Just ps
s')) | ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s' = ps -> Maybe ps
forall a. a -> Maybe a
Just ps
s
| Bool
otherwise = Maybe ps
forall a. Maybe a
Nothing
getInterlineStyle VBox ps s
_ VBox ps s
_ = Maybe ps
forall a. Maybe a
Nothing
interlineGlue :: ComparableStyle ps => VerState ps -> VBox ps s -> VBox ps s -> Maybe (VBox ps s, PDFFloat, PDFFloat)
interlineGlue :: forall ps s.
ComparableStyle ps =>
VerState ps
-> VBox ps s -> VBox ps s -> Maybe (VBox ps s, PDFFloat, PDFFloat)
interlineGlue VerState ps
settings VBox ps s
a VBox ps s
b | VBox ps s -> Bool
forall ps s. VBox ps s -> Bool
notGlue VBox ps s
a Bool -> Bool -> Bool
&& VBox ps s -> Bool
forall ps s. VBox ps s -> Bool
notGlue VBox ps s
b =
let p :: PDFFloat
p = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent VBox ps s
a
h :: PDFFloat
h = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
b PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent VBox ps s
b
(PDFFloat
ba,PDFFloat
by,PDFFloat
bz) = VerState ps -> (PDFFloat, PDFFloat, PDFFloat)
forall s. VerState s -> (PDFFloat, PDFFloat, PDFFloat)
baselineskip VerState ps
settings
(PDFFloat
lw,PDFFloat
ly,PDFFloat
lz) = VerState ps -> (PDFFloat, PDFFloat, PDFFloat)
forall s. VerState s -> (PDFFloat, PDFFloat, PDFFloat)
lineskip VerState ps
settings
li :: PDFFloat
li = VerState ps -> PDFFloat
forall s. VerState s -> PDFFloat
lineskiplimit VerState ps
settings
istyle :: Maybe ps
istyle = VBox ps s -> VBox ps s -> Maybe ps
forall ps s.
ComparableStyle ps =>
VBox ps s -> VBox ps s -> Maybe ps
getInterlineStyle VBox ps s
a VBox ps s
b
theWidth :: PDFFloat
theWidth = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxWidth VBox ps s
a
theDelta :: PDFFloat
theDelta = VBox ps s -> PDFFloat
forall ps s. VBox ps s -> PDFFloat
getBoxDelta VBox ps s
a
in
if PDFFloat
p PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
<= -PDFFloat
1000
then
Maybe (VBox ps s, PDFFloat, PDFFloat)
forall a. Maybe a
Nothing
else
if PDFFloat
ba PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
p PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
h PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
>= PDFFloat
li
then
(VBox ps s, PDFFloat, PDFFloat)
-> Maybe (VBox ps s, PDFFloat, PDFFloat)
forall a. a -> Maybe a
Just ((VBox ps s, PDFFloat, PDFFloat)
-> Maybe (VBox ps s, PDFFloat, PDFFloat))
-> (VBox ps s, PDFFloat, PDFFloat)
-> Maybe (VBox ps s, PDFFloat, PDFFloat)
forall a b. (a -> b) -> a -> b
$ (Maybe ps
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> VBox ps s
forall ps s.
Maybe ps
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> VBox ps s
vglue Maybe ps
istyle (PDFFloat
baPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
pPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
h) PDFFloat
by PDFFloat
bz PDFFloat
theWidth PDFFloat
theDelta,PDFFloat
by,PDFFloat
bz)
else
(VBox ps s, PDFFloat, PDFFloat)
-> Maybe (VBox ps s, PDFFloat, PDFFloat)
forall a. a -> Maybe a
Just ((VBox ps s, PDFFloat, PDFFloat)
-> Maybe (VBox ps s, PDFFloat, PDFFloat))
-> (VBox ps s, PDFFloat, PDFFloat)
-> Maybe (VBox ps s, PDFFloat, PDFFloat)
forall a b. (a -> b) -> a -> b
$ (Maybe ps
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> VBox ps s
forall ps s.
Maybe ps
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> VBox ps s
vglue Maybe ps
istyle PDFFloat
lw PDFFloat
ly PDFFloat
lz PDFFloat
theWidth PDFFloat
theDelta,PDFFloat
ly,PDFFloat
lz)
| Bool
otherwise = Maybe (VBox ps s, PDFFloat, PDFFloat)
forall a. Maybe a
Nothing
addTo :: ComparableStyle ps => VerState ps -> VBox ps s -> Container ps s -> Container ps s
addTo :: forall ps s.
ComparableStyle ps =>
VerState ps -> VBox ps s -> Container ps s -> Container ps s
addTo VerState ps
_ VBox ps s
line (Container PDFFloat
px PDFFloat
py PDFFloat
w PDFFloat
maxh PDFFloat
h PDFFloat
y PDFFloat
z PDFFloat
t []) = PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
forall ps s.
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
Container PDFFloat
px PDFFloat
py PDFFloat
w PDFFloat
maxh ((VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
line)PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+PDFFloat
h) PDFFloat
y PDFFloat
z PDFFloat
t [VBox ps s
line]
addTo VerState ps
settings VBox ps s
line (Container PDFFloat
px PDFFloat
py PDFFloat
w PDFFloat
maxh PDFFloat
h PDFFloat
y PDFFloat
z PDFFloat
t l :: [VBox ps s]
l@(VBox ps s
a:[VBox ps s]
_)) =
case VerState ps
-> VBox ps s -> VBox ps s -> Maybe (VBox ps s, PDFFloat, PDFFloat)
forall ps s.
ComparableStyle ps =>
VerState ps
-> VBox ps s -> VBox ps s -> Maybe (VBox ps s, PDFFloat, PDFFloat)
interlineGlue VerState ps
settings VBox ps s
a VBox ps s
line of
Maybe (VBox ps s, PDFFloat, PDFFloat)
Nothing ->
let h' :: PDFFloat
h' = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
line PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
h
y' :: PDFFloat
y' = PDFFloat
y PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall a. MaybeGlue a => a -> PDFFloat
glueY VBox ps s
line
z' :: PDFFloat
z' = PDFFloat
z PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall a. MaybeGlue a => a -> PDFFloat
glueZ VBox ps s
line
in
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
forall ps s.
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
Container PDFFloat
px PDFFloat
py PDFFloat
w PDFFloat
maxh PDFFloat
h' PDFFloat
y' PDFFloat
z' PDFFloat
t (VBox ps s
lineVBox ps s -> [VBox ps s] -> [VBox ps s]
forall a. a -> [a] -> [a]
:[VBox ps s]
l)
Just (VBox ps s
v,PDFFloat
ny,PDFFloat
nz) ->
let h' :: PDFFloat
h' = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
line PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
h PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
v
y' :: PDFFloat
y' = PDFFloat
y PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
ny PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall a. MaybeGlue a => a -> PDFFloat
glueY VBox ps s
line
z' :: PDFFloat
z' = PDFFloat
z PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
nz PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall a. MaybeGlue a => a -> PDFFloat
glueZ VBox ps s
line
in
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
forall ps s.
PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> [VBox ps s]
-> Container ps s
Container PDFFloat
px PDFFloat
py PDFFloat
w PDFFloat
maxh PDFFloat
h' PDFFloat
y' PDFFloat
z' PDFFloat
t (VBox ps s
lineVBox ps s -> [VBox ps s] -> [VBox ps s]
forall a. a -> [a] -> [a]
:VBox ps s
vVBox ps s -> [VBox ps s] -> [VBox ps s]
forall a. a -> [a] -> [a]
:[VBox ps s]
l)
isOverfull :: Container ps s -> Bool
isOverfull :: forall ps s. Container ps s -> Bool
isOverfull (Container PDFFloat
_ PDFFloat
_ PDFFloat
_ PDFFloat
maxh PDFFloat
h PDFFloat
y PDFFloat
z PDFFloat
_ [VBox ps s]
_) = let r :: PDFFloat
r = PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat -> PDFFloat
dilatationRatio PDFFloat
maxh PDFFloat
h PDFFloat
y PDFFloat
z
in
if PDFFloat
r PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
>= PDFFloat
bigAdjustRatio then PDFFloat
h PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
> PDFFloat
maxh else PDFFloat
r PDFFloat -> PDFFloat -> Bool
forall a. Ord a => a -> a -> Bool
<= -PDFFloat
1
class (ComparableStyle a, Style s) => ParagraphStyle a s | a -> s where
lineWidth :: a
-> PDFFloat
-> Int
-> PDFFloat
linePosition :: a
-> PDFFloat
-> Int
-> PDFFloat
interline :: a
-> Maybe (Rectangle -> Draw ())
interline a
_ = Maybe (Rectangle -> Draw ())
forall a. Maybe a
Nothing
lineWidth a
_ PDFFloat
w Int
_ = PDFFloat
w
linePosition a
_ PDFFloat
_ = PDFFloat -> Int -> PDFFloat
forall a b. a -> b -> a
const PDFFloat
0.0
paragraphChange :: a
-> Int
-> [Letter s]
-> (a,[Letter s])
paragraphChange a
a Int
_ [Letter s]
l = (a
a,[Letter s]
l)
paragraphStyle :: a
-> Maybe (Rectangle -> Draw b -> Draw ())
paragraphStyle a
_ = Maybe (Rectangle -> Draw b -> Draw ())
forall a. Maybe a
Nothing
getBoxDelta :: VBox ps s -> PDFFloat
getBoxDelta :: forall ps s. VBox ps s -> PDFFloat
getBoxDelta (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_) = PDFFloat
0.0
getBoxDelta (VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_ Maybe ps
_) = PDFFloat
0.0
getBoxDelta (VGlue PDFFloat
_ PDFFloat
_ PDFFloat
delta Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_) = PDFFloat
delta
getBoxDelta (SomeVBox PDFFloat
delta (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
_ Maybe ps
_) = PDFFloat
delta
isSameParaStyle :: ComparableStyle ps => ps -> VBox ps s -> Bool
isSameParaStyle :: forall ps s. ComparableStyle ps => ps -> VBox ps s -> Bool
isSameParaStyle ps
s (Paragraph Int
_ [Letter s]
_ (Just ps
s') BRState
_) = ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s'
isSameParaStyle ps
s (VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_ (Just ps
s')) = ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s'
isSameParaStyle ps
s (VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ (Just ps
s')) = ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s'
isSameParaStyle ps
s (SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
_ (Just ps
s')) = ps
s ps -> ps -> Bool
forall a. ComparableStyle a => a -> a -> Bool
`isSameStyleAs` ps
s'
isSameParaStyle ps
_ VBox ps s
_ = Bool
False
recurseStrokeVBoxes :: (ParagraphStyle ps s) => Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
recurseStrokeVBoxes :: forall ps s.
ParagraphStyle ps s =>
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
recurseStrokeVBoxes Int
_ [] PDFFloat
_ PDFFloat
_ = () -> Draw ()
forall a. a -> Draw a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
recurseStrokeVBoxes Int
_ (Paragraph Int
_ [Letter s]
_ Maybe ps
_ BRState
_:[VBox ps s]
_) PDFFloat
_ PDFFloat
_ = () -> Draw ()
forall a. a -> Draw a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
recurseStrokeVBoxes Int
nb (a :: VBox ps s
a@(VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ Maybe ps
_):[VBox ps s]
l) PDFFloat
xa PDFFloat
y = do
let h :: PDFFloat
h = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
a
VBox ps s -> PDFFloat -> PDFFloat -> Draw ()
forall a. DisplayableBox a => a -> PDFFloat -> PDFFloat -> Draw ()
strokeBox VBox ps s
a PDFFloat
xa PDFFloat
y
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
recurseStrokeVBoxes Int
nb [VBox ps s]
l PDFFloat
xa (PDFFloat
yPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
h)
recurseStrokeVBoxes Int
nb (VBox ps s
a:[VBox ps s]
l) PDFFloat
xa PDFFloat
y = do
let h :: PDFFloat
h = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
a
VBox ps s -> PDFFloat -> PDFFloat -> Draw ()
forall a. DisplayableBox a => a -> PDFFloat -> PDFFloat -> Draw ()
strokeBox VBox ps s
a PDFFloat
xa PDFFloat
y
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
recurseStrokeVBoxes (Int
nbInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [VBox ps s]
l PDFFloat
xa (PDFFloat
yPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
h)
drawWithParaStyle :: (ParagraphStyle ps s) => ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
drawWithParaStyle :: forall ps s.
ParagraphStyle ps s =>
ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
drawWithParaStyle ps
style [VBox ps s]
b PDFFloat
xa PDFFloat
y' = do
let ([VBox ps s]
l',[VBox ps s]
l'') = (VBox ps s -> Bool) -> [VBox ps s] -> ([VBox ps s], [VBox ps s])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (ps -> VBox ps s -> Bool
forall ps s. ComparableStyle ps => ps -> VBox ps s -> Bool
isSameParaStyle ps
style) [VBox ps s]
b
h' :: PDFFloat
h' = (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
ny -> PDFFloat
x' PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
ny) PDFFloat
0.0 [VBox ps s]
l'
if (Maybe (Rectangle -> Draw Any -> Draw ()) -> Bool
forall a. Maybe a -> Bool
isJust (Maybe (Rectangle -> Draw Any -> Draw ()) -> Bool)
-> (ps -> Maybe (Rectangle -> Draw Any -> Draw ())) -> ps -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ps -> Maybe (Rectangle -> Draw Any -> Draw ())
forall b. ps -> Maybe (Rectangle -> Draw b -> Draw ())
forall a s b.
ParagraphStyle a s =>
a -> Maybe (Rectangle -> Draw b -> Draw ())
paragraphStyle (ps -> Bool) -> ps -> Bool
forall a b. (a -> b) -> a -> b
$ ps
style)
then do
let xleft :: PDFFloat
xleft = ([PDFFloat] -> PDFFloat
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum ([PDFFloat] -> PDFFloat) -> [PDFFloat] -> PDFFloat
forall a b. (a -> b) -> a -> b
$ PDFFloat
100000PDFFloat -> [PDFFloat] -> [PDFFloat]
forall a. a -> [a] -> [a]
:(VBox ps s -> PDFFloat) -> [VBox ps s] -> [PDFFloat]
forall a b. (a -> b) -> [a] -> [b]
map VBox ps s -> PDFFloat
forall ps s. VBox ps s -> PDFFloat
getBoxDelta [VBox ps s]
l' ) PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
xa
xright :: PDFFloat
xright = ([PDFFloat] -> PDFFloat
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([PDFFloat] -> PDFFloat) -> [PDFFloat] -> PDFFloat
forall a b. (a -> b) -> a -> b
$ PDFFloat
0PDFFloat -> [PDFFloat] -> [PDFFloat]
forall a. a -> [a] -> [a]
:((VBox ps s -> PDFFloat) -> [VBox ps s] -> [PDFFloat]
forall a b. (a -> b) -> [a] -> [b]
map (\VBox ps s
x -> VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxWidth VBox ps s
x PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ VBox ps s -> PDFFloat
forall ps s. VBox ps s -> PDFFloat
getBoxDelta VBox ps s
x) [VBox ps s]
l')) PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
+ PDFFloat
xa
(Maybe (Rectangle -> Draw () -> Draw ())
-> Rectangle -> Draw () -> Draw ()
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (Rectangle -> Draw () -> Draw ())
-> Rectangle -> Draw () -> Draw ())
-> (ps -> Maybe (Rectangle -> Draw () -> Draw ()))
-> ps
-> Rectangle
-> Draw ()
-> Draw ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ps -> Maybe (Rectangle -> Draw () -> Draw ())
forall b. ps -> Maybe (Rectangle -> Draw b -> Draw ())
forall a s b.
ParagraphStyle a s =>
a -> Maybe (Rectangle -> Draw b -> Draw ())
paragraphStyle (ps -> Rectangle -> Draw () -> Draw ())
-> ps -> Rectangle -> Draw () -> Draw ()
forall a b. (a -> b) -> a -> b
$ ps
style) (Point -> Point -> Rectangle
Rectangle (PDFFloat
xleft PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ (PDFFloat
y'PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
h')) (PDFFloat
xright PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y')) (Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
recurseStrokeVBoxes Int
1 [VBox ps s]
l' PDFFloat
xa PDFFloat
y')
else
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
Int -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
recurseStrokeVBoxes Int
1 [VBox ps s]
l' PDFFloat
xa PDFFloat
y'
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
strokeVBoxes [VBox ps s]
l'' PDFFloat
xa (PDFFloat
y' PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- PDFFloat
h')
strokeVBoxes :: (ParagraphStyle ps s) => [VBox ps s]
-> PDFFloat
-> PDFFloat
-> Draw ()
strokeVBoxes :: forall ps s.
ParagraphStyle ps s =>
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
strokeVBoxes [] PDFFloat
_ PDFFloat
_ = () -> Draw ()
forall a. a -> Draw a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
strokeVBoxes b :: [VBox ps s]
b@((Paragraph Int
_ [Letter s]
_ (Just ps
s') BRState
_):[VBox ps s]
_) PDFFloat
xa PDFFloat
y = ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
drawWithParaStyle ps
s' [VBox ps s]
b PDFFloat
xa PDFFloat
y
strokeVBoxes b :: [VBox ps s]
b@((VBox PDFFloat
_ PDFFloat
_ PDFFloat
_ [VBox ps s]
_ (Just ps
s')):[VBox ps s]
_) PDFFloat
xa PDFFloat
y = ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
drawWithParaStyle ps
s' [VBox ps s]
b PDFFloat
xa PDFFloat
y
strokeVBoxes b :: [VBox ps s]
b@((VGlue PDFFloat
_ PDFFloat
_ PDFFloat
_ Maybe (PDFFloat, PDFFloat)
_ (Just ps
s')):[VBox ps s]
_) PDFFloat
xa PDFFloat
y = ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
drawWithParaStyle ps
s' [VBox ps s]
b PDFFloat
xa PDFFloat
y
strokeVBoxes b :: [VBox ps s]
b@((SomeVBox PDFFloat
_ (PDFFloat, PDFFloat, PDFFloat)
_ AnyBox
_ (Just ps
s')):[VBox ps s]
_) PDFFloat
xa PDFFloat
y = ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
ps -> [VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
drawWithParaStyle ps
s' [VBox ps s]
b PDFFloat
xa PDFFloat
y
strokeVBoxes (VBox ps s
a:[VBox ps s]
l) PDFFloat
xa PDFFloat
y =
do
let h :: PDFFloat
h = VBox ps s -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight VBox ps s
a
VBox ps s -> PDFFloat -> PDFFloat -> Draw ()
forall a. DisplayableBox a => a -> PDFFloat -> PDFFloat -> Draw ()
strokeBox VBox ps s
a PDFFloat
xa PDFFloat
y
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
forall ps s.
ParagraphStyle ps s =>
[VBox ps s] -> PDFFloat -> PDFFloat -> Draw ()
strokeVBoxes [VBox ps s]
l PDFFloat
xa (PDFFloat
yPDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
-PDFFloat
h)