{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Adw.Structs.BreakpointCondition
(
BreakpointCondition(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveBreakpointConditionMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
BreakpointConditionCopyMethodInfo ,
#endif
breakpointConditionCopy ,
#if defined(ENABLE_OVERLOADING)
BreakpointConditionFreeMethodInfo ,
#endif
breakpointConditionFree ,
breakpointConditionNewAnd ,
breakpointConditionNewLength ,
breakpointConditionNewOr ,
breakpointConditionNewRatio ,
breakpointConditionParse ,
#if defined(ENABLE_OVERLOADING)
BreakpointConditionToStringMethodInfo ,
#endif
breakpointConditionToString ,
) 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 {-# SOURCE #-} qualified GI.Adw.Enums as Adw.Enums
#else
import {-# SOURCE #-} qualified GI.Adw.Enums as Adw.Enums
#endif
newtype BreakpointCondition = BreakpointCondition (SP.ManagedPtr BreakpointCondition)
deriving (BreakpointCondition -> BreakpointCondition -> Bool
(BreakpointCondition -> BreakpointCondition -> Bool)
-> (BreakpointCondition -> BreakpointCondition -> Bool)
-> Eq BreakpointCondition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BreakpointCondition -> BreakpointCondition -> Bool
== :: BreakpointCondition -> BreakpointCondition -> Bool
$c/= :: BreakpointCondition -> BreakpointCondition -> Bool
/= :: BreakpointCondition -> BreakpointCondition -> Bool
Eq)
instance SP.ManagedPtrNewtype BreakpointCondition where
toManagedPtr :: BreakpointCondition -> ManagedPtr BreakpointCondition
toManagedPtr (BreakpointCondition ManagedPtr BreakpointCondition
p) = ManagedPtr BreakpointCondition
p
foreign import ccall "adw_breakpoint_condition_get_type" c_adw_breakpoint_condition_get_type ::
IO GType
type instance O.ParentTypes BreakpointCondition = '[]
instance O.HasParentTypes BreakpointCondition
instance B.Types.TypedObject BreakpointCondition where
glibType :: IO GType
glibType = IO GType
c_adw_breakpoint_condition_get_type
instance B.Types.GBoxed BreakpointCondition
instance B.GValue.IsGValue (Maybe BreakpointCondition) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_adw_breakpoint_condition_get_type
gvalueSet_ :: Ptr GValue -> Maybe BreakpointCondition -> IO ()
gvalueSet_ Ptr GValue
gv Maybe BreakpointCondition
P.Nothing = Ptr GValue -> Ptr BreakpointCondition -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr BreakpointCondition
forall a. Ptr a
FP.nullPtr :: FP.Ptr BreakpointCondition)
gvalueSet_ Ptr GValue
gv (P.Just BreakpointCondition
obj) = BreakpointCondition -> (Ptr BreakpointCondition -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr BreakpointCondition
obj (Ptr GValue -> Ptr BreakpointCondition -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe BreakpointCondition)
gvalueGet_ Ptr GValue
gv = do
Ptr BreakpointCondition
ptr <- Ptr GValue -> IO (Ptr BreakpointCondition)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr BreakpointCondition)
if Ptr BreakpointCondition
ptr Ptr BreakpointCondition -> Ptr BreakpointCondition -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr BreakpointCondition
forall a. Ptr a
FP.nullPtr
then BreakpointCondition -> Maybe BreakpointCondition
forall a. a -> Maybe a
P.Just (BreakpointCondition -> Maybe BreakpointCondition)
-> IO BreakpointCondition -> IO (Maybe BreakpointCondition)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr BreakpointCondition -> BreakpointCondition)
-> Ptr BreakpointCondition -> IO BreakpointCondition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr BreakpointCondition -> BreakpointCondition
BreakpointCondition Ptr BreakpointCondition
ptr
else Maybe BreakpointCondition -> IO (Maybe BreakpointCondition)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BreakpointCondition
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BreakpointCondition
type instance O.AttributeList BreakpointCondition = BreakpointConditionAttributeList
type BreakpointConditionAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "adw_breakpoint_condition_new_and" adw_breakpoint_condition_new_and ::
Ptr BreakpointCondition ->
Ptr BreakpointCondition ->
IO (Ptr BreakpointCondition)
breakpointConditionNewAnd ::
(B.CallStack.HasCallStack, MonadIO m) =>
BreakpointCondition
-> BreakpointCondition
-> m BreakpointCondition
breakpointConditionNewAnd :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BreakpointCondition -> BreakpointCondition -> m BreakpointCondition
breakpointConditionNewAnd BreakpointCondition
condition1 BreakpointCondition
condition2 = IO BreakpointCondition -> m BreakpointCondition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BreakpointCondition -> m BreakpointCondition)
-> IO BreakpointCondition -> m BreakpointCondition
forall a b. (a -> b) -> a -> b
$ do
Ptr BreakpointCondition
condition1' <- BreakpointCondition -> IO (Ptr BreakpointCondition)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed BreakpointCondition
condition1
Ptr BreakpointCondition
condition2' <- BreakpointCondition -> IO (Ptr BreakpointCondition)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed BreakpointCondition
condition2
Ptr BreakpointCondition
result <- Ptr BreakpointCondition
-> Ptr BreakpointCondition -> IO (Ptr BreakpointCondition)
adw_breakpoint_condition_new_and Ptr BreakpointCondition
condition1' Ptr BreakpointCondition
condition2'
Text -> Ptr BreakpointCondition -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"breakpointConditionNewAnd" Ptr BreakpointCondition
result
BreakpointCondition
result' <- ((ManagedPtr BreakpointCondition -> BreakpointCondition)
-> Ptr BreakpointCondition -> IO BreakpointCondition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BreakpointCondition -> BreakpointCondition
BreakpointCondition) Ptr BreakpointCondition
result
BreakpointCondition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BreakpointCondition
condition1
BreakpointCondition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BreakpointCondition
condition2
BreakpointCondition -> IO BreakpointCondition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BreakpointCondition
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "adw_breakpoint_condition_new_length" adw_breakpoint_condition_new_length ::
CUInt ->
CDouble ->
CUInt ->
IO (Ptr BreakpointCondition)
breakpointConditionNewLength ::
(B.CallStack.HasCallStack, MonadIO m) =>
Adw.Enums.BreakpointConditionLengthType
-> Double
-> Adw.Enums.LengthUnit
-> m BreakpointCondition
breakpointConditionNewLength :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BreakpointConditionLengthType
-> Double -> LengthUnit -> m BreakpointCondition
breakpointConditionNewLength BreakpointConditionLengthType
type_ Double
value LengthUnit
unit = IO BreakpointCondition -> m BreakpointCondition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BreakpointCondition -> m BreakpointCondition)
-> IO BreakpointCondition -> m BreakpointCondition
forall a b. (a -> b) -> a -> b
$ do
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (BreakpointConditionLengthType -> Int)
-> BreakpointConditionLengthType
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BreakpointConditionLengthType -> Int
forall a. Enum a => a -> Int
fromEnum) BreakpointConditionLengthType
type_
let value' :: CDouble
value' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
value
let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (LengthUnit -> Int) -> LengthUnit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LengthUnit -> Int
forall a. Enum a => a -> Int
fromEnum) LengthUnit
unit
Ptr BreakpointCondition
result <- CUInt -> CDouble -> CUInt -> IO (Ptr BreakpointCondition)
adw_breakpoint_condition_new_length CUInt
type_' CDouble
value' CUInt
unit'
Text -> Ptr BreakpointCondition -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"breakpointConditionNewLength" Ptr BreakpointCondition
result
BreakpointCondition
result' <- ((ManagedPtr BreakpointCondition -> BreakpointCondition)
-> Ptr BreakpointCondition -> IO BreakpointCondition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BreakpointCondition -> BreakpointCondition
BreakpointCondition) Ptr BreakpointCondition
result
BreakpointCondition -> IO BreakpointCondition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BreakpointCondition
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "adw_breakpoint_condition_new_or" adw_breakpoint_condition_new_or ::
Ptr BreakpointCondition ->
Ptr BreakpointCondition ->
IO (Ptr BreakpointCondition)
breakpointConditionNewOr ::
(B.CallStack.HasCallStack, MonadIO m) =>
BreakpointCondition
-> BreakpointCondition
-> m BreakpointCondition
breakpointConditionNewOr :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BreakpointCondition -> BreakpointCondition -> m BreakpointCondition
breakpointConditionNewOr BreakpointCondition
condition1 BreakpointCondition
condition2 = IO BreakpointCondition -> m BreakpointCondition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BreakpointCondition -> m BreakpointCondition)
-> IO BreakpointCondition -> m BreakpointCondition
forall a b. (a -> b) -> a -> b
$ do
Ptr BreakpointCondition
condition1' <- BreakpointCondition -> IO (Ptr BreakpointCondition)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed BreakpointCondition
condition1
Ptr BreakpointCondition
condition2' <- BreakpointCondition -> IO (Ptr BreakpointCondition)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed BreakpointCondition
condition2
Ptr BreakpointCondition
result <- Ptr BreakpointCondition
-> Ptr BreakpointCondition -> IO (Ptr BreakpointCondition)
adw_breakpoint_condition_new_or Ptr BreakpointCondition
condition1' Ptr BreakpointCondition
condition2'
Text -> Ptr BreakpointCondition -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"breakpointConditionNewOr" Ptr BreakpointCondition
result
BreakpointCondition
result' <- ((ManagedPtr BreakpointCondition -> BreakpointCondition)
-> Ptr BreakpointCondition -> IO BreakpointCondition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BreakpointCondition -> BreakpointCondition
BreakpointCondition) Ptr BreakpointCondition
result
BreakpointCondition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BreakpointCondition
condition1
BreakpointCondition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BreakpointCondition
condition2
BreakpointCondition -> IO BreakpointCondition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BreakpointCondition
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "adw_breakpoint_condition_new_ratio" adw_breakpoint_condition_new_ratio ::
CUInt ->
Int32 ->
Int32 ->
IO (Ptr BreakpointCondition)
breakpointConditionNewRatio ::
(B.CallStack.HasCallStack, MonadIO m) =>
Adw.Enums.BreakpointConditionRatioType
-> Int32
-> Int32
-> m BreakpointCondition
breakpointConditionNewRatio :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BreakpointConditionRatioType
-> Int32 -> Int32 -> m BreakpointCondition
breakpointConditionNewRatio BreakpointConditionRatioType
type_ Int32
width Int32
height = IO BreakpointCondition -> m BreakpointCondition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BreakpointCondition -> m BreakpointCondition)
-> IO BreakpointCondition -> m BreakpointCondition
forall a b. (a -> b) -> a -> b
$ do
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (BreakpointConditionRatioType -> Int)
-> BreakpointConditionRatioType
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BreakpointConditionRatioType -> Int
forall a. Enum a => a -> Int
fromEnum) BreakpointConditionRatioType
type_
Ptr BreakpointCondition
result <- CUInt -> Int32 -> Int32 -> IO (Ptr BreakpointCondition)
adw_breakpoint_condition_new_ratio CUInt
type_' Int32
width Int32
height
Text -> Ptr BreakpointCondition -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"breakpointConditionNewRatio" Ptr BreakpointCondition
result
BreakpointCondition
result' <- ((ManagedPtr BreakpointCondition -> BreakpointCondition)
-> Ptr BreakpointCondition -> IO BreakpointCondition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BreakpointCondition -> BreakpointCondition
BreakpointCondition) Ptr BreakpointCondition
result
BreakpointCondition -> IO BreakpointCondition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BreakpointCondition
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "adw_breakpoint_condition_copy" adw_breakpoint_condition_copy ::
Ptr BreakpointCondition ->
IO (Ptr BreakpointCondition)
breakpointConditionCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
BreakpointCondition
-> m BreakpointCondition
breakpointConditionCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BreakpointCondition -> m BreakpointCondition
breakpointConditionCopy BreakpointCondition
self = IO BreakpointCondition -> m BreakpointCondition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BreakpointCondition -> m BreakpointCondition)
-> IO BreakpointCondition -> m BreakpointCondition
forall a b. (a -> b) -> a -> b
$ do
Ptr BreakpointCondition
self' <- BreakpointCondition -> IO (Ptr BreakpointCondition)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BreakpointCondition
self
Ptr BreakpointCondition
result <- Ptr BreakpointCondition -> IO (Ptr BreakpointCondition)
adw_breakpoint_condition_copy Ptr BreakpointCondition
self'
Text -> Ptr BreakpointCondition -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"breakpointConditionCopy" Ptr BreakpointCondition
result
BreakpointCondition
result' <- ((ManagedPtr BreakpointCondition -> BreakpointCondition)
-> Ptr BreakpointCondition -> IO BreakpointCondition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BreakpointCondition -> BreakpointCondition
BreakpointCondition) Ptr BreakpointCondition
result
BreakpointCondition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BreakpointCondition
self
BreakpointCondition -> IO BreakpointCondition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BreakpointCondition
result'
#if defined(ENABLE_OVERLOADING)
data BreakpointConditionCopyMethodInfo
instance (signature ~ (m BreakpointCondition), MonadIO m) => O.OverloadedMethod BreakpointConditionCopyMethodInfo BreakpointCondition signature where
overloadedMethod = breakpointConditionCopy
instance O.OverloadedMethodInfo BreakpointConditionCopyMethodInfo BreakpointCondition where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Adw.Structs.BreakpointCondition.breakpointConditionCopy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.7/docs/GI-Adw-Structs-BreakpointCondition.html#v:breakpointConditionCopy"
})
#endif
foreign import ccall "adw_breakpoint_condition_free" adw_breakpoint_condition_free ::
Ptr BreakpointCondition ->
IO ()
breakpointConditionFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
BreakpointCondition
-> m ()
breakpointConditionFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BreakpointCondition -> m ()
breakpointConditionFree BreakpointCondition
self = 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 BreakpointCondition
self' <- BreakpointCondition -> IO (Ptr BreakpointCondition)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BreakpointCondition
self
Ptr BreakpointCondition -> IO ()
adw_breakpoint_condition_free Ptr BreakpointCondition
self'
BreakpointCondition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BreakpointCondition
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data BreakpointConditionFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod BreakpointConditionFreeMethodInfo BreakpointCondition signature where
overloadedMethod = breakpointConditionFree
instance O.OverloadedMethodInfo BreakpointConditionFreeMethodInfo BreakpointCondition where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Adw.Structs.BreakpointCondition.breakpointConditionFree",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.7/docs/GI-Adw-Structs-BreakpointCondition.html#v:breakpointConditionFree"
})
#endif
foreign import ccall "adw_breakpoint_condition_to_string" adw_breakpoint_condition_to_string ::
Ptr BreakpointCondition ->
IO CString
breakpointConditionToString ::
(B.CallStack.HasCallStack, MonadIO m) =>
BreakpointCondition
-> m T.Text
breakpointConditionToString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
BreakpointCondition -> m Text
breakpointConditionToString BreakpointCondition
self = 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
Ptr BreakpointCondition
self' <- BreakpointCondition -> IO (Ptr BreakpointCondition)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BreakpointCondition
self
CString
result <- Ptr BreakpointCondition -> IO CString
adw_breakpoint_condition_to_string Ptr BreakpointCondition
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"breakpointConditionToString" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
BreakpointCondition -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BreakpointCondition
self
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data BreakpointConditionToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod BreakpointConditionToStringMethodInfo BreakpointCondition signature where
overloadedMethod = breakpointConditionToString
instance O.OverloadedMethodInfo BreakpointConditionToStringMethodInfo BreakpointCondition where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Adw.Structs.BreakpointCondition.breakpointConditionToString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.7/docs/GI-Adw-Structs-BreakpointCondition.html#v:breakpointConditionToString"
})
#endif
foreign import ccall "adw_breakpoint_condition_parse" adw_breakpoint_condition_parse ::
CString ->
IO (Ptr BreakpointCondition)
breakpointConditionParse ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m BreakpointCondition
breakpointConditionParse :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m BreakpointCondition
breakpointConditionParse Text
str = IO BreakpointCondition -> m BreakpointCondition
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BreakpointCondition -> m BreakpointCondition)
-> IO BreakpointCondition -> m BreakpointCondition
forall a b. (a -> b) -> a -> b
$ do
CString
str' <- Text -> IO CString
textToCString Text
str
Ptr BreakpointCondition
result <- CString -> IO (Ptr BreakpointCondition)
adw_breakpoint_condition_parse CString
str'
Text -> Ptr BreakpointCondition -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"breakpointConditionParse" Ptr BreakpointCondition
result
BreakpointCondition
result' <- ((ManagedPtr BreakpointCondition -> BreakpointCondition)
-> Ptr BreakpointCondition -> IO BreakpointCondition
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr BreakpointCondition -> BreakpointCondition
BreakpointCondition) Ptr BreakpointCondition
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
BreakpointCondition -> IO BreakpointCondition
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BreakpointCondition
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveBreakpointConditionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveBreakpointConditionMethod "copy" o = BreakpointConditionCopyMethodInfo
ResolveBreakpointConditionMethod "free" o = BreakpointConditionFreeMethodInfo
ResolveBreakpointConditionMethod "toString" o = BreakpointConditionToStringMethodInfo
ResolveBreakpointConditionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveBreakpointConditionMethod t BreakpointCondition, O.OverloadedMethod info BreakpointCondition p) => OL.IsLabel t (BreakpointCondition -> 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 ~ ResolveBreakpointConditionMethod t BreakpointCondition, O.OverloadedMethod info BreakpointCondition p, R.HasField t BreakpointCondition p) => R.HasField t BreakpointCondition p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveBreakpointConditionMethod t BreakpointCondition, O.OverloadedMethodInfo info BreakpointCondition) => OL.IsLabel t (O.MethodProxy info BreakpointCondition) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif