module LIO.Error (
Annotatable(..), withContext
, AnyLabelError(..), lerrToException, lerrFromException
, GenericPrivDesc(..), LabelError(..), labelError, labelErrorP
, InsufficientPrivs(..), insufficientPrivs
, ResultExceedsLabel(..)
) where
import safe qualified Control.Exception as IO
import safe Data.Typeable
import safe LIO.Exception
import safe LIO.Label
import LIO.TCB
class Annotatable e where
annotate :: String -> e -> e
data AnyLabelError = forall e. (Exception e, Annotatable e) =>
AnyLabelError e deriving Typeable
instance Show AnyLabelError where
showsPrec d (AnyLabelError e) = showsPrec d e
instance Annotatable AnyLabelError where
annotate s (AnyLabelError e) = AnyLabelError $ annotate s e
instance Exception AnyLabelError
withContext :: String -> LIO l a -> LIO l a
withContext ctx (LIOTCB act) =
LIOTCB $ \st -> act st `IO.catch` \e ->
IO.throwIO $ annotate ctx (e :: AnyLabelError)
lerrToException :: (Exception e, Annotatable e) => e -> SomeException
lerrToException = toException . AnyLabelError
lerrFromException :: (Exception e) => SomeException -> Maybe e
lerrFromException se = do
AnyLabelError e <- fromException se
cast e
data GenericPrivDesc l = forall p. (PrivDesc l p) => GenericPrivDesc p
instance Show (GenericPrivDesc l) where
showsPrec d (GenericPrivDesc p) = showsPrec d p
data LabelError l = LabelError {
lerrContext :: [String]
, lerrFailure :: String
, lerrCurLabel :: l
, lerrCurClearance :: l
, lerrPrivs :: [GenericPrivDesc l]
, lerrLabels :: [l]
} deriving (Show, Typeable)
instance Annotatable (LabelError l) where
annotate a e = e { lerrContext = a : lerrContext e }
instance Label l => Exception (LabelError l) where
toException = lerrToException
fromException = lerrFromException
labelError :: (Label l) => String
-> [l]
-> LIO l a
labelError fl ls = do
st <- getLIOStateTCB
throwLIO LabelError {
lerrContext = []
, lerrFailure = fl
, lerrCurLabel = lioLabel st
, lerrCurClearance = lioClearance st
, lerrPrivs = []
, lerrLabels = ls
}
labelErrorP :: (Label l, PrivDesc l p) => String
-> Priv p
-> [l]
-> LIO l a
labelErrorP fl p ls = do
st <- getLIOStateTCB
throwLIO LabelError {
lerrContext = []
, lerrFailure = fl
, lerrCurLabel = lioLabel st
, lerrCurClearance = lioClearance st
, lerrPrivs = [GenericPrivDesc $ privDesc p]
, lerrLabels = ls
}
data InsufficientPrivs = forall p. (SpeaksFor p) => InsufficientPrivs {
inspContext :: [String]
, inspFailure :: String
, inspSupplied :: p
, inspNeeded :: p
} deriving (Typeable)
instance Show InsufficientPrivs where
showsPrec _ (InsufficientPrivs c l s n) =
("InsufficientPrivs { inspContext = " ++) . shows c .
(", inspLocation = " ++) . shows l .
(", inspSupplied = " ++) . shows s .
(", inspNeeded = " ++) . shows n .
(" }" ++)
instance Annotatable InsufficientPrivs where
annotate a e = e { inspContext = a : inspContext e }
instance Exception InsufficientPrivs where
toException = lerrToException
fromException = lerrFromException
insufficientPrivs :: (SpeaksFor p) =>
String
-> p
-> p
-> a
insufficientPrivs fl supplied needed
| isPriv supplied = error $ "insufficientPrivs: " ++ show fl ++
" supplied actual privileges instead of description"
| otherwise = IO.throw $ InsufficientPrivs [] fl supplied needed
data ResultExceedsLabel l = ResultExceedsLabel {
relContext :: [String]
, relLocation :: String
, relDeclaredLabel :: l
, relActualLabel :: Maybe l
} deriving (Show, Typeable)
instance Annotatable (ResultExceedsLabel l) where
annotate a e = e { relContext = a : relContext e }
instance (Label l) => Exception (ResultExceedsLabel l) where
toException = lerrToException
fromException = lerrFromException