| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
LIO.DCLabel
Description
Disjunction Category Labels (DCLabels) are a label format that
encodes authority, secrecy restrictions, and integrity properties
using propositional logic.
A DCLabel consists of two boolean formulas over Principals.  Each
formula is in conjunctive normal form, represented by type CNF.  The
first CNF (dcSecrecy) specifies what combinations of principals
are allowed to make data public.  The second CNF (dcIntegrity)
specifies which combinations of principals have endorsed the integrity
of the data.
The %% operator allows one to construct a DCLabel by joining a
secrecy CNF on the left with an integrity CNF on the right.  A
DCLabel can also be directly constructed with the constructor
DCLabel.  However, %% has the added convenience of accepting any
argument types that are instances of ToCNF.
For example, the following expresses data that can be exported by the
principal "Alice" and may have been written by anybody:  "Alice"
.  (%% TruetoCNF True
A CNF is created using the (\/) and (/\) operators.  The
disjunction operator (\/) is used to compute a CNF equivalent to
the disjunciton of two Principals, Strings, or CNFs. For
example:
p1 =principal"p1" p2 =principal"p2" p3 =principal"p3" e1 = p1\/p2 e2 = e1\/"p4"
Similarly, the conjunction operator (/\) creates a CNF as a
conjunction of Principals, Strings, Disjunctions, or CNFs.
e3 = p1\/p2 e4 = e1/\"p4"/\p3
Note that because a CNF formula is stored as a conjunction of
Disjunctions, it is much more efficient to apply /\ to the result
of \/ than vice versa.  It would be logical for /\ to have higher
fixity than \/.  Unfortunately, this makes formulas harder to read
(given the convention of AND binding more tightly than OR).  Hence
\/ and /\ have been given the same fixity but different
associativities, preventing the two from being mixed in the same
expression without explicit parentheses.
Consider the following, example:
cnf1 = ("Alice" \/ "Bob") /\ "Carla"
cnf2 = "Alice" /\ "Carla"
dc1 = cnf1 %% cnf2
dc2 = "Djon" %% "Alice"
pr = PrivTCB $ "Alice" /\ "Carla"
  This will result in the following:
>>>dc1"Carla" /\ ("Alice" \/ "Bob") %% "Alice" /\ "Carla">>>dc2"Djon" %% "Alice">>>canFlowTo dc1 dc2False>>>canFlowToP pr dc1 dc2True
Because the \/ and /\ operators accept strings and Principals as
well as CNFs, it is sometimes easy to forget that strings and
Principals are not actually CNFs.  For example:
>>>"Alice" /\ "Bob" `speaksFor` "Alice" \/ "Bob"True>>>"Alice" `speaksFor` "Alice" \/ "Bob"<interactive>:12:21: Couldn't match expected type `[Char]' with actual type `CNF'
To convert a single string or Principal to a CNF, you must use the
toCNF method:
>>>toCNF "Alice" `speaksFor` "Alice" \/ "Bob"True
- type DC = LIO DCLabel
- type DCPriv = Priv CNF
- type DCLabeled = Labeled DCLabel
- dcDefaultState :: LIOState DCLabel
- evalDC :: DC a -> IO a
- tryDC :: DC a -> IO (Either SomeException a, LIOState DCLabel)
- data Principal
- principalBS :: ByteString -> Principal
- principal :: String -> Principal
- data DCLabel = DCLabel {- dcSecrecy :: !CNF
- dcIntegrity :: !CNF
 
- dcPublic :: DCLabel
- (%%) :: (ToCNF a, ToCNF b) => a -> b -> DCLabel
- (/\) :: (ToCNF a, ToCNF b) => a -> b -> CNF
- (\/) :: (ToCNF a, ToCNF b) => a -> b -> CNF
- data CNF
- class ToCNF c where
- principalName :: Principal -> ByteString
- data Disjunction
- dToSet :: Disjunction -> Set Principal
- dFromList :: [Principal] -> Disjunction
- cTrue :: CNF
- cFalse :: CNF
- cToSet :: CNF -> Set Disjunction
- cFromList :: [Disjunction] -> CNF
Top-level aliases and functions
dcDefaultState :: LIOState DCLabel Source #
A common default starting state, where lioLabel = dcPubliclioClearance = False %% True
evalDC :: DC a -> IO a Source #
Wrapper function for running LIO DCLabel
evalDC dc =evalLIOdcdcDefaultState
tryDC :: DC a -> IO (Either SomeException a, LIOState DCLabel) Source #
tryDC dc =tryLIOdcdcDefaultState
Main types and functions
A Principal is a primitive source of authority, represented as
 a string.  The interpretation of principal strings is up to the
 application.  Reasonable schemes include encoding user names,
 domain names, and/or URLs in the Principal type.
principalBS :: ByteString -> Principal Source #
Create a principal from a strict ByteString.
principal :: String -> Principal Source #
Create a principal from a String.  The String is packed into
 a ByteString using fromString, which will almost certainly
 give unexpected results for non-ASCII unicode code points.
Main DCLabel type.  DCLabels use CNF boolean formulas over
 principals to express authority exercised by a combination of
 principals.  A DCLabel contains two CNFs.  One, dcSecrecy,
 specifies the minimum authority required to make data with the
 label completely public.  The second, dcIntegrity, expresses the
 minimum authority that was used to endorse data with the label, or,
 for mutable objects, the minimum authority required to modify the
 object.
DCLabels are more conveniently expressed using the %% operator,
 with dcSecrecy on the left and dcIntegrity on the right, i.e.:
 (dcSecrecyValue %% dcIntegrityValue).
DCLabels enforce the following relations:
- If cnf1andcnf2areCNFs describing authority, thencnf1 `if and only ifspeaksFor` cnf2cnf1logically impliescnf2(often writtencnf1 ⟹ cnf2). For example,("A", while/\"B") `speaksFor`toCNF"A"toCNF"A" `speaksFor` ("A"\/"C")
- Given two DCLabelsdc1 = (s1and%%i1)dc2 = (s2,%%i2)dc1 `(often writtencanFlowTo` dc2dc1⊑dc2) if and only ifs2 `. In other words, data can flow in the direction of requiring more authority to make it public or removing integrity endorsements.speaksFor` s1 && i1 `speaksFor` i2
- Given two DCLabelsdc1 = (s1and%%i1)dc2 = (s2, and a%%i2)p::representing privileges,CNFcanFlowToPp dc1 dc2dc1⊑ₚdc2) if and only if(p./\s2) `speaksFor` s2 && (p/\i1) `speaksFor` i2
Constructors
| DCLabel | |
| Fields 
 | |
dcPublic = True %% True
This label corresponds to public data with no integrity guarantees.
 For instance, an unrestricted Internet socket should be labeled
 dcPublic.  The significance of dcPublic is that given data
 labeled (s %% i), s is the exact minimum authority such that
 (s %% i) ⊑ₛ dcPublic, while i is the exact
 minimum authority such that dcPublic ⊑ᵢ (s %% i).
As a type, a CNF is always a conjunction of Disjunctions of
 Principals.  However, mathematically speaking, a single
 Principal or single Disjunction is also a degenerate example of
 conjunctive normal form.  Class ToCNF abstracts over the
 differences between these types, promoting them all to CNF.
Minimal complete definition
Lower-level functions
principalName :: Principal -> ByteString Source #
Extract the name of a principal as a strict ByteString.
 (Use show to get it as a regular String.)
data Disjunction Source #
Represents a disjunction of Principals, or one clause of a
 CNF.  There is generally not much need to work directly with
 Disjunctions unless you need to serialize and de-serialize them
 (by means of dToSet and dFromList).
Instances
| Eq Disjunction Source # | |
| Ord Disjunction Source # | |
| Read Disjunction Source # | Note that a disjunction containing more than one element must be surrounded by parentheses to parse correctly. | 
| Show Disjunction Source # | |
| Monoid Disjunction Source # | |
| ToCNF Disjunction Source # | |
dToSet :: Disjunction -> Set Principal Source #
Expose the set of Principals being ORed together in a
 Disjunction.
dFromList :: [Principal] -> Disjunction Source #
Convert a list of Principals into a Disjunction.
A CNF that is always True--i.e., trivially satisfiable.  When
 dcSecrecy = cTruedcIntegrity = cTruecTrue conveys no
 privileges; canFlowToP cTrue l1 l2canFlowTo l1 l2
Note that toCNF True = cTruedcPublic = DCLabel
 cTrue cTrue
A CNF that is always False.  If dcSecrecy = cFalsecFalse generally shouldn't appear in a
 data label.  However, it is convenient to include as the
 dcSecrecy component of lioClearance to indicate a thread may
 arbitrarily raise its label.
dcIntegrity = cFalse
As a privilege description, cFalse indicates impossibly high
 privileges (i.e., higher than could be achieved through any
 combination of Principals).  cFalse ` for any
 speaksFor` pCNF p.  This can be a useful concept for bootstrapping
 privileges within the DC monad itself.  For instance, the result
 of privInit cFalseDC code,
 which can in turn use delegate to create arbitrary finite
 privileges to pass to less privileged code.
cToSet :: CNF -> Set Disjunction Source #
Convert a CNF to a Set of Disjunctions.  Mostly useful if
 you wish to serialize a DCLabel.
cFromList :: [Disjunction] -> CNF Source #
Convert a list of Disjunctions into a CNF.  Mostly useful if
 you wish to de-serialize a CNF.