{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- 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.
-- 
-- The direct accessors, such as 'GI.Gio.Objects.FileInfo.fileInfoGetName', are slightly more
-- optimized than the generic attribute accessors, such as
-- 'GI.Gio.Objects.FileInfo.fileInfoGetAttributeByteString'.This optimization will matter
-- only if calling the API in a tight loop.
-- 
-- 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                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clearStatus]("GI.Gio.Objects.FileInfo#g:method:clearStatus"), [copyInto]("GI.Gio.Objects.FileInfo#g:method:copyInto"), [dup]("GI.Gio.Objects.FileInfo#g:method:dup"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasAttribute]("GI.Gio.Objects.FileInfo#g:method:hasAttribute"), [hasNamespace]("GI.Gio.Objects.FileInfo#g:method:hasNamespace"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [listAttributes]("GI.Gio.Objects.FileInfo#g:method:listAttributes"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeAttribute]("GI.Gio.Objects.FileInfo#g:method:removeAttribute"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetAttributeMask]("GI.Gio.Objects.FileInfo#g:method:unsetAttributeMask"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessDateTime]("GI.Gio.Objects.FileInfo#g:method:getAccessDateTime"), [getAttributeAsString]("GI.Gio.Objects.FileInfo#g:method:getAttributeAsString"), [getAttributeBoolean]("GI.Gio.Objects.FileInfo#g:method:getAttributeBoolean"), [getAttributeByteString]("GI.Gio.Objects.FileInfo#g:method:getAttributeByteString"), [getAttributeData]("GI.Gio.Objects.FileInfo#g:method:getAttributeData"), [getAttributeInt32]("GI.Gio.Objects.FileInfo#g:method:getAttributeInt32"), [getAttributeInt64]("GI.Gio.Objects.FileInfo#g:method:getAttributeInt64"), [getAttributeObject]("GI.Gio.Objects.FileInfo#g:method:getAttributeObject"), [getAttributeStatus]("GI.Gio.Objects.FileInfo#g:method:getAttributeStatus"), [getAttributeString]("GI.Gio.Objects.FileInfo#g:method:getAttributeString"), [getAttributeStringv]("GI.Gio.Objects.FileInfo#g:method:getAttributeStringv"), [getAttributeType]("GI.Gio.Objects.FileInfo#g:method:getAttributeType"), [getAttributeUint32]("GI.Gio.Objects.FileInfo#g:method:getAttributeUint32"), [getAttributeUint64]("GI.Gio.Objects.FileInfo#g:method:getAttributeUint64"), [getContentType]("GI.Gio.Objects.FileInfo#g:method:getContentType"), [getCreationDateTime]("GI.Gio.Objects.FileInfo#g:method:getCreationDateTime"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDeletionDate]("GI.Gio.Objects.FileInfo#g:method:getDeletionDate"), [getDisplayName]("GI.Gio.Objects.FileInfo#g:method:getDisplayName"), [getEditName]("GI.Gio.Objects.FileInfo#g:method:getEditName"), [getEtag]("GI.Gio.Objects.FileInfo#g:method:getEtag"), [getFileType]("GI.Gio.Objects.FileInfo#g:method:getFileType"), [getIcon]("GI.Gio.Objects.FileInfo#g:method:getIcon"), [getIsBackup]("GI.Gio.Objects.FileInfo#g:method:getIsBackup"), [getIsHidden]("GI.Gio.Objects.FileInfo#g:method:getIsHidden"), [getIsSymlink]("GI.Gio.Objects.FileInfo#g:method:getIsSymlink"), [getModificationDateTime]("GI.Gio.Objects.FileInfo#g:method:getModificationDateTime"), [getModificationTime]("GI.Gio.Objects.FileInfo#g:method:getModificationTime"), [getName]("GI.Gio.Objects.FileInfo#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSize]("GI.Gio.Objects.FileInfo#g:method:getSize"), [getSortOrder]("GI.Gio.Objects.FileInfo#g:method:getSortOrder"), [getSymbolicIcon]("GI.Gio.Objects.FileInfo#g:method:getSymbolicIcon"), [getSymlinkTarget]("GI.Gio.Objects.FileInfo#g:method:getSymlinkTarget").
-- 
-- ==== Setters
-- [setAccessDateTime]("GI.Gio.Objects.FileInfo#g:method:setAccessDateTime"), [setAttribute]("GI.Gio.Objects.FileInfo#g:method:setAttribute"), [setAttributeBoolean]("GI.Gio.Objects.FileInfo#g:method:setAttributeBoolean"), [setAttributeByteString]("GI.Gio.Objects.FileInfo#g:method:setAttributeByteString"), [setAttributeInt32]("GI.Gio.Objects.FileInfo#g:method:setAttributeInt32"), [setAttributeInt64]("GI.Gio.Objects.FileInfo#g:method:setAttributeInt64"), [setAttributeMask]("GI.Gio.Objects.FileInfo#g:method:setAttributeMask"), [setAttributeObject]("GI.Gio.Objects.FileInfo#g:method:setAttributeObject"), [setAttributeStatus]("GI.Gio.Objects.FileInfo#g:method:setAttributeStatus"), [setAttributeString]("GI.Gio.Objects.FileInfo#g:method:setAttributeString"), [setAttributeStringv]("GI.Gio.Objects.FileInfo#g:method:setAttributeStringv"), [setAttributeUint32]("GI.Gio.Objects.FileInfo#g:method:setAttributeUint32"), [setAttributeUint64]("GI.Gio.Objects.FileInfo#g:method:setAttributeUint64"), [setContentType]("GI.Gio.Objects.FileInfo#g:method:setContentType"), [setCreationDateTime]("GI.Gio.Objects.FileInfo#g:method:setCreationDateTime"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDisplayName]("GI.Gio.Objects.FileInfo#g:method:setDisplayName"), [setEditName]("GI.Gio.Objects.FileInfo#g:method:setEditName"), [setFileType]("GI.Gio.Objects.FileInfo#g:method:setFileType"), [setIcon]("GI.Gio.Objects.FileInfo#g:method:setIcon"), [setIsHidden]("GI.Gio.Objects.FileInfo#g:method:setIsHidden"), [setIsSymlink]("GI.Gio.Objects.FileInfo#g:method:setIsSymlink"), [setModificationDateTime]("GI.Gio.Objects.FileInfo#g:method:setModificationDateTime"), [setModificationTime]("GI.Gio.Objects.FileInfo#g:method:setModificationTime"), [setName]("GI.Gio.Objects.FileInfo#g:method:setName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSize]("GI.Gio.Objects.FileInfo#g:method:setSize"), [setSortOrder]("GI.Gio.Objects.FileInfo#g:method:setSortOrder"), [setSymbolicIcon]("GI.Gio.Objects.FileInfo#g:method:setSymbolicIcon"), [setSymlinkTarget]("GI.Gio.Objects.FileInfo#g:method:setSymlinkTarget").

#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                             ,


-- ** getAccessDateTime #method:getAccessDateTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetAccessDateTimeMethodInfo     ,
#endif
    fileInfoGetAccessDateTime               ,


-- ** 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                  ,


-- ** getCreationDateTime #method:getCreationDateTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetCreationDateTimeMethodInfo   ,
#endif
    fileInfoGetCreationDateTime             ,


-- ** 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                    ,


-- ** getModificationDateTime #method:getModificationDateTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoGetModificationDateTimeMethodInfo,
#endif
    fileInfoGetModificationDateTime         ,


-- ** 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                 ,


-- ** setAccessDateTime #method:setAccessDateTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetAccessDateTimeMethodInfo     ,
#endif
    fileInfoSetAccessDateTime               ,


-- ** 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                  ,


-- ** setCreationDateTime #method:setCreationDateTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetCreationDateTimeMethodInfo   ,
#endif
    fileInfoSetCreationDateTime             ,


-- ** 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                    ,


-- ** setModificationDateTime #method:setModificationDateTime#

#if defined(ENABLE_OVERLOADING)
    FileInfoSetModificationDateTimeMethodInfo,
#endif
    fileInfoSetModificationDateTime         ,


-- ** 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.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 (SP.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)

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

foreign import ccall "g_file_info_get_type"
    c_g_file_info_get_type :: IO B.Types.GType

instance B.Types.TypedObject FileInfo where
    glibType :: IO GType
glibType = IO GType
c_g_file_info_get_type

instance B.Types.GObject FileInfo

-- | Type class for types which can be safely cast to `FileInfo`, for instance with `toFileInfo`.
class (SP.GObject o, O.IsDescendantOf FileInfo o) => IsFileInfo o
instance (SP.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 :: (MIO.MonadIO m, IsFileInfo o) => o -> m FileInfo
toFileInfo :: forall (m :: * -> *) o.
(MonadIO m, IsFileInfo o) =>
o -> m FileInfo
toFileInfo = IO FileInfo -> m FileInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr FileInfo -> FileInfo
FileInfo

-- | Convert 'FileInfo' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe FileInfo) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_file_info_get_type
    gvalueSet_ :: Ptr GValue -> Maybe FileInfo -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FileInfo
P.Nothing = Ptr GValue -> Ptr FileInfo -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr FileInfo
forall a. Ptr a
FP.nullPtr :: FP.Ptr FileInfo)
    gvalueSet_ Ptr GValue
gv (P.Just FileInfo
obj) = FileInfo -> (Ptr FileInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FileInfo
obj (Ptr GValue -> Ptr FileInfo -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe FileInfo)
gvalueGet_ Ptr GValue
gv = do
        Ptr FileInfo
ptr <- Ptr GValue -> IO (Ptr FileInfo)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr FileInfo)
        if Ptr FileInfo
ptr Ptr FileInfo -> Ptr FileInfo -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FileInfo
forall a. Ptr a
FP.nullPtr
        then FileInfo -> Maybe FileInfo
forall a. a -> Maybe a
P.Just (FileInfo -> Maybe FileInfo) -> IO FileInfo -> IO (Maybe FileInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe FileInfo -> IO (Maybe FileInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FileInfo
forall a. Maybe a
P.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 "getAccessDateTime" o = FileInfoGetAccessDateTimeMethodInfo
    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 "getCreationDateTime" o = FileInfoGetCreationDateTimeMethodInfo
    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 "getModificationDateTime" o = FileInfoGetModificationDateTimeMethodInfo
    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 "setAccessDateTime" o = FileInfoSetAccessDateTimeMethodInfo
    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 "setCreationDateTime" o = FileInfoSetCreationDateTimeMethodInfo
    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 "setModificationDateTime" o = FileInfoSetModificationDateTimeMethodInfo
    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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFileInfoMethod t FileInfo, O.OverloadedMethod info FileInfo p, R.HasField t FileInfo p) => R.HasField t FileInfo p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFileInfoMethod t FileInfo, O.OverloadedMethodInfo info FileInfo) => OL.IsLabel t (O.MethodProxy info FileInfo) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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 Text
"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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m ()
fileInfoClearStatus 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.OverloadedMethod FileInfoClearStatusMethodInfo a signature where
    overloadedMethod = fileInfoClearStatus

instance O.OverloadedMethodInfo FileInfoClearStatusMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoClearStatus",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileInfo a, IsFileInfo b) =>
a -> b -> m ()
fileInfoCopyInto a
srcInfo 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.OverloadedMethod FileInfoCopyIntoMethodInfo a signature where
    overloadedMethod = fileInfoCopyInto

instance O.OverloadedMethodInfo FileInfoCopyIntoMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoCopyInto",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m FileInfo
fileInfoDup 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 Text
"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.OverloadedMethod FileInfoDupMethodInfo a signature where
    overloadedMethod = fileInfoDup

instance O.OverloadedMethodInfo FileInfoDupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoDup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoDup"
        })


#endif

-- method FileInfo::get_access_date_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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "DateTime" })
-- throws : False
-- Skip return : False

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

-- | Gets the access time of the current /@info@/ and returns it as a
-- t'GI.GLib.Structs.DateTime.DateTime'.
-- 
-- This requires the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_ACCESS' attribute. If
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_ACCESS_USEC' is provided, the resulting t'GI.GLib.Structs.DateTime.DateTime'
-- will have microsecond precision.
-- 
-- /Since: 2.70/
fileInfoGetAccessDateTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m (Maybe GLib.DateTime.DateTime)
    -- ^ __Returns:__ access time, or 'P.Nothing' if unknown
fileInfoGetAccessDateTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe DateTime)
fileInfoGetAccessDateTime a
info = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe 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_access_date_time Ptr FileInfo
info'
    Maybe DateTime
maybeResult <- Ptr DateTime
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DateTime
result ((Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime))
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ \Ptr DateTime
result' -> do
        DateTime
result'' <- ((ManagedPtr DateTime -> DateTime) -> Ptr DateTime -> IO DateTime
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime) Ptr DateTime
result'
        DateTime -> IO DateTime
forall (m :: * -> *) a. Monad m => a -> m a
return DateTime
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe DateTime -> IO (Maybe DateTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DateTime
maybeResult

#if defined(ENABLE_OVERLOADING)
data FileInfoGetAccessDateTimeMethodInfo
instance (signature ~ (m (Maybe GLib.DateTime.DateTime)), MonadIO m, IsFileInfo a) => O.OverloadedMethod FileInfoGetAccessDateTimeMethodInfo a signature where
    overloadedMethod = fileInfoGetAccessDateTime

instance O.OverloadedMethodInfo FileInfoGetAccessDateTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAccessDateTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoGetAccessDateTime"
        })


#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, formatted as a string.
-- This escapes things as needed to make the string valid
-- UTF-8.
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 (Maybe T.Text)
    -- ^ __Returns:__ a UTF-8 string associated with the given /@attribute@/, or
    --    'P.Nothing' if the attribute wasn’t set.
    --    When you\'re done with the string it must be freed with 'GI.GLib.Functions.free'.
fileInfoGetAttributeAsString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m (Maybe Text)
fileInfoGetAttributeAsString a
info Text
attribute = 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
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'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem 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
attribute'
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetAttributeAsStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeAsString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m Bool
fileInfoGetAttributeBoolean a
info 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
/= CInt
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.OverloadedMethod FileInfoGetAttributeBooleanMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeBoolean

instance O.OverloadedMethodInfo FileInfoGetAttributeBooleanMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeBoolean",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe T.Text)
    -- ^ __Returns:__ the contents of the /@attribute@/ value as a byte string, or
    -- 'P.Nothing' otherwise.
fileInfoGetAttributeByteString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m (Maybe Text)
fileInfoGetAttributeByteString a
info Text
attribute = 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
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'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (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
attribute'
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetAttributeByteStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeByteString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a
-> Text -> m (Bool, FileAttributeType, Ptr (), FileAttributeStatus)
fileInfoGetAttributeData a
info 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)
callocMem :: 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
/= CInt
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.OverloadedMethod FileInfoGetAttributeDataMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeData

instance O.OverloadedMethodInfo FileInfoGetAttributeDataMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m Int32
fileInfoGetAttributeInt32 a
info 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.OverloadedMethod FileInfoGetAttributeInt32MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeInt32

instance O.OverloadedMethodInfo FileInfoGetAttributeInt32MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeInt32",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 a 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m Int64
fileInfoGetAttributeInt64 a
info 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.OverloadedMethod FileInfoGetAttributeInt64MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeInt64

instance O.OverloadedMethodInfo FileInfoGetAttributeInt64MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeInt64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe GObject.Object.Object)
    -- ^ __Returns:__ a t'GI.GObject.Objects.Object.Object' associated with the given /@attribute@/,
    -- or 'P.Nothing' otherwise.
fileInfoGetAttributeObject :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m (Maybe Object)
fileInfoGetAttributeObject a
info Text
attribute = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe 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'
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
result' -> do
        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'
        Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attribute'
    Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetAttributeObjectMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeObject",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m FileAttributeStatus
fileInfoGetAttributeStatus a
info 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.OverloadedMethod FileInfoGetAttributeStatusMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeStatus

instance O.OverloadedMethodInfo FileInfoGetAttributeStatusMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeStatus",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe T.Text)
    -- ^ __Returns:__ the contents of the /@attribute@/ value as a UTF-8 string,
    -- or 'P.Nothing' otherwise.
fileInfoGetAttributeString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m (Maybe Text)
fileInfoGetAttributeString a
info Text
attribute = 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
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'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (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
attribute'
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetAttributeStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe [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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m (Maybe [Text])
fileInfoGetAttributeStringv a
info Text
attribute = 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
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'
    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
$ \Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray 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
attribute'
    Maybe [Text] -> IO (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetAttributeStringvMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeStringv",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m FileAttributeType
fileInfoGetAttributeType a
info 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.OverloadedMethod FileInfoGetAttributeTypeMethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeType

instance O.OverloadedMethodInfo FileInfoGetAttributeTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m Word32
fileInfoGetAttributeUint32 a
info 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.OverloadedMethod FileInfoGetAttributeUint32MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeUint32

instance O.OverloadedMethodInfo FileInfoGetAttributeUint32MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeUint32",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m Word64
fileInfoGetAttributeUint64 a
info 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.OverloadedMethod FileInfoGetAttributeUint64MethodInfo a signature where
    overloadedMethod = fileInfoGetAttributeUint64

instance O.OverloadedMethodInfo FileInfoGetAttributeUint64MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetAttributeUint64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe T.Text)
    -- ^ __Returns:__ a string containing the file\'s content type,
    -- or 'P.Nothing' if unknown.
fileInfoGetContentType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe Text)
fileInfoGetContentType a
info = 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
result <- Ptr FileInfo -> IO CString
g_file_info_get_content_type Ptr FileInfo
info'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetContentTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetContentType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoGetContentType"
        })


#endif

-- method FileInfo::get_creation_date_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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "DateTime" })
-- throws : False
-- Skip return : False

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

-- | Gets the creation time of the current /@info@/ and returns it as a
-- t'GI.GLib.Structs.DateTime.DateTime'.
-- 
-- This requires the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_CREATED' attribute. If
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_CREATED_USEC' is provided, the resulting t'GI.GLib.Structs.DateTime.DateTime'
-- will have microsecond precision.
-- 
-- /Since: 2.70/
fileInfoGetCreationDateTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m (Maybe GLib.DateTime.DateTime)
    -- ^ __Returns:__ creation time, or 'P.Nothing' if unknown
fileInfoGetCreationDateTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe DateTime)
fileInfoGetCreationDateTime a
info = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe 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_creation_date_time Ptr FileInfo
info'
    Maybe DateTime
maybeResult <- Ptr DateTime
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DateTime
result ((Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime))
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ \Ptr DateTime
result' -> do
        DateTime
result'' <- ((ManagedPtr DateTime -> DateTime) -> Ptr DateTime -> IO DateTime
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime) Ptr DateTime
result'
        DateTime -> IO DateTime
forall (m :: * -> *) a. Monad m => a -> m a
return DateTime
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe DateTime -> IO (Maybe DateTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DateTime
maybeResult

#if defined(ENABLE_OVERLOADING)
data FileInfoGetCreationDateTimeMethodInfo
instance (signature ~ (m (Maybe GLib.DateTime.DateTime)), MonadIO m, IsFileInfo a) => O.OverloadedMethod FileInfoGetCreationDateTimeMethodInfo a signature where
    overloadedMethod = fileInfoGetCreationDateTime

instance O.OverloadedMethodInfo FileInfoGetCreationDateTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetCreationDateTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoGetCreationDateTime"
        })


#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 (Maybe GLib.DateTime.DateTime)
    -- ^ __Returns:__ a t'GI.GLib.Structs.DateTime.DateTime', or 'P.Nothing'.
fileInfoGetDeletionDate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe DateTime)
fileInfoGetDeletionDate a
info = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe 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'
    Maybe DateTime
maybeResult <- Ptr DateTime
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DateTime
result ((Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime))
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ \Ptr DateTime
result' -> do
        DateTime
result'' <- ((ManagedPtr DateTime -> DateTime) -> Ptr DateTime -> IO DateTime
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime) Ptr DateTime
result'
        DateTime -> IO DateTime
forall (m :: * -> *) a. Monad m => a -> m a
return DateTime
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe DateTime -> IO (Maybe DateTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DateTime
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetDeletionDateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetDeletionDate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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. This is guaranteed to always be set.
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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m Text
fileInfoGetDisplayName 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 Text
"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.OverloadedMethod FileInfoGetDisplayNameMethodInfo a signature where
    overloadedMethod = fileInfoGetDisplayName

instance O.OverloadedMethodInfo FileInfoGetDisplayNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetDisplayName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m Text
fileInfoGetEditName 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 Text
"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.OverloadedMethod FileInfoGetEditNameMethodInfo a signature where
    overloadedMethod = fileInfoGetEditName

instance O.OverloadedMethodInfo FileInfoGetEditNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetEditName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe T.Text)
    -- ^ __Returns:__ a string containing the value of the \"etag:value\" attribute.
fileInfoGetEtag :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe Text)
fileInfoGetEtag a
info = 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
result <- Ptr FileInfo -> IO CString
g_file_info_get_etag Ptr FileInfo
info'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetEtagMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetEtag",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m FileType
fileInfoGetFileType 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.OverloadedMethod FileInfoGetFileTypeMethodInfo a signature where
    overloadedMethod = fileInfoGetFileType

instance O.OverloadedMethodInfo FileInfoGetFileTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetFileType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe Gio.Icon.Icon)
    -- ^ __Returns:__ t'GI.Gio.Interfaces.Icon.Icon' for the given /@info@/.
fileInfoGetIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe Icon)
fileInfoGetIcon a
info = IO (Maybe Icon) -> m (Maybe Icon)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe 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'
    Maybe Icon
maybeResult <- Ptr Icon -> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Icon
result ((Ptr Icon -> IO Icon) -> IO (Maybe Icon))
-> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ \Ptr Icon
result' -> do
        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'
        Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe Icon -> IO (Maybe Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Icon
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m Bool
fileInfoGetIsBackup 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
/= CInt
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.OverloadedMethod FileInfoGetIsBackupMethodInfo a signature where
    overloadedMethod = fileInfoGetIsBackup

instance O.OverloadedMethodInfo FileInfoGetIsBackupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetIsBackup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m Bool
fileInfoGetIsHidden 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
/= CInt
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.OverloadedMethod FileInfoGetIsHiddenMethodInfo a signature where
    overloadedMethod = fileInfoGetIsHidden

instance O.OverloadedMethodInfo FileInfoGetIsHiddenMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetIsHidden",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m Bool
fileInfoGetIsSymlink 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
/= CInt
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.OverloadedMethod FileInfoGetIsSymlinkMethodInfo a signature where
    overloadedMethod = fileInfoGetIsSymlink

instance O.OverloadedMethodInfo FileInfoGetIsSymlinkMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetIsSymlink",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoGetIsSymlink"
        })


#endif

-- method FileInfo::get_modification_date_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
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "DateTime" })
-- throws : False
-- Skip return : False

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

-- | Gets the modification time of the current /@info@/ and returns it as a
-- t'GI.GLib.Structs.DateTime.DateTime'.
-- 
-- This requires the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_MODIFIED' attribute. If
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_MODIFIED_USEC' is provided, the resulting t'GI.GLib.Structs.DateTime.DateTime'
-- will have microsecond precision.
-- 
-- /Since: 2.62/
fileInfoGetModificationDateTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> m (Maybe GLib.DateTime.DateTime)
    -- ^ __Returns:__ modification time, or 'P.Nothing' if unknown
fileInfoGetModificationDateTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe DateTime)
fileInfoGetModificationDateTime a
info = IO (Maybe DateTime) -> m (Maybe DateTime)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DateTime) -> m (Maybe DateTime))
-> IO (Maybe DateTime) -> m (Maybe 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_modification_date_time Ptr FileInfo
info'
    Maybe DateTime
maybeResult <- Ptr DateTime
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DateTime
result ((Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime))
-> (Ptr DateTime -> IO DateTime) -> IO (Maybe DateTime)
forall a b. (a -> b) -> a -> b
$ \Ptr DateTime
result' -> do
        DateTime
result'' <- ((ManagedPtr DateTime -> DateTime) -> Ptr DateTime -> IO DateTime
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DateTime -> DateTime
GLib.DateTime.DateTime) Ptr DateTime
result'
        DateTime -> IO DateTime
forall (m :: * -> *) a. Monad m => a -> m a
return DateTime
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe DateTime -> IO (Maybe DateTime)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DateTime
maybeResult

#if defined(ENABLE_OVERLOADING)
data FileInfoGetModificationDateTimeMethodInfo
instance (signature ~ (m (Maybe GLib.DateTime.DateTime)), MonadIO m, IsFileInfo a) => O.OverloadedMethod FileInfoGetModificationDateTimeMethodInfo a signature where
    overloadedMethod = fileInfoGetModificationDateTime

instance O.OverloadedMethodInfo FileInfoGetModificationDateTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetModificationDateTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoGetModificationDateTime"
        })


#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 ()

{-# DEPRECATED fileInfoGetModificationTime ["(Since version 2.62)","Use 'GI.Gio.Objects.FileInfo.fileInfoGetModificationDateTime' instead, as","   t'GI.GLib.Structs.TimeVal.TimeVal' is deprecated due to the year 2038 problem."] #-}
-- | 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m TimeVal
fileInfoGetModificationTime 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)
SP.callocBytes Int
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, BoxedPtr 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.OverloadedMethod FileInfoGetModificationTimeMethodInfo a signature where
    overloadedMethod = fileInfoGetModificationTime

instance O.OverloadedMethodInfo FileInfoGetModificationTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetModificationTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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. This is guaranteed to always be set.
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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m [Char]
fileInfoGetName 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 Text
"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.OverloadedMethod FileInfoGetNameMethodInfo a signature where
    overloadedMethod = fileInfoGetName

instance O.OverloadedMethodInfo FileInfoGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (in bytes). The size is retrieved through the value of
-- the 'GI.Gio.Constants.FILE_ATTRIBUTE_STANDARD_SIZE' attribute and is converted
-- from @/guint64/@ to @/goffset/@ before returning the result.
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 (in bytes).
fileInfoGetSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m Int64
fileInfoGetSize 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.OverloadedMethod FileInfoGetSizeMethodInfo a signature where
    overloadedMethod = fileInfoGetSize

instance O.OverloadedMethodInfo FileInfoGetSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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](#g:signal:sort_order)\" attribute.
fileInfoGetSortOrder :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m Int32
fileInfoGetSortOrder 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.OverloadedMethod FileInfoGetSortOrderMethodInfo a signature where
    overloadedMethod = fileInfoGetSortOrder

instance O.OverloadedMethodInfo FileInfoGetSortOrderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetSortOrder",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe Gio.Icon.Icon)
    -- ^ __Returns:__ t'GI.Gio.Interfaces.Icon.Icon' for the given /@info@/.
fileInfoGetSymbolicIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe Icon)
fileInfoGetSymbolicIcon a
info = IO (Maybe Icon) -> m (Maybe Icon)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Icon) -> m (Maybe Icon))
-> IO (Maybe Icon) -> m (Maybe 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'
    Maybe Icon
maybeResult <- Ptr Icon -> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Icon
result ((Ptr Icon -> IO Icon) -> IO (Maybe Icon))
-> (Ptr Icon -> IO Icon) -> IO (Maybe Icon)
forall a b. (a -> b) -> a -> b
$ \Ptr Icon
result' -> do
        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'
        Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe Icon -> IO (Maybe Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Icon
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetSymbolicIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetSymbolicIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 (Maybe T.Text)
    -- ^ __Returns:__ a string containing the symlink target.
fileInfoGetSymlinkTarget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m (Maybe Text)
fileInfoGetSymlinkTarget a
info = 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
result <- Ptr FileInfo -> IO CString
g_file_info_get_symlink_target Ptr FileInfo
info'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo FileInfoGetSymlinkTargetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoGetSymlinkTarget",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 /@info@/ has an attribute named /@attribute@/,
    --     'P.False' otherwise.
fileInfoHasAttribute :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m Bool
fileInfoHasAttribute a
info 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
/= CInt
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.OverloadedMethod FileInfoHasAttributeMethodInfo a signature where
    overloadedMethod = fileInfoHasAttribute

instance O.OverloadedMethodInfo FileInfoHasAttributeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoHasAttribute",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 /@info@/ has an attribute in /@nameSpace@/,
    --     'P.False' otherwise.
fileInfoHasNamespace :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m Bool
fileInfoHasNamespace a
info 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
/= CInt
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.OverloadedMethod FileInfoHasNamespaceMethodInfo a signature where
    overloadedMethod = fileInfoHasNamespace

instance O.OverloadedMethodInfo FileInfoHasNamespaceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoHasNamespace",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Maybe Text -> m (Maybe [Text])
fileInfoListAttributes a
info 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
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just 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
$ \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.OverloadedMethod FileInfoListAttributesMethodInfo a signature where
    overloadedMethod = fileInfoListAttributes

instance O.OverloadedMethodInfo FileInfoListAttributesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoListAttributes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m ()
fileInfoRemoveAttribute a
info 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.OverloadedMethod FileInfoRemoveAttributeMethodInfo a signature where
    overloadedMethod = fileInfoRemoveAttribute

instance O.OverloadedMethodInfo FileInfoRemoveAttributeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoRemoveAttribute",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoRemoveAttribute"
        })


#endif

-- method FileInfo::set_access_date_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 = "atime"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateTime" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDateTime." , 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_access_date_time" g_file_info_set_access_date_time :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr GLib.DateTime.DateTime ->           -- atime : TInterface (Name {namespace = "GLib", name = "DateTime"})
    IO ()

-- | Sets the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_ACCESS' and
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_ACCESS_USEC' attributes in the file info to the
-- given date\/time value.
-- 
-- /Since: 2.70/
fileInfoSetAccessDateTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> GLib.DateTime.DateTime
    -- ^ /@atime@/: a t'GI.GLib.Structs.DateTime.DateTime'.
    -> m ()
fileInfoSetAccessDateTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> DateTime -> m ()
fileInfoSetAccessDateTime a
info DateTime
atime = 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 DateTime
atime' <- DateTime -> IO (Ptr DateTime)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DateTime
atime
    Ptr FileInfo -> Ptr DateTime -> IO ()
g_file_info_set_access_date_time Ptr FileInfo
info' Ptr DateTime
atime'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    DateTime -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DateTime
atime
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetAccessDateTimeMethodInfo
instance (signature ~ (GLib.DateTime.DateTime -> m ()), MonadIO m, IsFileInfo a) => O.OverloadedMethod FileInfoSetAccessDateTimeMethodInfo a signature where
    overloadedMethod = fileInfoSetAccessDateTime

instance O.OverloadedMethodInfo FileInfoSetAccessDateTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAccessDateTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoSetAccessDateTime"
        })


#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> FileAttributeType -> Ptr () -> m ()
fileInfoSetAttribute a
info Text
attribute FileAttributeType
type_ 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.OverloadedMethod FileInfoSetAttributeMethodInfo a signature where
    overloadedMethod = fileInfoSetAttribute

instance O.OverloadedMethodInfo FileInfoSetAttributeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttribute",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> Bool -> m ()
fileInfoSetAttributeBoolean a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeBooleanMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeBoolean

instance O.OverloadedMethodInfo FileInfoSetAttributeBooleanMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeBoolean",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> Text -> m ()
fileInfoSetAttributeByteString a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeByteStringMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeByteString

instance O.OverloadedMethodInfo FileInfoSetAttributeByteStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeByteString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> Int32 -> m ()
fileInfoSetAttributeInt32 a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeInt32MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeInt32

instance O.OverloadedMethodInfo FileInfoSetAttributeInt32MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeInt32",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> Int64 -> m ()
fileInfoSetAttributeInt64 a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeInt64MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeInt64

instance O.OverloadedMethodInfo FileInfoSetAttributeInt64MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeInt64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> FileAttributeMatcher -> m ()
fileInfoSetAttributeMask a
info 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.OverloadedMethod FileInfoSetAttributeMaskMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeMask

instance O.OverloadedMethodInfo FileInfoSetAttributeMaskMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeMask",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileInfo a, IsObject b) =>
a -> Text -> b -> m ()
fileInfoSetAttributeObject a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeObjectMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeObject

instance O.OverloadedMethodInfo FileInfoSetAttributeObjectMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeObject",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> FileAttributeStatus -> m Bool
fileInfoSetAttributeStatus a
info Text
attribute 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
/= CInt
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.OverloadedMethod FileInfoSetAttributeStatusMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeStatus

instance O.OverloadedMethodInfo FileInfoSetAttributeStatusMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeStatus",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> Text -> m ()
fileInfoSetAttributeString a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeStringMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeString

instance O.OverloadedMethodInfo FileInfoSetAttributeStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> [Text] -> m ()
fileInfoSetAttributeStringv a
info Text
attribute [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.OverloadedMethod FileInfoSetAttributeStringvMethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeStringv

instance O.OverloadedMethodInfo FileInfoSetAttributeStringvMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeStringv",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> Word32 -> m ()
fileInfoSetAttributeUint32 a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeUint32MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeUint32

instance O.OverloadedMethodInfo FileInfoSetAttributeUint32MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeUint32",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> Word64 -> m ()
fileInfoSetAttributeUint64 a
info Text
attribute 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.OverloadedMethod FileInfoSetAttributeUint64MethodInfo a signature where
    overloadedMethod = fileInfoSetAttributeUint64

instance O.OverloadedMethodInfo FileInfoSetAttributeUint64MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetAttributeUint64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m ()
fileInfoSetContentType a
info 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.OverloadedMethod FileInfoSetContentTypeMethodInfo a signature where
    overloadedMethod = fileInfoSetContentType

instance O.OverloadedMethodInfo FileInfoSetContentTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetContentType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoSetContentType"
        })


#endif

-- method FileInfo::set_creation_date_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 = "creation_time"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DateTime" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDateTime." , 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_creation_date_time" g_file_info_set_creation_date_time :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr GLib.DateTime.DateTime ->           -- creation_time : TInterface (Name {namespace = "GLib", name = "DateTime"})
    IO ()

-- | Sets the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_CREATED' and
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_CREATED_USEC' attributes in the file info to the
-- given date\/time value.
-- 
-- /Since: 2.70/
fileInfoSetCreationDateTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> GLib.DateTime.DateTime
    -- ^ /@creationTime@/: a t'GI.GLib.Structs.DateTime.DateTime'.
    -> m ()
fileInfoSetCreationDateTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> DateTime -> m ()
fileInfoSetCreationDateTime a
info DateTime
creationTime = 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 DateTime
creationTime' <- DateTime -> IO (Ptr DateTime)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DateTime
creationTime
    Ptr FileInfo -> Ptr DateTime -> IO ()
g_file_info_set_creation_date_time Ptr FileInfo
info' Ptr DateTime
creationTime'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    DateTime -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DateTime
creationTime
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetCreationDateTimeMethodInfo
instance (signature ~ (GLib.DateTime.DateTime -> m ()), MonadIO m, IsFileInfo a) => O.OverloadedMethod FileInfoSetCreationDateTimeMethodInfo a signature where
    overloadedMethod = fileInfoSetCreationDateTime

instance O.OverloadedMethodInfo FileInfoSetCreationDateTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetCreationDateTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoSetCreationDateTime"
        })


#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m ()
fileInfoSetDisplayName a
info 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.OverloadedMethod FileInfoSetDisplayNameMethodInfo a signature where
    overloadedMethod = fileInfoSetDisplayName

instance O.OverloadedMethodInfo FileInfoSetDisplayNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetDisplayName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m ()
fileInfoSetEditName a
info 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.OverloadedMethod FileInfoSetEditNameMethodInfo a signature where
    overloadedMethod = fileInfoSetEditName

instance O.OverloadedMethodInfo FileInfoSetEditNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetEditName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> FileType -> m ()
fileInfoSetFileType a
info 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.OverloadedMethod FileInfoSetFileTypeMethodInfo a signature where
    overloadedMethod = fileInfoSetFileType

instance O.OverloadedMethodInfo FileInfoSetFileTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetFileType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileInfo a, IsIcon b) =>
a -> b -> m ()
fileInfoSetIcon a
info 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.OverloadedMethod FileInfoSetIconMethodInfo a signature where
    overloadedMethod = fileInfoSetIcon

instance O.OverloadedMethodInfo FileInfoSetIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Bool -> m ()
fileInfoSetIsHidden a
info 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.OverloadedMethod FileInfoSetIsHiddenMethodInfo a signature where
    overloadedMethod = fileInfoSetIsHidden

instance O.OverloadedMethodInfo FileInfoSetIsHiddenMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetIsHidden",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Bool -> m ()
fileInfoSetIsSymlink a
info 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.OverloadedMethod FileInfoSetIsSymlinkMethodInfo a signature where
    overloadedMethod = fileInfoSetIsSymlink

instance O.OverloadedMethodInfo FileInfoSetIsSymlinkMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetIsSymlink",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoSetIsSymlink"
        })


#endif

-- method FileInfo::set_modification_date_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 = "DateTime" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDateTime." , 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_date_time" g_file_info_set_modification_date_time :: 
    Ptr FileInfo ->                         -- info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr GLib.DateTime.DateTime ->           -- mtime : TInterface (Name {namespace = "GLib", name = "DateTime"})
    IO ()

-- | Sets the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_MODIFIED' and
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_MODIFIED_USEC' attributes in the file info to the
-- given date\/time value.
-- 
-- /Since: 2.62/
fileInfoSetModificationDateTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsFileInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.FileInfo.FileInfo'.
    -> GLib.DateTime.DateTime
    -- ^ /@mtime@/: a t'GI.GLib.Structs.DateTime.DateTime'.
    -> m ()
fileInfoSetModificationDateTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> DateTime -> m ()
fileInfoSetModificationDateTime a
info DateTime
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 DateTime
mtime' <- DateTime -> IO (Ptr DateTime)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DateTime
mtime
    Ptr FileInfo -> Ptr DateTime -> IO ()
g_file_info_set_modification_date_time Ptr FileInfo
info' Ptr DateTime
mtime'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    DateTime -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DateTime
mtime
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FileInfoSetModificationDateTimeMethodInfo
instance (signature ~ (GLib.DateTime.DateTime -> m ()), MonadIO m, IsFileInfo a) => O.OverloadedMethod FileInfoSetModificationDateTimeMethodInfo a signature where
    overloadedMethod = fileInfoSetModificationDateTime

instance O.OverloadedMethodInfo FileInfoSetModificationDateTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetModificationDateTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoSetModificationDateTime"
        })


#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 ()

{-# DEPRECATED fileInfoSetModificationTime ["(Since version 2.62)","Use 'GI.Gio.Objects.FileInfo.fileInfoSetModificationDateTime' instead, as","   t'GI.GLib.Structs.TimeVal.TimeVal' is deprecated due to the year 2038 problem."] #-}
-- | Sets the 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_MODIFIED' and
-- 'GI.Gio.Constants.FILE_ATTRIBUTE_TIME_MODIFIED_USEC' attributes 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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> TimeVal -> m ()
fileInfoSetModificationTime a
info 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.OverloadedMethod FileInfoSetModificationTimeMethodInfo a signature where
    overloadedMethod = fileInfoSetModificationTime

instance O.OverloadedMethodInfo FileInfoSetModificationTimeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetModificationTime",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> [Char] -> m ()
fileInfoSetName a
info [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.OverloadedMethod FileInfoSetNameMethodInfo a signature where
    overloadedMethod = fileInfoSetName

instance O.OverloadedMethodInfo FileInfoSetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Int64 -> m ()
fileInfoSetSize a
info 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.OverloadedMethod FileInfoSetSizeMethodInfo a signature where
    overloadedMethod = fileInfoSetSize

instance O.OverloadedMethodInfo FileInfoSetSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Int32 -> m ()
fileInfoSetSortOrder a
info 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.OverloadedMethod FileInfoSetSortOrderMethodInfo a signature where
    overloadedMethod = fileInfoSetSortOrder

instance O.OverloadedMethodInfo FileInfoSetSortOrderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetSortOrder",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFileInfo a, IsIcon b) =>
a -> b -> m ()
fileInfoSetSymbolicIcon a
info 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.OverloadedMethod FileInfoSetSymbolicIconMethodInfo a signature where
    overloadedMethod = fileInfoSetSymbolicIcon

instance O.OverloadedMethodInfo FileInfoSetSymbolicIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetSymbolicIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> Text -> m ()
fileInfoSetSymlinkTarget a
info 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.OverloadedMethod FileInfoSetSymlinkTargetMethodInfo a signature where
    overloadedMethod = fileInfoSetSymlinkTarget

instance O.OverloadedMethodInfo FileInfoSetSymlinkTargetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoSetSymlinkTarget",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFileInfo a) =>
a -> m ()
fileInfoUnsetAttributeMask 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.OverloadedMethod FileInfoUnsetAttributeMaskMethodInfo a signature where
    overloadedMethod = fileInfoUnsetAttributeMask

instance O.OverloadedMethodInfo FileInfoUnsetAttributeMaskMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FileInfo.fileInfoUnsetAttributeMask",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-FileInfo.html#v:fileInfoUnsetAttributeMask"
        })


#endif