| Safe Haskell | Trustworthy |
|---|
LIO.Error
Description
This module exports exception types thrown in response to label
failures. In addition, it provides withContext, a function that
annotates any exceptions in the AnyLabelError hierarchy that are
thrown within a given scope. These annotations should be used to add
function names to exceptions, so as to make it easier to pinpoint the
cause of a label error.
- class Annotatable e where
- withContext :: String -> LIO l a -> LIO l a
- data AnyLabelError = forall e . (Exception e, Annotatable e) => AnyLabelError e
- lerrToException :: (Exception e, Annotatable e) => e -> SomeException
- lerrFromException :: Exception e => SomeException -> Maybe e
- data GenericPrivDesc l = forall p . PrivDesc l p => GenericPrivDesc p
- data LabelError l = LabelError {
- lerrContext :: [String]
- lerrFailure :: String
- lerrCurLabel :: l
- lerrCurClearance :: l
- lerrPrivs :: [GenericPrivDesc l]
- lerrLabels :: [l]
- labelError :: Label l => String -> [l] -> LIO l a
- labelErrorP :: (Label l, PrivDesc l p) => String -> Priv p -> [l] -> LIO l a
- data InsufficientPrivs = forall p . SpeaksFor p => InsufficientPrivs {
- inspContext :: [String]
- inspFailure :: String
- inspSupplied :: p
- inspNeeded :: p
- insufficientPrivs :: SpeaksFor p => String -> p -> p -> a
- data ResultExceedsLabel l = ResultExceedsLabel {
- relContext :: [String]
- relLocation :: String
- relDeclaredLabel :: l
- relActualLabel :: Maybe l
Documentation
class Annotatable e whereSource
Class of error messages that can be annotated with context.
withContext :: String -> LIO l a -> LIO l aSource
Executes an action with a context string, which will be added to any label exception thrown.
Note: this function wraps an action with a catch, and thus may
incur a small runtime cost (though it is well under 100 ns on
machines we benchmarked).
data AnyLabelError Source
Parent of all label-related exceptions.
Constructors
| forall e . (Exception e, Annotatable e) => AnyLabelError e |
lerrToException :: (Exception e, Annotatable e) => e -> SomeExceptionSource
Definition of toException for children of AnyLabelError in
the exception hierarchy.
lerrFromException :: Exception e => SomeException -> Maybe eSource
Definition of fromException for children of AnyLabelError in
the exception hierarchy.
data GenericPrivDesc l Source
A generic privilege description for recording relevant privileges in exceptions.
Constructors
| forall p . PrivDesc l p => GenericPrivDesc p |
Instances
| Show (GenericPrivDesc l) |
data LabelError l Source
Main error type thrown by label failures in the LIO monad.
Constructors
| LabelError | |
Fields
| |
Instances
| Typeable1 LabelError | |
| Show l => Show (LabelError l) | |
| Label l => Exception (LabelError l) | |
| Annotatable (LabelError l) |
Throw a label-error exception.
Arguments
| :: (Label l, PrivDesc l p) | |
| => String | Function that failed. |
| -> Priv p | Privileges involved. |
| -> [l] | Labels involved. |
| -> LIO l a |
Throw a label-error exception.
data InsufficientPrivs Source
Error indicating insufficient privileges (independent of the
current label). This exception is thrown by delegate, and
should also be thrown by gates that receive insufficient privilege
descriptions (see LIO.Delegate).
Constructors
| forall p . SpeaksFor p => InsufficientPrivs | |
Fields
| |
Arguments
| :: SpeaksFor p | |
| => String | Function in which error occurs |
| -> p | Description of privileges supplied |
| -> p | Description of privileges needed |
| -> a |
Raise InsufficientPrivs error.
data ResultExceedsLabel l Source
Error raised when a computation spawned by lFork terminates
with its current label above the label of the result.
Constructors
| ResultExceedsLabel | |
Fields
| |
Instances
| Typeable1 ResultExceedsLabel | |
| Show l => Show (ResultExceedsLabel l) | |
| Label l => Exception (ResultExceedsLabel l) | |
| Annotatable (ResultExceedsLabel l) |