{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This structure represents a single  text selection within a document. This
-- selection is defined by two points in the content, where each one is defined
-- by an AtkObject supporting the AtkText interface and a character offset
-- relative to it.
-- 
-- The end object must appear after the start object in the accessibility tree,
-- i.e. the end object must be reachable from the start object by navigating
-- forward (next, first child etc).
-- 
-- This struct also contains a /@startIsActive@/ boolean, to communicate if the
-- start of the selection is the active point or not.
-- 
-- The active point corresponds to the user\'s focus or point of interest. The
-- user moves the active point to expand or collapse the range. The anchor
-- point is the other point of the range and typically remains constant. In
-- most cases, anchor is the start of the range and active is the end. However,
-- when selecting backwards (e.g. pressing shift+left arrow in a text field),
-- the start of the range is the active point, as the user moves this to
-- manipulate the selection.
-- 
-- /Since: 2.52/

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

module GI.Atk.Structs.TextSelection
    ( 

-- * Exported types
    TextSelection(..)                       ,
    newZeroTextSelection                    ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveTextSelectionMethod              ,
#endif



 -- * Properties


-- ** endObject #attr:endObject#
-- | the AtkText containing the end of the selection.

    clearTextSelectionEndObject             ,
    getTextSelectionEndObject               ,
    setTextSelectionEndObject               ,
#if defined(ENABLE_OVERLOADING)
    textSelection_endObject                 ,
#endif


-- ** endOffset #attr:endOffset#
-- | the text offset of the end of the selection within /@endObject@/.

    getTextSelectionEndOffset               ,
    setTextSelectionEndOffset               ,
#if defined(ENABLE_OVERLOADING)
    textSelection_endOffset                 ,
#endif


-- ** startIsActive #attr:startIsActive#
-- | a gboolean indicating whether the start of the selection
--                  is the active point.

    getTextSelectionStartIsActive           ,
    setTextSelectionStartIsActive           ,
#if defined(ENABLE_OVERLOADING)
    textSelection_startIsActive             ,
#endif


-- ** startObject #attr:startObject#
-- | the AtkText containing the start of the selection.

    clearTextSelectionStartObject           ,
    getTextSelectionStartObject             ,
    setTextSelectionStartObject             ,
#if defined(ENABLE_OVERLOADING)
    textSelection_startObject               ,
#endif


-- ** startOffset #attr:startOffset#
-- | the text offset of the beginning of the selection within
--                /@startObject@/.

    getTextSelectionStartOffset             ,
    setTextSelectionStartOffset             ,
#if defined(ENABLE_OVERLOADING)
    textSelection_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.GHashTable as B.GHT
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.Kind as DK
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 qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import {-# SOURCE #-} qualified GI.Atk.Enums as Atk.Enums
import {-# SOURCE #-} qualified GI.Atk.Objects.Object as Atk.Object
import {-# SOURCE #-} qualified GI.Atk.Objects.Relation as Atk.Relation
import {-# SOURCE #-} qualified GI.Atk.Objects.RelationSet as Atk.RelationSet
import {-# SOURCE #-} qualified GI.Atk.Objects.StateSet as Atk.StateSet
import {-# SOURCE #-} qualified GI.Atk.Structs.PropertyValues as Atk.PropertyValues
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ValueArray as GObject.ValueArray

#else
import {-# SOURCE #-} qualified GI.Atk.Objects.Object as Atk.Object

#endif

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

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

instance BoxedPtr TextSelection where
    boxedPtrCopy :: TextSelection -> IO TextSelection
boxedPtrCopy = \TextSelection
p -> TextSelection
-> (Ptr TextSelection -> IO TextSelection) -> IO TextSelection
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TextSelection
p (Int -> Ptr TextSelection -> IO (Ptr TextSelection)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
32 (Ptr TextSelection -> IO (Ptr TextSelection))
-> (Ptr TextSelection -> IO TextSelection)
-> Ptr TextSelection
-> IO TextSelection
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TextSelection -> TextSelection)
-> Ptr TextSelection -> IO TextSelection
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr TextSelection -> TextSelection
TextSelection)
    boxedPtrFree :: TextSelection -> IO ()
boxedPtrFree = \TextSelection
x -> TextSelection -> (Ptr TextSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr TextSelection
x Ptr TextSelection -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr TextSelection where
    boxedPtrCalloc :: IO (Ptr TextSelection)
boxedPtrCalloc = Int -> IO (Ptr TextSelection)
forall a. Int -> IO (Ptr a)
callocBytes Int
32


-- | Construct a `TextSelection` struct initialized to zero.
newZeroTextSelection :: MonadIO m => m TextSelection
newZeroTextSelection :: forall (m :: * -> *). MonadIO m => m TextSelection
newZeroTextSelection = IO TextSelection -> m TextSelection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextSelection -> m TextSelection)
-> IO TextSelection -> m TextSelection
forall a b. (a -> b) -> a -> b
$ IO (Ptr TextSelection)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr TextSelection)
-> (Ptr TextSelection -> IO TextSelection) -> IO TextSelection
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TextSelection -> TextSelection)
-> Ptr TextSelection -> IO TextSelection
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TextSelection -> TextSelection
TextSelection

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


-- | Get the value of the “@start_object@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textSelection #startObject
-- @
getTextSelectionStartObject :: MonadIO m => TextSelection -> m (Maybe Atk.Object.Object)
getTextSelectionStartObject :: forall (m :: * -> *).
MonadIO m =>
TextSelection -> m (Maybe Object)
getTextSelectionStartObject TextSelection
s = IO (Maybe Object) -> m (Maybe Object)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ TextSelection
-> (Ptr TextSelection -> IO (Maybe Object)) -> IO (Maybe Object)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO (Maybe Object)) -> IO (Maybe Object))
-> (Ptr TextSelection -> IO (Maybe Object)) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Ptr Object
val <- Ptr (Ptr Object) -> IO (Ptr Object)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr (Ptr Object)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (Ptr Atk.Object.Object)
    Maybe Object
result <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Object
val ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
val' -> do
        Object
val'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
val'
        Object -> IO Object
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
val''
    Maybe Object -> IO (Maybe Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
result

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

-- | Set the value of the “@start_object@” 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' #startObject
-- @
clearTextSelectionStartObject :: MonadIO m => TextSelection -> m ()
clearTextSelectionStartObject :: forall (m :: * -> *). MonadIO m => TextSelection -> m ()
clearTextSelectionStartObject TextSelection
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextSelection -> (Ptr TextSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO ()) -> IO ())
-> (Ptr TextSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Ptr (Ptr Object) -> Ptr Object -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr (Ptr Object)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr Object
forall a. Ptr a
FP.nullPtr :: Ptr Atk.Object.Object)

#if defined(ENABLE_OVERLOADING)
data TextSelectionStartObjectFieldInfo
instance AttrInfo TextSelectionStartObjectFieldInfo where
    type AttrBaseTypeConstraint TextSelectionStartObjectFieldInfo = (~) TextSelection
    type AttrAllowedOps TextSelectionStartObjectFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TextSelectionStartObjectFieldInfo = (~) (Ptr Atk.Object.Object)
    type AttrTransferTypeConstraint TextSelectionStartObjectFieldInfo = (~)(Ptr Atk.Object.Object)
    type AttrTransferType TextSelectionStartObjectFieldInfo = (Ptr Atk.Object.Object)
    type AttrGetType TextSelectionStartObjectFieldInfo = Maybe Atk.Object.Object
    type AttrLabel TextSelectionStartObjectFieldInfo = "start_object"
    type AttrOrigin TextSelectionStartObjectFieldInfo = TextSelection
    attrGet = getTextSelectionStartObject
    attrSet = setTextSelectionStartObject
    attrConstruct = undefined
    attrClear = clearTextSelectionStartObject
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.TextSelection.startObject"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.28/docs/GI-Atk-Structs-TextSelection.html#g:attr:startObject"
        })

textSelection_startObject :: AttrLabelProxy "startObject"
textSelection_startObject = 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' textSelection #startOffset
-- @
getTextSelectionStartOffset :: MonadIO m => TextSelection -> m Int32
getTextSelectionStartOffset :: forall (m :: * -> *). MonadIO m => TextSelection -> m Int32
getTextSelectionStartOffset TextSelection
s = IO Int32 -> m Int32
forall a. IO a -> m a
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
$ TextSelection -> (Ptr TextSelection -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO Int32) -> IO Int32)
-> (Ptr TextSelection -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
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' textSelection [ #startOffset 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextSelectionStartOffset :: MonadIO m => TextSelection -> Int32 -> m ()
setTextSelectionStartOffset :: forall (m :: * -> *). MonadIO m => TextSelection -> Int32 -> m ()
setTextSelectionStartOffset TextSelection
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextSelection -> (Ptr TextSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO ()) -> IO ())
-> (Ptr TextSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Int32
val :: Int32)

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

textSelection_startOffset :: AttrLabelProxy "startOffset"
textSelection_startOffset = AttrLabelProxy

#endif


-- | Get the value of the “@end_object@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textSelection #endObject
-- @
getTextSelectionEndObject :: MonadIO m => TextSelection -> m (Maybe Atk.Object.Object)
getTextSelectionEndObject :: forall (m :: * -> *).
MonadIO m =>
TextSelection -> m (Maybe Object)
getTextSelectionEndObject TextSelection
s = IO (Maybe Object) -> m (Maybe Object)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ TextSelection
-> (Ptr TextSelection -> IO (Maybe Object)) -> IO (Maybe Object)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO (Maybe Object)) -> IO (Maybe Object))
-> (Ptr TextSelection -> IO (Maybe Object)) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Ptr Object
val <- Ptr (Ptr Object) -> IO (Ptr Object)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr (Ptr Object)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO (Ptr Atk.Object.Object)
    Maybe Object
