{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

A #PopplerTextAttributes is used to describe text attributes of a range of text
-}

module GI.Poppler.Structs.TextAttributes
    ( 

-- * Exported types
    TextAttributes(..)                      ,
    noTextAttributes                        ,


 -- * Methods
-- ** textAttributesCopy
    textAttributesCopy                      ,


-- ** textAttributesFree
    textAttributesFree                      ,


-- ** textAttributesNew
    textAttributesNew                       ,




 -- * Properties
-- ** Color
    textAttributesReadColor                 ,


-- ** EndIndex
    textAttributesReadEndIndex              ,


-- ** FontName
    textAttributesReadFontName              ,


-- ** FontSize
    textAttributesReadFontSize              ,


-- ** IsUnderlined
    textAttributesReadIsUnderlined          ,


-- ** StartIndex
    textAttributesReadStartIndex            ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Poppler.Types
import GI.Poppler.Callbacks

newtype TextAttributes = TextAttributes (ForeignPtr TextAttributes)
foreign import ccall "poppler_text_attributes_get_type" c_poppler_text_attributes_get_type :: 
    IO GType

instance BoxedObject TextAttributes where
    boxedType _ = c_poppler_text_attributes_get_type

noTextAttributes :: Maybe TextAttributes
noTextAttributes = Nothing

textAttributesReadFontName :: TextAttributes -> IO T.Text
textAttributesReadFontName s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    val' <- cstringToText val
    return val'

textAttributesReadFontSize :: TextAttributes -> IO Double
textAttributesReadFontSize s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CDouble
    let val' = realToFrac val
    return val'

textAttributesReadIsUnderlined :: TextAttributes -> IO Bool
textAttributesReadIsUnderlined s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CInt
    let val' = (/= 0) val
    return val'

textAttributesReadColor :: TextAttributes -> IO Color
textAttributesReadColor s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO (Ptr Color)
    val' <- (newBoxed Color) val
    return val'

textAttributesReadStartIndex :: TextAttributes -> IO Int32
textAttributesReadStartIndex s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 28) :: IO Int32
    return val

textAttributesReadEndIndex :: TextAttributes -> IO Int32
textAttributesReadEndIndex s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Int32
    return val

-- method TextAttributes::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Poppler" "TextAttributes"
-- throws : False
-- Skip return : False

foreign import ccall "poppler_text_attributes_new" poppler_text_attributes_new :: 
    IO (Ptr TextAttributes)


textAttributesNew ::
    (MonadIO m) =>
    m TextAttributes
textAttributesNew  = liftIO $ do
    result <- poppler_text_attributes_new
    checkUnexpectedReturnNULL "poppler_text_attributes_new" result
    result' <- (wrapBoxed TextAttributes) result
    return result'

-- method TextAttributes::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Poppler" "TextAttributes", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Poppler" "TextAttributes", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Poppler" "TextAttributes"
-- throws : False
-- Skip return : False

foreign import ccall "poppler_text_attributes_copy" poppler_text_attributes_copy :: 
    Ptr TextAttributes ->                   -- _obj : TInterface "Poppler" "TextAttributes"
    IO (Ptr TextAttributes)


textAttributesCopy ::
    (MonadIO m) =>
    TextAttributes ->                       -- _obj
    m TextAttributes
textAttributesCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- poppler_text_attributes_copy _obj'
    checkUnexpectedReturnNULL "poppler_text_attributes_copy" result
    result' <- (wrapBoxed TextAttributes) result
    touchManagedPtr _obj
    return result'

-- method TextAttributes::free
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Poppler" "TextAttributes", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Poppler" "TextAttributes", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "poppler_text_attributes_free" poppler_text_attributes_free :: 
    Ptr TextAttributes ->                   -- _obj : TInterface "Poppler" "TextAttributes"
    IO ()


textAttributesFree ::
    (MonadIO m) =>
    TextAttributes ->                       -- _obj
    m ()
textAttributesFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    poppler_text_attributes_free _obj'
    touchManagedPtr _obj
    return ()