{-# 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)
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 ,
#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.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
import qualified GHC.Records as R
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
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
/= :: CssSection -> CssSection -> Bool
$c/= :: CssSection -> CssSection -> Bool
== :: CssSection -> CssSection -> Bool
$c== :: 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 (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, *)])
#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 (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 File
maybeFile <- case Maybe a
file of
Maybe a
Nothing -> Ptr File -> IO (Ptr File)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
forall a. Ptr a
nullPtr
Just a
jFile -> do
Ptr File
jFile' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jFile
Ptr File -> IO (Ptr File)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr File
jFile'
Ptr CssLocation
start' <- CssLocation -> IO (Ptr CssLocation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssLocation
start
Ptr CssLocation
end' <- CssLocation -> IO (Ptr CssLocation)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssLocation
end
Ptr CssSection
result <- Ptr File
-> Ptr CssLocation -> Ptr CssLocation -> IO (Ptr CssSection)
gtk_css_section_new Ptr File
maybeFile Ptr CssLocation
start' Ptr CssLocation
end'
Text -> Ptr CssSection -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cssSectionNew" 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
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
file a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
CssLocation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssLocation
start
CssLocation -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssLocation
end
CssSection -> IO CssSection
forall (m :: * -> *) a. Monad m => a -> m a
return CssSection
result'
#if defined(ENABLE_OVERLOADING)
#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 (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
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Ptr CssLocation
result <- Ptr CssSection -> IO (Ptr CssLocation)
gtk_css_section_get_end_location Ptr CssSection
section'
Text -> Ptr CssLocation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cssSectionGetEndLocation" Ptr CssLocation
result
CssLocation
result' <- ((ManagedPtr CssLocation -> CssLocation)
-> Ptr CssLocation -> IO CssLocation
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr CssLocation -> CssLocation
Gtk.CssLocation.CssLocation) Ptr CssLocation
result
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
CssLocation -> IO CssLocation
forall (m :: * -> *) a. Monad m => a -> m a
return CssLocation
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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionGetEndLocation",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/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 Gio.File.File
cssSectionGetFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CssSection -> m File
cssSectionGetFile CssSection
section = IO File -> m File
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 (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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionGetFile",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/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 (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 (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 (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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionGetParent",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/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 (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
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
Ptr CssLocation
result <- Ptr CssSection -> IO (Ptr CssLocation)
gtk_css_section_get_start_location Ptr CssSection
section'
Text -> Ptr CssLocation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cssSectionGetStartLocation" Ptr CssLocation
result
CssLocation
result' <- ((ManagedPtr CssLocation -> CssLocation)
-> Ptr CssLocation -> IO CssLocation
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr CssLocation -> CssLocation
Gtk.CssLocation.CssLocation) Ptr CssLocation
result
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
CssLocation -> IO CssLocation
forall (m :: * -> *) a. Monad m => a -> m a
return CssLocation
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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionGetStartLocation",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/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 (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 String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
Ptr CssSection -> Ptr String -> IO ()
gtk_css_section_print Ptr CssSection
section' Ptr String
string'
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionPrint",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/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 (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 (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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionRef",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/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 (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
Ptr CssSection
section' <- CssSection -> IO (Ptr CssSection)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr CssSection
section
CString
result <- Ptr CssSection -> IO CString
gtk_css_section_to_string Ptr CssSection
section'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cssSectionToString" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
CssSection -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr CssSection
section
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionToString",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/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 (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 (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 = O.MethodInfo {
O.overloadedMethodName = "GI.Gtk.Structs.CssSection.cssSectionUnref",
O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Structs-CssSection.html#v:cssSectionUnref"
}
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveCssSectionMethod (t :: Symbol) (o :: *) :: * where
ResolveCssSectionMethod "print" o = CssSectionPrintMethodInfo
ResolveCssSectionMethod "ref" o = CssSectionRefMethodInfo
ResolveCssSectionMethod "toString" o = CssSectionToStringMethodInfo
ResolveCssSectionMethod "unref" o = CssSectionUnrefMethodInfo
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