{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.CssSection
(
CssSection(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveCssSectionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
CssSectionGetBytesMethodInfo ,
#endif
cssSectionGetBytes ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetEndLocationMethodInfo ,
#endif
cssSectionGetEndLocation ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetFileMethodInfo ,
#endif
cssSectionGetFile ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetParentMethodInfo ,
#endif
cssSectionGetParent ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetStartLocationMethodInfo ,
#endif
cssSectionGetStartLocation ,
cssSectionNew ,
cssSectionNewWithBytes ,
#if defined(ENABLE_OVERLOADING)
CssSectionPrintMethodInfo ,
#endif
cssSectionPrint ,
#if defined(ENABLE_OVERLOADING)
CssSectionRefMethodInfo ,
#endif
cssSectionRef ,
#if defined(ENABLE_OVERLOADING)
CssSectionToStringMethodInfo ,
#endif
cssSectionToString ,
#if defined(ENABLE_OVERLOADING)
CssSectionUnrefMethodInfo ,
#endif
cssSectionUnref ,
) 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
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.Gio.Interfaces.File as Gio.File
import {-# SOURCE #-} qualified GI.Gtk.Structs.CssLocation as Gtk.CssLocation
#else
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.Gio.Interfaces.File as Gio.File
import {-# SOURCE #-} qualified GI.Gtk.Structs.CssLocation as Gtk.CssLocation
#endif
newtype CssSection = CssSection (SP.ManagedPtr CssSection)
deriving (CssSection -> CssSection -> Bool
(CssSection -> CssSection -> Bool)
-> (CssSection -> CssSection -> Bool) -> Eq CssSection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CssSection -> CssSection -> Bool
== :: CssSection -> CssSection -> Bool
$c/= :: CssSection -> CssSection -> Bool
/= :: CssSection -> CssSection -> Bool
Eq)
instance SP.ManagedPtrNewtype CssSection where
toManagedPtr :: CssSection -> ManagedPtr CssSection
toManagedPtr (CssSection ManagedPtr CssSection
p) = ManagedPtr CssSection
p
foreign import ccall "gtk_css_section_get_type" c_gtk_css_section_get_type ::
IO GType
type instance O.ParentTypes CssSection = '[]
instance O.HasParentTypes CssSection
instance B.Types.TypedObject CssSection where
glibType :: IO GType
glibType = IO GType
c_gtk_css_section_get_type
instance B.Types.GBoxed CssSection
instance B.GValue.IsGValue (Maybe CssSection) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_css_section_get_type
gvalueSet_ :: Ptr GValue -> Maybe CssSection -> IO ()
gvalueSet_ Ptr GValue
gv Maybe CssSection
P.Nothing = Ptr GValue -> Ptr CssSection -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr CssSection
forall a. Ptr a
FP.nullPtr :: FP.Ptr CssSection)
gvalueSet_ Ptr GValue
gv (P.Just CssSection
obj) = CssSection -> (Ptr CssSection -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CssSection
obj (Ptr GValue -> Ptr CssSection -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe CssSection)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr CssSection)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr CssSection)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed CssSection ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CssSection
type instance O.AttributeList CssSection = CssSectionAttributeList
type CssSectionAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_css_section_new" gtk_css_section_new ::
Ptr Gio.File.File ->
Ptr Gtk.CssLocation.CssLocation ->
Ptr Gtk.CssLocation.CssLocation ->
IO (Ptr CssSection)
cssSectionNew ::
(B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a) =>
Maybe (a)
-> Gtk.CssLocation.CssLocation
-> Gtk.CssLocation.CssLocation
-> m CssSection
cssSectionNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFile a) =>
Maybe a -> CssLocation -> CssLocation -> m CssSection
cssSectionNew Maybe a
file CssLocation
start CssLocation
end = IO CssSection -> m CssSection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CssSection -> m CssSection) -> IO CssSection -> m CssSection
forall a b. (a -> b) -> a -> b
$ do
maybeFile <- case Maybe a
file of
Maybe a
Nothing -> Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
forall a. Ptr a
FP.nullPtr
Just a
jFile -> do
jFile' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jFile
return jFile'
start' <- unsafeManagedPtrGetPtr start
end' <- unsafeManagedPtrGetPtr end
result <- gtk_css_section_new maybeFile start' end'
checkUnexpectedReturnNULL "cssSectionNew" result
result' <- (wrapBoxed CssSection) result
whenJust file touchManagedPtr
touchManagedPtr start
touchManagedPtr end
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_css_section_new_with_bytes" gtk_css_section_new_with_bytes ::
Ptr Gio.File.File ->
Ptr GLib.Bytes.Bytes ->
Ptr Gtk.CssLocation.CssLocation ->
Ptr Gtk.CssLocation.CssLocation ->
IO (Ptr CssSection)
cssSectionNewWithBytes ::
(B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a) =>
Maybe (a)
-> Maybe (GLib.Bytes.Bytes)
-> Gtk.CssLocation.CssLocation
-> Gtk.CssLocation.CssLocation
-> m CssSection
cssSectionNewWithBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFile a) =>
Maybe a
-> Maybe Bytes -> CssLocation -> CssLocation -> m CssSection
cssSectionNewWithBytes Maybe a
file Maybe Bytes
bytes CssLocation
start CssLocation
end = IO CssSection -> m CssSection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CssSection -> m CssSection) -> IO CssSection -> m CssSection
forall a b. (a -> b) -> a -> b
$ do
maybeFile <- case Maybe a
file of
Maybe a
Nothing -> Ptr File -> IO (Ptr File)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
forall a. Ptr a
FP.nullPtr
Just a
jFile -> do
jFile' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jFile
return jFile'
maybeBytes <- case bytes of
Maybe Bytes
Nothing -> Ptr Bytes -> IO (Ptr Bytes)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Bytes
forall a. Ptr a
FP.nullPtr
Just Bytes
jBytes -> do
jBytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
jBytes
return jBytes'
start' <- unsafeManagedPtrGetPtr start
end' <- unsafeManagedPtrGetPtr end
result <- gtk_css_section_new_with_bytes maybeFile maybeBytes start' end'
checkUnexpectedReturnNULL "cssSectionNewWithBytes" result
result' <- (wrapBoxed CssSection) result
whenJust file touchManagedPtr
whenJust bytes touchManagedPtr
touchManagedPtr start
touchManagedPtr end
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_css_section_get_bytes" gtk_css_section_get_bytes ::
Ptr CssSection ->
IO (Ptr GLib.Bytes.Bytes)
cssSectionGetBytes ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m (Maybe GLib.Bytes.Bytes)
cssSectionGetBytes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m (Maybe Bytes)
cssSectionGetBytes CssSection
section = IO (Maybe Bytes) -> m (Maybe Bytes)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Bytes) -> m (Maybe Bytes))
-> IO (Maybe Bytes) -> m (Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
result <- gtk_css_section_get_bytes section'
maybeResult <- convertIfNonNull result $ \Ptr Bytes
result' -> do
result'' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result'
return result''
touchManagedPtr section
return maybeResult
#if defined(ENABLE_OVERLOADING)
data CssSectionGetBytesMethodInfo
instance (signature ~ (m (Maybe GLib.Bytes.Bytes)), MonadIO m) => O.OverloadedMethod CssSectionGetBytesMethodInfo CssSection signature where
overloadedMethod = cssSectionGetBytes
instance O.OverloadedMethodInfo CssSectionGetBytesMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetBytes",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetBytes"
})
#endif
foreign import ccall "gtk_css_section_get_end_location" gtk_css_section_get_end_location ::
Ptr CssSection ->
IO (Ptr Gtk.CssLocation.CssLocation)
cssSectionGetEndLocation ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m Gtk.CssLocation.CssLocation
cssSectionGetEndLocation :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m CssLocation
cssSectionGetEndLocation CssSection
section = IO CssLocation -> m CssLocation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CssLocation -> m CssLocation)
-> IO CssLocation -> m CssLocation
forall a b. (a -> b) -> a -> b
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
result <- gtk_css_section_get_end_location section'
checkUnexpectedReturnNULL "cssSectionGetEndLocation" result
result' <- (newPtr Gtk.CssLocation.CssLocation) result
touchManagedPtr section
return result'
#if defined(ENABLE_OVERLOADING)
data CssSectionGetEndLocationMethodInfo
instance (signature ~ (m Gtk.CssLocation.CssLocation), MonadIO m) => O.OverloadedMethod CssSectionGetEndLocationMethodInfo CssSection signature where
overloadedMethod = cssSectionGetEndLocation
instance O.OverloadedMethodInfo CssSectionGetEndLocationMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetEndLocation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetEndLocation"
})
#endif
foreign import ccall "gtk_css_section_get_file" gtk_css_section_get_file ::
Ptr CssSection ->
IO (Ptr Gio.File.File)
cssSectionGetFile ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m (Maybe Gio.File.File)
cssSectionGetFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m (Maybe File)
cssSectionGetFile CssSection
section = IO (Maybe File) -> m (Maybe File)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe File) -> m (Maybe File))
-> IO (Maybe File) -> m (Maybe File)
forall a b. (a -> b) -> a -> b
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
result <- gtk_css_section_get_file section'
maybeResult <- convertIfNonNull result $ \Ptr File
result' -> do
result'' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
result'
return result''
touchManagedPtr section
return maybeResult
#if defined(ENABLE_OVERLOADING)
data CssSectionGetFileMethodInfo
instance (signature ~ (m (Maybe Gio.File.File)), MonadIO m) => O.OverloadedMethod CssSectionGetFileMethodInfo CssSection signature where
overloadedMethod = cssSectionGetFile
instance O.OverloadedMethodInfo CssSectionGetFileMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetFile",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetFile"
})
#endif
foreign import ccall "gtk_css_section_get_parent" gtk_css_section_get_parent ::
Ptr CssSection ->
IO (Ptr CssSection)
cssSectionGetParent ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m (Maybe CssSection)
cssSectionGetParent :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m (Maybe CssSection)
cssSectionGetParent CssSection
section = IO (Maybe CssSection) -> m (Maybe CssSection)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe CssSection) -> m (Maybe CssSection))
-> IO (Maybe CssSection) -> m (Maybe CssSection)
forall a b. (a -> b) -> a -> b
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
result <- gtk_css_section_get_parent section'
maybeResult <- convertIfNonNull result $ \Ptr CssSection
result' -> do
result'' <- ((ManagedPtr CssSection -> CssSection)
-> Ptr CssSection -> IO CssSection
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr CssSection -> CssSection
CssSection) Ptr CssSection
result'
return result''
touchManagedPtr section
return maybeResult
#if defined(ENABLE_OVERLOADING)
data CssSectionGetParentMethodInfo
instance (signature ~ (m (Maybe CssSection)), MonadIO m) => O.OverloadedMethod CssSectionGetParentMethodInfo CssSection signature where
overloadedMethod = cssSectionGetParent
instance O.OverloadedMethodInfo CssSectionGetParentMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetParent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetParent"
})
#endif
foreign import ccall "gtk_css_section_get_start_location" gtk_css_section_get_start_location ::
Ptr CssSection ->
IO (Ptr Gtk.CssLocation.CssLocation)
cssSectionGetStartLocation ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m Gtk.CssLocation.CssLocation
cssSectionGetStartLocation :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m CssLocation
cssSectionGetStartLocation CssSection
section = IO CssLocation -> m CssLocation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CssLocation -> m CssLocation)
-> IO CssLocation -> m CssLocation
forall a b. (a -> b) -> a -> b
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
result <- gtk_css_section_get_start_location section'
checkUnexpectedReturnNULL "cssSectionGetStartLocation" result
result' <- (newPtr Gtk.CssLocation.CssLocation) result
touchManagedPtr section
return result'
#if defined(ENABLE_OVERLOADING)
data CssSectionGetStartLocationMethodInfo
instance (signature ~ (m Gtk.CssLocation.CssLocation), MonadIO m) => O.OverloadedMethod CssSectionGetStartLocationMethodInfo CssSection signature where
overloadedMethod = cssSectionGetStartLocation
instance O.OverloadedMethodInfo CssSectionGetStartLocationMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetStartLocation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetStartLocation"
})
#endif
foreign import ccall "gtk_css_section_print" gtk_css_section_print ::
Ptr CssSection ->
Ptr GLib.String.String ->
IO ()
cssSectionPrint ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> GLib.String.String
-> m ()
cssSectionPrint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> String -> m ()
cssSectionPrint CssSection
section String
string = 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
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
string' <- unsafeManagedPtrGetPtr string
gtk_css_section_print section' string'
touchManagedPtr section
touchManagedPtr string
return ()
#if defined(ENABLE_OVERLOADING)
data CssSectionPrintMethodInfo
instance (signature ~ (GLib.String.String -> m ()), MonadIO m) => O.OverloadedMethod CssSectionPrintMethodInfo CssSection signature where
overloadedMethod = cssSectionPrint
instance O.OverloadedMethodInfo CssSectionPrintMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionPrint",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionPrint"
})
#endif
foreign import ccall "gtk_css_section_ref" gtk_css_section_ref ::
Ptr CssSection ->
IO (Ptr CssSection)
cssSectionRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m CssSection
cssSectionRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m CssSection
cssSectionRef CssSection
section = IO CssSection -> m CssSection
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CssSection -> m CssSection) -> IO CssSection -> m CssSection
forall a b. (a -> b) -> a -> b
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
result <- gtk_css_section_ref section'
checkUnexpectedReturnNULL "cssSectionRef" result
result' <- (wrapBoxed CssSection) result
touchManagedPtr section
return result'
#if defined(ENABLE_OVERLOADING)
data CssSectionRefMethodInfo
instance (signature ~ (m CssSection), MonadIO m) => O.OverloadedMethod CssSectionRefMethodInfo CssSection signature where
overloadedMethod = cssSectionRef
instance O.OverloadedMethodInfo CssSectionRefMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionRef"
})
#endif
foreign import ccall "gtk_css_section_to_string" gtk_css_section_to_string ::
Ptr CssSection ->
IO CString
cssSectionToString ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m T.Text
cssSectionToString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m Text
cssSectionToString CssSection
section = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
result <- gtk_css_section_to_string section'
checkUnexpectedReturnNULL "cssSectionToString" result
result' <- cstringToText result
freeMem result
touchManagedPtr section
return result'
#if defined(ENABLE_OVERLOADING)
data CssSectionToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod CssSectionToStringMethodInfo CssSection signature where
overloadedMethod = cssSectionToString
instance O.OverloadedMethodInfo CssSectionToStringMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionToString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionToString"
})
#endif
foreign import ccall "gtk_css_section_unref" gtk_css_section_unref ::
Ptr CssSection ->
IO ()
cssSectionUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m ()
cssSectionUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m ()
cssSectionUnref CssSection
section = 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
$ do
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed CssSection
section
gtk_css_section_unref section'
touchManagedPtr section
return ()
#if defined(ENABLE_OVERLOADING)
data CssSectionUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod CssSectionUnrefMethodInfo CssSection signature where
overloadedMethod = cssSectionUnref
instance O.OverloadedMethodInfo CssSectionUnrefMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveCssSectionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveCssSectionMethod "print" o = CssSectionPrintMethodInfo
ResolveCssSectionMethod "ref" o = CssSectionRefMethodInfo
ResolveCssSectionMethod "toString" o = CssSectionToStringMethodInfo
ResolveCssSectionMethod "unref" o = CssSectionUnrefMethodInfo
ResolveCssSectionMethod "getBytes" o = CssSectionGetBytesMethodInfo
ResolveCssSectionMethod "getEndLocation" o = CssSectionGetEndLocationMethodInfo
ResolveCssSectionMethod "getFile" o = CssSectionGetFileMethodInfo
ResolveCssSectionMethod "getParent" o = CssSectionGetParentMethodInfo
ResolveCssSectionMethod "getStartLocation" o = CssSectionGetStartLocationMethodInfo
ResolveCssSectionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveCssSectionMethod t CssSection, O.OverloadedMethod info CssSection p) => OL.IsLabel t (CssSection -> 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 ~ ResolveCssSectionMethod t CssSection, O.OverloadedMethod info CssSection p, R.HasField t CssSection p) => R.HasField t CssSection p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveCssSectionMethod t CssSection, O.OverloadedMethodInfo info CssSection) => OL.IsLabel t (O.MethodProxy info CssSection) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif