{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.OSTree.Objects.SePolicy
    ( 

-- * Exported types
    SePolicy(..)                            ,
    IsSePolicy                              ,
    toSePolicy                              ,


 -- * 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"), [init]("GI.Gio.Interfaces.Initable#g:method:init"), [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"), [restorecon]("GI.OSTree.Objects.SePolicy#g:method:restorecon"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [setfscreatecon]("GI.OSTree.Objects.SePolicy#g:method:setfscreatecon"), [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
-- [getCsum]("GI.OSTree.Objects.SePolicy#g:method:getCsum"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getLabel]("GI.OSTree.Objects.SePolicy#g:method:getLabel"), [getName]("GI.OSTree.Objects.SePolicy#g:method:getName"), [getPath]("GI.OSTree.Objects.SePolicy#g:method:getPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveSePolicyMethod                   ,
#endif

-- ** fscreateconCleanup #method:fscreateconCleanup#

    sePolicyFscreateconCleanup              ,


-- ** getCsum #method:getCsum#

#if defined(ENABLE_OVERLOADING)
    SePolicyGetCsumMethodInfo               ,
#endif
    sePolicyGetCsum                         ,


-- ** getLabel #method:getLabel#

#if defined(ENABLE_OVERLOADING)
    SePolicyGetLabelMethodInfo              ,
#endif
    sePolicyGetLabel                        ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    SePolicyGetNameMethodInfo               ,
#endif
    sePolicyGetName                         ,


-- ** getPath #method:getPath#

#if defined(ENABLE_OVERLOADING)
    SePolicyGetPathMethodInfo               ,
#endif
    sePolicyGetPath                         ,


-- ** new #method:new#

    sePolicyNew                             ,


-- ** newAt #method:newAt#

    sePolicyNewAt                           ,


-- ** newFromCommit #method:newFromCommit#

    sePolicyNewFromCommit                   ,


-- ** restorecon #method:restorecon#

#if defined(ENABLE_OVERLOADING)
    SePolicyRestoreconMethodInfo            ,
#endif
    sePolicyRestorecon                      ,


-- ** setfscreatecon #method:setfscreatecon#

#if defined(ENABLE_OVERLOADING)
    SePolicySetfscreateconMethodInfo        ,
#endif
    sePolicySetfscreatecon                  ,




 -- * Properties


-- ** path #attr:path#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SePolicyPathPropertyInfo                ,
#endif
    constructSePolicyPath                   ,
    getSePolicyPath                         ,
#if defined(ENABLE_OVERLOADING)
    sePolicyPath                            ,
#endif


-- ** rootfsDfd #attr:rootfsDfd#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SePolicyRootfsDfdPropertyInfo           ,
#endif
    constructSePolicyRootfsDfd              ,
    getSePolicyRootfsDfd                    ,
#if defined(ENABLE_OVERLOADING)
    sePolicyRootfsDfd                       ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.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 qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
import {-# SOURCE #-} qualified GI.OSTree.Flags as OSTree.Flags
import {-# SOURCE #-} qualified GI.OSTree.Objects.Repo as OSTree.Repo

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

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

foreign import ccall "ostree_sepolicy_get_type"
    c_ostree_sepolicy_get_type :: IO B.Types.GType

instance B.Types.TypedObject SePolicy where
    glibType :: IO GType
glibType = IO GType
c_ostree_sepolicy_get_type

instance B.Types.GObject SePolicy

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

instance O.HasParentTypes SePolicy
type instance O.ParentTypes SePolicy = '[GObject.Object.Object, Gio.Initable.Initable]

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

-- | Convert 'SePolicy' 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 SePolicy) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ostree_sepolicy_get_type
    gvalueSet_ :: Ptr GValue -> Maybe SePolicy -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SePolicy
P.Nothing = Ptr GValue -> Ptr SePolicy -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SePolicy
forall a. Ptr a
FP.nullPtr :: FP.Ptr SePolicy)
    gvalueSet_ Ptr GValue
gv (P.Just SePolicy
obj) = SePolicy -> (Ptr SePolicy -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SePolicy
obj (Ptr GValue -> Ptr SePolicy -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe SePolicy)
gvalueGet_ Ptr GValue
gv = do
        Ptr SePolicy
ptr <- Ptr GValue -> IO (Ptr SePolicy)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SePolicy)
        if Ptr SePolicy
ptr Ptr SePolicy -> Ptr SePolicy -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SePolicy
forall a. Ptr a
FP.nullPtr
        then SePolicy -> Maybe SePolicy
forall a. a -> Maybe a
P.Just (SePolicy -> Maybe SePolicy) -> IO SePolicy -> IO (Maybe SePolicy)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr SePolicy -> SePolicy) -> Ptr SePolicy -> IO SePolicy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SePolicy -> SePolicy
SePolicy Ptr SePolicy
ptr
        else Maybe SePolicy -> IO (Maybe SePolicy)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SePolicy
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveSePolicyMethod (t :: Symbol) (o :: *) :: * where
    ResolveSePolicyMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSePolicyMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSePolicyMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSePolicyMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSePolicyMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSePolicyMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveSePolicyMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSePolicyMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSePolicyMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSePolicyMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSePolicyMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSePolicyMethod "restorecon" o = SePolicyRestoreconMethodInfo
    ResolveSePolicyMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSePolicyMethod "setfscreatecon" o = SePolicySetfscreateconMethodInfo
    ResolveSePolicyMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSePolicyMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSePolicyMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSePolicyMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSePolicyMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSePolicyMethod "getCsum" o = SePolicyGetCsumMethodInfo
    ResolveSePolicyMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSePolicyMethod "getLabel" o = SePolicyGetLabelMethodInfo
    ResolveSePolicyMethod "getName" o = SePolicyGetNameMethodInfo
    ResolveSePolicyMethod "getPath" o = SePolicyGetPathMethodInfo
    ResolveSePolicyMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSePolicyMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSePolicyMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSePolicyMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSePolicyMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSePolicyMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "path"
   -- Type: TInterface (Name {namespace = "Gio", name = "File"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@path@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' sePolicy #path
-- @
getSePolicyPath :: (MonadIO m, IsSePolicy o) => o -> m Gio.File.File
getSePolicyPath :: forall (m :: * -> *) o. (MonadIO m, IsSePolicy o) => o -> m File
getSePolicyPath o
obj = IO File -> m File
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe File) -> IO File
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getSePolicyPath" (IO (Maybe File) -> IO File) -> IO (Maybe File) -> IO File
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr File -> File) -> IO (Maybe File)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"path" ManagedPtr File -> File
Gio.File.File

-- | Construct a `GValueConstruct` with valid value for the “@path@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSePolicyPath :: (IsSePolicy o, MIO.MonadIO m, Gio.File.IsFile a) => a -> m (GValueConstruct o)
constructSePolicyPath :: forall o (m :: * -> *) a.
(IsSePolicy o, MonadIO m, IsFile a) =>
a -> m (GValueConstruct o)
constructSePolicyPath a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"path" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data SePolicyPathPropertyInfo
instance AttrInfo SePolicyPathPropertyInfo where
    type AttrAllowedOps SePolicyPathPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SePolicyPathPropertyInfo = IsSePolicy
    type AttrSetTypeConstraint SePolicyPathPropertyInfo = Gio.File.IsFile
    type AttrTransferTypeConstraint SePolicyPathPropertyInfo = Gio.File.IsFile
    type AttrTransferType SePolicyPathPropertyInfo = Gio.File.File
    type AttrGetType SePolicyPathPropertyInfo = Gio.File.File
    type AttrLabel SePolicyPathPropertyInfo = "path"
    type AttrOrigin SePolicyPathPropertyInfo = SePolicy
    attrGet = getSePolicyPath
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.File.File v
    attrConstruct = constructSePolicyPath
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.path"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#g:attr:path"
        })
