LIO.TCB
Contents
Description
This module implements the core of the Labeled IO library for
information flow control 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 the evalLIO
function. (Though usually a wrapper
function is employed depending on the type of labels used by an
application. For example, with LIO.DCLabel, you would use
evalDC
to execute an untrusted computation, and with LIO.HiStar
labels, the function is evalHS
. There are also abbreviations for
the LIO
monad type of a particular label--for instance DC
or
HS
.)
A data structure Labeled
(labeled value) protects access to pure
values. Without the appropriate privileges, one cannot produce a
pure value that depends on a secret Labeled
, or conversely produce a
high-integrity Labeled
based on pure data. The function toLabeled
allows one to seal off the results of an LIO computation inside an
Labeled
without tainting the current flow of execution. unlabel
conversely allows one to use the value stored within a Labeled
.
Any code that imports this module is part of the
Trusted Computing Base (TCB) of the system. Hence, untrusted
code must be prevented from importing this module. The exported
symbols ending ...TCB
can be used to violate label protections
even from within pure code or the LIO Monad. A safe subset of
these symbols is exported by the LIO.Base module, which is how
untrusted code should access the core label functionality.
(LIO.Base is also re-exported by LIO.LIO, the main gateway to
this library.)
- data POrdering
- class Eq a => POrd a where
- o2po :: Ordering -> POrdering
- class (POrd a, Show a, Read a, Typeable a) => Label a where
- class (Label l, Monoid p, PrivTCB p) => Priv l p where
- data NoPrivs = NoPrivs
- data Label l => LIO l s a
- getLabel :: Label l => LIO l s l
- setLabelP :: Priv l p => p -> l -> LIO l s ()
- getClearance :: Label l => LIO l s l
- lowerClr :: Label l => l -> LIO l s ()
- lowerClrP :: Priv l p => p -> l -> LIO l s ()
- withClearance :: Label l => l -> LIO l s a -> LIO l s a
- taint :: Label l => l -> LIO l s ()
- taintP :: Priv l p => p -> l -> LIO l s ()
- wguard :: Label l => l -> LIO l s ()
- wguardP :: Priv l p => p -> l -> LIO l s ()
- aguard :: Label l => l -> LIO l s ()
- aguardP :: Priv l p => p -> l -> LIO l s ()
- data Label l => Labeled l t
- label :: Label l => l -> a -> LIO l s (Labeled l a)
- labelP :: Priv l p => p -> l -> a -> LIO l s (Labeled l a)
- unlabel :: Label l => Labeled l a -> LIO l s a
- unlabelP :: Priv l p => p -> Labeled l a -> LIO l s a
- toLabeled :: Label l => l -> LIO l s a -> LIO l s (Labeled l a)
- toLabeledP :: Priv l p => p -> l -> LIO l s a -> LIO l s (Labeled l a)
- discard :: Label l => l -> LIO l s a -> LIO l s ()
- labelOf :: Label l => Labeled l a -> l
- taintLabeled :: Label l => l -> Labeled l a -> LIO l s (Labeled l a)
- data LabelFault
- = LerrLow
- | LerrHigh
- | LerrClearance
- | LerrPriv
- | LerrInval
- class Monad m => MonadCatch m where
- catchP :: (Label l, Exception e, Priv l p) => p -> LIO l s a -> (l -> e -> LIO l s a) -> LIO l s a
- handleP :: (Label l, Exception e, Priv l p) => p -> (l -> e -> LIO l s a) -> LIO l s a -> LIO l s a
- onExceptionP :: Priv l p => p -> LIO l s a -> LIO l s b -> LIO l s a
- bracketP :: Priv l p => p -> LIO l s a -> (a -> LIO l s c) -> (a -> LIO l s b) -> LIO l s b
- evaluate :: Label l => a -> LIO l s a
- evalLIO :: Label l => LIO l s a -> s -> IO (a, l)
- data Label l => LIOstate l s = LIOstate {
- labelState :: s
- lioL :: l
- lioC :: l
- runLIO :: forall l s a. Label l => LIO l s a -> LIOstate l s -> IO (a, LIOstate l s)
- class ShowTCB a where
- class ReadTCB a where
- readsPrecTCB :: Int -> ReadS a
- readTCB :: String -> a
- labelTCB :: Label l => l -> a -> Labeled l a
- class PrivTCB t
- class MintTCB t i where
- mintTCB :: i -> t
- unlabelTCB :: Label l => Labeled l a -> a
- setLabelTCB :: Label l => l -> LIO l s ()
- lowerClrTCB :: Label l => l -> LIO l s ()
- getTCB :: Label l => LIO l s s
- putTCB :: Label l => s -> LIO l s ()
- ioTCB :: Label l => IO a -> LIO l s a
- rtioTCB :: Label l => IO a -> LIO l s a
- rethrowTCB :: Label l => LIO l s a -> LIO l s a
- class MonadCatch m => OnExceptionTCB m where
- onExceptionTCB :: m a -> m b -> m a
- bracketTCB :: m a -> (a -> m c) -> (a -> m b) -> m b
- newstate :: Label l => s -> LIOstate l s
- data Label l => LIOstate l s = LIOstate {
- labelState :: s
- lioL :: l
- lioC :: l
- runLIO :: forall l s a. Label l => LIO l s a -> LIOstate l s -> IO (a, LIOstate l s)
Basic label functions
Labels are a way of describing who can observe and modify data. There
is a partial order, generally pronounced "can flow to" on labels.
In Haskell we write this partial order `leq
` (in the literature it
is usually written as a square less than or equal sign--\sqsubseteq
in TeX).
The idea is that data labeled l1
should affect data labeled l2
only if
l1
`leq
` l2
, (i.e., l1
can flow to l2
). The LIO
monad keeps
track of the current label of the executing code (accessible via the
getLabel
function). Code may attempt to perform various IO or
memory operations on labeled data. Touching data may change the
current label or throw an exception if an operation would violate
can-flow-to restrictions.
If the current label is lcurrent
, then it is only permissible to
read data labeled lr
if lr `
. This is sometimes
termed "no read up" in the literature; however, because the partial
order allows for incomparable labels (i.e., two labels leq
` lcurrentl1
and l2
such that not (l1 `
), a more
appropriate phrasing would be "read only what can flow to your
label". Note that, rather than throw an exception, reading data will
often just increase the current label to ensure that leq
` l2) && not (l2 `leq
` l1)lr `
. The LIO monad keeps a second label, called the clearance
(see leq
`
lcurrentgetClearance
), that represents the highest value the
current thread can raise its label to.
Conversely, it is only permissible to modify data labeled lw
when
lcurrent `
, a property often cited as "no write down",
but more accurately characterized as "write only what you can flow
to". In practice, there are very few IO abstractions in which it is
possible to do a pure write that doesn't also involve observing some
state. For instance, writing to a file handle and not getting an
exception tells you that the handle is not closed. Thus, in practice,
the requirement for modifying data labeled leq
` lwlw
is almost always that
lcurrent == lw
.
Note that higher labels are neither more nor less privileged than
lower ones. Simply, the higher one's label is, the more things one
can read. Conversely, the lower one's label, the more things one can
write. But, because labels are a partial and not a total order,
some data may be completely inaccessible to a particular omputatoin; for
instance, if the current label is lcurrent
, the current clearance is
ccurrent
, and some data is labeled ld
, such that not (lcurrent
`
, then the current thread can
neither read nor write the data, at least without invoking some
privilege.
leq
` ld || ld `leq
` ccurrent)
Privilege comes from a separate class called Priv
, representing the
ability to bypass the protection of certain labels. Essentially,
privilege allows you to behave as if l1 `
even when that is
not the case. The process of making data labeled leq
` l2l1
affect data
labeled l2
when not (l1 `
is called downgrading.
leq
` l2)
The basic method of the Priv
object is leqp
, which performs the
more permissive can-flow-to check in the presence of particular
privileges. Many LIO
operations have variants ending ...P
that
take a privilege argument to act in a more permissive way. All Priv
types are monoids, and so can be combined with mappend
.
How to create Priv
objects is specific to the particular label type
in use. The method used is mintTCB
, but the arguments depend on the
particular label type. (Obviously, the symbol mintTCB
must not be
available to untrusted code.)
class (POrd a, Show a, Read a, Typeable a) => Label a whereSource
Methods
bottom
top
least upper bound (join) of two labels
greatest lower bound (meet) of two labels
class (Label l, Monoid p, PrivTCB p) => Priv l p whereSource
Methods
leqp :: p -> l -> l -> BoolSource
leqp p l1 l2
means that privileges p
are sufficient to
downgrade data from l1
to l2
. Note that
implies leq
l1 l2
for all leq
p l1 l2p
, but for some labels and
privileges, leqp
will hold even where
does not.
leq
Arguments
:: p | Privileges |
-> l | Label from which data must flow |
-> l | Goal label |
-> l | Result |
Roughly speaking, the function
result = lostar p label goal
computes how close one can come to downgrading data labeled
label
to goal
given privileges p
. When p ==
,
NoPrivs
result ==
. If lub
label goalp
contains all possible
privileges, then result == goal
.
More specifically, result
is the greatest lower bound of the
set of all labels r
satisfying:
Operationally, lostar
captures the minimum change required to
the current label when viewing data labeled label
. A common
pattern is to use the result of getLabel
as goal
(i.e.,
the goal is to use privileges p
to avoid changing the label
at all), and then compute result
based on the label
of data
the code is about to observe. For example, taintP
could be
implemented as:
taintP p l = do lcurrent <-getLabel
taint
(lostar p l lcurrent)
Constructors
NoPrivs |
Labeled IO Monad (LIO)
The LIO
monad is a wrapper around IO
that keeps track of the
current label and clearance. It is possible to raise one's label
or lower one's clearance without privilege, but moving in the other
direction requires appropriate privilege.
LIO
is parameterized by two types. The first is the particular
label type. The second type is state specific to the label type.
Trusted label implementation code can use getTCB
and putTCB
to
get and set the label state.
data Label l => LIO l s a Source
Instances
Label l => MonadError IOException (LIO l s) | |
Monad (LIO l s) | |
Functor (LIO l s) | |
MonadFix (LIO l s) | |
Label l => MonadCatch (LIO l s) | |
Label l => OnExceptionTCB (LIO l s) | |
Label l => MonadLIO (LIO l s) l s | |
(Label l, CloseOps (LHandle l h) (LIO l s), HandleOps h b IO) => HandleOps (LHandle l h) b (LIO l s) | |
Label l => CloseOps (LHandle l Handle) (LIO l s) | |
Label l => DirectoryOps (LHandle l Handle) (LIO l s) |
setLabelP :: Priv l p => p -> l -> LIO l s ()Source
If the current label is oldLabel
and the current clearance is
clearance
, this function allows code to raise the label to any
value newLabel
such that
oldLabel `
.
Note that there is no leq
` newLabel && newLabel `leq
` clearancesetLabel
variant without the ...P
because
the taint
function provides essentially the same functionality
that setLabel
would.
getClearance :: Label l => LIO l s lSource
Returns the current value of the thread's clearance.
lowerClr :: Label l => l -> LIO l s ()Source
Reduce the current clearance. One cannot raise the current label or create object with labels higher than the current clearance.
lowerClrP :: Priv l p => p -> l -> LIO l s ()Source
Raise the current clearance (undoing the effects of lowerClr
).
This requires privileges.
withClearance :: Label l => l -> LIO l s a -> LIO l s aSource
Lowers the clearance of a computation, then restores the
clearance to its previous value. Useful to wrap around a
computation if you want to be sure you can catch exceptions thrown
by it. Also useful to wrap around toLabeled
to ensure that the
computation does not access data exceeding a particular label. If
withClearance
is given a label that can't flow to the current
clearance, then the clearance is lowered to the greatest lower
bound of the label supplied and the current clearance.
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 lowerClrP
.
LIO guards
Guards are used by 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 theleq
` lcurrenttaint
function, so named becuase it "taints" the current LIO context by raisinglcurrent
untilldata `
. (Specifically, it does this by computing the least upper bound of the two labels with theleq
` lcurrentlub
method of theLabel
class.) However, if after doing this it would be the case thatnot (lcurrent `
, thenleq
` ccurrent)taint
throws exceptionLerrClearance
rather than raising the current label. - When writing an object, it should be the case that
ldata `
. (As stated, this is the same as sayingleq
` lcurrent && lcurrent `leq
` ldataldata == lcurrent
, but the two are different when usingleqp
instead ofleq
.) This is ensured by thewguard
(write guard) 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. - When creating or allocating objects, it is permissible for
them to be higher than the current label, so long as they are
bellow the current clearance. In other words, it must be the
case that
lcurrent `
. This is ensured by theleq
` ldata && ldata `leq
` ccurrentaguard
(allocation guard) function.
The taintP
, wguardP
, and aguardP
functions are variants of the
above that take privilege to be more permissive and raise the current
label less.
taint :: Label l => l -> LIO l s ()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 leq
` l'
if LerrClearance
l'
would have to be
higher than the current clearance.
wguardP :: Priv l p => p -> l -> LIO l s ()Source
Like wguard
, but takes privilege argument to be more permissive.
aguard :: Label l => l -> LIO l s ()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 aguard l
does not throw an exception.
aguardP :: Priv l p => p -> l -> LIO l s ()Source
Like aguardP
, but takes privilege argument to be more permissive.
Labeled values
labelP :: Priv l p => p -> l -> a -> LIO l s (Labeled l a)Source
Constructs an Labeled
using privilege to allow the Labeled
's label
to be below the current label. If the current label is lcurrent
and the current clearance is ccurrent
, then the privilege p
and
label l
specified must satisfy
(leqp p lcurrent l) && l `
.
Note that privilege is not used to bypass the clearance. You must
use leq
` ccurrentlowerClrP
to raise the clearance first if you wish to
create an Labeled
at a higher label than the current clearance.
unlabel :: Label l => Labeled l a -> LIO l s aSource
Within the LIO
monad, this function takes an Labeled
and returns
the value. Thus, in the LIO
monad one can say:
x <- unlabel (xv :: Labeled SomeLabelType Int)
And now it is possible to use the value of x
, which is the pure
value of what was stored in xv
. Of course, unlabel
also raises
the current label. If raising the label would exceed the current
clearance, then unlabel
throws LerrClearance
.
However, you can use labelOf
to check if unlabel
will suceed without
throwing an exception.
unlabelP :: Priv l p => p -> Labeled l a -> LIO l s aSource
Extracts the value of an Labeled
just like unlabel
, but takes a
privilege argument to minimize the amount the current label must be
raised. Will still throw LerrClearance
under the same
circumstances as unlabel
.
toLabeled :: Label l => l -> LIO l s a -> LIO l s (Labeled l a)Source
toLabeled
is the dual of unlabel
. It allows one to invoke
computations that would raise the current label, but without
actually raising the label. Instead, the result of the computation
is packaged into a Labeled
with a supplied label.
Thus, to get at the result of the
computation one will have to call unlabel
and raise the label, but
this can be postponed, or done inside some other call to toLabeled
.
This suggestst that the provided label must be above the current
label and below the current clearance.
Note that toLabeled
always restores the clearance to whatever it was
when it was invoked, regardless of what occured in the computation
producing the value of the Labeled
.
This higlights one main use of clearance: to ensure that a Labeled
computed does not exceed a particular label.
discard :: Label l => l -> LIO l s a -> LIO l s ()Source
Executes a computation that would raise the current label, but
discards the result so as to keep the label the same. Used when
one only cares about the side effects of a computation. For
instance, if log_handle
is an LHandle
with a high label, one
can execute
discard ltop $ hputStrLn
log_handle "Log message"
to create a log message without affecting the current label. (Of
course, if log_handle
is closed and this throws an exception, it
may not be possible to catch the exception within the LIO
monad
without sufficient privileges--see catchP
.)
Exceptions
Exception type thrown by LIO library
data LabelFault Source
Constructors
LerrLow | Requested label too low |
LerrHigh | Current label too high |
LerrClearance | Label would exceed clearance |
LerrPriv | Insufficient privileges |
LerrInval | Invalid request |
Instances
Throwing and catching labeled exceptions
We must re-define the throwIO
and catch
functions to work in
the LIO
monad. A complication is that exceptions could
potentially leak information. For instance, within a block of code
wrapped by discard
, one might examine a secret bit, and throw an
exception when the bit is 1 but not 0. Allowing untrusted code to
catch the exception leaks the bit.
The solution is to wrap exceptions up with a label. The exception
may be caught, but only if the label of the exception can flow to
the label at the point the catch statement began execution. For
compatibility, the throwIO
, catch
, and onException
functions
are now methods that work in both the IO
or LIO
monad.
If an exception is uncaught in the LIO
monad, the evalLIO
function will unlabel and re-throw the exception, so that it is
okay to throw exceptions from within the LIO
monad and catch them
within the IO
monad. (Of course, code in the IO
monad must be
careful not to let the LIO
code exploit it to exfiltrate
information.)
Wherever possible, however, code should use the catchP
and
onExceptionP
variants that use whatever privilege is available to
downgrade the exception. Privileged code that must always run some
cleanup function can use the onExceptionTCB
and bracketTCB
functions to run the cleanup code on all exceptions.
Note: Do not use throw
(as opposed to throwIO
) within the
LIO
monad. Because throw
can be invoked from pure code, it has
no notion of current label and so cannot assign an appropriate
label to the exception. As a result, the exception will not be
catchable within the LIO
monad and will propagate all the way out
of the evalLIO
function. Similarly, asynchronous exceptions
(such as divide by zero or undefined values in lazily evaluated
expressions) cannot be caught within the LIO
monad.
class Monad m => MonadCatch m whereSource
MonadCatch
is the class used to generalize the standard IO
catch
and throwIO
functions to methods that can be defined in
multiple monads.
Methods
throwIO :: Exception e => e -> m aSource
catch :: Exception e => m a -> (e -> m a) -> m aSource
handle :: Exception e => (e -> m a) -> m a -> m aSource
onException :: m a -> m b -> m aSource
Instances
MonadCatch IO | |
Label l => MonadCatch (LIO l s) |
Arguments
:: (Label l, Exception e, Priv l p) | |
=> p | Privileges with which to downgrade exception |
-> LIO l s a | Computation to run |
-> (l -> e -> LIO l s a) | Exception handler |
-> LIO l s a | Result of computation or handler |
Catches an exception, so long as the label at the point where the exception was thrown can flow to the label at which catchP is invoked, modulo the privileges specified. Note that the handler receives an an extra first argument (before the exception), which is the label when the exception was thrown.
Arguments
:: (Label l, Exception e, Priv l p) | |
=> p | Privileges with which to downgrade exception |
-> (l -> e -> LIO l s a) | Exception handler |
-> LIO l s a | Computation to run |
-> LIO l s a | Result of computation or handler |
Version of catchP
with arguments swapped.
Arguments
:: Priv l p | |
=> p | Privileges to downgrade exception |
-> LIO l s a | The computation to run |
-> LIO l s b | Handler to run on exception |
-> LIO l s a | Result if no exception thrown |
onException
cannot run its handler if the label was raised in
the computation that threw the exception. This variant allows
privileges to be supplied, so as to catch exceptions thrown with a
raised label.
bracketP :: Priv l p => p -> LIO l s a -> (a -> LIO l s c) -> (a -> LIO l s b) -> LIO l s bSource
Like standard bracket
, but with privileges to downgrade
exception.
Executing computations
Arguments
:: Label l | |
=> LIO l s a | The LIO computation to execute |
-> s | Initial value of label-specific state |
-> IO (a, l) | IO computation that will execute first argument |
Produces an IO
computation that will execute a particular 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--it just can't execute them without access to
ioTCB
.)
Privileged operations
runLIO :: forall l s a. Label l => LIO l s a -> LIOstate l s -> IO (a, LIOstate l s)Source
Execute an LIO action.
PrivTCB
is a method-less class whose only purpose is to be
unavailable to unprivileged code. Since (PrivTCB t) =>
is in the
context of class Priv
and unprivileged code cannot create new
instances of the PrivTCB
class, this ensures unprivileged code
cannot create new instances of the Priv
class either, even though
the symbol Priv
is exported by LIO.Base and visible to
untrusted code.
Methods
A function that mints new objects (such as instances of
Priv
) in a way that only privileged code should be allowed to
do. Because the MintTCB method is only available to
priviledged code, other modules imported by unpriviledged code
can define instances of mintTCB.
unlabelTCB :: Label l => Labeled l a -> aSource
Extracts the value from an Labeled
, discarding the label and any
protection.
setLabelTCB :: Label l => l -> LIO l s ()Source
Set the current label to anything, with no security check.
lowerClrTCB :: Label l => l -> LIO l s ()Source
Set the current clearance to anything, with no security check.
rtioTCB :: Label l => IO a -> LIO l s aSource
Lifts an IO
computation into the LIO
monad. If the IO
computation throws an exception, it labels the exception with the
current label so that the exception can be caught with catch
or
catchP
. This function's name stands for "re-throw io", because
the functionality is a combination of rethrowTCB
and ioTCB
.
Effectively
rtioTCB =rethrowTCB
.ioTCB
rethrowTCB :: Label l => LIO l s a -> LIO l s aSource
Privileged code that does IO operations may cause exceptions that
should be caught by untrusted code in the LIO
monad. Such
operations should be wrapped by rethrowTCB
(or rtioTCB
, which
uses rethrowTCB
) to ensure the exception is labeled. Note that
it is very important that the computation executed inside
rethrowTCB
not in any way change the label, as otherwise
rethrowTCB
would put the wrong label on the exception.
class MonadCatch m => OnExceptionTCB m whereSource
For privileged code that needs to catch all exceptions in some
cleanup function. Note that for the LIO
monad, these methods do
not call rethrowTCB
to label the exceptions. It is assumed
that you will use rtioTCB
instead of ioTCB
for IO within the
computation arguments of these methods.
Methods
onExceptionTCB :: m a -> m b -> m aSource
bracketTCB :: m a -> (a -> m c) -> (a -> m b) -> m bSource
Instances
OnExceptionTCB IO | |
Label l => OnExceptionTCB (LIO l s) |