{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gio.Objects.Task.Task' represents and manages a cancellable \"task\".
-- 
-- == Asynchronous operations
-- 
-- The most common usage of t'GI.Gio.Objects.Task.Task' is as a t'GI.Gio.Interfaces.AsyncResult.AsyncResult', to
-- manage data during an asynchronous operation. You call
-- 'GI.Gio.Objects.Task.taskNew' in the \"start\" method, followed by
-- 'GI.Gio.Objects.Task.taskSetTaskData' and the like if you need to keep some
-- additional data associated with the task, and then pass the
-- task object around through your asynchronous operation.
-- Eventually, you will call a method such as
-- 'GI.Gio.Objects.Task.taskReturnPointer' or 'GI.Gio.Objects.Task.taskReturnError', which will
-- save the value you give it and then invoke the task\'s callback
-- function in the
-- [thread-default main context][g-main-context-push-thread-default]
-- where it was created (waiting until the next iteration of the main
-- loop first, if necessary). The caller will pass the t'GI.Gio.Objects.Task.Task' back to
-- the operation\'s finish function (as a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'), and you can
-- use 'GI.Gio.Objects.Task.taskPropagatePointer' or the like to extract the
-- return value.
-- 
-- Here is an example for using GTask as a GAsyncResult:
-- 
-- === /C code/
-- >
-- >    typedef struct {
-- >      CakeFrostingType frosting;
-- >      char *message;
-- >    } DecorationData;
-- >
-- >    static void
-- >    decoration_data_free (DecorationData *decoration)
-- >    {
-- >      g_free (decoration->message);
-- >      g_slice_free (DecorationData, decoration);
-- >    }
-- >
-- >    static void
-- >    baked_cb (Cake     *cake,
-- >              gpointer  user_data)
-- >    {
-- >      GTask *task = user_data;
-- >      DecorationData *decoration = g_task_get_task_data (task);
-- >      GError *error = NULL;
-- >
-- >      if (cake == NULL)
-- >        {
-- >          g_task_return_new_error (task, BAKER_ERROR, BAKER_ERROR_NO_FLOUR,
-- >                                   "Go to the supermarket");
-- >          g_object_unref (task);
-- >          return;
-- >        }
-- >
-- >      if (!cake_decorate (cake, decoration->frosting, decoration->message, &error))
-- >        {
-- >          g_object_unref (cake);
-- >          // g_task_return_error() takes ownership of error
-- >          g_task_return_error (task, error);
-- >          g_object_unref (task);
-- >          return;
-- >        }
-- >
-- >      g_task_return_pointer (task, cake, g_object_unref);
-- >      g_object_unref (task);
-- >    }
-- >
-- >    void
-- >    baker_bake_cake_async (Baker               *self,
-- >                           guint                radius,
-- >                           CakeFlavor           flavor,
-- >                           CakeFrostingType     frosting,
-- >                           const char          *message,
-- >                           GCancellable        *cancellable,
-- >                           GAsyncReadyCallback  callback,
-- >                           gpointer             user_data)
-- >    {
-- >      GTask *task;
-- >      DecorationData *decoration;
-- >      Cake  *cake;
-- >
-- >      task = g_task_new (self, cancellable, callback, user_data);
-- >      if (radius < 3)
-- >        {
-- >          g_task_return_new_error (task, BAKER_ERROR, BAKER_ERROR_TOO_SMALL,
-- >                                   "%ucm radius cakes are silly",
-- >                                   radius);
-- >          g_object_unref (task);
-- >          return;
-- >        }
-- >
-- >      cake = _baker_get_cached_cake (self, radius, flavor, frosting, message);
-- >      if (cake != NULL)
-- >        {
-- >          // _baker_get_cached_cake() returns a reffed cake
-- >          g_task_return_pointer (task, cake, g_object_unref);
-- >          g_object_unref (task);
-- >          return;
-- >        }
-- >
-- >      decoration = g_slice_new (DecorationData);
-- >      decoration->frosting = frosting;
-- >      decoration->message = g_strdup (message);
-- >      g_task_set_task_data (task, decoration, (GDestroyNotify) decoration_data_free);
-- >
-- >      _baker_begin_cake (self, radius, flavor, cancellable, baked_cb, task);
-- >    }
-- >
-- >    Cake *
-- >    baker_bake_cake_finish (Baker         *self,
-- >                            GAsyncResult  *result,
-- >                            GError       **error)
-- >    {
-- >      g_return_val_if_fail (g_task_is_valid (result, self), NULL);
-- >
-- >      return g_task_propagate_pointer (G_TASK (result), error);
-- >    }
-- 
-- 
-- == Chained asynchronous operations
-- 
-- t'GI.Gio.Objects.Task.Task' also tries to simplify asynchronous operations that
-- internally chain together several smaller asynchronous
-- operations. 'GI.Gio.Objects.Task.taskGetCancellable', 'GI.Gio.Objects.Task.taskGetContext',
-- and 'GI.Gio.Objects.Task.taskGetPriority' allow you to get back the task\'s
-- t'GI.Gio.Objects.Cancellable.Cancellable', t'GI.GLib.Structs.MainContext.MainContext', and [I\/O priority][io-priority]
-- when starting a new subtask, so you don\'t have to keep track
-- of them yourself. @/g_task_attach_source()/@ simplifies the case
-- of waiting for a source to fire (automatically using the correct
-- t'GI.GLib.Structs.MainContext.MainContext' and priority).
-- 
-- Here is an example for chained asynchronous operations:
--   
-- === /C code/
-- >
-- >    typedef struct {
-- >      Cake *cake;
-- >      CakeFrostingType frosting;
-- >      char *message;
-- >    } BakingData;
-- >
-- >    static void
-- >    decoration_data_free (BakingData *bd)
-- >    {
-- >      if (bd->cake)
-- >        g_object_unref (bd->cake);
-- >      g_free (bd->message);
-- >      g_slice_free (BakingData, bd);
-- >    }
-- >
-- >    static void
-- >    decorated_cb (Cake         *cake,
-- >                  GAsyncResult *result,
-- >                  gpointer      user_data)
-- >    {
-- >      GTask *task = user_data;
-- >      GError *error = NULL;
-- >
-- >      if (!cake_decorate_finish (cake, result, &error))
-- >        {
-- >          g_object_unref (cake);
-- >          g_task_return_error (task, error);
-- >          g_object_unref (task);
-- >          return;
-- >        }
-- >
-- >      // baking_data_free() will drop its ref on the cake, so we have to
-- >      // take another here to give to the caller.
-- >      g_task_return_pointer (task, g_object_ref (cake), g_object_unref);
-- >      g_object_unref (task);
-- >    }
-- >
-- >    static gboolean
-- >    decorator_ready (gpointer user_data)
-- >    {
-- >      GTask *task = user_data;
-- >      BakingData *bd = g_task_get_task_data (task);
-- >
-- >      cake_decorate_async (bd->cake, bd->frosting, bd->message,
-- >                           g_task_get_cancellable (task),
-- >                           decorated_cb, task);
-- >
-- >      return G_SOURCE_REMOVE;
-- >    }
-- >
-- >    static void
-- >    baked_cb (Cake     *cake,
-- >              gpointer  user_data)
-- >    {
-- >      GTask *task = user_data;
-- >      BakingData *bd = g_task_get_task_data (task);
-- >      GError *error = NULL;
-- >
-- >      if (cake == NULL)
-- >        {
-- >          g_task_return_new_error (task, BAKER_ERROR, BAKER_ERROR_NO_FLOUR,
-- >                                   "Go to the supermarket");
-- >          g_object_unref (task);
-- >          return;
-- >        }
-- >
-- >      bd->cake = cake;
-- >
-- >      // Bail out now if the user has already cancelled
-- >      if (g_task_return_error_if_cancelled (task))
-- >        {
-- >          g_object_unref (task);
-- >          return;
-- >        }
-- >
-- >      if (cake_decorator_available (cake))
-- >        decorator_ready (task);
-- >      else
-- >        {
-- >          GSource *source;
-- >
-- >          source = cake_decorator_wait_source_new (cake);
-- >          // Attach @source to @task's GMainContext and have it call
-- >          // decorator_ready() when it is ready.
-- >          g_task_attach_source (task, source, decorator_ready);
-- >          g_source_unref (source);
-- >        }
-- >    }
-- >
-- >    void
-- >    baker_bake_cake_async (Baker               *self,
-- >                           guint                radius,
-- >                           CakeFlavor           flavor,
-- >                           CakeFrostingType     frosting,
-- >                           const char          *message,
-- >                           gint                 priority,
-- >                           GCancellable        *cancellable,
-- >                           GAsyncReadyCallback  callback,
-- >                           gpointer             user_data)
-- >    {
-- >      GTask *task;
-- >      BakingData *bd;
-- >
-- >      task = g_task_new (self, cancellable, callback, user_data);
-- >      g_task_set_priority (task, priority);
-- >
-- >      bd = g_slice_new0 (BakingData);
-- >      bd->frosting = frosting;
-- >      bd->message = g_strdup (message);
-- >      g_task_set_task_data (task, bd, (GDestroyNotify) baking_data_free);
-- >
-- >      _baker_begin_cake (self, radius, flavor, cancellable, baked_cb, task);
-- >    }
-- >
-- >    Cake *
-- >    baker_bake_cake_finish (Baker         *self,
-- >                            GAsyncResult  *result,
-- >                            GError       **error)
-- >    {
-- >      g_return_val_if_fail (g_task_is_valid (result, self), NULL);
-- >
-- >      return g_task_propagate_pointer (G_TASK (result), error);
-- >    }
-- 
-- 
-- == Asynchronous operations from synchronous ones
-- 
-- You can use 'GI.Gio.Objects.Task.taskRunInThread' to turn a synchronous
-- operation into an asynchronous one, by running it in a thread.
-- When it completes, the result will be dispatched to the
-- [thread-default main context][g-main-context-push-thread-default]
-- where the t'GI.Gio.Objects.Task.Task' was created.
-- 
-- Running a task in a thread:
--   
-- === /C code/
-- >
-- >    typedef struct {
-- >      guint radius;
-- >      CakeFlavor flavor;
-- >      CakeFrostingType frosting;
-- >      char *message;
-- >    } CakeData;
-- >
-- >    static void
-- >    cake_data_free (CakeData *cake_data)
-- >    {
-- >      g_free (cake_data->message);
-- >      g_slice_free (CakeData, cake_data);
-- >    }
-- >
-- >    static void
-- >    bake_cake_thread (GTask         *task,
-- >                      gpointer       source_object,
-- >                      gpointer       task_data,
-- >                      GCancellable  *cancellable)
-- >    {
-- >      Baker *self = source_object;
-- >      CakeData *cake_data = task_data;
-- >      Cake *cake;
-- >      GError *error = NULL;
-- >
-- >      cake = bake_cake (baker, cake_data->radius, cake_data->flavor,
-- >                        cake_data->frosting, cake_data->message,
-- >                        cancellable, &error);
-- >      if (cake)
-- >        g_task_return_pointer (task, cake, g_object_unref);
-- >      else
-- >        g_task_return_error (task, error);
-- >    }
-- >
-- >    void
-- >    baker_bake_cake_async (Baker               *self,
-- >                           guint                radius,
-- >                           CakeFlavor           flavor,
-- >                           CakeFrostingType     frosting,
-- >                           const char          *message,
-- >                           GCancellable        *cancellable,
-- >                           GAsyncReadyCallback  callback,
-- >                           gpointer             user_data)
-- >    {
-- >      CakeData *cake_data;
-- >      GTask *task;
-- >
-- >      cake_data = g_slice_new (CakeData);
-- >      cake_data->radius = radius;
-- >      cake_data->flavor = flavor;
-- >      cake_data->frosting = frosting;
-- >      cake_data->message = g_strdup (message);
-- >      task = g_task_new (self, cancellable, callback, user_data);
-- >      g_task_set_task_data (task, cake_data, (GDestroyNotify) cake_data_free);
-- >      g_task_run_in_thread (task, bake_cake_thread);
-- >      g_object_unref (task);
-- >    }
-- >
-- >    Cake *
-- >    baker_bake_cake_finish (Baker         *self,
-- >                            GAsyncResult  *result,
-- >                            GError       **error)
-- >    {
-- >      g_return_val_if_fail (g_task_is_valid (result, self), NULL);
-- >
-- >      return g_task_propagate_pointer (G_TASK (result), error);
-- >    }
-- 
-- 
-- == Adding cancellability to uncancellable tasks
-- 
-- Finally, 'GI.Gio.Objects.Task.taskRunInThread' and 'GI.Gio.Objects.Task.taskRunInThreadSync'
-- can be used to turn an uncancellable operation into a
-- cancellable one. If you call 'GI.Gio.Objects.Task.taskSetReturnOnCancel',
-- passing 'P.True', then if the task\'s t'GI.Gio.Objects.Cancellable.Cancellable' is cancelled,
-- it will return control back to the caller immediately, while
-- allowing the task thread to continue running in the background
-- (and simply discarding its result when it finally does finish).
-- Provided that the task thread is careful about how it uses
-- locks and other externally-visible resources, this allows you
-- to make \"GLib-friendly\" asynchronous and cancellable
-- synchronous variants of blocking APIs.
-- 
-- Cancelling a task:
--   
-- === /C code/
-- >
-- >    static void
-- >    bake_cake_thread (GTask         *task,
-- >                      gpointer       source_object,
-- >                      gpointer       task_data,
-- >                      GCancellable  *cancellable)
-- >    {
-- >      Baker *self = source_object;
-- >      CakeData *cake_data = task_data;
-- >      Cake *cake;
-- >      GError *error = NULL;
-- >
-- >      cake = bake_cake (baker, cake_data->radius, cake_data->flavor,
-- >                        cake_data->frosting, cake_data->message,
-- >                        &error);
-- >      if (error)
-- >        {
-- >          g_task_return_error (task, error);
-- >          return;
-- >        }
-- >
-- >      // If the task has already been cancelled, then we don't want to add
-- >      // the cake to the cake cache. Likewise, we don't  want to have the
-- >      // task get cancelled in the middle of updating the cache.
-- >      // g_task_set_return_on_cancel() will return %TRUE here if it managed
-- >      // to disable return-on-cancel, or %FALSE if the task was cancelled
-- >      // before it could.
-- >      if (g_task_set_return_on_cancel (task, FALSE))
-- >        {
-- >          // If the caller cancels at this point, their
-- >          // GAsyncReadyCallback won't be invoked until we return,
-- >          // so we don't have to worry that this code will run at
-- >          // the same time as that code does. But if there were
-- >          // other functions that might look at the cake cache,
-- >          // then we'd probably need a GMutex here as well.
-- >          baker_add_cake_to_cache (baker, cake);
-- >          g_task_return_pointer (task, cake, g_object_unref);
-- >        }
-- >    }
-- >
-- >    void
-- >    baker_bake_cake_async (Baker               *self,
-- >                           guint                radius,
-- >                           CakeFlavor           flavor,
-- >                           CakeFrostingType     frosting,
-- >                           const char          *message,
-- >                           GCancellable        *cancellable,
-- >                           GAsyncReadyCallback  callback,
-- >                           gpointer             user_data)
-- >    {
-- >      CakeData *cake_data;
-- >      GTask *task;
-- >
-- >      cake_data = g_slice_new (CakeData);
-- >
-- >      ...
-- >
-- >      task = g_task_new (self, cancellable, callback, user_data);
-- >      g_task_set_task_data (task, cake_data, (GDestroyNotify) cake_data_free);
-- >      g_task_set_return_on_cancel (task, TRUE);
-- >      g_task_run_in_thread (task, bake_cake_thread);
-- >    }
-- >
-- >    Cake *
-- >    baker_bake_cake_sync (Baker               *self,
-- >                          guint                radius,
-- >                          CakeFlavor           flavor,
-- >                          CakeFrostingType     frosting,
-- >                          const char          *message,
-- >                          GCancellable        *cancellable,
-- >                          GError             **error)
-- >    {
-- >      CakeData *cake_data;
-- >      GTask *task;
-- >      Cake *cake;
-- >
-- >      cake_data = g_slice_new (CakeData);
-- >
-- >      ...
-- >
-- >      task = g_task_new (self, cancellable, NULL, NULL);
-- >      g_task_set_task_data (task, cake_data, (GDestroyNotify) cake_data_free);
-- >      g_task_set_return_on_cancel (task, TRUE);
-- >      g_task_run_in_thread_sync (task, bake_cake_thread);
-- >
-- >      cake = g_task_propagate_pointer (task, error);
-- >      g_object_unref (task);
-- >      return cake;
-- >    }
-- 
-- 
-- == Porting from GSimpleAsyncResult
-- 
-- t'GI.Gio.Objects.Task.Task'\'s API attempts to be simpler than t'GI.Gio.Objects.SimpleAsyncResult.SimpleAsyncResult'\'s
-- in several ways:
-- 
-- * You can save task-specific data with 'GI.Gio.Objects.Task.taskSetTaskData', and
-- retrieve it later with 'GI.Gio.Objects.Task.taskGetTaskData'. This replaces the
-- abuse of @/g_simple_async_result_set_op_res_gpointer()/@ for the same
-- purpose with t'GI.Gio.Objects.SimpleAsyncResult.SimpleAsyncResult'.
-- * In addition to the task data, t'GI.Gio.Objects.Task.Task' also keeps track of the
-- [priority][io-priority], t'GI.Gio.Objects.Cancellable.Cancellable', and
-- t'GI.GLib.Structs.MainContext.MainContext' associated with the task, so tasks that consist of
-- a chain of simpler asynchronous operations will have easy access
-- to those values when starting each sub-task.
-- * 'GI.Gio.Objects.Task.taskReturnErrorIfCancelled' provides simplified
-- handling for cancellation. In addition, cancellation
-- overrides any other t'GI.Gio.Objects.Task.Task' return value by default, like
-- t'GI.Gio.Objects.SimpleAsyncResult.SimpleAsyncResult' does when
-- 'GI.Gio.Objects.SimpleAsyncResult.simpleAsyncResultSetCheckCancellable' is called.
-- (You can use 'GI.Gio.Objects.Task.taskSetCheckCancellable' to turn off that
-- behavior.) On the other hand, 'GI.Gio.Objects.Task.taskRunInThread'
-- guarantees that it will always run your
-- @task_func@, even if the task\'s t'GI.Gio.Objects.Cancellable.Cancellable'
-- is already cancelled before the task gets a chance to run;
-- you can start your @task_func@ with a
-- 'GI.Gio.Objects.Task.taskReturnErrorIfCancelled' check if you need the
-- old behavior.
-- * The \"return\" methods (eg, 'GI.Gio.Objects.Task.taskReturnPointer')
-- automatically cause the task to be \"completed\" as well, and
-- there is no need to worry about the \"complete\" vs \"complete
-- in idle\" distinction. (t'GI.Gio.Objects.Task.Task' automatically figures out
-- whether the task\'s callback can be invoked directly, or
-- if it needs to be sent to another t'GI.GLib.Structs.MainContext.MainContext', or delayed
-- until the next iteration of the current t'GI.GLib.Structs.MainContext.MainContext'.)
-- * The \"finish\" functions for t'GI.Gio.Objects.Task.Task' based operations are generally
-- much simpler than t'GI.Gio.Objects.SimpleAsyncResult.SimpleAsyncResult' ones, normally consisting
-- of only a single call to 'GI.Gio.Objects.Task.taskPropagatePointer' or the like.
-- Since 'GI.Gio.Objects.Task.taskPropagatePointer' \"steals\" the return value from
-- the t'GI.Gio.Objects.Task.Task', it is not necessary to juggle pointers around to
-- prevent it from being freed twice.
-- * With t'GI.Gio.Objects.SimpleAsyncResult.SimpleAsyncResult', it was common to call
-- 'GI.Gio.Objects.SimpleAsyncResult.simpleAsyncResultPropagateError' from the
-- @_finish()@ wrapper function, and have
-- virtual method implementations only deal with successful
-- returns. This behavior is deprecated, because it makes it
-- difficult for a subclass to chain to a parent class\'s async
-- methods. Instead, the wrapper function should just be a
-- simple wrapper, and the virtual method should call an
-- appropriate @g_task_propagate_@ function.
-- Note that wrapper methods can now use
-- 'GI.Gio.Interfaces.AsyncResult.asyncResultLegacyPropagateError' to do old-style
-- t'GI.Gio.Objects.SimpleAsyncResult.SimpleAsyncResult' error-returning behavior, and
-- 'GI.Gio.Interfaces.AsyncResult.asyncResultIsTagged' to check if a result is tagged as
-- having come from the @_async()@ wrapper
-- function (for \"short-circuit\" results, such as when passing
-- 0 to 'GI.Gio.Objects.InputStream.inputStreamReadAsync').
-- 

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

module GI.Gio.Objects.Task
    ( 

-- * Exported types
    Task(..)                                ,
    IsTask                                  ,
    toTask                                  ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hadError]("GI.Gio.Objects.Task#g:method:hadError"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isTagged]("GI.Gio.Interfaces.AsyncResult#g:method:isTagged"), [legacyPropagateError]("GI.Gio.Interfaces.AsyncResult#g:method:legacyPropagateError"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [propagateBoolean]("GI.Gio.Objects.Task#g:method:propagateBoolean"), [propagateInt]("GI.Gio.Objects.Task#g:method:propagateInt"), [propagatePointer]("GI.Gio.Objects.Task#g:method:propagatePointer"), [propagateValue]("GI.Gio.Objects.Task#g:method:propagateValue"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [returnBoolean]("GI.Gio.Objects.Task#g:method:returnBoolean"), [returnError]("GI.Gio.Objects.Task#g:method:returnError"), [returnErrorIfCancelled]("GI.Gio.Objects.Task#g:method:returnErrorIfCancelled"), [returnInt]("GI.Gio.Objects.Task#g:method:returnInt"), [returnPointer]("GI.Gio.Objects.Task#g:method:returnPointer"), [returnValue]("GI.Gio.Objects.Task#g:method:returnValue"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [runInThread]("GI.Gio.Objects.Task#g:method:runInThread"), [runInThreadSync]("GI.Gio.Objects.Task#g:method:runInThreadSync"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCancellable]("GI.Gio.Objects.Task#g:method:getCancellable"), [getCheckCancellable]("GI.Gio.Objects.Task#g:method:getCheckCancellable"), [getCompleted]("GI.Gio.Objects.Task#g:method:getCompleted"), [getContext]("GI.Gio.Objects.Task#g:method:getContext"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getName]("GI.Gio.Objects.Task#g:method:getName"), [getPriority]("GI.Gio.Objects.Task#g:method:getPriority"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getReturnOnCancel]("GI.Gio.Objects.Task#g:method:getReturnOnCancel"), [getSourceObject]("GI.Gio.Objects.Task#g:method:getSourceObject"), [getSourceTag]("GI.Gio.Objects.Task#g:method:getSourceTag"), [getTaskData]("GI.Gio.Objects.Task#g:method:getTaskData"), [getUserData]("GI.Gio.Interfaces.AsyncResult#g:method:getUserData").
-- 
-- ==== Setters
-- [setCheckCancellable]("GI.Gio.Objects.Task#g:method:setCheckCancellable"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setName]("GI.Gio.Objects.Task#g:method:setName"), [setPriority]("GI.Gio.Objects.Task#g:method:setPriority"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReturnOnCancel]("GI.Gio.Objects.Task#g:method:setReturnOnCancel"), [setSourceTag]("GI.Gio.Objects.Task#g:method:setSourceTag"), [setTaskData]("GI.Gio.Objects.Task#g:method:setTaskData").

#if defined(ENABLE_OVERLOADING)
    ResolveTaskMethod                       ,
#endif

-- ** getCancellable #method:getCancellable#

#if defined(ENABLE_OVERLOADING)
    TaskGetCancellableMethodInfo            ,
#endif
    taskGetCancellable                      ,


-- ** getCheckCancellable #method:getCheckCancellable#

#if defined(ENABLE_OVERLOADING)
    TaskGetCheckCancellableMethodInfo       ,
#endif
    taskGetCheckCancellable                 ,


-- ** getCompleted #method:getCompleted#

#if defined(ENABLE_OVERLOADING)
    TaskGetCompletedMethodInfo              ,
#endif
    taskGetCompleted                        ,


-- ** getContext #method:getContext#

#if defined(ENABLE_OVERLOADING)
    TaskGetContextMethodInfo                ,
#endif
    taskGetContext                          ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    TaskGetNameMethodInfo                   ,
#endif
    taskGetName                             ,


-- ** getPriority #method:getPriority#

#if defined(ENABLE_OVERLOADING)
    TaskGetPriorityMethodInfo               ,
#endif
    taskGetPriority                         ,


-- ** getReturnOnCancel #method:getReturnOnCancel#

#if defined(ENABLE_OVERLOADING)
    TaskGetReturnOnCancelMethodInfo         ,
#endif
    taskGetReturnOnCancel                   ,


-- ** getSourceObject #method:getSourceObject#

#if defined(ENABLE_OVERLOADING)
    TaskGetSourceObjectMethodInfo           ,
#endif
    taskGetSourceObject                     ,


-- ** getSourceTag #method:getSourceTag#

#if defined(ENABLE_OVERLOADING)
    TaskGetSourceTagMethodInfo              ,
#endif
    taskGetSourceTag                        ,


-- ** getTaskData #method:getTaskData#

#if defined(ENABLE_OVERLOADING)
    TaskGetTaskDataMethodInfo               ,
#endif
    taskGetTaskData                         ,


-- ** hadError #method:hadError#

#if defined(ENABLE_OVERLOADING)
    TaskHadErrorMethodInfo                  ,
#endif
    taskHadError                            ,


-- ** isValid #method:isValid#

    taskIsValid                             ,


-- ** new #method:new#

    taskNew                                 ,


-- ** propagateBoolean #method:propagateBoolean#

#if defined(ENABLE_OVERLOADING)
    TaskPropagateBooleanMethodInfo          ,
#endif
    taskPropagateBoolean                    ,


-- ** propagateInt #method:propagateInt#

#if defined(ENABLE_OVERLOADING)
    TaskPropagateIntMethodInfo              ,
#endif
    taskPropagateInt                        ,


-- ** propagatePointer #method:propagatePointer#

#if defined(ENABLE_OVERLOADING)
    TaskPropagatePointerMethodInfo          ,
#endif
    taskPropagatePointer                    ,


-- ** propagateValue #method:propagateValue#

#if defined(ENABLE_OVERLOADING)
    TaskPropagateValueMethodInfo            ,
#endif
    taskPropagateValue                      ,


-- ** reportError #method:reportError#

    taskReportError                         ,


-- ** returnBoolean #method:returnBoolean#

#if defined(ENABLE_OVERLOADING)
    TaskReturnBooleanMethodInfo             ,
#endif
    taskReturnBoolean                       ,


-- ** returnError #method:returnError#

#if defined(ENABLE_OVERLOADING)
    TaskReturnErrorMethodInfo               ,
#endif
    taskReturnError                         ,


-- ** returnErrorIfCancelled #method:returnErrorIfCancelled#

#if defined(ENABLE_OVERLOADING)
    TaskReturnErrorIfCancelledMethodInfo    ,
#endif
    taskReturnErrorIfCancelled              ,


-- ** returnInt #method:returnInt#

#if defined(ENABLE_OVERLOADING)
    TaskReturnIntMethodInfo                 ,
#endif
    taskReturnInt                           ,


-- ** returnPointer #method:returnPointer#

#if defined(ENABLE_OVERLOADING)
    TaskReturnPointerMethodInfo             ,
#endif
    taskReturnPointer                       ,


-- ** returnValue #method:returnValue#

#if defined(ENABLE_OVERLOADING)
    TaskReturnValueMethodInfo               ,
#endif
    taskReturnValue                         ,


-- ** runInThread #method:runInThread#

#if defined(ENABLE_OVERLOADING)
    TaskRunInThreadMethodInfo               ,
#endif
    taskRunInThread                         ,


-- ** runInThreadSync #method:runInThreadSync#

#if defined(ENABLE_OVERLOADING)
    TaskRunInThreadSyncMethodInfo           ,
#endif
    taskRunInThreadSync                     ,


-- ** setCheckCancellable #method:setCheckCancellable#

#if defined(ENABLE_OVERLOADING)
    TaskSetCheckCancellableMethodInfo       ,
#endif
    taskSetCheckCancellable                 ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    TaskSetNameMethodInfo                   ,
#endif
    taskSetName                             ,


-- ** setPriority #method:setPriority#

#if defined(ENABLE_OVERLOADING)
    TaskSetPriorityMethodInfo               ,
#endif
    taskSetPriority                         ,


-- ** setReturnOnCancel #method:setReturnOnCancel#

#if defined(ENABLE_OVERLOADING)
    TaskSetReturnOnCancelMethodInfo         ,
#endif
    taskSetReturnOnCancel                   ,


-- ** setSourceTag #method:setSourceTag#

#if defined(ENABLE_OVERLOADING)
    TaskSetSourceTagMethodInfo              ,
#endif
    taskSetSourceTag                        ,


-- ** setTaskData #method:setTaskData#

#if defined(ENABLE_OVERLOADING)
    TaskSetTaskDataMethodInfo               ,
#endif
    taskSetTaskData                         ,




 -- * Properties


-- ** completed #attr:completed#
-- | Whether the task has completed, meaning its callback (if set) has been
-- invoked. This can only happen after 'GI.Gio.Objects.Task.taskReturnPointer',
-- 'GI.Gio.Objects.Task.taskReturnError' or one of the other return functions have been called
-- on the task.
-- 
-- This property is guaranteed to change from 'P.False' to 'P.True' exactly once.
-- 
-- The [Object::notify]("GI.GObject.Objects.Object#g:signal:notify") signal for this change is emitted in the same main
-- context as the task’s callback, immediately after that callback is invoked.
-- 
-- /Since: 2.44/

#if defined(ENABLE_OVERLOADING)
    TaskCompletedPropertyInfo               ,
#endif
    getTaskCompleted                        ,
#if defined(ENABLE_OVERLOADING)
    taskCompleted                           ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.MainContext as GLib.MainContext
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable

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

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

foreign import ccall "g_task_get_type"
    c_g_task_get_type :: IO B.Types.GType

instance B.Types.TypedObject Task where
    glibType :: IO GType
glibType = IO GType
c_g_task_get_type

instance B.Types.GObject Task

-- | Type class for types which can be safely cast to `Task`, for instance with `toTask`.
class (SP.GObject o, O.IsDescendantOf Task o) => IsTask o
instance (SP.GObject o, O.IsDescendantOf Task o) => IsTask o

instance O.HasParentTypes Task
type instance O.ParentTypes Task = '[GObject.Object.Object, Gio.AsyncResult.AsyncResult]

-- | Cast to `Task`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toTask :: (MIO.MonadIO m, IsTask o) => o -> m Task
toTask :: forall (m :: * -> *) o. (MonadIO m, IsTask o) => o -> m Task
toTask = IO Task -> m Task
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Task -> m Task) -> (o -> IO Task) -> o -> m Task
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Task -> Task) -> o -> IO Task
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Task -> Task
Task

-- | Convert 'Task' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Task) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_task_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Task -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Task
P.Nothing = Ptr GValue -> Ptr Task -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Task
forall a. Ptr a
FP.nullPtr :: FP.Ptr Task)
    gvalueSet_ Ptr GValue
gv (P.Just Task
obj) = Task -> (Ptr Task -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Task
obj (Ptr GValue -> Ptr Task -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Task)
gvalueGet_ Ptr GValue
gv = do
        Ptr Task
ptr <- Ptr GValue -> IO (Ptr Task)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Task)
        if Ptr Task
ptr Ptr Task -> Ptr Task -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Task
forall a. Ptr a
FP.nullPtr
        then Task -> Maybe Task
forall a. a -> Maybe a
P.Just (Task -> Maybe Task) -> IO Task -> IO (Maybe Task)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Task -> Task) -> Ptr Task -> IO Task
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Task -> Task
Task Ptr Task
ptr
        else Maybe Task -> IO (Maybe Task)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Task
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveTaskMethod (t :: Symbol) (o :: *) :: * where
    ResolveTaskMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTaskMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTaskMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTaskMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTaskMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTaskMethod "hadError" o = TaskHadErrorMethodInfo
    ResolveTaskMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTaskMethod "isTagged" o = Gio.AsyncResult.AsyncResultIsTaggedMethodInfo
    ResolveTaskMethod "legacyPropagateError" o = Gio.AsyncResult.AsyncResultLegacyPropagateErrorMethodInfo
    ResolveTaskMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTaskMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTaskMethod "propagateBoolean" o = TaskPropagateBooleanMethodInfo
    ResolveTaskMethod "propagateInt" o = TaskPropagateIntMethodInfo
    ResolveTaskMethod "propagatePointer" o = TaskPropagatePointerMethodInfo
    ResolveTaskMethod "propagateValue" o = TaskPropagateValueMethodInfo
    ResolveTaskMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTaskMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTaskMethod "returnBoolean" o = TaskReturnBooleanMethodInfo
    ResolveTaskMethod "returnError" o = TaskReturnErrorMethodInfo
    ResolveTaskMethod "returnErrorIfCancelled" o = TaskReturnErrorIfCancelledMethodInfo
    ResolveTaskMethod "returnInt" o = TaskReturnIntMethodInfo
    ResolveTaskMethod "returnPointer" o = TaskReturnPointerMethodInfo
    ResolveTaskMethod "returnValue" o = TaskReturnValueMethodInfo
    ResolveTaskMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTaskMethod "runInThread" o = TaskRunInThreadMethodInfo
    ResolveTaskMethod "runInThreadSync" o = TaskRunInThreadSyncMethodInfo
    ResolveTaskMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTaskMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTaskMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTaskMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTaskMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTaskMethod "getCancellable" o = TaskGetCancellableMethodInfo
    ResolveTaskMethod "getCheckCancellable" o = TaskGetCheckCancellableMethodInfo
    ResolveTaskMethod "getCompleted" o = TaskGetCompletedMethodInfo
    ResolveTaskMethod "getContext" o = TaskGetContextMethodInfo
    ResolveTaskMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTaskMethod "getName" o = TaskGetNameMethodInfo
    ResolveTaskMethod "getPriority" o = TaskGetPriorityMethodInfo
    ResolveTaskMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTaskMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTaskMethod "getReturnOnCancel" o = TaskGetReturnOnCancelMethodInfo
    ResolveTaskMethod "getSourceObject" o = TaskGetSourceObjectMethodInfo
    ResolveTaskMethod "getSourceTag" o = TaskGetSourceTagMethodInfo
    ResolveTaskMethod "getTaskData" o = TaskGetTaskDataMethodInfo
    ResolveTaskMethod "getUserData" o = Gio.AsyncResult.AsyncResultGetUserDataMethodInfo
    ResolveTaskMethod "setCheckCancellable" o = TaskSetCheckCancellableMethodInfo
    ResolveTaskMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTaskMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTaskMethod "setName" o = TaskSetNameMethodInfo
    ResolveTaskMethod "setPriority" o = TaskSetPriorityMethodInfo
    ResolveTaskMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTaskMethod "setReturnOnCancel" o = TaskSetReturnOnCancelMethodInfo
    ResolveTaskMethod "setSourceTag" o = TaskSetSourceTagMethodInfo
    ResolveTaskMethod "setTaskData" o = TaskSetTaskDataMethodInfo
    ResolveTaskMethod l o = O.MethodResolutionFailed l o

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

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

#endif

instance (info ~ ResolveTaskMethod t Task, O.OverloadedMethodInfo info Task) => OL.IsLabel t (O.MethodProxy info Task) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "completed"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@completed@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' task #completed
-- @
getTaskCompleted :: (MonadIO m, IsTask o) => o -> m Bool
getTaskCompleted :: forall (m :: * -> *) o. (MonadIO m, IsTask o) => o -> m Bool
getTaskCompleted o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"completed"

#if defined(ENABLE_OVERLOADING)
data TaskCompletedPropertyInfo
instance AttrInfo TaskCompletedPropertyInfo where
    type AttrAllowedOps TaskCompletedPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint TaskCompletedPropertyInfo = IsTask
    type AttrSetTypeConstraint TaskCompletedPropertyInfo = (~) ()
    type AttrTransferTypeConstraint TaskCompletedPropertyInfo = (~) ()
    type AttrTransferType TaskCompletedPropertyInfo = ()
    type AttrGetType TaskCompletedPropertyInfo = Bool
    type AttrLabel TaskCompletedPropertyInfo = "completed"
    type AttrOrigin TaskCompletedPropertyInfo = Task
    attrGet = getTaskCompleted
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.Task.completed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-Task.html#g:attr:completed"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Task
type instance O.AttributeList Task = TaskAttributeList
type TaskAttributeList = ('[ '("completed", TaskCompletedPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
taskCompleted :: AttrLabelProxy "completed"
taskCompleted = AttrLabelProxy

#endif

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

#endif

-- method Task::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "source_object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GObject that owns\n  this task, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional #GCancellable object, %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncReadyCallback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data passed to @callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Task" })
-- throws : False
-- Skip return : False

foreign import ccall "g_task_new" g_task_new :: 
    Ptr GObject.Object.Object ->            -- source_object : TInterface (Name {namespace = "GObject", name = "Object"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- callback_data : TBasicType TPtr
    IO (Ptr Task)

-- | Creates a t'GI.Gio.Objects.Task.Task' acting on /@sourceObject@/, which will eventually be
-- used to invoke /@callback@/ in the current
-- [thread-default main context][g-main-context-push-thread-default].
-- 
-- Call this in the \"start\" method of your asynchronous method, and
-- pass the t'GI.Gio.Objects.Task.Task' around throughout the asynchronous operation. You
-- can use 'GI.Gio.Objects.Task.taskSetTaskData' to attach task-specific data to the
-- object, which you can retrieve later via 'GI.Gio.Objects.Task.taskGetTaskData'.
-- 
-- By default, if /@cancellable@/ is cancelled, then the return value of
-- the task will always be 'GI.Gio.Enums.IOErrorEnumCancelled', even if the task had
-- already completed before the cancellation. This allows for
-- simplified handling in cases where cancellation may imply that
-- other objects that the task depends on have been destroyed. If you
-- do not want this behavior, you can use
-- 'GI.Gio.Objects.Task.taskSetCheckCancellable' to change it.
-- 
-- /Since: 2.36/
taskNew ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a, Gio.Cancellable.IsCancellable b) =>
    Maybe (a)
    -- ^ /@sourceObject@/: the t'GI.GObject.Objects.Object.Object' that owns
    --   this task, or 'P.Nothing'.
    -> Maybe (b)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback'.
    -> m Task
    -- ^ __Returns:__ a t'GI.Gio.Objects.Task.Task'.
taskNew :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsObject a, IsCancellable b) =>
Maybe a -> Maybe b -> Maybe AsyncReadyCallback -> m Task
taskNew Maybe a
sourceObject Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO Task -> m Task
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Task -> m Task) -> IO Task -> m Task
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
maybeSourceObject <- case Maybe a
sourceObject of
        Maybe a
Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
        Just a
jSourceObject -> do
            Ptr Object
jSourceObject' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jSourceObject
            Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jSourceObject'
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let callbackData :: Ptr a
callbackData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Task
result <- Ptr Object
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO (Ptr Task)
g_task_new Ptr Object
maybeSourceObject Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
callbackData
    Text -> Ptr Task -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"taskNew" Ptr Task
result
    Task
result' <- ((ManagedPtr Task -> Task) -> Ptr Task -> IO Task
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Task -> Task
Task) Ptr Task
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
sourceObject a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Task -> IO Task
forall (m :: * -> *) a. Monad m => a -> m a
return Task
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "g_task_get_cancellable" g_task_get_cancellable :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO (Ptr Gio.Cancellable.Cancellable)

-- | Gets /@task@/\'s t'GI.Gio.Objects.Cancellable.Cancellable'
-- 
-- /Since: 2.36/
taskGetCancellable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m Gio.Cancellable.Cancellable
    -- ^ __Returns:__ /@task@/\'s t'GI.Gio.Objects.Cancellable.Cancellable'
taskGetCancellable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Cancellable
taskGetCancellable a
task = IO Cancellable -> m Cancellable
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Cancellable -> m Cancellable)
-> IO Cancellable -> m Cancellable
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr Cancellable
result <- Ptr Task -> IO (Ptr Cancellable)
g_task_get_cancellable Ptr Task
task'
    Text -> Ptr Cancellable -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"taskGetCancellable" Ptr Cancellable
result
    Cancellable
result' <- ((ManagedPtr Cancellable -> Cancellable)
-> Ptr Cancellable -> IO Cancellable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Cancellable -> Cancellable
Gio.Cancellable.Cancellable) Ptr Cancellable
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Cancellable -> IO Cancellable
forall (m :: * -> *) a. Monad m => a -> m a
return Cancellable
result'

#if defined(ENABLE_OVERLOADING)
data TaskGetCancellableMethodInfo
instance (signature ~ (m Gio.Cancellable.Cancellable), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetCancellableMethodInfo a signature where
    overloadedMethod = taskGetCancellable

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


#endif

-- method Task::get_check_cancellable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTask" , 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_task_get_check_cancellable" g_task_get_check_cancellable :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO CInt

-- | Gets /@task@/\'s check-cancellable flag. See
-- 'GI.Gio.Objects.Task.taskSetCheckCancellable' for more details.
-- 
-- /Since: 2.36/
taskGetCheckCancellable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: the t'GI.Gio.Objects.Task.Task'
    -> m Bool
taskGetCheckCancellable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Bool
taskGetCheckCancellable a
task = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    CInt
result <- Ptr Task -> IO CInt
g_task_get_check_cancellable Ptr Task
task'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TaskGetCheckCancellableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetCheckCancellableMethodInfo a signature where
    overloadedMethod = taskGetCheckCancellable

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


#endif

-- method Task::get_completed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask." , 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_task_get_completed" g_task_get_completed :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO CInt

-- | Gets the value of [Task:completed]("GI.Gio.Objects.Task#g:attr:completed"). This changes from 'P.False' to 'P.True' after
-- the task’s callback is invoked, and will return 'P.False' if called from inside
-- the callback.
-- 
-- /Since: 2.44/
taskGetCompleted ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the task has completed, 'P.False' otherwise.
taskGetCompleted :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Bool
taskGetCompleted a
task = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    CInt
result <- Ptr Task -> IO CInt
g_task_get_completed Ptr Task
task'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TaskGetCompletedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetCompletedMethodInfo a signature where
    overloadedMethod = taskGetCompleted

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


#endif

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

foreign import ccall "g_task_get_context" g_task_get_context :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO (Ptr GLib.MainContext.MainContext)

-- | Gets the t'GI.GLib.Structs.MainContext.MainContext' that /@task@/ will return its result in (that
-- is, the context that was the
-- [thread-default main context][g-main-context-push-thread-default]
-- at the point when /@task@/ was created).
-- 
-- This will always return a non-'P.Nothing' value, even if the task\'s
-- context is the default t'GI.GLib.Structs.MainContext.MainContext'.
-- 
-- /Since: 2.36/
taskGetContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m GLib.MainContext.MainContext
    -- ^ __Returns:__ /@task@/\'s t'GI.GLib.Structs.MainContext.MainContext'
taskGetContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m MainContext
taskGetContext a
task = IO MainContext -> m MainContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MainContext -> m MainContext)
-> IO MainContext -> m MainContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr MainContext
result <- Ptr Task -> IO (Ptr MainContext)
g_task_get_context Ptr Task
task'
    Text -> Ptr MainContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"taskGetContext" Ptr MainContext
result
    MainContext
result' <- ((ManagedPtr MainContext -> MainContext)
-> Ptr MainContext -> IO MainContext
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr MainContext -> MainContext
GLib.MainContext.MainContext) Ptr MainContext
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    MainContext -> IO MainContext
forall (m :: * -> *) a. Monad m => a -> m a
return MainContext
result'

#if defined(ENABLE_OVERLOADING)
data TaskGetContextMethodInfo
instance (signature ~ (m GLib.MainContext.MainContext), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetContextMethodInfo a signature where
    overloadedMethod = taskGetContext

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


#endif

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

foreign import ccall "g_task_get_name" g_task_get_name :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO CString

-- | Gets /@task@/’s name. See 'GI.Gio.Objects.Task.taskSetName'.
-- 
-- /Since: 2.60/
taskGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ /@task@/’s name, or 'P.Nothing'
taskGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m (Maybe Text)
taskGetName a
task = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    CString
result <- Ptr Task -> IO CString
g_task_get_name Ptr Task
task'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

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


#endif

-- method Task::get_priority
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , 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_task_get_priority" g_task_get_priority :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO Int32

-- | Gets /@task@/\'s priority
-- 
-- /Since: 2.36/
taskGetPriority ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m Int32
    -- ^ __Returns:__ /@task@/\'s priority
taskGetPriority :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Int32
taskGetPriority a
task = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Int32
result <- Ptr Task -> IO Int32
g_task_get_priority Ptr Task
task'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data TaskGetPriorityMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetPriorityMethodInfo a signature where
    overloadedMethod = taskGetPriority

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


#endif

-- method Task::get_return_on_cancel
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTask" , 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_task_get_return_on_cancel" g_task_get_return_on_cancel :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO CInt

-- | Gets /@task@/\'s return-on-cancel flag. See
-- 'GI.Gio.Objects.Task.taskSetReturnOnCancel' for more details.
-- 
-- /Since: 2.36/
taskGetReturnOnCancel ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: the t'GI.Gio.Objects.Task.Task'
    -> m Bool
taskGetReturnOnCancel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Bool
taskGetReturnOnCancel a
task = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    CInt
result <- Ptr Task -> IO CInt
g_task_get_return_on_cancel Ptr Task
task'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TaskGetReturnOnCancelMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetReturnOnCancelMethodInfo a signature where
    overloadedMethod = taskGetReturnOnCancel

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


#endif

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

foreign import ccall "g_task_get_source_object" g_task_get_source_object :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO (Ptr GObject.Object.Object)

-- | Gets the source object from /@task@/. Like
-- 'GI.Gio.Interfaces.AsyncResult.asyncResultGetSourceObject', but does not ref the object.
-- 
-- /Since: 2.36/
taskGetSourceObject ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m (Maybe GObject.Object.Object)
    -- ^ __Returns:__ /@task@/\'s source object, or 'P.Nothing'
taskGetSourceObject :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m (Maybe Object)
taskGetSourceObject a
task = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr Object
result <- Ptr Task -> IO (Ptr Object)
g_task_get_source_object Ptr Task
task'
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \Ptr Object
result' -> do
        Object
result'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result'
        Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

#if defined(ENABLE_OVERLOADING)
data TaskGetSourceObjectMethodInfo
instance (signature ~ (m (Maybe GObject.Object.Object)), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetSourceObjectMethodInfo a signature where
    overloadedMethod = taskGetSourceObject

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


#endif

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

foreign import ccall "g_task_get_source_tag" g_task_get_source_tag :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO (Ptr ())

-- | Gets /@task@/\'s source tag. See 'GI.Gio.Objects.Task.taskSetSourceTag'.
-- 
-- /Since: 2.36/
taskGetSourceTag ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m (Ptr ())
    -- ^ __Returns:__ /@task@/\'s source tag
taskGetSourceTag :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m (Ptr ())
taskGetSourceTag a
task = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr ()
result <- Ptr Task -> IO (Ptr ())
g_task_get_source_tag Ptr Task
task'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data TaskGetSourceTagMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetSourceTagMethodInfo a signature where
    overloadedMethod = taskGetSourceTag

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


#endif

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

foreign import ccall "g_task_get_task_data" g_task_get_task_data :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO (Ptr ())

-- | Gets /@task@/\'s @task_data@.
-- 
-- /Since: 2.36/
taskGetTaskData ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m (Ptr ())
    -- ^ __Returns:__ /@task@/\'s @task_data@.
taskGetTaskData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m (Ptr ())
taskGetTaskData a
task = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr ()
result <- Ptr Task -> IO (Ptr ())
g_task_get_task_data Ptr Task
task'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data TaskGetTaskDataMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsTask a) => O.OverloadedMethod TaskGetTaskDataMethodInfo a signature where
    overloadedMethod = taskGetTaskData

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


#endif

-- method Task::had_error
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask." , 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_task_had_error" g_task_had_error :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO CInt

-- | Tests if /@task@/ resulted in an error.
-- 
-- /Since: 2.36/
taskHadError ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the task resulted in an error, 'P.False' otherwise.
taskHadError :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Bool
taskHadError a
task = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    CInt
result <- Ptr Task -> IO CInt
g_task_had_error Ptr Task
task'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TaskHadErrorMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTask a) => O.OverloadedMethod TaskHadErrorMethodInfo a signature where
    overloadedMethod = taskHadError

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


#endif

-- method Task::propagate_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask." , 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_task_propagate_boolean" g_task_propagate_boolean :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Gets the result of /@task@/ as a t'P.Bool'.
-- 
-- If the task resulted in an error, or was cancelled, then this will
-- instead return 'P.False' and set /@error@/.
-- 
-- Since this method transfers ownership of the return value (or
-- error) to the caller, you may only call it once.
-- 
-- /Since: 2.36/
taskPropagateBoolean ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
taskPropagateBoolean :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m ()
taskPropagateBoolean a
task = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    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 Task -> Ptr (Ptr GError) -> IO CInt
g_task_propagate_boolean Ptr Task
task'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data TaskPropagateBooleanMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskPropagateBooleanMethodInfo a signature where
    overloadedMethod = taskPropagateBoolean

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


#endif

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

foreign import ccall "g_task_propagate_int" g_task_propagate_int :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr (Ptr GError) ->                     -- error
    IO Int64

-- | Gets the result of /@task@/ as an integer (@/gssize/@).
-- 
-- If the task resulted in an error, or was cancelled, then this will
-- instead return -1 and set /@error@/.
-- 
-- Since this method transfers ownership of the return value (or
-- error) to the caller, you may only call it once.
-- 
-- /Since: 2.36/
taskPropagateInt ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'.
    -> m Int64
    -- ^ __Returns:__ the task result, or -1 on error /(Can throw 'Data.GI.Base.GError.GError')/
taskPropagateInt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Int64
taskPropagateInt a
task = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
        Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Task -> Ptr (Ptr GError) -> IO Int64
g_task_propagate_int Ptr Task
task'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
        Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data TaskPropagateIntMethodInfo
instance (signature ~ (m Int64), MonadIO m, IsTask a) => O.OverloadedMethod TaskPropagateIntMethodInfo a signature where
    overloadedMethod = taskPropagateInt

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


#endif

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

foreign import ccall "g_task_propagate_pointer" g_task_propagate_pointer :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr ())

-- | Gets the result of /@task@/ as a pointer, and transfers ownership
-- of that value to the caller.
-- 
-- If the task resulted in an error, or was cancelled, then this will
-- instead return 'P.Nothing' and set /@error@/.
-- 
-- Since this method transfers ownership of the return value (or
-- error) to the caller, you may only call it once.
-- 
-- /Since: 2.36/
taskPropagatePointer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m (Ptr ())
    -- ^ __Returns:__ the task result, or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
taskPropagatePointer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m (Ptr ())
taskPropagatePointer a
task = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    IO (Ptr ()) -> IO () -> IO (Ptr ())
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr ()
result <- (Ptr (Ptr GError) -> IO (Ptr ())) -> IO (Ptr ())
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr (Ptr GError) -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Ptr Task -> Ptr (Ptr GError) -> IO (Ptr ())
g_task_propagate_pointer Ptr Task
task'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
        Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data TaskPropagatePointerMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m, IsTask a) => O.OverloadedMethod TaskPropagatePointerMethodInfo a signature where
    overloadedMethod = taskPropagatePointer

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


#endif

-- method Task::propagate_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the #GValue"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_task_propagate_value" g_task_propagate_value :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr GValue ->                           -- value : TGValue
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Gets the result of /@task@/ as a t'GI.GObject.Structs.Value.Value', and transfers ownership of
-- that value to the caller. As with 'GI.Gio.Objects.Task.taskReturnValue', this is
-- a generic low-level method; 'GI.Gio.Objects.Task.taskPropagatePointer' and the like
-- will usually be more useful for C code.
-- 
-- If the task resulted in an error, or was cancelled, then this will
-- instead set /@error@/ and return 'P.False'.
-- 
-- Since this method transfers ownership of the return value (or
-- error) to the caller, you may only call it once.
-- 
-- /Since: 2.64/
taskPropagateValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m (GValue)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
taskPropagateValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m GValue
taskPropagateValue a
task = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
    Ptr Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
24 :: IO (Ptr GValue)
    IO GValue -> IO () -> IO GValue
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 Task -> Ptr GValue -> Ptr (Ptr GError) -> IO CInt
g_task_propagate_value Ptr Task
task' Ptr GValue
value
        GValue
value' <- Ptr GValue -> IO GValue
B.GValue.wrapGValuePtr Ptr GValue
value
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
        GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'
     ) (do
        Ptr GValue -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr GValue
value
     )

#if defined(ENABLE_OVERLOADING)
data TaskPropagateValueMethodInfo
instance (signature ~ (m (GValue)), MonadIO m, IsTask a) => O.OverloadedMethod TaskPropagateValueMethodInfo a signature where
    overloadedMethod = taskPropagateValue

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


#endif

-- method Task::return_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #gboolean result of a task function."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_return_boolean" g_task_return_boolean :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    CInt ->                                 -- result : TBasicType TBoolean
    IO ()

-- | Sets /@task@/\'s result to /@result@/ and completes the task (see
-- 'GI.Gio.Objects.Task.taskReturnPointer' for more discussion of exactly what this
-- means).
-- 
-- /Since: 2.36/
taskReturnBoolean ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'.
    -> Bool
    -- ^ /@result@/: the t'P.Bool' result of a task function.
    -> m ()
taskReturnBoolean :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Bool -> m ()
taskReturnBoolean a
task Bool
result_ = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    let result_' :: CInt
result_' = (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
result_
    Ptr Task -> CInt -> IO ()
g_task_return_boolean Ptr Task
task' CInt
result_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskReturnBooleanMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskReturnBooleanMethodInfo a signature where
    overloadedMethod = taskReturnBoolean

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


#endif

-- method Task::return_error
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "error"
--           , argType = TError
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GError result of a task function."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_return_error" g_task_return_error :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr GError ->                           -- error : TError
    IO ()

-- | Sets /@task@/\'s result to /@error@/ (which /@task@/ assumes ownership of)
-- and completes the task (see 'GI.Gio.Objects.Task.taskReturnPointer' for more
-- discussion of exactly what this means).
-- 
-- Note that since the task takes ownership of /@error@/, and since the
-- task may be completed before returning from 'GI.Gio.Objects.Task.taskReturnError',
-- you cannot assume that /@error@/ is still valid after calling this.
-- Call 'GI.GLib.Structs.Error.errorCopy' on the error if you need to keep a local copy
-- as well.
-- 
-- See also @/g_task_return_new_error()/@.
-- 
-- /Since: 2.36/
taskReturnError ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'.
    -> GError
    -- ^ /@error@/: the t'GError' result of a task function.
    -> m ()
taskReturnError :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> GError -> m ()
taskReturnError a
task GError
error_ = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr GError
error_' <- GError -> IO (Ptr GError)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed GError
error_
    Ptr Task -> Ptr GError -> IO ()
g_task_return_error Ptr Task
task' Ptr GError
error_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    GError -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GError
error_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskReturnErrorMethodInfo
instance (signature ~ (GError -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskReturnErrorMethodInfo a signature where
    overloadedMethod = taskReturnError

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


#endif

-- method Task::return_error_if_cancelled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , 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_task_return_error_if_cancelled" g_task_return_error_if_cancelled :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    IO CInt

-- | Checks if /@task@/\'s t'GI.Gio.Objects.Cancellable.Cancellable' has been cancelled, and if so, sets
-- /@task@/\'s error accordingly and completes the task (see
-- 'GI.Gio.Objects.Task.taskReturnPointer' for more discussion of exactly what this
-- means).
-- 
-- /Since: 2.36/
taskReturnErrorIfCancelled ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@task@/ has been cancelled, 'P.False' if not
taskReturnErrorIfCancelled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> m Bool
taskReturnErrorIfCancelled a
task = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    CInt
result <- Ptr Task -> IO CInt
g_task_return_error_if_cancelled Ptr Task
task'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TaskReturnErrorIfCancelledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTask a) => O.OverloadedMethod TaskReturnErrorIfCancelledMethodInfo a signature where
    overloadedMethod = taskReturnErrorIfCancelled

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


#endif

-- method Task::return_int
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the integer (#gssize) result of a task function."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_return_int" g_task_return_int :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Int64 ->                                -- result : TBasicType TInt64
    IO ()

-- | Sets /@task@/\'s result to /@result@/ and completes the task (see
-- 'GI.Gio.Objects.Task.taskReturnPointer' for more discussion of exactly what this
-- means).
-- 
-- /Since: 2.36/
taskReturnInt ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'.
    -> Int64
    -- ^ /@result@/: the integer (@/gssize/@) result of a task function.
    -> m ()
taskReturnInt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Int64 -> m ()
taskReturnInt a
task Int64
result_ = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr Task -> Int64 -> IO ()
g_task_return_int Ptr Task
task' Int64
result_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskReturnIntMethodInfo
instance (signature ~ (Int64 -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskReturnIntMethodInfo a signature where
    overloadedMethod = taskReturnInt

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


#endif

-- method Task::return_pointer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the pointer result of a task\n    function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "result_destroy"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDestroyNotify function."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_return_pointer" g_task_return_pointer :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr () ->                               -- result : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- result_destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Sets /@task@/\'s result to /@result@/ and completes the task. If /@result@/
-- is not 'P.Nothing', then /@resultDestroy@/ will be used to free /@result@/ if
-- the caller does not take ownership of it with
-- 'GI.Gio.Objects.Task.taskPropagatePointer'.
-- 
-- \"Completes the task\" means that for an ordinary asynchronous task
-- it will either invoke the task\'s callback, or else queue that
-- callback to be invoked in the proper t'GI.GLib.Structs.MainContext.MainContext', or in the next
-- iteration of the current t'GI.GLib.Structs.MainContext.MainContext'. For a task run via
-- 'GI.Gio.Objects.Task.taskRunInThread' or 'GI.Gio.Objects.Task.taskRunInThreadSync', calling this
-- method will save /@result@/ to be returned to the caller later, but
-- the task will not actually be completed until the t'GI.Gio.Callbacks.TaskThreadFunc'
-- exits.
-- 
-- Note that since the task may be completed before returning from
-- 'GI.Gio.Objects.Task.taskReturnPointer', you cannot assume that /@result@/ is still
-- valid after calling this, unless you are still holding another
-- reference on it.
-- 
-- /Since: 2.36/
taskReturnPointer ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> Ptr ()
    -- ^ /@result@/: the pointer result of a task
    --     function
    -> Maybe (GLib.Callbacks.DestroyNotify)
    -- ^ /@resultDestroy@/: a t'GI.GLib.Callbacks.DestroyNotify' function.
    -> m ()
taskReturnPointer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Ptr () -> Maybe DestroyNotify -> m ()
taskReturnPointer a
task Ptr ()
result_ Maybe DestroyNotify
resultDestroy = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    FunPtr DestroyNotify
maybeResultDestroy <- case Maybe DestroyNotify
resultDestroy of
        Maybe DestroyNotify
Nothing -> FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr DestroyNotify
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just DestroyNotify
jResultDestroy -> do
            Ptr (FunPtr DestroyNotify)
ptrresultDestroy <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
            FunPtr DestroyNotify
jResultDestroy' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptrresultDestroy) DestroyNotify
jResultDestroy)
            Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptrresultDestroy FunPtr DestroyNotify
jResultDestroy'
            FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr DestroyNotify
jResultDestroy'
    Ptr Task -> Ptr () -> FunPtr DestroyNotify -> IO ()
g_task_return_pointer Ptr Task
task' Ptr ()
result_ FunPtr DestroyNotify
maybeResultDestroy
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskReturnPointerMethodInfo
instance (signature ~ (Ptr () -> Maybe (GLib.Callbacks.DestroyNotify) -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskReturnPointerMethodInfo a signature where
    overloadedMethod = taskReturnPointer

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


#endif

-- method Task::return_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #GValue result of\n                                     a task function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_return_value" g_task_return_value :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr GValue ->                           -- result : TGValue
    IO ()

-- | Sets /@task@/\'s result to /@result@/ (by copying it) and completes the task.
-- 
-- If /@result@/ is 'P.Nothing' then a t'GI.GObject.Structs.Value.Value' of type @/G_TYPE_POINTER/@
-- with a value of 'P.Nothing' will be used for the result.
-- 
-- This is a very generic low-level method intended primarily for use
-- by language bindings; for C code, 'GI.Gio.Objects.Task.taskReturnPointer' and the
-- like will normally be much easier to use.
-- 
-- /Since: 2.64/
taskReturnValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> Maybe (GValue)
    -- ^ /@result@/: the t'GI.GObject.Structs.Value.Value' result of
    --                                      a task function
    -> m ()
taskReturnValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Maybe GValue -> m ()
taskReturnValue a
task Maybe GValue
result_ = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr GValue
maybeResult_ <- case Maybe GValue
result_ of
        Maybe GValue
Nothing -> Ptr GValue -> IO (Ptr GValue)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GValue
forall a. Ptr a
nullPtr
        Just GValue
jResult_ -> do
            Ptr GValue
jResult_' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
jResult_
            Ptr GValue -> IO (Ptr GValue)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GValue
jResult_'
    Ptr Task -> Ptr GValue -> IO ()
g_task_return_value Ptr Task
task' Ptr GValue
maybeResult_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Maybe GValue -> (GValue -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GValue
result_ GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskReturnValueMethodInfo
instance (signature ~ (Maybe (GValue) -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskReturnValueMethodInfo a signature where
    overloadedMethod = taskReturnValue

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


#endif

-- method Task::run_in_thread
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "task_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TaskThreadFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTaskThreadFunc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_run_in_thread" g_task_run_in_thread :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    FunPtr Gio.Callbacks.C_TaskThreadFunc -> -- task_func : TInterface (Name {namespace = "Gio", name = "TaskThreadFunc"})
    IO ()

-- | Runs /@taskFunc@/ in another thread. When /@taskFunc@/ returns, /@task@/\'s
-- t'GI.Gio.Callbacks.AsyncReadyCallback' will be invoked in /@task@/\'s t'GI.GLib.Structs.MainContext.MainContext'.
-- 
-- This takes a ref on /@task@/ until the task completes.
-- 
-- See t'GI.Gio.Callbacks.TaskThreadFunc' for more details about how /@taskFunc@/ is handled.
-- 
-- Although GLib currently rate-limits the tasks queued via
-- 'GI.Gio.Objects.Task.taskRunInThread', you should not assume that it will always
-- do this. If you have a very large number of tasks to run (several tens of
-- tasks), but don\'t want them to all run at once, you should only queue a
-- limited number of them (around ten) at a time.
-- 
-- /Since: 2.36/
taskRunInThread ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> Gio.Callbacks.TaskThreadFunc
    -- ^ /@taskFunc@/: a t'GI.Gio.Callbacks.TaskThreadFunc'
    -> m ()
taskRunInThread :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> TaskThreadFunc -> m ()
taskRunInThread a
task TaskThreadFunc
taskFunc = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr (FunPtr C_TaskThreadFunc)
ptrtaskFunc <- IO (Ptr (FunPtr C_TaskThreadFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_TaskThreadFunc))
    FunPtr C_TaskThreadFunc
taskFunc' <- C_TaskThreadFunc -> IO (FunPtr C_TaskThreadFunc)
Gio.Callbacks.mk_TaskThreadFunc (Maybe (Ptr (FunPtr C_TaskThreadFunc))
-> TaskThreadFunc -> C_TaskThreadFunc
Gio.Callbacks.wrap_TaskThreadFunc (Ptr (FunPtr C_TaskThreadFunc)
-> Maybe (Ptr (FunPtr C_TaskThreadFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_TaskThreadFunc)
ptrtaskFunc) TaskThreadFunc
taskFunc)
    Ptr (FunPtr C_TaskThreadFunc) -> FunPtr C_TaskThreadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_TaskThreadFunc)
ptrtaskFunc FunPtr C_TaskThreadFunc
taskFunc'
    Ptr Task -> FunPtr C_TaskThreadFunc -> IO ()
g_task_run_in_thread Ptr Task
task' FunPtr C_TaskThreadFunc
taskFunc'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskRunInThreadMethodInfo
instance (signature ~ (Gio.Callbacks.TaskThreadFunc -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskRunInThreadMethodInfo a signature where
    overloadedMethod = taskRunInThread

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


#endif

-- method Task::run_in_thread_sync
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "task_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "TaskThreadFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTaskThreadFunc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_run_in_thread_sync" g_task_run_in_thread_sync :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    FunPtr Gio.Callbacks.C_TaskThreadFunc -> -- task_func : TInterface (Name {namespace = "Gio", name = "TaskThreadFunc"})
    IO ()

-- | Runs /@taskFunc@/ in another thread, and waits for it to return or be
-- cancelled. You can use 'GI.Gio.Objects.Task.taskPropagatePointer', etc, afterward
-- to get the result of /@taskFunc@/.
-- 
-- See t'GI.Gio.Callbacks.TaskThreadFunc' for more details about how /@taskFunc@/ is handled.
-- 
-- Normally this is used with tasks created with a 'P.Nothing'
-- @callback@, but note that even if the task does
-- have a callback, it will not be invoked when /@taskFunc@/ returns.
-- [Task:completed]("GI.Gio.Objects.Task#g:attr:completed") will be set to 'P.True' just before this function returns.
-- 
-- Although GLib currently rate-limits the tasks queued via
-- 'GI.Gio.Objects.Task.taskRunInThreadSync', you should not assume that it will
-- always do this. If you have a very large number of tasks to run,
-- but don\'t want them to all run at once, you should only queue a
-- limited number of them at a time.
-- 
-- /Since: 2.36/
taskRunInThreadSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> Gio.Callbacks.TaskThreadFunc
    -- ^ /@taskFunc@/: a t'GI.Gio.Callbacks.TaskThreadFunc'
    -> m ()
taskRunInThreadSync :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> TaskThreadFunc -> m ()
taskRunInThreadSync a
task TaskThreadFunc
taskFunc = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr (FunPtr C_TaskThreadFunc)
ptrtaskFunc <- IO (Ptr (FunPtr C_TaskThreadFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_TaskThreadFunc))
    FunPtr C_TaskThreadFunc
taskFunc' <- C_TaskThreadFunc -> IO (FunPtr C_TaskThreadFunc)
Gio.Callbacks.mk_TaskThreadFunc (Maybe (Ptr (FunPtr C_TaskThreadFunc))
-> TaskThreadFunc -> C_TaskThreadFunc
Gio.Callbacks.wrap_TaskThreadFunc (Ptr (FunPtr C_TaskThreadFunc)
-> Maybe (Ptr (FunPtr C_TaskThreadFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_TaskThreadFunc)
ptrtaskFunc) TaskThreadFunc
taskFunc)
    Ptr (FunPtr C_TaskThreadFunc) -> FunPtr C_TaskThreadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_TaskThreadFunc)
ptrtaskFunc FunPtr C_TaskThreadFunc
taskFunc'
    Ptr Task -> FunPtr C_TaskThreadFunc -> IO ()
g_task_run_in_thread_sync Ptr Task
task' FunPtr C_TaskThreadFunc
taskFunc'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskRunInThreadSyncMethodInfo
instance (signature ~ (Gio.Callbacks.TaskThreadFunc -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskRunInThreadSyncMethodInfo a signature where
    overloadedMethod = taskRunInThreadSync

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


#endif

-- method Task::set_check_cancellable
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "check_cancellable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether #GTask will check the state of\n  its #GCancellable for you."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_set_check_cancellable" g_task_set_check_cancellable :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    CInt ->                                 -- check_cancellable : TBasicType TBoolean
    IO ()

-- | Sets or clears /@task@/\'s check-cancellable flag. If this is 'P.True'
-- (the default), then 'GI.Gio.Objects.Task.taskPropagatePointer', etc, and
-- 'GI.Gio.Objects.Task.taskHadError' will check the task\'s t'GI.Gio.Objects.Cancellable.Cancellable' first, and
-- if it has been cancelled, then they will consider the task to have
-- returned an \"Operation was cancelled\" error
-- ('GI.Gio.Enums.IOErrorEnumCancelled'), regardless of any other error or return
-- value the task may have had.
-- 
-- If /@checkCancellable@/ is 'P.False', then the t'GI.Gio.Objects.Task.Task' will not check the
-- cancellable itself, and it is up to /@task@/\'s owner to do this (eg,
-- via 'GI.Gio.Objects.Task.taskReturnErrorIfCancelled').
-- 
-- If you are using 'GI.Gio.Objects.Task.taskSetReturnOnCancel' as well, then
-- you must leave check-cancellable set 'P.True'.
-- 
-- /Since: 2.36/
taskSetCheckCancellable ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: the t'GI.Gio.Objects.Task.Task'
    -> Bool
    -- ^ /@checkCancellable@/: whether t'GI.Gio.Objects.Task.Task' will check the state of
    --   its t'GI.Gio.Objects.Cancellable.Cancellable' for you.
    -> m ()
taskSetCheckCancellable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Bool -> m ()
taskSetCheckCancellable a
task Bool
checkCancellable = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    let checkCancellable' :: CInt
checkCancellable' = (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
checkCancellable
    Ptr Task -> CInt -> IO ()
g_task_set_check_cancellable Ptr Task
task' CInt
checkCancellable'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskSetCheckCancellableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskSetCheckCancellableMethodInfo a signature where
    overloadedMethod = taskSetCheckCancellable

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


#endif

-- method Task::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTask" , 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 "a human readable name for the task, or %NULL to unset it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_set_name" g_task_set_name :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Sets /@task@/’s name, used in debugging and profiling. The name defaults to
-- 'P.Nothing'.
-- 
-- The task name should describe in a human readable way what the task does.
-- For example, ‘Open file’ or ‘Connect to network host’. It is used to set the
-- name of the t'GI.GLib.Structs.Source.Source' used for idle completion of the task.
-- 
-- This function may only be called before the /@task@/ is first used in a thread
-- other than the one it was constructed in.
-- 
-- /Since: 2.60/
taskSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: a t'GI.Gio.Objects.Task.Task'
    -> Maybe (T.Text)
    -- ^ /@name@/: a human readable name for the task, or 'P.Nothing' to unset it
    -> m ()
taskSetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Maybe Text -> m ()
taskSetName a
task Maybe 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    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'
    Ptr Task -> CString -> IO ()
g_task_set_name Ptr Task
task' CString
maybeName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method Task::set_priority
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "priority"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the [priority][io-priority] of the request"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_set_priority" g_task_set_priority :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Int32 ->                                -- priority : TBasicType TInt
    IO ()

-- | Sets /@task@/\'s priority. If you do not call this, it will default to
-- 'GI.GLib.Constants.PRIORITY_DEFAULT'.
-- 
-- This will affect the priority of @/GSources/@ created with
-- @/g_task_attach_source()/@ and the scheduling of tasks run in threads,
-- and can also be explicitly retrieved later via
-- 'GI.Gio.Objects.Task.taskGetPriority'.
-- 
-- /Since: 2.36/
taskSetPriority ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: the t'GI.Gio.Objects.Task.Task'
    -> Int32
    -- ^ /@priority@/: the [priority][io-priority] of the request
    -> m ()
taskSetPriority :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Int32 -> m ()
taskSetPriority a
task Int32
priority = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr Task -> Int32 -> IO ()
g_task_set_priority Ptr Task
task' Int32
priority
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskSetPriorityMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskSetPriorityMethodInfo a signature where
    overloadedMethod = taskSetPriority

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


#endif

-- method Task::set_return_on_cancel
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "return_on_cancel"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether the task returns automatically when\n  it is cancelled."
--                 , 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_task_set_return_on_cancel" g_task_set_return_on_cancel :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    CInt ->                                 -- return_on_cancel : TBasicType TBoolean
    IO CInt

-- | Sets or clears /@task@/\'s return-on-cancel flag. This is only
-- meaningful for tasks run via 'GI.Gio.Objects.Task.taskRunInThread' or
-- 'GI.Gio.Objects.Task.taskRunInThreadSync'.
-- 
-- If /@returnOnCancel@/ is 'P.True', then cancelling /@task@/\'s
-- t'GI.Gio.Objects.Cancellable.Cancellable' will immediately cause it to return, as though the
-- task\'s t'GI.Gio.Callbacks.TaskThreadFunc' had called
-- 'GI.Gio.Objects.Task.taskReturnErrorIfCancelled' and then returned.
-- 
-- This allows you to create a cancellable wrapper around an
-- uninterruptible function. The t'GI.Gio.Callbacks.TaskThreadFunc' just needs to be
-- careful that it does not modify any externally-visible state after
-- it has been cancelled. To do that, the thread should call
-- 'GI.Gio.Objects.Task.taskSetReturnOnCancel' again to (atomically) set
-- return-on-cancel 'P.False' before making externally-visible changes;
-- if the task gets cancelled before the return-on-cancel flag could
-- be changed, 'GI.Gio.Objects.Task.taskSetReturnOnCancel' will indicate this by
-- returning 'P.False'.
-- 
-- You can disable and re-enable this flag multiple times if you wish.
-- If the task\'s t'GI.Gio.Objects.Cancellable.Cancellable' is cancelled while return-on-cancel is
-- 'P.False', then calling 'GI.Gio.Objects.Task.taskSetReturnOnCancel' to set it 'P.True'
-- again will cause the task to be cancelled at that point.
-- 
-- If the task\'s t'GI.Gio.Objects.Cancellable.Cancellable' is already cancelled before you call
-- 'GI.Gio.Objects.Task.taskRunInThread'\/'GI.Gio.Objects.Task.taskRunInThreadSync', then the
-- t'GI.Gio.Callbacks.TaskThreadFunc' will still be run (for consistency), but the task
-- will also be completed right away.
-- 
-- /Since: 2.36/
taskSetReturnOnCancel ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: the t'GI.Gio.Objects.Task.Task'
    -> Bool
    -- ^ /@returnOnCancel@/: whether the task returns automatically when
    --   it is cancelled.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@task@/\'s return-on-cancel flag was changed to
    --   match /@returnOnCancel@/. 'P.False' if /@task@/ has already been
    --   cancelled.
taskSetReturnOnCancel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Bool -> m Bool
taskSetReturnOnCancel a
task Bool
returnOnCancel = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    let returnOnCancel' :: CInt
returnOnCancel' = (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
returnOnCancel
    CInt
result <- Ptr Task -> CInt -> IO CInt
g_task_set_return_on_cancel Ptr Task
task' CInt
returnOnCancel'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TaskSetReturnOnCancelMethodInfo
instance (signature ~ (Bool -> m Bool), MonadIO m, IsTask a) => O.OverloadedMethod TaskSetReturnOnCancelMethodInfo a signature where
    overloadedMethod = taskSetReturnOnCancel

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


#endif

-- method Task::set_source_tag
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_tag"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an opaque pointer indicating the source of this task"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_set_source_tag" g_task_set_source_tag :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr () ->                               -- source_tag : TBasicType TPtr
    IO ()

-- | Sets /@task@/\'s source tag. You can use this to tag a task return
-- value with a particular pointer (usually a pointer to the function
-- doing the tagging) and then later check it using
-- 'GI.Gio.Objects.Task.taskGetSourceTag' (or 'GI.Gio.Interfaces.AsyncResult.asyncResultIsTagged') in the
-- task\'s \"finish\" function, to figure out if the response came from a
-- particular place.
-- 
-- /Since: 2.36/
taskSetSourceTag ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: the t'GI.Gio.Objects.Task.Task'
    -> Ptr ()
    -- ^ /@sourceTag@/: an opaque pointer indicating the source of this task
    -> m ()
taskSetSourceTag :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Ptr () -> m ()
taskSetSourceTag a
task Ptr ()
sourceTag = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    Ptr Task -> DestroyNotify
g_task_set_source_tag Ptr Task
task' Ptr ()
sourceTag
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskSetSourceTagMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskSetSourceTagMethodInfo a signature where
    overloadedMethod = taskSetSourceTag

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


#endif

-- method Task::set_task_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "task"
--           , argType = TInterface Name { namespace = "Gio" , name = "Task" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GTask" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "task_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "task-specific data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "task_data_destroy"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GDestroyNotify for @task_data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_set_task_data" g_task_set_task_data :: 
    Ptr Task ->                             -- task : TInterface (Name {namespace = "Gio", name = "Task"})
    Ptr () ->                               -- task_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- task_data_destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO ()

-- | Sets /@task@/\'s task data (freeing the existing task data, if any).
-- 
-- /Since: 2.36/
taskSetTaskData ::
    (B.CallStack.HasCallStack, MonadIO m, IsTask a) =>
    a
    -- ^ /@task@/: the t'GI.Gio.Objects.Task.Task'
    -> Ptr ()
    -- ^ /@taskData@/: task-specific data
    -> Maybe (GLib.Callbacks.DestroyNotify)
    -- ^ /@taskDataDestroy@/: t'GI.GLib.Callbacks.DestroyNotify' for /@taskData@/
    -> m ()
taskSetTaskData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTask a) =>
a -> Ptr () -> Maybe DestroyNotify -> m ()
taskSetTaskData a
task Ptr ()
taskData Maybe DestroyNotify
taskDataDestroy = 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 Task
task' <- a -> IO (Ptr Task)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
task
    FunPtr DestroyNotify
maybeTaskDataDestroy <- case Maybe DestroyNotify
taskDataDestroy of
        Maybe DestroyNotify
Nothing -> FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr DestroyNotify
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just DestroyNotify
jTaskDataDestroy -> do
            Ptr (FunPtr DestroyNotify)
ptrtaskDataDestroy <- IO (Ptr (FunPtr DestroyNotify))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
            FunPtr DestroyNotify
jTaskDataDestroy' <- DestroyNotify -> IO (FunPtr DestroyNotify)
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr DestroyNotify))
-> DestroyNotify -> DestroyNotify
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr DestroyNotify) -> Maybe (Ptr (FunPtr DestroyNotify))
forall a. a -> Maybe a
Just Ptr (FunPtr DestroyNotify)
ptrtaskDataDestroy) DestroyNotify
jTaskDataDestroy)
            Ptr (FunPtr DestroyNotify) -> FunPtr DestroyNotify -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr DestroyNotify)
ptrtaskDataDestroy FunPtr DestroyNotify
jTaskDataDestroy'
            FunPtr DestroyNotify -> IO (FunPtr DestroyNotify)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr DestroyNotify
jTaskDataDestroy'
    Ptr Task -> Ptr () -> FunPtr DestroyNotify -> IO ()
g_task_set_task_data Ptr Task
task' Ptr ()
taskData FunPtr DestroyNotify
maybeTaskDataDestroy
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
task
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TaskSetTaskDataMethodInfo
instance (signature ~ (Ptr () -> Maybe (GLib.Callbacks.DestroyNotify) -> m ()), MonadIO m, IsTask a) => O.OverloadedMethod TaskSetTaskDataMethodInfo a signature where
    overloadedMethod = taskSetTaskData

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


#endif

-- method Task::is_valid
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GAsyncResult" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the source object\n  expected to be associated with the task"
--                 , 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_task_is_valid" g_task_is_valid :: 
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr GObject.Object.Object ->            -- source_object : TInterface (Name {namespace = "GObject", name = "Object"})
    IO CInt

-- | Checks that /@result@/ is a t'GI.Gio.Objects.Task.Task', and that /@sourceObject@/ is its
-- source object (or that /@sourceObject@/ is 'P.Nothing' and /@result@/ has no
-- source object). This can be used in @/g_return_if_fail()/@ checks.
-- 
-- /Since: 2.36/
taskIsValid ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.AsyncResult.IsAsyncResult a, GObject.Object.IsObject b) =>
    a
    -- ^ /@result@/: A t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> Maybe (b)
    -- ^ /@sourceObject@/: the source object
    --   expected to be associated with the task
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@result@/ and /@sourceObject@/ are valid, 'P.False'
    -- if not
taskIsValid :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAsyncResult a, IsObject b) =>
a -> Maybe b -> m Bool
taskIsValid a
result_ Maybe b
sourceObject = 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 AsyncResult
result_' <- a -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
result_
    Ptr Object
maybeSourceObject <- case Maybe b
sourceObject of
        Maybe b
Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
        Just b
jSourceObject -> do
            Ptr Object
jSourceObject' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jSourceObject
            Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jSourceObject'
    CInt
result <- Ptr AsyncResult -> Ptr Object -> IO CInt
g_task_is_valid Ptr AsyncResult
result_' Ptr Object
maybeSourceObject
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
result_
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
sourceObject b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Task::report_error
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "source_object"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GObject that owns\n  this task, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncReadyCallback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data passed to @callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_tag"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an opaque pointer indicating the source of this task"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "error"
--           , argType = TError
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "error to report" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_task_report_error" g_task_report_error :: 
    Ptr GObject.Object.Object ->            -- source_object : TInterface (Name {namespace = "GObject", name = "Object"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- callback_data : TBasicType TPtr
    Ptr () ->                               -- source_tag : TBasicType TPtr
    Ptr GError ->                           -- error : TError
    IO ()

-- | Creates a t'GI.Gio.Objects.Task.Task' and then immediately calls 'GI.Gio.Objects.Task.taskReturnError'
-- on it. Use this in the wrapper function of an asynchronous method
-- when you want to avoid even calling the virtual method. You can
-- then use 'GI.Gio.Interfaces.AsyncResult.asyncResultIsTagged' in the finish method wrapper to
-- check if the result there is tagged as having been created by the
-- wrapper method, and deal with it appropriately if so.
-- 
-- See also @/g_task_report_new_error()/@.
-- 
-- /Since: 2.36/
taskReportError ::
    (B.CallStack.HasCallStack, MonadIO m, GObject.Object.IsObject a) =>
    Maybe (a)
    -- ^ /@sourceObject@/: the t'GI.GObject.Objects.Object.Object' that owns
    --   this task, or 'P.Nothing'.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback'.
    -> Ptr ()
    -- ^ /@sourceTag@/: an opaque pointer indicating the source of this task
    -> GError
    -- ^ /@error@/: error to report
    -> m ()
taskReportError :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
Maybe a -> Maybe AsyncReadyCallback -> Ptr () -> GError -> m ()
taskReportError Maybe a
sourceObject Maybe AsyncReadyCallback
callback Ptr ()
sourceTag GError
error_ = 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 Object
maybeSourceObject <- case Maybe a
sourceObject of
        Maybe a
Nothing -> Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
forall a. Ptr a
nullPtr
        Just a
jSourceObject -> do
            Ptr Object
jSourceObject' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jSourceObject
            Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
jSourceObject'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    Ptr GError
error_' <- GError -> IO (Ptr GError)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed GError
error_
    let callbackData :: Ptr a
callbackData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Object
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> Ptr ()
-> Ptr GError
-> IO ()
g_task_report_error Ptr Object
maybeSourceObject FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
callbackData Ptr ()
sourceTag Ptr GError
error_'
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
sourceObject a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    GError -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GError
error_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif