{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The @GBookmarkFile@ structure contains only
-- private data and should not be directly accessed.

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

module GI.GLib.Structs.BookmarkFile
    ( 

-- * Exported types
    BookmarkFile(..)                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveBookmarkFileMethod               ,
#endif


-- ** addApplication #method:addApplication#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileAddApplicationMethodInfo    ,
#endif
    bookmarkFileAddApplication              ,


-- ** addGroup #method:addGroup#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileAddGroupMethodInfo          ,
#endif
    bookmarkFileAddGroup                    ,


-- ** errorQuark #method:errorQuark#

    bookmarkFileErrorQuark                  ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileFreeMethodInfo              ,
#endif
    bookmarkFileFree                        ,


-- ** getAdded #method:getAdded#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetAddedMethodInfo          ,
#endif
    bookmarkFileGetAdded                    ,


-- ** getAppInfo #method:getAppInfo#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetAppInfoMethodInfo        ,
#endif
    bookmarkFileGetAppInfo                  ,


-- ** getApplications #method:getApplications#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetApplicationsMethodInfo   ,
#endif
    bookmarkFileGetApplications             ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetDescriptionMethodInfo    ,
#endif
    bookmarkFileGetDescription              ,


-- ** getGroups #method:getGroups#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetGroupsMethodInfo         ,
#endif
    bookmarkFileGetGroups                   ,


-- ** getIcon #method:getIcon#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetIconMethodInfo           ,
#endif
    bookmarkFileGetIcon                     ,


-- ** getIsPrivate #method:getIsPrivate#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetIsPrivateMethodInfo      ,
#endif
    bookmarkFileGetIsPrivate                ,


-- ** getMimeType #method:getMimeType#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetMimeTypeMethodInfo       ,
#endif
    bookmarkFileGetMimeType                 ,


-- ** getModified #method:getModified#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetModifiedMethodInfo       ,
#endif
    bookmarkFileGetModified                 ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetSizeMethodInfo           ,
#endif
    bookmarkFileGetSize                     ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetTitleMethodInfo          ,
#endif
    bookmarkFileGetTitle                    ,


-- ** getUris #method:getUris#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetUrisMethodInfo           ,
#endif
    bookmarkFileGetUris                     ,


-- ** getVisited #method:getVisited#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileGetVisitedMethodInfo        ,
#endif
    bookmarkFileGetVisited                  ,


-- ** hasApplication #method:hasApplication#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileHasApplicationMethodInfo    ,
#endif
    bookmarkFileHasApplication              ,


-- ** hasGroup #method:hasGroup#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileHasGroupMethodInfo          ,
#endif
    bookmarkFileHasGroup                    ,


-- ** hasItem #method:hasItem#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileHasItemMethodInfo           ,
#endif
    bookmarkFileHasItem                     ,


-- ** loadFromData #method:loadFromData#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileLoadFromDataMethodInfo      ,
#endif
    bookmarkFileLoadFromData                ,


-- ** loadFromDataDirs #method:loadFromDataDirs#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileLoadFromDataDirsMethodInfo  ,
#endif
    bookmarkFileLoadFromDataDirs            ,


-- ** loadFromFile #method:loadFromFile#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileLoadFromFileMethodInfo      ,
#endif
    bookmarkFileLoadFromFile                ,


-- ** moveItem #method:moveItem#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileMoveItemMethodInfo          ,
#endif
    bookmarkFileMoveItem                    ,


-- ** removeApplication #method:removeApplication#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileRemoveApplicationMethodInfo ,
#endif
    bookmarkFileRemoveApplication           ,


-- ** removeGroup #method:removeGroup#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileRemoveGroupMethodInfo       ,
#endif
    bookmarkFileRemoveGroup                 ,


-- ** removeItem #method:removeItem#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileRemoveItemMethodInfo        ,
#endif
    bookmarkFileRemoveItem                  ,


-- ** setAdded #method:setAdded#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetAddedMethodInfo          ,
#endif
    bookmarkFileSetAdded                    ,


-- ** setAppInfo #method:setAppInfo#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetAppInfoMethodInfo        ,
#endif
    bookmarkFileSetAppInfo                  ,


-- ** setDescription #method:setDescription#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetDescriptionMethodInfo    ,
#endif
    bookmarkFileSetDescription              ,


-- ** setGroups #method:setGroups#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetGroupsMethodInfo         ,
#endif
    bookmarkFileSetGroups                   ,


-- ** setIcon #method:setIcon#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetIconMethodInfo           ,
#endif
    bookmarkFileSetIcon                     ,


-- ** setIsPrivate #method:setIsPrivate#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetIsPrivateMethodInfo      ,
#endif
    bookmarkFileSetIsPrivate                ,


-- ** setMimeType #method:setMimeType#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetMimeTypeMethodInfo       ,
#endif
    bookmarkFileSetMimeType                 ,


-- ** setModified #method:setModified#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetModifiedMethodInfo       ,
#endif
    bookmarkFileSetModified                 ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetTitleMethodInfo          ,
#endif
    bookmarkFileSetTitle                    ,


-- ** setVisited #method:setVisited#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileSetVisitedMethodInfo        ,
#endif
    bookmarkFileSetVisited                  ,


-- ** toData #method:toData#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileToDataMethodInfo            ,
#endif
    bookmarkFileToData                      ,


-- ** toFile #method:toFile#

#if defined(ENABLE_OVERLOADING)
    BookmarkFileToFileMethodInfo            ,
#endif
    bookmarkFileToFile                      ,




    ) 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.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


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

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

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr BookmarkFile where
    boxedPtrCopy :: BookmarkFile -> IO BookmarkFile
boxedPtrCopy = BookmarkFile -> IO BookmarkFile
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: BookmarkFile -> IO ()
boxedPtrFree = \BookmarkFile
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


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

-- method BookmarkFile::add_application
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the application registering the bookmark\n  or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "exec"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "command line to be used to launch the bookmark or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_add_application" g_bookmark_file_add_application :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- exec : TBasicType TUTF8
    IO ()

-- | Adds the application with /@name@/ and /@exec@/ to the list of
-- applications that have registered a bookmark for /@uri@/ into
-- /@bookmark@/.
-- 
-- Every bookmark inside a t'GI.GLib.Structs.BookmarkFile.BookmarkFile' must have at least an
-- application registered.  Each application must provide a name, a
-- command line useful for launching the bookmark, the number of times
-- the bookmark has been registered by the application and the last
-- time the application registered this bookmark.
-- 
-- If /@name@/ is 'P.Nothing', the name of the application will be the
-- same returned by 'GI.GLib.Functions.getApplicationName'; if /@exec@/ is 'P.Nothing', the
-- command line will be a composition of the program name as
-- returned by 'GI.GLib.Functions.getPrgname' and the \"%u\" modifier, which will be
-- expanded to the bookmark\'s URI.
-- 
-- This function will automatically take care of updating the
-- registrations count and timestamping in case an application
-- with the same /@name@/ had already registered a bookmark for
-- /@uri@/ inside /@bookmark@/.
-- 
-- If no bookmark for /@uri@/ is found, one is created.
-- 
-- /Since: 2.12/
bookmarkFileAddApplication ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> Maybe (T.Text)
    -- ^ /@name@/: the name of the application registering the bookmark
    --   or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@exec@/: command line to be used to launch the bookmark or 'P.Nothing'
    -> m ()
bookmarkFileAddApplication :: BookmarkFile -> Text -> Maybe Text -> Maybe Text -> m ()
bookmarkFileAddApplication BookmarkFile
bookmark Text
uri Maybe Text
name Maybe Text
exec = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
maybeName <- case Maybe Text
name of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jName -> do
            CString
jName' <- Text -> IO CString
textToCString Text
jName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jName'
    CString
maybeExec <- case Maybe Text
exec of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jExec -> do
            CString
jExec' <- Text -> IO CString
textToCString Text
jExec
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jExec'
    Ptr BookmarkFile -> CString -> CString -> CString -> IO ()
g_bookmark_file_add_application Ptr BookmarkFile
bookmark' CString
uri' CString
maybeName CString
maybeExec
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeExec
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileAddApplicationMethodInfo
instance (signature ~ (T.Text -> Maybe (T.Text) -> Maybe (T.Text) -> m ()), MonadIO m) => O.MethodInfo BookmarkFileAddApplicationMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileAddApplication

#endif

-- method BookmarkFile::add_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the group name to be added"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_add_group" g_bookmark_file_add_group :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- group : TBasicType TUTF8
    IO ()

-- | Adds /@group@/ to the list of groups to which the bookmark for /@uri@/
-- belongs to.
-- 
-- If no bookmark for /@uri@/ is found then it is created.
-- 
-- /Since: 2.12/
bookmarkFileAddGroup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@group@/: the group name to be added
    -> m ()
bookmarkFileAddGroup :: BookmarkFile -> Text -> Text -> m ()
bookmarkFileAddGroup BookmarkFile
bookmark Text
uri Text
group = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
group' <- Text -> IO CString
textToCString Text
group
    Ptr BookmarkFile -> CString -> CString -> IO ()
g_bookmark_file_add_group Ptr BookmarkFile
bookmark' CString
uri' CString
group'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
group'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileAddGroupMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileAddGroupMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileAddGroup

#endif

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

foreign import ccall "g_bookmark_file_free" g_bookmark_file_free :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    IO ()

-- | Frees a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'.
-- 
-- /Since: 2.12/
bookmarkFileFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> m ()
bookmarkFileFree :: BookmarkFile -> m ()
bookmarkFileFree BookmarkFile
bookmark = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    Ptr BookmarkFile -> IO ()
g_bookmark_file_free Ptr BookmarkFile
bookmark'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo BookmarkFileFreeMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileFree

#endif

-- method BookmarkFile::get_added
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_added" g_bookmark_file_get_added :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CLong

-- | Gets the time the bookmark for /@uri@/ was added to /@bookmark@/
-- 
-- In the event the URI cannot be found, -1 is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileGetAdded ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m CLong
    -- ^ __Returns:__ a timestamp /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetAdded :: BookmarkFile -> Text -> m CLong
bookmarkFileGetAdded BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO CLong -> IO () -> IO CLong
forall a b. IO a -> IO b -> IO a
onException (do
        CLong
result <- (Ptr (Ptr GError) -> IO CLong) -> IO CLong
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CLong) -> IO CLong)
-> (Ptr (Ptr GError) -> IO CLong) -> IO CLong
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CLong
g_bookmark_file_get_added Ptr BookmarkFile
bookmark' CString
uri'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetAddedMethodInfo
instance (signature ~ (T.Text -> m CLong), MonadIO m) => O.MethodInfo BookmarkFileGetAddedMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetAdded

#endif

-- method BookmarkFile::get_app_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application's name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "exec"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the command line of the application, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the registration count, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "stamp"
--           , argType = TBasicType TLong
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the last registration time, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_app_info" g_bookmark_file_get_app_info :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- name : TBasicType TUTF8
    Ptr CString ->                          -- exec : TBasicType TUTF8
    Ptr Word32 ->                           -- count : TBasicType TUInt
    Ptr CLong ->                            -- stamp : TBasicType TLong
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Gets the registration information of /@appName@/ for the bookmark for
-- /@uri@/.  See 'GI.GLib.Structs.BookmarkFile.bookmarkFileSetAppInfo' for more information about
-- the returned data.
-- 
-- The string returned in /@appExec@/ must be freed.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.  In the
-- event that no application with name /@appName@/ has registered a bookmark
-- for /@uri@/,  'P.False' is returned and error is set to
-- @/G_BOOKMARK_FILE_ERROR_APP_NOT_REGISTERED/@. In the event that unquoting
-- the command line fails, an error of the @/G_SHELL_ERROR/@ domain is
-- set and 'P.False' is returned.
-- 
-- /Since: 2.12/
bookmarkFileGetAppInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@name@/: an application\'s name
    -> m ((T.Text, Word32, CLong))
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetAppInfo :: BookmarkFile -> Text -> Text -> m (Text, Word32, CLong)
bookmarkFileGetAppInfo BookmarkFile
bookmark Text
uri Text
name = IO (Text, Word32, CLong) -> m (Text, Word32, CLong)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Word32, CLong) -> m (Text, Word32, CLong))
-> IO (Text, Word32, CLong) -> m (Text, Word32, CLong)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr CString
exec <- IO (Ptr CString)
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
stamp <- IO (Ptr CLong)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CLong)
    IO (Text, Word32, CLong) -> IO () -> IO (Text, Word32, CLong)
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString
-> CString
-> Ptr CString
-> Ptr Word32
-> Ptr CLong
-> Ptr (Ptr GError)
-> IO CInt
g_bookmark_file_get_app_info Ptr BookmarkFile
bookmark' CString
uri' CString
name' Ptr CString
exec Ptr Word32
count Ptr CLong
stamp
        CString
exec' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
exec
        Text
exec'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
exec'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
exec'
        Word32
count' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
count
        CLong
stamp' <- Ptr CLong -> IO CLong
forall a. Storable a => Ptr a -> IO a
peek Ptr CLong
stamp
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
exec
        Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
count
        Ptr CLong -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CLong
stamp
        (Text, Word32, CLong) -> IO (Text, Word32, CLong)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
exec'', Word32
count', CLong
stamp')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
exec
        Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
count
        Ptr CLong -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CLong
stamp
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetAppInfoMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ((T.Text, Word32, CLong))), MonadIO m) => O.MethodInfo BookmarkFileGetAppInfoMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetAppInfo

#endif

-- method BookmarkFile::get_applications
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , 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 of the length of the returned list, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "return location of the length of the returned list, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 2 (TBasicType TUTF8))
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_applications" g_bookmark_file_get_applications :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CString)

-- | Retrieves the names of the applications that have registered the
-- bookmark for /@uri@/.
-- 
-- In the event the URI cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileGetApplications ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m [T.Text]
    -- ^ __Returns:__ a newly allocated 'P.Nothing'-terminated array of strings.
    --   Use 'GI.GLib.Functions.strfreev' to free it. /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetApplications :: BookmarkFile -> Text -> m [Text]
bookmarkFileGetApplications BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO [Text] -> IO () -> IO [Text]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CString
result <- (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString))
-> (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> Ptr Word64 -> Ptr (Ptr GError) -> IO (Ptr CString)
g_bookmark_file_get_applications Ptr BookmarkFile
bookmark' CString
uri' Ptr Word64
length_
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bookmarkFileGetApplications" Ptr CString
result
        [Text]
result' <- (Word64 -> Ptr CString -> IO [Text]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [Text]
unpackUTF8CArrayWithLength Word64
length_') Ptr CString
result
        (Word64 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Word64
length_') CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetApplicationsMethodInfo
instance (signature ~ (T.Text -> m [T.Text]), MonadIO m) => O.MethodInfo BookmarkFileGetApplicationsMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetApplications

#endif

-- method BookmarkFile::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_description" g_bookmark_file_get_description :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Retrieves the description of the bookmark for /@uri@/.
-- 
-- In the event the URI cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string or 'P.Nothing' if the specified
    --   URI cannot be found. /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetDescription :: BookmarkFile -> Text -> m Text
bookmarkFileGetDescription BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CString
g_bookmark_file_get_description Ptr BookmarkFile
bookmark' CString
uri'
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bookmarkFileGetDescription" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetDescriptionMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m) => O.MethodInfo BookmarkFileGetDescriptionMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetDescription

#endif

-- method BookmarkFile::get_groups
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , 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 string, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "return location for the length of the returned string, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 2 (TBasicType TUTF8))
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_groups" g_bookmark_file_get_groups :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CString)

-- | Retrieves the list of group names of the bookmark for /@uri@/.
-- 
-- In the event the URI cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- The returned array is 'P.Nothing' terminated, so /@length@/ may optionally
-- be 'P.Nothing'.
-- 
-- /Since: 2.12/
bookmarkFileGetGroups ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m [T.Text]
    -- ^ __Returns:__ a newly allocated 'P.Nothing'-terminated array of group names.
    --   Use 'GI.GLib.Functions.strfreev' to free it. /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetGroups :: BookmarkFile -> Text -> m [Text]
bookmarkFileGetGroups BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO [Text] -> IO () -> IO [Text]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CString
result <- (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString))
-> (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> Ptr Word64 -> Ptr (Ptr GError) -> IO (Ptr CString)
g_bookmark_file_get_groups Ptr BookmarkFile
bookmark' CString
uri' Ptr Word64
length_
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bookmarkFileGetGroups" Ptr CString
result
        [Text]
result' <- (Word64 -> Ptr CString -> IO [Text]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [Text]
unpackUTF8CArrayWithLength Word64
length_') Ptr CString
result
        (Word64 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Word64
length_') CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetGroupsMethodInfo
instance (signature ~ (T.Text -> m [T.Text]), MonadIO m) => O.MethodInfo BookmarkFileGetGroupsMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetGroups

#endif

-- method BookmarkFile::get_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "href"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the icon's location or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "mime_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the icon's MIME type or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_icon" g_bookmark_file_get_icon :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr CString ->                          -- href : TBasicType TUTF8
    Ptr CString ->                          -- mime_type : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Gets the icon of the bookmark for /@uri@/.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileGetIcon ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m ((T.Text, T.Text))
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetIcon :: BookmarkFile -> Text -> m (Text, Text)
bookmarkFileGetIcon BookmarkFile
bookmark Text
uri = IO (Text, Text) -> m (Text, Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Text) -> m (Text, Text))
-> IO (Text, Text) -> m (Text, Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr CString
href <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    Ptr CString
mimeType <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    IO (Text, Text) -> IO () -> IO (Text, Text)
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString
-> Ptr CString
-> Ptr CString
-> Ptr (Ptr GError)
-> IO CInt
g_bookmark_file_get_icon Ptr BookmarkFile
bookmark' CString
uri' Ptr CString
href Ptr CString
mimeType
        CString
href' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
href
        Text
href'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
href'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
href'
        CString
mimeType' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
mimeType
        Text
mimeType'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
mimeType'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
mimeType'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
href
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
mimeType
        (Text, Text) -> IO (Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
href'', Text
mimeType'')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
href
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
mimeType
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetIconMethodInfo
instance (signature ~ (T.Text -> m ((T.Text, T.Text))), MonadIO m) => O.MethodInfo BookmarkFileGetIconMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetIcon

#endif

-- method BookmarkFile::get_is_private
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_is_private" g_bookmark_file_get_is_private :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Gets whether the private flag of the bookmark for /@uri@/ is set.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.  In the
-- event that the private flag cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_INVALID_VALUE/@.
-- 
-- /Since: 2.12/
bookmarkFileGetIsPrivate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetIsPrivate :: BookmarkFile -> Text -> m ()
bookmarkFileGetIsPrivate BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_get_is_private Ptr BookmarkFile
bookmark' CString
uri'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetIsPrivateMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileGetIsPrivateMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetIsPrivate

#endif

-- method BookmarkFile::get_mime_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_mime_type" g_bookmark_file_get_mime_type :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Retrieves the MIME type of the resource pointed by /@uri@/.
-- 
-- In the event the URI cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.  In the
-- event that the MIME type cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_INVALID_VALUE/@.
-- 
-- /Since: 2.12/
bookmarkFileGetMimeType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string or 'P.Nothing' if the specified
    --   URI cannot be found. /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetMimeType :: BookmarkFile -> Text -> m Text
bookmarkFileGetMimeType BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CString
g_bookmark_file_get_mime_type Ptr BookmarkFile
bookmark' CString
uri'
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bookmarkFileGetMimeType" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetMimeTypeMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m) => O.MethodInfo BookmarkFileGetMimeTypeMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetMimeType

#endif

-- method BookmarkFile::get_modified
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_modified" g_bookmark_file_get_modified :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CLong

-- | Gets the time when the bookmark for /@uri@/ was last modified.
-- 
-- In the event the URI cannot be found, -1 is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileGetModified ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m CLong
    -- ^ __Returns:__ a timestamp /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetModified :: BookmarkFile -> Text -> m CLong
bookmarkFileGetModified BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO CLong -> IO () -> IO CLong
forall a b. IO a -> IO b -> IO a
onException (do
        CLong
result <- (Ptr (Ptr GError) -> IO CLong) -> IO CLong
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CLong) -> IO CLong)
-> (Ptr (Ptr GError) -> IO CLong) -> IO CLong
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CLong
g_bookmark_file_get_modified Ptr BookmarkFile
bookmark' CString
uri'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetModifiedMethodInfo
instance (signature ~ (T.Text -> m CLong), MonadIO m) => O.MethodInfo BookmarkFileGetModifiedMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetModified

#endif

-- method BookmarkFile::get_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , 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 "g_bookmark_file_get_size" g_bookmark_file_get_size :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    IO Int32

-- | Gets the number of bookmarks inside /@bookmark@/.
-- 
-- /Since: 2.12/
bookmarkFileGetSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> m Int32
    -- ^ __Returns:__ the number of bookmarks
bookmarkFileGetSize :: BookmarkFile -> m Int32
bookmarkFileGetSize BookmarkFile
bookmark = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    Int32
result <- Ptr BookmarkFile -> IO Int32
g_bookmark_file_get_size Ptr BookmarkFile
bookmark'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo BookmarkFileGetSizeMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetSize

#endif

-- method BookmarkFile::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_title" g_bookmark_file_get_title :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Returns the title of the bookmark for /@uri@/.
-- 
-- If /@uri@/ is 'P.Nothing', the title of /@bookmark@/ is returned.
-- 
-- In the event the URI cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> Maybe (T.Text)
    -- ^ /@uri@/: a valid URI or 'P.Nothing'
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string or 'P.Nothing' if the specified
    --   URI cannot be found. /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetTitle :: BookmarkFile -> Maybe Text -> m Text
bookmarkFileGetTitle BookmarkFile
bookmark Maybe Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
maybeUri <- case Maybe Text
uri of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jUri -> do
            CString
jUri' <- Text -> IO CString
textToCString Text
jUri
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jUri'
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CString
g_bookmark_file_get_title Ptr BookmarkFile
bookmark' CString
maybeUri
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bookmarkFileGetTitle" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeUri
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeUri
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetTitleMethodInfo
instance (signature ~ (Maybe (T.Text) -> m T.Text), MonadIO m) => O.MethodInfo BookmarkFileGetTitleMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetTitle

#endif

-- method BookmarkFile::get_uris
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , 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 returned URIs, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "return location for the number of returned URIs, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_get_uris" g_bookmark_file_get_uris :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    IO (Ptr CString)

-- | Returns all URIs of the bookmarks in the bookmark file /@bookmark@/.
-- The array of returned URIs will be 'P.Nothing'-terminated, so /@length@/ may
-- optionally be 'P.Nothing'.
-- 
-- /Since: 2.12/
bookmarkFileGetUris ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> m [T.Text]
    -- ^ __Returns:__ a newly allocated 'P.Nothing'-terminated array of strings.
    --   Use 'GI.GLib.Functions.strfreev' to free it.
bookmarkFileGetUris :: BookmarkFile -> m [Text]
bookmarkFileGetUris BookmarkFile
bookmark = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr CString
result <- Ptr BookmarkFile -> Ptr Word64 -> IO (Ptr CString)
g_bookmark_file_get_uris Ptr BookmarkFile
bookmark' Ptr Word64
length_
    Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bookmarkFileGetUris" Ptr CString
result
    [Text]
result' <- (Word64 -> Ptr CString -> IO [Text]
forall a.
(HasCallStack, Integral a) =>
a -> Ptr CString -> IO [Text]
unpackUTF8CArrayWithLength Word64
length_') Ptr CString
result
    (Word64 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Word64
length_') CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetUrisMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.MethodInfo BookmarkFileGetUrisMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetUris

#endif

-- method BookmarkFile::get_visited
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TLong)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_get_visited" g_bookmark_file_get_visited :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CLong

-- | Gets the time the bookmark for /@uri@/ was last visited.
-- 
-- In the event the URI cannot be found, -1 is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileGetVisited ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m CLong
    -- ^ __Returns:__ a timestamp. /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileGetVisited :: BookmarkFile -> Text -> m CLong
bookmarkFileGetVisited BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO CLong -> IO () -> IO CLong
forall a b. IO a -> IO b -> IO a
onException (do
        CLong
result <- (Ptr (Ptr GError) -> IO CLong) -> IO CLong
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CLong) -> IO CLong)
-> (Ptr (Ptr GError) -> IO CLong) -> IO CLong
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CLong
g_bookmark_file_get_visited Ptr BookmarkFile
bookmark' CString
uri'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CLong -> IO CLong
forall (m :: * -> *) a. Monad m => a -> m a
return CLong
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileGetVisitedMethodInfo
instance (signature ~ (T.Text -> m CLong), MonadIO m) => O.MethodInfo BookmarkFileGetVisitedMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileGetVisited

#endif

-- method BookmarkFile::has_application
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_has_application" g_bookmark_file_has_application :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- name : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Checks whether the bookmark for /@uri@/ inside /@bookmark@/ has been
-- registered by application /@name@/.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileHasApplication ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@name@/: the name of the application
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileHasApplication :: BookmarkFile -> Text -> Text -> m ()
bookmarkFileHasApplication BookmarkFile
bookmark Text
uri Text
name = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
name' <- Text -> IO CString
textToCString Text
name
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_has_application Ptr BookmarkFile
bookmark' CString
uri' CString
name'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileHasApplicationMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileHasApplicationMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileHasApplication

#endif

-- method BookmarkFile::has_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the group name to be searched"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_has_group" g_bookmark_file_has_group :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- group : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Checks whether /@group@/ appears in the list of groups to which
-- the bookmark for /@uri@/ belongs to.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileHasGroup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@group@/: the group name to be searched
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileHasGroup :: BookmarkFile -> Text -> Text -> m ()
bookmarkFileHasGroup BookmarkFile
bookmark Text
uri Text
group = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
group' <- Text -> IO CString
textToCString Text
group
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_has_group Ptr BookmarkFile
bookmark' CString
uri' CString
group'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
group'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
group'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileHasGroupMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileHasGroupMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileHasGroup

#endif

-- method BookmarkFile::has_item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_has_item" g_bookmark_file_has_item :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    IO CInt

-- | Looks whether the desktop bookmark has an item with its URI set to /@uri@/.
-- 
-- /Since: 2.12/
bookmarkFileHasItem ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@uri@/ is inside /@bookmark@/, 'P.False' otherwise
bookmarkFileHasItem :: BookmarkFile -> Text -> m Bool
bookmarkFileHasItem BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CInt
result <- Ptr BookmarkFile -> CString -> IO CInt
g_bookmark_file_has_item Ptr BookmarkFile
bookmark' CString
uri'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

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

#endif

-- method BookmarkFile::load_from_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an empty #GBookmarkFile struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 2 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "desktop bookmarks\n   loaded in memory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the length of @data in bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of @data in bytes"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_load_from_data" g_bookmark_file_load_from_data :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    Ptr Word8 ->                            -- data : TCArray False (-1) 2 (TBasicType TUInt8)
    Word64 ->                               -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Loads a bookmark file from memory into an empty t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
-- structure.  If the object cannot be created then /@error@/ is set to a
-- t'GI.GLib.Enums.BookmarkFileError'.
-- 
-- /Since: 2.12/
bookmarkFileLoadFromData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: an empty t'GI.GLib.Structs.BookmarkFile.BookmarkFile' struct
    -> ByteString
    -- ^ /@data@/: desktop bookmarks
    --    loaded in memory
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileLoadFromData :: BookmarkFile -> ByteString -> m ()
bookmarkFileLoadFromData BookmarkFile
bookmark ByteString
data_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let length_ :: Word64
length_ = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
data_
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> Ptr Word8 -> Word64 -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_load_from_data Ptr BookmarkFile
bookmark' Ptr Word8
data_' Word64
length_
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileLoadFromDataMethodInfo
instance (signature ~ (ByteString -> m ()), MonadIO m) => O.MethodInfo BookmarkFileLoadFromDataMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileLoadFromData

#endif

-- method BookmarkFile::load_from_data_dirs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a relative path to a filename to open and parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "full_path"
--           , argType = TBasicType TFileName
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for a string\n   containing the full path of the file, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_load_from_data_dirs" g_bookmark_file_load_from_data_dirs :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- file : TBasicType TFileName
    Ptr CString ->                          -- full_path : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This function looks for a desktop bookmark file named /@file@/ in the
-- paths returned from 'GI.GLib.Functions.getUserDataDir' and 'GI.GLib.Functions.getSystemDataDirs',
-- loads the file into /@bookmark@/ and returns the file\'s full path in
-- /@fullPath@/.  If the file could not be loaded then /@error@/ is
-- set to either a t'GI.GLib.Enums.FileError' or t'GI.GLib.Enums.BookmarkFileError'.
-- 
-- /Since: 2.12/
bookmarkFileLoadFromDataDirs ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> [Char]
    -- ^ /@file@/: a relative path to a filename to open and parse
    -> m ((Maybe [Char]))
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileLoadFromDataDirs :: BookmarkFile -> [Char] -> m (Maybe [Char])
bookmarkFileLoadFromDataDirs BookmarkFile
bookmark [Char]
file = IO (Maybe [Char]) -> m (Maybe [Char])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Char]) -> m (Maybe [Char]))
-> IO (Maybe [Char]) -> m (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ do
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
file' <- [Char] -> IO CString
stringToCString [Char]
file
    Ptr CString
fullPath <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    IO (Maybe [Char]) -> IO () -> IO (Maybe [Char])
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> Ptr CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_load_from_data_dirs Ptr BookmarkFile
bookmark' CString
file' Ptr CString
fullPath
        CString
fullPath' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
fullPath
        Maybe [Char]
maybeFullPath' <- CString -> (CString -> IO [Char]) -> IO (Maybe [Char])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
fullPath' ((CString -> IO [Char]) -> IO (Maybe [Char]))
-> (CString -> IO [Char]) -> IO (Maybe [Char])
forall a b. (a -> b) -> a -> b
$ \CString
fullPath'' -> do
            [Char]
fullPath''' <- HasCallStack => CString -> IO [Char]
CString -> IO [Char]
cstringToString CString
fullPath''
            [Char] -> IO [Char]
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
fullPath'''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fullPath'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
fullPath
        Maybe [Char] -> IO (Maybe [Char])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Char]
