module Graphics.Rendering.Pango.BasicTypes (
  GInt,
  Language(Language),
  emptyLanguage,
  languageFromString,
  FontStyle(..),
  Weight(..),
  Variant(..),
  Stretch(..),
  Underline(..),
  PangoGravity(..),
  PangoGravityHint(..),
  PangoString(PangoString),
  makeNewPangoString,
  withPangoString,
  PangoItem(PangoItem),
  PangoItemRaw(PangoItemRaw),
  makeNewPangoItemRaw,
  withPangoItemRaw,
  GlyphItem(GlyphItem),
  GlyphStringRaw(GlyphStringRaw),
  makeNewGlyphStringRaw,
  PangoLayout(PangoLayout),
  LayoutIter(LayoutIter),
  LayoutIterRaw(LayoutIterRaw),
  makeNewLayoutIterRaw,
  LayoutLine(LayoutLine),
  LayoutLineRaw(LayoutLineRaw),
  makeNewLayoutLineRaw,
  FontDescription(FontDescription),
  makeNewFontDescription,
  PangoAttrList,
  CPangoAttribute,
  ) where
import Control.Monad (liftM)
import Data.IORef ( IORef )
import qualified Data.Text as T (unpack)
import System.Glib.FFI
import System.Glib.UTFString
import Graphics.Rendering.Pango.Types (Font, PangoLayoutRaw)
newtype Language = Language (Ptr (Language)) deriving Eq
type GInt = (CInt)
instance Show Language where
  show (Language ptr)
    | ptr==nullPtr = ""
    | otherwise = T.unpack . unsafePerformIO $ peekUTFString (castPtr ptr)
emptyLanguage :: Language
emptyLanguage = Language nullPtr
languageFromString :: GlibString string => string -> IO Language
languageFromString language = liftM Language $
  withUTFString language pango_language_from_string
data FontStyle = StyleNormal
               | StyleOblique
               | StyleItalic
               deriving (Enum,Eq)
instance Show FontStyle where
  showsPrec _ StyleNormal = shows "normal"
  showsPrec _ StyleOblique = shows "oblique"
  showsPrec _ StyleItalic = shows "italic"
data Weight = WeightThin
            | WeightUltralight
            | WeightLight
            | WeightBook
            | WeightNormal
            | WeightMedium
            | WeightSemibold
            | WeightBold
            | WeightUltrabold
            | WeightHeavy
            | WeightUltraheavy
            deriving (Eq)
instance Enum Weight where
  fromEnum WeightThin = 100
  fromEnum WeightUltralight = 200
  fromEnum WeightLight = 300
  fromEnum WeightBook = 380
  fromEnum WeightNormal = 400
  fromEnum WeightMedium = 500
  fromEnum WeightSemibold = 600
  fromEnum WeightBold = 700
  fromEnum WeightUltrabold = 800
  fromEnum WeightHeavy = 900
  fromEnum WeightUltraheavy = 1000
  toEnum 100 = WeightThin
  toEnum 200 = WeightUltralight
  toEnum 300 = WeightLight
  toEnum 380 = WeightBook
  toEnum 400 = WeightNormal
  toEnum 500 = WeightMedium
  toEnum 600 = WeightSemibold
  toEnum 700 = WeightBold
  toEnum 800 = WeightUltrabold
  toEnum 900 = WeightHeavy
  toEnum 1000 = WeightUltraheavy
  toEnum unmatched = error ("Weight.toEnum: Cannot match " ++ show unmatched)
  succ WeightThin = WeightUltralight
  succ WeightUltralight = WeightLight
  succ WeightLight = WeightBook
  succ WeightBook = WeightNormal
  succ WeightNormal = WeightMedium
  succ WeightMedium = WeightSemibold
  succ WeightSemibold = WeightBold
  succ WeightBold = WeightUltrabold
  succ WeightUltrabold = WeightHeavy
  succ WeightHeavy = WeightUltraheavy
  succ _ = undefined
  pred WeightUltralight = WeightThin
  pred WeightLight = WeightUltralight
  pred WeightBook = WeightLight
  pred WeightNormal = WeightBook
  pred WeightMedium = WeightNormal
  pred WeightSemibold = WeightMedium
  pred WeightBold = WeightSemibold
  pred WeightUltrabold = WeightBold
  pred WeightHeavy = WeightUltrabold
  pred WeightUltraheavy = WeightHeavy
  pred _ = undefined
  enumFromTo x y | fromEnum x == fromEnum y = [ y ]
                 | otherwise = x : enumFromTo (succ x) y
  enumFrom x = enumFromTo x WeightUltraheavy
  enumFromThen _ _ =     error "Enum Weight: enumFromThen not implemented"
  enumFromThenTo _ _ _ =     error "Enum Weight: enumFromThenTo not implemented"
instance Show Weight where
  showsPrec _ WeightUltralight = shows "ultralight"
  showsPrec _ WeightLight = shows "light"
  showsPrec _ WeightNormal = shows "normal"
  showsPrec _ WeightSemibold = shows "semibold"
  showsPrec _ WeightBold = shows "bold"
  showsPrec _ WeightUltrabold = shows "ultrabold"
  showsPrec _ WeightHeavy = shows "heavy"
  showsPrec _ WeightThin = shows "thin"
  showsPrec _ WeightBook = shows "book"
  showsPrec _ WeightMedium = shows "medium"
  showsPrec _ WeightUltraheavy = shows "ultraheavy"
data Variant = VariantNormal
             | VariantSmallCaps
             deriving (Enum,Eq)
instance Show Variant where
  showsPrec _ VariantNormal = shows "normal"
  showsPrec _ VariantSmallCaps = shows "smallcaps"
data Stretch = StretchUltraCondensed
             | StretchExtraCondensed
             | StretchCondensed
             | StretchSemiCondensed
             | StretchNormal
             | StretchSemiExpanded
             | StretchExpanded
             | StretchExtraExpanded
             | StretchUltraExpanded
             deriving (Enum,Eq)
instance Show Stretch where
  showsPrec _ StretchUltraCondensed = shows "ultracondensed"
  showsPrec _ StretchExtraCondensed = shows "extracondensed"
  showsPrec _ StretchCondensed = shows "condensed"
  showsPrec _ StretchSemiCondensed = shows "semicondensed"
  showsPrec _ StretchNormal = shows "normal"
  showsPrec _ StretchSemiExpanded = shows "semiexpanded"
  showsPrec _ StretchExpanded = shows "expanded"
  showsPrec _ StretchExtraExpanded = shows "extraexpanded"
  showsPrec _ StretchUltraExpanded = shows "ultraexpanded"
data Underline = UnderlineNone
               | UnderlineSingle
               | UnderlineDouble
               | UnderlineLow
               | UnderlineError
               deriving (Enum,Eq)
instance Show Underline where
  showsPrec _ UnderlineNone = shows "none"
  showsPrec _ UnderlineSingle = shows "single"
  showsPrec _ UnderlineDouble = shows "double"
  showsPrec _ UnderlineLow = shows "low"
  showsPrec _ UnderlineError = shows "error"
data PangoGravity = PangoGravitySouth
                  | PangoGravityEast
                  | PangoGravityNorth
                  | PangoGravityWest
                  | PangoGravityAuto
                  deriving (Enum,Eq)
instance Show PangoGravity where
  show PangoGravitySouth = "south"
  show PangoGravityEast = "east"
  show PangoGravityNorth = "north"
  show PangoGravityWest = "west"
  show PangoGravityAuto = "auto"
data PangoGravityHint = PangoGravityHintNatural
                      | PangoGravityHintStrong
                      | PangoGravityHintLine
                      deriving (Enum,Eq)
instance Show PangoGravityHint where
  show PangoGravityHintNatural = "natural"
  show PangoGravityHintStrong = "strong"
  show PangoGravityHintLine = "line"
data PangoString = PangoString UTFCorrection CInt (ForeignPtr CChar)
makeNewPangoString :: GlibString string => string -> IO PangoString
makeNewPangoString str = do
  let correct = genUTFOfs str
  (strPtr, len) <- newUTFStringLen str
  let cLen = fromIntegral len
  liftM (PangoString correct cLen) $ newForeignPtr strPtr finalizerFree
withPangoString :: PangoString ->
     (UTFCorrection -> CInt -> Ptr CChar -> IO a) -> IO a
withPangoString (PangoString c l ptr) act = withForeignPtr ptr $ \strPtr ->
  act c l strPtr
newtype GlyphStringRaw = GlyphStringRaw (ForeignPtr (GlyphStringRaw))
makeNewGlyphStringRaw :: Ptr GlyphStringRaw -> IO GlyphStringRaw
makeNewGlyphStringRaw llPtr = do
  liftM GlyphStringRaw $ newForeignPtr llPtr pango_glyph_string_free
foreign import ccall unsafe "&pango_glyph_string_free"
  pango_glyph_string_free :: FinalizerPtr GlyphStringRaw
newtype PangoItemRaw = PangoItemRaw (ForeignPtr (PangoItemRaw))
makeNewPangoItemRaw :: Ptr PangoItemRaw -> IO PangoItemRaw
makeNewPangoItemRaw llPtr = do
  liftM PangoItemRaw $ newForeignPtr llPtr pango_item_free
withPangoItemRaw :: PangoItemRaw -> (Ptr PangoItemRaw -> IO a) -> IO a
withPangoItemRaw (PangoItemRaw pir) act = withForeignPtr pir act
foreign import ccall unsafe "&pango_item_free"
  pango_item_free :: FinalizerPtr PangoItemRaw
type GlyphItemRaw = Ptr (())
data PangoItem = PangoItem PangoString PangoItemRaw
data GlyphItem = GlyphItem PangoItem GlyphStringRaw
data PangoLayout = PangoLayout (IORef PangoString) PangoLayoutRaw
data LayoutIter = LayoutIter (IORef PangoString) LayoutIterRaw
newtype LayoutIterRaw = LayoutIterRaw (ForeignPtr (LayoutIterRaw))
makeNewLayoutIterRaw :: Ptr LayoutIterRaw -> IO LayoutIterRaw
makeNewLayoutIterRaw liPtr =
  liftM LayoutIterRaw $ newForeignPtr liPtr layout_iter_free
foreign import ccall unsafe "&pango_layout_iter_free"
  layout_iter_free :: FinalizerPtr LayoutIterRaw
data LayoutLine = LayoutLine (IORef PangoString) LayoutLineRaw
newtype LayoutLineRaw = LayoutLineRaw (ForeignPtr (LayoutLineRaw))
makeNewLayoutLineRaw :: Ptr LayoutLineRaw -> IO LayoutLineRaw
makeNewLayoutLineRaw llPtr = do
  liftM LayoutLineRaw $ newForeignPtr llPtr pango_layout_line_unref
foreign import ccall unsafe "&pango_layout_line_unref"
  pango_layout_line_unref :: FinalizerPtr LayoutLineRaw
newtype FontDescription = FontDescription (ForeignPtr (FontDescription))
makeNewFontDescription :: Ptr FontDescription -> IO FontDescription
makeNewFontDescription llPtr = do
  liftM FontDescription $ newForeignPtr llPtr pango_font_description_free
foreign import ccall unsafe "&pango_font_description_free"
  pango_font_description_free :: FinalizerPtr FontDescription
type PangoAttrList = Ptr (())
type CPangoAttribute = Ptr (())
instance Show FontDescription where
  show fd = unsafePerformIO $ do
    strPtr <- (\(FontDescription arg1) -> withForeignPtr arg1 $ \argPtr1 ->pango_font_description_to_string argPtr1) fd
    str <- peekUTFString strPtr
    g_free (castPtr strPtr)
    return $ T.unpack str
foreign import ccall safe "pango_language_from_string"
  pango_language_from_string :: ((Ptr CChar) -> (IO (Ptr Language)))
foreign import ccall unsafe "pango_font_description_to_string"
  pango_font_description_to_string :: ((Ptr FontDescription) -> (IO (Ptr CChar)))
foreign import ccall unsafe "g_free"
  g_free :: ((Ptr ()) -> (IO ()))