result <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Object
val ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
val' -> do
        Object
val'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
val'
        Object -> IO Object
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Object
val''
    Maybe Object -> IO (Maybe Object)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
result

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

-- | Set the value of the “@end_object@” 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' #endObject
-- @
clearTextSelectionEndObject :: MonadIO m => TextSelection -> m ()
clearTextSelectionEndObject :: forall (m :: * -> *). MonadIO m => TextSelection -> m ()
clearTextSelectionEndObject TextSelection
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextSelection -> (Ptr TextSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO ()) -> IO ())
-> (Ptr TextSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Ptr (Ptr Object) -> Ptr Object -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr (Ptr Object)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr Object
forall a. Ptr a
FP.nullPtr :: Ptr Atk.Object.Object)

#if defined(ENABLE_OVERLOADING)
data TextSelectionEndObjectFieldInfo
instance AttrInfo TextSelectionEndObjectFieldInfo where
    type AttrBaseTypeConstraint TextSelectionEndObjectFieldInfo = (~) TextSelection
    type AttrAllowedOps TextSelectionEndObjectFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TextSelectionEndObjectFieldInfo = (~) (Ptr Atk.Object.Object)
    type AttrTransferTypeConstraint TextSelectionEndObjectFieldInfo = (~)(Ptr Atk.Object.Object)
    type AttrTransferType TextSelectionEndObjectFieldInfo = (Ptr Atk.Object.Object)
    type AttrGetType TextSelectionEndObjectFieldInfo = Maybe Atk.Object.Object
    type AttrLabel TextSelectionEndObjectFieldInfo = "end_object"
    type AttrOrigin TextSelectionEndObjectFieldInfo = TextSelection
    attrGet = getTextSelectionEndObject
    attrSet = setTextSelectionEndObject
    attrConstruct = undefined
    attrClear = clearTextSelectionEndObject
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Structs.TextSelection.endObject"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.28/docs/GI-Atk-Structs-TextSelection.html#g:attr:endObject"
        })

