lio-0.10.0.0: Labeled IO Information Flow Control Library

Safe HaskellUnsafe

LIO.TCB

Contents

Description

This module exports

  • The definition of the LIO monad and relevant trusted state access/modifying functions.
  • Various other types whose constructors are privileged and must be hidden from untrusted code.
  • Uncatchable exceptions used to pop threads out of the LIO monad unconditionally.
  • Combinators for executing IO actions within the LIO monad.

The documentation and external, safe LIO interface is provided in LIO.Core.

Synopsis

LIO monad

data LIOState l Source

Internal state of an LIO computation.

Constructors

LIOState 

Fields

lioLabel :: !l

Current label.

lioClearance :: !l

Current clearance.

Instances

Eq l => Eq (LIOState l) 
Read l => Read (LIOState l) 
Show l => Show (LIOState l) 

newtype LIO l a Source

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.

Constructors

LIOTCB 

Fields

unLIOTCB :: IORef (LIOState l) -> IO a
 

Instances

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) 

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 :: Label l => (LIOState l -> LIOState l) -> LIO l ()Source

Update the internal state given some function.

updateLIOStateTCB :: Label l => (LIOState l -> LIOState l) -> LIO l ()Source

Deprecated: Use modifyLIOStateTCB instead

Executing IO actions

ioTCB :: IO a -> LIO l aSource

Lifts an IO computation into the LIO monad. Note that exceptions thrown within the IO computation cannot directly be caught within the LIO computation. Thus, you will generally want to use rethrowIoTCB.

Privileged constructors

newtype Priv a Source

A newtype wrapper that can be used by trusted code to bless privileges. Privilege-related functions are defined in LIO.Privs, but the constructor, PrivTCB, allows one to mint arbitrary privileges and hence must be located in this file.

Constructors

PrivTCB a 

Instances

data Labeled l t Source

Labeled l a is a value that associates a label of type l with a value of type a. Labeled values allow users to label data with a label other than the current label. In an embedded setting this is akin to having first class labeled values. Note that Labeled is an instance of LabelOf, which effectively means that the label of a Labeled value is usually just protected by the current label. (Of course if you have a nested labeled value then the label on the inner labeled value's label is the outer label.)

Constructors

LabeledTCB !l t 

Instances

Typeable2 Labeled 
LabelOf Labeled 
(Label l, Read l, Read a) => ReadTCB (Labeled l a)

Trusted Read instance.

(Label l, Show a) => ShowTCB (Labeled l a)

Trusted Show instance.

Uncatchable exception type

data UncatchableTCB Source

An uncatchable exception hierarchy use 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.

Constructors

forall e . Exception e => UncatchableTCB e 

makeCatchable :: SomeException -> SomeExceptionSource

Simple utility function that strips UncatchableTCB from around an exception.

Trusted Show and Read

class ShowTCB a whereSource

It would be a security issue to make certain objects a member of the Show class, but nonetheless it is useful to be able to examine such objects when debugging. The showTCB method can be used to examine such objects.

Methods

showTCB :: a -> StringSource

Instances

(Label l, Show a) => ShowTCB (Labeled l a)

Trusted Show instance.

(Label l, Show t) => ShowTCB (LObj l t) 

class ReadTCB a whereSource

It is useful to have the dual of ShowTCB, ReadTCB, that allows for the reading of strings that were created using showTCB. Only readTCB (corresponding to read) and readsPrecTCB (corresponding to readsPrec) are implemented.

Methods

readsPrecTCB :: Int -> ReadS aSource

Trusted readsPrec

readTCB :: String -> aSource

Trusted read

Instances

(Label l, Read l, Read a) => ReadTCB (Labeled l a)

Trusted Read instance.