#endif

-- VVV Prop "rootfs-dfd"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@rootfs-dfd@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' sePolicy #rootfsDfd
-- @
getSePolicyRootfsDfd :: (MonadIO m, IsSePolicy o) => o -> m Int32
getSePolicyRootfsDfd :: forall (m :: * -> *) o. (MonadIO m, IsSePolicy o) => o -> m Int32
getSePolicyRootfsDfd 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
"rootfs-dfd"

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

#if defined(ENABLE_OVERLOADING)
data SePolicyRootfsDfdPropertyInfo
instance AttrInfo SePolicyRootfsDfdPropertyInfo where
    type AttrAllowedOps SePolicyRootfsDfdPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SePolicyRootfsDfdPropertyInfo = IsSePolicy
    type AttrSetTypeConstraint SePolicyRootfsDfdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SePolicyRootfsDfdPropertyInfo = (~) Int32
    type AttrTransferType SePolicyRootfsDfdPropertyInfo = Int32
    type AttrGetType SePolicyRootfsDfdPropertyInfo = Int32
    type AttrLabel SePolicyRootfsDfdPropertyInfo = "rootfs-dfd"
    type AttrOrigin SePolicyRootfsDfdPropertyInfo = SePolicy
    attrGet = getSePolicyRootfsDfd
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSePolicyRootfsDfd
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.rootfsDfd"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#g:attr:rootfsDfd"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SePolicy
type instance O.AttributeList SePolicy = SePolicyAttributeList
type SePolicyAttributeList = ('[ '("path", SePolicyPathPropertyInfo), '("rootfsDfd", SePolicyRootfsDfdPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
sePolicyPath :: AttrLabelProxy "path"
sePolicyPath = AttrLabelProxy

sePolicyRootfsDfd :: AttrLabelProxy "rootfsDfd"
sePolicyRootfsDfd = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SePolicy = SePolicySignalList
type SePolicySignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method SePolicy::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "path"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Path to a root directory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "OSTree" , name = "SePolicy" })
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sepolicy_new" ostree_sepolicy_new :: 
    Ptr Gio.File.File ->                    -- path : TInterface (Name {namespace = "Gio", name = "File"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SePolicy)

-- | /No description available in the introspection data./
sePolicyNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.File.IsFile a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@path@/: Path to a root directory
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m SePolicy
    -- ^ __Returns:__ An accessor object for SELinux policy in root located at /@path@/ /(Can throw 'Data.GI.Base.GError.GError')/
sePolicyNew :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFile a, IsCancellable b) =>
a -> Maybe b -> m SePolicy
sePolicyNew a
path Maybe b
cancellable = IO SePolicy -> m SePolicy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SePolicy -> m SePolicy) -> IO SePolicy -> m SePolicy
forall a b. (a -> b) -> a -> b
$ do
    Ptr File
path' <- a -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
path
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO SePolicy -> IO () -> IO SePolicy
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr SePolicy
result <- (Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy))
-> (Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy)
forall a b. (a -> b) -> a -> b
$ Ptr File
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr SePolicy)
ostree_sepolicy_new Ptr File
path' Ptr Cancellable
maybeCancellable
        Text -> Ptr SePolicy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sePolicyNew" Ptr SePolicy
result
        SePolicy
result' <- ((ManagedPtr SePolicy -> SePolicy) -> Ptr SePolicy -> IO SePolicy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SePolicy -> SePolicy
SePolicy) Ptr SePolicy
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
path
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        SePolicy -> IO SePolicy
forall (m :: * -> *) a. Monad m => a -> m a
return SePolicy
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method SePolicy::new_at
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "rootfs_dfd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Directory fd for rootfs (will not be cloned)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "OSTree" , name = "SePolicy" })
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sepolicy_new_at" ostree_sepolicy_new_at :: 
    Int32 ->                                -- rootfs_dfd : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SePolicy)

-- | /No description available in the introspection data./
-- 
-- /Since: 2017.4/
sePolicyNewAt ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    Int32
    -- ^ /@rootfsDfd@/: Directory fd for rootfs (will not be cloned)
    -> Maybe (a)
    -- ^ /@cancellable@/: Cancellable
    -> m SePolicy
    -- ^ __Returns:__ An accessor object for SELinux policy in root located at /@rootfsDfd@/ /(Can throw 'Data.GI.Base.GError.GError')/
sePolicyNewAt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCancellable a) =>
Int32 -> Maybe a -> m SePolicy
sePolicyNewAt Int32
rootfsDfd Maybe a
cancellable = IO SePolicy -> m SePolicy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SePolicy -> m SePolicy) -> IO SePolicy -> m SePolicy
forall a b. (a -> b) -> a -> b
$ do
    Ptr Cancellable
maybeCancellable <- case Maybe a
cancellable of
        Maybe a
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just a
jCancellable -> do
            Ptr Cancellable
jCancellable' <- a -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO SePolicy -> IO () -> IO SePolicy
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr SePolicy
result <- (Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy))
-> (Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy)
forall a b. (a -> b) -> a -> b
$ Int32 -> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr SePolicy)
ostree_sepolicy_new_at Int32
rootfsDfd Ptr Cancellable
maybeCancellable
        Text -> Ptr SePolicy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sePolicyNewAt" Ptr SePolicy
result
        SePolicy
result' <- ((ManagedPtr SePolicy -> SePolicy) -> Ptr SePolicy -> IO SePolicy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SePolicy -> SePolicy
SePolicy) Ptr SePolicy
result
        Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
cancellable a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        SePolicy -> IO SePolicy
forall (m :: * -> *) a. Monad m => a -> m a
return SePolicy
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method SePolicy::new_from_commit
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "repo"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "Repo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The repo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rev"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "ostree ref or checksum"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "OSTree" , name = "SePolicy" })
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sepolicy_new_from_commit" ostree_sepolicy_new_from_commit :: 
    Ptr OSTree.Repo.Repo ->                 -- repo : TInterface (Name {namespace = "OSTree", name = "Repo"})
    CString ->                              -- rev : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SePolicy)

-- | Extract the SELinux policy from a commit object via a partial checkout.  This is useful
-- for labeling derived content as separate commits.
-- 
-- This function is the backend of @ostree_repo_commit_modifier_set_sepolicy_from_commit()@.
sePolicyNewFromCommit ::
    (B.CallStack.HasCallStack, MonadIO m, OSTree.Repo.IsRepo a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@repo@/: The repo
    -> T.Text
    -- ^ /@rev@/: ostree ref or checksum
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m SePolicy
    -- ^ __Returns:__ A new policy /(Can throw 'Data.GI.Base.GError.GError')/
sePolicyNewFromCommit :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRepo a, IsCancellable b) =>
a -> Text -> Maybe b -> m SePolicy
sePolicyNewFromCommit a
repo Text
rev Maybe b
cancellable = IO SePolicy -> m SePolicy
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SePolicy -> m SePolicy) -> IO SePolicy -> m SePolicy
forall a b. (a -> b) -> a -> b
$ do
    Ptr Repo
repo' <- a -> IO (Ptr Repo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repo
    CString
rev' <- Text -> IO CString
textToCString Text
rev
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO SePolicy -> IO () -> IO SePolicy
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr SePolicy
result <- (Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy))
-> (Ptr (Ptr GError) -> IO (Ptr SePolicy)) -> IO (Ptr SePolicy)
forall a b. (a -> b) -> a -> b
$ Ptr Repo
-> CString
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr SePolicy)
ostree_sepolicy_new_from_commit Ptr Repo
repo' CString
rev' Ptr Cancellable
maybeCancellable
        Text -> Ptr SePolicy -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sePolicyNewFromCommit" Ptr SePolicy
result
        SePolicy
result' <- ((ManagedPtr SePolicy -> SePolicy) -> Ptr SePolicy -> IO SePolicy
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SePolicy -> SePolicy
SePolicy) Ptr SePolicy
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repo
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
rev'
        SePolicy -> IO SePolicy
forall (m :: * -> *) a. Monad m => a -> m a
return SePolicy
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
rev'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method SePolicy::get_csum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SePolicy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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 "ostree_sepolicy_get_csum" ostree_sepolicy_get_csum :: 
    Ptr SePolicy ->                         -- self : TInterface (Name {namespace = "OSTree", name = "SePolicy"})
    IO CString

-- | /No description available in the introspection data./
-- 
-- /Since: 2016.5/
sePolicyGetCsum ::
    (B.CallStack.HasCallStack, MonadIO m, IsSePolicy a) =>
    a
    -> m T.Text
    -- ^ __Returns:__ Checksum of current policy
sePolicyGetCsum :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSePolicy a) =>
a -> m Text
sePolicyGetCsum a
self = 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 SePolicy
self' <- a -> IO (Ptr SePolicy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr SePolicy -> IO CString
ostree_sepolicy_get_csum Ptr SePolicy
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sePolicyGetCsum" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SePolicyGetCsumMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSePolicy a) => O.OverloadedMethod SePolicyGetCsumMethodInfo a signature where
    overloadedMethod = sePolicyGetCsum

instance O.OverloadedMethodInfo SePolicyGetCsumMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.sePolicyGetCsum",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#v:sePolicyGetCsum"
        })


#endif

-- method SePolicy::get_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SePolicy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Self" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relpath"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Path" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unix_mode"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Unix mode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for security context"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sepolicy_get_label" ostree_sepolicy_get_label :: 
    Ptr SePolicy ->                         -- self : TInterface (Name {namespace = "OSTree", name = "SePolicy"})
    CString ->                              -- relpath : TBasicType TUTF8
    Word32 ->                               -- unix_mode : TBasicType TUInt32
    Ptr CString ->                          -- out_label : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Store in /@outLabel@/ the security context for the given /@relpath@/ and
-- mode /@unixMode@/.  If the policy does not specify a label, 'P.Nothing'
-- will be returned.
sePolicyGetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsSePolicy a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@self@/: Self
    -> T.Text
    -- ^ /@relpath@/: Path
    -> Word32
    -- ^ /@unixMode@/: Unix mode
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m (T.Text)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sePolicyGetLabel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSePolicy a, IsCancellable b) =>
a -> Text -> Word32 -> Maybe b -> m Text
sePolicyGetLabel a
self Text
relpath Word32
unixMode Maybe b
cancellable = 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 SePolicy
self' <- a -> IO (Ptr SePolicy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
relpath' <- Text -> IO CString
textToCString Text
relpath
    Ptr CString
outLabel <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr SePolicy
-> CString
-> Word32
-> Ptr CString
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
ostree_sepolicy_get_label Ptr SePolicy
self' CString
relpath' Word32
unixMode Ptr CString
outLabel Ptr Cancellable
maybeCancellable
        CString
outLabel' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
outLabel
        Text
outLabel'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
outLabel'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
outLabel'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
relpath'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
outLabel
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
outLabel''
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
relpath'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
outLabel
     )

#if defined(ENABLE_OVERLOADING)
data SePolicyGetLabelMethodInfo
instance (signature ~ (T.Text -> Word32 -> Maybe (b) -> m (T.Text)), MonadIO m, IsSePolicy a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod SePolicyGetLabelMethodInfo a signature where
    overloadedMethod = sePolicyGetLabel

instance O.OverloadedMethodInfo SePolicyGetLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.sePolicyGetLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#v:sePolicyGetLabel"
        })


#endif

-- method SePolicy::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SePolicy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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 "ostree_sepolicy_get_name" ostree_sepolicy_get_name :: 
    Ptr SePolicy ->                         -- self : TInterface (Name {namespace = "OSTree", name = "SePolicy"})
    IO CString

-- | /No description available in the introspection data./
sePolicyGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsSePolicy a) =>
    a
    -> m T.Text
    -- ^ __Returns:__ Type of current policy
sePolicyGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSePolicy a) =>
a -> m Text
sePolicyGetName a
self = 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 SePolicy
self' <- a -> IO (Ptr SePolicy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr SePolicy -> IO CString
ostree_sepolicy_get_name Ptr SePolicy
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sePolicyGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data SePolicyGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSePolicy a) => O.OverloadedMethod SePolicyGetNameMethodInfo a signature where
    overloadedMethod = sePolicyGetName

instance O.OverloadedMethodInfo SePolicyGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.sePolicyGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#v:sePolicyGetName"
        })


#endif

-- method SePolicy::get_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SePolicy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A SePolicy object" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "File" })
-- throws : False
-- Skip return : False

foreign import ccall "ostree_sepolicy_get_path" ostree_sepolicy_get_path :: 
    Ptr SePolicy ->                         -- self : TInterface (Name {namespace = "OSTree", name = "SePolicy"})
    IO (Ptr Gio.File.File)

-- | This API should be considered deprecated, because it\'s supported for
-- policy objects to be created from file-descriptor relative paths, which
-- may not be globally accessible.
sePolicyGetPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsSePolicy a) =>
    a
    -- ^ /@self@/: A SePolicy object
    -> m Gio.File.File
    -- ^ __Returns:__ Path to rootfs
sePolicyGetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSePolicy a) =>
a -> m File
sePolicyGetPath a
self = IO File -> m File
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ do
    Ptr SePolicy
self' <- a -> IO (Ptr SePolicy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr File
result <- Ptr SePolicy -> IO (Ptr File)
ostree_sepolicy_get_path Ptr SePolicy
self'
    Text -> Ptr File -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sePolicyGetPath" Ptr File
result
    File
result' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr File -> File
Gio.File.File) Ptr File
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    File -> IO File
forall (m :: * -> *) a. Monad m => a -> m a
return File
result'

#if defined(ENABLE_OVERLOADING)
data SePolicyGetPathMethodInfo
instance (signature ~ (m Gio.File.File), MonadIO m, IsSePolicy a) => O.OverloadedMethod SePolicyGetPathMethodInfo a signature where
    overloadedMethod = sePolicyGetPath

instance O.OverloadedMethodInfo SePolicyGetPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.sePolicyGetPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#v:sePolicyGetPath"
        })


#endif

-- method SePolicy::restorecon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SePolicy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Self" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Path string to use for policy lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "File attributes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Physical path to target file"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "SePolicyRestoreconFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags controlling behavior"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_new_label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "New label, or %NULL if unchanged"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sepolicy_restorecon" ostree_sepolicy_restorecon :: 
    Ptr SePolicy ->                         -- self : TInterface (Name {namespace = "OSTree", name = "SePolicy"})
    CString ->                              -- path : TBasicType TUTF8
    Ptr Gio.FileInfo.FileInfo ->            -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr Gio.File.File ->                    -- target : TInterface (Name {namespace = "Gio", name = "File"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "OSTree", name = "SePolicyRestoreconFlags"})
    Ptr CString ->                          -- out_new_label : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Reset the security context of /@target@/ based on the SELinux policy.
sePolicyRestorecon ::
    (B.CallStack.HasCallStack, MonadIO m, IsSePolicy a, Gio.FileInfo.IsFileInfo b, Gio.File.IsFile c, Gio.Cancellable.IsCancellable d) =>
    a
    -- ^ /@self@/: Self
    -> T.Text
    -- ^ /@path@/: Path string to use for policy lookup
    -> Maybe (b)
    -- ^ /@info@/: File attributes
    -> c
    -- ^ /@target@/: Physical path to target file
    -> [OSTree.Flags.SePolicyRestoreconFlags]
    -- ^ /@flags@/: Flags controlling behavior
    -> Maybe (d)
    -- ^ /@cancellable@/: Cancellable
    -> m (T.Text)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sePolicyRestorecon :: forall (m :: * -> *) a b c d.
(HasCallStack, MonadIO m, IsSePolicy a, IsFileInfo b, IsFile c,
 IsCancellable d) =>
a
-> Text
-> Maybe b
-> c
-> [SePolicyRestoreconFlags]
-> Maybe d
-> m Text
sePolicyRestorecon a
self Text
path Maybe b
info c
target [SePolicyRestoreconFlags]
flags Maybe d
cancellable = 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 SePolicy
self' <- a -> IO (Ptr SePolicy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr FileInfo
maybeInfo <- case Maybe b
info of
        Maybe b
Nothing -> Ptr FileInfo -> IO (Ptr FileInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileInfo
forall a. Ptr a
nullPtr
        Just b
jInfo -> do
            Ptr FileInfo
jInfo' <- b -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jInfo
            Ptr FileInfo -> IO (Ptr FileInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileInfo
jInfo'
    Ptr File
target' <- c -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
target
    let flags' :: CUInt
flags' = [SePolicyRestoreconFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SePolicyRestoreconFlags]
flags
    Ptr CString
outNewLabel <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    Ptr Cancellable
maybeCancellable <- case Maybe d
cancellable of
        Maybe d
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just d
jCancellable -> do
            Ptr Cancellable
jCancellable' <- d -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr SePolicy
-> CString
-> Ptr FileInfo
-> Ptr File
-> CUInt
-> Ptr CString
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
ostree_sepolicy_restorecon Ptr SePolicy
self' CString
path' Ptr FileInfo
maybeInfo Ptr File
target' CUInt
flags' Ptr CString
outNewLabel Ptr Cancellable
maybeCancellable
        CString
outNewLabel' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
outNewLabel
        Text
outNewLabel'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
outNewLabel'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
outNewLabel'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
info b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
target
        Maybe d -> (d -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe d
cancellable d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
outNewLabel
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
outNewLabel''
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
outNewLabel
     )

#if defined(ENABLE_OVERLOADING)
data SePolicyRestoreconMethodInfo
instance (signature ~ (T.Text -> Maybe (b) -> c -> [OSTree.Flags.SePolicyRestoreconFlags] -> Maybe (d) -> m (T.Text)), MonadIO m, IsSePolicy a, Gio.FileInfo.IsFileInfo b, Gio.File.IsFile c, Gio.Cancellable.IsCancellable d) => O.OverloadedMethod SePolicyRestoreconMethodInfo a signature where
    overloadedMethod = sePolicyRestorecon

instance O.OverloadedMethodInfo SePolicyRestoreconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.sePolicyRestorecon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#v:sePolicyRestorecon"
        })


#endif

-- method SePolicy::setfscreatecon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SePolicy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Policy" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Use this path to determine a label"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Used along with @path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sepolicy_setfscreatecon" ostree_sepolicy_setfscreatecon :: 
    Ptr SePolicy ->                         -- self : TInterface (Name {namespace = "OSTree", name = "SePolicy"})
    CString ->                              -- path : TBasicType TUTF8
    Word32 ->                               -- mode : TBasicType TUInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
sePolicySetfscreatecon ::
    (B.CallStack.HasCallStack, MonadIO m, IsSePolicy a) =>
    a
    -- ^ /@self@/: Policy
    -> T.Text
    -- ^ /@path@/: Use this path to determine a label
    -> Word32
    -- ^ /@mode@/: Used along with /@path@/
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sePolicySetfscreatecon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSePolicy a) =>
a -> Text -> Word32 -> m ()
sePolicySetfscreatecon a
self Text
path Word32
mode = 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 SePolicy
self' <- a -> IO (Ptr SePolicy)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
path' <- Text -> IO CString
textToCString Text
path
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr SePolicy -> CString -> Word32 -> Ptr (Ptr GError) -> IO CInt
ostree_sepolicy_setfscreatecon Ptr SePolicy
self' CString
path' Word32
mode
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
     )

#if defined(ENABLE_OVERLOADING)
data SePolicySetfscreateconMethodInfo
instance (signature ~ (T.Text -> Word32 -> m ()), MonadIO m, IsSePolicy a) => O.OverloadedMethod SePolicySetfscreateconMethodInfo a signature where
    overloadedMethod = sePolicySetfscreatecon

instance O.OverloadedMethodInfo SePolicySetfscreateconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Objects.SePolicy.sePolicySetfscreatecon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Objects-SePolicy.html#v:sePolicySetfscreatecon"
        })


#endif

-- method SePolicy::fscreatecon_cleanup
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "unused"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Not used, just in case you didn't infer that from the parameter name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ostree_sepolicy_fscreatecon_cleanup" ostree_sepolicy_fscreatecon_cleanup :: 
    Ptr () ->                               -- unused : TBasicType TPtr
    IO ()

-- | Cleanup function for 'GI.OSTree.Objects.SePolicy.sePolicySetfscreatecon'.
sePolicyFscreateconCleanup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Ptr ()
    -- ^ /@unused@/: Not used, just in case you didn\'t infer that from the parameter name
    -> m ()
sePolicyFscreateconCleanup :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Ptr () -> m ()
sePolicyFscreateconCleanup Ptr ()
unused = 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 () -> IO ()
ostree_sepolicy_fscreatecon_cleanup Ptr ()
unused
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif