{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.MountOperationHandlerIface_
(
MountOperationHandlerIface_(..) ,
newZeroMountOperationHandlerIface_ ,
#if defined(ENABLE_OVERLOADING)
ResolveMountOperationHandlerIface_Method,
#endif
getMountOperationHandlerIface_ParentIface,
#if defined(ENABLE_OVERLOADING)
mountOperationHandlerIface__parentIface ,
#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 GI.GObject.Structs.TypeInterface as GObject.TypeInterface
newtype MountOperationHandlerIface_ = MountOperationHandlerIface_ (SP.ManagedPtr MountOperationHandlerIface_)
deriving (MountOperationHandlerIface_ -> MountOperationHandlerIface_ -> Bool
(MountOperationHandlerIface_
-> MountOperationHandlerIface_ -> Bool)
-> (MountOperationHandlerIface_
-> MountOperationHandlerIface_ -> Bool)
-> Eq MountOperationHandlerIface_
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MountOperationHandlerIface_ -> MountOperationHandlerIface_ -> Bool
== :: MountOperationHandlerIface_ -> MountOperationHandlerIface_ -> Bool
$c/= :: MountOperationHandlerIface_ -> MountOperationHandlerIface_ -> Bool
/= :: MountOperationHandlerIface_ -> MountOperationHandlerIface_ -> Bool
Eq)
instance SP.ManagedPtrNewtype MountOperationHandlerIface_ where
toManagedPtr :: MountOperationHandlerIface_
-> ManagedPtr MountOperationHandlerIface_
toManagedPtr (MountOperationHandlerIface_ ManagedPtr MountOperationHandlerIface_
p) = ManagedPtr MountOperationHandlerIface_
p
instance BoxedPtr MountOperationHandlerIface_ where
boxedPtrCopy :: MountOperationHandlerIface_ -> IO MountOperationHandlerIface_
boxedPtrCopy = \MountOperationHandlerIface_
p -> MountOperationHandlerIface_
-> (Ptr MountOperationHandlerIface_
-> IO MountOperationHandlerIface_)
-> IO MountOperationHandlerIface_
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr MountOperationHandlerIface_
p (Int
-> Ptr MountOperationHandlerIface_
-> IO (Ptr MountOperationHandlerIface_)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
48 (Ptr MountOperationHandlerIface_
-> IO (Ptr MountOperationHandlerIface_))
-> (Ptr MountOperationHandlerIface_
-> IO MountOperationHandlerIface_)
-> Ptr MountOperationHandlerIface_
-> IO MountOperationHandlerIface_
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr MountOperationHandlerIface_
-> MountOperationHandlerIface_)
-> Ptr MountOperationHandlerIface_
-> IO MountOperationHandlerIface_
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr MountOperationHandlerIface_
-> MountOperationHandlerIface_
MountOperationHandlerIface_)
boxedPtrFree :: MountOperationHandlerIface_ -> IO ()
boxedPtrFree = \MountOperationHandlerIface_
x -> MountOperationHandlerIface_
-> (Ptr MountOperationHandlerIface_ -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr MountOperationHandlerIface_
x Ptr MountOperationHandlerIface_ -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr MountOperationHandlerIface_ where
boxedPtrCalloc :: IO (Ptr MountOperationHandlerIface_)
boxedPtrCalloc = Int -> IO (Ptr MountOperationHandlerIface_)
forall a. Int -> IO (Ptr a)
callocBytes Int
48
newZeroMountOperationHandlerIface_ :: MonadIO m => m MountOperationHandlerIface_
newZeroMountOperationHandlerIface_ :: forall (m :: * -> *). MonadIO m => m MountOperationHandlerIface_
newZeroMountOperationHandlerIface_ = IO MountOperationHandlerIface_ -> m MountOperationHandlerIface_
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MountOperationHandlerIface_ -> m MountOperationHandlerIface_)
-> IO MountOperationHandlerIface_ -> m MountOperationHandlerIface_
forall a b. (a -> b) -> a -> b
$ IO (Ptr MountOperationHandlerIface_)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr MountOperationHandlerIface_)
-> (Ptr MountOperationHandlerIface_
-> IO MountOperationHandlerIface_)
-> IO MountOperationHandlerIface_
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr MountOperationHandlerIface_
-> MountOperationHandlerIface_)
-> Ptr MountOperationHandlerIface_
-> IO MountOperationHandlerIface_
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr MountOperationHandlerIface_
-> MountOperationHandlerIface_
MountOperationHandlerIface_
instance tag ~ 'AttrSet => Constructible MountOperationHandlerIface_ tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr MountOperationHandlerIface_
-> MountOperationHandlerIface_)
-> [AttrOp MountOperationHandlerIface_ tag]
-> m MountOperationHandlerIface_
new ManagedPtr MountOperationHandlerIface_
-> MountOperationHandlerIface_
_ [AttrOp MountOperationHandlerIface_ tag]
attrs = do
MountOperationHandlerIface_
o <- m MountOperationHandlerIface_
forall (m :: * -> *). MonadIO m => m MountOperationHandlerIface_
newZeroMountOperationHandlerIface_
MountOperationHandlerIface_
-> [AttrOp MountOperationHandlerIface_ 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set MountOperationHandlerIface_
o [AttrOp MountOperationHandlerIface_ tag]
[AttrOp MountOperationHandlerIface_ 'AttrSet]
attrs
MountOperationHandlerIface_ -> m MountOperationHandlerIface_
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return MountOperationHandlerIface_
o
getMountOperationHandlerIface_ParentIface :: MonadIO m => MountOperationHandlerIface_ -> m GObject.TypeInterface.TypeInterface
getMountOperationHandlerIface_ParentIface :: forall (m :: * -> *).
MonadIO m =>
MountOperationHandlerIface_ -> m TypeInterface
getMountOperationHandlerIface_ParentIface MountOperationHandlerIface_
s = IO TypeInterface -> m TypeInterface
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TypeInterface -> m TypeInterface)
-> IO TypeInterface -> m TypeInterface
forall a b. (a -> b) -> a -> b
$ MountOperationHandlerIface_
-> (Ptr MountOperationHandlerIface_ -> IO TypeInterface)
-> IO TypeInterface
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr MountOperationHandlerIface_
s ((Ptr MountOperationHandlerIface_ -> IO TypeInterface)
-> IO TypeInterface)
-> (Ptr MountOperationHandlerIface_ -> IO TypeInterface)
-> IO TypeInterface
forall a b. (a -> b) -> a -> b
$ \Ptr MountOperationHandlerIface_
ptr -> do
let val :: Ptr TypeInterface
val = Ptr MountOperationHandlerIface_
ptr Ptr MountOperationHandlerIface_ -> Int -> Ptr TypeInterface
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: (Ptr GObject.TypeInterface.TypeInterface)
TypeInterface
val' <- ((ManagedPtr TypeInterface -> TypeInterface)
-> Ptr TypeInterface -> IO TypeInterface
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TypeInterface -> TypeInterface
GObject.TypeInterface.TypeInterface) Ptr TypeInterface
val
TypeInterface -> IO TypeInterface
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeInterface
val'
#if defined(ENABLE_OVERLOADING)
data MountOperationHandlerIface_ParentIfaceFieldInfo
instance AttrInfo MountOperationHandlerIface_ParentIfaceFieldInfo where
type AttrBaseTypeConstraint MountOperationHandlerIface_ParentIfaceFieldInfo = (~) MountOperationHandlerIface_
type AttrAllowedOps MountOperationHandlerIface_ParentIfaceFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint MountOperationHandlerIface_ParentIfaceFieldInfo = (~) (Ptr GObject.TypeInterface.TypeInterface)
type AttrTransferTypeConstraint MountOperationHandlerIface_ParentIfaceFieldInfo = (~)(Ptr GObject.TypeInterface.TypeInterface)
type AttrTransferType MountOperationHandlerIface_ParentIfaceFieldInfo = (Ptr GObject.TypeInterface.TypeInterface)
type AttrGetType MountOperationHandlerIface_ParentIfaceFieldInfo = GObject.TypeInterface.TypeInterface
type AttrLabel MountOperationHandlerIface_ParentIfaceFieldInfo = "parent_iface"
type AttrOrigin MountOperationHandlerIface_ParentIfaceFieldInfo = MountOperationHandlerIface_
attrGet = getMountOperationHandlerIface_ParentIface
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.MountOperationHandlerIface_.parentIface"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-MountOperationHandlerIface_.html#g:attr:parentIface"
})
mountOperationHandlerIface__parentIface :: AttrLabelProxy "parentIface"
mountOperationHandlerIface__parentIface = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MountOperationHandlerIface_
type instance O.AttributeList MountOperationHandlerIface_ = MountOperationHandlerIface_AttributeList
type MountOperationHandlerIface_AttributeList = ('[ '("parentIface", MountOperationHandlerIface_ParentIfaceFieldInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveMountOperationHandlerIface_Method (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveMountOperationHandlerIface_Method l o = O.MethodResolutionFailed l o
instance (info ~ ResolveMountOperationHandlerIface_Method t MountOperationHandlerIface_, O.OverloadedMethod info MountOperationHandlerIface_ p) => OL.IsLabel t (MountOperationHandlerIface_ -> 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 ~ ResolveMountOperationHandlerIface_Method t MountOperationHandlerIface_, O.OverloadedMethod info MountOperationHandlerIface_ p, R.HasField t MountOperationHandlerIface_ p) => R.HasField t MountOperationHandlerIface_ p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveMountOperationHandlerIface_Method t MountOperationHandlerIface_, O.OverloadedMethodInfo info MountOperationHandlerIface_) => OL.IsLabel t (O.MethodProxy info MountOperationHandlerIface_) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif