Safe Haskell | Trustworthy |
---|
This module implements the core of the Labeled IO (LIO) information
flow control (IFC) library. It provides a monad, LIO
, that is
intended to be used as a replacement for the IO
monad in untrusted
code. The idea is for untrusted code to provide a computation in the
LIO
monad, which trusted code can then safely execute through
evalLIO
and similar functions (e.g., evalDC
in
LIO.DCLabel).
Unlike IO
, the LIO
monad keeps track of a current label
(accessible via the getLabel
function) during each computation. The
current label effectively tracks the sensitivity of all the data that
the computation has observed. For example, if the computation has
read a "secret" mutable reference (see LIO.LIORef) and then the
result of a "top-secret" thread (see LIO.Concurrent) then the
current label will be at least "top-secret". Labels are described
in more detail in the documentation for LIO.Label, as well as the
documentation for particular label formats (such as LIO.DCLabel).
The role of the current label is two-fold: First, the current label
protects all pure values currently in scope. For example, the current
label is the label on constants (such as 3
and "tis a string"
)
as well as function arguments. More interestingly, consider reading a
secret reference:
val <- readLIORef secret
Though the label of secret
may be "secret", val
is not
explicitly labeled. Hence, to protect the contents of the LIORef
that has been read into val
, the current label must be at least
"secret" before returning from readLIORef
. More generally, if the
current label is l_cur
, then it is only permissible to read data
labeled l_r
if l_r `
. Note that, instead of
throwing an exception, reading data often just increases the current
label to ensure that canFlowTo
` l_curl_r `
. This is acomplished
using a function such as canFlowTo
` l_curtaint
.
The second purpose of the current label is to prevent inforation leaks
into public channels. Specifically, it is only permissible to modify
or write to data labeled l_w
when l_cur`
. Thus,
the following attempt to leak the canFlowTo
` l_wval
after reading it from a secret
LIORef
would fail:
writeLIORef public val
In addition to the current label, the LIO monad keeps a second label,
the current clearance (accessible via the getClearance
function).
The clearance can be used to enforce a "need-to-know" policy, since
it represents the highest value the current label can be raised to.
In other words, if the current clearance is l_clear
then the
computation cannot create, read or write to objects labeled l
such
that (l `
.
canFlowTo
` l_clear) == False
- data LIO l a
- class (Label l, Monad m) => MonadLIO l m | m -> l where
- data LIOState l = LIOState {
- lioLabel :: !l
- lioClearance :: !l
- evalLIO :: LIO l a -> LIOState l -> IO a
- runLIO :: LIO l a -> LIOState l -> IO (a, LIOState l)
- getLabel :: Label l => LIO l l
- setLabel :: Label l => l -> LIO l ()
- setLabelP :: PrivDesc l p => Priv p -> l -> LIO l ()
- getClearance :: Label l => LIO l l
- setClearance :: Label l => l -> LIO l ()
- setClearanceP :: PrivDesc l p => Priv p -> l -> LIO l ()
- scopeClearance :: Label l => LIO l a -> LIO l a
- withClearance :: Label l => l -> LIO l a -> LIO l a
- withClearanceP :: PrivDesc l p => Priv p -> l -> LIO l a -> LIO l a
- data AnyLabelError = forall e . (Exception e, Annotatable e) => AnyLabelError e
- data LabelError l = LabelError {
- lerrContext :: [String]
- lerrFailure :: String
- lerrCurLabel :: l
- lerrCurClearance :: l
- lerrPrivs :: [GenericPrivDesc l]
- lerrLabels :: [l]
- data InsufficientPrivs = forall p . SpeaksFor p => InsufficientPrivs {
- inspContext :: [String]
- inspFailure :: String
- inspSupplied :: p
- inspNeeded :: p
- guardAlloc :: Label l => l -> LIO l ()
- guardAllocP :: PrivDesc l p => Priv p -> l -> LIO l ()
- taint :: Label l => l -> LIO l ()
- taintP :: PrivDesc l p => Priv p -> l -> LIO l ()
- guardWrite :: Label l => l -> LIO l ()
- guardWriteP :: PrivDesc l p => Priv p -> l -> LIO l ()
LIO monad
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).
Typeable2 LIO | |
Label l => MonadLIO l (LIO l) | |
GuardIO l (IO r) (LIO l r) | |
LabelIO l (IO r) (LIO l r) | |
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) | |
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) | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> LIO l r) | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> LIO l r) | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> LIO l r) | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> a5 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> LIO l r) | |
GuardIO l (a1 -> a2 -> a3 -> a4 -> IO r) (a1 -> a2 -> a3 -> a4 -> LIO l r) | |
GuardIO l (a1 -> a2 -> a3 -> IO r) (a1 -> a2 -> a3 -> LIO l r) | |
GuardIO l (a1 -> a2 -> IO r) (a1 -> a2 -> LIO l r) | |
GuardIO l (a1 -> IO r) (a1 -> LIO l r) | |
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) | |
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) | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> a8 -> LIO l r) | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> a7 -> LIO l r) | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> LIO l r) | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> a5 -> IO r) (a1 -> a2 -> a3 -> a4 -> a5 -> LIO l r) | |
LabelIO l (a1 -> a2 -> a3 -> a4 -> IO r) (a1 -> a2 -> a3 -> a4 -> LIO l r) | |
LabelIO l (a1 -> a2 -> a3 -> IO r) (a1 -> a2 -> a3 -> LIO l r) | |
LabelIO l (a1 -> a2 -> IO r) (a1 -> a2 -> LIO l r) | |
LabelIO l (a1 -> IO r) (a1 -> LIO l r) | |
Monad (LIO l) | |
Functor (LIO l) | |
Applicative (LIO l) |
class (Label l, Monad m) => MonadLIO l m | m -> l whereSource
Synonym for monad in which LIO
is the base monad.
Execute LIO actions
Internal state of an LIO
computation.
LIOState | |
|
evalLIO :: LIO l a -> LIOState l -> IO aSource
Given an LIO
computation and some initial state, return an IO
action which, when executed, will perform the IFC-safe LIO
computation.
Because untrusted code cannot execute IO
computations, this function
should only be useful within trusted code. No harm is done from
exposing the evalLIO
symbol to untrusted code. (In general,
untrusted code is free to produce IO
computations, but it cannot
execute them.)
Unlike runLIO
, this function throws an exception if the
underlying LIO
action terminates with an exception.
Manipulating label state
setLabel :: Label l => l -> LIO l ()Source
Raises the current label to the provided label, which must be
between the current label and clearance. See taint
.
setLabelP :: PrivDesc l p => Priv p -> l -> LIO l ()Source
If the current label is oldLabel
and the current clearance is
clearance
, this function allows code to raise the current label
to any value newLabel
such that
. (Note the privilege
argument affects the label check, not the clearance check; call
canFlowToP
priv oldLabel
newLabel && canFlowTo
newLabel clearancesetClearanceP
first to raise the clearance.)
Manipulating clearance
getClearance :: Label l => LIO l lSource
Returns the thread's current clearance.
setClearance :: Label l => l -> LIO l ()Source
Lowers the current clearance. The new clerance must be between the current label and previous current clerance. One cannot raise the current label or create object with labels higher than the current clearance.
setClearanceP :: PrivDesc l p => Priv p -> l -> LIO l ()Source
Raises the current clearance (undoing the effects of
setClearance
) by exercising privileges. If the current label is
l
and current clearance is c
, then setClearanceP p cnew
succeeds only if the new clearance is can flow to the current
clearance (modulo privileges), i.e.,
. Additionally, the current label must flow to the new
clearance, i.e., canFlowToP
p cnew c ==
Truel `
== True.
canFlowTo
` cnew
Since LIO guards that are used when reading/writing data (e.g.,
guardAllocP
) do not use privileges when comparing labels with the
current clearance, code must always raise the current clearance, to
read/write data above the current clearance.
scopeClearance :: Label l => LIO l a -> LIO l aSource
Runs an LIO
action and re-sets the current clearance to its
previous value once the action returns. In particular, if the
action lowers the current clearance, the clearance will be restored
upon return.
Note that scopeClearance
always restores the clearance. If
that causes the clearance to drop below the current label, a
ClearanceViolation
exception is thrown. That exception can only
be caught outside a second scopeClearance
that restores the
clearance to higher than the current label.
withClearance :: Label l => l -> LIO l a -> LIO l aSource
Temporarily lowers the clearance for a computation, then restores it. Equivalent to:
withClearance c lio =scopeClearance
$setClearance
c >> lio
Note that if the computation inside withClearance
acquires any
Priv
s, it may still be able to raise its clearance above the
supplied argument using setClearanceP
.
withClearanceP :: PrivDesc l p => Priv p -> l -> LIO l a -> LIO l aSource
A variant of withClearance
that takes privileges. Equivalent
to:
withClearanceP p c lio =scopeClearance
$setClearanceP
p c >> lio
Exceptions thrown by LIO
data AnyLabelError Source
Parent of all label-related exceptions.
forall e . (Exception e, Annotatable e) => AnyLabelError e |
data LabelError l Source
Main error type thrown by label failures in the LIO
monad.
LabelError | |
|
Typeable1 LabelError | |
Show l => Show (LabelError l) | |
Label l => Exception (LabelError l) | |
Annotatable (LabelError l) |
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).
forall p . SpeaksFor p => InsufficientPrivs | |
|
Guards
Guards are used by (usually privileged) code to check that the
invoking, unprivileged code has access to particular data. If the
current label is lcurrent
and the current clearance is
ccurrent
, then the following checks should be performed when
accessing data labeled ldata
:
- When reading an object labeled
ldata
, it must be the case thatldata `
. This check is performed by thecanFlowTo
` lcurrenttaint
function, so named because it "taints" the currentLIO
context by raisinglcurrent
untilldata `
. Specifically, it does this by computing the least upper bound orcanFlowTo
` lcurrentlub
of the two labels. (Notetaint
will fail if the new label cannot flow to the current clearance.) - When creating or allocating objects, it is permissible for
them to be higher than the current label, so long as they are
below the current clearance. In other words, it must be the
case that
lcurrent `
. This is ensured by thecanFlowTo
` ldata && ldata `canFlowTo
` ccurrentguardAlloc
function. - When writing an object, it should be the case that
lcurrent `
. (As stated, this is the same as sayingcanFlowTo
` ldata && ldata `canFlowTo
` lcurrentldata == lcurrent
, but the two are different when usingcanFlowToP
instead ofcanFlowTo
.) This is ensured by theguardWrite
function, which does the equivalent oftaint
to ensure the target labelldata
can flow to the current label, then throws an exception iflcurrent
cannot flow back to the target label.
Note that a write always implies a read. Hence, when writing to an
object for which you can observe the result (which is frequently the
case), you must use guardWrite
. However, when performing a write
for which there are no observable side-effects to the writer, i.e.,
you cannot observe the success or failure of the write, then it is
safe to use guardAlloc
.
The taintP
, guardAllocP
, and guardWriteP
functions are variants
of the above that take privilege to be more permissive and raise the
current label less.
Allocate/write-only guards
guardAlloc :: Label l => l -> LIO l ()Source
Ensures the label argument is between the current IO label and
current IO clearance. Use this function in code that allocates
objects--untrusted code shouldn't be able to create an object
labeled l
unless guardAlloc l
does not throw an exception.
Similarly use this guard in any code that writes to an
object labeled l
for which the write has no observable
side-effects.
guardAllocP :: PrivDesc l p => Priv p -> l -> LIO l ()Source
Like guardAlloc
, but takes a privilege argument to be more
permissive. Note: privileges are only used when checking that
the current label can flow to the target label; guardAllocP
still
always throws an exception when the target label is higher than the
current clearance.
Read-only guards
taint :: Label l => l -> LIO l ()Source
Use taint l
in trusted code before observing an object labeled
l
. This will raise the current label to a value l'
such that
l `
, or throw a canFlowTo
` l'LabelError
exception if l'
would have to be higher than the current clearance.
Read-write guards
guardWrite :: Label l => l -> LIO l ()Source
Use guardWrite l
in any (trusted) code before modifying an
object labeled l
, for which the modification can be observed,
i.e., the write implies a read.
The implementation of guardWrite
is straight forward:
guardWrite l = guardAlloc l >> taint l
This guarantees that l
`canFlowTo
` the current label (and
clearance), and that the current label `canFlowTo
` l
.
guardWriteP :: PrivDesc l p => Priv p -> l -> LIO l ()Source
Like guardWrite
, but takes a privilege argument to be more
permissive.