{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A structure used to describe a text range.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Atk.Structs.TextRange
    ( 

-- * Exported types
    TextRange(..)                           ,
    newZeroTextRange                        ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveTextRangeMethod                  ,
#endif



 -- * Properties


-- ** bounds #attr:bounds#
-- | A rectangle giving the bounds of the text range

    getTextRangeBounds                      ,
#if defined(ENABLE_OVERLOADING)
    textRange_bounds                        ,
#endif


-- ** content #attr:content#
-- | The text in the text range

    clearTextRangeContent                   ,
    getTextRangeContent                     ,
    setTextRangeContent                     ,
#if defined(ENABLE_OVERLOADING)
    textRange_content                       ,
#endif


-- ** endOffset #attr:endOffset#
-- | The end offset of a AtkTextRange

    getTextRangeEndOffset                   ,
    setTextRangeEndOffset                   ,
#if defined(ENABLE_OVERLOADING)
    textRange_endOffset                     ,
#endif


-- ** startOffset #attr:startOffset#
-- | The start offset of a AtkTextRange

    getTextRangeStartOffset                 ,
    setTextRangeStartOffset                 ,
#if defined(ENABLE_OVERLOADING)
    textRange_startOffset                   ,
#endif




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
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.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
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 qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Atk.Structs.TextRectangle as Atk.TextRectangle

-- | Memory-managed wrapper type.
newtype TextRange = TextRange (SP.ManagedPtr TextRange)
    deriving (TextRange -> TextRange -> Bool
(TextRange -> TextRange -> Bool)
-> (TextRange -> TextRange -> Bool) -> Eq TextRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextRange -> TextRange -> Bool
$c/= :: TextRange -> TextRange -> Bool
== :: TextRange -> TextRange -> Bool
$c== :: TextRange -> TextRange -> Bool
Eq)

instance SP.ManagedPtrNewtype TextRange where
    toManagedPtr :: TextRange -> ManagedPtr TextRange
toManagedPtr (TextRange ManagedPtr TextRange
p) = ManagedPtr TextRange
p

foreign import ccall "atk_text_range_get_type" c_atk_text_range_get_type :: 
    IO GType

type instance O.ParentTypes TextRange = '[]
instance O.HasParentTypes TextRange

instance B.Types.TypedObject TextRange where
    glibType :: IO GType
glibType = IO GType
c_atk_text_range_get_type

instance B.Types.GBoxed TextRange

-- | Convert 'TextRange' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe TextRange) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_atk_text_range_get_type
    gvalueSet_ :: Ptr GValue -> Maybe TextRange -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TextRange
P.Nothing = Ptr GValue -> Ptr TextRange -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr TextRange
forall a. Ptr a
FP.nullPtr :: FP.Ptr TextRange)
    gvalueSet_ Ptr GValue
gv (P.Just TextRange
obj) = TextRange -> (Ptr TextRange -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TextRange
obj (Ptr GValue -> Ptr TextRange -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe TextRange)
gvalueGet_ Ptr GValue
gv = do
        Ptr TextRange
ptr <- Ptr GValue -> IO (Ptr TextRange)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr TextRange)
        if Ptr TextRange
ptr Ptr TextRange -> Ptr TextRange -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TextRange
forall a. Ptr a
FP.nullPtr
        then TextRange -> Maybe TextRange
forall a. a -> Maybe a
P.Just (TextRange -> Maybe TextRange)
-> IO TextRange -> IO (Maybe TextRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr TextRange -> TextRange)
-> Ptr TextRange -> IO TextRange
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr TextRange -> TextRange
TextRange Ptr TextRange
ptr
        else Maybe TextRange -> IO (Maybe TextRange)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextRange
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `TextRange` struct initialized to zero.
newZeroTextRange :: MonadIO m => m TextRange
newZeroTextRange :: forall (m :: * -> *). MonadIO m => m TextRange
newZeroTextRange = IO TextRange -> m TextRange
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextRange -> m TextRange) -> IO TextRange -> m TextRange
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr TextRange)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
32 IO (Ptr TextRange)
-> (Ptr TextRange -> IO TextRange) -> IO TextRange
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TextRange -> TextRange)
-> Ptr TextRange -> IO TextRange
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextRange -> TextRange
TextRange

instance tag ~ 'AttrSet => Constructible TextRange tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr TextRange -> TextRange)
-> [AttrOp TextRange tag] -> m TextRange
new ManagedPtr TextRange -> TextRange
_ [AttrOp TextRange tag]
attrs = do
        TextRange
o <- m TextRange
forall (m :: * -> *). MonadIO m => m TextRange
newZeroTextRange
        TextRange -> [AttrOp TextRange 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TextRange
o [AttrOp TextRange tag]
[AttrOp TextRange 'AttrSet]
attrs
        TextRange -> m TextRange
forall (m :: * -> *) a. Monad m => a -> m a
return TextRange
o


-- | Get the value of the “@bounds@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textRange #bounds
-- @
getTextRangeBounds :: MonadIO m => TextRange -> m Atk.TextRectangle.TextRectangle
getTextRangeBounds :: forall (m :: * -> *). MonadIO m => TextRange -> m TextRectangle
getTextRangeBounds TextRange
s = IO TextRectangle -> m TextRectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextRectangle -> m TextRectangle)
-> IO TextRectangle -> m TextRectangle
forall a b. (a -> b) -> a -> b
$ TextRange
-> (Ptr TextRange -> IO TextRectangle) -> IO TextRectangle
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO TextRectangle) -> IO TextRectangle)
-> (Ptr TextRange -> IO TextRectangle) -> IO TextRectangle
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    let val :: Ptr TextRectangle
val = Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr TextRectangle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: (Ptr Atk.TextRectangle.TextRectangle)
    TextRectangle
val' <- ((ManagedPtr TextRectangle -> TextRectangle)
-> Ptr TextRectangle -> IO TextRectangle
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TextRectangle -> TextRectangle
Atk.TextRectangle.TextRectangle) Ptr TextRectangle
val
    TextRectangle -> IO TextRectangle
forall (m :: * -> *) a. Monad m => a -> m a
return TextRectangle
val'

#if defined(ENABLE_OVERLOADING)
data TextRangeBoundsFieldInfo
instance AttrInfo TextRangeBoundsFieldInfo where
    type AttrBaseTypeConstraint TextRangeBoundsFieldInfo = (~) TextRange
    type AttrAllowedOps TextRangeBoundsFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint TextRangeBoundsFieldInfo = (~) (Ptr Atk.TextRectangle.TextRectangle)
    type AttrTransferTypeConstraint TextRangeBoundsFieldInfo = (~)(Ptr Atk.TextRectangle.TextRectangle)
    type AttrTransferType TextRangeBoundsFieldInfo = (Ptr Atk.TextRectangle.TextRectangle)
    type AttrGetType TextRangeBoundsFieldInfo = Atk.TextRectangle.TextRectangle
    type AttrLabel TextRangeBoundsFieldInfo = "bounds"
    type AttrOrigin TextRangeBoundsFieldInfo = TextRange
    attrGet = getTextRangeBounds
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.TextRange.bounds"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Structs-TextRange.html#g:attr:bounds"
        })

textRange_bounds :: AttrLabelProxy "bounds"
textRange_bounds = AttrLabelProxy

#endif


-- | Get the value of the “@start_offset@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textRange #startOffset
-- @
getTextRangeStartOffset :: MonadIO m => TextRange -> m Int32
getTextRangeStartOffset :: forall (m :: * -> *). MonadIO m => TextRange -> m Int32
getTextRangeStartOffset TextRange
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ TextRange -> (Ptr TextRange -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO Int32) -> IO Int32)
-> (Ptr TextRange -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@start_offset@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textRange [ #startOffset 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextRangeStartOffset :: MonadIO m => TextRange -> Int32 -> m ()
setTextRangeStartOffset :: forall (m :: * -> *). MonadIO m => TextRange -> Int32 -> m ()
setTextRangeStartOffset TextRange
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextRange -> (Ptr TextRange -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO ()) -> IO ())
-> (Ptr TextRange -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextRangeStartOffsetFieldInfo
instance AttrInfo TextRangeStartOffsetFieldInfo where
    type AttrBaseTypeConstraint TextRangeStartOffsetFieldInfo = (~) TextRange
    type AttrAllowedOps TextRangeStartOffsetFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextRangeStartOffsetFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextRangeStartOffsetFieldInfo = (~)Int32
    type AttrTransferType TextRangeStartOffsetFieldInfo = Int32
    type AttrGetType TextRangeStartOffsetFieldInfo = Int32
    type AttrLabel TextRangeStartOffsetFieldInfo = "start_offset"
    type AttrOrigin TextRangeStartOffsetFieldInfo = TextRange
    attrGet = getTextRangeStartOffset
    attrSet = setTextRangeStartOffset
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.TextRange.startOffset"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Structs-TextRange.html#g:attr:startOffset"
        })

textRange_startOffset :: AttrLabelProxy "startOffset"
textRange_startOffset = AttrLabelProxy

#endif


-- | Get the value of the “@end_offset@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textRange #endOffset
-- @
getTextRangeEndOffset :: MonadIO m => TextRange -> m Int32
getTextRangeEndOffset :: forall (m :: * -> *). MonadIO m => TextRange -> m Int32
getTextRangeEndOffset TextRange
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ TextRange -> (Ptr TextRange -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO Int32) -> IO Int32)
-> (Ptr TextRange -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@end_offset@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textRange [ #endOffset 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextRangeEndOffset :: MonadIO m => TextRange -> Int32 -> m ()
setTextRangeEndOffset :: forall (m :: * -> *). MonadIO m => TextRange -> Int32 -> m ()
setTextRangeEndOffset TextRange
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextRange -> (Ptr TextRange -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO ()) -> IO ())
-> (Ptr TextRange -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextRangeEndOffsetFieldInfo
instance AttrInfo TextRangeEndOffsetFieldInfo where
    type AttrBaseTypeConstraint TextRangeEndOffsetFieldInfo = (~) TextRange
    type AttrAllowedOps TextRangeEndOffsetFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextRangeEndOffsetFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextRangeEndOffsetFieldInfo = (~)Int32
    type AttrTransferType TextRangeEndOffsetFieldInfo = Int32
    type AttrGetType TextRangeEndOffsetFieldInfo = Int32
    type AttrLabel TextRangeEndOffsetFieldInfo = "end_offset"
    type AttrOrigin TextRangeEndOffsetFieldInfo = TextRange
    attrGet = getTextRangeEndOffset
    attrSet = setTextRangeEndOffset
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.TextRange.endOffset"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Structs-TextRange.html#g:attr:endOffset"
        })

textRange_endOffset :: AttrLabelProxy "endOffset"
textRange_endOffset = AttrLabelProxy

#endif


-- | Get the value of the “@content@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textRange #content
-- @
getTextRangeContent :: MonadIO m => TextRange -> m (Maybe T.Text)
getTextRangeContent :: forall (m :: * -> *). MonadIO m => TextRange -> m (Maybe Text)
getTextRangeContent TextRange
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ TextRange -> (Ptr TextRange -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr TextRange -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@content@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textRange [ #content 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextRangeContent :: MonadIO m => TextRange -> CString -> m ()
setTextRangeContent :: forall (m :: * -> *). MonadIO m => TextRange -> CString -> m ()
setTextRangeContent TextRange
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextRange -> (Ptr TextRange -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO ()) -> IO ())
-> (Ptr TextRange -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CString
val :: CString)

-- | Set the value of the “@content@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #content
-- @
clearTextRangeContent :: MonadIO m => TextRange -> m ()
clearTextRangeContent :: forall (m :: * -> *). MonadIO m => TextRange -> m ()
clearTextRangeContent TextRange
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextRange -> (Ptr TextRange -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextRange
s ((Ptr TextRange -> IO ()) -> IO ())
-> (Ptr TextRange -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextRange
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextRange
ptr Ptr TextRange -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data TextRangeContentFieldInfo
instance AttrInfo TextRangeContentFieldInfo where
    type AttrBaseTypeConstraint TextRangeContentFieldInfo = (~) TextRange
    type AttrAllowedOps TextRangeContentFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TextRangeContentFieldInfo = (~) CString
    type AttrTransferTypeConstraint TextRangeContentFieldInfo = (~)CString
    type AttrTransferType TextRangeContentFieldInfo = CString
    type AttrGetType TextRangeContentFieldInfo = Maybe T.Text
    type AttrLabel TextRangeContentFieldInfo = "content"
    type AttrOrigin TextRangeContentFieldInfo = TextRange
    attrGet = getTextRangeContent
    attrSet = setTextRangeContent
    attrConstruct = undefined
    attrClear = clearTextRangeContent
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.TextRange.content"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Structs-TextRange.html#g:attr:content"
        })

textRange_content :: AttrLabelProxy "content"
textRange_content = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TextRange
type instance O.AttributeList TextRange = TextRangeAttributeList
type TextRangeAttributeList = ('[ '("bounds", TextRangeBoundsFieldInfo), '("startOffset", TextRangeStartOffsetFieldInfo), '("endOffset", TextRangeEndOffsetFieldInfo), '("content", TextRangeContentFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTextRangeMethod (t :: Symbol) (o :: *) :: * where
    ResolveTextRangeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTextRangeMethod t TextRange, O.OverloadedMethod info TextRange p) => OL.IsLabel t (TextRange -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTextRangeMethod t TextRange, O.OverloadedMethod info TextRange p, R.HasField t TextRange p) => R.HasField t TextRange p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveTextRangeMethod t TextRange, O.OverloadedMethodInfo info TextRange) => OL.IsLabel t (O.MethodProxy info TextRange) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif