{-# LANGUAGE MultiParamTypeClasses #-}
---------------------------------------------------------
-- |
-- Copyright   : (c) 2006-2016, alpheccar.org
-- License     : BSD-style
--
-- Maintainer  : misc@NOSPAMalpheccar.org
-- Stability   : experimental
-- Portability : portable
--
-- Standard styles for typesettings
---------------------------------------------------------
-- #hide
module Graphics.PDF.Typesetting.StandardStyle(
 -- * Styles
   StandardStyle(..)
 , StandardParagraphStyle(..)
 ) where
     
import Graphics.PDF.Colors
import Graphics.PDF.Text
import Graphics.PDF.Typesetting.Vertical
import Graphics.PDF.Typesetting.Box
     
-- | Standard styles for sentences
data StandardStyle = Font PDFFont Color Color

-- | Standard styles for paragraphs
data StandardParagraphStyle = NormalParagraph


instance ComparableStyle StandardStyle where
  isSameStyleAs :: StandardStyle -> StandardStyle -> Bool
isSameStyleAs (Font PDFFont
a Color
sca Color
fca) (Font PDFFont
b Color
scb Color
fcb) = PDFFont
a PDFFont -> PDFFont -> Bool
forall a. Eq a => a -> a -> Bool
== PDFFont
b Bool -> Bool -> Bool
&& Color
sca Color -> Color -> Bool
forall a. Eq a => a -> a -> Bool
== Color
scb Bool -> Bool -> Bool
&& Color
fca Color -> Color -> Bool
forall a. Eq a => a -> a -> Bool
== Color
fcb
  --isSameStyleAs _ _ = False
    
instance ComparableStyle StandardParagraphStyle where
  isSameStyleAs :: StandardParagraphStyle -> StandardParagraphStyle -> Bool
isSameStyleAs StandardParagraphStyle
NormalParagraph StandardParagraphStyle
NormalParagraph = Bool
True 
  
instance Style StandardStyle where
    textStyle :: StandardStyle -> TextStyle
textStyle (Font PDFFont
a Color
sc Color
fc) = PDFFont
-> Color
-> Color
-> TextMode
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> PDFFloat
-> TextStyle
TextStyle PDFFont
a Color
sc Color
fc TextMode
FillText PDFFloat
1.0 PDFFloat
1.0 PDFFloat
1.0 PDFFloat
1.0 

instance ParagraphStyle StandardParagraphStyle StandardStyle