{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.StateMachine
(
StateMachine(..) ,
IsStateMachine ,
toStateMachine ,
#if defined(ENABLE_OVERLOADING)
ResolveStateMachineMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
StateMachineAddBindingMethodInfo ,
#endif
stateMachineAddBinding ,
#if defined(ENABLE_OVERLOADING)
StateMachineAddPropertyvMethodInfo ,
#endif
stateMachineAddPropertyv ,
#if defined(ENABLE_OVERLOADING)
StateMachineAddStyleMethodInfo ,
#endif
stateMachineAddStyle ,
#if defined(ENABLE_OVERLOADING)
StateMachineCreateActionMethodInfo ,
#endif
stateMachineCreateAction ,
#if defined(ENABLE_OVERLOADING)
StateMachineGetStateMethodInfo ,
#endif
stateMachineGetState ,
#if defined(ENABLE_OVERLOADING)
StateMachineIsStateMethodInfo ,
#endif
stateMachineIsState ,
stateMachineNew ,
#if defined(ENABLE_OVERLOADING)
StateMachineSetStateMethodInfo ,
#endif
stateMachineSetState ,
#if defined(ENABLE_OVERLOADING)
StateMachineStatePropertyInfo ,
#endif
constructStateMachineState ,
getStateMachineState ,
setStateMachineState ,
#if defined(ENABLE_OVERLOADING)
stateMachineState ,
#endif
) 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.GObject.Flags as GObject.Flags
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Action as Gio.Action
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#else
import qualified GI.GObject.Flags as GObject.Flags
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Action as Gio.Action
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
#endif
newtype StateMachine = StateMachine (SP.ManagedPtr StateMachine)
deriving (StateMachine -> StateMachine -> Bool
(StateMachine -> StateMachine -> Bool)
-> (StateMachine -> StateMachine -> Bool) -> Eq StateMachine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StateMachine -> StateMachine -> Bool
== :: StateMachine -> StateMachine -> Bool
$c/= :: StateMachine -> StateMachine -> Bool
/= :: StateMachine -> StateMachine -> Bool
Eq)
instance SP.ManagedPtrNewtype StateMachine where
toManagedPtr :: StateMachine -> ManagedPtr StateMachine
toManagedPtr (StateMachine ManagedPtr StateMachine
p) = ManagedPtr StateMachine
p
foreign import ccall "dzl_state_machine_get_type"
c_dzl_state_machine_get_type :: IO B.Types.GType
instance B.Types.TypedObject StateMachine where
glibType :: IO GType
glibType = IO GType
c_dzl_state_machine_get_type
instance B.Types.GObject StateMachine
class (SP.GObject o, O.IsDescendantOf StateMachine o) => IsStateMachine o
instance (SP.GObject o, O.IsDescendantOf StateMachine o) => IsStateMachine o
instance O.HasParentTypes StateMachine
type instance O.ParentTypes StateMachine = '[GObject.Object.Object, Gtk.Buildable.Buildable]
toStateMachine :: (MIO.MonadIO m, IsStateMachine o) => o -> m StateMachine
toStateMachine :: forall (m :: * -> *) o.
(MonadIO m, IsStateMachine o) =>
o -> m StateMachine
toStateMachine = IO StateMachine -> m StateMachine
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO StateMachine -> m StateMachine)
-> (o -> IO StateMachine) -> o -> m StateMachine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr StateMachine -> StateMachine) -> o -> IO StateMachine
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr StateMachine -> StateMachine
StateMachine
instance B.GValue.IsGValue (Maybe StateMachine) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_state_machine_get_type
gvalueSet_ :: Ptr GValue -> Maybe StateMachine -> IO ()
gvalueSet_ Ptr GValue
gv Maybe StateMachine
P.Nothing = Ptr GValue -> Ptr StateMachine -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr StateMachine
forall a. Ptr a
FP.nullPtr :: FP.Ptr StateMachine)
gvalueSet_ Ptr GValue
gv (P.Just StateMachine
obj) = StateMachine -> (Ptr StateMachine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StateMachine
obj (Ptr GValue -> Ptr StateMachine -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe StateMachine)
gvalueGet_ Ptr GValue
gv = do
Ptr StateMachine
ptr <- Ptr GValue -> IO (Ptr StateMachine)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr StateMachine)
if Ptr StateMachine
ptr Ptr StateMachine -> Ptr StateMachine -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr StateMachine
forall a. Ptr a
FP.nullPtr
then StateMachine -> Maybe StateMachine
forall a. a -> Maybe a
P.Just (StateMachine -> Maybe StateMachine)
-> IO StateMachine -> IO (Maybe StateMachine)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr StateMachine -> StateMachine)
-> Ptr StateMachine -> IO StateMachine
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr StateMachine -> StateMachine
StateMachine Ptr StateMachine
ptr
else Maybe StateMachine -> IO (Maybe StateMachine)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StateMachine
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveStateMachineMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveStateMachineMethod "addBinding" o = StateMachineAddBindingMethodInfo
ResolveStateMachineMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveStateMachineMethod "addPropertyv" o = StateMachineAddPropertyvMethodInfo
ResolveStateMachineMethod "addStyle" o = StateMachineAddStyleMethodInfo
ResolveStateMachineMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveStateMachineMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveStateMachineMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveStateMachineMethod "createAction" o = StateMachineCreateActionMethodInfo
ResolveStateMachineMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveStateMachineMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveStateMachineMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveStateMachineMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveStateMachineMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveStateMachineMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveStateMachineMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveStateMachineMethod "isState" o = StateMachineIsStateMethodInfo
ResolveStateMachineMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveStateMachineMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveStateMachineMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveStateMachineMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveStateMachineMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveStateMachineMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveStateMachineMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveStateMachineMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveStateMachineMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveStateMachineMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveStateMachineMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveStateMachineMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveStateMachineMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveStateMachineMethod "getName" o = Gtk.Buildable.BuildableGetNameMethodInfo
ResolveStateMachineMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveStateMachineMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveStateMachineMethod "getState" o = StateMachineGetStateMethodInfo
ResolveStateMachineMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveStateMachineMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveStateMachineMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveStateMachineMethod "setName" o = Gtk.Buildable.BuildableSetNameMethodInfo
ResolveStateMachineMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveStateMachineMethod "setState" o = StateMachineSetStateMethodInfo
ResolveStateMachineMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveStateMachineMethod t StateMachine, O.OverloadedMethod info StateMachine p) => OL.IsLabel t (StateMachine -> 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 ~ ResolveStateMachineMethod t StateMachine, O.OverloadedMethod info StateMachine p, R.HasField t StateMachine p) => R.HasField t StateMachine p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveStateMachineMethod t StateMachine, O.OverloadedMethodInfo info StateMachine) => OL.IsLabel t (O.MethodProxy info StateMachine) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getStateMachineState :: (MonadIO m, IsStateMachine o) => o -> m T.Text
getStateMachineState :: forall (m :: * -> *) o.
(MonadIO m, IsStateMachine o) =>
o -> m Text
getStateMachineState o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getStateMachineState" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"state"
setStateMachineState :: (MonadIO m, IsStateMachine o) => o -> T.Text -> m ()
setStateMachineState :: forall (m :: * -> *) o.
(MonadIO m, IsStateMachine o) =>
o -> Text -> m ()
setStateMachineState o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"state" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructStateMachineState :: (IsStateMachine o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructStateMachineState :: forall o (m :: * -> *).
(IsStateMachine o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructStateMachineState Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"state" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data StateMachineStatePropertyInfo
instance AttrInfo StateMachineStatePropertyInfo where
type AttrAllowedOps StateMachineStatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint StateMachineStatePropertyInfo = IsStateMachine
type AttrSetTypeConstraint StateMachineStatePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint StateMachineStatePropertyInfo = (~) T.Text
type AttrTransferType StateMachineStatePropertyInfo = T.Text
type AttrGetType StateMachineStatePropertyInfo = T.Text
type AttrLabel StateMachineStatePropertyInfo = "state"
type AttrOrigin StateMachineStatePropertyInfo = StateMachine
attrGet = getStateMachineState
attrSet = setStateMachineState
attrTransfer _ v = do
return v
attrConstruct = constructStateMachineState
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.state"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#g:attr:state"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StateMachine
type instance O.AttributeList StateMachine = StateMachineAttributeList
type StateMachineAttributeList = ('[ '("state", StateMachineStatePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
stateMachineState :: AttrLabelProxy "state"
stateMachineState = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StateMachine = StateMachineSignalList
type StateMachineSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_state_machine_new" dzl_state_machine_new ::
IO (Ptr StateMachine)
stateMachineNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m StateMachine
stateMachineNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m StateMachine
stateMachineNew = IO StateMachine -> m StateMachine
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StateMachine -> m StateMachine)
-> IO StateMachine -> m StateMachine
forall a b. (a -> b) -> a -> b
$ do
Ptr StateMachine
result <- IO (Ptr StateMachine)
dzl_state_machine_new
Text -> Ptr StateMachine -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateMachineNew" Ptr StateMachine
result
StateMachine
result' <- ((ManagedPtr StateMachine -> StateMachine)
-> Ptr StateMachine -> IO StateMachine
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StateMachine -> StateMachine
StateMachine) Ptr StateMachine
result
StateMachine -> IO StateMachine
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return StateMachine
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_state_machine_add_binding" dzl_state_machine_add_binding ::
Ptr StateMachine ->
CString ->
Ptr () ->
CString ->
Ptr () ->
CString ->
CUInt ->
IO ()
stateMachineAddBinding ::
(B.CallStack.HasCallStack, MonadIO m, IsStateMachine a) =>
a
-> T.Text
-> Ptr ()
-> T.Text
-> Ptr ()
-> T.Text
-> [GObject.Flags.BindingFlags]
-> m ()
stateMachineAddBinding :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStateMachine a) =>
a
-> Text
-> Ptr ()
-> Text
-> Ptr ()
-> Text
-> [BindingFlags]
-> m ()
stateMachineAddBinding a
self Text
state Ptr ()
sourceObject Text
sourceProperty Ptr ()
targetObject Text
targetProperty [BindingFlags]
flags = 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 StateMachine
self' <- a -> IO (Ptr StateMachine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
state' <- Text -> IO CString
textToCString Text
state
CString
sourceProperty' <- Text -> IO CString
textToCString Text
sourceProperty
CString
targetProperty' <- Text -> IO CString
textToCString Text
targetProperty
let flags' :: CUInt
flags' = [BindingFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [BindingFlags]
flags
Ptr StateMachine
-> CString
-> Ptr ()
-> CString
-> Ptr ()
-> CString
-> CUInt
-> IO ()
dzl_state_machine_add_binding Ptr StateMachine
self' CString
state' Ptr ()
sourceObject CString
sourceProperty' Ptr ()
targetObject CString
targetProperty' CUInt
flags'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
state'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
sourceProperty'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetProperty'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StateMachineAddBindingMethodInfo
instance (signature ~ (T.Text -> Ptr () -> T.Text -> Ptr () -> T.Text -> [GObject.Flags.BindingFlags] -> m ()), MonadIO m, IsStateMachine a) => O.OverloadedMethod StateMachineAddBindingMethodInfo a signature where
overloadedMethod = stateMachineAddBinding
instance O.OverloadedMethodInfo StateMachineAddBindingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.stateMachineAddBinding",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#v:stateMachineAddBinding"
})
#endif
foreign import ccall "dzl_state_machine_add_propertyv" dzl_state_machine_add_propertyv ::
Ptr StateMachine ->
CString ->
Ptr () ->
CString ->
Ptr GValue ->
IO ()
stateMachineAddPropertyv ::
(B.CallStack.HasCallStack, MonadIO m, IsStateMachine a) =>
a
-> T.Text
-> Ptr ()
-> T.Text
-> GValue
-> m ()
stateMachineAddPropertyv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStateMachine a) =>
a -> Text -> Ptr () -> Text -> GValue -> m ()
stateMachineAddPropertyv a
self Text
state Ptr ()
object Text
property GValue
value = 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 StateMachine
self' <- a -> IO (Ptr StateMachine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
state' <- Text -> IO CString
textToCString Text
state
CString
property' <- Text -> IO CString
textToCString Text
property
Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
Ptr StateMachine
-> CString -> Ptr () -> CString -> Ptr GValue -> IO ()
dzl_state_machine_add_propertyv Ptr StateMachine
self' CString
state' Ptr ()
object CString
property' Ptr GValue
value'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
state'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StateMachineAddPropertyvMethodInfo
instance (signature ~ (T.Text -> Ptr () -> T.Text -> GValue -> m ()), MonadIO m, IsStateMachine a) => O.OverloadedMethod StateMachineAddPropertyvMethodInfo a signature where
overloadedMethod = stateMachineAddPropertyv
instance O.OverloadedMethodInfo StateMachineAddPropertyvMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.stateMachineAddPropertyv",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#v:stateMachineAddPropertyv"
})
#endif
foreign import ccall "dzl_state_machine_add_style" dzl_state_machine_add_style ::
Ptr StateMachine ->
CString ->
Ptr Gtk.Widget.Widget ->
CString ->
IO ()
stateMachineAddStyle ::
(B.CallStack.HasCallStack, MonadIO m, IsStateMachine a, Gtk.Widget.IsWidget b) =>
a
-> T.Text
-> b
-> T.Text
-> m ()
stateMachineAddStyle :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsStateMachine a, IsWidget b) =>
a -> Text -> b -> Text -> m ()
stateMachineAddStyle a
self Text
state b
widget Text
style = 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 StateMachine
self' <- a -> IO (Ptr StateMachine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
state' <- Text -> IO CString
textToCString Text
state
Ptr Widget
widget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
widget
CString
style' <- Text -> IO CString
textToCString Text
style
Ptr StateMachine -> CString -> Ptr Widget -> CString -> IO ()
dzl_state_machine_add_style Ptr StateMachine
self' CString
state' Ptr Widget
widget' CString
style'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
widget
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
state'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
style'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StateMachineAddStyleMethodInfo
instance (signature ~ (T.Text -> b -> T.Text -> m ()), MonadIO m, IsStateMachine a, Gtk.Widget.IsWidget b) => O.OverloadedMethod StateMachineAddStyleMethodInfo a signature where
overloadedMethod = stateMachineAddStyle
instance O.OverloadedMethodInfo StateMachineAddStyleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.stateMachineAddStyle",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#v:stateMachineAddStyle"
})
#endif
foreign import ccall "dzl_state_machine_create_action" dzl_state_machine_create_action ::
Ptr StateMachine ->
CString ->
IO (Ptr Gio.Action.Action)
stateMachineCreateAction ::
(B.CallStack.HasCallStack, MonadIO m, IsStateMachine a) =>
a
-> T.Text
-> m Gio.Action.Action
stateMachineCreateAction :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStateMachine a) =>
a -> Text -> m Action
stateMachineCreateAction a
self Text
name = IO Action -> m Action
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Action -> m Action) -> IO Action -> m Action
forall a b. (a -> b) -> a -> b
$ do
Ptr StateMachine
self' <- a -> IO (Ptr StateMachine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
name' <- Text -> IO CString
textToCString Text
name
Ptr Action
result <- Ptr StateMachine -> CString -> IO (Ptr Action)
dzl_state_machine_create_action Ptr StateMachine
self' CString
name'
Text -> Ptr Action -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateMachineCreateAction" Ptr Action
result
Action
result' <- ((ManagedPtr Action -> Action) -> Ptr Action -> IO Action
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Action -> Action
Gio.Action.Action) Ptr Action
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
Action -> IO Action
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Action
result'
#if defined(ENABLE_OVERLOADING)
data StateMachineCreateActionMethodInfo
instance (signature ~ (T.Text -> m Gio.Action.Action), MonadIO m, IsStateMachine a) => O.OverloadedMethod StateMachineCreateActionMethodInfo a signature where
overloadedMethod = stateMachineCreateAction
instance O.OverloadedMethodInfo StateMachineCreateActionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.stateMachineCreateAction",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#v:stateMachineCreateAction"
})
#endif
foreign import ccall "dzl_state_machine_get_state" dzl_state_machine_get_state ::
Ptr StateMachine ->
IO CString
stateMachineGetState ::
(B.CallStack.HasCallStack, MonadIO m, IsStateMachine a) =>
a
-> m T.Text
stateMachineGetState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStateMachine a) =>
a -> m Text
stateMachineGetState a
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 StateMachine
self' <- a -> IO (Ptr StateMachine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
result <- Ptr StateMachine -> IO CString
dzl_state_machine_get_state Ptr StateMachine
self'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stateMachineGetState" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
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 StateMachineGetStateMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsStateMachine a) => O.OverloadedMethod StateMachineGetStateMethodInfo a signature where
overloadedMethod = stateMachineGetState
instance O.OverloadedMethodInfo StateMachineGetStateMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.stateMachineGetState",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#v:stateMachineGetState"
})
#endif
foreign import ccall "dzl_state_machine_is_state" dzl_state_machine_is_state ::
Ptr StateMachine ->
CString ->
IO CInt
stateMachineIsState ::
(B.CallStack.HasCallStack, MonadIO m, IsStateMachine a) =>
a
-> Maybe (T.Text)
-> m Bool
stateMachineIsState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStateMachine a) =>
a -> Maybe Text -> m Bool
stateMachineIsState a
self Maybe Text
state = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr StateMachine
self' <- a -> IO (Ptr StateMachine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
maybeState <- case Maybe Text
state of
Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just Text
jState -> do
CString
jState' <- Text -> IO CString
textToCString Text
jState
CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jState'
CInt
result <- Ptr StateMachine -> CString -> IO CInt
dzl_state_machine_is_state Ptr StateMachine
self' CString
maybeState
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeState
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data StateMachineIsStateMethodInfo
instance (signature ~ (Maybe (T.Text) -> m Bool), MonadIO m, IsStateMachine a) => O.OverloadedMethod StateMachineIsStateMethodInfo a signature where
overloadedMethod = stateMachineIsState
instance O.OverloadedMethodInfo StateMachineIsStateMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.stateMachineIsState",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#v:stateMachineIsState"
})
#endif
foreign import ccall "dzl_state_machine_set_state" dzl_state_machine_set_state ::
Ptr StateMachine ->
CString ->
IO ()
stateMachineSetState ::
(B.CallStack.HasCallStack, MonadIO m, IsStateMachine a) =>
a
-> T.Text
-> m ()
stateMachineSetState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStateMachine a) =>
a -> Text -> m ()
stateMachineSetState a
self Text
state = 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 StateMachine
self' <- a -> IO (Ptr StateMachine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
state' <- Text -> IO CString
textToCString Text
state
Ptr StateMachine -> CString -> IO ()
dzl_state_machine_set_state Ptr StateMachine
self' CString
state'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
state'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StateMachineSetStateMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsStateMachine a) => O.OverloadedMethod StateMachineSetStateMethodInfo a signature where
overloadedMethod = stateMachineSetState
instance O.OverloadedMethodInfo StateMachineSetStateMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.StateMachine.stateMachineSetState",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-StateMachine.html#v:stateMachineSetState"
})
#endif