{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
---------------------------------------------------------
-- |
-- Copyright   : (c) 2006-2016, alpheccar.org
-- License     : BSD-style
--
-- Maintainer  : misc@NOSPAMalpheccar.org
-- Stability   : experimental
-- Portability : portable
--
-- Box
---------------------------------------------------------
-- #hide
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

-- | Make a drawing box. A box object containing a Draw value
mkDrawBox :: Draw () -> DrawBox
mkDrawBox :: Draw () -> DrawBox
mkDrawBox Draw ()
d = Draw () -> DrawBox
DrawBox Draw ()
d

-- | A box containing a Draw value
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"

-- | Dimension of a box : width, height and descent
type BoxDimension = (PDFFloat,PDFFloat,PDFFloat)

-- | Text style used by PDF operators
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 -- ^ Scaling factor for normal space size (scale also the dilation and compression factors)
                           , TextStyle -> PDFFloat
scaleDilatation :: !PDFFloat -- ^ Scale the dilation factor of glues
                           , TextStyle -> PDFFloat
scaleCompression :: !PDFFloat -- ^ Scale the compression factor of glues
                           }
                           deriving(TextStyle -> TextStyle -> Bool
(TextStyle -> TextStyle -> Bool)
-> (TextStyle -> TextStyle -> Bool) -> Eq TextStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextStyle -> TextStyle -> Bool
$c/= :: TextStyle -> TextStyle -> Bool
== :: TextStyle -> TextStyle -> Bool
$c== :: TextStyle -> TextStyle -> Bool
Eq)
             
-- | What kind of style drawing function is required for a word
-- when word styling is enabled              
data StyleFunction = DrawWord -- ^ Must style a word
                   | DrawGlue -- ^ Must style a glue
                   deriving(StyleFunction -> StyleFunction -> Bool
(StyleFunction -> StyleFunction -> Bool)
-> (StyleFunction -> StyleFunction -> Bool) -> Eq StyleFunction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StyleFunction -> StyleFunction -> Bool
$c/= :: StyleFunction -> StyleFunction -> Bool
== :: StyleFunction -> StyleFunction -> Bool
$c== :: StyleFunction -> StyleFunction -> Bool
Eq)  
                   
-- | Used to compare two style without taking into account the style state
class ComparableStyle a where   
    isSameStyleAs :: a -> a -> Bool                     
                  
-- | Style of text  (sentences and words). Minimum definition textStyle      
class ComparableStyle a => Style a where
    -- ^ Modify the look of a sentence (sequence of words using the same style on a line)
    sentenceStyle :: a -- ^ The style
                  -> Maybe (Rectangle -> Draw b -> Draw ()) -- ^ Function receiving the bounding rectangle and the command for drawing the sentence
    sentenceStyle a
_ = Maybe (Rectangle -> Draw b -> Draw ())
forall a. Maybe a
Nothing

    -- ^ Modify the look of a word
    wordStyle :: a -- ^ The style
              -> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ()) -- ^ Word styling function
    wordStyle a
_ = Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ())
forall a. Maybe a
Nothing
    
    textStyle :: a -> TextStyle

    -- | A style may contain data changed from word to word
    updateStyle :: a -> a
    updateStyle = a -> a
forall a. a -> a
id
    
    -- | A style may change the height of words
    -- 
    -- > Default implementation
    -- > styleHeight = getHeight . textFont . textStyle
    -- 
    styleHeight :: a -> PDFFloat
    
    -- | A style may change the descent of lines
    --
    -- > Default implementation
    -- > styleDescent = getDescent . textFont . textStyle
    --
    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 :: 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


-- | A box is an object with dimensions and used in the typesetting process
class Box a where
     -- | Box width
     boxWidth :: a -- ^ Box
              -> PDFFloat -- ^ Width of the box
              
     -- | Box height
     boxHeight :: a -> PDFFloat
     -- | Distance between box bottom and box baseline
     boxDescent :: a -> PDFFloat
     -- | Distance between box top and box baseline
     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

-- | A box that can be displayed
class DisplayableBox a where
     -- | Draw a box
     strokeBox :: a -- ^ The box
               -> PDFFloat -- ^ Horizontal position
               -> PDFFloat -- ^ Vertical position (top of the box and NOT baseline)
               -> 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