{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.FileAttributeMatcher
(
FileAttributeMatcher(..) ,
noFileAttributeMatcher ,
#if defined(ENABLE_OVERLOADING)
ResolveFileAttributeMatcherMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherEnumerateNamespaceMethodInfo,
#endif
fileAttributeMatcherEnumerateNamespace ,
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherEnumerateNextMethodInfo,
#endif
fileAttributeMatcherEnumerateNext ,
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherMatchesMethodInfo ,
#endif
fileAttributeMatcherMatches ,
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherMatchesOnlyMethodInfo,
#endif
fileAttributeMatcherMatchesOnly ,
fileAttributeMatcherNew ,
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherRefMethodInfo ,
#endif
fileAttributeMatcherRef ,
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherSubtractMethodInfo ,
#endif
fileAttributeMatcherSubtract ,
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherToStringMethodInfo ,
#endif
fileAttributeMatcherToString ,
#if defined(ENABLE_OVERLOADING)
FileAttributeMatcherUnrefMethodInfo ,
#endif
fileAttributeMatcherUnref ,
) 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.ManagedPtr as B.ManagedPtr
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 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
newtype FileAttributeMatcher = FileAttributeMatcher (ManagedPtr FileAttributeMatcher)
deriving (FileAttributeMatcher -> FileAttributeMatcher -> Bool
(FileAttributeMatcher -> FileAttributeMatcher -> Bool)
-> (FileAttributeMatcher -> FileAttributeMatcher -> Bool)
-> Eq FileAttributeMatcher
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
$c/= :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
== :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
$c== :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
Eq)
foreign import ccall "g_file_attribute_matcher_get_type" c_g_file_attribute_matcher_get_type ::
IO GType
instance BoxedObject FileAttributeMatcher where
boxedType :: FileAttributeMatcher -> IO GType
boxedType _ = IO GType
c_g_file_attribute_matcher_get_type
instance B.GValue.IsGValue FileAttributeMatcher where
toGValue :: FileAttributeMatcher -> IO GValue
toGValue o :: FileAttributeMatcher
o = do
GType
gtype <- IO GType
c_g_file_attribute_matcher_get_type
FileAttributeMatcher
-> (Ptr FileAttributeMatcher -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileAttributeMatcher
o (GType
-> (GValue -> Ptr FileAttributeMatcher -> IO ())
-> Ptr FileAttributeMatcher
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr FileAttributeMatcher -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO FileAttributeMatcher
fromGValue gv :: GValue
gv = do
Ptr FileAttributeMatcher
ptr <- GValue -> IO (Ptr FileAttributeMatcher)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr FileAttributeMatcher)
(ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr FileAttributeMatcher -> FileAttributeMatcher
FileAttributeMatcher Ptr FileAttributeMatcher
ptr
noFileAttributeMatcher :: Maybe FileAttributeMatcher
noFileAttributeMatcher :: Maybe FileAttributeMatcher
noFileAttributeMatcher = Maybe FileAttributeMatcher
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileAttributeMatcher
type instance O.AttributeList FileAttributeMatcher = FileAttributeMatcherAttributeList
type FileAttributeMatcherAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_file_attribute_matcher_new" g_file_attribute_matcher_new ::
CString ->
IO (Ptr FileAttributeMatcher)
fileAttributeMatcherNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m FileAttributeMatcher
fileAttributeMatcherNew :: Text -> m FileAttributeMatcher
fileAttributeMatcherNew attributes :: Text
attributes = IO FileAttributeMatcher -> m FileAttributeMatcher
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileAttributeMatcher -> m FileAttributeMatcher)
-> IO FileAttributeMatcher -> m FileAttributeMatcher
forall a b. (a -> b) -> a -> b
$ do
CString
attributes' <- Text -> IO CString
textToCString Text
attributes
Ptr FileAttributeMatcher
result <- CString -> IO (Ptr FileAttributeMatcher)
g_file_attribute_matcher_new CString
attributes'
Text -> Ptr FileAttributeMatcher -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileAttributeMatcherNew" Ptr FileAttributeMatcher
result
FileAttributeMatcher
result' <- ((ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FileAttributeMatcher -> FileAttributeMatcher
FileAttributeMatcher) Ptr FileAttributeMatcher
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attributes'
FileAttributeMatcher -> IO FileAttributeMatcher
forall (m :: * -> *) a. Monad m => a -> m a
return FileAttributeMatcher
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_file_attribute_matcher_enumerate_namespace" g_file_attribute_matcher_enumerate_namespace ::
Ptr FileAttributeMatcher ->
CString ->
IO CInt
fileAttributeMatcherEnumerateNamespace ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> T.Text
-> m Bool
fileAttributeMatcherEnumerateNamespace :: FileAttributeMatcher -> Text -> m Bool
fileAttributeMatcherEnumerateNamespace matcher :: FileAttributeMatcher
matcher ns :: Text
ns = 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 FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
CString
ns' <- Text -> IO CString
textToCString Text
ns
CInt
result <- Ptr FileAttributeMatcher -> CString -> IO CInt
g_file_attribute_matcher_enumerate_namespace Ptr FileAttributeMatcher
matcher' CString
ns'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
ns'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherEnumerateNamespaceMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo FileAttributeMatcherEnumerateNamespaceMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherEnumerateNamespace
#endif
foreign import ccall "g_file_attribute_matcher_enumerate_next" g_file_attribute_matcher_enumerate_next ::
Ptr FileAttributeMatcher ->
IO CString
fileAttributeMatcherEnumerateNext ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> m T.Text
fileAttributeMatcherEnumerateNext :: FileAttributeMatcher -> m Text
fileAttributeMatcherEnumerateNext matcher :: FileAttributeMatcher
matcher = 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 FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
CString
result <- Ptr FileAttributeMatcher -> IO CString
g_file_attribute_matcher_enumerate_next Ptr FileAttributeMatcher
matcher'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileAttributeMatcherEnumerateNext" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherEnumerateNextMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo FileAttributeMatcherEnumerateNextMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherEnumerateNext
#endif
foreign import ccall "g_file_attribute_matcher_matches" g_file_attribute_matcher_matches ::
Ptr FileAttributeMatcher ->
CString ->
IO CInt
fileAttributeMatcherMatches ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> T.Text
-> m Bool
fileAttributeMatcherMatches :: FileAttributeMatcher -> Text -> m Bool
fileAttributeMatcherMatches matcher :: FileAttributeMatcher
matcher attribute :: Text
attribute = 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 FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
CString
attribute' <- Text -> IO CString
textToCString Text
attribute
CInt
result <- Ptr FileAttributeMatcher -> CString -> IO CInt
g_file_attribute_matcher_matches Ptr FileAttributeMatcher
matcher' CString
attribute'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherMatchesMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo FileAttributeMatcherMatchesMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherMatches
#endif
foreign import ccall "g_file_attribute_matcher_matches_only" g_file_attribute_matcher_matches_only ::
Ptr FileAttributeMatcher ->
CString ->
IO CInt
fileAttributeMatcherMatchesOnly ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> T.Text
-> m Bool
fileAttributeMatcherMatchesOnly :: FileAttributeMatcher -> Text -> m Bool
fileAttributeMatcherMatchesOnly matcher :: FileAttributeMatcher
matcher attribute :: Text
attribute = 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 FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
CString
attribute' <- Text -> IO CString
textToCString Text
attribute
CInt
result <- Ptr FileAttributeMatcher -> CString -> IO CInt
g_file_attribute_matcher_matches_only Ptr FileAttributeMatcher
matcher' CString
attribute'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherMatchesOnlyMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo FileAttributeMatcherMatchesOnlyMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherMatchesOnly
#endif
foreign import ccall "g_file_attribute_matcher_ref" g_file_attribute_matcher_ref ::
Ptr FileAttributeMatcher ->
IO (Ptr FileAttributeMatcher)
fileAttributeMatcherRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> m FileAttributeMatcher
fileAttributeMatcherRef :: FileAttributeMatcher -> m FileAttributeMatcher
fileAttributeMatcherRef matcher :: FileAttributeMatcher
matcher = IO FileAttributeMatcher -> m FileAttributeMatcher
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileAttributeMatcher -> m FileAttributeMatcher)
-> IO FileAttributeMatcher -> m FileAttributeMatcher
forall a b. (a -> b) -> a -> b
$ do
Ptr FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
Ptr FileAttributeMatcher
result <- Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
g_file_attribute_matcher_ref Ptr FileAttributeMatcher
matcher'
Text -> Ptr FileAttributeMatcher -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileAttributeMatcherRef" Ptr FileAttributeMatcher
result
FileAttributeMatcher
result' <- ((ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FileAttributeMatcher -> FileAttributeMatcher
FileAttributeMatcher) Ptr FileAttributeMatcher
result
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
FileAttributeMatcher -> IO FileAttributeMatcher
forall (m :: * -> *) a. Monad m => a -> m a
return FileAttributeMatcher
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherRefMethodInfo
instance (signature ~ (m FileAttributeMatcher), MonadIO m) => O.MethodInfo FileAttributeMatcherRefMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherRef
#endif
foreign import ccall "g_file_attribute_matcher_subtract" g_file_attribute_matcher_subtract ::
Ptr FileAttributeMatcher ->
Ptr FileAttributeMatcher ->
IO (Ptr FileAttributeMatcher)
fileAttributeMatcherSubtract ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> FileAttributeMatcher
-> m FileAttributeMatcher
fileAttributeMatcherSubtract :: FileAttributeMatcher
-> FileAttributeMatcher -> m FileAttributeMatcher
fileAttributeMatcherSubtract matcher :: FileAttributeMatcher
matcher subtract :: FileAttributeMatcher
subtract = IO FileAttributeMatcher -> m FileAttributeMatcher
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileAttributeMatcher -> m FileAttributeMatcher)
-> IO FileAttributeMatcher -> m FileAttributeMatcher
forall a b. (a -> b) -> a -> b
$ do
Ptr FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
Ptr FileAttributeMatcher
subtract' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
subtract
Ptr FileAttributeMatcher
result <- Ptr FileAttributeMatcher
-> Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
g_file_attribute_matcher_subtract Ptr FileAttributeMatcher
matcher' Ptr FileAttributeMatcher
subtract'
Text -> Ptr FileAttributeMatcher -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileAttributeMatcherSubtract" Ptr FileAttributeMatcher
result
FileAttributeMatcher
result' <- ((ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FileAttributeMatcher -> FileAttributeMatcher
FileAttributeMatcher) Ptr FileAttributeMatcher
result
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
subtract
FileAttributeMatcher -> IO FileAttributeMatcher
forall (m :: * -> *) a. Monad m => a -> m a
return FileAttributeMatcher
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherSubtractMethodInfo
instance (signature ~ (FileAttributeMatcher -> m FileAttributeMatcher), MonadIO m) => O.MethodInfo FileAttributeMatcherSubtractMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherSubtract
#endif
foreign import ccall "g_file_attribute_matcher_to_string" g_file_attribute_matcher_to_string ::
Ptr FileAttributeMatcher ->
IO CString
fileAttributeMatcherToString ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> m T.Text
fileAttributeMatcherToString :: FileAttributeMatcher -> m Text
fileAttributeMatcherToString matcher :: FileAttributeMatcher
matcher = 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 FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
CString
result <- Ptr FileAttributeMatcher -> IO CString
g_file_attribute_matcher_to_string Ptr FileAttributeMatcher
matcher'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileAttributeMatcherToString" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherToStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo FileAttributeMatcherToStringMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherToString
#endif
foreign import ccall "g_file_attribute_matcher_unref" g_file_attribute_matcher_unref ::
Ptr FileAttributeMatcher ->
IO ()
fileAttributeMatcherUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> m ()
fileAttributeMatcherUnref :: FileAttributeMatcher -> m ()
fileAttributeMatcherUnref matcher :: FileAttributeMatcher
matcher = 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 FileAttributeMatcher
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
Ptr FileAttributeMatcher -> IO ()
g_file_attribute_matcher_unref Ptr FileAttributeMatcher
matcher'
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo FileAttributeMatcherUnrefMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherUnref
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveFileAttributeMatcherMethod (t :: Symbol) (o :: *) :: * where
ResolveFileAttributeMatcherMethod "enumerateNamespace" o = FileAttributeMatcherEnumerateNamespaceMethodInfo
ResolveFileAttributeMatcherMethod "enumerateNext" o = FileAttributeMatcherEnumerateNextMethodInfo
ResolveFileAttributeMatcherMethod "matches" o = FileAttributeMatcherMatchesMethodInfo
ResolveFileAttributeMatcherMethod "matchesOnly" o = FileAttributeMatcherMatchesOnlyMethodInfo
ResolveFileAttributeMatcherMethod "ref" o = FileAttributeMatcherRefMethodInfo
ResolveFileAttributeMatcherMethod "subtract" o = FileAttributeMatcherSubtractMethodInfo
ResolveFileAttributeMatcherMethod "toString" o = FileAttributeMatcherToStringMethodInfo
ResolveFileAttributeMatcherMethod "unref" o = FileAttributeMatcherUnrefMethodInfo
ResolveFileAttributeMatcherMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFileAttributeMatcherMethod t FileAttributeMatcher, O.MethodInfo info FileAttributeMatcher p) => OL.IsLabel t (FileAttributeMatcher -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif