Win32-errors-0.1: Alternative error handling for Win32 foreign calls

PortabilityWindows
Stabilityexperimental
Maintainermikesteele81@gmail.com
Safe HaskellTrustworthy

System.Win32.Error

Description

This package assumes that you will be using strict Text values for string handling. Consider using the following language pragma and import statements:

 {-# LANGUAGE OverloadedStrings #-}

 module Main where

 import Data.Text (Text)
 import qualified Data.Text as T
 import qualified Data.Text.Foreign as T

This module is intended to be imported qualified.

 import System.Win32.Errors (ErrCode, Win32Exception)
 import qualified System.Win32.Errors as E

See the Win32Exception type's documentation for an instructions on working with functions that may throw exceptions of this type.

Synopsis

Documentation

data Win32Exception Source

Exception type for Win32 errors.

This type will be thrown as an extensible exception when a foreign call out to part of the Win32 indicates that an error has occurred. In most cases you should wrap an IO computation in a call to tryWin32.

The following example uses the custom createFile function described in System.Win32.Error.Foreign:

 eHandle <- do
     h <- E.tryWin32 $ createFile "c:\\missing.txt" gENERIC_READ oPEN_EXISTING
     -- perform other actions
     return h
 case eHandle of
   Right handle -> do
     -- do something with the file handle
   Left w32Err -> do
     case E.errCode w32Err of
       E.InvalidHandle -> do
         -- perform cleanup
       -- handle other error codes.
     T.putStrLn $ E.systemMessage w32Err

Constructors

Win32Exception 

Fields

function :: Text

The foreign action which triggered this exception.

errCode :: ErrCode

The error code

systemMessage :: Text

The standard system message associated with the error code.

tryWin32 :: IO a -> IO (Either Win32Exception a)Source

Actions calling out to Win32 may throw exceptions. Wrapping the action in tryWin32 will catch Win32Exception exceptions, but will allow any other exception type to pass through.

toDWORD :: ErrCode -> DWORDSource

Convert an ErrCode into a DWORD.

fromDWORD :: DWORD -> ErrCodeSource

Convert a DWORD into an ErrCode. Values which don't have a corresponding constructor will end up becoming an Other.

data ErrCode Source

Win32 actions typically return an error code to indicate success or failure. These codes are intended to be globally unique, though there may be some overlap. MSDN documents which errors may be returned by any given action.

The naming of errors follows a convention. An error such as ERROR_SUCCESS becomes Success, ERROR_FILE_NOT_FOUND becomes FileNotFound, and so on. There are thousands of errors, so it would be impractical to add them all. The Other constructor is used to represent error codes which are not handled specifically.

User's of this library are encouraged to submit new error codes. Add new entries to System.Win32.Errors.Mapping. Send your pull requests along with a link to relevent documentation to https://github.com/mikesteele81/Win32-errors.git.

Instances

Eq ErrCode 
Show ErrCode 
Storable ErrCode

Performs marshalling by converting to and from DWORD.