{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Functionality for manipulating basic metadata for files. t'GI.Gio.Objects.FileInfo.FileInfo'
-- implements methods for getting information that all files should
-- contain, and allows for manipulation of extended attributes.
-- 
-- See [GFileAttribute][gio-GFileAttribute] for more information on how
-- GIO handles file attributes.
-- 
-- To obtain a t'GI.Gio.Objects.FileInfo.FileInfo' for a t'GI.Gio.Interfaces.File.File', use 'GI.Gio.Interfaces.File.fileQueryInfo' (or its
-- async variant). To obtain a t'GI.Gio.Objects.FileInfo.FileInfo' for a file input or output
-- stream, use 'GI.Gio.Objects.FileInputStream.fileInputStreamQueryInfo' or
-- 'GI.Gio.Objects.FileOutputStream.fileOutputStreamQueryInfo' (or their async variants).
-- 
-- To change the actual attributes of a file, you should then set the
-- attribute in the t'GI.Gio.Objects.FileInfo.FileInfo' and call 'GI.Gio.Interfaces.File.fileSetAttributesFromInfo'
-- or 'GI.Gio.Interfaces.File.fileSetAttributesAsync' on a GFile.
-- 
-- However, not all attributes can be changed in the file. For instance,
-- the actual size of a file cannot be changed via 'GI.Gio.Objects.FileInfo.fileInfoSetSize'.
-- You may call 'GI.Gio.Interfaces.File.fileQuerySettableAttributes' and
-- 'GI.Gio.Interfaces.File.fileQueryWritableNamespaces' to discover the settable attributes
-- of a particular file at runtime.
-- 
-- t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher' allows for searching through a t'GI.Gio.Objects.FileInfo.FileInfo' for
-- attributes.

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

module GI.Gio.Objects.FileInfo
    ( 

-- * Exported types
    FileInfo(..)                            ,
    IsFileInfo                              ,
    toFileInfo                              ,
    noFileInfo                              ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveFileInfoMethod                   ,
#endif


-- ** clearStatus #method:clearStatus#

#if defined(ENABLE_OVERLOADING)
    FileInfoClearStatusMethodInfo           ,
#endif
    fileInfoClearStatus                     ,


-- ** copyInto #method:copyInto#

#if defined(ENABLE_OVERLOADING)
    FileInfoCopyIntoMethodInfo              ,
#endif
    fileInfoCopyInto                        ,


-- ** dup #method:dup#

#if defined(ENABLE_OVERLOADING)
    FileInfoDupMethodInfo                   ,
#endif
    fileInfoDup                             ,


-- ** getAttributeAsString #method:getAttributeAsString#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeAsStringMethodInfo  ,
#endif
    fileInfoGetAttributeAsString            ,


-- ** getAttributeBoolean #method:getAttributeBoolean#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeBooleanMethodInfo   ,
#endif
    fileInfoGetAttributeBoolean             ,


-- ** getAttributeByteString #method:getAttributeByteString#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeByteStringMethodInfo,
#endif
    fileInfoGetAttributeByteString          ,


-- ** getAttributeData #method:getAttributeData#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeDataMethodInfo      ,
#endif
    fileInfoGetAttributeData                ,


-- ** getAttributeInt32 #method:getAttributeInt32#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeInt32MethodInfo     ,
#endif
    fileInfoGetAttributeInt32               ,


-- ** getAttributeInt64 #method:getAttributeInt64#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeInt64MethodInfo     ,
#endif
    fileInfoGetAttributeInt64               ,


-- ** getAttributeObject #method:getAttributeObject#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeObjectMethodInfo    ,
#endif
    fileInfoGetAttributeObject              ,


-- ** getAttributeStatus #method:getAttributeStatus#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeStatusMethodInfo    ,
#endif
    fileInfoGetAttributeStatus              ,


-- ** getAttributeString #method:getAttributeString#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeStringMethodInfo    ,
#endif
    fileInfoGetAttributeString              ,


-- ** getAttributeStringv #method:getAttributeStringv#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeStringvMethodInfo   ,
#endif
    fileInfoGetAttributeStringv             ,


-- ** getAttributeType #method:getAttributeType#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeTypeMethodInfo      ,
#endif
    fileInfoGetAttributeType                ,


-- ** getAttributeUint32 #method:getAttributeUint32#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeUint32MethodInfo    ,
#endif
    fileInfoGetAttributeUint32              ,


-- ** getAttributeUint64 #method:getAttributeUint64#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAttributeUint64MethodInfo    ,
#endif
    fileInfoGetAttributeUint64              ,


-- ** getContentType #method:getContentType#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetContentTypeMethodInfo        ,
#endif
    fileInfoGetContentType                  ,


-- ** getDeletionDate #method:getDeletionDate#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetDeletionDateMethodInfo       ,
#endif
    fileInfoGetDeletionDate                 ,


-- ** getDisplayName #method:getDisplayName#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetDisplayNameMethodInfo        ,
#endif
    fileInfoGetDisplayName                  ,


-- ** getEditName #method:getEditName#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetEditNameMethodInfo           ,
#endif
    fileInfoGetEditName                     ,


-- ** getEtag #method:getEtag#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetEtagMethodInfo               ,
#endif
    fileInfoGetEtag                         ,


-- ** getFileType #method:getFileType#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetFileTypeMethodInfo           ,
#endif
    fileInfoGetFileType                     ,


-- ** getIcon #method:getIcon#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetIconMethodInfo               ,
#endif
    fileInfoGetIcon                         ,


-- ** getIsBackup #method:getIsBackup#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetIsBackupMethodInfo           ,
#endif
    fileInfoGetIsBackup                     ,


-- ** getIsHidden #method:getIsHidden#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetIsHiddenMethodInfo           ,
#endif
    fileInfoGetIsHidden                     ,


-- ** getIsSymlink #method:getIsSymlink#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetIsSymlinkMethodInfo          ,
#endif
    fileInfoGetIsSymlink                    ,


-- ** getModificationTime #method:getModificationTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetModificationTimeMethodInfo   ,
#endif
    fileInfoGetModificationTime             ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetNameMethodInfo               ,
#endif
    fileInfoGetName                         ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetSizeMethodInfo               ,
#endif
    fileInfoGetSize                         ,


-- ** getSortOrder #method:getSortOrder#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetSortOrderMethodInfo          ,
#endif
    fileInfoGetSortOrder                    ,


-- ** getSymbolicIcon #method:getSymbolicIcon#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetSymbolicIconMethodInfo       ,
#endif
    fileInfoGetSymbolicIcon                 ,


-- ** getSymlinkTarget #method:getSymlinkTarget#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetSymlinkTargetMethodInfo      ,
#endif
    fileInfoGetSymlinkTarget                ,


-- ** hasAttribute #method:hasAttribute#

#if defined(ENABLE_OVERLOADING)
    FileInfoHasAttributeMethodInfo          ,
#endif
    fileInfoHasAttribute                    ,


-- ** hasNamespace #method:hasNamespace#

#if defined(ENABLE_OVERLOADING)
    FileInfoHasNamespaceMethodInfo          ,
#endif
    fileInfoHasNamespace                    ,


-- ** listAttributes #method:listAttributes#

#if defined(ENABLE_OVERLOADING)
    FileInfoListAttributesMethodInfo        ,
#endif
    fileInfoListAttributes                  ,


-- ** new #method:new#

    fileInfoNew                             ,


-- ** removeAttribute #method:removeAttribute#

#if defined(ENABLE_OVERLOADING)
    FileInfoRemoveAttributeMethodInfo       ,
#endif
    fileInfoRemoveAttribute                 ,


-- ** setAttribute #method:setAttribute#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeMethodInfo          ,
#endif
    fileInfoSetAttribute                    ,


-- ** setAttributeBoolean #method:setAttributeBoolean#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeBooleanMethodInfo   ,
#endif
    fileInfoSetAttributeBoolean             ,


-- ** setAttributeByteString #method:setAttributeByteString#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeByteStringMethodInfo,
#endif
    fileInfoSetAttributeByteString          ,


-- ** setAttributeInt32 #method:setAttributeInt32#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeInt32MethodInfo     ,
#endif
    fileInfoSetAttributeInt32               ,


-- ** setAttributeInt64 #method:setAttributeInt64#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeInt64MethodInfo     ,
#endif
    fileInfoSetAttributeInt64               ,


-- ** setAttributeMask #method:setAttributeMask#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeMaskMethodInfo      ,
#endif
    fileInfoSetAttributeMask                ,


-- ** setAttributeObject #method:setAttributeObject#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeObjectMethodInfo    ,
#endif
    fileInfoSetAttributeObject              ,


-- ** setAttributeStatus #method:setAttributeStatus#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeStatusMethodInfo    ,
#endif
    fileInfoSetAttributeStatus              ,


-- ** setAttributeString #method:setAttributeString#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeStringMethodInfo    ,
#endif
    fileInfoSetAttributeString              ,


-- ** setAttributeStringv #method:setAttributeStringv#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeStringvMethodInfo   ,
#endif
    fileInfoSetAttributeStringv             ,


-- ** setAttributeUint32 #method:setAttributeUint32#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeUint32MethodInfo    ,
#endif
    fileInfoSetAttributeUint32              ,


-- ** setAttributeUint64 #method:setAttributeUint64#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAttributeUint64MethodInfo    ,
#endif
    fileInfoSetAttributeUint64              ,


-- ** setContentType #method:setContentType#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetContentTypeMethodInfo        ,
#endif
    fileInfoSetContentType                  ,


-- ** setDisplayName #method:setDisplayName#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetDisplayNameMethodInfo        ,
#endif
    fileInfoSetDisplayName                  ,


-- ** setEditName #method:setEditName#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetEditNameMethodInfo           ,
#endif
    fileInfoSetEditName                     ,


-- ** setFileType #method:setFileType#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetFileTypeMethodInfo           ,
#endif
    fileInfoSetFileType                     ,


-- ** setIcon #method:setIcon#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetIconMethodInfo               ,
#endif
    fileInfoSetIcon                         ,


-- ** setIsHidden #method:setIsHidden#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetIsHiddenMethodInfo           ,
#endif
    fileInfoSetIsHidden                     ,


-- ** setIsSymlink #method:setIsSymlink#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetIsSymlinkMethodInfo          ,
#endif
    fileInfoSetIsSymlink                    ,


-- ** setModificationTime #method:setModificationTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetModificationTimeMethodInfo   ,
#endif
    fileInfoSetModificationTime             ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetNameMethodInfo               ,
#endif
    fileInfoSetName                         ,


-- ** setSize #method:setSize#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetSizeMethodInfo               ,
#endif
    fileInfoSetSize                         ,


-- ** setSortOrder #method:setSortOrder#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetSortOrderMethodInfo          ,
#endif
    fileInfoSetSortOrder                    ,


-- ** setSymbolicIcon #method:setSymbolicIcon#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetSymbolicIconMethodInfo       ,
#endif
    fileInfoSetSymbolicIcon                 ,


-- ** setSymlinkTarget #method:setSymlinkTarget#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetSymlinkTargetMethodInfo      ,
#endif
    fileInfoSetSymlinkTarget                ,


-- ** unsetAttributeMask #method:unsetAttributeMask#

#if defined(ENABLE_OVERLOADING)
    FileInfoUnsetAttributeMaskMethodInfo    ,
#endif
    fileInfoUnsetAttributeMask              ,




    ) 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

import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.TimeVal as GLib.TimeVal
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeMatcher as Gio.FileAttributeMatcher

-- | Memory-managed wrapper type.
newtype FileInfo = FileInfo (ManagedPtr FileInfo)
    deriving (FileInfo -> FileInfo -> Bool
(FileInfo -> FileInfo -> Bool)
-> (FileInfo -> FileInfo -> Bool) -> Eq FileInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileInfo -> FileInfo -> Bool
$c/= :: FileInfo -> FileInfo -> Bool
== :: FileInfo -> FileInfo -> Bool
$c== :: FileInfo -> FileInfo -> Bool
Eq)
foreign import ccall "g_file_info_get_type"
    c_g_file_info_get_type :: IO GType

instance GObject FileInfo where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_file_info_get_type
    

-- | Convert 'FileInfo' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue FileInfo where
    toGValue :: FileInfo -> IO GValue
toGValue o :: FileInfo
o = do
        GType
gtype <- IO GType
c_g_file_info_get_type
        FileInfo -> (Ptr FileInfo -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileInfo
o (GType
-> (GValue -> Ptr FileInfo -> IO ()) -> Ptr FileInfo -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr FileInfo -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO FileInfo
fromGValue gv :: GValue
gv = do
        Ptr FileInfo
ptr <- GValue -> IO (Ptr FileInfo)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr FileInfo)
        (ManagedPtr FileInfo -> FileInfo) -> Ptr FileInfo -> IO FileInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FileInfo -> FileInfo
FileInfo Ptr FileInfo
ptr
        
    

-- | Type class for types which can be safely cast to `FileInfo`, for instance with `toFileInfo`.
class (GObject o, O.IsDescendantOf FileInfo o) => IsFileInfo o
instance (GObject o, O.IsDescendantOf FileInfo o) => IsFileInfo o

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

-- | Cast to `FileInfo`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toFileInfo :: (MonadIO m, IsFileInfo o) => o -> m FileInfo
toFileInfo :: o -> m FileInfo
toFileInfo = IO FileInfo -> m FileInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileInfo -> m FileInfo)
-> (o -> IO FileInfo) -> o -> m FileInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FileInfo -> FileInfo) -> o -> IO FileInfo
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr FileInfo -> FileInfo
FileInfo

-- | A convenience alias for `Nothing` :: `Maybe` `FileInfo`.
noFileInfo :: Maybe FileInfo
noFileInfo :: Maybe FileInfo
noFileInfo = Maybe FileInfo
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveFileInfoMethod (t :: Symbol) (o :: *) :: * where
    ResolveFileInfoMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveFileInfoMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveFileInfoMethod "clearStatus" o = FileInfoClearStatusMethodInfo
    ResolveFileInfoMethod "copyInto" o = FileInfoCopyIntoMethodInfo
    ResolveFileInfoMethod "dup" o = FileInfoDupMethodInfo
    ResolveFileInfoMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveFileInfoMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveFileInfoMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveFileInfoMethod "hasAttribute" o = FileInfoHasAttributeMethodInfo
    ResolveFileInfoMethod "hasNamespace" o = FileInfoHasNamespaceMethodInfo
    ResolveFileInfoMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveFileInfoMethod "listAttributes" o = FileInfoListAttributesMethodInfo
    ResolveFileInfoMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveFileInfoMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveFileInfoMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveFileInfoMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveFileInfoMethod "removeAttribute" o = FileInfoRemoveAttributeMethodInfo
    ResolveFileInfoMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveFileInfoMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveFileInfoMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveFileInfoMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveFileInfoMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveFileInfoMethod "unsetAttributeMask" o = FileInfoUnsetAttributeMaskMethodInfo
    ResolveFileInfoMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveFileInfoMethod "getAttributeAsString" o = FileInfoGetAttributeAsStringMethodInfo
    ResolveFileInfoMethod "getAttributeBoolean" o = FileInfoGetAttributeBooleanMethodInfo
    ResolveFileInfoMethod "getAttributeByteString" o = FileInfoGetAttributeByteStringMethodInfo
    ResolveFileInfoMethod "getAttributeData" o = FileInfoGetAttributeDataMethodInfo
    ResolveFileInfoMethod "getAttributeInt32" o = FileInfoGetAttributeInt32MethodInfo
    ResolveFileInfoMethod "getAttributeInt64" o = FileInfoGetAttributeInt64MethodInfo
    ResolveFileInfoMethod "getAttributeObject" o = FileInfoGetAttributeObjectMethodInfo
    ResolveFileInfoMethod "getAttributeStatus" o = FileInfoGetAttributeStatusMethodInfo
    ResolveFileInfoMethod "getAttributeString" o = FileInfoGetAttributeStringMethodInfo
    ResolveFileInfoMethod "getAttributeStringv" o = FileInfoGetAttributeStringvMethodInfo
    ResolveFileInfoMethod "getAttributeType" o = FileInfoGetAttributeTypeMethodInfo
    ResolveFileInfoMethod "getAttributeUint32" o = FileInfoGetAttributeUint32MethodInfo
    ResolveFileInfoMethod "getAttributeUint64" o = FileInfoGetAttributeUint64MethodInfo
    ResolveFileInfoMethod "getContentType" o = FileInfoGetContentTypeMethodInfo
    ResolveFileInfoMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveFileInfoMethod "getDeletionDate" o = FileInfoGetDeletionDateMethodInfo
    ResolveFileInfoMethod "getDisplayName" o = FileInfoGetDisplayNameMethodInfo
    ResolveFileInfoMethod "getEditName" o = FileInfoGetEditNameMethodInfo
    ResolveFileInfoMethod "getEtag" o = FileInfoGetEtagMethodInfo
    ResolveFileInfoMethod "getFileType" o = FileInfoGetFileTypeMethodInfo
    ResolveFileInfoMethod "getIcon" o = FileInfoGetIconMethodInfo
    ResolveFileInfoMethod "getIsBackup" o = FileInfoGetIsBackupMethodInfo
    ResolveFileInfoMethod "getIsHidden" o = FileInfoGetIsHiddenMethodInfo
    ResolveFileInfoMethod "getIsSymlink" o = FileInfoGetIsSymlinkMethodInfo
    ResolveFileInfoMethod "getModificationTime" o = FileInfoGetModificationTimeMethodInfo
    ResolveFileInfoMethod "getName" o = FileInfoGetNameMethodInfo
    ResolveFileInfoMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveFileInfoMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveFileInfoMethod "getSize" o = FileInfoGetSizeMethodInfo
    ResolveFileInfoMethod "getSortOrder" o = FileInfoGetSortOrderMethodInfo
    ResolveFileInfoMethod "getSymbolicIcon" o = FileInfoGetSymbolicIconMethodInfo
    ResolveFileInfoMethod "getSymlinkTarget" o = FileInfoGetSymlinkTargetMethodInfo
    ResolveFileInfoMethod "setAttribute" o = FileInfoSetAttributeMethodInfo
    ResolveFileInfoMethod "setAttributeBoolean" o = FileInfoSetAttributeBooleanMethodInfo
    ResolveFileInfoMethod "setAttributeByteString" o = FileInfoSetAttributeByteStringMethodInfo
    ResolveFileInfoMethod "setAttributeInt32" o = FileInfoSetAttributeInt32MethodInfo
    ResolveFileInfoMethod "setAttributeInt64" o = FileInfoSetAttributeInt64MethodInfo
    ResolveFileInfoMethod "setAttributeMask" o = FileInfoSetAttributeMaskMethodInfo
    ResolveFileInfoMethod "setAttributeObject" o = FileInfoSetAttributeObjectMethodInfo
    ResolveFileInfoMethod "setAttributeStatus" o = FileInfoSetAttributeStatusMethodInfo
    ResolveFileInfoMethod "setAttributeString" o = FileInfoSetAttributeStringMethodInfo
    ResolveFileInfoMethod "setAttributeStringv" o = FileInfoSetAttributeStringvMethodInfo
    ResolveFileInfoMethod "setAttributeUint32" o = FileInfoSetAttributeUint32MethodInfo
    ResolveFileInfoMethod "setAttributeUint64" o = FileInfoSetAttributeUint64MethodInfo
    ResolveFileInfoMethod "setContentType" o = FileInfoSetContentTypeMethodInfo
    ResolveFileInfoMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveFileInfoMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveFileInfoMethod "setDisplayName" o = FileInfoSetDisplayNameMethodInfo
    ResolveFileInfoMethod "setEditName" o = FileInfoSetEditNameMethodInfo
    ResolveFileInfoMethod "setFileType" o = FileInfoSetFileTypeMethodInfo
    ResolveFileInfoMethod "setIcon" o = FileInfoSetIconMethodInfo
    ResolveFileInfoMethod "setIsHidden" o = FileInfoSetIsHiddenMethodInfo
    ResolveFileInfoMethod "setIsSymlink" o = FileInfoSetIsSymlinkMethodInfo
    ResolveFileInfoMethod "setModificationTime" o = FileInfoSetModificationTimeMethodInfo
    ResolveFileInfoMethod "setName" o = FileInfoSetNameMethodInfo
    ResolveFileInfoMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveFileInfoMethod "setSize" o = FileInfoSetSizeMethodInfo
    ResolveFileInfoMethod "setSortOrder" o = FileInfoSetSortOrderMethodInfo
    ResolveFileInfoMethod "setSymbolicIcon" o = FileInfoSetSymbolicIconMethodInfo
    ResolveFileInfoMethod "setSymlinkTarget" o = FileInfoSetSymlinkTargetMethodInfo
    ResolveFileInfoMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFileInfoMethod t FileInfo, O.MethodInfo info FileInfo p) => OL.IsLabel t (FileInfo -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FileInfo
type instance O.AttributeList FileInfo = FileInfoAttributeList
type FileInfoAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

foreign import ccall "g_file_info_new" g_file_info_new :: 
    IO (Ptr FileInfo)

-- | Creates a new file info structure.
fileInfoNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m FileInfo
    -- ^ __Returns:__ a t'GI.Gio.Objects.FileInfo.FileInfo'.
fileInfoNew :: m FileInfo
fileInfoNew  = IO FileInfo -> m FileInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileInfo -> m FileInfo) -> IO FileInfo -> m FileInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
result <- IO (Ptr FileInfo)
g_file_info_new
    Text -> Ptr FileInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoNew" Ptr FileInfo
result
    FileInfo
result' <- ((ManagedPtr FileInfo -> FileInfo) -> Ptr FileInfo -> IO FileInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr FileInfo -> FileInfo
FileInfo) Ptr FileInfo
result
    FileInfo -> IO FileInfo
forall (m :: * -> *) a. Monad m => a -> m a
return FileInfo
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FileInfo::clear_status
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_clear_status" g_file_info_clear_status :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO ()

-- | Clears the status information from /@info@/.
fileInfoClearStatus ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m ()
fileInfoClearStatus :: a -> m ()
fileInfoClearStatus info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr FileInfo -> IO ()
g_file_info_clear_status Ptr FileInfo
info'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoClearStatusMethodInfo
instance (signature ~ (m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoClearStatusMethodInfo a signature where
    overloadedMethod = fileInfoClearStatus

#endif

-- method FileInfo::copy_into
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src_info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "source to copy attributes from."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest_info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "destination to copy attributes to."
--                 , 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_info_copy_into" g_file_info_copy_into :: 
    Ptr FileInfo ->                         -- src_info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr FileInfo ->                         -- dest_info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO ()

-- | First clears all of the [GFileAttribute][gio-GFileAttribute] of /@destInfo@/,
-- and then copies all of the file attributes from /@srcInfo@/ to /@destInfo@/.
fileInfoCopyInto ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a, IsFileInfo b) =>
    a
    -- ^ /@srcInfo@/: source to copy attributes from.
    -> b
    -- ^ /@destInfo@/: destination to copy attributes to.
    -> m ()
fileInfoCopyInto :: a -> b -> m ()
fileInfoCopyInto srcInfo :: a
srcInfo destInfo :: b
destInfo = 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 FileInfo
srcInfo' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
srcInfo
    Ptr FileInfo
destInfo' <- b -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
destInfo
    Ptr FileInfo -> Ptr FileInfo -> IO ()
g_file_info_copy_into Ptr FileInfo
srcInfo' Ptr FileInfo
destInfo'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
srcInfo
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
destInfo
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoCopyIntoMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsFileInfo a, IsFileInfo b) => O.MethodInfo FileInfoCopyIntoMethodInfo a signature where
    overloadedMethod = fileInfoCopyInto

#endif

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

foreign import ccall "g_file_info_dup" g_file_info_dup :: 
    Ptr FileInfo ->                         -- other : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO (Ptr FileInfo)

-- | Duplicates a file info structure.
fileInfoDup ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@other@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m FileInfo
    -- ^ __Returns:__ a duplicate t'GI.Gio.Objects.FileInfo.FileInfo' of /@other@/.
fileInfoDup :: a -> m FileInfo
fileInfoDup other :: a
other = IO FileInfo -> m FileInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileInfo -> m FileInfo) -> IO FileInfo -> m FileInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
other' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
other
    Ptr FileInfo
result <- Ptr FileInfo -> IO (Ptr FileInfo)
g_file_info_dup Ptr FileInfo
other'
    Text -> Ptr FileInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoDup" Ptr FileInfo
result
    FileInfo
result' <- ((ManagedPtr FileInfo -> FileInfo) -> Ptr FileInfo -> IO FileInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr FileInfo -> FileInfo
FileInfo) Ptr FileInfo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
other
    FileInfo -> IO FileInfo
forall (m :: * -> *) a. Monad m => a -> m a
return FileInfo
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoDupMethodInfo
instance (signature ~ (m FileInfo), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoDupMethodInfo a signature where
    overloadedMethod = fileInfoDup

#endif

-- method FileInfo::get_attribute_as_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_as_string" g_file_info_get_attribute_as_string :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CString

-- | Gets the value of a attribute, formated as a string.
-- This escapes things as needed to make the string valid
-- utf8.
fileInfoGetAttributeAsString ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m T.Text
    -- ^ __Returns:__ a UTF-8 string associated with the given /@attribute@/.
    --    When you\'re done with the string it must be freed with 'GI.GLib.Functions.free'.
fileInfoGetAttributeAsString :: a -> Text -> m Text
fileInfoGetAttributeAsString info :: a
info attribute :: Text
attribute = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CString
result <- Ptr FileInfo -> CString -> IO CString
g_file_info_get_attribute_as_string Ptr FileInfo
info' CString
attribute'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetAttributeAsString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeAsStringMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeAsStringMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeAsString

#endif

-- method FileInfo::get_attribute_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_attribute_boolean" g_file_info_get_attribute_boolean :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CInt

-- | Gets the value of a boolean attribute. If the attribute does not
-- contain a boolean value, 'P.False' will be returned.
fileInfoGetAttributeBoolean ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Bool
    -- ^ __Returns:__ the boolean value contained within the attribute.
fileInfoGetAttributeBoolean :: a -> Text -> m Bool
fileInfoGetAttributeBoolean info :: a
info 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CInt
result <- Ptr FileInfo -> CString -> IO CInt
g_file_info_get_attribute_boolean Ptr FileInfo
info' CString
attribute'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    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 FileInfoGetAttributeBooleanMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeBooleanMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeBoolean

#endif

-- method FileInfo::get_attribute_byte_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_byte_string" g_file_info_get_attribute_byte_string :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CString

-- | Gets the value of a byte string attribute. If the attribute does
-- not contain a byte string, 'P.Nothing' will be returned.
fileInfoGetAttributeByteString ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m T.Text
    -- ^ __Returns:__ the contents of the /@attribute@/ value as a byte string, or
    -- 'P.Nothing' otherwise.
fileInfoGetAttributeByteString :: a -> Text -> m Text
fileInfoGetAttributeByteString info :: a
info attribute :: Text
attribute = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CString
result <- Ptr FileInfo -> CString -> IO CString
g_file_info_get_attribute_byte_string Ptr FileInfo
info' CString
attribute'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetAttributeByteString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeByteStringMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeByteStringMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeByteString

#endif

-- method FileInfo::get_attribute_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo" , 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
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileAttributeType" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the attribute type, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "value_pp"
--           , argType = TBasicType TPtr
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the\n   attribute value, or %NULL; the attribute value will not be %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "status"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "FileAttributeStatus" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the attribute status, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_data" g_file_info_get_attribute_data :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    Ptr CUInt ->                            -- type : TInterface (Name {namespace = "Gio", name = "FileAttributeType"})
    Ptr (Ptr ()) ->                         -- value_pp : TBasicType TPtr
    Ptr CUInt ->                            -- status : TInterface (Name {namespace = "Gio", name = "FileAttributeStatus"})
    IO CInt

-- | Gets the attribute type, value and status for an attribute key.
fileInfoGetAttributeData ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'
    -> T.Text
    -- ^ /@attribute@/: a file attribute key
    -> m ((Bool, Gio.Enums.FileAttributeType, Ptr (), Gio.Enums.FileAttributeStatus))
    -- ^ __Returns:__ 'P.True' if /@info@/ has an attribute named /@attribute@/,
    --      'P.False' otherwise.
fileInfoGetAttributeData :: a
-> Text -> m (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
fileInfoGetAttributeData info :: a
info attribute :: Text
attribute = IO (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
-> m (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
 -> m (Bool, FileAttributeType, Ptr (), FileAttributeStatus))
-> IO (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
-> m (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr CUInt
type_ <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    Ptr (Ptr ())
valuePp <- IO (Ptr (Ptr ()))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr ()))
    Ptr CUInt
status <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    CInt
result <- Ptr FileInfo
-> CString -> Ptr CUInt -> Ptr (Ptr ()) -> Ptr CUInt -> IO CInt
g_file_info_get_attribute_data Ptr FileInfo
info' CString
attribute' Ptr CUInt
type_ Ptr (Ptr ())
valuePp Ptr CUInt
status
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    CUInt
type_' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
type_
    let type_'' :: FileAttributeType
type_'' = (Int -> FileAttributeType
forall a. Enum a => Int -> a
toEnum (Int -> FileAttributeType)
-> (CUInt -> Int) -> CUInt -> FileAttributeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
type_'
    Ptr ()
valuePp' <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr ())
valuePp
    CUInt
status' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
status
    let status'' :: FileAttributeStatus
status'' = (Int -> FileAttributeStatus
forall a. Enum a => Int -> a
toEnum (Int -> FileAttributeStatus)
-> (CUInt -> Int) -> CUInt -> FileAttributeStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
status'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
type_
    Ptr (Ptr ()) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr ())
valuePp
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
status
    (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
-> IO (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', FileAttributeType
type_'', Ptr ()
valuePp', FileAttributeStatus
status'')

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeDataMethodInfo
instance (signature ~ (T.Text -> m ((Bool, Gio.Enums.FileAttributeType, Ptr (), Gio.Enums.FileAttributeStatus))), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeDataMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeData

#endif

-- method FileInfo::get_attribute_int32
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 TInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_int32" g_file_info_get_attribute_int32 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO Int32

-- | Gets a signed 32-bit integer contained within the attribute. If the
-- attribute does not contain a signed 32-bit integer, or is invalid,
-- 0 will be returned.
fileInfoGetAttributeInt32 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Int32
    -- ^ __Returns:__ a signed 32-bit integer from the attribute.
fileInfoGetAttributeInt32 :: a -> Text -> m Int32
fileInfoGetAttributeInt32 info :: a
info attribute :: Text
attribute = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Int32
result <- Ptr FileInfo -> CString -> IO Int32
g_file_info_get_attribute_int32 Ptr FileInfo
info' CString
attribute'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeInt32MethodInfo
instance (signature ~ (T.Text -> m Int32), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeInt32MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeInt32

#endif

-- method FileInfo::get_attribute_int64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 TInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_int64" g_file_info_get_attribute_int64 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO Int64

-- | Gets a signed 64-bit integer contained within the attribute. If the
-- attribute does not contain an signed 64-bit integer, or is invalid,
-- 0 will be returned.
fileInfoGetAttributeInt64 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Int64
    -- ^ __Returns:__ a signed 64-bit integer from the attribute.
fileInfoGetAttributeInt64 :: a -> Text -> m Int64
fileInfoGetAttributeInt64 info :: a
info attribute :: Text
attribute = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Int64
result <- Ptr FileInfo -> CString -> IO Int64
g_file_info_get_attribute_int64 Ptr FileInfo
info' CString
attribute'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeInt64MethodInfo
instance (signature ~ (T.Text -> m Int64), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeInt64MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeInt64

#endif

-- method FileInfo::get_attribute_object
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 (TInterface Name { namespace = "GObject" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_object" g_file_info_get_attribute_object :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO (Ptr GObject.Object.Object)

-- | Gets the value of a t'GI.GObject.Objects.Object.Object' attribute. If the attribute does
-- not contain a t'GI.GObject.Objects.Object.Object', 'P.Nothing' will be returned.
fileInfoGetAttributeObject ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m GObject.Object.Object
    -- ^ __Returns:__ a t'GI.GObject.Objects.Object.Object' associated with the given /@attribute@/, or
    -- 'P.Nothing' otherwise.
fileInfoGetAttributeObject :: a -> Text -> m Object
fileInfoGetAttributeObject info :: a
info attribute :: Text
attribute = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr Object
result <- Ptr FileInfo -> CString -> IO (Ptr Object)
g_file_info_get_attribute_object Ptr FileInfo
info' CString
attribute'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetAttributeObject" Ptr Object
result
    Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeObjectMethodInfo
instance (signature ~ (T.Text -> m GObject.Object.Object), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeObjectMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeObject

#endif

-- method FileInfo::get_attribute_status
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo" , 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
--               (TInterface
--                  Name { namespace = "Gio" , name = "FileAttributeStatus" })
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_status" g_file_info_get_attribute_status :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CUInt

-- | Gets the attribute status for an attribute key.
fileInfoGetAttributeStatus ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'
    -> T.Text
    -- ^ /@attribute@/: a file attribute key
    -> m Gio.Enums.FileAttributeStatus
    -- ^ __Returns:__ a t'GI.Gio.Enums.FileAttributeStatus' for the given /@attribute@/, or
    --    'GI.Gio.Enums.FileAttributeStatusUnset' if the key is invalid.
fileInfoGetAttributeStatus :: a -> Text -> m FileAttributeStatus
fileInfoGetAttributeStatus info :: a
info attribute :: Text
attribute = IO FileAttributeStatus -> m FileAttributeStatus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileAttributeStatus -> m FileAttributeStatus)
-> IO FileAttributeStatus -> m FileAttributeStatus
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CUInt
result <- Ptr FileInfo -> CString -> IO CUInt
g_file_info_get_attribute_status Ptr FileInfo
info' CString
attribute'
    let result' :: FileAttributeStatus
result' = (Int -> FileAttributeStatus
forall a. Enum a => Int -> a
toEnum (Int -> FileAttributeStatus)
-> (CUInt -> Int) -> CUInt -> FileAttributeStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    FileAttributeStatus -> IO FileAttributeStatus
forall (m :: * -> *) a. Monad m => a -> m a
return FileAttributeStatus
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeStatusMethodInfo
instance (signature ~ (T.Text -> m Gio.Enums.FileAttributeStatus), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeStatusMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeStatus

#endif

-- method FileInfo::get_attribute_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_string" g_file_info_get_attribute_string :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CString

-- | Gets the value of a string attribute. If the attribute does
-- not contain a string, 'P.Nothing' will be returned.
fileInfoGetAttributeString ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m T.Text
    -- ^ __Returns:__ the contents of the /@attribute@/ value as a UTF-8 string, or
    -- 'P.Nothing' otherwise.
fileInfoGetAttributeString :: a -> Text -> m Text
fileInfoGetAttributeString info :: a
info attribute :: Text
attribute = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CString
result <- Ptr FileInfo -> CString -> IO CString
g_file_info_get_attribute_string Ptr FileInfo
info' CString
attribute'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetAttributeString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeStringMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeStringMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeString

#endif

-- method FileInfo::get_attribute_stringv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_stringv" g_file_info_get_attribute_stringv :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO (Ptr CString)

-- | Gets the value of a stringv attribute. If the attribute does
-- not contain a stringv, 'P.Nothing' will be returned.
-- 
-- /Since: 2.22/
fileInfoGetAttributeStringv ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m [T.Text]
    -- ^ __Returns:__ the contents of the /@attribute@/ value as a stringv, or
    -- 'P.Nothing' otherwise. Do not free. These returned strings are UTF-8.
fileInfoGetAttributeStringv :: a -> Text -> m [Text]
fileInfoGetAttributeStringv info :: a
info attribute :: Text
attribute = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr CString
result <- Ptr FileInfo -> CString -> IO (Ptr CString)
g_file_info_get_attribute_stringv Ptr FileInfo
info' CString
attribute'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetAttributeStringv" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeStringvMethodInfo
instance (signature ~ (T.Text -> m [T.Text]), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeStringvMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeStringv

#endif

-- method FileInfo::get_attribute_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--               (TInterface
--                  Name { namespace = "Gio" , name = "FileAttributeType" })
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_type" g_file_info_get_attribute_type :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CUInt

-- | Gets the attribute type for an attribute key.
fileInfoGetAttributeType ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Gio.Enums.FileAttributeType
    -- ^ __Returns:__ a t'GI.Gio.Enums.FileAttributeType' for the given /@attribute@/, or
    -- 'GI.Gio.Enums.FileAttributeTypeInvalid' if the key is not set.
fileInfoGetAttributeType :: a -> Text -> m FileAttributeType
fileInfoGetAttributeType info :: a
info attribute :: Text
attribute = IO FileAttributeType -> m FileAttributeType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileAttributeType -> m FileAttributeType)
-> IO FileAttributeType -> m FileAttributeType
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CUInt
result <- Ptr FileInfo -> CString -> IO CUInt
g_file_info_get_attribute_type Ptr FileInfo
info' CString
attribute'
    let result' :: FileAttributeType
result' = (Int -> FileAttributeType
forall a. Enum a => Int -> a
toEnum (Int -> FileAttributeType)
-> (CUInt -> Int) -> CUInt -> FileAttributeType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    FileAttributeType -> IO FileAttributeType
forall (m :: * -> *) a. Monad m => a -> m a
return FileAttributeType
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeTypeMethodInfo
instance (signature ~ (T.Text -> m Gio.Enums.FileAttributeType), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeTypeMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeType

#endif

-- method FileInfo::get_attribute_uint32
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_uint32" g_file_info_get_attribute_uint32 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO Word32

-- | Gets an unsigned 32-bit integer contained within the attribute. If the
-- attribute does not contain an unsigned 32-bit integer, or is invalid,
-- 0 will be returned.
fileInfoGetAttributeUint32 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Word32
    -- ^ __Returns:__ an unsigned 32-bit integer from the attribute.
fileInfoGetAttributeUint32 :: a -> Text -> m Word32
fileInfoGetAttributeUint32 info :: a
info attribute :: Text
attribute = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Word32
result <- Ptr FileInfo -> CString -> IO Word32
g_file_info_get_attribute_uint32 Ptr FileInfo
info' CString
attribute'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeUint32MethodInfo
instance (signature ~ (T.Text -> m Word32), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeUint32MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeUint32

#endif

-- method FileInfo::get_attribute_uint64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_attribute_uint64" g_file_info_get_attribute_uint64 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO Word64

-- | Gets a unsigned 64-bit integer contained within the attribute. If the
-- attribute does not contain an unsigned 64-bit integer, or is invalid,
-- 0 will be returned.
fileInfoGetAttributeUint64 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Word64
    -- ^ __Returns:__ a unsigned 64-bit integer from the attribute.
fileInfoGetAttributeUint64 :: a -> Text -> m Word64
fileInfoGetAttributeUint64 info :: a
info attribute :: Text
attribute = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Word64
result <- Ptr FileInfo -> CString -> IO Word64
g_file_info_get_attribute_uint64 Ptr FileInfo
info' CString
attribute'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAttributeUint64MethodInfo
instance (signature ~ (T.Text -> m Word64), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetAttributeUint64MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeUint64

#endif

-- method FileInfo::get_content_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_content_type" g_file_info_get_content_type :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CString

-- | Gets the file\'s content type.
fileInfoGetContentType ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m T.Text
    -- ^ __Returns:__ a string containing the file\'s content type.
fileInfoGetContentType :: a -> m Text
fileInfoGetContentType info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr FileInfo -> IO CString
g_file_info_get_content_type Ptr FileInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetContentType" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetContentTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetContentTypeMethodInfo a signature where
    overloadedMethod = fileInfoGetContentType

#endif

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

foreign import ccall "g_file_info_get_deletion_date" g_file_info_get_deletion_date :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO (Ptr GLib.DateTime.DateTime)

-- | Returns the t'GI.GLib.Structs.DateTime.DateTime' representing the deletion date of the file, as
-- available in G_FILE_ATTRIBUTE_TRASH_DELETION_DATE. If the
-- G_FILE_ATTRIBUTE_TRASH_DELETION_DATE attribute is unset, 'P.Nothing' is returned.
-- 
-- /Since: 2.36/
fileInfoGetDeletionDate ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m GLib.DateTime.DateTime
    -- ^ __Returns:__ a t'GI.GLib.Structs.DateTime.DateTime', or 'P.Nothing'.
fileInfoGetDeletionDate :: a -> m DateTime
fileInfoGetDeletionDate info :: a
info = IO DateTime -> m DateTime
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DateTime -> m DateTime) -> IO DateTime -> m DateTime
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr DateTime
result <- Ptr FileInfo -> IO (Ptr DateTime)
g_file_info_get_deletion_date Ptr FileInfo
info'
    Text -> Ptr DateTime -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetDeletionDate" Ptr DateTime
result
    DateTime
result' <- ((ManagedPtr DateTime -> DateTime) -> Ptr DateTime -> IO DateTime
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime) Ptr DateTime
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    DateTime -> IO DateTime
forall (m :: * -> *) a. Monad m => a -> m a
return DateTime
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetDeletionDateMethodInfo
instance (signature ~ (m GLib.DateTime.DateTime), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetDeletionDateMethodInfo a signature where
    overloadedMethod = fileInfoGetDeletionDate

#endif

-- method FileInfo::get_display_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_display_name" g_file_info_get_display_name :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CString

-- | Gets a display name for a file.
fileInfoGetDisplayName ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m T.Text
    -- ^ __Returns:__ a string containing the display name.
fileInfoGetDisplayName :: a -> m Text
fileInfoGetDisplayName info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr FileInfo -> IO CString
g_file_info_get_display_name Ptr FileInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetDisplayName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetDisplayNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetDisplayNameMethodInfo a signature where
    overloadedMethod = fileInfoGetDisplayName

#endif

-- method FileInfo::get_edit_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_edit_name" g_file_info_get_edit_name :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CString

-- | Gets the edit name for a file.
fileInfoGetEditName ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m T.Text
    -- ^ __Returns:__ a string containing the edit name.
fileInfoGetEditName :: a -> m Text
fileInfoGetEditName info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr FileInfo -> IO CString
g_file_info_get_edit_name Ptr FileInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetEditName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetEditNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetEditNameMethodInfo a signature where
    overloadedMethod = fileInfoGetEditName

#endif

-- method FileInfo::get_etag
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_etag" g_file_info_get_etag :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CString

-- | Gets the [entity tag][gfile-etag] for a given
-- t'GI.Gio.Objects.FileInfo.FileInfo'. See 'GI.Gio.Constants.FILE_ATTRIBUTE_ETAG_VALUE'.
fileInfoGetEtag ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m T.Text
    -- ^ __Returns:__ a string containing the value of the \"etag:value\" attribute.
fileInfoGetEtag :: a -> m Text
fileInfoGetEtag info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr FileInfo -> IO CString
g_file_info_get_etag Ptr FileInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetEtag" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetEtagMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetEtagMethodInfo a signature where
    overloadedMethod = fileInfoGetEtag

#endif

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

foreign import ccall "g_file_info_get_file_type" g_file_info_get_file_type :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CUInt

-- | Gets a file\'s type (whether it is a regular file, symlink, etc).
-- This is different from the file\'s content type, see 'GI.Gio.Objects.FileInfo.fileInfoGetContentType'.
fileInfoGetFileType ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Gio.Enums.FileType
    -- ^ __Returns:__ a t'GI.Gio.Enums.FileType' for the given file.
fileInfoGetFileType :: a -> m FileType
fileInfoGetFileType info :: a
info = IO FileType -> m FileType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileType -> m FileType) -> IO FileType -> m FileType
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CUInt
result <- Ptr FileInfo -> IO CUInt
g_file_info_get_file_type Ptr FileInfo
info'
    let result' :: FileType
result' = (Int -> FileType
forall a. Enum a => Int -> a
toEnum (Int -> FileType) -> (CUInt -> Int) -> CUInt -> FileType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    FileType -> IO FileType
forall (m :: * -> *) a. Monad m => a -> m a
return FileType
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetFileTypeMethodInfo
instance (signature ~ (m Gio.Enums.FileType), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetFileTypeMethodInfo a signature where
    overloadedMethod = fileInfoGetFileType

#endif

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

foreign import ccall "g_file_info_get_icon" g_file_info_get_icon :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO (Ptr Gio.Icon.Icon)

-- | Gets the icon for a file.
fileInfoGetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Gio.Icon.Icon
    -- ^ __Returns:__ t'GI.Gio.Interfaces.Icon.Icon' for the given /@info@/.
fileInfoGetIcon :: a -> m Icon
fileInfoGetIcon info :: a
info = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr Icon
result <- Ptr FileInfo -> IO (Ptr Icon)
g_file_info_get_icon Ptr FileInfo
info'
    Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetIcon" Ptr Icon
result
    Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetIconMethodInfo
instance (signature ~ (m Gio.Icon.Icon), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetIconMethodInfo a signature where
    overloadedMethod = fileInfoGetIcon

#endif

-- method FileInfo::get_is_backup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_is_backup" g_file_info_get_is_backup :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CInt

-- | Checks if a file is a backup file.
fileInfoGetIsBackup ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if file is a backup file, 'P.False' otherwise.
fileInfoGetIsBackup :: a -> m Bool
fileInfoGetIsBackup info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CInt
result <- Ptr FileInfo -> IO CInt
g_file_info_get_is_backup Ptr FileInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetIsBackupMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetIsBackupMethodInfo a signature where
    overloadedMethod = fileInfoGetIsBackup

#endif

-- method FileInfo::get_is_hidden
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_is_hidden" g_file_info_get_is_hidden :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CInt

-- | Checks if a file is hidden.
fileInfoGetIsHidden ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the file is a hidden file, 'P.False' otherwise.
fileInfoGetIsHidden :: a -> m Bool
fileInfoGetIsHidden info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CInt
result <- Ptr FileInfo -> IO CInt
g_file_info_get_is_hidden Ptr FileInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetIsHiddenMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetIsHiddenMethodInfo a signature where
    overloadedMethod = fileInfoGetIsHidden

#endif

-- method FileInfo::get_is_symlink
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_is_symlink" g_file_info_get_is_symlink :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CInt

-- | Checks if a file is a symlink.
fileInfoGetIsSymlink ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the given /@info@/ is a symlink.
fileInfoGetIsSymlink :: a -> m Bool
fileInfoGetIsSymlink info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CInt
result <- Ptr FileInfo -> IO CInt
g_file_info_get_is_symlink Ptr FileInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetIsSymlinkMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetIsSymlinkMethodInfo a signature where
    overloadedMethod = fileInfoGetIsSymlink

#endif

-- method FileInfo::get_modification_time
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "TimeVal" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTimeVal." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_get_modification_time" g_file_info_get_modification_time :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr GLib.TimeVal.TimeVal ->             -- result : TInterface (Name {namespace = "GLib", name = "TimeVal"})
    IO ()

-- | Gets the modification time of the current /@info@/ and sets it
-- in /@result@/.
fileInfoGetModificationTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m (GLib.TimeVal.TimeVal)
fileInfoGetModificationTime :: a -> m TimeVal
fileInfoGetModificationTime info :: a
info = IO TimeVal -> m TimeVal
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TimeVal -> m TimeVal) -> IO TimeVal -> m TimeVal
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr TimeVal
result_ <- Int -> IO (Ptr TimeVal)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr GLib.TimeVal.TimeVal)
    Ptr FileInfo -> Ptr TimeVal -> IO ()
g_file_info_get_modification_time Ptr FileInfo
info' Ptr TimeVal
result_
    TimeVal
result_' <- ((ManagedPtr TimeVal -> TimeVal) -> Ptr TimeVal -> IO TimeVal
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TimeVal -> TimeVal
GLib.TimeVal.TimeVal) Ptr TimeVal
result_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    TimeVal -> IO TimeVal
forall (m :: * -> *) a. Monad m => a -> m a
return TimeVal
result_'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetModificationTimeMethodInfo
instance (signature ~ (m (GLib.TimeVal.TimeVal)), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetModificationTimeMethodInfo a signature where
    overloadedMethod = fileInfoGetModificationTime

#endif

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

foreign import ccall "g_file_info_get_name" g_file_info_get_name :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CString

-- | Gets the name for a file.
fileInfoGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m [Char]
    -- ^ __Returns:__ a string containing the file name.
fileInfoGetName :: a -> m [Char]
fileInfoGetName info :: a
info = IO [Char] -> m [Char]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> m [Char]) -> IO [Char] -> m [Char]
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr FileInfo -> IO CString
g_file_info_get_name Ptr FileInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetName" CString
result
    [Char]
result' <- HasCallStack => CString -> IO [Char]
CString -> IO [Char]
cstringToString CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    [Char] -> IO [Char]
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetNameMethodInfo
instance (signature ~ (m [Char]), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetNameMethodInfo a signature where
    overloadedMethod = fileInfoGetName

#endif

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

foreign import ccall "g_file_info_get_size" g_file_info_get_size :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO Int64

-- | Gets the file\'s size.
fileInfoGetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Int64
    -- ^ __Returns:__ a @/goffset/@ containing the file\'s size.
fileInfoGetSize :: a -> m Int64
fileInfoGetSize info :: a
info = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Int64
result <- Ptr FileInfo -> IO Int64
g_file_info_get_size Ptr FileInfo
info'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result

#if defined(ENABLE_OVERLOADING)
data FileInfoGetSizeMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetSizeMethodInfo a signature where
    overloadedMethod = fileInfoGetSize

#endif

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

foreign import ccall "g_file_info_get_sort_order" g_file_info_get_sort_order :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO Int32

-- | Gets the value of the sort_order attribute from the t'GI.Gio.Objects.FileInfo.FileInfo'.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_SORT_ORDER'.
fileInfoGetSortOrder ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Int32
    -- ^ __Returns:__ a @/gint32/@ containing the value of the \"standard[sort_order](#signal:sort_order)\" attribute.
fileInfoGetSortOrder :: a -> m Int32
fileInfoGetSortOrder info :: a
info = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Int32
result <- Ptr FileInfo -> IO Int32
g_file_info_get_sort_order Ptr FileInfo
info'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data FileInfoGetSortOrderMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetSortOrderMethodInfo a signature where
    overloadedMethod = fileInfoGetSortOrder

#endif

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

foreign import ccall "g_file_info_get_symbolic_icon" g_file_info_get_symbolic_icon :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO (Ptr Gio.Icon.Icon)

-- | Gets the symbolic icon for a file.
-- 
-- /Since: 2.34/
fileInfoGetSymbolicIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m Gio.Icon.Icon
    -- ^ __Returns:__ t'GI.Gio.Interfaces.Icon.Icon' for the given /@info@/.
fileInfoGetSymbolicIcon :: a -> m Icon
fileInfoGetSymbolicIcon info :: a
info = IO Icon -> m Icon
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Icon -> m Icon) -> IO Icon -> m Icon
forall a b. (a -> b) -> a -> b
$ do
    Ptr FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr Icon
result <- Ptr FileInfo -> IO (Ptr Icon)
g_file_info_get_symbolic_icon Ptr FileInfo
info'
    Text -> Ptr Icon -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetSymbolicIcon" Ptr Icon
result
    Icon
result' <- ((ManagedPtr Icon -> Icon) -> Ptr Icon -> IO Icon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetSymbolicIconMethodInfo
instance (signature ~ (m Gio.Icon.Icon), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetSymbolicIconMethodInfo a signature where
    overloadedMethod = fileInfoGetSymbolicIcon

#endif

-- method FileInfo::get_symlink_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_get_symlink_target" g_file_info_get_symlink_target :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO CString

-- | Gets the symlink target for a given t'GI.Gio.Objects.FileInfo.FileInfo'.
fileInfoGetSymlinkTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m T.Text
    -- ^ __Returns:__ a string containing the symlink target.
fileInfoGetSymlinkTarget :: a -> m Text
fileInfoGetSymlinkTarget info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr FileInfo -> IO CString
g_file_info_get_symlink_target Ptr FileInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fileInfoGetSymlinkTarget" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoGetSymlinkTargetMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoGetSymlinkTargetMethodInfo a signature where
    overloadedMethod = fileInfoGetSymlinkTarget

#endif

-- method FileInfo::has_attribute
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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_info_has_attribute" g_file_info_has_attribute :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO CInt

-- | Checks if a file info structure has an attribute named /@attribute@/.
fileInfoHasAttribute ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@ginfo@/ has an attribute named /@attribute@/,
    --     'P.False' otherwise.
fileInfoHasAttribute :: a -> Text -> m Bool
fileInfoHasAttribute info :: a
info 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CInt
result <- Ptr FileInfo -> CString -> IO CInt
g_file_info_has_attribute Ptr FileInfo
info' CString
attribute'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    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 FileInfoHasAttributeMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoHasAttributeMethodInfo a signature where
    overloadedMethod = fileInfoHasAttribute

#endif

-- method FileInfo::has_namespace
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name_space"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "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_info_has_namespace" g_file_info_has_namespace :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- name_space : TBasicType TUTF8
    IO CInt

-- | Checks if a file info structure has an attribute in the
-- specified /@nameSpace@/.
-- 
-- /Since: 2.22/
fileInfoHasNamespace ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@nameSpace@/: a file attribute namespace.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@ginfo@/ has an attribute in /@nameSpace@/,
    --     'P.False' otherwise.
fileInfoHasNamespace :: a -> Text -> m Bool
fileInfoHasNamespace info :: a
info nameSpace :: Text
nameSpace = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
nameSpace' <- Text -> IO CString
textToCString Text
nameSpace
    CInt
result <- Ptr FileInfo -> CString -> IO CInt
g_file_info_has_namespace Ptr FileInfo
info' CString
nameSpace'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
nameSpace'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FileInfoHasNamespaceMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoHasNamespaceMethodInfo a signature where
    overloadedMethod = fileInfoHasNamespace

#endif

-- method FileInfo::list_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name_space"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a file attribute key's namespace, or %NULL to list\n  all attributes."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_list_attributes" g_file_info_list_attributes :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- name_space : TBasicType TUTF8
    IO (Ptr CString)

-- | Lists the file info structure\'s attributes.
fileInfoListAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> Maybe (T.Text)
    -- ^ /@nameSpace@/: a file attribute key\'s namespace, or 'P.Nothing' to list
    --   all attributes.
    -> m (Maybe [T.Text])
    -- ^ __Returns:__ a
    -- null-terminated array of strings of all of the possible attribute
    -- types for the given /@nameSpace@/, or 'P.Nothing' on error.
fileInfoListAttributes :: a -> Maybe Text -> m (Maybe [Text])
fileInfoListAttributes info :: a
info nameSpace :: Maybe Text
nameSpace = IO (Maybe [Text]) -> m (Maybe [Text])
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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
maybeNameSpace <- case Maybe Text
nameSpace of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jNameSpace :: Text
jNameSpace -> do
            CString
jNameSpace' <- Text -> IO CString
textToCString Text
jNameSpace
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jNameSpace'
    Ptr CString
result <- Ptr FileInfo -> CString -> IO (Ptr CString)
g_file_info_list_attributes Ptr FileInfo
info' CString
maybeNameSpace
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeNameSpace
    Maybe [Text] -> IO (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

#if defined(ENABLE_OVERLOADING)
data FileInfoListAttributesMethodInfo
instance (signature ~ (Maybe (T.Text) -> m (Maybe [T.Text])), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoListAttributesMethodInfo a signature where
    overloadedMethod = fileInfoListAttributes

#endif

-- method FileInfo::remove_attribute
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_remove_attribute" g_file_info_remove_attribute :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    IO ()

-- | Removes all cases of /@attribute@/ from /@info@/ if it exists.
fileInfoRemoveAttribute ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> m ()
fileInfoRemoveAttribute :: a -> Text -> m ()
fileInfoRemoveAttribute info :: a
info attribute :: Text
attribute = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr FileInfo -> CString -> IO ()
g_file_info_remove_attribute Ptr FileInfo
info' CString
attribute'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoRemoveAttributeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoRemoveAttributeMethodInfo a signature where
    overloadedMethod = fileInfoRemoveAttribute

#endif

-- method FileInfo::set_attribute
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileAttributeType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileAttributeType"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value_p"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_set_attribute" g_file_info_set_attribute :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    CUInt ->                                -- type : TInterface (Name {namespace = "Gio", name = "FileAttributeType"})
    Ptr () ->                               -- value_p : TBasicType TPtr
    IO ()

-- | Sets the /@attribute@/ to contain the given value, if possible. To unset the
-- attribute, use 'GI.Gio.Enums.FileAttributeTypeInvalid' for /@type@/.
fileInfoSetAttribute ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> Gio.Enums.FileAttributeType
    -- ^ /@type@/: a t'GI.Gio.Enums.FileAttributeType'
    -> Ptr ()
    -- ^ /@valueP@/: pointer to the value
    -> m ()
fileInfoSetAttribute :: a -> Text -> FileAttributeType -> Ptr () -> m ()
fileInfoSetAttribute info :: a
info attribute :: Text
attribute type_ :: FileAttributeType
type_ valueP :: Ptr ()
valueP = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (FileAttributeType -> Int) -> FileAttributeType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileAttributeType -> Int
forall a. Enum a => a -> Int
fromEnum) FileAttributeType
type_
    Ptr FileInfo -> CString -> CUInt -> Ptr () -> IO ()
g_file_info_set_attribute Ptr FileInfo
info' CString
attribute' CUInt
type_' Ptr ()
valueP
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeMethodInfo
instance (signature ~ (T.Text -> Gio.Enums.FileAttributeType -> Ptr () -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeMethodInfo a signature where
    overloadedMethod = fileInfoSetAttribute

#endif

-- method FileInfo::set_attribute_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a boolean value." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_set_attribute_boolean" g_file_info_set_attribute_boolean :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    CInt ->                                 -- attr_value : TBasicType TBoolean
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeBoolean ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> Bool
    -- ^ /@attrValue@/: a boolean value.
    -> m ()
fileInfoSetAttributeBoolean :: a -> Text -> Bool -> m ()
fileInfoSetAttributeBoolean info :: a
info attribute :: Text
attribute attrValue :: Bool
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    let attrValue' :: CInt
attrValue' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
attrValue
    Ptr FileInfo -> CString -> CInt -> IO ()
g_file_info_set_attribute_boolean Ptr FileInfo
info' CString
attribute' CInt
attrValue'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeBooleanMethodInfo
instance (signature ~ (T.Text -> Bool -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeBooleanMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeBoolean

#endif

-- method FileInfo::set_attribute_byte_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a byte string." , 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_info_set_attribute_byte_string" g_file_info_set_attribute_byte_string :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    CString ->                              -- attr_value : TBasicType TUTF8
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeByteString ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> T.Text
    -- ^ /@attrValue@/: a byte string.
    -> m ()
fileInfoSetAttributeByteString :: a -> Text -> Text -> m ()
fileInfoSetAttributeByteString info :: a
info attribute :: Text
attribute attrValue :: Text
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CString
attrValue' <- Text -> IO CString
textToCString Text
attrValue
    Ptr FileInfo -> CString -> CString -> IO ()
g_file_info_set_attribute_byte_string Ptr FileInfo
info' CString
attribute' CString
attrValue'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attrValue'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeByteStringMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeByteStringMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeByteString

#endif

-- method FileInfo::set_attribute_int32
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TBasicType TInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a signed 32-bit integer"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_set_attribute_int32" g_file_info_set_attribute_int32 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    Int32 ->                                -- attr_value : TBasicType TInt32
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeInt32 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> Int32
    -- ^ /@attrValue@/: a signed 32-bit integer
    -> m ()
fileInfoSetAttributeInt32 :: a -> Text -> Int32 -> m ()
fileInfoSetAttributeInt32 info :: a
info attribute :: Text
attribute attrValue :: Int32
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr FileInfo -> CString -> Int32 -> IO ()
g_file_info_set_attribute_int32 Ptr FileInfo
info' CString
attribute' Int32
attrValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeInt32MethodInfo
instance (signature ~ (T.Text -> Int32 -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeInt32MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeInt32

#endif

-- method FileInfo::set_attribute_int64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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 "attribute name to set."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "int64 value to set attribute to."
--                 , 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_info_set_attribute_int64" g_file_info_set_attribute_int64 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    Int64 ->                                -- attr_value : TBasicType TInt64
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeInt64 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: attribute name to set.
    -> Int64
    -- ^ /@attrValue@/: int64 value to set attribute to.
    -> m ()
fileInfoSetAttributeInt64 :: a -> Text -> Int64 -> m ()
fileInfoSetAttributeInt64 info :: a
info attribute :: Text
attribute attrValue :: Int64
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr FileInfo -> CString -> Int64 -> IO ()
g_file_info_set_attribute_int64 Ptr FileInfo
info' CString
attribute' Int64
attrValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeInt64MethodInfo
instance (signature ~ (T.Text -> Int64 -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeInt64MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeInt64

#endif

-- method FileInfo::set_attribute_mask
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mask"
--           , 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_info_set_attribute_mask" g_file_info_set_attribute_mask :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr Gio.FileAttributeMatcher.FileAttributeMatcher -> -- mask : TInterface (Name {namespace = "Gio", name = "FileAttributeMatcher"})
    IO ()

-- | Sets /@mask@/ on /@info@/ to match specific attribute types.
fileInfoSetAttributeMask ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> Gio.FileAttributeMatcher.FileAttributeMatcher
    -- ^ /@mask@/: a t'GI.Gio.Structs.FileAttributeMatcher.FileAttributeMatcher'.
    -> m ()
fileInfoSetAttributeMask :: a -> FileAttributeMatcher -> m ()
fileInfoSetAttributeMask info :: a
info mask :: FileAttributeMatcher
mask = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr FileAttributeMatcher
mask' <- FileAttributeMatcher -> IO (Ptr FileAttributeMatcher)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FileAttributeMatcher
mask
    Ptr FileInfo -> Ptr FileAttributeMatcher -> IO ()
g_file_info_set_attribute_mask Ptr FileInfo
info' Ptr FileAttributeMatcher
mask'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    FileAttributeMatcher -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FileAttributeMatcher
mask
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeMaskMethodInfo
instance (signature ~ (Gio.FileAttributeMatcher.FileAttributeMatcher -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeMaskMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeMask

#endif

-- method FileInfo::set_attribute_object
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GObject." , 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_info_set_attribute_object" g_file_info_set_attribute_object :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    Ptr GObject.Object.Object ->            -- attr_value : TInterface (Name {namespace = "GObject", name = "Object"})
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeObject ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a, GObject.Object.IsObject b) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> b
    -- ^ /@attrValue@/: a t'GI.GObject.Objects.Object.Object'.
    -> m ()
fileInfoSetAttributeObject :: a -> Text -> b -> m ()
fileInfoSetAttributeObject info :: a
info attribute :: Text
attribute attrValue :: b
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr Object
attrValue' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
attrValue
    Ptr FileInfo -> CString -> Ptr Object -> IO ()
g_file_info_set_attribute_object Ptr FileInfo
info' CString
attribute' Ptr Object
attrValue'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
attrValue
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeObjectMethodInfo
instance (signature ~ (T.Text -> b -> m ()), MonadIO m, IsFileInfo a, GObject.Object.IsObject b) => O.MethodInfo FileInfoSetAttributeObjectMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeObject

#endif

-- method FileInfo::set_attribute_status
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo" , 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
--           }
--       , Arg
--           { argCName = "status"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "FileAttributeStatus" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileAttributeStatus"
--                 , 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_info_set_attribute_status" g_file_info_set_attribute_status :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    CUInt ->                                -- status : TInterface (Name {namespace = "Gio", name = "FileAttributeStatus"})
    IO CInt

-- | Sets the attribute status for an attribute key. This is only
-- needed by external code that implement 'GI.Gio.Interfaces.File.fileSetAttributesFromInfo'
-- or similar functions.
-- 
-- The attribute must exist in /@info@/ for this to work. Otherwise 'P.False'
-- is returned and /@info@/ is unchanged.
-- 
-- /Since: 2.22/
fileInfoSetAttributeStatus ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'
    -> T.Text
    -- ^ /@attribute@/: a file attribute key
    -> Gio.Enums.FileAttributeStatus
    -- ^ /@status@/: a t'GI.Gio.Enums.FileAttributeStatus'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the status was changed, 'P.False' if the key was not set.
fileInfoSetAttributeStatus :: a -> Text -> FileAttributeStatus -> m Bool
fileInfoSetAttributeStatus info :: a
info attribute :: Text
attribute status :: FileAttributeStatus
status = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    let status' :: CUInt
status' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (FileAttributeStatus -> Int) -> FileAttributeStatus -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileAttributeStatus -> Int
forall a. Enum a => a -> Int
fromEnum) FileAttributeStatus
status
    CInt
result <- Ptr FileInfo -> CString -> CUInt -> IO CInt
g_file_info_set_attribute_status Ptr FileInfo
info' CString
attribute' CUInt
status'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    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 FileInfoSetAttributeStatusMethodInfo
instance (signature ~ (T.Text -> Gio.Enums.FileAttributeStatus -> m Bool), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeStatusMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeStatus

#endif

-- method FileInfo::set_attribute_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a UTF-8 string." , 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_info_set_attribute_string" g_file_info_set_attribute_string :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    CString ->                              -- attr_value : TBasicType TUTF8
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeString ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> T.Text
    -- ^ /@attrValue@/: a UTF-8 string.
    -> m ()
fileInfoSetAttributeString :: a -> Text -> Text -> m ()
fileInfoSetAttributeString info :: a
info attribute :: Text
attribute attrValue :: Text
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    CString
attrValue' <- Text -> IO CString
textToCString Text
attrValue
    Ptr FileInfo -> CString -> CString -> IO ()
g_file_info_set_attribute_string Ptr FileInfo
info' CString
attribute' CString
attrValue'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attrValue'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeStringMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeStringMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeString

#endif

-- method FileInfo::set_attribute_stringv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %NULL\n  terminated array of UTF-8 strings."
--                 , 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_info_set_attribute_stringv" g_file_info_set_attribute_stringv :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    Ptr CString ->                          -- attr_value : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
-- 
-- Sinze: 2.22
fileInfoSetAttributeStringv ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key
    -> [T.Text]
    -- ^ /@attrValue@/: a 'P.Nothing'
    --   terminated array of UTF-8 strings.
    -> m ()
fileInfoSetAttributeStringv :: a -> Text -> [Text] -> m ()
fileInfoSetAttributeStringv info :: a
info attribute :: Text
attribute attrValue :: [Text]
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr CString
attrValue' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
attrValue
    Ptr FileInfo -> CString -> Ptr CString -> IO ()
g_file_info_set_attribute_stringv Ptr FileInfo
info' CString
attribute' Ptr CString
attrValue'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
attrValue'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
attrValue'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeStringvMethodInfo
instance (signature ~ (T.Text -> [T.Text] -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeStringvMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeStringv

#endif

-- method FileInfo::set_attribute_uint32
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an unsigned 32-bit integer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_set_attribute_uint32" g_file_info_set_attribute_uint32 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    Word32 ->                               -- attr_value : TBasicType TUInt32
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeUint32 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> Word32
    -- ^ /@attrValue@/: an unsigned 32-bit integer.
    -> m ()
fileInfoSetAttributeUint32 :: a -> Text -> Word32 -> m ()
fileInfoSetAttributeUint32 info :: a
info attribute :: Text
attribute attrValue :: Word32
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr FileInfo -> CString -> Word32 -> IO ()
g_file_info_set_attribute_uint32 Ptr FileInfo
info' CString
attribute' Word32
attrValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeUint32MethodInfo
instance (signature ~ (T.Text -> Word32 -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeUint32MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeUint32

#endif

-- method FileInfo::set_attribute_uint64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , 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
--           }
--       , Arg
--           { argCName = "attr_value"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an unsigned 64-bit integer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_set_attribute_uint64" g_file_info_set_attribute_uint64 :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- attribute : TBasicType TUTF8
    Word64 ->                               -- attr_value : TBasicType TUInt64
    IO ()

-- | Sets the /@attribute@/ to contain the given /@attrValue@/,
-- if possible.
fileInfoSetAttributeUint64 ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@attribute@/: a file attribute key.
    -> Word64
    -- ^ /@attrValue@/: an unsigned 64-bit integer.
    -> m ()
fileInfoSetAttributeUint64 :: a -> Text -> Word64 -> m ()
fileInfoSetAttributeUint64 info :: a
info attribute :: Text
attribute attrValue :: Word64
attrValue = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
attribute' <- Text -> IO CString
textToCString Text
attribute
    Ptr FileInfo -> CString -> Word64 -> IO ()
g_file_info_set_attribute_uint64 Ptr FileInfo
info' CString
attribute' Word64
attrValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAttributeUint64MethodInfo
instance (signature ~ (T.Text -> Word64 -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetAttributeUint64MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeUint64

#endif

-- method FileInfo::set_content_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "content_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a content type. See [GContentType][gio-GContentType]"
--                 , 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_info_set_content_type" g_file_info_set_content_type :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- content_type : TBasicType TUTF8
    IO ()

-- | Sets the content type attribute for a given t'GI.Gio.Objects.FileInfo.FileInfo'.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_CONTENT_TYPE'.
fileInfoSetContentType ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@contentType@/: a content type. See [GContentType][gio-GContentType]
    -> m ()
fileInfoSetContentType :: a -> Text -> m ()
fileInfoSetContentType info :: a
info contentType :: Text
contentType = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
contentType' <- Text -> IO CString
textToCString Text
contentType
    Ptr FileInfo -> CString -> IO ()
g_file_info_set_content_type Ptr FileInfo
info' CString
contentType'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
contentType'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetContentTypeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetContentTypeMethodInfo a signature where
    overloadedMethod = fileInfoSetContentType

#endif

-- method FileInfo::set_display_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "display_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing a display name."
--                 , 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_info_set_display_name" g_file_info_set_display_name :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- display_name : TBasicType TUTF8
    IO ()

-- | Sets the display name for the current t'GI.Gio.Objects.FileInfo.FileInfo'.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_DISPLAY_NAME'.
fileInfoSetDisplayName ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@displayName@/: a string containing a display name.
    -> m ()
fileInfoSetDisplayName :: a -> Text -> m ()
fileInfoSetDisplayName info :: a
info displayName :: Text
displayName = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
displayName' <- Text -> IO CString
textToCString Text
displayName
    Ptr FileInfo -> CString -> IO ()
g_file_info_set_display_name Ptr FileInfo
info' CString
displayName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
displayName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetDisplayNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetDisplayNameMethodInfo a signature where
    overloadedMethod = fileInfoSetDisplayName

#endif

-- method FileInfo::set_edit_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "edit_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing an edit name."
--                 , 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_info_set_edit_name" g_file_info_set_edit_name :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- edit_name : TBasicType TUTF8
    IO ()

-- | Sets the edit name for the current file.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_EDIT_NAME'.
fileInfoSetEditName ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@editName@/: a string containing an edit name.
    -> m ()
fileInfoSetEditName :: a -> Text -> m ()
fileInfoSetEditName info :: a
info editName :: Text
editName = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
editName' <- Text -> IO CString
textToCString Text
editName
    Ptr FileInfo -> CString -> IO ()
g_file_info_set_edit_name Ptr FileInfo
info' CString
editName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
editName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetEditNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetEditNameMethodInfo a signature where
    overloadedMethod = fileInfoSetEditName

#endif

-- method FileInfo::set_file_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileType." , 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_info_set_file_type" g_file_info_set_file_type :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CUInt ->                                -- type : TInterface (Name {namespace = "Gio", name = "FileType"})
    IO ()

-- | Sets the file type in a t'GI.Gio.Objects.FileInfo.FileInfo' to /@type@/.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_TYPE'.
fileInfoSetFileType ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> Gio.Enums.FileType
    -- ^ /@type@/: a t'GI.Gio.Enums.FileType'.
    -> m ()
fileInfoSetFileType :: a -> FileType -> m ()
fileInfoSetFileType info :: a
info type_ :: FileType
type_ = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (FileType -> Int) -> FileType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileType -> Int
forall a. Enum a => a -> Int
fromEnum) FileType
type_
    Ptr FileInfo -> CUInt -> IO ()
g_file_info_set_file_type Ptr FileInfo
info' CUInt
type_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetFileTypeMethodInfo
instance (signature ~ (Gio.Enums.FileType -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetFileTypeMethodInfo a signature where
    overloadedMethod = fileInfoSetFileType

#endif

-- method FileInfo::set_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon." , 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_info_set_icon" g_file_info_set_icon :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO ()

-- | Sets the icon for a given t'GI.Gio.Objects.FileInfo.FileInfo'.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_ICON'.
fileInfoSetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> b
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon'.
    -> m ()
fileInfoSetIcon :: a -> b -> m ()
fileInfoSetIcon info :: a
info icon :: b
icon = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    Ptr FileInfo -> Ptr Icon -> IO ()
g_file_info_set_icon Ptr FileInfo
info' Ptr Icon
icon'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetIconMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsFileInfo a, Gio.Icon.IsIcon b) => O.MethodInfo FileInfoSetIconMethodInfo a signature where
    overloadedMethod = fileInfoSetIcon

#endif

-- method FileInfo::set_is_hidden
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_hidden"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #gboolean." , 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_info_set_is_hidden" g_file_info_set_is_hidden :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CInt ->                                 -- is_hidden : TBasicType TBoolean
    IO ()

-- | Sets the \"is_hidden\" attribute in a t'GI.Gio.Objects.FileInfo.FileInfo' according to /@isHidden@/.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_IS_HIDDEN'.
fileInfoSetIsHidden ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> Bool
    -- ^ /@isHidden@/: a t'P.Bool'.
    -> m ()
fileInfoSetIsHidden :: a -> Bool -> m ()
fileInfoSetIsHidden info :: a
info isHidden :: Bool
isHidden = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    let isHidden' :: CInt
isHidden' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isHidden
    Ptr FileInfo -> CInt -> IO ()
g_file_info_set_is_hidden Ptr FileInfo
info' CInt
isHidden'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetIsHiddenMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetIsHiddenMethodInfo a signature where
    overloadedMethod = fileInfoSetIsHidden

#endif

-- method FileInfo::set_is_symlink
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_symlink"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #gboolean." , 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_info_set_is_symlink" g_file_info_set_is_symlink :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CInt ->                                 -- is_symlink : TBasicType TBoolean
    IO ()

-- | Sets the \"is_symlink\" attribute in a t'GI.Gio.Objects.FileInfo.FileInfo' according to /@isSymlink@/.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_IS_SYMLINK'.
fileInfoSetIsSymlink ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> Bool
    -- ^ /@isSymlink@/: a t'P.Bool'.
    -> m ()
fileInfoSetIsSymlink :: a -> Bool -> m ()
fileInfoSetIsSymlink info :: a
info isSymlink :: Bool
isSymlink = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    let isSymlink' :: CInt
isSymlink' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isSymlink
    Ptr FileInfo -> CInt -> IO ()
g_file_info_set_is_symlink Ptr FileInfo
info' CInt
isSymlink'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetIsSymlinkMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetIsSymlinkMethodInfo a signature where
    overloadedMethod = fileInfoSetIsSymlink

#endif

-- method FileInfo::set_modification_time
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mtime"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "TimeVal" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTimeVal." , 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_info_set_modification_time" g_file_info_set_modification_time :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr GLib.TimeVal.TimeVal ->             -- mtime : TInterface (Name {namespace = "GLib", name = "TimeVal"})
    IO ()

-- | Sets the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_MODIFIED' attribute in the file
-- info to the given time value.
fileInfoSetModificationTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> GLib.TimeVal.TimeVal
    -- ^ /@mtime@/: a t'GI.GLib.Structs.TimeVal.TimeVal'.
    -> m ()
fileInfoSetModificationTime :: a -> TimeVal -> m ()
fileInfoSetModificationTime info :: a
info mtime :: TimeVal
mtime = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr TimeVal
mtime' <- TimeVal -> IO (Ptr TimeVal)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TimeVal
mtime
    Ptr FileInfo -> Ptr TimeVal -> IO ()
g_file_info_set_modification_time Ptr FileInfo
info' Ptr TimeVal
mtime'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    TimeVal -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TimeVal
mtime
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetModificationTimeMethodInfo
instance (signature ~ (GLib.TimeVal.TimeVal -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetModificationTimeMethodInfo a signature where
    overloadedMethod = fileInfoSetModificationTime

#endif

-- method FileInfo::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing a name."
--                 , 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_info_set_name" g_file_info_set_name :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- name : TBasicType TFileName
    IO ()

-- | Sets the name attribute for the current t'GI.Gio.Objects.FileInfo.FileInfo'.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_NAME'.
fileInfoSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> [Char]
    -- ^ /@name@/: a string containing a name.
    -> m ()
fileInfoSetName :: a -> [Char] -> m ()
fileInfoSetName info :: a
info name :: [Char]
name = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
name' <- [Char] -> IO CString
stringToCString [Char]
name
    Ptr FileInfo -> CString -> IO ()
g_file_info_set_name Ptr FileInfo
info' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetNameMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetNameMethodInfo a signature where
    overloadedMethod = fileInfoSetName

#endif

-- method FileInfo::set_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #goffset containing the file's size."
--                 , 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_info_set_size" g_file_info_set_size :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Int64 ->                                -- size : TBasicType TInt64
    IO ()

-- | Sets the 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_SIZE' attribute in the file info
-- to the given size.
fileInfoSetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> Int64
    -- ^ /@size@/: a @/goffset/@ containing the file\'s size.
    -> m ()
fileInfoSetSize :: a -> Int64 -> m ()
fileInfoSetSize info :: a
info size :: Int64
size = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr FileInfo -> Int64 -> IO ()
g_file_info_set_size Ptr FileInfo
info' Int64
size
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetSizeMethodInfo
instance (signature ~ (Int64 -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetSizeMethodInfo a signature where
    overloadedMethod = fileInfoSetSize

#endif

-- method FileInfo::set_sort_order
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sort_order"
--           , argType = TBasicType TInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a sort order integer."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_file_info_set_sort_order" g_file_info_set_sort_order :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Int32 ->                                -- sort_order : TBasicType TInt32
    IO ()

-- | Sets the sort order attribute in the file info structure. See
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_SORT_ORDER'.
fileInfoSetSortOrder ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> Int32
    -- ^ /@sortOrder@/: a sort order integer.
    -> m ()
fileInfoSetSortOrder :: a -> Int32 -> m ()
fileInfoSetSortOrder info :: a
info sortOrder :: Int32
sortOrder = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr FileInfo -> Int32 -> IO ()
g_file_info_set_sort_order Ptr FileInfo
info' Int32
sortOrder
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetSortOrderMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetSortOrderMethodInfo a signature where
    overloadedMethod = fileInfoSetSortOrder

#endif

-- method FileInfo::set_symbolic_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon." , 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_info_set_symbolic_icon" g_file_info_set_symbolic_icon :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO ()

-- | Sets the symbolic icon for a given t'GI.Gio.Objects.FileInfo.FileInfo'.
-- See 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_SYMBOLIC_ICON'.
-- 
-- /Since: 2.34/
fileInfoSetSymbolicIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> b
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon'.
    -> m ()
fileInfoSetSymbolicIcon :: a -> b -> m ()
fileInfoSetSymbolicIcon info :: a
info icon :: b
icon = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr Icon
icon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
icon
    Ptr FileInfo -> Ptr Icon -> IO ()
g_file_info_set_symbolic_icon Ptr FileInfo
info' Ptr Icon
icon'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
icon
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetSymbolicIconMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsFileInfo a, Gio.Icon.IsIcon b) => O.MethodInfo FileInfoSetSymbolicIconMethodInfo a signature where
    overloadedMethod = fileInfoSetSymbolicIcon

#endif

-- method FileInfo::set_symlink_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFileInfo." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "symlink_target"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a static string containing a path to a symlink target."
--                 , 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_info_set_symlink_target" g_file_info_set_symlink_target :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    CString ->                              -- symlink_target : TBasicType TUTF8
    IO ()

-- | Sets the 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_SYMLINK_TARGET' attribute in the file info
-- to the given symlink target.
fileInfoSetSymlinkTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> T.Text
    -- ^ /@symlinkTarget@/: a static string containing a path to a symlink target.
    -> m ()
fileInfoSetSymlinkTarget :: a -> Text -> m ()
fileInfoSetSymlinkTarget info :: a
info symlinkTarget :: Text
symlinkTarget = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
symlinkTarget' <- Text -> IO CString
textToCString Text
symlinkTarget
    Ptr FileInfo -> CString -> IO ()
g_file_info_set_symlink_target Ptr FileInfo
info' CString
symlinkTarget'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
symlinkTarget'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetSymlinkTargetMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoSetSymlinkTargetMethodInfo a signature where
    overloadedMethod = fileInfoSetSymlinkTarget

#endif

-- method FileInfo::unset_attribute_mask
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GFileInfo." , 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_info_unset_attribute_mask" g_file_info_unset_attribute_mask :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    IO ()

-- | Unsets a mask set by 'GI.Gio.Objects.FileInfo.fileInfoSetAttributeMask', if one
-- is set.
fileInfoUnsetAttributeMask ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m ()
fileInfoUnsetAttributeMask :: a -> m ()
fileInfoUnsetAttributeMask info :: a
info = 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 FileInfo
info' <- a -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr FileInfo -> IO ()
g_file_info_unset_attribute_mask Ptr FileInfo
info'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoUnsetAttributeMaskMethodInfo
instance (signature ~ (m ()), MonadIO m, IsFileInfo a) => O.MethodInfo FileInfoUnsetAttributeMaskMethodInfo a signature where
    overloadedMethod = fileInfoUnsetAttributeMask

#endif