{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Structs.RecentInfo.RecentInfo'-struct contains private data only, and should
-- be accessed using the provided API.
-- 
-- t'GI.Gtk.Structs.RecentInfo.RecentInfo' constains all the meta-data
-- associated with an entry in the recently used files list.
-- 
-- /Since: 2.10/

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

module GI.Gtk.Structs.RecentInfo
    ( 

-- * Exported types
    RecentInfo(..)                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveRecentInfoMethod                 ,
#endif


-- ** createAppInfo #method:createAppInfo#

#if defined(ENABLE_OVERLOADING)
    RecentInfoCreateAppInfoMethodInfo       ,
#endif
    recentInfoCreateAppInfo                 ,


-- ** exists #method:exists#

#if defined(ENABLE_OVERLOADING)
    RecentInfoExistsMethodInfo              ,
#endif
    recentInfoExists                        ,


-- ** getAdded #method:getAdded#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetAddedMethodInfo            ,
#endif
    recentInfoGetAdded                      ,


-- ** getAge #method:getAge#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetAgeMethodInfo              ,
#endif
    recentInfoGetAge                        ,


-- ** getApplicationInfo #method:getApplicationInfo#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetApplicationInfoMethodInfo  ,
#endif
    recentInfoGetApplicationInfo            ,


-- ** getApplications #method:getApplications#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetApplicationsMethodInfo     ,
#endif
    recentInfoGetApplications               ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetDescriptionMethodInfo      ,
#endif
    recentInfoGetDescription                ,


-- ** getDisplayName #method:getDisplayName#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetDisplayNameMethodInfo      ,
#endif
    recentInfoGetDisplayName                ,


-- ** getGicon #method:getGicon#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetGiconMethodInfo            ,
#endif
    recentInfoGetGicon                      ,


-- ** getGroups #method:getGroups#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetGroupsMethodInfo           ,
#endif
    recentInfoGetGroups                     ,


-- ** getIcon #method:getIcon#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetIconMethodInfo             ,
#endif
    recentInfoGetIcon                       ,


-- ** getMimeType #method:getMimeType#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetMimeTypeMethodInfo         ,
#endif
    recentInfoGetMimeType                   ,


-- ** getModified #method:getModified#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetModifiedMethodInfo         ,
#endif
    recentInfoGetModified                   ,


-- ** getPrivateHint #method:getPrivateHint#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetPrivateHintMethodInfo      ,
#endif
    recentInfoGetPrivateHint                ,


-- ** getShortName #method:getShortName#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetShortNameMethodInfo        ,
#endif
    recentInfoGetShortName                  ,


-- ** getUri #method:getUri#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetUriMethodInfo              ,
#endif
    recentInfoGetUri                        ,


-- ** getUriDisplay #method:getUriDisplay#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetUriDisplayMethodInfo       ,
#endif
    recentInfoGetUriDisplay                 ,


-- ** getVisited #method:getVisited#

#if defined(ENABLE_OVERLOADING)
    RecentInfoGetVisitedMethodInfo          ,
#endif
    recentInfoGetVisited                    ,


-- ** hasApplication #method:hasApplication#

#if defined(ENABLE_OVERLOADING)
    RecentInfoHasApplicationMethodInfo      ,
#endif
    recentInfoHasApplication                ,


-- ** hasGroup #method:hasGroup#

#if defined(ENABLE_OVERLOADING)
    RecentInfoHasGroupMethodInfo            ,
#endif
    recentInfoHasGroup                      ,


-- ** isLocal #method:isLocal#

#if defined(ENABLE_OVERLOADING)
    RecentInfoIsLocalMethodInfo             ,
#endif
    recentInfoIsLocal                       ,


-- ** lastApplication #method:lastApplication#

#if defined(ENABLE_OVERLOADING)
    RecentInfoLastApplicationMethodInfo     ,
#endif
    recentInfoLastApplication               ,


-- ** match #method:match#

#if defined(ENABLE_OVERLOADING)
    RecentInfoMatchMethodInfo               ,
#endif
    recentInfoMatch                         ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    RecentInfoRefMethodInfo                 ,
#endif
    recentInfoRef                           ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    RecentInfoUnrefMethodInfo               ,
#endif
    recentInfoUnref                         ,




    ) 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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import qualified GI.Gio.Interfaces.Icon as Gio.Icon

-- | Memory-managed wrapper type.
newtype RecentInfo = RecentInfo (SP.ManagedPtr RecentInfo)
    deriving (RecentInfo -> RecentInfo -> Bool
(RecentInfo -> RecentInfo -> Bool)
-> (RecentInfo -> RecentInfo -> Bool) -> Eq RecentInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecentInfo -> RecentInfo -> Bool
$c/= :: RecentInfo -> RecentInfo -> Bool
== :: RecentInfo -> RecentInfo -> Bool
$c== :: RecentInfo -> RecentInfo -> Bool
Eq)

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

foreign import ccall "gtk_recent_info_get_type" c_gtk_recent_info_get_type :: 
    IO GType

type instance O.ParentTypes RecentInfo = '[]
instance O.HasParentTypes RecentInfo

instance B.Types.TypedObject RecentInfo where
    glibType :: IO GType
glibType = IO GType
c_gtk_recent_info_get_type

instance B.Types.GBoxed RecentInfo

-- | Convert 'RecentInfo' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue RecentInfo where
    toGValue :: RecentInfo -> IO GValue
toGValue RecentInfo
o = do
        GType
gtype <- IO GType
c_gtk_recent_info_get_type
        RecentInfo -> (Ptr RecentInfo -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RecentInfo
o (GType
-> (GValue -> Ptr RecentInfo -> IO ())
-> Ptr RecentInfo
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr RecentInfo -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO RecentInfo
fromGValue GValue
gv = do
        Ptr RecentInfo
ptr <- GValue -> IO (Ptr RecentInfo)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr RecentInfo)
        (ManagedPtr RecentInfo -> RecentInfo)
-> Ptr RecentInfo -> IO RecentInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr RecentInfo -> RecentInfo
RecentInfo Ptr RecentInfo
ptr
        
    


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

-- method RecentInfo::create_app_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "app_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the application that should\n  be mapped to a #GAppInfo; if %NULL is used then the default\n  application for the MIME type is used"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "AppInfo" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_recent_info_create_app_info" gtk_recent_info_create_app_info :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    CString ->                              -- app_name : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.AppInfo.AppInfo)

-- | Creates a t'GI.Gio.Interfaces.AppInfo.AppInfo' for the specified t'GI.Gtk.Structs.RecentInfo.RecentInfo'
recentInfoCreateAppInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> Maybe (T.Text)
    -- ^ /@appName@/: the name of the application that should
    --   be mapped to a t'GI.Gio.Interfaces.AppInfo.AppInfo'; if 'P.Nothing' is used then the default
    --   application for the MIME type is used
    -> m (Maybe Gio.AppInfo.AppInfo)
    -- ^ __Returns:__ the newly created t'GI.Gio.Interfaces.AppInfo.AppInfo', or 'P.Nothing'.
    --   In case of error, /@error@/ will be set either with a
    --   @/GTK_RECENT_MANAGER_ERROR/@ or a @/G_IO_ERROR/@ /(Can throw 'Data.GI.Base.GError.GError')/
recentInfoCreateAppInfo :: RecentInfo -> Maybe Text -> m (Maybe AppInfo)
recentInfoCreateAppInfo RecentInfo
info Maybe Text
appName = IO (Maybe AppInfo) -> m (Maybe AppInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AppInfo) -> m (Maybe AppInfo))
-> IO (Maybe AppInfo) -> m (Maybe AppInfo)
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
maybeAppName <- case Maybe Text
appName of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jAppName -> do
            Ptr CChar
jAppName' <- Text -> IO (Ptr CChar)
textToCString Text
jAppName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jAppName'
    IO (Maybe AppInfo) -> IO () -> IO (Maybe AppInfo)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr AppInfo
result <- (Ptr (Ptr GError) -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo))
-> (Ptr (Ptr GError) -> IO (Ptr AppInfo)) -> IO (Ptr AppInfo)
forall a b. (a -> b) -> a -> b
$ Ptr RecentInfo -> Ptr CChar -> Ptr (Ptr GError) -> IO (Ptr AppInfo)
gtk_recent_info_create_app_info Ptr RecentInfo
info' Ptr CChar
maybeAppName
        Maybe AppInfo
maybeResult <- Ptr AppInfo -> (Ptr AppInfo -> IO AppInfo) -> IO (Maybe AppInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AppInfo
result ((Ptr AppInfo -> IO AppInfo) -> IO (Maybe AppInfo))
-> (Ptr AppInfo -> IO AppInfo) -> IO (Maybe AppInfo)
forall a b. (a -> b) -> a -> b
$ \Ptr AppInfo
result' -> do
            AppInfo
result'' <- ((ManagedPtr AppInfo -> AppInfo) -> Ptr AppInfo -> IO AppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AppInfo -> AppInfo
Gio.AppInfo.AppInfo) Ptr AppInfo
result'
            AppInfo -> IO AppInfo
forall (m :: * -> *) a. Monad m => a -> m a
return AppInfo
result''
        RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeAppName
        Maybe AppInfo -> IO (Maybe AppInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AppInfo
maybeResult
     ) (do
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeAppName
     )

#if defined(ENABLE_OVERLOADING)
data RecentInfoCreateAppInfoMethodInfo
instance (signature ~ (Maybe (T.Text) -> m (Maybe Gio.AppInfo.AppInfo)), MonadIO m) => O.MethodInfo RecentInfoCreateAppInfoMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoCreateAppInfo

#endif

-- method RecentInfo::exists
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_exists" gtk_recent_info_exists :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CInt

-- | Checks whether the resource pointed by /@info@/ still exists.
-- At the moment this check is done only on resources pointing
-- to local files.
-- 
-- /Since: 2.10/
recentInfoExists ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the resource exists
recentInfoExists :: RecentInfo -> m Bool
recentInfoExists RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    CInt
result <- Ptr RecentInfo -> IO CInt
gtk_recent_info_exists Ptr RecentInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoExistsMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo RecentInfoExistsMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoExists

#endif

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

foreign import ccall "gtk_recent_info_get_added" gtk_recent_info_get_added :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CLong

-- | Gets the timestamp (seconds from system’s Epoch) when the resource
-- was added to the recently used resources list.
-- 
-- /Since: 2.10/
recentInfoGetAdded ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m CLong
    -- ^ __Returns:__ the number of seconds elapsed from system’s Epoch when
    --   the resource was added to the list, or -1 on failure.
recentInfoGetAdded :: RecentInfo -> m CLong
recentInfoGetAdded RecentInfo
info = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    CLong
result <- Ptr RecentInfo -> IO CLong
gtk_recent_info_get_added Ptr RecentInfo
info'
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetAddedMethodInfo
instance (signature ~ (m CLong), MonadIO m) => O.MethodInfo RecentInfoGetAddedMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetAdded

#endif

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

foreign import ccall "gtk_recent_info_get_age" gtk_recent_info_get_age :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO Int32

-- | Gets the number of days elapsed since the last update
-- of the resource pointed by /@info@/.
-- 
-- /Since: 2.10/
recentInfoGetAge ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m Int32
    -- ^ __Returns:__ a positive integer containing the number of days
    --   elapsed since the time this resource was last modified
recentInfoGetAge :: RecentInfo -> m Int32
recentInfoGetAge RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Int32
result <- Ptr RecentInfo -> IO Int32
gtk_recent_info_get_age Ptr RecentInfo
info'
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetAgeMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo RecentInfoGetAgeMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetAge

#endif

-- method RecentInfo::get_application_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "app_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the name of the application that has registered this item"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "app_exec"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the string containing\n   the command line"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the number of times this item was registered"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "time_"
--           , argType = TBasicType TLong
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the timestamp this item was last registered\n   for this application"
--                 , 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 "gtk_recent_info_get_application_info" gtk_recent_info_get_application_info :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    CString ->                              -- app_name : TBasicType TUTF8
    Ptr CString ->                          -- app_exec : TBasicType TUTF8
    Ptr Word32 ->                           -- count : TBasicType TUInt
    Ptr CLong ->                            -- time_ : TBasicType TLong
    IO CInt

-- | Gets the data regarding the application that has registered the resource
-- pointed by /@info@/.
-- 
-- If the command line contains any escape characters defined inside the
-- storage specification, they will be expanded.
-- 
-- /Since: 2.10/
recentInfoGetApplicationInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> T.Text
    -- ^ /@appName@/: the name of the application that has registered this item
    -> m ((Bool, T.Text, Word32, CLong))
    -- ^ __Returns:__ 'P.True' if an application with /@appName@/ has registered this
    --   resource inside the recently used list, or 'P.False' otherwise. The
    --   /@appExec@/ string is owned by the t'GI.Gtk.Structs.RecentInfo.RecentInfo' and should not be
    --   modified or freed
recentInfoGetApplicationInfo :: RecentInfo -> Text -> m (Bool, Text, Word32, CLong)
recentInfoGetApplicationInfo RecentInfo
info Text
appName = IO (Bool, Text, Word32, CLong) -> m (Bool, Text, Word32, CLong)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Text, Word32, CLong) -> m (Bool, Text, Word32, CLong))
-> IO (Bool, Text, Word32, CLong) -> m (Bool, Text, Word32, CLong)
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
appName' <- Text -> IO (Ptr CChar)
textToCString Text
appName
    Ptr (Ptr CChar)
appExec <- IO (Ptr (Ptr CChar))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    Ptr Word32
count <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr CLong
time_ <- IO (Ptr CLong)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CLong)
    CInt
result <- Ptr RecentInfo
-> Ptr CChar
-> Ptr (Ptr CChar)
-> Ptr Word32
-> Ptr CLong
-> IO CInt
gtk_recent_info_get_application_info Ptr RecentInfo
info' Ptr CChar
appName' Ptr (Ptr CChar)
appExec Ptr Word32
count Ptr CLong
time_
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr CChar
appExec' <- Ptr (Ptr CChar) -> IO (Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CChar)
appExec
    Text
appExec'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
appExec'
    Word32
count' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
count
    CLong
time_' <- Ptr CLong -> IO CLong
forall a. Storable a => Ptr a -> IO a
peek Ptr CLong
time_
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
appName'
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
appExec
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
count
    Ptr CLong -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CLong
time_
    (Bool, Text, Word32, CLong) -> IO (Bool, Text, Word32, CLong)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Text
appExec'', Word32
count', CLong
time_')

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetApplicationInfoMethodInfo
instance (signature ~ (T.Text -> m ((Bool, T.Text, Word32, CLong))), MonadIO m) => O.MethodInfo RecentInfoGetApplicationInfoMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetApplicationInfo

#endif

-- method RecentInfo::get_applications
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the length of the returned list"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) 1 (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_info_get_applications" gtk_recent_info_get_applications :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    IO (Ptr CString)

-- | Retrieves the list of applications that have registered this resource.
-- 
-- /Since: 2.10/
recentInfoGetApplications ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m (([T.Text], Word64))
    -- ^ __Returns:__ 
    --     a newly allocated 'P.Nothing'-terminated array of strings.
    --     Use 'GI.GLib.Functions.strfreev' to free it.
recentInfoGetApplications :: RecentInfo -> m ([Text], Word64)
recentInfoGetApplications RecentInfo
info = IO ([Text], Word64) -> m ([Text], Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], Word64) -> m ([Text], Word64))
-> IO ([Text], Word64) -> m ([Text], Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr (Ptr CChar)
result <- Ptr RecentInfo -> Ptr Word64 -> IO (Ptr (Ptr CChar))
gtk_recent_info_get_applications Ptr RecentInfo
info' Ptr Word64
length_
    Text -> Ptr (Ptr CChar) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoGetApplications" Ptr (Ptr CChar)
result
    [Text]
result' <- HasCallStack => Ptr (Ptr CChar) -> IO [Text]
Ptr (Ptr CChar) -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr (Ptr CChar)
result
    (Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
result
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
result
    Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
    ([Text], Word64) -> IO ([Text], Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
result', Word64
length_')

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetApplicationsMethodInfo
instance (signature ~ (m (([T.Text], Word64))), MonadIO m) => O.MethodInfo RecentInfoGetApplicationsMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetApplications

#endif

-- method RecentInfo::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_get_description" gtk_recent_info_get_description :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CString

-- | Gets the (short) description of the resource.
-- 
-- /Since: 2.10/
recentInfoGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m T.Text
    -- ^ __Returns:__ the description of the resource. The returned string
    --   is owned by the recent manager, and should not be freed.
recentInfoGetDescription :: RecentInfo -> m Text
recentInfoGetDescription RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
result <- Ptr RecentInfo -> IO (Ptr CChar)
gtk_recent_info_get_description Ptr RecentInfo
info'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoGetDescription" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo RecentInfoGetDescriptionMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetDescription

#endif

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

-- | Gets the name of the resource. If none has been defined, the basename
-- of the resource is obtained.
-- 
-- /Since: 2.10/
recentInfoGetDisplayName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m T.Text
    -- ^ __Returns:__ the display name of the resource. The returned string
    --   is owned by the recent manager, and should not be freed.
recentInfoGetDisplayName :: RecentInfo -> m Text
recentInfoGetDisplayName RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
result <- Ptr RecentInfo -> IO (Ptr CChar)
gtk_recent_info_get_display_name Ptr RecentInfo
info'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoGetDisplayName" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetDisplayNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo RecentInfoGetDisplayNameMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetDisplayName

#endif

-- method RecentInfo::get_gicon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_get_gicon" gtk_recent_info_get_gicon :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO (Ptr Gio.Icon.Icon)

-- | Retrieves the icon associated to the resource MIME type.
-- 
-- /Since: 2.22/
recentInfoGetGicon ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m (Maybe Gio.Icon.Icon)
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.Icon.Icon' containing the icon, or 'P.Nothing'.
    --   Use 'GI.GObject.Objects.Object.objectUnref' when finished using the icon
recentInfoGetGicon :: RecentInfo -> m (Maybe Icon)
recentInfoGetGicon RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr Icon
result <- Ptr RecentInfo -> IO (Ptr Icon)
gtk_recent_info_get_gicon Ptr RecentInfo
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
wrapObject ManagedPtr Icon -> Icon
Gio.Icon.Icon) Ptr Icon
result'
        Icon -> IO Icon
forall (m :: * -> *) a. Monad m => a -> m a
return Icon
result''
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Maybe Icon -> IO (Maybe Icon)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Icon
maybeResult

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetGiconMethodInfo
instance (signature ~ (m (Maybe Gio.Icon.Icon)), MonadIO m) => O.MethodInfo RecentInfoGetGiconMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetGicon

#endif

-- method RecentInfo::get_groups
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the number of groups returned"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) 1 (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_info_get_groups" gtk_recent_info_get_groups :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    IO (Ptr CString)

-- | Returns all groups registered for the recently used item /@info@/.
-- The array of returned group names will be 'P.Nothing' terminated, so
-- length might optionally be 'P.Nothing'.
-- 
-- /Since: 2.10/
recentInfoGetGroups ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m (([T.Text], Word64))
    -- ^ __Returns:__ 
    --   a newly allocated 'P.Nothing' terminated array of strings.
    --   Use 'GI.GLib.Functions.strfreev' to free it.
recentInfoGetGroups :: RecentInfo -> m ([Text], Word64)
recentInfoGetGroups RecentInfo
info = IO ([Text], Word64) -> m ([Text], Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], Word64) -> m ([Text], Word64))
-> IO ([Text], Word64) -> m ([Text], Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr (Ptr CChar)
result <- Ptr RecentInfo -> Ptr Word64 -> IO (Ptr (Ptr CChar))
gtk_recent_info_get_groups Ptr RecentInfo
info' Ptr Word64
length_
    Text -> Ptr (Ptr CChar) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoGetGroups" Ptr (Ptr CChar)
result
    [Text]
result' <- HasCallStack => Ptr (Ptr CChar) -> IO [Text]
Ptr (Ptr CChar) -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr (Ptr CChar)
result
    (Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
result
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
result
    Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
    ([Text], Word64) -> IO ([Text], Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
result', Word64
length_')

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetGroupsMethodInfo
instance (signature ~ (m (([T.Text], Word64))), MonadIO m) => O.MethodInfo RecentInfoGetGroupsMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetGroups

#endif

-- method RecentInfo::get_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the size of the icon in pixels"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_recent_info_get_icon" gtk_recent_info_get_icon :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    Int32 ->                                -- size : TBasicType TInt
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Retrieves the icon of size /@size@/ associated to the resource MIME type.
-- 
-- /Since: 2.10/
recentInfoGetIcon ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> Int32
    -- ^ /@size@/: the size of the icon in pixels
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    -- ^ __Returns:__ a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' containing the icon,
    --     or 'P.Nothing'. Use 'GI.GObject.Objects.Object.objectUnref' when finished using the icon.
recentInfoGetIcon :: RecentInfo -> Int32 -> m (Maybe Pixbuf)
recentInfoGetIcon RecentInfo
info Int32
size = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr Pixbuf
result <- Ptr RecentInfo -> Int32 -> IO (Ptr Pixbuf)
gtk_recent_info_get_icon Ptr RecentInfo
info' Int32
size
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetIconMethodInfo
instance (signature ~ (Int32 -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m) => O.MethodInfo RecentInfoGetIconMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetIcon

#endif

-- method RecentInfo::get_mime_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_get_mime_type" gtk_recent_info_get_mime_type :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CString

-- | Gets the MIME type of the resource.
-- 
-- /Since: 2.10/
recentInfoGetMimeType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m T.Text
    -- ^ __Returns:__ the MIME type of the resource. The returned string
    --   is owned by the recent manager, and should not be freed.
recentInfoGetMimeType :: RecentInfo -> m Text
recentInfoGetMimeType RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
result <- Ptr RecentInfo -> IO (Ptr CChar)
gtk_recent_info_get_mime_type Ptr RecentInfo
info'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoGetMimeType" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetMimeTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo RecentInfoGetMimeTypeMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetMimeType

#endif

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

foreign import ccall "gtk_recent_info_get_modified" gtk_recent_info_get_modified :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CLong

-- | Gets the timestamp (seconds from system’s Epoch) when the meta-data
-- for the resource was last modified.
-- 
-- /Since: 2.10/
recentInfoGetModified ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m CLong
    -- ^ __Returns:__ the number of seconds elapsed from system’s Epoch when
    --   the resource was last modified, or -1 on failure.
recentInfoGetModified :: RecentInfo -> m CLong
recentInfoGetModified RecentInfo
info = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    CLong
result <- Ptr RecentInfo -> IO CLong
gtk_recent_info_get_modified Ptr RecentInfo
info'
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetModifiedMethodInfo
instance (signature ~ (m CLong), MonadIO m) => O.MethodInfo RecentInfoGetModifiedMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetModified

#endif

-- method RecentInfo::get_private_hint
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_get_private_hint" gtk_recent_info_get_private_hint :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CInt

-- | Gets the value of the “private” flag. Resources in the recently used
-- list that have this flag set to 'P.True' should only be displayed by the
-- applications that have registered them.
-- 
-- /Since: 2.10/
recentInfoGetPrivateHint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the private flag was found, 'P.False' otherwise
recentInfoGetPrivateHint :: RecentInfo -> m Bool
recentInfoGetPrivateHint RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    CInt
result <- Ptr RecentInfo -> IO CInt
gtk_recent_info_get_private_hint Ptr RecentInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetPrivateHintMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo RecentInfoGetPrivateHintMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetPrivateHint

#endif

-- method RecentInfo::get_short_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #GtkRecentInfo" , 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 "gtk_recent_info_get_short_name" gtk_recent_info_get_short_name :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CString

-- | Computes a valid UTF-8 string that can be used as the
-- name of the item in a menu or list. For example, calling
-- this function on an item that refers to
-- “file:\/\/\/foo\/bar.txt” will yield “bar.txt”.
-- 
-- /Since: 2.10/
recentInfoGetShortName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: an t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m T.Text
    -- ^ __Returns:__ A newly-allocated string in UTF-8 encoding
    --   free it with 'GI.GLib.Functions.free'
recentInfoGetShortName :: RecentInfo -> m Text
recentInfoGetShortName RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
result <- Ptr RecentInfo -> IO (Ptr CChar)
gtk_recent_info_get_short_name Ptr RecentInfo
info'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoGetShortName" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetShortNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo RecentInfoGetShortNameMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetShortName

#endif

-- method RecentInfo::get_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_get_uri" gtk_recent_info_get_uri :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CString

-- | Gets the URI of the resource.
-- 
-- /Since: 2.10/
recentInfoGetUri ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m T.Text
    -- ^ __Returns:__ the URI of the resource. The returned string is
    --   owned by the recent manager, and should not be freed.
recentInfoGetUri :: RecentInfo -> m Text
recentInfoGetUri RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
result <- Ptr RecentInfo -> IO (Ptr CChar)
gtk_recent_info_get_uri Ptr RecentInfo
info'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoGetUri" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo RecentInfoGetUriMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetUri

#endif

-- method RecentInfo::get_uri_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_get_uri_display" gtk_recent_info_get_uri_display :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CString

-- | Gets a displayable version of the resource’s URI. If the resource
-- is local, it returns a local path; if the resource is not local,
-- it returns the UTF-8 encoded content of 'GI.Gtk.Structs.RecentInfo.recentInfoGetUri'.
-- 
-- /Since: 2.10/
recentInfoGetUriDisplay ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a newly allocated UTF-8 string containing the
    --   resource’s URI or 'P.Nothing'. Use 'GI.GLib.Functions.free' when done using it.
recentInfoGetUriDisplay :: RecentInfo -> m (Maybe Text)
recentInfoGetUriDisplay RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
result <- Ptr RecentInfo -> IO (Ptr CChar)
gtk_recent_info_get_uri_display Ptr RecentInfo
info'
    Maybe Text
maybeResult <- Ptr CChar -> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CChar
result ((Ptr CChar -> IO Text) -> IO (Maybe Text))
-> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
result' -> do
        Text
result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetUriDisplayMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.MethodInfo RecentInfoGetUriDisplayMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetUriDisplay

#endif

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

foreign import ccall "gtk_recent_info_get_visited" gtk_recent_info_get_visited :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CLong

-- | Gets the timestamp (seconds from system’s Epoch) when the meta-data
-- for the resource was last visited.
-- 
-- /Since: 2.10/
recentInfoGetVisited ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m CLong
    -- ^ __Returns:__ the number of seconds elapsed from system’s Epoch when
    --   the resource was last visited, or -1 on failure.
recentInfoGetVisited :: RecentInfo -> m CLong
recentInfoGetVisited RecentInfo
info = IO CLong -> m CLong
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CLong -> m CLong) -> IO CLong -> m CLong
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    CLong
result <- Ptr RecentInfo -> IO CLong
gtk_recent_info_get_visited Ptr RecentInfo
info'
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result

#if defined(ENABLE_OVERLOADING)
data RecentInfoGetVisitedMethodInfo
instance (signature ~ (m CLong), MonadIO m) => O.MethodInfo RecentInfoGetVisitedMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoGetVisited

#endif

-- method RecentInfo::has_application
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "app_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing an application name"
--                 , 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 "gtk_recent_info_has_application" gtk_recent_info_has_application :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    CString ->                              -- app_name : TBasicType TUTF8
    IO CInt

-- | Checks whether an application registered this resource using /@appName@/.
-- 
-- /Since: 2.10/
recentInfoHasApplication ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> T.Text
    -- ^ /@appName@/: a string containing an application name
    -> m Bool
    -- ^ __Returns:__ 'P.True' if an application with name /@appName@/ was found,
    --   'P.False' otherwise
recentInfoHasApplication :: RecentInfo -> Text -> m Bool
recentInfoHasApplication RecentInfo
info Text
appName = 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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
appName' <- Text -> IO (Ptr CChar)
textToCString Text
appName
    CInt
result <- Ptr RecentInfo -> Ptr CChar -> IO CInt
gtk_recent_info_has_application Ptr RecentInfo
info' Ptr CChar
appName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
appName'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoHasApplicationMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo RecentInfoHasApplicationMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoHasApplication

#endif

-- method RecentInfo::has_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name of a group" , 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 "gtk_recent_info_has_group" gtk_recent_info_has_group :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    CString ->                              -- group_name : TBasicType TUTF8
    IO CInt

-- | Checks whether /@groupName@/ appears inside the groups
-- registered for the recently used item /@info@/.
-- 
-- /Since: 2.10/
recentInfoHasGroup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> T.Text
    -- ^ /@groupName@/: name of a group
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the group was found
recentInfoHasGroup :: RecentInfo -> Text -> m Bool
recentInfoHasGroup RecentInfo
info Text
groupName = 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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
groupName' <- Text -> IO (Ptr CChar)
textToCString Text
groupName
    CInt
result <- Ptr RecentInfo -> Ptr CChar -> IO CInt
gtk_recent_info_has_group Ptr RecentInfo
info' Ptr CChar
groupName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
groupName'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoHasGroupMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo RecentInfoHasGroupMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoHasGroup

#endif

-- method RecentInfo::is_local
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_is_local" gtk_recent_info_is_local :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CInt

-- | Checks whether the resource is local or not by looking at the
-- scheme of its URI.
-- 
-- /Since: 2.10/
recentInfoIsLocal ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the resource is local
recentInfoIsLocal :: RecentInfo -> m Bool
recentInfoIsLocal RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    CInt
result <- Ptr RecentInfo -> IO CInt
gtk_recent_info_is_local Ptr RecentInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoIsLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo RecentInfoIsLocalMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoIsLocal

#endif

-- method RecentInfo::last_application
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_last_application" gtk_recent_info_last_application :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CString

-- | Gets the name of the last application that have registered the
-- recently used resource represented by /@info@/.
-- 
-- /Since: 2.10/
recentInfoLastApplication ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m T.Text
    -- ^ __Returns:__ an application name. Use 'GI.GLib.Functions.free' to free it.
recentInfoLastApplication :: RecentInfo -> m Text
recentInfoLastApplication RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr CChar
result <- Ptr RecentInfo -> IO (Ptr CChar)
gtk_recent_info_last_application Ptr RecentInfo
info'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoLastApplication" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoLastApplicationMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo RecentInfoLastApplicationMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoLastApplication

#endif

-- method RecentInfo::match
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info_a"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info_b"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RecentInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkRecentInfo" , 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 "gtk_recent_info_match" gtk_recent_info_match :: 
    Ptr RecentInfo ->                       -- info_a : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    Ptr RecentInfo ->                       -- info_b : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO CInt

-- | Checks whether two t'GI.Gtk.Structs.RecentInfo.RecentInfo'-struct point to the same
-- resource.
-- 
-- /Since: 2.10/
recentInfoMatch ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@infoA@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> RecentInfo
    -- ^ /@infoB@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if both t'GI.Gtk.Structs.RecentInfo.RecentInfo'-struct point to the same
    --   resource, 'P.False' otherwise
recentInfoMatch :: RecentInfo -> RecentInfo -> m Bool
recentInfoMatch RecentInfo
infoA RecentInfo
infoB = 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 RecentInfo
infoA' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
infoA
    Ptr RecentInfo
infoB' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
infoB
    CInt
result <- Ptr RecentInfo -> Ptr RecentInfo -> IO CInt
gtk_recent_info_match Ptr RecentInfo
infoA' Ptr RecentInfo
infoB'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
infoA
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
infoB
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoMatchMethodInfo
instance (signature ~ (RecentInfo -> m Bool), MonadIO m) => O.MethodInfo RecentInfoMatchMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoMatch

#endif

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

foreign import ccall "gtk_recent_info_ref" gtk_recent_info_ref :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO (Ptr RecentInfo)

-- | Increases the reference count of /@recentInfo@/ by one.
-- 
-- /Since: 2.10/
recentInfoRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m RecentInfo
    -- ^ __Returns:__ the recent info object with its reference count
    --     increased by one
recentInfoRef :: RecentInfo -> m RecentInfo
recentInfoRef RecentInfo
info = IO RecentInfo -> m RecentInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RecentInfo -> m RecentInfo) -> IO RecentInfo -> m RecentInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr RecentInfo
result <- Ptr RecentInfo -> IO (Ptr RecentInfo)
gtk_recent_info_ref Ptr RecentInfo
info'
    Text -> Ptr RecentInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"recentInfoRef" Ptr RecentInfo
result
    RecentInfo
result' <- ((ManagedPtr RecentInfo -> RecentInfo)
-> Ptr RecentInfo -> IO RecentInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RecentInfo -> RecentInfo
RecentInfo) Ptr RecentInfo
result
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    RecentInfo -> IO RecentInfo
forall (m :: * -> *) a. Monad m => a -> m a
return RecentInfo
result'

#if defined(ENABLE_OVERLOADING)
data RecentInfoRefMethodInfo
instance (signature ~ (m RecentInfo), MonadIO m) => O.MethodInfo RecentInfoRefMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoRef

#endif

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

foreign import ccall "gtk_recent_info_unref" gtk_recent_info_unref :: 
    Ptr RecentInfo ->                       -- info : TInterface (Name {namespace = "Gtk", name = "RecentInfo"})
    IO ()

-- | Decreases the reference count of /@info@/ by one. If the reference
-- count reaches zero, /@info@/ is deallocated, and the memory freed.
-- 
-- /Since: 2.10/
recentInfoUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    RecentInfo
    -- ^ /@info@/: a t'GI.Gtk.Structs.RecentInfo.RecentInfo'
    -> m ()
recentInfoUnref :: RecentInfo -> m ()
recentInfoUnref RecentInfo
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 RecentInfo
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
    Ptr RecentInfo -> IO ()
gtk_recent_info_unref Ptr RecentInfo
info'
    RecentInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr RecentInfo
info
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RecentInfoUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo RecentInfoUnrefMethodInfo RecentInfo signature where
    overloadedMethod = recentInfoUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRecentInfoMethod (t :: Symbol) (o :: *) :: * where
    ResolveRecentInfoMethod "createAppInfo" o = RecentInfoCreateAppInfoMethodInfo
    ResolveRecentInfoMethod "exists" o = RecentInfoExistsMethodInfo
    ResolveRecentInfoMethod "hasApplication" o = RecentInfoHasApplicationMethodInfo
    ResolveRecentInfoMethod "hasGroup" o = RecentInfoHasGroupMethodInfo
    ResolveRecentInfoMethod "isLocal" o = RecentInfoIsLocalMethodInfo
    ResolveRecentInfoMethod "lastApplication" o = RecentInfoLastApplicationMethodInfo
    ResolveRecentInfoMethod "match" o = RecentInfoMatchMethodInfo
    ResolveRecentInfoMethod "ref" o = RecentInfoRefMethodInfo
    ResolveRecentInfoMethod "unref" o = RecentInfoUnrefMethodInfo
    ResolveRecentInfoMethod "getAdded" o = RecentInfoGetAddedMethodInfo
    ResolveRecentInfoMethod "getAge" o = RecentInfoGetAgeMethodInfo
    ResolveRecentInfoMethod "getApplicationInfo" o = RecentInfoGetApplicationInfoMethodInfo
    ResolveRecentInfoMethod "getApplications" o = RecentInfoGetApplicationsMethodInfo
    ResolveRecentInfoMethod "getDescription" o = RecentInfoGetDescriptionMethodInfo
    ResolveRecentInfoMethod "getDisplayName" o = RecentInfoGetDisplayNameMethodInfo
    ResolveRecentInfoMethod "getGicon" o = RecentInfoGetGiconMethodInfo
    ResolveRecentInfoMethod "getGroups" o = RecentInfoGetGroupsMethodInfo
    ResolveRecentInfoMethod "getIcon" o = RecentInfoGetIconMethodInfo
    ResolveRecentInfoMethod "getMimeType" o = RecentInfoGetMimeTypeMethodInfo
    ResolveRecentInfoMethod "getModified" o = RecentInfoGetModifiedMethodInfo
    ResolveRecentInfoMethod "getPrivateHint" o = RecentInfoGetPrivateHintMethodInfo
    ResolveRecentInfoMethod "getShortName" o = RecentInfoGetShortNameMethodInfo
    ResolveRecentInfoMethod "getUri" o = RecentInfoGetUriMethodInfo
    ResolveRecentInfoMethod "getUriDisplay" o = RecentInfoGetUriDisplayMethodInfo
    ResolveRecentInfoMethod "getVisited" o = RecentInfoGetVisitedMethodInfo
    ResolveRecentInfoMethod l o = O.MethodResolutionFailed l o

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

#endif