{-# LINE 2 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}
{-# OPTIONS_HADDOCK hide #-}
-- -*-haskell-*-
-- GIMP Toolkit (GTK) - pango non-GObject types PangoTypes
--
-- Author : Axel Simon
--
-- Created: 9 Feburary 2003
--
-- Copyright (C) 1999-2005 Axel Simon
--
-- This library is free software; you can redistribute it and/or
-- modify it under the terms of the GNU Lesser General Public
-- License as published by the Free Software Foundation; either
-- version 2.1 of the License, or (at your option) any later version.
--
-- This library is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-- Lesser General Public License for more details.
--
-- #hide

-- |
-- Maintainer : gtk2hs-users@lists.sourceforge.net
-- Stability : provisional
-- Portability : portable (depends on GHC)
--
-- Define types used in Pango which are not derived from GObject.
--
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)
-- {#import Graphics.Rendering.Pango.Enums#}


{-# LINE 85 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

-- | An RFC-3066 language designator to choose scripts.
--
newtype Language = Language (Ptr (Language)) deriving Eq

-- | Define the gint that c2hs is the Haskell type.
type GInt = (CInt)
{-# LINE 92 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

instance Show Language where
  show (Language ptr)
    | ptr==nullPtr = ""
    | otherwise = T.unpack . unsafePerformIO $ peekUTFString (castPtr ptr)

-- | Specifying no particular language.
emptyLanguage :: Language
emptyLanguage = Language nullPtr

-- | Take a RFC-3066 format language tag as a string and convert it to a
-- 'Language' type that can be efficiently passed around and compared with
-- other language tags.
--
-- * This function first canonicalizes the string by converting it to
-- lowercase, mapping \'_\' to \'-\', and stripping all characters
-- other than letters and \'-\'.
--
languageFromString :: GlibString string => string -> IO Language
languageFromString language = liftM Language $
  withUTFString language pango_language_from_string
{-# LINE 113 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

-- | The style of a font.
--
-- * 'StyleOblique' is a slanted font like 'StyleItalic',
-- but in a roman style.
--
data FontStyle = StyleNormal
               | StyleOblique
               | StyleItalic
               deriving (Enum,Eq)

{-# LINE 120 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

instance Show FontStyle where
  showsPrec _ StyleNormal = shows "normal"
  showsPrec _ StyleOblique = shows "oblique"
  showsPrec _ StyleItalic = shows "italic"

-- | Define attributes for 'Weight'.
--
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"

{-# LINE 129 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

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"


-- | The variant of a font.
--
-- * The 'VariantSmallCaps' is a version of a font where lower case
-- letters are shown as physically smaller upper case letters.
--
data Variant = VariantNormal
             | VariantSmallCaps
             deriving (Enum,Eq)

{-# LINE 151 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

instance Show Variant where
  showsPrec _ VariantNormal = shows "normal"
  showsPrec _ VariantSmallCaps = shows "smallcaps"

-- | Define how wide characters are.
--
data Stretch = StretchUltraCondensed
             | StretchExtraCondensed
             | StretchCondensed
             | StretchSemiCondensed
             | StretchNormal
             | StretchSemiExpanded
             | StretchExpanded
             | StretchExtraExpanded
             | StretchUltraExpanded
             deriving (Enum,Eq)

{-# LINE 159 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

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"

-- | Define attributes for 'Underline'.
--
-- * The squiggly underline for errors is only available in Gtk 2.4 and higher.
--
data Underline = UnderlineNone
               | UnderlineSingle
               | UnderlineDouble
               | UnderlineLow
               | UnderlineError
               deriving (Enum,Eq)

{-# LINE 176 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

instance Show Underline where
  showsPrec _ UnderlineNone = shows "none"
  showsPrec _ UnderlineSingle = shows "single"
  showsPrec _ UnderlineDouble = shows "double"
  showsPrec _ UnderlineLow = shows "low"
  showsPrec _ UnderlineError = shows "error"


-- | The 'PangoGravity' type represents the orientation of glyphs in a
-- segment of text. The value 'GravitySouth', for instance, indicates that the
-- text stands upright, i.e. that the base of the letter is directed
-- downwards.
--
-- This is useful when rendering vertical text layouts. In those situations,
-- the layout is rotated using a non-identity 'PangoMatrix', and then glyph
-- orientation is controlled using 'PangoGravity'. Not every value in this
-- enumeration makes sense for every usage of 'Gravity'; for example,
-- 'PangoGravityAuto' only can be passed to 'pangoContextSetBaseGravity' and
-- can only be returned by 'pangoContextGetBaseGravity'.
--
-- * See also: 'PangoGravityHint'
--
-- * Gravity is resolved from the context matrix.
--
-- * Since Pango 1.16
--
data PangoGravity = PangoGravitySouth
                  | PangoGravityEast
                  | PangoGravityNorth
                  | PangoGravityWest
                  | PangoGravityAuto
                  deriving (Enum,Eq)

{-# LINE 204 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

instance Show PangoGravity where
  show PangoGravitySouth = "south"
  show PangoGravityEast = "east"
  show PangoGravityNorth = "north"
  show PangoGravityWest = "west"
  show PangoGravityAuto = "auto"

-- | The 'PangoGravityHint' defines how horizontal scripts should behave in a
-- vertical context.
--
-- * 'PangoGravityHintNatural': scripts will take their natural gravity based
-- on the base gravity and the script. This is the default.
--
-- * 'PangoGravityHintStrong': always use the base gravity set, regardless of
-- the script.
--
-- * 'PangoGravityHintLine': for scripts not in their natural direction (eg.
-- Latin in East gravity), choose per-script gravity such that every script
-- respects the line progression. This means, Latin and Arabic will take
-- opposite gravities and both flow top-to-bottom for example.
--
data PangoGravityHint = PangoGravityHintNatural
                      | PangoGravityHintStrong
                      | PangoGravityHintLine
                      deriving (Enum,Eq)

{-# LINE 227 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

instance Show PangoGravityHint where
  show PangoGravityHintNatural = "natural"
  show PangoGravityHintStrong = "strong"
  show PangoGravityHintLine = "line"



-- A string that is stored with each GlyphString, PangoItem
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

-- paired with PangoString to create a Haskell GlyphString
newtype GlyphStringRaw = GlyphStringRaw (ForeignPtr (GlyphStringRaw))
{-# LINE 252 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

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

-- paired with PangoString and UTFCorrection to create a Haskell PangoItem
newtype PangoItemRaw = PangoItemRaw (ForeignPtr (PangoItemRaw))
{-# LINE 262 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

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 (())
{-# LINE 275 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}


-- With each GlyphString we pair a UTFCorrection
-- and the marshalled UTF8 string. Together, this data
-- enables us to bind all functions that take or return
-- indices into the CString, rather then unicode position. Note that text
-- handling is particularly horrible with UTF8: Several UTF8 bytes can make
-- up one Unicode character (a Haskell Char), and several Unicode characters
-- can form a cluster (e.g. a letter and an accent). We protect the user from
-- UTF8\/Haskell String conversions, but not from clusters.

-- | A sequence of characters that are rendered with the same settings.
--
-- * A preprocessing stage done by 'itemize' splits the input text into
-- several chunks such that each chunk can be rendered with the same
-- font, direction, slant, etc. Some attributes such as the color,
-- underline or strikethrough do not affect a break into several
-- 'PangoItem's. See also 'GlyphItem'.
--
data PangoItem = PangoItem PangoString PangoItemRaw

-- | A sequence of glyphs for a chunk of a string.
--
-- * A glyph item contains the graphical representation of a 'PangoItem'.
-- Clusters (like @e@ and an accent modifier) as well as legatures
-- (such as @ffi@ turning into a single letter that omits the dot over the
-- @i@) are usually represented as a single glyph.
--
data GlyphItem = GlyphItem PangoItem GlyphStringRaw

-- | A rendered paragraph.
data PangoLayout = PangoLayout (IORef PangoString) PangoLayoutRaw

-- | An iterator to examine a layout.
--
data LayoutIter = LayoutIter (IORef PangoString) LayoutIterRaw

newtype LayoutIterRaw = LayoutIterRaw (ForeignPtr (LayoutIterRaw))
{-# LINE 313 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

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

-- | A single line in a 'PangoLayout'.
--
data LayoutLine = LayoutLine (IORef PangoString) LayoutLineRaw

newtype LayoutLineRaw = LayoutLineRaw (ForeignPtr (LayoutLineRaw))
{-# LINE 326 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

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

-- | A possibly partial description of font(s).
--
newtype FontDescription = FontDescription (ForeignPtr (FontDescription))
{-# LINE 337 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

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

-- Attributes
type PangoAttrList = Ptr (())
{-# LINE 347 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

type CPangoAttribute = Ptr (())
{-# LINE 349 "./Graphics/Rendering/Pango/BasicTypes.chs" #-}

-- dirty hack to make PangoAttribute showable
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 ()))