textSelection_endObject :: AttrLabelProxy "endObject"
textSelection_endObject = 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' textSelection #endOffset
-- @
getTextSelectionEndOffset :: MonadIO m => TextSelection -> m Int32
getTextSelectionEndOffset :: forall (m :: * -> *). MonadIO m => TextSelection -> m Int32
getTextSelectionEndOffset TextSelection
s = IO Int32 -> m Int32
forall a. IO a -> m a
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
$ TextSelection -> (Ptr TextSelection -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO Int32) -> IO Int32)
-> (Ptr TextSelection -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
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' textSelection [ #endOffset 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextSelectionEndOffset :: MonadIO m => TextSelection -> Int32 -> m ()
setTextSelectionEndOffset :: forall (m :: * -> *). MonadIO m => TextSelection -> Int32 -> m ()
setTextSelectionEndOffset TextSelection
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextSelection -> (Ptr TextSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO ()) -> IO ())
-> (Ptr TextSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Int32
val :: Int32)

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

textSelection_endOffset :: AttrLabelProxy "endOffset"
textSelection_endOffset = AttrLabelProxy

#endif


-- | Get the value of the “@start_is_active@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textSelection #startIsActive
-- @
getTextSelectionStartIsActive :: MonadIO m => TextSelection -> m Bool
getTextSelectionStartIsActive :: forall (m :: * -> *). MonadIO m => TextSelection -> m Bool
getTextSelectionStartIsActive TextSelection
s = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ TextSelection -> (Ptr TextSelection -> IO Bool) -> IO Bool
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO Bool) -> IO Bool)
-> (Ptr TextSelection -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) :: IO CInt
    let val' :: Bool
val' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
val
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
val'

-- | Set the value of the “@start_is_active@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textSelection [ #startIsActive 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextSelectionStartIsActive :: MonadIO m => TextSelection -> Bool -> m ()
setTextSelectionStartIsActive :: forall (m :: * -> *). MonadIO m => TextSelection -> Bool -> m ()
setTextSelectionStartIsActive TextSelection
s Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextSelection -> (Ptr TextSelection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextSelection
s ((Ptr TextSelection -> IO ()) -> IO ())
-> (Ptr TextSelection -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TextSelection
ptr -> do
    let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
val
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextSelection
ptr Ptr TextSelection -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) (CInt
val' :: CInt)

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

textSelection_startIsActive :: AttrLabelProxy "startIsActive"
textSelection_startIsActive = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TextSelection
type instance O.AttributeList TextSelection = TextSelectionAttributeList
type TextSelectionAttributeList = ('[ '("startObject", TextSelectionStartObjectFieldInfo), '("startOffset", TextSelectionStartOffsetFieldInfo), '("endObject", TextSelectionEndObjectFieldInfo), '("endOffset", TextSelectionEndOffsetFieldInfo), '("startIsActive", TextSelectionStartIsActiveFieldInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTextSelectionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveTextSelectionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTextSelectionMethod t TextSelection, O.OverloadedMethod info TextSelection p) => OL.IsLabel t (TextSelection -> 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 ~ ResolveTextSelectionMethod t TextSelection, O.OverloadedMethod info TextSelection p, R.HasField t TextSelection p) => R.HasField t TextSelection p where
    getField = O.overloadedMethod @info

#endif

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

#endif