#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Pango.Structs.Item
(
Item(..) ,
newZeroItem ,
noItem ,
#if ENABLE_OVERLOADING
ItemCopyMethodInfo ,
#endif
itemCopy ,
#if ENABLE_OVERLOADING
ItemFreeMethodInfo ,
#endif
itemFree ,
itemNew ,
#if ENABLE_OVERLOADING
ItemSplitMethodInfo ,
#endif
itemSplit ,
getItemAnalysis ,
#if ENABLE_OVERLOADING
item_analysis ,
#endif
getItemLength ,
#if ENABLE_OVERLOADING
item_length ,
#endif
setItemLength ,
getItemNumChars ,
#if ENABLE_OVERLOADING
item_numChars ,
#endif
setItemNumChars ,
getItemOffset ,
#if ENABLE_OVERLOADING
item_offset ,
#endif
setItemOffset ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import {-# SOURCE #-} qualified GI.Pango.Structs.Analysis as Pango.Analysis
newtype Item = Item (ManagedPtr Item)
foreign import ccall "pango_item_get_type" c_pango_item_get_type ::
IO GType
instance BoxedObject Item where
boxedType _ = c_pango_item_get_type
newZeroItem :: MonadIO m => m Item
newZeroItem = liftIO $ callocBoxedBytes 64 >>= wrapBoxed Item
instance tag ~ 'AttrSet => Constructible Item tag where
new _ attrs = do
o <- newZeroItem
GI.Attributes.set o attrs
return o
noItem :: Maybe Item
noItem = Nothing
getItemOffset :: MonadIO m => Item -> m Int32
getItemOffset s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO Int32
return val
setItemOffset :: MonadIO m => Item -> Int32 -> m ()
setItemOffset s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (val :: Int32)
#if ENABLE_OVERLOADING
data ItemOffsetFieldInfo
instance AttrInfo ItemOffsetFieldInfo where
type AttrAllowedOps ItemOffsetFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint ItemOffsetFieldInfo = (~) Int32
type AttrBaseTypeConstraint ItemOffsetFieldInfo = (~) Item
type AttrGetType ItemOffsetFieldInfo = Int32
type AttrLabel ItemOffsetFieldInfo = "offset"
type AttrOrigin ItemOffsetFieldInfo = Item
attrGet _ = getItemOffset
attrSet _ = setItemOffset
attrConstruct = undefined
attrClear _ = undefined
item_offset :: AttrLabelProxy "offset"
item_offset = AttrLabelProxy
#endif
getItemLength :: MonadIO m => Item -> m Int32
getItemLength s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 4) :: IO Int32
return val
setItemLength :: MonadIO m => Item -> Int32 -> m ()
setItemLength s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 4) (val :: Int32)
#if ENABLE_OVERLOADING
data ItemLengthFieldInfo
instance AttrInfo ItemLengthFieldInfo where
type AttrAllowedOps ItemLengthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint ItemLengthFieldInfo = (~) Int32
type AttrBaseTypeConstraint ItemLengthFieldInfo = (~) Item
type AttrGetType ItemLengthFieldInfo = Int32
type AttrLabel ItemLengthFieldInfo = "length"
type AttrOrigin ItemLengthFieldInfo = Item
attrGet _ = getItemLength
attrSet _ = setItemLength
attrConstruct = undefined
attrClear _ = undefined
item_length :: AttrLabelProxy "length"
item_length = AttrLabelProxy
#endif
getItemNumChars :: MonadIO m => Item -> m Int32
getItemNumChars s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO Int32
return val
setItemNumChars :: MonadIO m => Item -> Int32 -> m ()
setItemNumChars s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Int32)
#if ENABLE_OVERLOADING
data ItemNumCharsFieldInfo
instance AttrInfo ItemNumCharsFieldInfo where
type AttrAllowedOps ItemNumCharsFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint ItemNumCharsFieldInfo = (~) Int32
type AttrBaseTypeConstraint ItemNumCharsFieldInfo = (~) Item
type AttrGetType ItemNumCharsFieldInfo = Int32
type AttrLabel ItemNumCharsFieldInfo = "num_chars"
type AttrOrigin ItemNumCharsFieldInfo = Item
attrGet _ = getItemNumChars
attrSet _ = setItemNumChars
attrConstruct = undefined
attrClear _ = undefined
item_numChars :: AttrLabelProxy "numChars"
item_numChars = AttrLabelProxy
#endif
getItemAnalysis :: MonadIO m => Item -> m Pango.Analysis.Analysis
getItemAnalysis s = liftIO $ withManagedPtr s $ \ptr -> do
let val = ptr `plusPtr` 16 :: (Ptr Pango.Analysis.Analysis)
val' <- (newPtr Pango.Analysis.Analysis) val
return val'
#if ENABLE_OVERLOADING
data ItemAnalysisFieldInfo
instance AttrInfo ItemAnalysisFieldInfo where
type AttrAllowedOps ItemAnalysisFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint ItemAnalysisFieldInfo = (~) (Ptr Pango.Analysis.Analysis)
type AttrBaseTypeConstraint ItemAnalysisFieldInfo = (~) Item
type AttrGetType ItemAnalysisFieldInfo = Pango.Analysis.Analysis
type AttrLabel ItemAnalysisFieldInfo = "analysis"
type AttrOrigin ItemAnalysisFieldInfo = Item
attrGet _ = getItemAnalysis
attrSet _ = undefined
attrConstruct = undefined
attrClear _ = undefined
item_analysis :: AttrLabelProxy "analysis"
item_analysis = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList Item
type instance O.AttributeList Item = ItemAttributeList
type ItemAttributeList = ('[ '("offset", ItemOffsetFieldInfo), '("length", ItemLengthFieldInfo), '("numChars", ItemNumCharsFieldInfo), '("analysis", ItemAnalysisFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "pango_item_new" pango_item_new ::
IO (Ptr Item)
itemNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Item
itemNew = liftIO $ do
result <- pango_item_new
checkUnexpectedReturnNULL "itemNew" result
result' <- (wrapBoxed Item) result
return result'
#if ENABLE_OVERLOADING
#endif
foreign import ccall "pango_item_copy" pango_item_copy ::
Ptr Item ->
IO (Ptr Item)
itemCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
Item
-> m (Maybe Item)
itemCopy item = liftIO $ do
item' <- unsafeManagedPtrGetPtr item
result <- pango_item_copy item'
maybeResult <- convertIfNonNull result $ \result' -> do
result'' <- (wrapBoxed Item) result'
return result''
touchManagedPtr item
return maybeResult
#if ENABLE_OVERLOADING
data ItemCopyMethodInfo
instance (signature ~ (m (Maybe Item)), MonadIO m) => O.MethodInfo ItemCopyMethodInfo Item signature where
overloadedMethod _ = itemCopy
#endif
foreign import ccall "pango_item_free" pango_item_free ::
Ptr Item ->
IO ()
itemFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
Item
-> m ()
itemFree item = liftIO $ do
item' <- unsafeManagedPtrGetPtr item
pango_item_free item'
touchManagedPtr item
return ()
#if ENABLE_OVERLOADING
data ItemFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ItemFreeMethodInfo Item signature where
overloadedMethod _ = itemFree
#endif
foreign import ccall "pango_item_split" pango_item_split ::
Ptr Item ->
Int32 ->
Int32 ->
IO (Ptr Item)
itemSplit ::
(B.CallStack.HasCallStack, MonadIO m) =>
Item
-> Int32
-> Int32
-> m Item
itemSplit orig splitIndex splitOffset = liftIO $ do
orig' <- unsafeManagedPtrGetPtr orig
result <- pango_item_split orig' splitIndex splitOffset
checkUnexpectedReturnNULL "itemSplit" result
result' <- (wrapBoxed Item) result
touchManagedPtr orig
return result'
#if ENABLE_OVERLOADING
data ItemSplitMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Item), MonadIO m) => O.MethodInfo ItemSplitMethodInfo Item signature where
overloadedMethod _ = itemSplit
#endif
#if ENABLE_OVERLOADING
type family ResolveItemMethod (t :: Symbol) (o :: *) :: * where
ResolveItemMethod "copy" o = ItemCopyMethodInfo
ResolveItemMethod "free" o = ItemFreeMethodInfo
ResolveItemMethod "split" o = ItemSplitMethodInfo
ResolveItemMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveItemMethod t Item, O.MethodInfo info Item p) => O.IsLabelProxy t (Item -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveItemMethod t Item, O.MethodInfo info Item p) => O.IsLabel t (Item -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif
#endif