{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
module Graphics.PDF.Typesetting.Box (
Box(..)
, DisplayableBox(..)
, AnyBox(..)
, Style(..)
, TextStyle(..)
, StyleFunction(..)
, BoxDimension
, DrawBox
, ComparableStyle(..)
, mkDrawBox
, styleFont
) where
import Graphics.PDF.LowLevel.Types
import Graphics.PDF.Draw
import Graphics.PDF.Text
import Graphics.PDF.Shapes
import Graphics.PDF.Coordinates
import Graphics.PDF.Fonts.Font
mkDrawBox :: Draw () -> DrawBox
mkDrawBox :: Draw () -> DrawBox
mkDrawBox Draw ()
d = Draw () -> DrawBox
DrawBox Draw ()
d
newtype DrawBox = DrawBox (Draw())
instance Box DrawBox where
boxWidth :: DrawBox -> PDFFloat
boxWidth DrawBox
_ = PDFFloat
0
boxHeight :: DrawBox -> PDFFloat
boxHeight DrawBox
_ = PDFFloat
0
boxDescent :: DrawBox -> PDFFloat
boxDescent DrawBox
_ = PDFFloat
0
instance DisplayableBox DrawBox where
strokeBox :: DrawBox -> PDFFloat -> PDFFloat -> Draw ()
strokeBox (DrawBox Draw ()
a) PDFFloat
x PDFFloat
y = do
Draw () -> Draw ()
forall a. Draw a -> Draw a
withNewContext (Draw () -> Draw ()) -> Draw () -> Draw ()
forall a b. (a -> b) -> a -> b
$ do
Matrix -> Draw ()
applyMatrix (Matrix -> Draw ()) -> Matrix -> Draw ()
forall a b. (a -> b) -> a -> b
$ Point -> Matrix
translate (PDFFloat
x PDFFloat -> PDFFloat -> Point
forall a. a -> a -> Complex a
:+ PDFFloat
y)
Draw ()
a
instance Show DrawBox where
show :: DrawBox -> String
show DrawBox
_ = String
"DrawBox"
type BoxDimension = (PDFFloat,PDFFloat,PDFFloat)
data TextStyle = TextStyle { TextStyle -> PDFFont
textFont :: !PDFFont
, TextStyle -> Color
textStrokeColor :: !Color
, TextStyle -> Color
textFillColor :: !Color
, TextStyle -> TextMode
textMode :: !TextMode
, TextStyle -> PDFFloat
penWidth :: !PDFFloat
, TextStyle -> PDFFloat
scaleSpace :: !PDFFloat
, TextStyle -> PDFFloat
scaleDilatation :: !PDFFloat
, TextStyle -> PDFFloat
scaleCompression :: !PDFFloat
}
deriving(TextStyle -> TextStyle -> Bool
(TextStyle -> TextStyle -> Bool)
-> (TextStyle -> TextStyle -> Bool) -> Eq TextStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextStyle -> TextStyle -> Bool
== :: TextStyle -> TextStyle -> Bool
$c/= :: TextStyle -> TextStyle -> Bool
/= :: TextStyle -> TextStyle -> Bool
Eq)
data StyleFunction = DrawWord
| DrawGlue
deriving(StyleFunction -> StyleFunction -> Bool
(StyleFunction -> StyleFunction -> Bool)
-> (StyleFunction -> StyleFunction -> Bool) -> Eq StyleFunction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StyleFunction -> StyleFunction -> Bool
== :: StyleFunction -> StyleFunction -> Bool
$c/= :: StyleFunction -> StyleFunction -> Bool
/= :: StyleFunction -> StyleFunction -> Bool
Eq)
class ComparableStyle a where
isSameStyleAs :: a -> a -> Bool
class ComparableStyle a => Style a where
sentenceStyle :: a
-> Maybe (Rectangle -> Draw b -> Draw ())
sentenceStyle a
_ = Maybe (Rectangle -> Draw b -> Draw ())
forall a. Maybe a
Nothing
wordStyle :: a
-> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ())
wordStyle a
_ = Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ())
forall a. Maybe a
Nothing
textStyle :: a -> TextStyle
updateStyle :: a -> a
updateStyle = a -> a
forall a. a -> a
id
styleHeight :: a -> PDFFloat
styleDescent :: a -> PDFFloat
styleHeight a
a =
let PDFFont AnyFont
f Int
s = TextStyle -> PDFFont
textFont (TextStyle -> PDFFont) -> (a -> TextStyle) -> a -> PDFFont
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (a -> PDFFont) -> a -> PDFFont
forall a b. (a -> b) -> a -> b
$ a
a in
AnyFont -> Int -> PDFFloat
forall f. IsFont f => f -> Int -> PDFFloat
getHeight AnyFont
f Int
s
styleDescent a
a =
let PDFFont AnyFont
f Int
s = TextStyle -> PDFFont
textFont (TextStyle -> PDFFont) -> (a -> TextStyle) -> a -> PDFFont
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> TextStyle
forall a. Style a => a -> TextStyle
textStyle (a -> PDFFont) -> a -> PDFFont
forall a b. (a -> b) -> a -> b
$ a
a in
AnyFont -> Int -> PDFFloat
forall f. IsFont f => f -> Int -> PDFFloat
getDescent AnyFont
f Int
s
styleFont :: Style s => s -> AnyFont
styleFont :: forall s. Style s => s -> AnyFont
styleFont s
style =
let PDFFont AnyFont
n Int
_ = 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
style
in
AnyFont
n
class Box a where
boxWidth :: a
-> PDFFloat
boxHeight :: a -> PDFFloat
boxDescent :: a -> PDFFloat
boxAscent :: a -> PDFFloat
boxAscent a
a = a -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight a
a PDFFloat -> PDFFloat -> PDFFloat
forall a. Num a => a -> a -> a
- a -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent a
a
instance Box BoxDimension where
boxWidth :: BoxDimension -> PDFFloat
boxWidth (PDFFloat
w,PDFFloat
_,PDFFloat
_) = PDFFloat
w
boxHeight :: BoxDimension -> PDFFloat
boxHeight (PDFFloat
_,PDFFloat
h,PDFFloat
_) = PDFFloat
h
boxDescent :: BoxDimension -> PDFFloat
boxDescent (PDFFloat
_,PDFFloat
_,PDFFloat
d) = PDFFloat
d
class DisplayableBox a where
strokeBox :: a
-> PDFFloat
-> PDFFloat
-> Draw ()
instance Box AnyBox where
boxWidth :: AnyBox -> PDFFloat
boxWidth (AnyBox a
a) = a -> PDFFloat
forall a. Box a => a -> PDFFloat
boxWidth a
a
boxHeight :: AnyBox -> PDFFloat
boxHeight (AnyBox a
a) = a -> PDFFloat
forall a. Box a => a -> PDFFloat
boxHeight a
a
boxDescent :: AnyBox -> PDFFloat
boxDescent (AnyBox a
a) = a -> PDFFloat
forall a. Box a => a -> PDFFloat
boxDescent a
a
instance DisplayableBox AnyBox where
strokeBox :: AnyBox -> PDFFloat -> PDFFloat -> Draw ()
strokeBox (AnyBox a
a) = a -> PDFFloat -> PDFFloat -> Draw ()
forall a. DisplayableBox a => a -> PDFFloat -> PDFFloat -> Draw ()
strokeBox a
a
instance Show AnyBox where
show :: AnyBox -> String
show (AnyBox a
a) = a -> String
forall a. Show a => a -> String
show a
a
data AnyBox = forall a. (Show a,Box a, DisplayableBox a) => AnyBox a