lio-0.11.7.0: Labeled IO Information Flow Control Library

Safe HaskellUnsafe
LanguageHaskell2010

LIO.TCB

Contents

Description

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.

Synopsis

LIO monad

data LIOState l Source #

Internal state of an LIO computation.

Constructors

LIOState 

Fields

Instances
Eq l => Eq (LIOState l) Source # 
Instance details

Defined in LIO.TCB

Methods

(==) :: LIOState l -> LIOState l -> Bool #

(/=) :: LIOState l -> LIOState l -> Bool #

Read l => Read (LIOState l) Source # 
Instance details

Defined in LIO.TCB

Show l => Show (LIOState l) Source # 
Instance details

Defined in LIO.TCB

Methods

showsPrec :: Int -> LIOState l -> ShowS #

show :: LIOState l -> String #

showList :: [LIOState l] -> ShowS #

newtype LIO l a Source #

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).

Constructors

LIOTCB (IORef (LIOState l) -> IO a) 
Instances
Label l => MonadLIO l (LIO l) Source # 
Instance details

Defined in LIO.Monad

Methods

liftLIO :: LIO l a -> LIO l a Source #

GuardIO l (IO r) (LIO l r) Source # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO l () -> IO r -> LIO l r Source #

LabelIO l (IO r) (LIO l r) Source # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO l () -> (a1 -> a2 -> IO r) -> a1 -> a2 -> LIO l r Source #

GuardIO l (a1 -> IO r) (a1 -> LIO l r) Source # 
Instance details

Defined in LIO.TCB.LObj

Methods

guardIOTCB :: LIO 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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (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 # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (a1 -> a2 -> a3 -> IO r) -> a1 -> a2 -> a3 -> LIO l r Source #

LabelIO l (a1 -> a2 -> IO r) (a1 -> a2 -> LIO l r) Source # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (a1 -> a2 -> IO r) -> a1 -> a2 -> LIO l r Source #

LabelIO l (a1 -> IO r) (a1 -> LIO l r) Source # 
Instance details

Defined in LIO.TCB.MLObj

Methods

labelIO :: (forall r0. IO r0 -> LIO l r0) -> (a1 -> IO r) -> a1 -> LIO l r Source #

Monad (LIO l) Source # 
Instance details

Defined in LIO.TCB

Methods

(>>=) :: LIO l a -> (a -> LIO l b) -> LIO l b #

(>>) :: LIO l a -> LIO l b -> LIO l b #

return :: a -> LIO l a #

fail :: String -> LIO l a #

Functor (LIO l) Source # 
Instance details

Defined in LIO.TCB

Methods

fmap :: (a -> b) -> LIO l a -> LIO l b #

(<$) :: a -> LIO l b -> LIO l a #

Applicative (LIO l) Source # 
Instance details

Defined in LIO.TCB

Methods

pure :: a -> LIO l a #

(<*>) :: LIO l (a -> b) -> LIO l a -> LIO l b #

liftA2 :: (a -> b -> c) -> LIO l a -> LIO l b -> LIO l c #

(*>) :: LIO l a -> LIO l b -> LIO l b #

(<*) :: LIO l a -> LIO l b -> LIO l a #

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

ioTCB :: IO a -> LIO l a Source #

Lifts an IO computation into the LIO monad. This function is dangerous and should only be called after appropriate checks ensure the IO computation will not violate IFC policy.

Privileged constructors

newtype Priv a Source #

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#v:privInit") from the IO monad before running your LIO computation.

Constructors

PrivTCB a 
Instances
PrivDesc l p => PrivDesc l (Priv p) Source # 
Instance details

Defined in LIO.Label

Methods

downgradeP :: Priv p -> l -> l Source #

canFlowToP :: Priv p -> l -> l -> Bool Source #

Eq a => Eq (Priv a) Source # 
Instance details

Defined in LIO.TCB

Methods

(==) :: Priv a -> Priv a -> Bool #

(/=) :: Priv a -> Priv a -> Bool #

Show a => Show (Priv a) Source # 
Instance details

Defined in LIO.TCB

Methods

showsPrec :: Int -> Priv a -> ShowS #

show :: Priv a -> String #

showList :: [Priv a] -> ShowS #

Semigroup p => Semigroup (Priv p) Source # 
Instance details

Defined in LIO.TCB

Methods

(<>) :: Priv p -> Priv p -> Priv p #

sconcat :: NonEmpty (Priv p) -> Priv p #

stimes :: Integral b => b -> Priv p -> Priv p #

Monoid p => Monoid (Priv p) Source # 
Instance details

Defined in LIO.TCB

Methods

mempty :: Priv p #

mappend :: Priv p -> Priv p -> Priv p #

mconcat :: [Priv p] -> Priv p #

SpeaksFor p => SpeaksFor (Priv p) Source # 
Instance details

Defined in LIO.Label

Methods

speaksFor :: Priv p -> Priv p -> Bool Source #

ToCNF (Priv CNF) Source # 
Instance details

Defined in LIO.DCLabel

Methods

toCNF :: Priv CNF -> CNF Source #

data Labeled l t Source #

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.

Constructors

LabeledTCB !l t 
Instances
LabelOf Labeled Source # 
Instance details

Defined in LIO.TCB

Methods

labelOf :: Labeled l a -> l Source #

(Show l, Show a) => ShowTCB (Labeled l a) Source #

Trusted Show instance.

Instance details

Defined in LIO.TCB

Methods

showTCB :: Labeled l a -> String Source #

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 LVals but not necessarily the actual value. To do so, simply provide an instance for LabelOf:

instance LabelOf LVal where
  labelOf (LValTCB l a) = l

Methods

labelOf :: t l a -> l Source #

Get the label of a labeled value or object. Note the label must be the second to last type constructor argument.

Instances
LabelOf LabeledResult Source # 
Instance details

Defined in LIO.TCB

Methods

labelOf :: LabeledResult l a -> l Source #

LabelOf Labeled Source # 
Instance details

Defined in LIO.TCB

Methods

labelOf :: Labeled l a -> l Source #

LabelOf LObj Source # 
Instance details

Defined in LIO.TCB.LObj

Methods

labelOf :: LObj l a -> l Source #

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.

Constructors

Exception e => UncatchableTCB e 

makeCatchable :: SomeException -> SomeException Source #

Simple utility function that strips UncatchableTCB from around an exception.

Trusted Show

class ShowTCB a where Source #

It would be a security issue to make certain objects members of the Show class. 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 -> String Source #

Instances
(Show l, Show a) => ShowTCB (Labeled l a) Source #

Trusted Show instance.

Instance details

Defined in LIO.TCB

Methods

showTCB :: Labeled l a -> String Source #

(Label l, Show t) => ShowTCB (LObj l t) Source # 
Instance details

Defined in LIO.TCB.LObj

Methods

showTCB :: LObj l t -> String Source #

LabeledResults

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.

Constructors

LabeledResultTCB 

Fields

Instances
LabelOf LabeledResult Source # 
Instance details

Defined in LIO.TCB

Methods

labelOf :: LabeledResult l a -> l Source #

data LResStatus l a Source #

Status of a LabeledResult.

Instances
(Show l, Show a) => Show (LResStatus l a) Source # 
Instance details

Defined in LIO.TCB

Methods

showsPrec :: Int -> LResStatus l a -> ShowS #

show :: LResStatus l a -> String #

showList :: [LResStatus l a] -> ShowS #