{-# 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)
CssSectionGetEndLineMethodInfo ,
#endif
cssSectionGetEndLine ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetEndPositionMethodInfo ,
#endif
cssSectionGetEndPosition ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetFileMethodInfo ,
#endif
cssSectionGetFile ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetParentMethodInfo ,
#endif
cssSectionGetParent ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetSectionTypeMethodInfo ,
#endif
cssSectionGetSectionType ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetStartLineMethodInfo ,
#endif
cssSectionGetStartLine ,
#if defined(ENABLE_OVERLOADING)
CssSectionGetStartPositionMethodInfo ,
#endif
cssSectionGetStartPosition ,
#if defined(ENABLE_OVERLOADING)
CssSectionRefMethodInfo ,
#endif
cssSectionRef ,
#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 GI.Gio.Interfaces.File as Gio.File
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
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 CssSection
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 CssSection
ptr Ptr CssSection -> Ptr CssSection -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CssSection
forall a. Ptr a
FP.nullPtr
then CssSection -> Maybe CssSection
forall a. a -> Maybe a
P.Just (CssSection -> Maybe CssSection)
-> IO CssSection -> IO (Maybe CssSection)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr CssSection -> CssSection)
-> Ptr CssSection -> IO CssSection
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr CssSection -> CssSection
CssSection Ptr CssSection
ptr
else Maybe CssSection -> IO (Maybe CssSection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CssSection
forall a. Maybe a
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_get_end_line" gtk_css_section_get_end_line ::
Ptr CssSection ->
IO Word32
cssSectionGetEndLine ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m Word32
cssSectionGetEndLine :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m Word32
cssSectionGetEndLine CssSection
section = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Word32
result <- Ptr CssSection -> IO Word32
gtk_css_section_get_end_line Ptr CssSection
section'
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data CssSectionGetEndLineMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod CssSectionGetEndLineMethodInfo CssSection signature where
overloadedMethod = cssSectionGetEndLine
instance O.OverloadedMethodInfo CssSectionGetEndLineMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetEndLine",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetEndLine"
})
#endif
foreign import ccall "gtk_css_section_get_end_position" gtk_css_section_get_end_position ::
Ptr CssSection ->
IO Word32
cssSectionGetEndPosition ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m Word32
cssSectionGetEndPosition :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m Word32
cssSectionGetEndPosition CssSection
section = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Word32
result <- Ptr CssSection -> IO Word32
gtk_css_section_get_end_position Ptr CssSection
section'
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data CssSectionGetEndPositionMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod CssSectionGetEndPositionMethodInfo CssSection signature where
overloadedMethod = cssSectionGetEndPosition
instance O.OverloadedMethodInfo CssSectionGetEndPositionMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetEndPosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetEndPosition"
})
#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 Gio.File.File
cssSectionGetFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m File
cssSectionGetFile CssSection
section = IO File -> m File
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ do
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Ptr File
result <- Ptr CssSection -> IO (Ptr File)
gtk_css_section_get_file Ptr CssSection
section'
Text -> Ptr File -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cssSectionGetFile" Ptr File
result
File
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
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
File -> IO File
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return File
result'
#if defined(ENABLE_OVERLOADING)
data CssSectionGetFileMethodInfo
instance (signature ~ (m 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-gtk-3.0.41/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
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Ptr CssSection
result <- Ptr CssSection -> IO (Ptr CssSection)
gtk_css_section_get_parent Ptr CssSection
section'
Maybe CssSection
maybeResult <- Ptr CssSection
-> (Ptr CssSection -> IO CssSection) -> IO (Maybe CssSection)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CssSection
result ((Ptr CssSection -> IO CssSection) -> IO (Maybe CssSection))
-> (Ptr CssSection -> IO CssSection) -> IO (Maybe CssSection)
forall a b. (a -> b) -> a -> b
$ \Ptr CssSection
result' -> do
CssSection
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'
CssSection -> IO CssSection
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CssSection
result''
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
Maybe CssSection -> IO (Maybe CssSection)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CssSection
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-gtk-3.0.41/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetParent"
})
#endif
foreign import ccall "gtk_css_section_get_section_type" gtk_css_section_get_section_type ::
Ptr CssSection ->
IO CUInt
cssSectionGetSectionType ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m Gtk.Enums.CssSectionType
cssSectionGetSectionType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m CssSectionType
cssSectionGetSectionType CssSection
section = IO CssSectionType -> m CssSectionType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CssSectionType -> m CssSectionType)
-> IO CssSectionType -> m CssSectionType
forall a b. (a -> b) -> a -> b
$ do
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
CUInt
result <- Ptr CssSection -> IO CUInt
gtk_css_section_get_section_type Ptr CssSection
section'
let result' :: CssSectionType
result' = (Int -> CssSectionType
forall a. Enum a => Int -> a
toEnum (Int -> CssSectionType)
-> (CUInt -> Int) -> CUInt -> CssSectionType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
CssSectionType -> IO CssSectionType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CssSectionType
result'
#if defined(ENABLE_OVERLOADING)
data CssSectionGetSectionTypeMethodInfo
instance (signature ~ (m Gtk.Enums.CssSectionType), MonadIO m) => O.OverloadedMethod CssSectionGetSectionTypeMethodInfo CssSection signature where
overloadedMethod = cssSectionGetSectionType
instance O.OverloadedMethodInfo CssSectionGetSectionTypeMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetSectionType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetSectionType"
})
#endif
foreign import ccall "gtk_css_section_get_start_line" gtk_css_section_get_start_line ::
Ptr CssSection ->
IO Word32
cssSectionGetStartLine ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m Word32
cssSectionGetStartLine :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m Word32
cssSectionGetStartLine CssSection
section = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Word32
result <- Ptr CssSection -> IO Word32
gtk_css_section_get_start_line Ptr CssSection
section'
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data CssSectionGetStartLineMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod CssSectionGetStartLineMethodInfo CssSection signature where
overloadedMethod = cssSectionGetStartLine
instance O.OverloadedMethodInfo CssSectionGetStartLineMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetStartLine",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetStartLine"
})
#endif
foreign import ccall "gtk_css_section_get_start_position" gtk_css_section_get_start_position ::
Ptr CssSection ->
IO Word32
cssSectionGetStartPosition ::
(B.CallStack.HasCallStack, MonadIO m) =>
CssSection
-> m Word32
cssSectionGetStartPosition :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m Word32
cssSectionGetStartPosition CssSection
section = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Word32
result <- Ptr CssSection -> IO Word32
gtk_css_section_get_start_position Ptr CssSection
section'
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data CssSectionGetStartPositionMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod CssSectionGetStartPositionMethodInfo CssSection signature where
overloadedMethod = cssSectionGetStartPosition
instance O.OverloadedMethodInfo CssSectionGetStartPositionMethodInfo CssSection where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.CssSection.cssSectionGetStartPosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionGetStartPosition"
})
#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
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Ptr CssSection
result <- Ptr CssSection -> IO (Ptr CssSection)
gtk_css_section_ref Ptr CssSection
section'
Text -> Ptr CssSection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cssSectionRef" Ptr CssSection
result
CssSection
result' <- ((ManagedPtr CssSection -> CssSection)
-> Ptr CssSection -> IO CssSection
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr CssSection -> CssSection
CssSection) Ptr CssSection
result
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
CssSection -> IO CssSection
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CssSection
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-gtk-3.0.41/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionRef"
})
#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
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Ptr CssSection -> IO ()
gtk_css_section_unref Ptr CssSection
section'
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
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-gtk-3.0.41/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 "ref" o = CssSectionRefMethodInfo
ResolveCssSectionMethod "unref" o = CssSectionUnrefMethodInfo
ResolveCssSectionMethod "getEndLine" o = CssSectionGetEndLineMethodInfo
ResolveCssSectionMethod "getEndPosition" o = CssSectionGetEndPositionMethodInfo
ResolveCssSectionMethod "getFile" o = CssSectionGetFileMethodInfo
ResolveCssSectionMethod "getParent" o = CssSectionGetParentMethodInfo
ResolveCssSectionMethod "getSectionType" o = CssSectionGetSectionTypeMethodInfo
ResolveCssSectionMethod "getStartLine" o = CssSectionGetStartLineMethodInfo
ResolveCssSectionMethod "getStartPosition" o = CssSectionGetStartPositionMethodInfo
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