maybeFullPath'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
fullPath
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileLoadFromDataDirsMethodInfo
instance (signature ~ ([Char] -> m ((Maybe [Char]))), MonadIO m) => O.MethodInfo BookmarkFileLoadFromDataDirsMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileLoadFromDataDirs

#endif

-- method BookmarkFile::load_from_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an empty #GBookmarkFile struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the path of a filename to load, in the\n    GLib file name encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_load_from_file" g_bookmark_file_load_from_file :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- filename : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Loads a desktop bookmark file into an empty t'GI.GLib.Structs.BookmarkFile.BookmarkFile' structure.
-- If the file could not be loaded then /@error@/ is set to either a t'GI.GLib.Enums.FileError'
-- or t'GI.GLib.Enums.BookmarkFileError'.
-- 
-- /Since: 2.12/
bookmarkFileLoadFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: an empty t'GI.GLib.Structs.BookmarkFile.BookmarkFile' struct
    -> [Char]
    -- ^ /@filename@/: the path of a filename to load, in the
    --     GLib file name encoding
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileLoadFromFile :: BookmarkFile -> [Char] -> m ()
bookmarkFileLoadFromFile BookmarkFile
bookmark [Char]
filename = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
filename' <- [Char] -> IO CString
stringToCString [Char]
filename
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_load_from_file Ptr BookmarkFile
bookmark' CString
filename'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileLoadFromFileMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m) => O.MethodInfo BookmarkFileLoadFromFileMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileLoadFromFile

#endif

-- method BookmarkFile::move_item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "old_uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "new_uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_move_item" g_bookmark_file_move_item :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- old_uri : TBasicType TUTF8
    CString ->                              -- new_uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Changes the URI of a bookmark item from /@oldUri@/ to /@newUri@/.  Any
-- existing bookmark for /@newUri@/ will be overwritten.  If /@newUri@/ is
-- 'P.Nothing', then the bookmark is removed.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- 
-- /Since: 2.12/
bookmarkFileMoveItem ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@oldUri@/: a valid URI
    -> Maybe (T.Text)
    -- ^ /@newUri@/: a valid URI, or 'P.Nothing'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileMoveItem :: BookmarkFile -> Text -> Maybe Text -> m ()
bookmarkFileMoveItem BookmarkFile
bookmark Text
oldUri Maybe Text
newUri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
oldUri' <- Text -> IO CString
textToCString Text
oldUri
    CString
maybeNewUri <- case Maybe Text
newUri of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jNewUri -> do
            CString
jNewUri' <- Text -> IO CString
textToCString Text
jNewUri
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jNewUri'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_move_item Ptr BookmarkFile
bookmark' CString
oldUri' CString
maybeNewUri
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
oldUri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeNewUri
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
oldUri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeNewUri
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileMoveItemMethodInfo
instance (signature ~ (T.Text -> Maybe (T.Text) -> m ()), MonadIO m) => O.MethodInfo BookmarkFileMoveItemMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileMoveItem

#endif

-- method BookmarkFile::remove_application
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_remove_application" g_bookmark_file_remove_application :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- name : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes application registered with /@name@/ from the list of applications
-- that have registered a bookmark for /@uri@/ inside /@bookmark@/.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- In the event that no application with name /@appName@/ has registered
-- a bookmark for /@uri@/,  'P.False' is returned and error is set to
-- @/G_BOOKMARK_FILE_ERROR_APP_NOT_REGISTERED/@.
-- 
-- /Since: 2.12/
bookmarkFileRemoveApplication ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@name@/: the name of the application
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileRemoveApplication :: BookmarkFile -> Text -> Text -> m ()
bookmarkFileRemoveApplication BookmarkFile
bookmark Text
uri Text
name = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
name' <- Text -> IO CString
textToCString Text
name
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_remove_application Ptr BookmarkFile
bookmark' CString
uri' CString
name'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileRemoveApplicationMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileRemoveApplicationMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileRemoveApplication

#endif

-- method BookmarkFile::remove_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the group name to be removed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_remove_group" g_bookmark_file_remove_group :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- group : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes /@group@/ from the list of groups to which the bookmark
-- for /@uri@/ belongs to.
-- 
-- In the event the URI cannot be found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@.
-- In the event no group was defined, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_INVALID_VALUE/@.
-- 
-- /Since: 2.12/
bookmarkFileRemoveGroup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@group@/: the group name to be removed
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileRemoveGroup :: BookmarkFile -> Text -> Text -> m ()
bookmarkFileRemoveGroup BookmarkFile
bookmark Text
uri Text
group = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
group' <- Text -> IO CString
textToCString Text
group
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_remove_group Ptr BookmarkFile
bookmark' CString
uri' CString
group'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
group'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
group'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileRemoveGroupMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileRemoveGroupMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileRemoveGroup

#endif

-- method BookmarkFile::remove_item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_remove_item" g_bookmark_file_remove_item :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes the bookmark for /@uri@/ from the bookmark file /@bookmark@/.
-- 
-- /Since: 2.12/
bookmarkFileRemoveItem ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileRemoveItem :: BookmarkFile -> Text -> m ()
bookmarkFileRemoveItem BookmarkFile
bookmark Text
uri = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_remove_item Ptr BookmarkFile
bookmark' CString
uri'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileRemoveItemMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileRemoveItemMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileRemoveItem

#endif

-- method BookmarkFile::set_added
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "added"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a timestamp or -1 to use the current time"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_added" g_bookmark_file_set_added :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CLong ->                                -- added : TBasicType TLong
    IO ()

-- | Sets the time the bookmark for /@uri@/ was added into /@bookmark@/.
-- 
-- If no bookmark for /@uri@/ is found then it is created.
-- 
-- /Since: 2.12/
bookmarkFileSetAdded ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> CLong
    -- ^ /@added@/: a timestamp or -1 to use the current time
    -> m ()
bookmarkFileSetAdded :: BookmarkFile -> Text -> CLong -> m ()
bookmarkFileSetAdded BookmarkFile
bookmark Text
uri CLong
added = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr BookmarkFile -> CString -> CLong -> IO ()
g_bookmark_file_set_added Ptr BookmarkFile
bookmark' CString
uri' CLong
added
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetAddedMethodInfo
instance (signature ~ (T.Text -> CLong -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetAddedMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetAdded

#endif

-- method BookmarkFile::set_app_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application's name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "exec"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an application's command line"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "count"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the number of registrations done for this application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stamp"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the time of the last registration for this application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_set_app_info" g_bookmark_file_set_app_info :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- exec : TBasicType TUTF8
    Int32 ->                                -- count : TBasicType TInt
    CLong ->                                -- stamp : TBasicType TLong
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Sets the meta-data of application /@name@/ inside the list of
-- applications that have registered a bookmark for /@uri@/ inside
-- /@bookmark@/.
-- 
-- You should rarely use this function; use 'GI.GLib.Structs.BookmarkFile.bookmarkFileAddApplication'
-- and 'GI.GLib.Structs.BookmarkFile.bookmarkFileRemoveApplication' instead.
-- 
-- /@name@/ can be any UTF-8 encoded string used to identify an
-- application.
-- /@exec@/ can have one of these two modifiers: \"%f\", which will
-- be expanded as the local file name retrieved from the bookmark\'s
-- URI; \"%u\", which will be expanded as the bookmark\'s URI.
-- The expansion is done automatically when retrieving the stored
-- command line using the 'GI.GLib.Structs.BookmarkFile.bookmarkFileGetAppInfo' function.
-- /@count@/ is the number of times the application has registered the
-- bookmark; if is \< 0, the current registration count will be increased
-- by one, if is 0, the application with /@name@/ will be removed from
-- the list of registered applications.
-- /@stamp@/ is the Unix time of the last registration; if it is -1, the
-- current time will be used.
-- 
-- If you try to remove an application by setting its registration count to
-- zero, and no bookmark for /@uri@/ is found, 'P.False' is returned and
-- /@error@/ is set to @/G_BOOKMARK_FILE_ERROR_URI_NOT_FOUND/@; similarly,
-- in the event that no application /@name@/ has registered a bookmark
-- for /@uri@/,  'P.False' is returned and error is set to
-- @/G_BOOKMARK_FILE_ERROR_APP_NOT_REGISTERED/@.  Otherwise, if no bookmark
-- for /@uri@/ is found, one is created.
-- 
-- /Since: 2.12/
bookmarkFileSetAppInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@name@/: an application\'s name
    -> T.Text
    -- ^ /@exec@/: an application\'s command line
    -> Int32
    -- ^ /@count@/: the number of registrations done for this application
    -> CLong
    -- ^ /@stamp@/: the time of the last registration for this application
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileSetAppInfo :: BookmarkFile -> Text -> Text -> Text -> Int32 -> CLong -> m ()
bookmarkFileSetAppInfo BookmarkFile
bookmark Text
uri Text
name Text
exec Int32
count CLong
stamp = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
exec' <- Text -> IO CString
textToCString Text
exec
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> CString
-> CString
-> CString
-> Int32
-> CLong
-> Ptr (Ptr GError)
-> IO CInt
g_bookmark_file_set_app_info Ptr BookmarkFile
bookmark' CString
uri' CString
name' CString
exec' Int32
count CLong
stamp
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
exec'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
exec'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetAppInfoMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> Int32 -> CLong -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetAppInfoMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetAppInfo

#endif

-- method BookmarkFile::set_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_description" g_bookmark_file_set_description :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- description : TBasicType TUTF8
    IO ()

-- | Sets /@description@/ as the description of the bookmark for /@uri@/.
-- 
-- If /@uri@/ is 'P.Nothing', the description of /@bookmark@/ is set.
-- 
-- If a bookmark for /@uri@/ cannot be found then it is created.
-- 
-- /Since: 2.12/
bookmarkFileSetDescription ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> Maybe (T.Text)
    -- ^ /@uri@/: a valid URI or 'P.Nothing'
    -> T.Text
    -- ^ /@description@/: a string
    -> m ()
bookmarkFileSetDescription :: BookmarkFile -> Maybe Text -> Text -> m ()
bookmarkFileSetDescription BookmarkFile
bookmark Maybe Text
uri Text
description = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
maybeUri <- case Maybe Text
uri of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jUri -> do
            CString
jUri' <- Text -> IO CString
textToCString Text
jUri
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jUri'
    CString
description' <- Text -> IO CString
textToCString Text
description
    Ptr BookmarkFile -> CString -> CString -> IO ()
g_bookmark_file_set_description Ptr BookmarkFile
bookmark' CString
maybeUri CString
description'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeUri
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetDescriptionMethodInfo
instance (signature ~ (Maybe (T.Text) -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetDescriptionMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetDescription

#endif

-- method BookmarkFile::set_groups
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an item's URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "groups"
--           , argType = TCArray False (-1) 3 (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an array of\n   group names, or %NULL to remove all groups"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of group name values in @groups"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of group name values in @groups"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_groups" g_bookmark_file_set_groups :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    Ptr CString ->                          -- groups : TCArray False (-1) 3 (TBasicType TUTF8)
    Word64 ->                               -- length : TBasicType TUInt64
    IO ()

-- | Sets a list of group names for the item with URI /@uri@/.  Each previously
-- set group name list is removed.
-- 
-- If /@uri@/ cannot be found then an item for it is created.
-- 
-- /Since: 2.12/
bookmarkFileSetGroups ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: an item\'s URI
    -> Maybe ([T.Text])
    -- ^ /@groups@/: an array of
    --    group names, or 'P.Nothing' to remove all groups
    -> m ()
bookmarkFileSetGroups :: BookmarkFile -> Text -> Maybe [Text] -> m ()
bookmarkFileSetGroups BookmarkFile
bookmark Text
uri Maybe [Text]
groups = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let length_ :: Word64
length_ = case Maybe [Text]
groups of
            Maybe [Text]
Nothing -> Word64
0
            Just [Text]
jGroups -> Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Text]
jGroups
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr CString
maybeGroups <- case Maybe [Text]
groups of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jGroups -> do
            Ptr CString
jGroups' <- [Text] -> IO (Ptr CString)
packUTF8CArray [Text]
jGroups
            Ptr CString -> IO (Ptr CString)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jGroups'
    Ptr BookmarkFile -> CString -> Ptr CString -> Word64 -> IO ()
g_bookmark_file_set_groups Ptr BookmarkFile
bookmark' CString
uri' Ptr CString
maybeGroups Word64
length_
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    (Word64 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Word64
length_) CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeGroups
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeGroups
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetGroupsMethodInfo
instance (signature ~ (T.Text -> Maybe ([T.Text]) -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetGroupsMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetGroups

#endif

-- method BookmarkFile::set_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "href"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the URI of the icon for the bookmark, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mime_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the MIME type of the icon for the bookmark"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_icon" g_bookmark_file_set_icon :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- href : TBasicType TUTF8
    CString ->                              -- mime_type : TBasicType TUTF8
    IO ()

-- | Sets the icon for the bookmark for /@uri@/. If /@href@/ is 'P.Nothing', unsets
-- the currently set icon. /@href@/ can either be a full URL for the icon
-- file or the icon name following the Icon Naming specification.
-- 
-- If no bookmark for /@uri@/ is found one is created.
-- 
-- /Since: 2.12/
bookmarkFileSetIcon ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> Maybe (T.Text)
    -- ^ /@href@/: the URI of the icon for the bookmark, or 'P.Nothing'
    -> T.Text
    -- ^ /@mimeType@/: the MIME type of the icon for the bookmark
    -> m ()
bookmarkFileSetIcon :: BookmarkFile -> Text -> Maybe Text -> Text -> m ()
bookmarkFileSetIcon BookmarkFile
bookmark Text
uri Maybe Text
href Text
mimeType = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
maybeHref <- case Maybe Text
href of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jHref -> do
            CString
jHref' <- Text -> IO CString
textToCString Text
jHref
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jHref'
    CString
mimeType' <- Text -> IO CString
textToCString Text
mimeType
    Ptr BookmarkFile -> CString -> CString -> CString -> IO ()
g_bookmark_file_set_icon Ptr BookmarkFile
bookmark' CString
uri' CString
maybeHref CString
mimeType'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeHref
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
mimeType'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetIconMethodInfo
instance (signature ~ (T.Text -> Maybe (T.Text) -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetIconMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetIcon

#endif

-- method BookmarkFile::set_is_private
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_private"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE if the bookmark should be marked as private"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_is_private" g_bookmark_file_set_is_private :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CInt ->                                 -- is_private : TBasicType TBoolean
    IO ()

-- | Sets the private flag of the bookmark for /@uri@/.
-- 
-- If a bookmark for /@uri@/ cannot be found then it is created.
-- 
-- /Since: 2.12/
bookmarkFileSetIsPrivate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> Bool
    -- ^ /@isPrivate@/: 'P.True' if the bookmark should be marked as private
    -> m ()
bookmarkFileSetIsPrivate :: BookmarkFile -> Text -> Bool -> m ()
bookmarkFileSetIsPrivate BookmarkFile
bookmark Text
uri Bool
isPrivate = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    let isPrivate' :: CInt
isPrivate' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isPrivate
    Ptr BookmarkFile -> CString -> CInt -> IO ()
g_bookmark_file_set_is_private Ptr BookmarkFile
bookmark' CString
uri' CInt
isPrivate'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method BookmarkFile::set_mime_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mime_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a MIME type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_mime_type" g_bookmark_file_set_mime_type :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- mime_type : TBasicType TUTF8
    IO ()

-- | Sets /@mimeType@/ as the MIME type of the bookmark for /@uri@/.
-- 
-- If a bookmark for /@uri@/ cannot be found then it is created.
-- 
-- /Since: 2.12/
bookmarkFileSetMimeType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> T.Text
    -- ^ /@mimeType@/: a MIME type
    -> m ()
bookmarkFileSetMimeType :: BookmarkFile -> Text -> Text -> m ()
bookmarkFileSetMimeType BookmarkFile
bookmark Text
uri Text
mimeType = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
mimeType' <- Text -> IO CString
textToCString Text
mimeType
    Ptr BookmarkFile -> CString -> CString -> IO ()
g_bookmark_file_set_mime_type Ptr BookmarkFile
bookmark' CString
uri' CString
mimeType'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
mimeType'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetMimeTypeMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetMimeTypeMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetMimeType

#endif

-- method BookmarkFile::set_modified
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modified"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a timestamp or -1 to use the current time"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_modified" g_bookmark_file_set_modified :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CLong ->                                -- modified : TBasicType TLong
    IO ()

-- | Sets the last time the bookmark for /@uri@/ was last modified.
-- 
-- If no bookmark for /@uri@/ is found then it is created.
-- 
-- The \"modified\" time should only be set when the bookmark\'s meta-data
-- was actually changed.  Every function of t'GI.GLib.Structs.BookmarkFile.BookmarkFile' that
-- modifies a bookmark also changes the modification time, except for
-- 'GI.GLib.Structs.BookmarkFile.bookmarkFileSetVisited'.
-- 
-- /Since: 2.12/
bookmarkFileSetModified ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> CLong
    -- ^ /@modified@/: a timestamp or -1 to use the current time
    -> m ()
bookmarkFileSetModified :: BookmarkFile -> Text -> CLong -> m ()
bookmarkFileSetModified BookmarkFile
bookmark Text
uri CLong
modified = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr BookmarkFile -> CString -> CLong -> IO ()
g_bookmark_file_set_modified Ptr BookmarkFile
bookmark' CString
uri' CLong
modified
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetModifiedMethodInfo
instance (signature ~ (T.Text -> CLong -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetModifiedMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetModified

#endif

-- method BookmarkFile::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a UTF-8 encoded string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_title" g_bookmark_file_set_title :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Sets /@title@/ as the title of the bookmark for /@uri@/ inside the
-- bookmark file /@bookmark@/.
-- 
-- If /@uri@/ is 'P.Nothing', the title of /@bookmark@/ is set.
-- 
-- If a bookmark for /@uri@/ cannot be found then it is created.
-- 
-- /Since: 2.12/
bookmarkFileSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> Maybe (T.Text)
    -- ^ /@uri@/: a valid URI or 'P.Nothing'
    -> T.Text
    -- ^ /@title@/: a UTF-8 encoded string
    -> m ()
bookmarkFileSetTitle :: BookmarkFile -> Maybe Text -> Text -> m ()
bookmarkFileSetTitle BookmarkFile
bookmark Maybe Text
uri Text
title = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
maybeUri <- case Maybe Text
uri of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jUri -> do
            CString
jUri' <- Text -> IO CString
textToCString Text
jUri
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jUri'
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr BookmarkFile -> CString -> CString -> IO ()
g_bookmark_file_set_title Ptr BookmarkFile
bookmark' CString
maybeUri CString
title'
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeUri
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetTitleMethodInfo
instance (signature ~ (Maybe (T.Text) -> T.Text -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetTitleMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetTitle

#endif

-- method BookmarkFile::set_visited
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "visited"
--           , argType = TBasicType TLong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a timestamp or -1 to use the current time"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_set_visited" g_bookmark_file_set_visited :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- uri : TBasicType TUTF8
    CLong ->                                -- visited : TBasicType TLong
    IO ()

-- | Sets the time the bookmark for /@uri@/ was last visited.
-- 
-- If no bookmark for /@uri@/ is found then it is created.
-- 
-- The \"visited\" time should only be set if the bookmark was launched,
-- either using the command line retrieved by 'GI.GLib.Structs.BookmarkFile.bookmarkFileGetAppInfo'
-- or by the default application for the bookmark\'s MIME type, retrieved
-- using 'GI.GLib.Structs.BookmarkFile.bookmarkFileGetMimeType'.  Changing the \"visited\" time
-- does not affect the \"modified\" time.
-- 
-- /Since: 2.12/
bookmarkFileSetVisited ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> CLong
    -- ^ /@visited@/: a timestamp or -1 to use the current time
    -> m ()
bookmarkFileSetVisited :: BookmarkFile -> Text -> CLong -> m ()
bookmarkFileSetVisited BookmarkFile
bookmark Text
uri CLong
visited = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr BookmarkFile -> CString -> CLong -> IO ()
g_bookmark_file_set_visited Ptr BookmarkFile
bookmark' CString
uri' CLong
visited
    BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data BookmarkFileSetVisitedMethodInfo
instance (signature ~ (T.Text -> CLong -> m ()), MonadIO m) => O.MethodInfo BookmarkFileSetVisitedMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileSetVisited

#endif

-- method BookmarkFile::to_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , 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 string, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "return location for the length of the returned string, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt8))
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_to_data" g_bookmark_file_to_data :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Word8)

-- | This function outputs /@bookmark@/ as a string.
-- 
-- /Since: 2.12/
bookmarkFileToData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> m ByteString
    -- ^ __Returns:__ 
    --   a newly allocated string holding the contents of the t'GI.GLib.Structs.BookmarkFile.BookmarkFile' /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileToData :: BookmarkFile -> m ByteString
bookmarkFileToData BookmarkFile
bookmark = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    Ptr BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO ByteString -> IO () -> IO ByteString
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Word8
result <- (Ptr (Ptr GError) -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Word8)) -> IO (Ptr Word8))
-> (Ptr (Ptr GError) -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile
-> Ptr Word64 -> Ptr (Ptr GError) -> IO (Ptr Word8)
g_bookmark_file_to_data Ptr BookmarkFile
bookmark' Ptr Word64
length_
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        Text -> Ptr Word8 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"bookmarkFileToData" Ptr Word8
result
        ByteString
result' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
length_') Ptr Word8
result
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
result
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'
     ) (do
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileToDataMethodInfo
instance (signature ~ (m ByteString), MonadIO m) => O.MethodInfo BookmarkFileToDataMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileToData

#endif

-- method BookmarkFile::to_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "bookmark"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "BookmarkFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBookmarkFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path of the output file"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_bookmark_file_to_file" g_bookmark_file_to_file :: 
    Ptr BookmarkFile ->                     -- bookmark : TInterface (Name {namespace = "GLib", name = "BookmarkFile"})
    CString ->                              -- filename : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This function outputs /@bookmark@/ into a file.  The write process is
-- guaranteed to be atomic by using 'GI.GLib.Functions.fileSetContents' internally.
-- 
-- /Since: 2.12/
bookmarkFileToFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    BookmarkFile
    -- ^ /@bookmark@/: a t'GI.GLib.Structs.BookmarkFile.BookmarkFile'
    -> [Char]
    -- ^ /@filename@/: path of the output file
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
bookmarkFileToFile :: BookmarkFile -> [Char] -> m ()
bookmarkFileToFile BookmarkFile
bookmark [Char]
filename = 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 BookmarkFile
bookmark' <- BookmarkFile -> IO (Ptr BookmarkFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr BookmarkFile
bookmark
    CString
filename' <- [Char] -> IO CString
stringToCString [Char]
filename
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr BookmarkFile -> CString -> Ptr (Ptr GError) -> IO CInt
g_bookmark_file_to_file Ptr BookmarkFile
bookmark' CString
filename'
        BookmarkFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr BookmarkFile
bookmark
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
data BookmarkFileToFileMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m) => O.MethodInfo BookmarkFileToFileMethodInfo BookmarkFile signature where
    overloadedMethod = bookmarkFileToFile

#endif

-- method BookmarkFile::error_quark
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TBasicType TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_error_quark" g_bookmark_file_error_quark :: 
    IO Word32

-- | /No description available in the introspection data./
bookmarkFileErrorQuark ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Word32
bookmarkFileErrorQuark :: m Word32
bookmarkFileErrorQuark  = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Word32
result <- IO Word32
g_bookmark_file_error_quark
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveBookmarkFileMethod (t :: Symbol) (o :: *) :: * where
    ResolveBookmarkFileMethod "addApplication" o = BookmarkFileAddApplicationMethodInfo
    ResolveBookmarkFileMethod "addGroup" o = BookmarkFileAddGroupMethodInfo
    ResolveBookmarkFileMethod "free" o = BookmarkFileFreeMethodInfo
    ResolveBookmarkFileMethod "hasApplication" o = BookmarkFileHasApplicationMethodInfo
    ResolveBookmarkFileMethod "hasGroup" o = BookmarkFileHasGroupMethodInfo
    ResolveBookmarkFileMethod "hasItem" o = BookmarkFileHasItemMethodInfo
    ResolveBookmarkFileMethod "loadFromData" o = BookmarkFileLoadFromDataMethodInfo
    ResolveBookmarkFileMethod "loadFromDataDirs" o = BookmarkFileLoadFromDataDirsMethodInfo
    ResolveBookmarkFileMethod "loadFromFile" o = BookmarkFileLoadFromFileMethodInfo
    ResolveBookmarkFileMethod "moveItem" o = BookmarkFileMoveItemMethodInfo
    ResolveBookmarkFileMethod "removeApplication" o = BookmarkFileRemoveApplicationMethodInfo
    ResolveBookmarkFileMethod "removeGroup" o = BookmarkFileRemoveGroupMethodInfo
    ResolveBookmarkFileMethod "removeItem" o = BookmarkFileRemoveItemMethodInfo
    ResolveBookmarkFileMethod "toData" o = BookmarkFileToDataMethodInfo
    ResolveBookmarkFileMethod "toFile" o = BookmarkFileToFileMethodInfo
    ResolveBookmarkFileMethod "getAdded" o = BookmarkFileGetAddedMethodInfo
    ResolveBookmarkFileMethod "getAppInfo" o = BookmarkFileGetAppInfoMethodInfo
    ResolveBookmarkFileMethod "getApplications" o = BookmarkFileGetApplicationsMethodInfo
    ResolveBookmarkFileMethod "getDescription" o = BookmarkFileGetDescriptionMethodInfo
    ResolveBookmarkFileMethod "getGroups" o = BookmarkFileGetGroupsMethodInfo
    ResolveBookmarkFileMethod "getIcon" o = BookmarkFileGetIconMethodInfo
    ResolveBookmarkFileMethod "getIsPrivate" o = BookmarkFileGetIsPrivateMethodInfo
    ResolveBookmarkFileMethod "getMimeType" o = BookmarkFileGetMimeTypeMethodInfo
    ResolveBookmarkFileMethod "getModified" o = BookmarkFileGetModifiedMethodInfo
    ResolveBookmarkFileMethod "getSize" o = BookmarkFileGetSizeMethodInfo
    ResolveBookmarkFileMethod "getTitle" o = BookmarkFileGetTitleMethodInfo
    ResolveBookmarkFileMethod "getUris" o = BookmarkFileGetUrisMethodInfo
    ResolveBookmarkFileMethod "getVisited" o = BookmarkFileGetVisitedMethodInfo
    ResolveBookmarkFileMethod "setAdded" o = BookmarkFileSetAddedMethodInfo
    ResolveBookmarkFileMethod "setAppInfo" o = BookmarkFileSetAppInfoMethodInfo
    ResolveBookmarkFileMethod "setDescription" o = BookmarkFileSetDescriptionMethodInfo
    ResolveBookmarkFileMethod "setGroups" o = BookmarkFileSetGroupsMethodInfo
    ResolveBookmarkFileMethod "setIcon" o = BookmarkFileSetIconMethodInfo
    ResolveBookmarkFileMethod "setIsPrivate" o = BookmarkFileSetIsPrivateMethodInfo
    ResolveBookmarkFileMethod "setMimeType" o = BookmarkFileSetMimeTypeMethodInfo
    ResolveBookmarkFileMethod "setModified" o = BookmarkFileSetModifiedMethodInfo
    ResolveBookmarkFileMethod "setTitle" o = BookmarkFileSetTitleMethodInfo
    ResolveBookmarkFileMethod "setVisited" o = BookmarkFileSetVisitedMethodInfo
    ResolveBookmarkFileMethod l o = O.MethodResolutionFailed l o

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

#endif