{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.RecentInfo
(
RecentInfo(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveRecentInfoMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
RecentInfoCreateAppInfoMethodInfo ,
#endif
recentInfoCreateAppInfo ,
#if defined(ENABLE_OVERLOADING)
RecentInfoExistsMethodInfo ,
#endif
recentInfoExists ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetAddedMethodInfo ,
#endif
recentInfoGetAdded ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetAgeMethodInfo ,
#endif
recentInfoGetAge ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetApplicationInfoMethodInfo ,
#endif
recentInfoGetApplicationInfo ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetApplicationsMethodInfo ,
#endif
recentInfoGetApplications ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetDescriptionMethodInfo ,
#endif
recentInfoGetDescription ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetDisplayNameMethodInfo ,
#endif
recentInfoGetDisplayName ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetGiconMethodInfo ,
#endif
recentInfoGetGicon ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetGroupsMethodInfo ,
#endif
recentInfoGetGroups ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetMimeTypeMethodInfo ,
#endif
recentInfoGetMimeType ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetModifiedMethodInfo ,
#endif
recentInfoGetModified ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetPrivateHintMethodInfo ,
#endif
recentInfoGetPrivateHint ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetShortNameMethodInfo ,
#endif
recentInfoGetShortName ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetUriMethodInfo ,
#endif
recentInfoGetUri ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetUriDisplayMethodInfo ,
#endif
recentInfoGetUriDisplay ,
#if defined(ENABLE_OVERLOADING)
RecentInfoGetVisitedMethodInfo ,
#endif
recentInfoGetVisited ,
#if defined(ENABLE_OVERLOADING)
RecentInfoHasApplicationMethodInfo ,
#endif
recentInfoHasApplication ,
#if defined(ENABLE_OVERLOADING)
RecentInfoHasGroupMethodInfo ,
#endif
recentInfoHasGroup ,
#if defined(ENABLE_OVERLOADING)
RecentInfoIsLocalMethodInfo ,
#endif
recentInfoIsLocal ,
#if defined(ENABLE_OVERLOADING)
RecentInfoLastApplicationMethodInfo ,
#endif
recentInfoLastApplication ,
#if defined(ENABLE_OVERLOADING)
RecentInfoMatchMethodInfo ,
#endif
recentInfoMatch ,
#if defined(ENABLE_OVERLOADING)
RecentInfoRefMethodInfo ,
#endif
recentInfoRef ,
#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.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
#else
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
#endif
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
$c== :: RecentInfo -> RecentInfo -> Bool
== :: RecentInfo -> RecentInfo -> Bool
$c/= :: RecentInfo -> RecentInfo -> Bool
/= :: 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
instance B.GValue.IsGValue (Maybe RecentInfo) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_recent_info_get_type
gvalueSet_ :: Ptr GValue -> Maybe RecentInfo -> IO ()
gvalueSet_ Ptr GValue
gv Maybe RecentInfo
P.Nothing = Ptr GValue -> Ptr RecentInfo -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr RecentInfo
forall a. Ptr a
FP.nullPtr :: FP.Ptr RecentInfo)
gvalueSet_ Ptr GValue
gv (P.Just RecentInfo
obj) = RecentInfo -> (Ptr RecentInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RecentInfo
obj (Ptr GValue -> Ptr RecentInfo -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe RecentInfo)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr RecentInfo)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr RecentInfo)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed RecentInfo ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RecentInfo
type instance O.AttributeList RecentInfo = RecentInfoAttributeList
type RecentInfoAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_recent_info_create_app_info" gtk_recent_info_create_app_info ::
Ptr RecentInfo ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr Gio.AppInfo.AppInfo)
recentInfoCreateAppInfo ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> Maybe (T.Text)
-> m (Maybe Gio.AppInfo.AppInfo)
recentInfoCreateAppInfo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> Maybe Text -> m (Maybe AppInfo)
recentInfoCreateAppInfo RecentInfo
info Maybe Text
appName = IO (Maybe AppInfo) -> m (Maybe AppInfo)
forall a. IO a -> m a
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
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
maybeAppName <- case appName of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
Just Text
jAppName -> do
jAppName' <- Text -> IO (Ptr CChar)
textToCString Text
jAppName
return jAppName'
onException (do
result <- propagateGError $ gtk_recent_info_create_app_info info' maybeAppName
maybeResult <- convertIfNonNull result $ \Ptr AppInfo
result' -> do
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'
return result''
touchManagedPtr info
freeMem maybeAppName
return maybeResult
) (do
freeMem maybeAppName
)
#if defined(ENABLE_OVERLOADING)
data RecentInfoCreateAppInfoMethodInfo
instance (signature ~ (Maybe (T.Text) -> m (Maybe Gio.AppInfo.AppInfo)), MonadIO m) => O.OverloadedMethod RecentInfoCreateAppInfoMethodInfo RecentInfo signature where
overloadedMethod = recentInfoCreateAppInfo
instance O.OverloadedMethodInfo RecentInfoCreateAppInfoMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoCreateAppInfo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoCreateAppInfo"
})
#endif
foreign import ccall "gtk_recent_info_exists" gtk_recent_info_exists ::
Ptr RecentInfo ->
IO CInt
recentInfoExists ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m Bool
recentInfoExists :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Bool
recentInfoExists RecentInfo
info = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_exists info'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoExistsMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod RecentInfoExistsMethodInfo RecentInfo signature where
overloadedMethod = recentInfoExists
instance O.OverloadedMethodInfo RecentInfoExistsMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoExists",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoExists"
})
#endif
foreign import ccall "gtk_recent_info_get_added" gtk_recent_info_get_added ::
Ptr RecentInfo ->
IO (Ptr GLib.DateTime.DateTime)
recentInfoGetAdded ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m GLib.DateTime.DateTime
recentInfoGetAdded :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m DateTime
recentInfoGetAdded RecentInfo
info = IO DateTime -> m DateTime
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DateTime -> m DateTime) -> IO DateTime -> m DateTime
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_added info'
checkUnexpectedReturnNULL "recentInfoGetAdded" result
result' <- (newBoxed GLib.DateTime.DateTime) result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetAddedMethodInfo
instance (signature ~ (m GLib.DateTime.DateTime), MonadIO m) => O.OverloadedMethod RecentInfoGetAddedMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetAdded
instance O.OverloadedMethodInfo RecentInfoGetAddedMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetAdded",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetAdded"
})
#endif
foreign import ccall "gtk_recent_info_get_age" gtk_recent_info_get_age ::
Ptr RecentInfo ->
IO Int32
recentInfoGetAge ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m Int32
recentInfoGetAge :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Int32
recentInfoGetAge RecentInfo
info = IO Int32 -> m Int32
forall a. IO a -> m a
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
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_age info'
touchManagedPtr info
return result
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetAgeMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod RecentInfoGetAgeMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetAge
instance O.OverloadedMethodInfo RecentInfoGetAgeMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetAge",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetAge"
})
#endif
foreign import ccall "gtk_recent_info_get_application_info" gtk_recent_info_get_application_info ::
Ptr RecentInfo ->
CString ->
Ptr CString ->
Ptr Word32 ->
Ptr (Ptr GLib.DateTime.DateTime) ->
IO CInt
recentInfoGetApplicationInfo ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> T.Text
-> m ((Bool, T.Text, Word32, GLib.DateTime.DateTime))
recentInfoGetApplicationInfo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> Text -> m (Bool, Text, Word32, DateTime)
recentInfoGetApplicationInfo RecentInfo
info Text
appName = IO (Bool, Text, Word32, DateTime)
-> m (Bool, Text, Word32, DateTime)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Text, Word32, DateTime)
-> m (Bool, Text, Word32, DateTime))
-> IO (Bool, Text, Word32, DateTime)
-> m (Bool, Text, Word32, DateTime)
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
appName' <- textToCString appName
appExec <- callocMem :: IO (Ptr CString)
count <- allocMem :: IO (Ptr Word32)
stamp <- callocMem :: IO (Ptr (Ptr GLib.DateTime.DateTime))
result <- gtk_recent_info_get_application_info info' appName' appExec count stamp
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
appExec' <- peek appExec
appExec'' <- cstringToText appExec'
count' <- peek count
stamp' <- peek stamp
stamp'' <- (newBoxed GLib.DateTime.DateTime) stamp'
touchManagedPtr info
freeMem appName'
freeMem appExec
freeMem count
freeMem stamp
return (result', appExec'', count', stamp'')
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetApplicationInfoMethodInfo
instance (signature ~ (T.Text -> m ((Bool, T.Text, Word32, GLib.DateTime.DateTime))), MonadIO m) => O.OverloadedMethod RecentInfoGetApplicationInfoMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetApplicationInfo
instance O.OverloadedMethodInfo RecentInfoGetApplicationInfoMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetApplicationInfo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetApplicationInfo"
})
#endif
foreign import ccall "gtk_recent_info_get_applications" gtk_recent_info_get_applications ::
Ptr RecentInfo ->
Ptr FCT.CSize ->
IO (Ptr CString)
recentInfoGetApplications ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m (([T.Text], FCT.CSize))
recentInfoGetApplications :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m ([Text], CSize)
recentInfoGetApplications RecentInfo
info = IO ([Text], CSize) -> m ([Text], CSize)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], CSize) -> m ([Text], CSize))
-> IO ([Text], CSize) -> m ([Text], CSize)
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
length_ <- allocMem :: IO (Ptr FCT.CSize)
result <- gtk_recent_info_get_applications info' length_
checkUnexpectedReturnNULL "recentInfoGetApplications" result
result' <- unpackZeroTerminatedUTF8CArray result
mapZeroTerminatedCArray freeMem result
freeMem result
length_' <- peek length_
touchManagedPtr info
freeMem length_
return (result', length_')
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetApplicationsMethodInfo
instance (signature ~ (m (([T.Text], FCT.CSize))), MonadIO m) => O.OverloadedMethod RecentInfoGetApplicationsMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetApplications
instance O.OverloadedMethodInfo RecentInfoGetApplicationsMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetApplications",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetApplications"
})
#endif
foreign import ccall "gtk_recent_info_get_description" gtk_recent_info_get_description ::
Ptr RecentInfo ->
IO CString
recentInfoGetDescription ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m T.Text
recentInfoGetDescription :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Text
recentInfoGetDescription RecentInfo
info = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_description info'
checkUnexpectedReturnNULL "recentInfoGetDescription" result
result' <- cstringToText result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod RecentInfoGetDescriptionMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetDescription
instance O.OverloadedMethodInfo RecentInfoGetDescriptionMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetDescription",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetDescription"
})
#endif
foreign import ccall "gtk_recent_info_get_display_name" gtk_recent_info_get_display_name ::
Ptr RecentInfo ->
IO CString
recentInfoGetDisplayName ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m T.Text
recentInfoGetDisplayName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Text
recentInfoGetDisplayName RecentInfo
info = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_display_name info'
checkUnexpectedReturnNULL "recentInfoGetDisplayName" result
result' <- cstringToText result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetDisplayNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod RecentInfoGetDisplayNameMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetDisplayName
instance O.OverloadedMethodInfo RecentInfoGetDisplayNameMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetDisplayName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetDisplayName"
})
#endif
foreign import ccall "gtk_recent_info_get_gicon" gtk_recent_info_get_gicon ::
Ptr RecentInfo ->
IO (Ptr Gio.Icon.Icon)
recentInfoGetGicon ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m (Maybe Gio.Icon.Icon)
recentInfoGetGicon :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m (Maybe Icon)
recentInfoGetGicon RecentInfo
info = IO (Maybe Icon) -> m (Maybe Icon)
forall a. IO a -> m a
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
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_gicon info'
maybeResult <- convertIfNonNull result $ \Ptr Icon
result' -> do
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'
return result''
touchManagedPtr info
return maybeResult
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetGiconMethodInfo
instance (signature ~ (m (Maybe Gio.Icon.Icon)), MonadIO m) => O.OverloadedMethod RecentInfoGetGiconMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetGicon
instance O.OverloadedMethodInfo RecentInfoGetGiconMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetGicon",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetGicon"
})
#endif
foreign import ccall "gtk_recent_info_get_groups" gtk_recent_info_get_groups ::
Ptr RecentInfo ->
Ptr FCT.CSize ->
IO (Ptr CString)
recentInfoGetGroups ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m (([T.Text], FCT.CSize))
recentInfoGetGroups :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m ([Text], CSize)
recentInfoGetGroups RecentInfo
info = IO ([Text], CSize) -> m ([Text], CSize)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], CSize) -> m ([Text], CSize))
-> IO ([Text], CSize) -> m ([Text], CSize)
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
length_ <- allocMem :: IO (Ptr FCT.CSize)
result <- gtk_recent_info_get_groups info' length_
checkUnexpectedReturnNULL "recentInfoGetGroups" result
result' <- unpackZeroTerminatedUTF8CArray result
mapZeroTerminatedCArray freeMem result
freeMem result
length_' <- peek length_
touchManagedPtr info
freeMem length_
return (result', length_')
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetGroupsMethodInfo
instance (signature ~ (m (([T.Text], FCT.CSize))), MonadIO m) => O.OverloadedMethod RecentInfoGetGroupsMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetGroups
instance O.OverloadedMethodInfo RecentInfoGetGroupsMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetGroups",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetGroups"
})
#endif
foreign import ccall "gtk_recent_info_get_mime_type" gtk_recent_info_get_mime_type ::
Ptr RecentInfo ->
IO CString
recentInfoGetMimeType ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m T.Text
recentInfoGetMimeType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Text
recentInfoGetMimeType RecentInfo
info = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_mime_type info'
checkUnexpectedReturnNULL "recentInfoGetMimeType" result
result' <- cstringToText result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetMimeTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod RecentInfoGetMimeTypeMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetMimeType
instance O.OverloadedMethodInfo RecentInfoGetMimeTypeMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetMimeType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetMimeType"
})
#endif
foreign import ccall "gtk_recent_info_get_modified" gtk_recent_info_get_modified ::
Ptr RecentInfo ->
IO (Ptr GLib.DateTime.DateTime)
recentInfoGetModified ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m GLib.DateTime.DateTime
recentInfoGetModified :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m DateTime
recentInfoGetModified RecentInfo
info = IO DateTime -> m DateTime
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DateTime -> m DateTime) -> IO DateTime -> m DateTime
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_modified info'
checkUnexpectedReturnNULL "recentInfoGetModified" result
result' <- (newBoxed GLib.DateTime.DateTime) result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetModifiedMethodInfo
instance (signature ~ (m GLib.DateTime.DateTime), MonadIO m) => O.OverloadedMethod RecentInfoGetModifiedMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetModified
instance O.OverloadedMethodInfo RecentInfoGetModifiedMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetModified",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetModified"
})
#endif
foreign import ccall "gtk_recent_info_get_private_hint" gtk_recent_info_get_private_hint ::
Ptr RecentInfo ->
IO CInt
recentInfoGetPrivateHint ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m Bool
recentInfoGetPrivateHint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Bool
recentInfoGetPrivateHint RecentInfo
info = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_private_hint info'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetPrivateHintMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod RecentInfoGetPrivateHintMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetPrivateHint
instance O.OverloadedMethodInfo RecentInfoGetPrivateHintMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetPrivateHint",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetPrivateHint"
})
#endif
foreign import ccall "gtk_recent_info_get_short_name" gtk_recent_info_get_short_name ::
Ptr RecentInfo ->
IO CString
recentInfoGetShortName ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m T.Text
recentInfoGetShortName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Text
recentInfoGetShortName RecentInfo
info = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_short_name info'
checkUnexpectedReturnNULL "recentInfoGetShortName" result
result' <- cstringToText result
freeMem result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetShortNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod RecentInfoGetShortNameMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetShortName
instance O.OverloadedMethodInfo RecentInfoGetShortNameMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetShortName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetShortName"
})
#endif
foreign import ccall "gtk_recent_info_get_uri" gtk_recent_info_get_uri ::
Ptr RecentInfo ->
IO CString
recentInfoGetUri ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m T.Text
recentInfoGetUri :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Text
recentInfoGetUri RecentInfo
info = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_uri info'
checkUnexpectedReturnNULL "recentInfoGetUri" result
result' <- cstringToText result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod RecentInfoGetUriMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetUri
instance O.OverloadedMethodInfo RecentInfoGetUriMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetUri",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetUri"
})
#endif
foreign import ccall "gtk_recent_info_get_uri_display" gtk_recent_info_get_uri_display ::
Ptr RecentInfo ->
IO CString
recentInfoGetUriDisplay ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m (Maybe T.Text)
recentInfoGetUriDisplay :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m (Maybe Text)
recentInfoGetUriDisplay RecentInfo
info = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_uri_display info'
maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
freeMem result'
return result''
touchManagedPtr info
return maybeResult
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetUriDisplayMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod RecentInfoGetUriDisplayMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetUriDisplay
instance O.OverloadedMethodInfo RecentInfoGetUriDisplayMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetUriDisplay",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetUriDisplay"
})
#endif
foreign import ccall "gtk_recent_info_get_visited" gtk_recent_info_get_visited ::
Ptr RecentInfo ->
IO (Ptr GLib.DateTime.DateTime)
recentInfoGetVisited ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m GLib.DateTime.DateTime
recentInfoGetVisited :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m DateTime
recentInfoGetVisited RecentInfo
info = IO DateTime -> m DateTime
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DateTime -> m DateTime) -> IO DateTime -> m DateTime
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_get_visited info'
checkUnexpectedReturnNULL "recentInfoGetVisited" result
result' <- (newBoxed GLib.DateTime.DateTime) result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoGetVisitedMethodInfo
instance (signature ~ (m GLib.DateTime.DateTime), MonadIO m) => O.OverloadedMethod RecentInfoGetVisitedMethodInfo RecentInfo signature where
overloadedMethod = recentInfoGetVisited
instance O.OverloadedMethodInfo RecentInfoGetVisitedMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoGetVisited",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoGetVisited"
})
#endif
foreign import ccall "gtk_recent_info_has_application" gtk_recent_info_has_application ::
Ptr RecentInfo ->
CString ->
IO CInt
recentInfoHasApplication ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> T.Text
-> m Bool
recentInfoHasApplication :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> Text -> m Bool
recentInfoHasApplication RecentInfo
info Text
appName = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
appName' <- textToCString appName
result <- gtk_recent_info_has_application info' appName'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr info
freeMem appName'
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoHasApplicationMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.OverloadedMethod RecentInfoHasApplicationMethodInfo RecentInfo signature where
overloadedMethod = recentInfoHasApplication
instance O.OverloadedMethodInfo RecentInfoHasApplicationMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoHasApplication",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoHasApplication"
})
#endif
foreign import ccall "gtk_recent_info_has_group" gtk_recent_info_has_group ::
Ptr RecentInfo ->
CString ->
IO CInt
recentInfoHasGroup ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> T.Text
-> m Bool
recentInfoHasGroup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> Text -> m Bool
recentInfoHasGroup RecentInfo
info Text
groupName = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
groupName' <- textToCString groupName
result <- gtk_recent_info_has_group info' groupName'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr info
freeMem groupName'
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoHasGroupMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.OverloadedMethod RecentInfoHasGroupMethodInfo RecentInfo signature where
overloadedMethod = recentInfoHasGroup
instance O.OverloadedMethodInfo RecentInfoHasGroupMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoHasGroup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoHasGroup"
})
#endif
foreign import ccall "gtk_recent_info_is_local" gtk_recent_info_is_local ::
Ptr RecentInfo ->
IO CInt
recentInfoIsLocal ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m Bool
recentInfoIsLocal :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Bool
recentInfoIsLocal RecentInfo
info = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_is_local info'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoIsLocalMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod RecentInfoIsLocalMethodInfo RecentInfo signature where
overloadedMethod = recentInfoIsLocal
instance O.OverloadedMethodInfo RecentInfoIsLocalMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoIsLocal",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoIsLocal"
})
#endif
foreign import ccall "gtk_recent_info_last_application" gtk_recent_info_last_application ::
Ptr RecentInfo ->
IO CString
recentInfoLastApplication ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m T.Text
recentInfoLastApplication :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m Text
recentInfoLastApplication RecentInfo
info = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_last_application info'
checkUnexpectedReturnNULL "recentInfoLastApplication" result
result' <- cstringToText result
freeMem result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoLastApplicationMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod RecentInfoLastApplicationMethodInfo RecentInfo signature where
overloadedMethod = recentInfoLastApplication
instance O.OverloadedMethodInfo RecentInfoLastApplicationMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoLastApplication",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoLastApplication"
})
#endif
foreign import ccall "gtk_recent_info_match" gtk_recent_info_match ::
Ptr RecentInfo ->
Ptr RecentInfo ->
IO CInt
recentInfoMatch ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> RecentInfo
-> m Bool
recentInfoMatch :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> RecentInfo -> m Bool
recentInfoMatch RecentInfo
infoA RecentInfo
infoB = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
infoA' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
infoA
infoB' <- unsafeManagedPtrGetPtr infoB
result <- gtk_recent_info_match infoA' infoB'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr infoA
touchManagedPtr infoB
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoMatchMethodInfo
instance (signature ~ (RecentInfo -> m Bool), MonadIO m) => O.OverloadedMethod RecentInfoMatchMethodInfo RecentInfo signature where
overloadedMethod = recentInfoMatch
instance O.OverloadedMethodInfo RecentInfoMatchMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoMatch",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoMatch"
})
#endif
foreign import ccall "gtk_recent_info_ref" gtk_recent_info_ref ::
Ptr RecentInfo ->
IO (Ptr RecentInfo)
recentInfoRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m RecentInfo
recentInfoRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m RecentInfo
recentInfoRef RecentInfo
info = IO RecentInfo -> m RecentInfo
forall a. IO a -> m a
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
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
result <- gtk_recent_info_ref info'
checkUnexpectedReturnNULL "recentInfoRef" result
result' <- (wrapBoxed RecentInfo) result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data RecentInfoRefMethodInfo
instance (signature ~ (m RecentInfo), MonadIO m) => O.OverloadedMethod RecentInfoRefMethodInfo RecentInfo signature where
overloadedMethod = recentInfoRef
instance O.OverloadedMethodInfo RecentInfoRefMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoRef"
})
#endif
foreign import ccall "gtk_recent_info_unref" gtk_recent_info_unref ::
Ptr RecentInfo ->
IO ()
recentInfoUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
RecentInfo
-> m ()
recentInfoUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
RecentInfo -> m ()
recentInfoUnref RecentInfo
info = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
info' <- RecentInfo -> IO (Ptr RecentInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr RecentInfo
info
gtk_recent_info_unref info'
touchManagedPtr info
return ()
#if defined(ENABLE_OVERLOADING)
data RecentInfoUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod RecentInfoUnrefMethodInfo RecentInfo signature where
overloadedMethod = recentInfoUnref
instance O.OverloadedMethodInfo RecentInfoUnrefMethodInfo RecentInfo where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RecentInfo.recentInfoUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-RecentInfo.html#v:recentInfoUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveRecentInfoMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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 "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.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveRecentInfoMethod t RecentInfo, O.OverloadedMethod info RecentInfo p, R.HasField t RecentInfo p) => R.HasField t RecentInfo p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveRecentInfoMethod t RecentInfo, O.OverloadedMethodInfo info RecentInfo) => OL.IsLabel t (O.MethodProxy info RecentInfo) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif