module Graphics.PDF.Typesetting.Box (
    Box(..)
  , DisplayableBox(..)
  , AnyBox(..)
  , Style(..)
  , TextStyle(..)
  , StyleFunction(..)
  , BoxDimension
  , DrawBox
  , ComparableStyle(..)
  , mkDrawBox
 ) where
     
import Graphics.PDF.LowLevel.Types
import Graphics.PDF.Draw
import Graphics.PDF.Text
import Graphics.PDF.Shapes
import Graphics.PDF.Coordinates
mkDrawBox :: Draw () -> DrawBox
mkDrawBox d = DrawBox d
newtype DrawBox = DrawBox (Draw())
instance Box DrawBox where
    boxWidth _ = 0
    boxHeight _ = 0
    boxDescent _ = 0
    
instance DisplayableBox DrawBox where
    strokeBox (DrawBox a) x y = do
        withNewContext $ do
            applyMatrix $ translate (x :+ y)
            a
    
instance Show DrawBox where
    show _ = "DrawBox"
type BoxDimension = (PDFFloat,PDFFloat,PDFFloat)
data TextStyle = TextStyle { textFont :: !PDFFont
                           , textStrokeColor :: !Color
                           , textFillColor :: !Color
                           , textMode :: !TextMode
                           , penWidth :: !PDFFloat
                           , scaleSpace :: !PDFFloat 
                           , scaleDilatation :: !PDFFloat 
                           , scaleCompression :: !PDFFloat 
                           }
                           deriving(Eq)
             
data StyleFunction = DrawWord 
                   | DrawGlue 
                   deriving(Eq)  
                   
class ComparableStyle a where   
    isSameStyleAs :: a -> a -> Bool                     
                  
class ComparableStyle a => Style a where
    
    sentenceStyle :: a 
                  -> Maybe (Rectangle -> Draw b -> Draw ()) 
    sentenceStyle _ = Nothing
    
    wordStyle :: a 
              -> Maybe (Rectangle -> StyleFunction -> Draw b -> Draw ()) 
    wordStyle _ = Nothing
    textStyle :: a -> TextStyle
    
    updateStyle :: a -> a
    updateStyle = id
    
    
    
    
    
    
    styleHeight :: a -> PDFFloat
    
    
    
    
    
    
    styleDescent :: a -> PDFFloat
    styleHeight = getHeight . textFont . textStyle 
    styleDescent = getDescent . textFont . textStyle 
class Box a where
     
     boxWidth :: a 
              -> PDFFloat 
              
     
     boxHeight :: a -> PDFFloat
     
     boxDescent :: a -> PDFFloat
     
     boxAscent :: a -> PDFFloat
     boxAscent a = boxHeight a  boxDescent a
     
instance Box BoxDimension where
    boxWidth (w,_,_) = w
    boxHeight (_,h,_) = h
    boxDescent (_,_,d) = d
class DisplayableBox a where
     
     strokeBox :: a 
               -> PDFFloat 
               -> PDFFloat 
               -> Draw ()
    
instance Box AnyBox where
    boxWidth (AnyBox a)  = boxWidth a
    boxHeight (AnyBox a) = boxHeight a
    boxDescent (AnyBox a) = boxDescent a
instance DisplayableBox AnyBox where
    strokeBox (AnyBox a)  = strokeBox a
  
instance Show AnyBox where
    show (AnyBox a)  = show a
    
data AnyBox = forall a. (Show a,Box a, DisplayableBox a) => AnyBox a