| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Data.GI.Base.GError
Contents
Description
To catch GError exceptions use the
 catchGError* or handleGError* functions. They work in a similar
 way to the standard catch and
 handle functions.
To catch just a single specific error use catchGErrorJust /
 handleGErrorJust. To catch any error in a particular error domain
 use catchGErrorJustDomain / handleGErrorJustDomain
For convenience, generated code also includes specialized variants
 of catchGErrorJust / handleGErrorJust for each error type. For
 example, for errors of type PixbufError one could
 invoke catchPixbufError /
 handlePixbufError. The definition is simply
catchPixbufError :: IO a -> (PixbufError -> GErrorMessage -> IO a) -> IO a catchPixbufError = catchGErrorJustDomain
Notice that the type is suitably specialized, so only errors of type PixbufError will be caught.
Synopsis
- newtype GError = GError (ManagedPtr GError)
- gerrorDomain :: GError -> IO GQuark
- gerrorCode :: GError -> IO GErrorCode
- gerrorMessage :: GError -> IO GErrorMessage
- type GErrorDomain = GQuark
- type GErrorCode = Int32
- type GErrorMessage = Text
- catchGErrorJust :: GErrorClass err => err -> IO a -> (GErrorMessage -> IO a) -> IO a
- catchGErrorJustDomain :: forall err a. GErrorClass err => IO a -> (err -> GErrorMessage -> IO a) -> IO a
- handleGErrorJust :: GErrorClass err => err -> (GErrorMessage -> IO a) -> IO a -> IO a
- handleGErrorJustDomain :: GErrorClass err => (err -> GErrorMessage -> IO a) -> IO a -> IO a
- gerrorNew :: GErrorDomain -> GErrorCode -> GErrorMessage -> IO GError
- class Enum err => GErrorClass err where- gerrorClassDomain :: err -> Text
 
- propagateGError :: (Ptr (Ptr GError) -> IO a) -> IO a
- checkGError :: (Ptr (Ptr GError) -> IO a) -> (GError -> IO a) -> IO a
- maybePokeGError :: Ptr (Ptr GError) -> Maybe GError -> IO ()
Unpacking GError
A GError, consisting of a domain, code and a human readable
 message. These can be accessed by gerrorDomain, gerrorCode and
 gerrorMessage below.
Constructors
| GError (ManagedPtr GError) | 
Instances
| Show GError Source # | |
| Exception GError Source # | |
| Defined in Data.GI.Base.GError Methods toException :: GError -> SomeException # fromException :: SomeException -> Maybe GError # displayException :: GError -> String # | |
| BoxedObject GError Source # | |
gerrorDomain :: GError -> IO GQuark Source #
Return the domain for the given GError. This is a GQuark, a
 textual representation can be obtained with
 quarkToString.
gerrorCode :: GError -> IO GErrorCode Source #
The numeric code for the given GError.
gerrorMessage :: GError -> IO GErrorMessage Source #
A text message describing the GError.
type GErrorDomain = GQuark Source #
A code used to identify the "namespace" of the error. Within each error domain all the error codes are defined in an enumeration. Each gtk/gnome module that uses GErrors has its own error domain. The rationale behind using error domains is so that each module can organise its own error codes without having to coordinate on a global error code list.
type GErrorCode = Int32 Source #
A code to identify a specific error within a given GErrorDomain. Most of
   time you will not need to deal with this raw code since there is an
   enumeration type for each error domain. Of course which enumeration to use
   depends on the error domain, but if you use catchGErrorJustDomain or
   handleGErrorJustDomain, this is worked out for you automatically.
type GErrorMessage = Text Source #
A human readable error message.
Catching GError exceptions
Arguments
| :: GErrorClass err | |
| => err | The error to catch | 
| -> IO a | The computation to run | 
| -> (GErrorMessage -> IO a) | Handler to invoke if an exception is raised | 
| -> IO a | 
This will catch just a specific GError exception. If you need to catch a
   range of related errors, catchGErrorJustDomain is probably more
   appropriate. Example:
do image <- catchGErrorJust PixbufErrorCorruptImage
              loadImage
              (\errorMessage -> do log errorMessage
                                   return mssingImagePlaceholder)catchGErrorJustDomain Source #
Arguments
| :: GErrorClass err | |
| => IO a | The computation to run | 
| -> (err -> GErrorMessage -> IO a) | Handler to invoke if an exception is raised | 
| -> IO a | 
Catch all GErrors from a particular error domain. The handler function should just deal with one error enumeration type. If you need to catch errors from more than one error domain, use this function twice with an appropriate handler functions for each.
catchGErrorJustDomain
  loadImage
  (\err message -> case err of
      PixbufErrorCorruptImage -> ...
      PixbufErrorInsufficientMemory -> ...
      PixbufErrorUnknownType -> ...
      _ -> ...)handleGErrorJust :: GErrorClass err => err -> (GErrorMessage -> IO a) -> IO a -> IO a Source #
A verson of handleGErrorJust with the arguments swapped around.
handleGErrorJustDomain :: GErrorClass err => (err -> GErrorMessage -> IO a) -> IO a -> IO a Source #
A verson of catchGErrorJustDomain with the arguments swapped around.
Creating new GErrors
gerrorNew :: GErrorDomain -> GErrorCode -> GErrorMessage -> IO GError Source #
Create a new GError.
Implementation specific details
The following are used in the implementation of the bindings, and are in general not necessary for using the API.
class Enum err => GErrorClass err where Source #
Each error domain's error enumeration type should be an instance of this class. This class helps to hide the raw error and domain codes from the user.
Example for PixbufError:
instance GErrorClass PixbufError where gerrorClassDomain _ = "gdk-pixbuf-error-quark"
Methods