Safe Haskell | Trustworthy |
---|
This module implements the core of the Labeled IO (LIO) library for
information flow control (IFC) in Haskell. 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 using evalLIO
-like functions. Though, usually a
wrapper function is employed depending on the type of labels used by
an application. For example, with LIO.DCLabel trusted code would
evalDC
to execute an untrusted computation.
Labels are a way of describing who can observe and modify data. (A
detailed consideration of labels is given in LIO.Label.) LIO
associates a current label with every LIO
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 refernce (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". The role of the current label is
two-fold. First, the current label protects all the data in scope --
it is the label associated with any unlabeled data. For example, the
current label is the label on constants such as 3
or "tis a
string"
. More interestingly, consider reading a "secret" file:
bs <- readFile "/secret/file.txt"
Though the label in the file store may be "secret", bs
has type
ByteString
, which is not explicitly labeled. Hence, to protect the
contents (bs
) the current label must be at least "secret" before
executing readFile
. 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, rather than throw an exception,
reading data will often just increase the current label to ensure that
canFlowTo
` L_curL_r `
using canFlowTo
` L_curtaint
.
Second, the current label prevents inforation leaks into public
channels. Specifically, it is only permissible to modify, or write
to, data labeled L_w
when L_cur`
. Thus, it the
following attempt to leak the secret canFlowTo
` L_wbs
would fail:
writeFile "/public/file.txt" bs
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 `
does not hold.
canFlowTo
` L_clear
This module exports the LIO
monad, functions to access the internal
state (e.g., getLabel
and getClearance
), functions for raising and
catching exceptions, and IFC guards. Exceptions are core to LIO since
they provide a way to deal with potentially-misbehaving untrusted
code. Specifically, when a computation is about to violate IFC (as
writeFile
above), an exception is raised. Guards provide a useful
abstraction for dealing with labeled objects; they should be used
before performing a read-only, write-only, or read-write operation on
a labeled object. The remaining core, but not all, abstractions are
exported by LIO.
- data LIO l a
- class (Monad m, Label l) => 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 MonitorFailure
- data VMonitorFailure = VMonitorFailure {}
- 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 state monad, with IO
as the underlying monad,
that carries along a current label (lioLabel
) and current clearance
(lioClearance
). The current label imposes restrictions on
what the current computation may read and write (e.g., no writes to
public channels after reading sensitive data). Since the current
label can be raised to be permissive in what a computation observes,
we need a way to prevent certain computations from reading overly
sensitive data. This is the role of the current clearance: it imposes
an upper bound on the current label.
Typeable2 LIO | |
Label l => MonadLIO l (LIO l) | |
GuardIO 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) | |
Monad (LIO l) | |
Functor (LIO l) | |
Applicative (LIO l) |
class (Monad m, Label l) => 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
Raise the current label to the provided label, which must be
between the current label and clearance. See taint
.
Manipulating clearance
getClearance :: Label l => LIO l lSource
Returns the current value of the thread's clearance.
setClearance :: Label l => l -> LIO l ()Source
Lower the current clearance. The new clerance must be between the current label and 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
Raise 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.,
must
hold. Additionally, the current label must flow to the new
clearance, i.e., canFlowToP
p cnew cl `
must hold.
canFlowTo
` cnew
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
Lowers the clearance of a computation, then restores the
clearance to its previous value (actually, to the upper bound of
the current label and previous value). Useful to wrap around a
computation if you want to be sure you can catch exceptions thrown
by it. The supplied clearance label must be bounded by the current
label and clearance as enforced by guardAlloc
.
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
Same as withClearance
, but uses privileges when applying
guardAllocP
to the supplied label.
Exceptions thrown by LIO
Library functions throw an exceptions before an IFC violation can take
place. MonitorFailure
should be used when the reason for failure is
sufficiently described by the type. Otherwise, VMonitorFailure
(i.e., "Verbose"-MonitorFailure
) should be used to further
describe the error.
data MonitorFailure Source
Exceptions thrown when some IFC restriction is about to be violated.
ClearanceViolation | Current label would exceed clearance, or object label is above clearance. |
CurrentLabelViolation | Clearance would be below current label, or object label is not above current label. |
InsufficientPrivs | Insufficient privileges. Thrown when lowering the current label or raising the clearance cannot be accomplished with the supplied privileges. |
CanFlowToViolation | Generic can-flow-to failure, use with
|
ResultExceedsLabel |
data VMonitorFailure Source
Verbose version of MonitorFailure
also carrying around a
detailed message.
VMonitorFailure | |
|
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 leastcanFlowTo
` lcurrentupperBound
of the two labels.) However, this is done only if the newlcurrent `
.canFlowTo
` ccurrent - 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 in this case a write always implies a read. Hence,
when writing to an object for which you can observe the result,
you must use guardWrite
. However, when performing a write for
which there is no observable side-effects to the writer, i.e.,
you cannot observe the success or failure of the write, then it
is safe to solely 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.
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.
If the label does not flow to clearance ClearanceViolation
is
thrown; if the current label does not flow to the argument label
CurrentLabelViolation
is thrown.
guardAllocP :: PrivDesc l p => Priv p -> l -> LIO l ()Source
Like guardAlloc
, but takes privilege argument to be more
permissive. Note: privileges are only used when checking that
the current label can flow to the given label.
Read-only
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 canFlowTo
` l'ClearanceViolation
if l'
would
have to be higher than the current clearance.
Write
guardWrite :: Label l => l -> LIO l ()Source
Use guardWrite l
in any (trusted) code before modifying an
object labeled l
, for which a the modification can be observed,
i.e., the write implies a read.
The implementation of guardWrite
is straight forward:
guardWrite l = taint l >> guardAlloc 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 privilege argument to be more
permissive.