{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Determines if a string matches a file attribute.

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

module GI.Gio.Structs.FileAttributeMatcher
    ( 

-- * Exported types
    FileAttributeMatcher(..)                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [enumerateNamespace]("GI.Gio.Structs.FileAttributeMatcher#g:method:enumerateNamespace"), [enumerateNext]("GI.Gio.Structs.FileAttributeMatcher#g:method:enumerateNext"), [matches]("GI.Gio.Structs.FileAttributeMatcher#g:method:matches"), [matchesOnly]("GI.Gio.Structs.FileAttributeMatcher#g:method:matchesOnly"), [ref]("GI.Gio.Structs.FileAttributeMatcher#g:method:ref"), [subtract]("GI.Gio.Structs.FileAttributeMatcher#g:method:subtract"), [toString]("GI.Gio.Structs.FileAttributeMatcher#g:method:toString"), [unref]("GI.Gio.Structs.FileAttributeMatcher#g:method:unref").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveFileAttributeMatcherMethod       ,
#endif

-- ** enumerateNamespace #method:enumerateNamespace#

#if defined(ENABLE_OVERLOADING)
    FileAttributeMatcherEnumerateNamespaceMethodInfo,
#endif
    fileAttributeMatcherEnumerateNamespace  ,


-- ** enumerateNext #method:enumerateNext#

#if defined(ENABLE_OVERLOADING)
    FileAttributeMatcherEnumerateNextMethodInfo,
#endif
    fileAttributeMatcherEnumerateNext       ,


-- ** matches #method:matches#

#if defined(ENABLE_OVERLOADING)
    FileAttributeMatcherMatchesMethodInfo   ,
#endif
    fileAttributeMatcherMatches             ,


-- ** matchesOnly #method:matchesOnly#

#if defined(ENABLE_OVERLOADING)
    FileAttributeMatcherMatchesOnlyMethodInfo,
#endif
    fileAttributeMatcherMatchesOnly         ,


-- ** new #method:new#

    fileAttributeMatcherNew                 ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    FileAttributeMatcherRefMethodInfo       ,
#endif
    fileAttributeMatcherRef                 ,


-- ** subtract #method:subtract#

#if defined(ENABLE_OVERLOADING)
    FileAttributeMatcherSubtractMethodInfo  ,
#endif
    fileAttributeMatcherSubtract            ,


-- ** toString #method:toString#

#if defined(ENABLE_OVERLOADING)
    FileAttributeMatcherToStringMethodInfo  ,
#endif
    fileAttributeMatcherToString            ,


-- ** unref #method:unref#

#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


-- | Memory-managed wrapper type.
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

-- | Convert 'FileAttributeMatcher' 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 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

-- method FileAttributeMatcher::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "attributes"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an attribute string to match."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "FileAttributeMatcher" })
-- throws : False
-- Skip return : False

foreign import ccall "g_file_attribute_matcher_new" g_file_attribute_matcher_new :: 
    CString ->                              -- attributes : TBasicType TUTF8
    IO (Ptr FileAttributeMatcher)

-- | Creates a new file attribute matcher, which matches attributes
-- against a given string. @/GFileAttributeMatchers/@ are reference
-- counted structures, and are created with a reference count of 1. If
-- the number of references falls to 0, the t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher' is
-- automatically destroyed.
-- 
-- The /@attributes@/ string should be formatted with specific keys separated
-- from namespaces with a double colon. Several \"namespace[key](#g:signal:key)\" strings may be
-- concatenated with a single comma (e.g. \"standard[type](#g:signal:type),standard[isHidden](#g:signal:isHidden)\").
-- The wildcard \"*\" may be used to match all keys and namespaces, or
-- \"namespace::*\" will match all keys in a given namespace.
-- 
-- == Examples of file attribute matcher strings and results
-- 
-- 
-- * @\"*\"@: matches all attributes.
-- * @\"standard::is-hidden\"@: matches only the key is-hidden in the
-- standard namespace.
-- * @\"standard::type,unix::*\"@: matches the type key in the standard
-- namespace and all keys in the unix namespace.
fileAttributeMatcherNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@attributes@/: an attribute string to match.
    -> m FileAttributeMatcher
    -- ^ __Returns:__ a t'GI.Gio.Structs.FileAttributeMatcher.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

-- method FileAttributeMatcher::enumerate_namespace
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "matcher"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "FileAttributeMatcher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileAttributeMatcher."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ns"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a string containing a file attribute namespace."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_attribute_matcher_enumerate_namespace" g_file_attribute_matcher_enumerate_namespace :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    CString ->                              -- ns : TBasicType TUTF8
    IO CInt

-- | Checks if the matcher will match all of the keys in a given namespace.
-- This will always return 'P.True' if a wildcard character is in use (e.g. if
-- matcher was created with \"standard::*\" and /@ns@/ is \"standard\", or if matcher was created
-- using \"*\" and namespace is anything.)
-- 
-- TODO: this is awkwardly worded.
fileAttributeMatcherEnumerateNamespace ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
    -> T.Text
    -- ^ /@ns@/: a string containing a file attribute namespace.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the matcher matches all of the entries
    -- in the given /@ns@/, 'P.False' otherwise.
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.32/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherEnumerateNamespace"
        })


#endif

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

foreign import ccall "g_file_attribute_matcher_enumerate_next" g_file_attribute_matcher_enumerate_next :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    IO CString

-- | Gets the next matched attribute from a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
fileAttributeMatcherEnumerateNext ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a string containing the next attribute or, 'P.Nothing' if
    -- no more attribute exist.
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.32/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherEnumerateNext"
        })


