{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.FileAttributeMatcher
(
FileAttributeMatcher(..) ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
#else
#endif
newtype FileAttributeMatcher = FileAttributeMatcher (SP.ManagedPtr FileAttributeMatcher)
deriving (FileAttributeMatcher -> FileAttributeMatcher -> Bool
(FileAttributeMatcher -> FileAttributeMatcher -> Bool)
-> (FileAttributeMatcher -> FileAttributeMatcher -> Bool)
-> Eq FileAttributeMatcher
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
== :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
$c/= :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
/= :: FileAttributeMatcher -> FileAttributeMatcher -> Bool
Eq)
instance SP.ManagedPtrNewtype FileAttributeMatcher where
toManagedPtr :: FileAttributeMatcher -> ManagedPtr FileAttributeMatcher
toManagedPtr (FileAttributeMatcher ManagedPtr FileAttributeMatcher
p) = ManagedPtr FileAttributeMatcher
p
foreign import ccall "g_file_attribute_matcher_get_type" c_g_file_attribute_matcher_get_type ::
IO GType
type instance O.ParentTypes FileAttributeMatcher = '[]
instance O.HasParentTypes FileAttributeMatcher
instance B.Types.TypedObject FileAttributeMatcher where
glibType :: IO GType
glibType = IO GType
c_g_file_attribute_matcher_get_type
instance B.Types.GBoxed FileAttributeMatcher
instance B.GValue.IsGValue (Maybe FileAttributeMatcher) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_file_attribute_matcher_get_type
gvalueSet_ :: Ptr GValue -> Maybe FileAttributeMatcher -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FileAttributeMatcher
P.Nothing = Ptr GValue -> Ptr FileAttributeMatcher -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr FileAttributeMatcher
forall a. Ptr a
FP.nullPtr :: FP.Ptr FileAttributeMatcher)
gvalueSet_ Ptr GValue
gv (P.Just FileAttributeMatcher
obj) = FileAttributeMatcher
-> (Ptr FileAttributeMatcher -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileAttributeMatcher
obj (Ptr GValue -> Ptr FileAttributeMatcher -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe FileAttributeMatcher)
gvalueGet_ Ptr GValue
gv = do
Ptr FileAttributeMatcher
ptr <- Ptr GValue -> IO (Ptr FileAttributeMatcher)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr FileAttributeMatcher)
if Ptr FileAttributeMatcher
ptr Ptr FileAttributeMatcher -> Ptr FileAttributeMatcher -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FileAttributeMatcher
forall a. Ptr a
FP.nullPtr
then FileAttributeMatcher -> Maybe FileAttributeMatcher
forall a. a -> Maybe a
P.Just (FileAttributeMatcher -> Maybe FileAttributeMatcher)
-> IO FileAttributeMatcher -> IO (Maybe FileAttributeMatcher)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr FileAttributeMatcher -> FileAttributeMatcher
FileAttributeMatcher Ptr FileAttributeMatcher
ptr
else Maybe FileAttributeMatcher -> IO (Maybe FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FileAttributeMatcher
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileAttributeMatcher
type instance O.AttributeList FileAttributeMatcher = FileAttributeMatcherAttributeList
type FileAttributeMatcherAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m FileAttributeMatcher
fileAttributeMatcherNew Text
attributes = IO FileAttributeMatcher -> m FileAttributeMatcher
forall a. IO a -> m a
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 Text
"fileAttributeMatcherNew" Ptr FileAttributeMatcher
result
FileAttributeMatcher
result' <- ((ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, GBoxed 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 a. a -> IO a
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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher -> Text -> m Bool
fileAttributeMatcherEnumerateNamespace FileAttributeMatcher
matcher Text
ns = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
/= CInt
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 a. a -> IO a
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.OverloadedMethod FileAttributeMatcherEnumerateNamespaceMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherEnumerateNamespace
instance O.OverloadedMethodInfo FileAttributeMatcherEnumerateNamespaceMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherEnumerateNamespace",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v: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 (Maybe T.Text)
fileAttributeMatcherEnumerateNext :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher -> m (Maybe Text)
fileAttributeMatcherEnumerateNext FileAttributeMatcher
matcher = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe 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'
Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherEnumerateNextMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod FileAttributeMatcherEnumerateNextMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherEnumerateNext
instance O.OverloadedMethodInfo FileAttributeMatcherEnumerateNextMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherEnumerateNext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher -> Text -> m Bool
fileAttributeMatcherMatches FileAttributeMatcher
matcher Text
attribute = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
/= CInt
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 a. a -> IO a
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.OverloadedMethod FileAttributeMatcherMatchesMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherMatches
instance O.OverloadedMethodInfo FileAttributeMatcherMatchesMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherMatches",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher -> Text -> m Bool
fileAttributeMatcherMatchesOnly FileAttributeMatcher
matcher Text
attribute = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
/= CInt
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 a. a -> IO a
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.OverloadedMethod FileAttributeMatcherMatchesOnlyMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherMatchesOnly
instance O.OverloadedMethodInfo FileAttributeMatcherMatchesOnlyMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherMatchesOnly",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher -> m FileAttributeMatcher
fileAttributeMatcherRef FileAttributeMatcher
matcher = IO FileAttributeMatcher -> m FileAttributeMatcher
forall a. IO a -> m a
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 Text
"fileAttributeMatcherRef" Ptr FileAttributeMatcher
result
FileAttributeMatcher
result' <- ((ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, GBoxed 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FileAttributeMatcher
result'
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherRefMethodInfo
instance (signature ~ (m FileAttributeMatcher), MonadIO m) => O.OverloadedMethod FileAttributeMatcherRefMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherRef
instance O.OverloadedMethodInfo FileAttributeMatcherRefMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v: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) =>
Maybe (FileAttributeMatcher)
-> Maybe (FileAttributeMatcher)
-> m (Maybe FileAttributeMatcher)
fileAttributeMatcherSubtract :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe FileAttributeMatcher
-> Maybe FileAttributeMatcher -> m (Maybe FileAttributeMatcher)
fileAttributeMatcherSubtract Maybe FileAttributeMatcher
matcher Maybe FileAttributeMatcher
subtract = IO (Maybe FileAttributeMatcher) -> m (Maybe FileAttributeMatcher)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FileAttributeMatcher) -> m (Maybe FileAttributeMatcher))
-> IO (Maybe FileAttributeMatcher)
-> m (Maybe FileAttributeMatcher)
forall a b. (a -> b) -> a -> b
$ do
Ptr FileAttributeMatcher
maybeMatcher <- case Maybe FileAttributeMatcher
matcher of
Maybe FileAttributeMatcher
Nothing -> Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileAttributeMatcher
forall a. Ptr a
FP.nullPtr
Just FileAttributeMatcher
jMatcher -> do
Ptr FileAttributeMatcher
jMatcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
jMatcher
Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileAttributeMatcher
jMatcher'
Ptr FileAttributeMatcher
maybeSubtract <- case Maybe FileAttributeMatcher
subtract of
Maybe FileAttributeMatcher
Nothing -> Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileAttributeMatcher
forall a. Ptr a
FP.nullPtr
Just FileAttributeMatcher
jSubtract -> do
Ptr FileAttributeMatcher
jSubtract' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
jSubtract
Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileAttributeMatcher
jSubtract'
Ptr FileAttributeMatcher
result <- Ptr FileAttributeMatcher
-> Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
g_file_attribute_matcher_subtract Ptr FileAttributeMatcher
maybeMatcher Ptr FileAttributeMatcher
maybeSubtract
Maybe FileAttributeMatcher
maybeResult <- Ptr FileAttributeMatcher
-> (Ptr FileAttributeMatcher -> IO FileAttributeMatcher)
-> IO (Maybe FileAttributeMatcher)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FileAttributeMatcher
result ((Ptr FileAttributeMatcher -> IO FileAttributeMatcher)
-> IO (Maybe FileAttributeMatcher))
-> (Ptr FileAttributeMatcher -> IO FileAttributeMatcher)
-> IO (Maybe FileAttributeMatcher)
forall a b. (a -> b) -> a -> b
$ \Ptr FileAttributeMatcher
result' -> do
FileAttributeMatcher
result'' <- ((ManagedPtr FileAttributeMatcher -> FileAttributeMatcher)
-> Ptr FileAttributeMatcher -> IO FileAttributeMatcher
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FileAttributeMatcher -> FileAttributeMatcher
FileAttributeMatcher) Ptr FileAttributeMatcher
result'
FileAttributeMatcher -> IO FileAttributeMatcher
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FileAttributeMatcher
result''
Maybe FileAttributeMatcher
-> (FileAttributeMatcher -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe FileAttributeMatcher
matcher FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe FileAttributeMatcher
-> (FileAttributeMatcher -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe FileAttributeMatcher
subtract FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe FileAttributeMatcher -> IO (Maybe FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FileAttributeMatcher
maybeResult
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherSubtractMethodInfo
instance (signature ~ (Maybe (FileAttributeMatcher) -> m (Maybe FileAttributeMatcher)), MonadIO m) => O.OverloadedMethod FileAttributeMatcherSubtractMethodInfo FileAttributeMatcher signature where
overloadedMethod i = fileAttributeMatcherSubtract (Just i)
instance O.OverloadedMethodInfo FileAttributeMatcherSubtractMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherSubtract",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v: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) =>
Maybe (FileAttributeMatcher)
-> m T.Text
fileAttributeMatcherToString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe FileAttributeMatcher -> m Text
fileAttributeMatcherToString Maybe FileAttributeMatcher
matcher = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr FileAttributeMatcher
maybeMatcher <- case Maybe FileAttributeMatcher
matcher of
Maybe FileAttributeMatcher
Nothing -> Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileAttributeMatcher
forall a. Ptr a
FP.nullPtr
Just FileAttributeMatcher
jMatcher -> do
Ptr FileAttributeMatcher
jMatcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
jMatcher
Ptr FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileAttributeMatcher
jMatcher'
CString
result <- Ptr FileAttributeMatcher -> IO CString
g_file_attribute_matcher_to_string Ptr FileAttributeMatcher
maybeMatcher
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"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
Maybe FileAttributeMatcher
-> (FileAttributeMatcher -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe FileAttributeMatcher
matcher FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Text -> IO Text
forall a. a -> IO a
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.OverloadedMethod FileAttributeMatcherToStringMethodInfo FileAttributeMatcher signature where
overloadedMethod i = fileAttributeMatcherToString (Just i)
instance O.OverloadedMethodInfo FileAttributeMatcherToStringMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherToString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher -> m ()
fileAttributeMatcherUnref FileAttributeMatcher
matcher = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FileAttributeMatcherUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod FileAttributeMatcherUnrefMethodInfo FileAttributeMatcher signature where
overloadedMethod = fileAttributeMatcherUnref
instance O.OverloadedMethodInfo FileAttributeMatcherUnrefMethodInfo FileAttributeMatcher where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.34/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveFileAttributeMatcherMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFileAttributeMatcherMethod t FileAttributeMatcher, O.OverloadedMethod info FileAttributeMatcher p, R.HasField t FileAttributeMatcher p) => R.HasField t FileAttributeMatcher p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveFileAttributeMatcherMethod t FileAttributeMatcher, O.OverloadedMethodInfo info FileAttributeMatcher) => OL.IsLabel t (O.MethodProxy info FileAttributeMatcher) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif