{-# LANGUAGE TypeApplications #-} -- | Copyright : Will Thompson, Iñaki García Etxebarria and Jonas Platte -- License : LGPL-2.1 -- Maintainer : Iñaki García Etxebarria -- -- t'GI.Atk.Interfaces.EditableText.EditableText' should be implemented by UI components which -- contain text which the user can edit, via the t'GI.Atk.Objects.Object.Object' -- corresponding to that component (see t'GI.Atk.Objects.Object.Object'). -- -- t'GI.Atk.Interfaces.EditableText.EditableText' is a subclass of t'GI.Atk.Interfaces.Text.Text', and as such, an object -- which implements t'GI.Atk.Interfaces.EditableText.EditableText' is by definition an t'GI.Atk.Interfaces.Text.Text' -- implementor as well. -- -- See also: t'GI.Atk.Interfaces.Text.Text' #if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__)) #define ENABLE_OVERLOADING #endif module GI.Atk.Interfaces.EditableText ( -- * Exported types EditableText(..) , IsEditableText , -- * Methods -- ** Overloaded methods #method:Overloaded methods# #if defined(ENABLE_OVERLOADING) ResolveEditableTextMethod , #endif -- ** copyText #method:copyText# #if defined(ENABLE_OVERLOADING) EditableTextCopyTextMethodInfo , #endif editableTextCopyText , -- ** cutText #method:cutText# #if defined(ENABLE_OVERLOADING) EditableTextCutTextMethodInfo , #endif editableTextCutText , -- ** deleteText #method:deleteText# #if defined(ENABLE_OVERLOADING) EditableTextDeleteTextMethodInfo , #endif editableTextDeleteText , -- ** insertText #method:insertText# #if defined(ENABLE_OVERLOADING) EditableTextInsertTextMethodInfo , #endif editableTextInsertText , -- ** pasteText #method:pasteText# #if defined(ENABLE_OVERLOADING) EditableTextPasteTextMethodInfo , #endif editableTextPasteText , -- ** setRunAttributes #method:setRunAttributes# #if defined(ENABLE_OVERLOADING) EditableTextSetRunAttributesMethodInfo , #endif editableTextSetRunAttributes , -- ** setTextContents #method:setTextContents# #if defined(ENABLE_OVERLOADING) EditableTextSetTextContentsMethodInfo , #endif editableTextSetTextContents , ) 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.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.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 -- interface EditableText -- | Memory-managed wrapper type. newtype EditableText = EditableText (SP.ManagedPtr EditableText) deriving (EditableText -> EditableText -> Bool (EditableText -> EditableText -> Bool) -> (EditableText -> EditableText -> Bool) -> Eq EditableText forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: EditableText -> EditableText -> Bool $c/= :: EditableText -> EditableText -> Bool == :: EditableText -> EditableText -> Bool $c== :: EditableText -> EditableText -> Bool Eq) instance SP.ManagedPtrNewtype EditableText where toManagedPtr :: EditableText -> ManagedPtr EditableText toManagedPtr (EditableText ManagedPtr EditableText p) = ManagedPtr EditableText p -- | Type class for types which implement `EditableText`. class (ManagedPtrNewtype o, O.IsDescendantOf EditableText o) => IsEditableText o instance (ManagedPtrNewtype o, O.IsDescendantOf EditableText o) => IsEditableText o -- XXX Wrapping a foreign struct/union with no known destructor or size, leak? instance BoxedPtr EditableText where boxedPtrCopy :: EditableText -> IO EditableText boxedPtrCopy = EditableText -> IO EditableText forall (m :: * -> *) a. Monad m => a -> m a return boxedPtrFree :: EditableText -> IO () boxedPtrFree = \EditableText _x -> () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) type family ResolveEditableTextMethod (t :: Symbol) (o :: *) :: * where ResolveEditableTextMethod "copyText" o = EditableTextCopyTextMethodInfo ResolveEditableTextMethod "cutText" o = EditableTextCutTextMethodInfo ResolveEditableTextMethod "deleteText" o = EditableTextDeleteTextMethodInfo ResolveEditableTextMethod "insertText" o = EditableTextInsertTextMethodInfo ResolveEditableTextMethod "pasteText" o = EditableTextPasteTextMethodInfo ResolveEditableTextMethod "setRunAttributes" o = EditableTextSetRunAttributesMethodInfo ResolveEditableTextMethod "setTextContents" o = EditableTextSetTextContentsMethodInfo ResolveEditableTextMethod l o = O.MethodResolutionFailed l o instance (info ~ ResolveEditableTextMethod t EditableText, O.MethodInfo info EditableText p) => OL.IsLabel t (EditableText -> p) where #if MIN_VERSION_base(4,10,0) fromLabel = O.overloadedMethod @info #else fromLabel _ = O.overloadedMethod @info #endif #endif -- method EditableText::copy_text -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "text" -- , argType = -- TInterface Name { namespace = "Atk" , name = "EditableText" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkEditableText" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "start_pos" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "start position" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "end_pos" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "end position" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "atk_editable_text_copy_text" atk_editable_text_copy_text :: Ptr EditableText -> -- text : TInterface (Name {namespace = "Atk", name = "EditableText"}) Int32 -> -- start_pos : TBasicType TInt Int32 -> -- end_pos : TBasicType TInt IO () -- | Copy text from /@startPos@/ up to, but not including /@endPos@/ -- to the clipboard. editableTextCopyText :: (B.CallStack.HasCallStack, MonadIO m, IsEditableText a) => a -- ^ /@text@/: an t'GI.Atk.Interfaces.EditableText.EditableText' -> Int32 -- ^ /@startPos@/: start position -> Int32 -- ^ /@endPos@/: end position -> m () editableTextCopyText :: a -> Int32 -> Int32 -> m () editableTextCopyText a text Int32 startPos Int32 endPos = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do Ptr EditableText text' <- a -> IO (Ptr EditableText) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a text Ptr EditableText -> Int32 -> Int32 -> IO () atk_editable_text_copy_text Ptr EditableText text' Int32 startPos Int32 endPos a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a text () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) data EditableTextCopyTextMethodInfo instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsEditableText a) => O.MethodInfo EditableTextCopyTextMethodInfo a signature where overloadedMethod = editableTextCopyText #endif -- method EditableText::cut_text -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "text" -- , argType = -- TInterface Name { namespace = "Atk" , name = "EditableText" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkEditableText" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "start_pos" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "start position" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "end_pos" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "end position" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "atk_editable_text_cut_text" atk_editable_text_cut_text :: Ptr EditableText -> -- text : TInterface (Name {namespace = "Atk", name = "EditableText"}) Int32 -> -- start_pos : TBasicType TInt Int32 -> -- end_pos : TBasicType TInt IO () -- | Copy text from /@startPos@/ up to, but not including /@endPos@/ -- to the clipboard and then delete from the widget. editableTextCutText :: (B.CallStack.HasCallStack, MonadIO m, IsEditableText a) => a -- ^ /@text@/: an t'GI.Atk.Interfaces.EditableText.EditableText' -> Int32 -- ^ /@startPos@/: start position -> Int32 -- ^ /@endPos@/: end position -> m () editableTextCutText :: a -> Int32 -> Int32 -> m () editableTextCutText a text Int32 startPos Int32 endPos = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do Ptr EditableText text' <- a -> IO (Ptr EditableText) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a text Ptr EditableText -> Int32 -> Int32 -> IO () atk_editable_text_cut_text Ptr EditableText text' Int32 startPos Int32 endPos a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a text () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) data EditableTextCutTextMethodInfo instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsEditableText a) => O.MethodInfo EditableTextCutTextMethodInfo a signature where overloadedMethod = editableTextCutText #endif -- method EditableText::delete_text -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "text" -- , argType = -- TInterface Name { namespace = "Atk" , name = "EditableText" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkEditableText" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "start_pos" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "start position" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "end_pos" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "end position" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "atk_editable_text_delete_text" atk_editable_text_delete_text :: Ptr EditableText -> -- text : TInterface (Name {namespace = "Atk", name = "EditableText"}) Int32 -> -- start_pos : TBasicType TInt Int32 -> -- end_pos : TBasicType TInt IO () -- | Delete text /@startPos@/ up to, but not including /@endPos@/. editableTextDeleteText :: (B.CallStack.HasCallStack, MonadIO m, IsEditableText a) => a -- ^ /@text@/: an t'GI.Atk.Interfaces.EditableText.EditableText' -> Int32 -- ^ /@startPos@/: start position -> Int32 -- ^ /@endPos@/: end position -> m () editableTextDeleteText :: a -> Int32 -> Int32 -> m () editableTextDeleteText a text Int32 startPos Int32 endPos = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do Ptr EditableText text' <- a -> IO (Ptr EditableText) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a text Ptr EditableText -> Int32 -> Int32 -> IO () atk_editable_text_delete_text Ptr EditableText text' Int32 startPos Int32 endPos a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a text () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) data EditableTextDeleteTextMethodInfo instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsEditableText a) => O.MethodInfo EditableTextDeleteTextMethodInfo a signature where overloadedMethod = editableTextDeleteText #endif -- method EditableText::insert_text -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "text" -- , argType = -- TInterface Name { namespace = "Atk" , name = "EditableText" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkEditableText" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "string" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the text to insert" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "length" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "the length of text to insert, in bytes" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "position" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = -- Just -- "The caller initializes this to\nthe position at which to insert the text. After the call it\npoints at the position after the newly inserted text." -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "atk_editable_text_insert_text" atk_editable_text_insert_text :: Ptr EditableText -> -- text : TInterface (Name {namespace = "Atk", name = "EditableText"}) CString -> -- string : TBasicType TUTF8 Int32 -> -- length : TBasicType TInt Int32 -> -- position : TBasicType TInt IO () -- | Insert text at a given position. editableTextInsertText :: (B.CallStack.HasCallStack, MonadIO m, IsEditableText a) => a -- ^ /@text@/: an t'GI.Atk.Interfaces.EditableText.EditableText' -> T.Text -- ^ /@string@/: the text to insert -> Int32 -- ^ /@length@/: the length of text to insert, in bytes -> Int32 -- ^ /@position@/: The caller initializes this to -- the position at which to insert the text. After the call it -- points at the position after the newly inserted text. -> m () editableTextInsertText :: a -> Text -> Int32 -> Int32 -> m () editableTextInsertText a text Text string Int32 length_ Int32 position = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do Ptr EditableText text' <- a -> IO (Ptr EditableText) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a text CString string' <- Text -> IO CString textToCString Text string Ptr EditableText -> CString -> Int32 -> Int32 -> IO () atk_editable_text_insert_text Ptr EditableText text' CString string' Int32 length_ Int32 position a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a text CString -> IO () forall a. Ptr a -> IO () freeMem CString string' () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) data EditableTextInsertTextMethodInfo instance (signature ~ (T.Text -> Int32 -> Int32 -> m ()), MonadIO m, IsEditableText a) => O.MethodInfo EditableTextInsertTextMethodInfo a signature where overloadedMethod = editableTextInsertText #endif -- method EditableText::paste_text -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "text" -- , argType = -- TInterface Name { namespace = "Atk" , name = "EditableText" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkEditableText" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "position" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "position to paste" , sinceVersion = Nothing } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "atk_editable_text_paste_text" atk_editable_text_paste_text :: Ptr EditableText -> -- text : TInterface (Name {namespace = "Atk", name = "EditableText"}) Int32 -> -- position : TBasicType TInt IO () -- | Paste text from clipboard to specified /@position@/. editableTextPasteText :: (B.CallStack.HasCallStack, MonadIO m, IsEditableText a) => a -- ^ /@text@/: an t'GI.Atk.Interfaces.EditableText.EditableText' -> Int32 -- ^ /@position@/: position to paste -> m () editableTextPasteText :: a -> Int32 -> m () editableTextPasteText a text Int32 position = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do Ptr EditableText text' <- a -> IO (Ptr EditableText) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a text Ptr EditableText -> Int32 -> IO () atk_editable_text_paste_text Ptr EditableText text' Int32 position a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a text () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) data EditableTextPasteTextMethodInfo instance (signature ~ (Int32 -> m ()), MonadIO m, IsEditableText a) => O.MethodInfo EditableTextPasteTextMethodInfo a signature where overloadedMethod = editableTextPasteText #endif -- method EditableText::set_run_attributes -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "text" -- , argType = -- TInterface Name { namespace = "Atk" , name = "EditableText" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkEditableText" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "attrib_set" -- , argType = TGSList (TBasicType TPtr) -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkAttributeSet" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "start_offset" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "start of range in which to set attributes" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "end_offset" -- , argType = TBasicType TInt -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "end of range in which to set attributes" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Just (TBasicType TBoolean) -- throws : False -- Skip return : False foreign import ccall "atk_editable_text_set_run_attributes" atk_editable_text_set_run_attributes :: Ptr EditableText -> -- text : TInterface (Name {namespace = "Atk", name = "EditableText"}) Ptr (GSList (Ptr ())) -> -- attrib_set : TGSList (TBasicType TPtr) Int32 -> -- start_offset : TBasicType TInt Int32 -> -- end_offset : TBasicType TInt IO CInt -- | Sets the attributes for a specified range. See the ATK_ATTRIBUTE -- macros (such as @/ATK_ATTRIBUTE_LEFT_MARGIN/@) for examples of attributes -- that can be set. Note that other attributes that do not have corresponding -- ATK_ATTRIBUTE macros may also be set for certain text widgets. editableTextSetRunAttributes :: (B.CallStack.HasCallStack, MonadIO m, IsEditableText a) => a -- ^ /@text@/: an t'GI.Atk.Interfaces.EditableText.EditableText' -> [Ptr ()] -- ^ /@attribSet@/: an @/AtkAttributeSet/@ -> Int32 -- ^ /@startOffset@/: start of range in which to set attributes -> Int32 -- ^ /@endOffset@/: end of range in which to set attributes -> m Bool -- ^ __Returns:__ 'P.True' if attributes successfully set for the specified -- range, otherwise 'P.False' editableTextSetRunAttributes :: a -> [Ptr ()] -> Int32 -> Int32 -> m Bool editableTextSetRunAttributes a text [Ptr ()] attribSet Int32 startOffset Int32 endOffset = IO Bool -> m Bool 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 $ do Ptr EditableText text' <- a -> IO (Ptr EditableText) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a text Ptr (GSList (Ptr ())) attribSet' <- [Ptr ()] -> IO (Ptr (GSList (Ptr ()))) forall a. [Ptr a] -> IO (Ptr (GSList (Ptr a))) packGSList [Ptr ()] attribSet CInt result <- Ptr EditableText -> Ptr (GSList (Ptr ())) -> Int32 -> Int32 -> IO CInt atk_editable_text_set_run_attributes Ptr EditableText text' Ptr (GSList (Ptr ())) attribSet' Int32 startOffset Int32 endOffset let result' :: Bool result' = (CInt -> CInt -> Bool forall a. Eq a => a -> a -> Bool /= CInt 0) CInt result a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a text Ptr (GSList (Ptr ())) -> IO () forall a. Ptr (GSList a) -> IO () g_slist_free Ptr (GSList (Ptr ())) attribSet' Bool -> IO Bool forall (m :: * -> *) a. Monad m => a -> m a return Bool result' #if defined(ENABLE_OVERLOADING) data EditableTextSetRunAttributesMethodInfo instance (signature ~ ([Ptr ()] -> Int32 -> Int32 -> m Bool), MonadIO m, IsEditableText a) => O.MethodInfo EditableTextSetRunAttributesMethodInfo a signature where overloadedMethod = editableTextSetRunAttributes #endif -- method EditableText::set_text_contents -- method type : OrdinaryMethod -- Args: [ Arg -- { argCName = "text" -- , argType = -- TInterface Name { namespace = "Atk" , name = "EditableText" } -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "an #AtkEditableText" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- , Arg -- { argCName = "string" -- , argType = TBasicType TUTF8 -- , direction = DirectionIn -- , mayBeNull = False -- , argDoc = -- Documentation -- { rawDocText = Just "string to set for text contents of @text" -- , sinceVersion = Nothing -- } -- , argScope = ScopeTypeInvalid -- , argClosure = -1 -- , argDestroy = -1 -- , argCallerAllocates = False -- , transfer = TransferNothing -- } -- ] -- Lengths: [] -- returnType: Nothing -- throws : False -- Skip return : False foreign import ccall "atk_editable_text_set_text_contents" atk_editable_text_set_text_contents :: Ptr EditableText -> -- text : TInterface (Name {namespace = "Atk", name = "EditableText"}) CString -> -- string : TBasicType TUTF8 IO () -- | Set text contents of /@text@/. editableTextSetTextContents :: (B.CallStack.HasCallStack, MonadIO m, IsEditableText a) => a -- ^ /@text@/: an t'GI.Atk.Interfaces.EditableText.EditableText' -> T.Text -- ^ /@string@/: string to set for text contents of /@text@/ -> m () editableTextSetTextContents :: a -> Text -> m () editableTextSetTextContents a text Text string = IO () -> m () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ do Ptr EditableText text' <- a -> IO (Ptr EditableText) forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b) unsafeManagedPtrCastPtr a text CString string' <- Text -> IO CString textToCString Text string Ptr EditableText -> CString -> IO () atk_editable_text_set_text_contents Ptr EditableText text' CString string' a -> IO () forall a. ManagedPtrNewtype a => a -> IO () touchManagedPtr a text CString -> IO () forall a. Ptr a -> IO () freeMem CString string' () -> IO () forall (m :: * -> *) a. Monad m => a -> m a return () #if defined(ENABLE_OVERLOADING) data EditableTextSetTextContentsMethodInfo instance (signature ~ (T.Text -> m ()), MonadIO m, IsEditableText a) => O.MethodInfo EditableTextSetTextContentsMethodInfo a signature where overloadedMethod = editableTextSetTextContents #endif #if defined(ENABLE_OVERLOADING) type instance O.SignalList EditableText = EditableTextSignalList type EditableTextSignalList = ('[ ] :: [(Symbol, *)]) #endif