#endif

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

foreign import ccall "g_file_attribute_matcher_matches" g_file_attribute_matcher_matches :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CInt

-- | Checks if an attribute will be matched by an attribute matcher. If
-- the matcher was created with the \"*\" matching string, this function
-- will always return 'P.True'.
fileAttributeMatcherMatches ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@attribute@/ matches /@matcher@/. 'P.False' otherwise.
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.32/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherMatches"
        })


#endif

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

foreign import ccall "g_file_attribute_matcher_matches_only" g_file_attribute_matcher_matches_only :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CInt

-- | Checks if an attribute matcher only matches a given attribute. Always
-- returns 'P.False' if \"*\" was used when creating the matcher.
fileAttributeMatcherMatchesOnly ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the matcher only matches /@attribute@/. 'P.False' otherwise.
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.32/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherMatchesOnly"
        })


#endif

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

foreign import ccall "g_file_attribute_matcher_ref" g_file_attribute_matcher_ref :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    IO (Ptr FileAttributeMatcher)

-- | References a file attribute matcher.
fileAttributeMatcherRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
    -> m FileAttributeMatcher
    -- ^ __Returns:__ a t'GI.Gio.Structs.FileAttributeMatcher.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.32/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherRef"
        })


#endif

-- method FileAttributeMatcher::subtract
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "matcher"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "FileAttributeMatcher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Matcher to subtract from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "subtract"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "FileAttributeMatcher" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The matcher to subtract"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "FileAttributeMatcher" })
-- throws : False
-- Skip return : False

foreign import ccall "g_file_attribute_matcher_subtract" g_file_attribute_matcher_subtract :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    Ptr FileAttributeMatcher ->             -- subtract : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    IO (Ptr FileAttributeMatcher)

-- | Subtracts all attributes of /@subtract@/ from /@matcher@/ and returns
-- a matcher that supports those attributes.
-- 
-- Note that currently it is not possible to remove a single
-- attribute when the /@matcher@/ matches the whole namespace - or remove
-- a namespace or attribute when the matcher matches everything. This
-- is a limitation of the current implementation, but may be fixed
-- in the future.
fileAttributeMatcherSubtract ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: Matcher to subtract from
    -> Maybe (FileAttributeMatcher)
    -- ^ /@subtract@/: The matcher to subtract
    -> m (Maybe FileAttributeMatcher)
    -- ^ __Returns:__ A file attribute matcher matching all attributes of
    --     /@matcher@/ that are not matched by /@subtract@/
fileAttributeMatcherSubtract :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher
-> Maybe FileAttributeMatcher -> m (Maybe FileAttributeMatcher)
fileAttributeMatcherSubtract 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
matcher' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
matcher
    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
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
matcher' 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''
    FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
    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 = fileAttributeMatcherSubtract

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.32/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherSubtract"
        })


#endif

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

foreign import ccall "g_file_attribute_matcher_to_string" g_file_attribute_matcher_to_string :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    IO CString

-- | Prints what the matcher is matching against. The format will be
-- equal to the format passed to 'GI.Gio.Structs.FileAttributeMatcher.fileAttributeMatcherNew'.
-- The output however, might not be identical, as the matcher may
-- decide to use a different order or omit needless parts.
-- 
-- /Since: 2.32/
fileAttributeMatcherToString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
    -> m T.Text
    -- ^ __Returns:__ a string describing the attributes the matcher matches
    --   against or 'P.Nothing' if /@matcher@/ was 'P.Nothing'.
fileAttributeMatcherToString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FileAttributeMatcher -> m Text
fileAttributeMatcherToString 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
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 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
    FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
matcher
    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 = fileAttributeMatcherToString

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.32/docs/GI-Gio-Structs-FileAttributeMatcher.html#v:fileAttributeMatcherToString"
        })


#endif

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

foreign import ccall "g_file_attribute_matcher_unref" g_file_attribute_matcher_unref :: 
    Ptr FileAttributeMatcher ->             -- matcher : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    IO ()

-- | Unreferences /@matcher@/. If the reference count falls below 1,
-- the /@matcher@/ is automatically freed.
fileAttributeMatcherUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FileAttributeMatcher
    -- ^ /@matcher@/: a t'GI.Gio.Structs.FileAttributeMatcher.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.32/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