{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.MountOperation.MountOperation' provides a mechanism for interacting with the user.
-- It can be used for authenticating mountable operations, such as loop
-- mounting files, hard drive partitions or server locations. It can
-- also be used to ask the user questions or show a list of applications
-- preventing unmount or eject operations from completing.
-- 
-- Note that t'GI.Gio.Objects.MountOperation.MountOperation' is used for more than just t'GI.Gio.Interfaces.Mount.Mount'
-- objects – for example it is also used in 'GI.Gio.Interfaces.Drive.driveStart' and
-- 'GI.Gio.Interfaces.Drive.driveStop'.
-- 
-- Users should instantiate a subclass of this that implements all the
-- various callbacks to show the required dialogs, such as
-- @/GtkMountOperation/@. If no user interaction is desired (for example
-- when automounting filesystems at login time), usually 'P.Nothing' can be
-- passed, see each method taking a t'GI.Gio.Objects.MountOperation.MountOperation' for details.
-- 
-- The term ‘TCRYPT’ is used to mean ‘compatible with TrueCrypt and VeraCrypt’.
-- <https://en.wikipedia.org/wiki/TrueCrypt TrueCrypt> is a discontinued system for
-- encrypting file containers, partitions or whole disks, typically used with Windows.
-- <https://www.veracrypt.fr/ VeraCrypt> is a maintained fork of TrueCrypt with various
-- improvements and auditing fixes.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gio.Objects.MountOperation
    ( 

-- * Exported types
    MountOperation(..)                      ,
    IsMountOperation                        ,
    toMountOperation                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [reply]("GI.Gio.Objects.MountOperation#g:method:reply"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAnonymous]("GI.Gio.Objects.MountOperation#g:method:getAnonymous"), [getChoice]("GI.Gio.Objects.MountOperation#g:method:getChoice"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDomain]("GI.Gio.Objects.MountOperation#g:method:getDomain"), [getIsTcryptHiddenVolume]("GI.Gio.Objects.MountOperation#g:method:getIsTcryptHiddenVolume"), [getIsTcryptSystemVolume]("GI.Gio.Objects.MountOperation#g:method:getIsTcryptSystemVolume"), [getPassword]("GI.Gio.Objects.MountOperation#g:method:getPassword"), [getPasswordSave]("GI.Gio.Objects.MountOperation#g:method:getPasswordSave"), [getPim]("GI.Gio.Objects.MountOperation#g:method:getPim"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getUsername]("GI.Gio.Objects.MountOperation#g:method:getUsername").
-- 
-- ==== Setters
-- [setAnonymous]("GI.Gio.Objects.MountOperation#g:method:setAnonymous"), [setChoice]("GI.Gio.Objects.MountOperation#g:method:setChoice"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDomain]("GI.Gio.Objects.MountOperation#g:method:setDomain"), [setIsTcryptHiddenVolume]("GI.Gio.Objects.MountOperation#g:method:setIsTcryptHiddenVolume"), [setIsTcryptSystemVolume]("GI.Gio.Objects.MountOperation#g:method:setIsTcryptSystemVolume"), [setPassword]("GI.Gio.Objects.MountOperation#g:method:setPassword"), [setPasswordSave]("GI.Gio.Objects.MountOperation#g:method:setPasswordSave"), [setPim]("GI.Gio.Objects.MountOperation#g:method:setPim"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setUsername]("GI.Gio.Objects.MountOperation#g:method:setUsername").

#if defined(ENABLE_OVERLOADING)
    ResolveMountOperationMethod             ,
#endif

-- ** getAnonymous #method:getAnonymous#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetAnonymousMethodInfo    ,
#endif
    mountOperationGetAnonymous              ,


-- ** getChoice #method:getChoice#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetChoiceMethodInfo       ,
#endif
    mountOperationGetChoice                 ,


-- ** getDomain #method:getDomain#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetDomainMethodInfo       ,
#endif
    mountOperationGetDomain                 ,


-- ** getIsTcryptHiddenVolume #method:getIsTcryptHiddenVolume#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetIsTcryptHiddenVolumeMethodInfo,
#endif
    mountOperationGetIsTcryptHiddenVolume   ,


-- ** getIsTcryptSystemVolume #method:getIsTcryptSystemVolume#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetIsTcryptSystemVolumeMethodInfo,
#endif
    mountOperationGetIsTcryptSystemVolume   ,


-- ** getPassword #method:getPassword#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetPasswordMethodInfo     ,
#endif
    mountOperationGetPassword               ,


-- ** getPasswordSave #method:getPasswordSave#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetPasswordSaveMethodInfo ,
#endif
    mountOperationGetPasswordSave           ,


-- ** getPim #method:getPim#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetPimMethodInfo          ,
#endif
    mountOperationGetPim                    ,


-- ** getUsername #method:getUsername#

#if defined(ENABLE_OVERLOADING)
    MountOperationGetUsernameMethodInfo     ,
#endif
    mountOperationGetUsername               ,


-- ** new #method:new#

    mountOperationNew                       ,


-- ** reply #method:reply#

#if defined(ENABLE_OVERLOADING)
    MountOperationReplyMethodInfo           ,
#endif
    mountOperationReply                     ,


-- ** setAnonymous #method:setAnonymous#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetAnonymousMethodInfo    ,
#endif
    mountOperationSetAnonymous              ,


-- ** setChoice #method:setChoice#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetChoiceMethodInfo       ,
#endif
    mountOperationSetChoice                 ,


-- ** setDomain #method:setDomain#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetDomainMethodInfo       ,
#endif
    mountOperationSetDomain                 ,


-- ** setIsTcryptHiddenVolume #method:setIsTcryptHiddenVolume#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetIsTcryptHiddenVolumeMethodInfo,
#endif
    mountOperationSetIsTcryptHiddenVolume   ,


-- ** setIsTcryptSystemVolume #method:setIsTcryptSystemVolume#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetIsTcryptSystemVolumeMethodInfo,
#endif
    mountOperationSetIsTcryptSystemVolume   ,


-- ** setPassword #method:setPassword#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetPasswordMethodInfo     ,
#endif
    mountOperationSetPassword               ,


-- ** setPasswordSave #method:setPasswordSave#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetPasswordSaveMethodInfo ,
#endif
    mountOperationSetPasswordSave           ,


-- ** setPim #method:setPim#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetPimMethodInfo          ,
#endif
    mountOperationSetPim                    ,


-- ** setUsername #method:setUsername#

#if defined(ENABLE_OVERLOADING)
    MountOperationSetUsernameMethodInfo     ,
#endif
    mountOperationSetUsername               ,




 -- * Properties


-- ** anonymous #attr:anonymous#
-- | Whether to use an anonymous user when authenticating.

#if defined(ENABLE_OVERLOADING)
    MountOperationAnonymousPropertyInfo     ,
#endif
    constructMountOperationAnonymous        ,
    getMountOperationAnonymous              ,
#if defined(ENABLE_OVERLOADING)
    mountOperationAnonymous                 ,
#endif
    setMountOperationAnonymous              ,


-- ** choice #attr:choice#
-- | The index of the user\'s choice when a question is asked during the
-- mount operation. See the [askQuestion]("GI.Gio.Objects.MountOperation#g:signal:askQuestion") signal.

#if defined(ENABLE_OVERLOADING)
    MountOperationChoicePropertyInfo        ,
#endif
    constructMountOperationChoice           ,
    getMountOperationChoice                 ,
#if defined(ENABLE_OVERLOADING)
    mountOperationChoice                    ,
#endif
    setMountOperationChoice                 ,


-- ** domain #attr:domain#
-- | The domain to use for the mount operation.

#if defined(ENABLE_OVERLOADING)
    MountOperationDomainPropertyInfo        ,
#endif
    constructMountOperationDomain           ,
    getMountOperationDomain                 ,
#if defined(ENABLE_OVERLOADING)
    mountOperationDomain                    ,
#endif
    setMountOperationDomain                 ,


-- ** isTcryptHiddenVolume #attr:isTcryptHiddenVolume#
-- | Whether the device to be unlocked is a TCRYPT hidden volume.
-- See <https://www.veracrypt.fr/en/Hidden%20Volume.html the VeraCrypt documentation>.
-- 
-- /Since: 2.58/

#if defined(ENABLE_OVERLOADING)
    MountOperationIsTcryptHiddenVolumePropertyInfo,
#endif
    constructMountOperationIsTcryptHiddenVolume,
    getMountOperationIsTcryptHiddenVolume   ,
#if defined(ENABLE_OVERLOADING)
    mountOperationIsTcryptHiddenVolume      ,
#endif
    setMountOperationIsTcryptHiddenVolume   ,


-- ** isTcryptSystemVolume #attr:isTcryptSystemVolume#
-- | Whether the device to be unlocked is a TCRYPT system volume.
-- In this context, a system volume is a volume with a bootloader
-- and operating system installed. This is only supported for Windows
-- operating systems. For further documentation, see
-- <https://www.veracrypt.fr/en/System%20Encryption.html the VeraCrypt documentation>.
-- 
-- /Since: 2.58/

#if defined(ENABLE_OVERLOADING)
    MountOperationIsTcryptSystemVolumePropertyInfo,
#endif
    constructMountOperationIsTcryptSystemVolume,
    getMountOperationIsTcryptSystemVolume   ,
#if defined(ENABLE_OVERLOADING)
    mountOperationIsTcryptSystemVolume      ,
#endif
    setMountOperationIsTcryptSystemVolume   ,


-- ** password #attr:password#
-- | The password that is used for authentication when carrying out
-- the mount operation.

#if defined(ENABLE_OVERLOADING)
    MountOperationPasswordPropertyInfo      ,
#endif
    constructMountOperationPassword         ,
    getMountOperationPassword               ,
#if defined(ENABLE_OVERLOADING)
    mountOperationPassword                  ,
#endif
    setMountOperationPassword               ,


-- ** passwordSave #attr:passwordSave#
-- | Determines if and how the password information should be saved.

#if defined(ENABLE_OVERLOADING)
    MountOperationPasswordSavePropertyInfo  ,
#endif
    constructMountOperationPasswordSave     ,
    getMountOperationPasswordSave           ,
#if defined(ENABLE_OVERLOADING)
    mountOperationPasswordSave              ,
#endif
    setMountOperationPasswordSave           ,


-- ** pim #attr:pim#
-- | The VeraCrypt PIM value, when unlocking a VeraCrypt volume. See
-- <https://www.veracrypt.fr/en/Personal%20Iterations%20Multiplier%20(PIM the VeraCrypt documentation>.html).
-- 
-- /Since: 2.58/

#if defined(ENABLE_OVERLOADING)
    MountOperationPimPropertyInfo           ,
#endif
    constructMountOperationPim              ,
    getMountOperationPim                    ,
#if defined(ENABLE_OVERLOADING)
    mountOperationPim                       ,
#endif
    setMountOperationPim                    ,


-- ** username #attr:username#
-- | The user name that is used for authentication when carrying out
-- the mount operation.

#if defined(ENABLE_OVERLOADING)
    MountOperationUsernamePropertyInfo      ,
#endif
    constructMountOperationUsername         ,
    getMountOperationUsername               ,
#if defined(ENABLE_OVERLOADING)
    mountOperationUsername                  ,
#endif
    setMountOperationUsername               ,




 -- * Signals


-- ** aborted #signal:aborted#

    C_MountOperationAbortedCallback         ,
    MountOperationAbortedCallback           ,
#if defined(ENABLE_OVERLOADING)
    MountOperationAbortedSignalInfo         ,
#endif
    afterMountOperationAborted              ,
    genClosure_MountOperationAborted        ,
    mk_MountOperationAbortedCallback        ,
    noMountOperationAbortedCallback         ,
    onMountOperationAborted                 ,
    wrap_MountOperationAbortedCallback      ,


-- ** askPassword #signal:askPassword#

    C_MountOperationAskPasswordCallback     ,
    MountOperationAskPasswordCallback       ,
#if defined(ENABLE_OVERLOADING)
    MountOperationAskPasswordSignalInfo     ,
#endif
    afterMountOperationAskPassword          ,
    genClosure_MountOperationAskPassword    ,
    mk_MountOperationAskPasswordCallback    ,
    noMountOperationAskPasswordCallback     ,
    onMountOperationAskPassword             ,
    wrap_MountOperationAskPasswordCallback  ,


-- ** askQuestion #signal:askQuestion#

    C_MountOperationAskQuestionCallback     ,
    MountOperationAskQuestionCallback       ,
#if defined(ENABLE_OVERLOADING)
    MountOperationAskQuestionSignalInfo     ,
#endif
    afterMountOperationAskQuestion          ,
    genClosure_MountOperationAskQuestion    ,
    mk_MountOperationAskQuestionCallback    ,
    noMountOperationAskQuestionCallback     ,
    onMountOperationAskQuestion             ,
    wrap_MountOperationAskQuestionCallback  ,


-- ** reply #signal:reply#

    C_MountOperationReplyCallback           ,
    MountOperationReplyCallback             ,
#if defined(ENABLE_OVERLOADING)
    MountOperationReplySignalInfo           ,
#endif
    afterMountOperationReply                ,
    genClosure_MountOperationReply          ,
    mk_MountOperationReplyCallback          ,
    noMountOperationReplyCallback           ,
    onMountOperationReply                   ,
    wrap_MountOperationReplyCallback        ,


-- ** showProcesses #signal:showProcesses#

    C_MountOperationShowProcessesCallback   ,
    MountOperationShowProcessesCallback     ,
#if defined(ENABLE_OVERLOADING)
    MountOperationShowProcessesSignalInfo   ,
#endif
    afterMountOperationShowProcesses        ,
    genClosure_MountOperationShowProcesses  ,
    mk_MountOperationShowProcessesCallback  ,
    noMountOperationShowProcessesCallback   ,
    onMountOperationShowProcesses           ,
    wrap_MountOperationShowProcessesCallback,


-- ** showUnmountProgress #signal:showUnmountProgress#

    C_MountOperationShowUnmountProgressCallback,
    MountOperationShowUnmountProgressCallback,
#if defined(ENABLE_OVERLOADING)
    MountOperationShowUnmountProgressSignalInfo,
#endif
    afterMountOperationShowUnmountProgress  ,
    genClosure_MountOperationShowUnmountProgress,
    mk_MountOperationShowUnmountProgressCallback,
    noMountOperationShowUnmountProgressCallback,
    onMountOperationShowUnmountProgress     ,
    wrap_MountOperationShowUnmountProgressCallback,




    ) 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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags

-- | Memory-managed wrapper type.
newtype MountOperation = MountOperation (SP.ManagedPtr MountOperation)
    deriving (MountOperation -> MountOperation -> Bool
(MountOperation -> MountOperation -> Bool)
-> (MountOperation -> MountOperation -> Bool) -> Eq MountOperation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MountOperation -> MountOperation -> Bool
$c/= :: MountOperation -> MountOperation -> Bool
== :: MountOperation -> MountOperation -> Bool
$c== :: MountOperation -> MountOperation -> Bool
Eq)

instance SP.ManagedPtrNewtype MountOperation where
    toManagedPtr :: MountOperation -> ManagedPtr MountOperation
toManagedPtr (MountOperation ManagedPtr MountOperation
p) = ManagedPtr MountOperation
p

foreign import ccall "g_mount_operation_get_type"
    c_g_mount_operation_get_type :: IO B.Types.GType

instance B.Types.TypedObject MountOperation where
    glibType :: IO GType
glibType = IO GType
c_g_mount_operation_get_type

instance B.Types.GObject MountOperation

-- | Type class for types which can be safely cast to `MountOperation`, for instance with `toMountOperation`.
class (SP.GObject o, O.IsDescendantOf MountOperation o) => IsMountOperation o
instance (SP.GObject o, O.IsDescendantOf MountOperation o) => IsMountOperation o

instance O.HasParentTypes MountOperation
type instance O.ParentTypes MountOperation = '[GObject.Object.Object]

-- | Cast to `MountOperation`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toMountOperation :: (MIO.MonadIO m, IsMountOperation o) => o -> m MountOperation
toMountOperation :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m MountOperation
toMountOperation = IO MountOperation -> m MountOperation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO MountOperation -> m MountOperation)
-> (o -> IO MountOperation) -> o -> m MountOperation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr MountOperation -> MountOperation)
-> o -> IO MountOperation
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr MountOperation -> MountOperation
MountOperation

-- | Convert 'MountOperation' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe MountOperation) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_mount_operation_get_type
    gvalueSet_ :: Ptr GValue -> Maybe MountOperation -> IO ()
gvalueSet_ Ptr GValue
gv Maybe MountOperation
P.Nothing = Ptr GValue -> Ptr MountOperation -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr MountOperation
forall a. Ptr a
FP.nullPtr :: FP.Ptr MountOperation)
    gvalueSet_ Ptr GValue
gv (P.Just MountOperation
obj) = MountOperation -> (Ptr MountOperation -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr MountOperation
obj (Ptr GValue -> Ptr MountOperation -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe MountOperation)
gvalueGet_ Ptr GValue
gv = do
        Ptr MountOperation
ptr <- Ptr GValue -> IO (Ptr MountOperation)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr MountOperation)
        if Ptr MountOperation
ptr Ptr MountOperation -> Ptr MountOperation -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr MountOperation
forall a. Ptr a
FP.nullPtr
        then MountOperation -> Maybe MountOperation
forall a. a -> Maybe a
P.Just (MountOperation -> Maybe MountOperation)
-> IO MountOperation -> IO (Maybe MountOperation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr MountOperation -> MountOperation)
-> Ptr MountOperation -> IO MountOperation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr MountOperation -> MountOperation
MountOperation Ptr MountOperation
ptr
        else Maybe MountOperation -> IO (Maybe MountOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MountOperation
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveMountOperationMethod (t :: Symbol) (o :: *) :: * where
    ResolveMountOperationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveMountOperationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveMountOperationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveMountOperationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveMountOperationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveMountOperationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveMountOperationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveMountOperationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveMountOperationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveMountOperationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveMountOperationMethod "reply" o = MountOperationReplyMethodInfo
    ResolveMountOperationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveMountOperationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveMountOperationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveMountOperationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveMountOperationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveMountOperationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveMountOperationMethod "getAnonymous" o = MountOperationGetAnonymousMethodInfo
    ResolveMountOperationMethod "getChoice" o = MountOperationGetChoiceMethodInfo
    ResolveMountOperationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveMountOperationMethod "getDomain" o = MountOperationGetDomainMethodInfo
    ResolveMountOperationMethod "getIsTcryptHiddenVolume" o = MountOperationGetIsTcryptHiddenVolumeMethodInfo
    ResolveMountOperationMethod "getIsTcryptSystemVolume" o = MountOperationGetIsTcryptSystemVolumeMethodInfo
    ResolveMountOperationMethod "getPassword" o = MountOperationGetPasswordMethodInfo
    ResolveMountOperationMethod "getPasswordSave" o = MountOperationGetPasswordSaveMethodInfo
    ResolveMountOperationMethod "getPim" o = MountOperationGetPimMethodInfo
    ResolveMountOperationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveMountOperationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveMountOperationMethod "getUsername" o = MountOperationGetUsernameMethodInfo
    ResolveMountOperationMethod "setAnonymous" o = MountOperationSetAnonymousMethodInfo
    ResolveMountOperationMethod "setChoice" o = MountOperationSetChoiceMethodInfo
    ResolveMountOperationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveMountOperationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveMountOperationMethod "setDomain" o = MountOperationSetDomainMethodInfo
    ResolveMountOperationMethod "setIsTcryptHiddenVolume" o = MountOperationSetIsTcryptHiddenVolumeMethodInfo
    ResolveMountOperationMethod "setIsTcryptSystemVolume" o = MountOperationSetIsTcryptSystemVolumeMethodInfo
    ResolveMountOperationMethod "setPassword" o = MountOperationSetPasswordMethodInfo
    ResolveMountOperationMethod "setPasswordSave" o = MountOperationSetPasswordSaveMethodInfo
    ResolveMountOperationMethod "setPim" o = MountOperationSetPimMethodInfo
    ResolveMountOperationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveMountOperationMethod "setUsername" o = MountOperationSetUsernameMethodInfo
    ResolveMountOperationMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveMountOperationMethod t MountOperation, O.OverloadedMethod info MountOperation p) => OL.IsLabel t (MountOperation -> 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 ~ ResolveMountOperationMethod t MountOperation, O.OverloadedMethod info MountOperation p, R.HasField t MountOperation p) => R.HasField t MountOperation p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveMountOperationMethod t MountOperation, O.OverloadedMethodInfo info MountOperation) => OL.IsLabel t (O.MethodProxy info MountOperation) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- signal MountOperation::aborted
-- | Emitted by the backend when e.g. a device becomes unavailable
-- while a mount operation is in progress.
-- 
-- Implementations of GMountOperation should handle this signal
-- by dismissing open password dialogs.
-- 
-- /Since: 2.20/
type MountOperationAbortedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MountOperationAbortedCallback`@.
noMountOperationAbortedCallback :: Maybe MountOperationAbortedCallback
noMountOperationAbortedCallback :: Maybe (IO ())
noMountOperationAbortedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MountOperationAbortedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MountOperationAbortedCallback`.
foreign import ccall "wrapper"
    mk_MountOperationAbortedCallback :: C_MountOperationAbortedCallback -> IO (FunPtr C_MountOperationAbortedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MountOperationAborted :: MonadIO m => MountOperationAbortedCallback -> m (GClosure C_MountOperationAbortedCallback)
genClosure_MountOperationAborted :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_MountOperationAbortedCallback)
genClosure_MountOperationAborted IO ()
cb = IO (GClosure C_MountOperationAbortedCallback)
-> m (GClosure C_MountOperationAbortedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MountOperationAbortedCallback)
 -> m (GClosure C_MountOperationAbortedCallback))
-> IO (GClosure C_MountOperationAbortedCallback)
-> m (GClosure C_MountOperationAbortedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAbortedCallback
cb' = IO () -> C_MountOperationAbortedCallback
wrap_MountOperationAbortedCallback IO ()
cb
    C_MountOperationAbortedCallback
-> IO (FunPtr C_MountOperationAbortedCallback)
mk_MountOperationAbortedCallback C_MountOperationAbortedCallback
cb' IO (FunPtr C_MountOperationAbortedCallback)
-> (FunPtr C_MountOperationAbortedCallback
    -> IO (GClosure C_MountOperationAbortedCallback))
-> IO (GClosure C_MountOperationAbortedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MountOperationAbortedCallback
-> IO (GClosure C_MountOperationAbortedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MountOperationAbortedCallback` into a `C_MountOperationAbortedCallback`.
wrap_MountOperationAbortedCallback ::
    MountOperationAbortedCallback ->
    C_MountOperationAbortedCallback
wrap_MountOperationAbortedCallback :: IO () -> C_MountOperationAbortedCallback
wrap_MountOperationAbortedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [aborted](#signal:aborted) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' mountOperation #aborted callback
-- @
-- 
-- 
onMountOperationAborted :: (IsMountOperation a, MonadIO m) => a -> MountOperationAbortedCallback -> m SignalHandlerId
onMountOperationAborted :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onMountOperationAborted a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAbortedCallback
cb' = IO () -> C_MountOperationAbortedCallback
wrap_MountOperationAbortedCallback IO ()
cb
    FunPtr C_MountOperationAbortedCallback
cb'' <- C_MountOperationAbortedCallback
-> IO (FunPtr C_MountOperationAbortedCallback)
mk_MountOperationAbortedCallback C_MountOperationAbortedCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"aborted" FunPtr C_MountOperationAbortedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [aborted](#signal:aborted) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' mountOperation #aborted callback
-- @
-- 
-- 
afterMountOperationAborted :: (IsMountOperation a, MonadIO m) => a -> MountOperationAbortedCallback -> m SignalHandlerId
afterMountOperationAborted :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterMountOperationAborted a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAbortedCallback
cb' = IO () -> C_MountOperationAbortedCallback
wrap_MountOperationAbortedCallback IO ()
cb
    FunPtr C_MountOperationAbortedCallback
cb'' <- C_MountOperationAbortedCallback
-> IO (FunPtr C_MountOperationAbortedCallback)
mk_MountOperationAbortedCallback C_MountOperationAbortedCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationAbortedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"aborted" FunPtr C_MountOperationAbortedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MountOperationAbortedSignalInfo
instance SignalInfo MountOperationAbortedSignalInfo where
    type HaskellCallbackType MountOperationAbortedSignalInfo = MountOperationAbortedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MountOperationAbortedCallback cb
        cb'' <- mk_MountOperationAbortedCallback cb'
        connectSignalFunPtr obj "aborted" cb'' connectMode detail

#endif

-- signal MountOperation::ask-password
-- | Emitted when a mount operation asks the user for a password.
-- 
-- If the message contains a line break, the first line should be
-- presented as a heading. For example, it may be used as the
-- primary text in a @/GtkMessageDialog/@.
type MountOperationAskPasswordCallback =
    T.Text
    -- ^ /@message@/: string containing a message to display to the user.
    -> T.Text
    -- ^ /@defaultUser@/: string containing the default user name.
    -> T.Text
    -- ^ /@defaultDomain@/: string containing the default domain.
    -> [Gio.Flags.AskPasswordFlags]
    -- ^ /@flags@/: a set of t'GI.Gio.Flags.AskPasswordFlags'.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MountOperationAskPasswordCallback`@.
noMountOperationAskPasswordCallback :: Maybe MountOperationAskPasswordCallback
noMountOperationAskPasswordCallback :: Maybe MountOperationAskPasswordCallback
noMountOperationAskPasswordCallback = Maybe MountOperationAskPasswordCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MountOperationAskPasswordCallback =
    Ptr () ->                               -- object
    CString ->
    CString ->
    CString ->
    CUInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MountOperationAskPasswordCallback`.
foreign import ccall "wrapper"
    mk_MountOperationAskPasswordCallback :: C_MountOperationAskPasswordCallback -> IO (FunPtr C_MountOperationAskPasswordCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MountOperationAskPassword :: MonadIO m => MountOperationAskPasswordCallback -> m (GClosure C_MountOperationAskPasswordCallback)
genClosure_MountOperationAskPassword :: forall (m :: * -> *).
MonadIO m =>
MountOperationAskPasswordCallback
-> m (GClosure C_MountOperationAskPasswordCallback)
genClosure_MountOperationAskPassword MountOperationAskPasswordCallback
cb = IO (GClosure C_MountOperationAskPasswordCallback)
-> m (GClosure C_MountOperationAskPasswordCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MountOperationAskPasswordCallback)
 -> m (GClosure C_MountOperationAskPasswordCallback))
-> IO (GClosure C_MountOperationAskPasswordCallback)
-> m (GClosure C_MountOperationAskPasswordCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAskPasswordCallback
cb' = MountOperationAskPasswordCallback
-> C_MountOperationAskPasswordCallback
wrap_MountOperationAskPasswordCallback MountOperationAskPasswordCallback
cb
    C_MountOperationAskPasswordCallback
-> IO (FunPtr C_MountOperationAskPasswordCallback)
mk_MountOperationAskPasswordCallback C_MountOperationAskPasswordCallback
cb' IO (FunPtr C_MountOperationAskPasswordCallback)
-> (FunPtr C_MountOperationAskPasswordCallback
    -> IO (GClosure C_MountOperationAskPasswordCallback))
-> IO (GClosure C_MountOperationAskPasswordCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MountOperationAskPasswordCallback
-> IO (GClosure C_MountOperationAskPasswordCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MountOperationAskPasswordCallback` into a `C_MountOperationAskPasswordCallback`.
wrap_MountOperationAskPasswordCallback ::
    MountOperationAskPasswordCallback ->
    C_MountOperationAskPasswordCallback
wrap_MountOperationAskPasswordCallback :: MountOperationAskPasswordCallback
-> C_MountOperationAskPasswordCallback
wrap_MountOperationAskPasswordCallback MountOperationAskPasswordCallback
_cb Ptr ()
_ CString
message CString
defaultUser CString
defaultDomain CUInt
flags Ptr ()
_ = do
    Text
message' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
message
    Text
defaultUser' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
defaultUser
    Text
defaultDomain' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
defaultDomain
    let flags' :: [AskPasswordFlags]
flags' = CUInt -> [AskPasswordFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
flags
    MountOperationAskPasswordCallback
_cb  Text
message' Text
defaultUser' Text
defaultDomain' [AskPasswordFlags]
flags'


-- | Connect a signal handler for the [askPassword](#signal:askPassword) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' mountOperation #askPassword callback
-- @
-- 
-- 
onMountOperationAskPassword :: (IsMountOperation a, MonadIO m) => a -> MountOperationAskPasswordCallback -> m SignalHandlerId
onMountOperationAskPassword :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationAskPasswordCallback -> m SignalHandlerId
onMountOperationAskPassword a
obj MountOperationAskPasswordCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAskPasswordCallback
cb' = MountOperationAskPasswordCallback
-> C_MountOperationAskPasswordCallback
wrap_MountOperationAskPasswordCallback MountOperationAskPasswordCallback
cb
    FunPtr C_MountOperationAskPasswordCallback
cb'' <- C_MountOperationAskPasswordCallback
-> IO (FunPtr C_MountOperationAskPasswordCallback)
mk_MountOperationAskPasswordCallback C_MountOperationAskPasswordCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationAskPasswordCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"ask-password" FunPtr C_MountOperationAskPasswordCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [askPassword](#signal:askPassword) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' mountOperation #askPassword callback
-- @
-- 
-- 
afterMountOperationAskPassword :: (IsMountOperation a, MonadIO m) => a -> MountOperationAskPasswordCallback -> m SignalHandlerId
afterMountOperationAskPassword :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationAskPasswordCallback -> m SignalHandlerId
afterMountOperationAskPassword a
obj MountOperationAskPasswordCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAskPasswordCallback
cb' = MountOperationAskPasswordCallback
-> C_MountOperationAskPasswordCallback
wrap_MountOperationAskPasswordCallback MountOperationAskPasswordCallback
cb
    FunPtr C_MountOperationAskPasswordCallback
cb'' <- C_MountOperationAskPasswordCallback
-> IO (FunPtr C_MountOperationAskPasswordCallback)
mk_MountOperationAskPasswordCallback C_MountOperationAskPasswordCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationAskPasswordCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"ask-password" FunPtr C_MountOperationAskPasswordCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MountOperationAskPasswordSignalInfo
instance SignalInfo MountOperationAskPasswordSignalInfo where
    type HaskellCallbackType MountOperationAskPasswordSignalInfo = MountOperationAskPasswordCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MountOperationAskPasswordCallback cb
        cb'' <- mk_MountOperationAskPasswordCallback cb'
        connectSignalFunPtr obj "ask-password" cb'' connectMode detail

#endif

-- signal MountOperation::ask-question
-- | Emitted when asking the user a question and gives a list of
-- choices for the user to choose from.
-- 
-- If the message contains a line break, the first line should be
-- presented as a heading. For example, it may be used as the
-- primary text in a @/GtkMessageDialog/@.
type MountOperationAskQuestionCallback =
    T.Text
    -- ^ /@message@/: string containing a message to display to the user.
    -> [T.Text]
    -- ^ /@choices@/: an array of strings for each possible choice.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MountOperationAskQuestionCallback`@.
noMountOperationAskQuestionCallback :: Maybe MountOperationAskQuestionCallback
noMountOperationAskQuestionCallback :: Maybe MountOperationAskQuestionCallback
noMountOperationAskQuestionCallback = Maybe MountOperationAskQuestionCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MountOperationAskQuestionCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr CString ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MountOperationAskQuestionCallback`.
foreign import ccall "wrapper"
    mk_MountOperationAskQuestionCallback :: C_MountOperationAskQuestionCallback -> IO (FunPtr C_MountOperationAskQuestionCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MountOperationAskQuestion :: MonadIO m => MountOperationAskQuestionCallback -> m (GClosure C_MountOperationAskQuestionCallback)
genClosure_MountOperationAskQuestion :: forall (m :: * -> *).
MonadIO m =>
MountOperationAskQuestionCallback
-> m (GClosure C_MountOperationAskQuestionCallback)
genClosure_MountOperationAskQuestion MountOperationAskQuestionCallback
cb = IO (GClosure C_MountOperationAskQuestionCallback)
-> m (GClosure C_MountOperationAskQuestionCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MountOperationAskQuestionCallback)
 -> m (GClosure C_MountOperationAskQuestionCallback))
-> IO (GClosure C_MountOperationAskQuestionCallback)
-> m (GClosure C_MountOperationAskQuestionCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAskQuestionCallback
cb' = MountOperationAskQuestionCallback
-> C_MountOperationAskQuestionCallback
wrap_MountOperationAskQuestionCallback MountOperationAskQuestionCallback
cb
    C_MountOperationAskQuestionCallback
-> IO (FunPtr C_MountOperationAskQuestionCallback)
mk_MountOperationAskQuestionCallback C_MountOperationAskQuestionCallback
cb' IO (FunPtr C_MountOperationAskQuestionCallback)
-> (FunPtr C_MountOperationAskQuestionCallback
    -> IO (GClosure C_MountOperationAskQuestionCallback))
-> IO (GClosure C_MountOperationAskQuestionCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MountOperationAskQuestionCallback
-> IO (GClosure C_MountOperationAskQuestionCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MountOperationAskQuestionCallback` into a `C_MountOperationAskQuestionCallback`.
wrap_MountOperationAskQuestionCallback ::
    MountOperationAskQuestionCallback ->
    C_MountOperationAskQuestionCallback
wrap_MountOperationAskQuestionCallback :: MountOperationAskQuestionCallback
-> C_MountOperationAskQuestionCallback
wrap_MountOperationAskQuestionCallback MountOperationAskQuestionCallback
_cb Ptr ()
_ CString
message Ptr CString
choices Ptr ()
_ = do
    Text
message' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
message
    [Text]
choices' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
choices
    MountOperationAskQuestionCallback
_cb  Text
message' [Text]
choices'


-- | Connect a signal handler for the [askQuestion](#signal:askQuestion) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' mountOperation #askQuestion callback
-- @
-- 
-- 
onMountOperationAskQuestion :: (IsMountOperation a, MonadIO m) => a -> MountOperationAskQuestionCallback -> m SignalHandlerId
onMountOperationAskQuestion :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationAskQuestionCallback -> m SignalHandlerId
onMountOperationAskQuestion a
obj MountOperationAskQuestionCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAskQuestionCallback
cb' = MountOperationAskQuestionCallback
-> C_MountOperationAskQuestionCallback
wrap_MountOperationAskQuestionCallback MountOperationAskQuestionCallback
cb
    FunPtr C_MountOperationAskQuestionCallback
cb'' <- C_MountOperationAskQuestionCallback
-> IO (FunPtr C_MountOperationAskQuestionCallback)
mk_MountOperationAskQuestionCallback C_MountOperationAskQuestionCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationAskQuestionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"ask-question" FunPtr C_MountOperationAskQuestionCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [askQuestion](#signal:askQuestion) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' mountOperation #askQuestion callback
-- @
-- 
-- 
afterMountOperationAskQuestion :: (IsMountOperation a, MonadIO m) => a -> MountOperationAskQuestionCallback -> m SignalHandlerId
afterMountOperationAskQuestion :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationAskQuestionCallback -> m SignalHandlerId
afterMountOperationAskQuestion a
obj MountOperationAskQuestionCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationAskQuestionCallback
cb' = MountOperationAskQuestionCallback
-> C_MountOperationAskQuestionCallback
wrap_MountOperationAskQuestionCallback MountOperationAskQuestionCallback
cb
    FunPtr C_MountOperationAskQuestionCallback
cb'' <- C_MountOperationAskQuestionCallback
-> IO (FunPtr C_MountOperationAskQuestionCallback)
mk_MountOperationAskQuestionCallback C_MountOperationAskQuestionCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationAskQuestionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"ask-question" FunPtr C_MountOperationAskQuestionCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MountOperationAskQuestionSignalInfo
instance SignalInfo MountOperationAskQuestionSignalInfo where
    type HaskellCallbackType MountOperationAskQuestionSignalInfo = MountOperationAskQuestionCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MountOperationAskQuestionCallback cb
        cb'' <- mk_MountOperationAskQuestionCallback cb'
        connectSignalFunPtr obj "ask-question" cb'' connectMode detail

#endif

-- signal MountOperation::reply
-- | Emitted when the user has replied to the mount operation.
type MountOperationReplyCallback =
    Gio.Enums.MountOperationResult
    -- ^ /@result@/: a t'GI.Gio.Enums.MountOperationResult' indicating how the request was handled
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MountOperationReplyCallback`@.
noMountOperationReplyCallback :: Maybe MountOperationReplyCallback
noMountOperationReplyCallback :: Maybe MountOperationReplyCallback
noMountOperationReplyCallback = Maybe MountOperationReplyCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MountOperationReplyCallback =
    Ptr () ->                               -- object
    CUInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MountOperationReplyCallback`.
foreign import ccall "wrapper"
    mk_MountOperationReplyCallback :: C_MountOperationReplyCallback -> IO (FunPtr C_MountOperationReplyCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MountOperationReply :: MonadIO m => MountOperationReplyCallback -> m (GClosure C_MountOperationReplyCallback)
genClosure_MountOperationReply :: forall (m :: * -> *).
MonadIO m =>
MountOperationReplyCallback
-> m (GClosure C_MountOperationReplyCallback)
genClosure_MountOperationReply MountOperationReplyCallback
cb = IO (GClosure C_MountOperationReplyCallback)
-> m (GClosure C_MountOperationReplyCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MountOperationReplyCallback)
 -> m (GClosure C_MountOperationReplyCallback))
-> IO (GClosure C_MountOperationReplyCallback)
-> m (GClosure C_MountOperationReplyCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationReplyCallback
cb' = MountOperationReplyCallback -> C_MountOperationReplyCallback
wrap_MountOperationReplyCallback MountOperationReplyCallback
cb
    C_MountOperationReplyCallback
-> IO (FunPtr C_MountOperationReplyCallback)
mk_MountOperationReplyCallback C_MountOperationReplyCallback
cb' IO (FunPtr C_MountOperationReplyCallback)
-> (FunPtr C_MountOperationReplyCallback
    -> IO (GClosure C_MountOperationReplyCallback))
-> IO (GClosure C_MountOperationReplyCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MountOperationReplyCallback
-> IO (GClosure C_MountOperationReplyCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MountOperationReplyCallback` into a `C_MountOperationReplyCallback`.
wrap_MountOperationReplyCallback ::
    MountOperationReplyCallback ->
    C_MountOperationReplyCallback
wrap_MountOperationReplyCallback :: MountOperationReplyCallback -> C_MountOperationReplyCallback
wrap_MountOperationReplyCallback MountOperationReplyCallback
_cb Ptr ()
_ CUInt
result_ Ptr ()
_ = do
    let result_' :: MountOperationResult
result_' = (Int -> MountOperationResult
forall a. Enum a => Int -> a
toEnum (Int -> MountOperationResult)
-> (CUInt -> Int) -> CUInt -> MountOperationResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result_
    MountOperationReplyCallback
_cb  MountOperationResult
result_'


-- | Connect a signal handler for the [reply](#signal:reply) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' mountOperation #reply callback
-- @
-- 
-- 
onMountOperationReply :: (IsMountOperation a, MonadIO m) => a -> MountOperationReplyCallback -> m SignalHandlerId
onMountOperationReply :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationReplyCallback -> m SignalHandlerId
onMountOperationReply a
obj MountOperationReplyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationReplyCallback
cb' = MountOperationReplyCallback -> C_MountOperationReplyCallback
wrap_MountOperationReplyCallback MountOperationReplyCallback
cb
    FunPtr C_MountOperationReplyCallback
cb'' <- C_MountOperationReplyCallback
-> IO (FunPtr C_MountOperationReplyCallback)
mk_MountOperationReplyCallback C_MountOperationReplyCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationReplyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"reply" FunPtr C_MountOperationReplyCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [reply](#signal:reply) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' mountOperation #reply callback
-- @
-- 
-- 
afterMountOperationReply :: (IsMountOperation a, MonadIO m) => a -> MountOperationReplyCallback -> m SignalHandlerId
afterMountOperationReply :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationReplyCallback -> m SignalHandlerId
afterMountOperationReply a
obj MountOperationReplyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationReplyCallback
cb' = MountOperationReplyCallback -> C_MountOperationReplyCallback
wrap_MountOperationReplyCallback MountOperationReplyCallback
cb
    FunPtr C_MountOperationReplyCallback
cb'' <- C_MountOperationReplyCallback
-> IO (FunPtr C_MountOperationReplyCallback)
mk_MountOperationReplyCallback C_MountOperationReplyCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationReplyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"reply" FunPtr C_MountOperationReplyCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MountOperationReplySignalInfo
instance SignalInfo MountOperationReplySignalInfo where
    type HaskellCallbackType MountOperationReplySignalInfo = MountOperationReplyCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MountOperationReplyCallback cb
        cb'' <- mk_MountOperationReplyCallback cb'
        connectSignalFunPtr obj "reply" cb'' connectMode detail

#endif

-- signal MountOperation::show-processes
-- | Emitted when one or more processes are blocking an operation
-- e.g. unmounting\/ejecting a t'GI.Gio.Interfaces.Mount.Mount' or stopping a t'GI.Gio.Interfaces.Drive.Drive'.
-- 
-- Note that this signal may be emitted several times to update the
-- list of blocking processes as processes close files. The
-- application should only respond with 'GI.Gio.Objects.MountOperation.mountOperationReply' to
-- the latest signal (setting t'GI.Gio.Objects.MountOperation.MountOperation':@/choice/@ to the choice
-- the user made).
-- 
-- If the message contains a line break, the first line should be
-- presented as a heading. For example, it may be used as the
-- primary text in a @/GtkMessageDialog/@.
-- 
-- /Since: 2.22/
type MountOperationShowProcessesCallback =
    T.Text
    -- ^ /@message@/: string containing a message to display to the user.
    -> [Int32]
    -- ^ /@processes@/: an array of @/GPid/@ for processes
    --   blocking the operation.
    -> [T.Text]
    -- ^ /@choices@/: an array of strings for each possible choice.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MountOperationShowProcessesCallback`@.
noMountOperationShowProcessesCallback :: Maybe MountOperationShowProcessesCallback
noMountOperationShowProcessesCallback :: Maybe MountOperationShowProcessesCallback
noMountOperationShowProcessesCallback = Maybe MountOperationShowProcessesCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MountOperationShowProcessesCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr (GArray Int32) ->
    Ptr CString ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MountOperationShowProcessesCallback`.
foreign import ccall "wrapper"
    mk_MountOperationShowProcessesCallback :: C_MountOperationShowProcessesCallback -> IO (FunPtr C_MountOperationShowProcessesCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MountOperationShowProcesses :: MonadIO m => MountOperationShowProcessesCallback -> m (GClosure C_MountOperationShowProcessesCallback)
genClosure_MountOperationShowProcesses :: forall (m :: * -> *).
MonadIO m =>
MountOperationShowProcessesCallback
-> m (GClosure C_MountOperationShowProcessesCallback)
genClosure_MountOperationShowProcesses MountOperationShowProcessesCallback
cb = IO (GClosure C_MountOperationShowProcessesCallback)
-> m (GClosure C_MountOperationShowProcessesCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MountOperationShowProcessesCallback)
 -> m (GClosure C_MountOperationShowProcessesCallback))
-> IO (GClosure C_MountOperationShowProcessesCallback)
-> m (GClosure C_MountOperationShowProcessesCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationShowProcessesCallback
cb' = MountOperationShowProcessesCallback
-> C_MountOperationShowProcessesCallback
wrap_MountOperationShowProcessesCallback MountOperationShowProcessesCallback
cb
    C_MountOperationShowProcessesCallback
-> IO (FunPtr C_MountOperationShowProcessesCallback)
mk_MountOperationShowProcessesCallback C_MountOperationShowProcessesCallback
cb' IO (FunPtr C_MountOperationShowProcessesCallback)
-> (FunPtr C_MountOperationShowProcessesCallback
    -> IO (GClosure C_MountOperationShowProcessesCallback))
-> IO (GClosure C_MountOperationShowProcessesCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MountOperationShowProcessesCallback
-> IO (GClosure C_MountOperationShowProcessesCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MountOperationShowProcessesCallback` into a `C_MountOperationShowProcessesCallback`.
wrap_MountOperationShowProcessesCallback ::
    MountOperationShowProcessesCallback ->
    C_MountOperationShowProcessesCallback
wrap_MountOperationShowProcessesCallback :: MountOperationShowProcessesCallback
-> C_MountOperationShowProcessesCallback
wrap_MountOperationShowProcessesCallback MountOperationShowProcessesCallback
_cb Ptr ()
_ CString
message Ptr (GArray Int32)
processes Ptr CString
choices Ptr ()
_ = do
    Text
message' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
message
    [Int32]
processes' <- Ptr (GArray Int32) -> IO [Int32]
forall a. Storable a => Ptr (GArray a) -> IO [a]
unpackGArray Ptr (GArray Int32)
processes
    [Text]
choices' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
choices
    MountOperationShowProcessesCallback
_cb  Text
message' [Int32]
processes' [Text]
choices'


-- | Connect a signal handler for the [showProcesses](#signal:showProcesses) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' mountOperation #showProcesses callback
-- @
-- 
-- 
onMountOperationShowProcesses :: (IsMountOperation a, MonadIO m) => a -> MountOperationShowProcessesCallback -> m SignalHandlerId
onMountOperationShowProcesses :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationShowProcessesCallback -> m SignalHandlerId
onMountOperationShowProcesses a
obj MountOperationShowProcessesCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationShowProcessesCallback
cb' = MountOperationShowProcessesCallback
-> C_MountOperationShowProcessesCallback
wrap_MountOperationShowProcessesCallback MountOperationShowProcessesCallback
cb
    FunPtr C_MountOperationShowProcessesCallback
cb'' <- C_MountOperationShowProcessesCallback
-> IO (FunPtr C_MountOperationShowProcessesCallback)
mk_MountOperationShowProcessesCallback C_MountOperationShowProcessesCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationShowProcessesCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"show-processes" FunPtr C_MountOperationShowProcessesCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [showProcesses](#signal:showProcesses) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' mountOperation #showProcesses callback
-- @
-- 
-- 
afterMountOperationShowProcesses :: (IsMountOperation a, MonadIO m) => a -> MountOperationShowProcessesCallback -> m SignalHandlerId
afterMountOperationShowProcesses :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationShowProcessesCallback -> m SignalHandlerId
afterMountOperationShowProcesses a
obj MountOperationShowProcessesCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationShowProcessesCallback
cb' = MountOperationShowProcessesCallback
-> C_MountOperationShowProcessesCallback
wrap_MountOperationShowProcessesCallback MountOperationShowProcessesCallback
cb
    FunPtr C_MountOperationShowProcessesCallback
cb'' <- C_MountOperationShowProcessesCallback
-> IO (FunPtr C_MountOperationShowProcessesCallback)
mk_MountOperationShowProcessesCallback C_MountOperationShowProcessesCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationShowProcessesCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"show-processes" FunPtr C_MountOperationShowProcessesCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MountOperationShowProcessesSignalInfo
instance SignalInfo MountOperationShowProcessesSignalInfo where
    type HaskellCallbackType MountOperationShowProcessesSignalInfo = MountOperationShowProcessesCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MountOperationShowProcessesCallback cb
        cb'' <- mk_MountOperationShowProcessesCallback cb'
        connectSignalFunPtr obj "show-processes" cb'' connectMode detail

#endif

-- signal MountOperation::show-unmount-progress
-- | Emitted when an unmount operation has been busy for more than some time
-- (typically 1.5 seconds).
-- 
-- When unmounting or ejecting a volume, the kernel might need to flush
-- pending data in its buffers to the volume stable storage, and this operation
-- can take a considerable amount of time. This signal may be emitted several
-- times as long as the unmount operation is outstanding, and then one
-- last time when the operation is completed, with /@bytesLeft@/ set to zero.
-- 
-- Implementations of GMountOperation should handle this signal by
-- showing an UI notification, and then dismiss it, or show another notification
-- of completion, when /@bytesLeft@/ reaches zero.
-- 
-- If the message contains a line break, the first line should be
-- presented as a heading. For example, it may be used as the
-- primary text in a @/GtkMessageDialog/@.
-- 
-- /Since: 2.34/
type MountOperationShowUnmountProgressCallback =
    T.Text
    -- ^ /@message@/: string containing a message to display to the user
    -> Int64
    -- ^ /@timeLeft@/: the estimated time left before the operation completes,
    --     in microseconds, or -1
    -> Int64
    -- ^ /@bytesLeft@/: the amount of bytes to be written before the operation
    --     completes (or -1 if such amount is not known), or zero if the operation
    --     is completed
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `MountOperationShowUnmountProgressCallback`@.
noMountOperationShowUnmountProgressCallback :: Maybe MountOperationShowUnmountProgressCallback
noMountOperationShowUnmountProgressCallback :: Maybe MountOperationShowUnmountProgressCallback
noMountOperationShowUnmountProgressCallback = Maybe MountOperationShowUnmountProgressCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_MountOperationShowUnmountProgressCallback =
    Ptr () ->                               -- object
    CString ->
    Int64 ->
    Int64 ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_MountOperationShowUnmountProgressCallback`.
foreign import ccall "wrapper"
    mk_MountOperationShowUnmountProgressCallback :: C_MountOperationShowUnmountProgressCallback -> IO (FunPtr C_MountOperationShowUnmountProgressCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_MountOperationShowUnmountProgress :: MonadIO m => MountOperationShowUnmountProgressCallback -> m (GClosure C_MountOperationShowUnmountProgressCallback)
genClosure_MountOperationShowUnmountProgress :: forall (m :: * -> *).
MonadIO m =>
MountOperationShowUnmountProgressCallback
-> m (GClosure C_MountOperationShowUnmountProgressCallback)
genClosure_MountOperationShowUnmountProgress MountOperationShowUnmountProgressCallback
cb = IO (GClosure C_MountOperationShowUnmountProgressCallback)
-> m (GClosure C_MountOperationShowUnmountProgressCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_MountOperationShowUnmountProgressCallback)
 -> m (GClosure C_MountOperationShowUnmountProgressCallback))
-> IO (GClosure C_MountOperationShowUnmountProgressCallback)
-> m (GClosure C_MountOperationShowUnmountProgressCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationShowUnmountProgressCallback
cb' = MountOperationShowUnmountProgressCallback
-> C_MountOperationShowUnmountProgressCallback
wrap_MountOperationShowUnmountProgressCallback MountOperationShowUnmountProgressCallback
cb
    C_MountOperationShowUnmountProgressCallback
-> IO (FunPtr C_MountOperationShowUnmountProgressCallback)
mk_MountOperationShowUnmountProgressCallback C_MountOperationShowUnmountProgressCallback
cb' IO (FunPtr C_MountOperationShowUnmountProgressCallback)
-> (FunPtr C_MountOperationShowUnmountProgressCallback
    -> IO (GClosure C_MountOperationShowUnmountProgressCallback))
-> IO (GClosure C_MountOperationShowUnmountProgressCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_MountOperationShowUnmountProgressCallback
-> IO (GClosure C_MountOperationShowUnmountProgressCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `MountOperationShowUnmountProgressCallback` into a `C_MountOperationShowUnmountProgressCallback`.
wrap_MountOperationShowUnmountProgressCallback ::
    MountOperationShowUnmountProgressCallback ->
    C_MountOperationShowUnmountProgressCallback
wrap_MountOperationShowUnmountProgressCallback :: MountOperationShowUnmountProgressCallback
-> C_MountOperationShowUnmountProgressCallback
wrap_MountOperationShowUnmountProgressCallback MountOperationShowUnmountProgressCallback
_cb Ptr ()
_ CString
message Int64
timeLeft Int64
bytesLeft Ptr ()
_ = do
    Text
message' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
message
    MountOperationShowUnmountProgressCallback
_cb  Text
message' Int64
timeLeft Int64
bytesLeft


-- | Connect a signal handler for the [showUnmountProgress](#signal:showUnmountProgress) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' mountOperation #showUnmountProgress callback
-- @
-- 
-- 
onMountOperationShowUnmountProgress :: (IsMountOperation a, MonadIO m) => a -> MountOperationShowUnmountProgressCallback -> m SignalHandlerId
onMountOperationShowUnmountProgress :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationShowUnmountProgressCallback -> m SignalHandlerId
onMountOperationShowUnmountProgress a
obj MountOperationShowUnmountProgressCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationShowUnmountProgressCallback
cb' = MountOperationShowUnmountProgressCallback
-> C_MountOperationShowUnmountProgressCallback
wrap_MountOperationShowUnmountProgressCallback MountOperationShowUnmountProgressCallback
cb
    FunPtr C_MountOperationShowUnmountProgressCallback
cb'' <- C_MountOperationShowUnmountProgressCallback
-> IO (FunPtr C_MountOperationShowUnmountProgressCallback)
mk_MountOperationShowUnmountProgressCallback C_MountOperationShowUnmountProgressCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationShowUnmountProgressCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"show-unmount-progress" FunPtr C_MountOperationShowUnmountProgressCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [showUnmountProgress](#signal:showUnmountProgress) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' mountOperation #showUnmountProgress callback
-- @
-- 
-- 
afterMountOperationShowUnmountProgress :: (IsMountOperation a, MonadIO m) => a -> MountOperationShowUnmountProgressCallback -> m SignalHandlerId
afterMountOperationShowUnmountProgress :: forall a (m :: * -> *).
(IsMountOperation a, MonadIO m) =>
a -> MountOperationShowUnmountProgressCallback -> m SignalHandlerId
afterMountOperationShowUnmountProgress a
obj MountOperationShowUnmountProgressCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_MountOperationShowUnmountProgressCallback
cb' = MountOperationShowUnmountProgressCallback
-> C_MountOperationShowUnmountProgressCallback
wrap_MountOperationShowUnmountProgressCallback MountOperationShowUnmountProgressCallback
cb
    FunPtr C_MountOperationShowUnmountProgressCallback
cb'' <- C_MountOperationShowUnmountProgressCallback
-> IO (FunPtr C_MountOperationShowUnmountProgressCallback)
mk_MountOperationShowUnmountProgressCallback C_MountOperationShowUnmountProgressCallback
cb'
    a
-> Text
-> FunPtr C_MountOperationShowUnmountProgressCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"show-unmount-progress" FunPtr C_MountOperationShowUnmountProgressCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data MountOperationShowUnmountProgressSignalInfo
instance SignalInfo MountOperationShowUnmountProgressSignalInfo where
    type HaskellCallbackType MountOperationShowUnmountProgressSignalInfo = MountOperationShowUnmountProgressCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_MountOperationShowUnmountProgressCallback cb
        cb'' <- mk_MountOperationShowUnmountProgressCallback cb'
        connectSignalFunPtr obj "show-unmount-progress" cb'' connectMode detail

#endif

-- VVV Prop "anonymous"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@anonymous@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #anonymous
-- @
getMountOperationAnonymous :: (MonadIO m, IsMountOperation o) => o -> m Bool
getMountOperationAnonymous :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Bool
getMountOperationAnonymous o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"anonymous"

-- | Set the value of the “@anonymous@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #anonymous 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationAnonymous :: (MonadIO m, IsMountOperation o) => o -> Bool -> m ()
setMountOperationAnonymous :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Bool -> m ()
setMountOperationAnonymous o
obj Bool
val = IO () -> m ()
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"anonymous" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@anonymous@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationAnonymous :: (IsMountOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructMountOperationAnonymous :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructMountOperationAnonymous Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"anonymous" Bool
val

#if defined(ENABLE_OVERLOADING)
data MountOperationAnonymousPropertyInfo
instance AttrInfo MountOperationAnonymousPropertyInfo where
    type AttrAllowedOps MountOperationAnonymousPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationAnonymousPropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationAnonymousPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint MountOperationAnonymousPropertyInfo = (~) Bool
    type AttrTransferType MountOperationAnonymousPropertyInfo = Bool
    type AttrGetType MountOperationAnonymousPropertyInfo = Bool
    type AttrLabel MountOperationAnonymousPropertyInfo = "anonymous"
    type AttrOrigin MountOperationAnonymousPropertyInfo = MountOperation
    attrGet = getMountOperationAnonymous
    attrSet = setMountOperationAnonymous
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationAnonymous
    attrClear = undefined
#endif

-- VVV Prop "choice"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@choice@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #choice
-- @
getMountOperationChoice :: (MonadIO m, IsMountOperation o) => o -> m Int32
getMountOperationChoice :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Int32
getMountOperationChoice o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"choice"

-- | Set the value of the “@choice@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #choice 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationChoice :: (MonadIO m, IsMountOperation o) => o -> Int32 -> m ()
setMountOperationChoice :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Int32 -> m ()
setMountOperationChoice o
obj Int32
val = IO () -> m ()
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"choice" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@choice@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationChoice :: (IsMountOperation o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructMountOperationChoice :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructMountOperationChoice Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"choice" Int32
val

#if defined(ENABLE_OVERLOADING)
data MountOperationChoicePropertyInfo
instance AttrInfo MountOperationChoicePropertyInfo where
    type AttrAllowedOps MountOperationChoicePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationChoicePropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationChoicePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint MountOperationChoicePropertyInfo = (~) Int32
    type AttrTransferType MountOperationChoicePropertyInfo = Int32
    type AttrGetType MountOperationChoicePropertyInfo = Int32
    type AttrLabel MountOperationChoicePropertyInfo = "choice"
    type AttrOrigin MountOperationChoicePropertyInfo = MountOperation
    attrGet = getMountOperationChoice
    attrSet = setMountOperationChoice
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationChoice
    attrClear = undefined
#endif

-- VVV Prop "domain"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@domain@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #domain
-- @
getMountOperationDomain :: (MonadIO m, IsMountOperation o) => o -> m T.Text
getMountOperationDomain :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Text
getMountOperationDomain o
obj = IO Text -> m Text
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
"getMountOperationDomain" (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
"domain"

-- | Set the value of the “@domain@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #domain 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationDomain :: (MonadIO m, IsMountOperation o) => o -> T.Text -> m ()
setMountOperationDomain :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Text -> m ()
setMountOperationDomain o
obj Text
val = IO () -> m ()
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
"domain" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@domain@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationDomain :: (IsMountOperation o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructMountOperationDomain :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructMountOperationDomain Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"domain" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data MountOperationDomainPropertyInfo
instance AttrInfo MountOperationDomainPropertyInfo where
    type AttrAllowedOps MountOperationDomainPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationDomainPropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationDomainPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint MountOperationDomainPropertyInfo = (~) T.Text
    type AttrTransferType MountOperationDomainPropertyInfo = T.Text
    type AttrGetType MountOperationDomainPropertyInfo = T.Text
    type AttrLabel MountOperationDomainPropertyInfo = "domain"
    type AttrOrigin MountOperationDomainPropertyInfo = MountOperation
    attrGet = getMountOperationDomain
    attrSet = setMountOperationDomain
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationDomain
    attrClear = undefined
#endif

-- VVV Prop "is-tcrypt-hidden-volume"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@is-tcrypt-hidden-volume@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #isTcryptHiddenVolume
-- @
getMountOperationIsTcryptHiddenVolume :: (MonadIO m, IsMountOperation o) => o -> m Bool
getMountOperationIsTcryptHiddenVolume :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Bool
getMountOperationIsTcryptHiddenVolume o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-tcrypt-hidden-volume"

-- | Set the value of the “@is-tcrypt-hidden-volume@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #isTcryptHiddenVolume 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationIsTcryptHiddenVolume :: (MonadIO m, IsMountOperation o) => o -> Bool -> m ()
setMountOperationIsTcryptHiddenVolume :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Bool -> m ()
setMountOperationIsTcryptHiddenVolume o
obj Bool
val = IO () -> m ()
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"is-tcrypt-hidden-volume" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@is-tcrypt-hidden-volume@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationIsTcryptHiddenVolume :: (IsMountOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructMountOperationIsTcryptHiddenVolume :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructMountOperationIsTcryptHiddenVolume Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"is-tcrypt-hidden-volume" Bool
val

#if defined(ENABLE_OVERLOADING)
data MountOperationIsTcryptHiddenVolumePropertyInfo
instance AttrInfo MountOperationIsTcryptHiddenVolumePropertyInfo where
    type AttrAllowedOps MountOperationIsTcryptHiddenVolumePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationIsTcryptHiddenVolumePropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationIsTcryptHiddenVolumePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint MountOperationIsTcryptHiddenVolumePropertyInfo = (~) Bool
    type AttrTransferType MountOperationIsTcryptHiddenVolumePropertyInfo = Bool
    type AttrGetType MountOperationIsTcryptHiddenVolumePropertyInfo = Bool
    type AttrLabel MountOperationIsTcryptHiddenVolumePropertyInfo = "is-tcrypt-hidden-volume"
    type AttrOrigin MountOperationIsTcryptHiddenVolumePropertyInfo = MountOperation
    attrGet = getMountOperationIsTcryptHiddenVolume
    attrSet = setMountOperationIsTcryptHiddenVolume
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationIsTcryptHiddenVolume
    attrClear = undefined
#endif

-- VVV Prop "is-tcrypt-system-volume"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@is-tcrypt-system-volume@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #isTcryptSystemVolume
-- @
getMountOperationIsTcryptSystemVolume :: (MonadIO m, IsMountOperation o) => o -> m Bool
getMountOperationIsTcryptSystemVolume :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Bool
getMountOperationIsTcryptSystemVolume o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-tcrypt-system-volume"

-- | Set the value of the “@is-tcrypt-system-volume@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #isTcryptSystemVolume 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationIsTcryptSystemVolume :: (MonadIO m, IsMountOperation o) => o -> Bool -> m ()
setMountOperationIsTcryptSystemVolume :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Bool -> m ()
setMountOperationIsTcryptSystemVolume o
obj Bool
val = IO () -> m ()
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"is-tcrypt-system-volume" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@is-tcrypt-system-volume@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationIsTcryptSystemVolume :: (IsMountOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructMountOperationIsTcryptSystemVolume :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructMountOperationIsTcryptSystemVolume Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"is-tcrypt-system-volume" Bool
val

#if defined(ENABLE_OVERLOADING)
data MountOperationIsTcryptSystemVolumePropertyInfo
instance AttrInfo MountOperationIsTcryptSystemVolumePropertyInfo where
    type AttrAllowedOps MountOperationIsTcryptSystemVolumePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationIsTcryptSystemVolumePropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationIsTcryptSystemVolumePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint MountOperationIsTcryptSystemVolumePropertyInfo = (~) Bool
    type AttrTransferType MountOperationIsTcryptSystemVolumePropertyInfo = Bool
    type AttrGetType MountOperationIsTcryptSystemVolumePropertyInfo = Bool
    type AttrLabel MountOperationIsTcryptSystemVolumePropertyInfo = "is-tcrypt-system-volume"
    type AttrOrigin MountOperationIsTcryptSystemVolumePropertyInfo = MountOperation
    attrGet = getMountOperationIsTcryptSystemVolume
    attrSet = setMountOperationIsTcryptSystemVolume
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationIsTcryptSystemVolume
    attrClear = undefined
#endif

-- VVV Prop "password"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@password@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #password
-- @
getMountOperationPassword :: (MonadIO m, IsMountOperation o) => o -> m T.Text
getMountOperationPassword :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Text
getMountOperationPassword o
obj = IO Text -> m Text
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
"getMountOperationPassword" (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
"password"

-- | Set the value of the “@password@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #password 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationPassword :: (MonadIO m, IsMountOperation o) => o -> T.Text -> m ()
setMountOperationPassword :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Text -> m ()
setMountOperationPassword o
obj Text
val = IO () -> m ()
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
"password" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@password@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationPassword :: (IsMountOperation o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructMountOperationPassword :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructMountOperationPassword Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"password" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data MountOperationPasswordPropertyInfo
instance AttrInfo MountOperationPasswordPropertyInfo where
    type AttrAllowedOps MountOperationPasswordPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationPasswordPropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationPasswordPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint MountOperationPasswordPropertyInfo = (~) T.Text
    type AttrTransferType MountOperationPasswordPropertyInfo = T.Text
    type AttrGetType MountOperationPasswordPropertyInfo = T.Text
    type AttrLabel MountOperationPasswordPropertyInfo = "password"
    type AttrOrigin MountOperationPasswordPropertyInfo = MountOperation
    attrGet = getMountOperationPassword
    attrSet = setMountOperationPassword
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationPassword
    attrClear = undefined
#endif

-- VVV Prop "password-save"
   -- Type: TInterface (Name {namespace = "Gio", name = "PasswordSave"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@password-save@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #passwordSave
-- @
getMountOperationPasswordSave :: (MonadIO m, IsMountOperation o) => o -> m Gio.Enums.PasswordSave
getMountOperationPasswordSave :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m PasswordSave
getMountOperationPasswordSave o
obj = IO PasswordSave -> m PasswordSave
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PasswordSave -> m PasswordSave)
-> IO PasswordSave -> m PasswordSave
forall a b. (a -> b) -> a -> b
$ o -> String -> IO PasswordSave
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"password-save"

-- | Set the value of the “@password-save@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #passwordSave 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationPasswordSave :: (MonadIO m, IsMountOperation o) => o -> Gio.Enums.PasswordSave -> m ()
setMountOperationPasswordSave :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> PasswordSave -> m ()
setMountOperationPasswordSave o
obj PasswordSave
val = IO () -> m ()
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 -> PasswordSave -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"password-save" PasswordSave
val

-- | Construct a `GValueConstruct` with valid value for the “@password-save@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationPasswordSave :: (IsMountOperation o, MIO.MonadIO m) => Gio.Enums.PasswordSave -> m (GValueConstruct o)
constructMountOperationPasswordSave :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
PasswordSave -> m (GValueConstruct o)
constructMountOperationPasswordSave PasswordSave
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> PasswordSave -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"password-save" PasswordSave
val

#if defined(ENABLE_OVERLOADING)
data MountOperationPasswordSavePropertyInfo
instance AttrInfo MountOperationPasswordSavePropertyInfo where
    type AttrAllowedOps MountOperationPasswordSavePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationPasswordSavePropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationPasswordSavePropertyInfo = (~) Gio.Enums.PasswordSave
    type AttrTransferTypeConstraint MountOperationPasswordSavePropertyInfo = (~) Gio.Enums.PasswordSave
    type AttrTransferType MountOperationPasswordSavePropertyInfo = Gio.Enums.PasswordSave
    type AttrGetType MountOperationPasswordSavePropertyInfo = Gio.Enums.PasswordSave
    type AttrLabel MountOperationPasswordSavePropertyInfo = "password-save"
    type AttrOrigin MountOperationPasswordSavePropertyInfo = MountOperation
    attrGet = getMountOperationPasswordSave
    attrSet = setMountOperationPasswordSave
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationPasswordSave
    attrClear = undefined
#endif

-- VVV Prop "pim"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@pim@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #pim
-- @
getMountOperationPim :: (MonadIO m, IsMountOperation o) => o -> m Word32
getMountOperationPim :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Word32
getMountOperationPim o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"pim"

-- | Set the value of the “@pim@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #pim 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationPim :: (MonadIO m, IsMountOperation o) => o -> Word32 -> m ()
setMountOperationPim :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Word32 -> m ()
setMountOperationPim o
obj Word32
val = IO () -> m ()
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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"pim" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@pim@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationPim :: (IsMountOperation o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructMountOperationPim :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructMountOperationPim Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"pim" Word32
val

#if defined(ENABLE_OVERLOADING)
data MountOperationPimPropertyInfo
instance AttrInfo MountOperationPimPropertyInfo where
    type AttrAllowedOps MountOperationPimPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationPimPropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationPimPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint MountOperationPimPropertyInfo = (~) Word32
    type AttrTransferType MountOperationPimPropertyInfo = Word32
    type AttrGetType MountOperationPimPropertyInfo = Word32
    type AttrLabel MountOperationPimPropertyInfo = "pim"
    type AttrOrigin MountOperationPimPropertyInfo = MountOperation
    attrGet = getMountOperationPim
    attrSet = setMountOperationPim
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationPim
    attrClear = undefined
#endif

-- VVV Prop "username"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@username@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' mountOperation #username
-- @
getMountOperationUsername :: (MonadIO m, IsMountOperation o) => o -> m T.Text
getMountOperationUsername :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> m Text
getMountOperationUsername o
obj = IO Text -> m Text
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
"getMountOperationUsername" (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
"username"

-- | Set the value of the “@username@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' mountOperation [ #username 'Data.GI.Base.Attributes.:=' value ]
-- @
setMountOperationUsername :: (MonadIO m, IsMountOperation o) => o -> T.Text -> m ()
setMountOperationUsername :: forall (m :: * -> *) o.
(MonadIO m, IsMountOperation o) =>
o -> Text -> m ()
setMountOperationUsername o
obj Text
val = IO () -> m ()
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
"username" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@username@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructMountOperationUsername :: (IsMountOperation o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructMountOperationUsername :: forall o (m :: * -> *).
(IsMountOperation o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructMountOperationUsername Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"username" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data MountOperationUsernamePropertyInfo
instance AttrInfo MountOperationUsernamePropertyInfo where
    type AttrAllowedOps MountOperationUsernamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint MountOperationUsernamePropertyInfo = IsMountOperation
    type AttrSetTypeConstraint MountOperationUsernamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint MountOperationUsernamePropertyInfo = (~) T.Text
    type AttrTransferType MountOperationUsernamePropertyInfo = T.Text
    type AttrGetType MountOperationUsernamePropertyInfo = T.Text
    type AttrLabel MountOperationUsernamePropertyInfo = "username"
    type AttrOrigin MountOperationUsernamePropertyInfo = MountOperation
    attrGet = getMountOperationUsername
    attrSet = setMountOperationUsername
    attrTransfer _ v = do
        return v
    attrConstruct = constructMountOperationUsername
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MountOperation
type instance O.AttributeList MountOperation = MountOperationAttributeList
type MountOperationAttributeList = ('[ '("anonymous", MountOperationAnonymousPropertyInfo), '("choice", MountOperationChoicePropertyInfo), '("domain", MountOperationDomainPropertyInfo), '("isTcryptHiddenVolume", MountOperationIsTcryptHiddenVolumePropertyInfo), '("isTcryptSystemVolume", MountOperationIsTcryptSystemVolumePropertyInfo), '("password", MountOperationPasswordPropertyInfo), '("passwordSave", MountOperationPasswordSavePropertyInfo), '("pim", MountOperationPimPropertyInfo), '("username", MountOperationUsernamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
mountOperationAnonymous :: AttrLabelProxy "anonymous"
mountOperationAnonymous = AttrLabelProxy

mountOperationChoice :: AttrLabelProxy "choice"
mountOperationChoice = AttrLabelProxy

mountOperationDomain :: AttrLabelProxy "domain"
mountOperationDomain = AttrLabelProxy

mountOperationIsTcryptHiddenVolume :: AttrLabelProxy "isTcryptHiddenVolume"
mountOperationIsTcryptHiddenVolume = AttrLabelProxy

mountOperationIsTcryptSystemVolume :: AttrLabelProxy "isTcryptSystemVolume"
mountOperationIsTcryptSystemVolume = AttrLabelProxy

mountOperationPassword :: AttrLabelProxy "password"
mountOperationPassword = AttrLabelProxy

mountOperationPasswordSave :: AttrLabelProxy "passwordSave"
mountOperationPasswordSave = AttrLabelProxy

mountOperationPim :: AttrLabelProxy "pim"
mountOperationPim = AttrLabelProxy

mountOperationUsername :: AttrLabelProxy "username"
mountOperationUsername = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList MountOperation = MountOperationSignalList
type MountOperationSignalList = ('[ '("aborted", MountOperationAbortedSignalInfo), '("askPassword", MountOperationAskPasswordSignalInfo), '("askQuestion", MountOperationAskQuestionSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("reply", MountOperationReplySignalInfo), '("showProcesses", MountOperationShowProcessesSignalInfo), '("showUnmountProgress", MountOperationShowUnmountProgressSignalInfo)] :: [(Symbol, *)])

#endif

-- method MountOperation::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "MountOperation" })
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_new" g_mount_operation_new :: 
    IO (Ptr MountOperation)

-- | Creates a new mount operation.
mountOperationNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m MountOperation
    -- ^ __Returns:__ a t'GI.Gio.Objects.MountOperation.MountOperation'.
mountOperationNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m MountOperation
mountOperationNew  = IO MountOperation -> m MountOperation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MountOperation -> m MountOperation)
-> IO MountOperation -> m MountOperation
forall a b. (a -> b) -> a -> b
$ do
    Ptr MountOperation
result <- IO (Ptr MountOperation)
g_mount_operation_new
    Text -> Ptr MountOperation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mountOperationNew" Ptr MountOperation
result
    MountOperation
result' <- ((ManagedPtr MountOperation -> MountOperation)
-> Ptr MountOperation -> IO MountOperation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MountOperation -> MountOperation
MountOperation) Ptr MountOperation
result
    MountOperation -> IO MountOperation
forall (m :: * -> *) a. Monad m => a -> m a
return MountOperation
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MountOperation::get_anonymous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_anonymous" g_mount_operation_get_anonymous :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO CInt

-- | Check to see whether the mount operation is being used
-- for an anonymous user.
mountOperationGetAnonymous ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if mount operation is anonymous.
mountOperationGetAnonymous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Bool
mountOperationGetAnonymous a
op = IO Bool -> m Bool
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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CInt
result <- Ptr MountOperation -> IO CInt
g_mount_operation_get_anonymous Ptr MountOperation
op'
    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
op
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MountOperationGetAnonymousMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetAnonymousMethodInfo a signature where
    overloadedMethod = mountOperationGetAnonymous

instance O.OverloadedMethodInfo MountOperationGetAnonymousMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetAnonymous",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetAnonymous"
        }


#endif

-- method MountOperation::get_choice
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_choice" g_mount_operation_get_choice :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO Int32

-- | Gets a choice from the mount operation.
mountOperationGetChoice ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m Int32
    -- ^ __Returns:__ an integer containing an index of the user\'s choice from
    -- the choice\'s list, or @0@.
mountOperationGetChoice :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Int32
mountOperationGetChoice a
op = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Int32
result <- Ptr MountOperation -> IO Int32
g_mount_operation_get_choice Ptr MountOperation
op'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data MountOperationGetChoiceMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetChoiceMethodInfo a signature where
    overloadedMethod = mountOperationGetChoice

instance O.OverloadedMethodInfo MountOperationGetChoiceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetChoice",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetChoice"
        }


#endif

-- method MountOperation::get_domain
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_domain" g_mount_operation_get_domain :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO CString

-- | Gets the domain of the mount operation.
mountOperationGetDomain ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m T.Text
    -- ^ __Returns:__ a string set to the domain.
mountOperationGetDomain :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Text
mountOperationGetDomain a
op = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
result <- Ptr MountOperation -> IO CString
g_mount_operation_get_domain Ptr MountOperation
op'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mountOperationGetDomain" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MountOperationGetDomainMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetDomainMethodInfo a signature where
    overloadedMethod = mountOperationGetDomain

instance O.OverloadedMethodInfo MountOperationGetDomainMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetDomain",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetDomain"
        }


#endif

-- method MountOperation::get_is_tcrypt_hidden_volume
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_is_tcrypt_hidden_volume" g_mount_operation_get_is_tcrypt_hidden_volume :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO CInt

-- | Check to see whether the mount operation is being used
-- for a TCRYPT hidden volume.
-- 
-- /Since: 2.58/
mountOperationGetIsTcryptHiddenVolume ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if mount operation is for hidden volume.
mountOperationGetIsTcryptHiddenVolume :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Bool
mountOperationGetIsTcryptHiddenVolume a
op = IO Bool -> m Bool
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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CInt
result <- Ptr MountOperation -> IO CInt
g_mount_operation_get_is_tcrypt_hidden_volume Ptr MountOperation
op'
    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
op
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MountOperationGetIsTcryptHiddenVolumeMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetIsTcryptHiddenVolumeMethodInfo a signature where
    overloadedMethod = mountOperationGetIsTcryptHiddenVolume

instance O.OverloadedMethodInfo MountOperationGetIsTcryptHiddenVolumeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetIsTcryptHiddenVolume",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetIsTcryptHiddenVolume"
        }


#endif

-- method MountOperation::get_is_tcrypt_system_volume
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_is_tcrypt_system_volume" g_mount_operation_get_is_tcrypt_system_volume :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO CInt

-- | Check to see whether the mount operation is being used
-- for a TCRYPT system volume.
-- 
-- /Since: 2.58/
mountOperationGetIsTcryptSystemVolume ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if mount operation is for system volume.
mountOperationGetIsTcryptSystemVolume :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Bool
mountOperationGetIsTcryptSystemVolume a
op = IO Bool -> m Bool
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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CInt
result <- Ptr MountOperation -> IO CInt
g_mount_operation_get_is_tcrypt_system_volume Ptr MountOperation
op'
    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
op
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MountOperationGetIsTcryptSystemVolumeMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetIsTcryptSystemVolumeMethodInfo a signature where
    overloadedMethod = mountOperationGetIsTcryptSystemVolume

instance O.OverloadedMethodInfo MountOperationGetIsTcryptSystemVolumeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetIsTcryptSystemVolume",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetIsTcryptSystemVolume"
        }


#endif

-- method MountOperation::get_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_password" g_mount_operation_get_password :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO CString

-- | Gets a password from the mount operation.
mountOperationGetPassword ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m T.Text
    -- ^ __Returns:__ a string containing the password within /@op@/.
mountOperationGetPassword :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Text
mountOperationGetPassword a
op = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
result <- Ptr MountOperation -> IO CString
g_mount_operation_get_password Ptr MountOperation
op'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mountOperationGetPassword" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MountOperationGetPasswordMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetPasswordMethodInfo a signature where
    overloadedMethod = mountOperationGetPassword

instance O.OverloadedMethodInfo MountOperationGetPasswordMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetPassword",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetPassword"
        }


#endif

-- method MountOperation::get_password_save
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "PasswordSave" })
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_password_save" g_mount_operation_get_password_save :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO CUInt

-- | Gets the state of saving passwords for the mount operation.
mountOperationGetPasswordSave ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m Gio.Enums.PasswordSave
    -- ^ __Returns:__ a t'GI.Gio.Enums.PasswordSave' flag.
mountOperationGetPasswordSave :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m PasswordSave
mountOperationGetPasswordSave a
op = IO PasswordSave -> m PasswordSave
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PasswordSave -> m PasswordSave)
-> IO PasswordSave -> m PasswordSave
forall a b. (a -> b) -> a -> b
$ do
    Ptr MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CUInt
result <- Ptr MountOperation -> IO CUInt
g_mount_operation_get_password_save Ptr MountOperation
op'
    let result' :: PasswordSave
result' = (Int -> PasswordSave
forall a. Enum a => Int -> a
toEnum (Int -> PasswordSave) -> (CUInt -> Int) -> CUInt -> PasswordSave
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    PasswordSave -> IO PasswordSave
forall (m :: * -> *) a. Monad m => a -> m a
return PasswordSave
result'

#if defined(ENABLE_OVERLOADING)
data MountOperationGetPasswordSaveMethodInfo
instance (signature ~ (m Gio.Enums.PasswordSave), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetPasswordSaveMethodInfo a signature where
    overloadedMethod = mountOperationGetPasswordSave

instance O.OverloadedMethodInfo MountOperationGetPasswordSaveMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetPasswordSave",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetPasswordSave"
        }


#endif

-- method MountOperation::get_pim
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_pim" g_mount_operation_get_pim :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO Word32

-- | Gets a PIM from the mount operation.
-- 
-- /Since: 2.58/
mountOperationGetPim ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m Word32
    -- ^ __Returns:__ The VeraCrypt PIM within /@op@/.
mountOperationGetPim :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Word32
mountOperationGetPim a
op = IO Word32 -> m Word32
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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Word32
result <- Ptr MountOperation -> IO Word32
g_mount_operation_get_pim Ptr MountOperation
op'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data MountOperationGetPimMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetPimMethodInfo a signature where
    overloadedMethod = mountOperationGetPim

instance O.OverloadedMethodInfo MountOperationGetPimMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetPim",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetPim"
        }


#endif

-- method MountOperation::get_username
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_get_username" g_mount_operation_get_username :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    IO CString

-- | Get the user name from the mount operation.
mountOperationGetUsername ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> m T.Text
    -- ^ __Returns:__ a string containing the user name.
mountOperationGetUsername :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> m Text
mountOperationGetUsername a
op = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
result <- Ptr MountOperation -> IO CString
g_mount_operation_get_username Ptr MountOperation
op'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mountOperationGetUsername" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data MountOperationGetUsernameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationGetUsernameMethodInfo a signature where
    overloadedMethod = mountOperationGetUsername

instance O.OverloadedMethodInfo MountOperationGetUsernameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationGetUsername",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationGetUsername"
        }


#endif

-- method MountOperation::reply
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "MountOperationResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperationResult"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_reply" g_mount_operation_reply :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CUInt ->                                -- result : TInterface (Name {namespace = "Gio", name = "MountOperationResult"})
    IO ()

-- | Emits the [reply]("GI.Gio.Objects.MountOperation#g:signal:reply") signal.
mountOperationReply ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'
    -> Gio.Enums.MountOperationResult
    -- ^ /@result@/: a t'GI.Gio.Enums.MountOperationResult'
    -> m ()
mountOperationReply :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> MountOperationResult -> m ()
mountOperationReply a
op MountOperationResult
result_ = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let result_' :: CUInt
result_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (MountOperationResult -> Int) -> MountOperationResult -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MountOperationResult -> Int
forall a. Enum a => a -> Int
fromEnum) MountOperationResult
result_
    Ptr MountOperation -> CUInt -> IO ()
g_mount_operation_reply Ptr MountOperation
op' CUInt
result_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationReplyMethodInfo
instance (signature ~ (Gio.Enums.MountOperationResult -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationReplyMethodInfo a signature where
    overloadedMethod = mountOperationReply

instance O.OverloadedMethodInfo MountOperationReplyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationReply",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationReply"
        }


#endif

-- method MountOperation::set_anonymous
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "anonymous"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "boolean value." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_anonymous" g_mount_operation_set_anonymous :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CInt ->                                 -- anonymous : TBasicType TBoolean
    IO ()

-- | Sets the mount operation to use an anonymous user if /@anonymous@/ is 'P.True'.
mountOperationSetAnonymous ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> Bool
    -- ^ /@anonymous@/: boolean value.
    -> m ()
mountOperationSetAnonymous :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Bool -> m ()
mountOperationSetAnonymous a
op Bool
anonymous = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let anonymous' :: CInt
anonymous' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
anonymous
    Ptr MountOperation -> CInt -> IO ()
g_mount_operation_set_anonymous Ptr MountOperation
op' CInt
anonymous'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetAnonymousMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetAnonymousMethodInfo a signature where
    overloadedMethod = mountOperationSetAnonymous

instance O.OverloadedMethodInfo MountOperationSetAnonymousMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetAnonymous",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetAnonymous"
        }


#endif

-- method MountOperation::set_choice
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "choice"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an integer." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_choice" g_mount_operation_set_choice :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    Int32 ->                                -- choice : TBasicType TInt
    IO ()

-- | Sets a default choice for the mount operation.
mountOperationSetChoice ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> Int32
    -- ^ /@choice@/: an integer.
    -> m ()
mountOperationSetChoice :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Int32 -> m ()
mountOperationSetChoice a
op Int32
choice = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr MountOperation -> Int32 -> IO ()
g_mount_operation_set_choice Ptr MountOperation
op' Int32
choice
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetChoiceMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetChoiceMethodInfo a signature where
    overloadedMethod = mountOperationSetChoice

instance O.OverloadedMethodInfo MountOperationSetChoiceMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetChoice",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetChoice"
        }


#endif

-- method MountOperation::set_domain
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "domain"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the domain to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_domain" g_mount_operation_set_domain :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CString ->                              -- domain : TBasicType TUTF8
    IO ()

-- | Sets the mount operation\'s domain.
mountOperationSetDomain ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> T.Text
    -- ^ /@domain@/: the domain to set.
    -> m ()
mountOperationSetDomain :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Text -> m ()
mountOperationSetDomain a
op Text
domain = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
domain' <- Text -> IO CString
textToCString Text
domain
    Ptr MountOperation -> CString -> IO ()
g_mount_operation_set_domain Ptr MountOperation
op' CString
domain'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
domain'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetDomainMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetDomainMethodInfo a signature where
    overloadedMethod = mountOperationSetDomain

instance O.OverloadedMethodInfo MountOperationSetDomainMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetDomain",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetDomain"
        }


#endif

-- method MountOperation::set_is_tcrypt_hidden_volume
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "hidden_volume"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "boolean value." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_is_tcrypt_hidden_volume" g_mount_operation_set_is_tcrypt_hidden_volume :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CInt ->                                 -- hidden_volume : TBasicType TBoolean
    IO ()

-- | Sets the mount operation to use a hidden volume if /@hiddenVolume@/ is 'P.True'.
-- 
-- /Since: 2.58/
mountOperationSetIsTcryptHiddenVolume ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> Bool
    -- ^ /@hiddenVolume@/: boolean value.
    -> m ()
mountOperationSetIsTcryptHiddenVolume :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Bool -> m ()
mountOperationSetIsTcryptHiddenVolume a
op Bool
hiddenVolume = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let hiddenVolume' :: CInt
hiddenVolume' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
hiddenVolume
    Ptr MountOperation -> CInt -> IO ()
g_mount_operation_set_is_tcrypt_hidden_volume Ptr MountOperation
op' CInt
hiddenVolume'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetIsTcryptHiddenVolumeMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetIsTcryptHiddenVolumeMethodInfo a signature where
    overloadedMethod = mountOperationSetIsTcryptHiddenVolume

instance O.OverloadedMethodInfo MountOperationSetIsTcryptHiddenVolumeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetIsTcryptHiddenVolume",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetIsTcryptHiddenVolume"
        }


#endif

-- method MountOperation::set_is_tcrypt_system_volume
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "system_volume"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "boolean value." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_is_tcrypt_system_volume" g_mount_operation_set_is_tcrypt_system_volume :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CInt ->                                 -- system_volume : TBasicType TBoolean
    IO ()

-- | Sets the mount operation to use a system volume if /@systemVolume@/ is 'P.True'.
-- 
-- /Since: 2.58/
mountOperationSetIsTcryptSystemVolume ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> Bool
    -- ^ /@systemVolume@/: boolean value.
    -> m ()
mountOperationSetIsTcryptSystemVolume :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Bool -> m ()
mountOperationSetIsTcryptSystemVolume a
op Bool
systemVolume = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let systemVolume' :: CInt
systemVolume' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
systemVolume
    Ptr MountOperation -> CInt -> IO ()
g_mount_operation_set_is_tcrypt_system_volume Ptr MountOperation
op' CInt
systemVolume'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetIsTcryptSystemVolumeMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetIsTcryptSystemVolumeMethodInfo a signature where
    overloadedMethod = mountOperationSetIsTcryptSystemVolume

instance O.OverloadedMethodInfo MountOperationSetIsTcryptSystemVolumeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetIsTcryptSystemVolume",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetIsTcryptSystemVolume"
        }


#endif

-- method MountOperation::set_password
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "password"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "password to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_password" g_mount_operation_set_password :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CString ->                              -- password : TBasicType TUTF8
    IO ()

-- | Sets the mount operation\'s password to /@password@/.
mountOperationSetPassword ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> T.Text
    -- ^ /@password@/: password to set.
    -> m ()
mountOperationSetPassword :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Text -> m ()
mountOperationSetPassword a
op Text
password = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
password' <- Text -> IO CString
textToCString Text
password
    Ptr MountOperation -> CString -> IO ()
g_mount_operation_set_password Ptr MountOperation
op' CString
password'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
password'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetPasswordMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetPasswordMethodInfo a signature where
    overloadedMethod = mountOperationSetPassword

instance O.OverloadedMethodInfo MountOperationSetPasswordMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetPassword",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetPassword"
        }


#endif

-- method MountOperation::set_password_save
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "save"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "PasswordSave" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a set of #GPasswordSave flags."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_password_save" g_mount_operation_set_password_save :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CUInt ->                                -- save : TInterface (Name {namespace = "Gio", name = "PasswordSave"})
    IO ()

-- | Sets the state of saving passwords for the mount operation.
mountOperationSetPasswordSave ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> Gio.Enums.PasswordSave
    -- ^ /@save@/: a set of t'GI.Gio.Enums.PasswordSave' flags.
    -> m ()
mountOperationSetPasswordSave :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> PasswordSave -> m ()
mountOperationSetPasswordSave a
op PasswordSave
save = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let save' :: CUInt
save' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PasswordSave -> Int) -> PasswordSave -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PasswordSave -> Int
forall a. Enum a => a -> Int
fromEnum) PasswordSave
save
    Ptr MountOperation -> CUInt -> IO ()
g_mount_operation_set_password_save Ptr MountOperation
op' CUInt
save'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetPasswordSaveMethodInfo
instance (signature ~ (Gio.Enums.PasswordSave -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetPasswordSaveMethodInfo a signature where
    overloadedMethod = mountOperationSetPasswordSave

instance O.OverloadedMethodInfo MountOperationSetPasswordSaveMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetPasswordSave",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetPasswordSave"
        }


#endif

-- method MountOperation::set_pim
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pim"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an unsigned integer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_pim" g_mount_operation_set_pim :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    Word32 ->                               -- pim : TBasicType TUInt
    IO ()

-- | Sets the mount operation\'s PIM to /@pim@/.
-- 
-- /Since: 2.58/
mountOperationSetPim ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> Word32
    -- ^ /@pim@/: an unsigned integer.
    -> m ()
mountOperationSetPim :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Word32 -> m ()
mountOperationSetPim a
op Word32
pim = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr MountOperation -> Word32 -> IO ()
g_mount_operation_set_pim Ptr MountOperation
op' Word32
pim
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetPimMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetPimMethodInfo a signature where
    overloadedMethod = mountOperationSetPim

instance O.OverloadedMethodInfo MountOperationSetPimMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetPim",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetPim"
        }


#endif

-- method MountOperation::set_username
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "op"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "MountOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GMountOperation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "username"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "input username." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mount_operation_set_username" g_mount_operation_set_username :: 
    Ptr MountOperation ->                   -- op : TInterface (Name {namespace = "Gio", name = "MountOperation"})
    CString ->                              -- username : TBasicType TUTF8
    IO ()

-- | Sets the user name within /@op@/ to /@username@/.
mountOperationSetUsername ::
    (B.CallStack.HasCallStack, MonadIO m, IsMountOperation a) =>
    a
    -- ^ /@op@/: a t'GI.Gio.Objects.MountOperation.MountOperation'.
    -> T.Text
    -- ^ /@username@/: input username.
    -> m ()
mountOperationSetUsername :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsMountOperation a) =>
a -> Text -> m ()
mountOperationSetUsername a
op Text
username = 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 MountOperation
op' <- a -> IO (Ptr MountOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
username' <- Text -> IO CString
textToCString Text
username
    Ptr MountOperation -> CString -> IO ()
g_mount_operation_set_username Ptr MountOperation
op' CString
username'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
username'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MountOperationSetUsernameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMountOperation a) => O.OverloadedMethod MountOperationSetUsernameMethodInfo a signature where
    overloadedMethod = mountOperationSetUsername

instance O.OverloadedMethodInfo MountOperationSetUsernameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.MountOperation.mountOperationSetUsername",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-MountOperation.html#v:mountOperationSetUsername"
        }


#endif