Safe Haskell | Unsafe |
---|---|
Language | Haskell98 |
This module exports symbols that must be accessible only to trusted
code. By convention, the names of such symbols always end
"...TCB
" (short for "trusted computing base"). In many cases, a
type is safe to export while its constructor is not. Hence, only the
constructor ends "TCB
", while the type is re-exported to safe code
(without constructors) from LIO.Core.
Security rests on the fact that untrusted code must be compiled with
-XSafe
. Because this module is flagged unsafe, it cannot be
imported from safe modules.
- data LIOState l = LIOState {
- lioLabel :: !l
- lioClearance :: !l
- newtype LIO l a = LIOTCB (IORef (LIOState l) -> IO a)
- getLIOStateTCB :: LIO l (LIOState l)
- putLIOStateTCB :: LIOState l -> LIO l ()
- modifyLIOStateTCB :: (LIOState l -> LIOState l) -> LIO l ()
- ioTCB :: IO a -> LIO l a
- newtype Priv a = PrivTCB a
- data Labeled l t = LabeledTCB !l t
- class LabelOf t where
- data UncatchableTCB = Exception e => UncatchableTCB e
- makeCatchable :: SomeException -> SomeException
- class ShowTCB a where
- data LabeledResult l a = LabeledResultTCB {
- lresThreadIdTCB :: !ThreadId
- lresLabelTCB :: !l
- lresBlockTCB :: !(MVar ())
- lresStatusTCB :: !(IORef (LResStatus l a))
- data LResStatus l a
- = LResEmpty
- | LResLabelTooHigh !l
- | LResResult a
LIO monad
Internal state of an LIO
computation.
LIOState | |
|
The LIO
monad is a wrapper around IO
that keeps track of a
current label and current clearance. Safe code cannot execute
arbitrary IO
actions from the LIO
monad. However, trusted
runtime functions can use ioTCB
to perform IO
actions (which
they should only do after appropriately checking labels).
Label l => MonadLIO l (LIO l) Source # | |
GuardIO l (IO r) (LIO l r) Source # | |
LabelIO l (IO r) (LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> IO r) (a1 -> a2 -> a3 -> a4 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> a3 -> IO r) (a1 -> a2 -> a3 -> LIO l r) Source # | |
GuardIO l (a1 -> a2 -> IO r) (a1 -> a2 -> LIO l r) Source # | |
GuardIO l (a1 -> IO r) (a1 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> a10 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> a9 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> IO r) (a1 -> a2 -> a3 -> a4 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> a3 -> IO r) (a1 -> a2 -> a3 -> LIO l r) Source # | |
LabelIO l (a1 -> a2 -> IO r) (a1 -> a2 -> LIO l r) Source # | |
LabelIO l (a1 -> IO r) (a1 -> LIO l r) Source # | |
Monad (LIO l) Source # | |
Functor (LIO l) Source # | |
Applicative (LIO l) Source # | |
Accessing internal state
getLIOStateTCB :: LIO l (LIOState l) Source #
Get internal state. This function is not actually unsafe, but to avoid future security bugs we leave all direct access to the internal state to trusted code.
putLIOStateTCB :: LIOState l -> LIO l () Source #
Set internal state.
modifyLIOStateTCB :: (LIOState l -> LIOState l) -> LIO l () Source #
Update the internal state given some function.
Executing IO actions
Privileged constructors
A newtype wrapper that can be used by trusted code to transform a
powerless description of privileges into actual privileges. The
constructor, PrivTCB
, is dangerous as it allows creation of
arbitrary privileges. Hence it is only exported by the unsafe
module LIO.TCB. A safe way to create arbitrary privileges is to
call privInit
(see LIO.Run) from the IO
monad
before running your LIO
computation.
PrivTCB a |
Labeled l a
is a value that associates a label of type l
with
a pure value of type a
. Labeled values allow users to label data
with a label other than the current label. Note that Labeled
is
an instance of LabelOf
, which means that only the contents of a
labeled value (the type t
) is kept secret, not the label. Of
course, if you have a Labeled
within a Labeled
, then the label
on the inner value will be protected by the outer label.
LabeledTCB !l t |
class LabelOf t where Source #
Generic class used to get the type of labeled objects. For, instance, if you wish to associate a label with a pure value (as in LIO.Labeled), you may create a data type:
data LVal l a = LValTCB l a
Then, you may wish to allow untrusted code to read the label of any
LVal
s but not necessarily the actual value. To do so, simply
provide an instance for LabelOf
:
instance LabelOf LVal where labelOf (LValTCB l a) = l
Uncatchable exception type
data UncatchableTCB Source #
An uncatchable exception hierarchy is used to terminate an
untrusted thread. Wrap the uncatchable exception in
UncatchableTCB
before throwing it to the thread. runLIO
will
subsequently unwrap the UncatchableTCB
constructor.
Note this can be circumvented by mapException
, which should be
made unsafe. In the interim, auditing untrusted code for this is
necessary.
Exception e => UncatchableTCB e |
makeCatchable :: SomeException -> SomeException Source #
Simple utility function that strips UncatchableTCB
from around an
exception.
Trusted Show
LabeledResult
s
data LabeledResult l a Source #
A LabeledResult
encapsulates a future result from a computation
spawned by lFork
or lForkP
. See LIO.Concurrent for a
description of the concurrency abstractions of LIO.
LabeledResultTCB | |
|
data LResStatus l a Source #
Status of a LabeledResult
.