Safe Haskell | Trustworthy |
---|---|
Language | Haskell98 |
LIO.FS.Simple
Contents
Description
This module provides a very simple API for interacting with a labeled filesystem. Each file and directory hsa an associated label that is used to track and control the information flowing to/from the file/directory. The API exposed by this module is analogous to a subset of the System.IO API. We currently do not allow operations on file handles. Rather, files must be read read and written to in whole (as strict ByteStrings).
The actual storage of labeled files is handled by the LIO.FS.TCB module. The filesystem is implemented as a file store in which labels are associated with files and directories using, extended attributes.
IMPORTANT: To use the labeled filesystem you must use withLIOFS
(or other initializers), otherwise any actions built using the
combinators of this module will crash.
An example use case shown below:
import LIO.FS.Simple import LIO.FS.Simple.DCLabel main = withDCFS "/tmp/lioFS" $ evalDC $ do createDirectoryP p lsecrets "secrets" writeFileP p ("secrets" </> "alice" ) "I like Bob!" where p = ... lsecrets = ....
The file store for the labeled filesystem (see LIO.FS.TCB) will
be created in /tmp/lioFS
, but this is transparent and the user
can think of the filesystem as having root /
. Note that for this to
work the filesystem must be mounted with the user_xattr
option.
For example, on GNU/Linux, you can remount your drive:
mount -o remount -o user_xattr devicename
In the current version of the filesystem, there is no notion of
changeable current working directory in the LIO
Monad, nor symbolic
links.
- initializeLIOFS :: Label l => FilePath -> Maybe l -> IO l
- withLIOFS :: Label l => FilePath -> Maybe l -> IO a -> IO a
- readFile :: MonadLIO l m => FilePath -> m ByteString
- readFileP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m ByteString
- writeFile :: MonadLIO l m => Maybe l -> FilePath -> ByteString -> m ()
- writeFileP :: (PrivDesc l p, MonadLIO l m) => Priv p -> Maybe l -> FilePath -> ByteString -> m ()
- appendFile :: MonadLIO l m => FilePath -> ByteString -> m ()
- appendFileP :: (PrivDesc l p, MonadLIO l m) => Priv p -> FilePath -> ByteString -> m ()
- removeFile :: MonadLIO l m => FilePath -> m ()
- removeFileP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m ()
- labelOfFile :: MonadLIO l m => FilePath -> m l
- labelOfFileP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m l
- getDirectoryContents :: MonadLIO l m => FilePath -> m [FilePath]
- getDirectoryContentsP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m [FilePath]
- createDirectory :: MonadLIO l m => l -> FilePath -> m ()
- createDirectoryP :: (MonadLIO l m, PrivDesc l p) => Priv p -> l -> FilePath -> m ()
- removeDirectory :: MonadLIO l m => FilePath -> m ()
- removeDirectoryP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m ()
- data FSError
- cleanUpPath :: CleanUpPath m => FilePath -> m FilePath
- taintObjPathP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m FilePath
- labelDirectoryRecursively :: Label l => l -> FilePath -> IO ()
Initializing labeled filesystem
initializeLIOFS :: Label l => FilePath -> Maybe l -> IO l Source
Initialize filesystem at the given path. The supplied path must
be absolute, otherwise initializeLIOFS
throw FSRootInvalid
. If
the FS has already been created then initializeLIOFS
solely
verifies that the root directory is not corrupt (see checkFSTCB
)
and returns the label of the root. Otherwise, a new FS is created
with the supplied label (see mkFSTCB
).
NOTE: This function should only be called once per process.
withLIOFS :: Label l => FilePath -> Maybe l -> IO a -> IO a Source
Top-level wrapper thatexecutes initializeLIOFS
followed by the
supplied action.
NOTE: This function should only be called once per process.
File operations
readFile :: MonadLIO l m => FilePath -> m ByteString Source
Reads a file and returns the contents of the file as a strict ByteString. The current label is raised to reflect all the traversed directories. If the file exists it is further raised to the label of the file to reflect the read.
Arguments
:: (MonadLIO l m, PrivDesc l p) | |
=> Priv p | Privileges |
-> FilePath | File to open |
-> m ByteString |
Same as readFile
but uses privilege in opening the file.
writeFile :: MonadLIO l m => Maybe l -> FilePath -> ByteString -> m () Source
Given an optional label, file path and string, write the string
to the file at specified path. The optional label (which must be
bounded by the current label and clearance, as enforced by
guardAlloc
) is used to set the label on the file, if the file
does not already exist; otherwise the label must flow to the label
of the file. (Supplying a Nothing
is the same as Just
supplying
the current label.) This function ensures that current label is
raised to reflect all the traversed directories. Note that if the
file does not already exist, it is further required that the
current computation be able to write to the containing directory,
as imposed by guardWrite
.
writeFileP :: (PrivDesc l p, MonadLIO l m) => Priv p -> Maybe l -> FilePath -> ByteString -> m () Source
Same as writeFile
but uses privilege when writing to the file.
appendFile :: MonadLIO l m => FilePath -> ByteString -> m () Source
Given a file path and string, append the string to the file at
specified path. This function ensures that current label is raised
to reflect all the traversed directories. Moreover, it requires
that the file this is appending to exists and its label is bounded
by the current label and clearance (as enforced by guardAlloc
).
appendFileP :: (PrivDesc l p, MonadLIO l m) => Priv p -> FilePath -> ByteString -> m () Source
Same as appendFile
but uses privilege when writing to the file.
removeFile :: MonadLIO l m => FilePath -> m () Source
Remove the file at the specified path. The current computation must be able to both write to the file and containing directory. Moreover, the current label is raised to reflect the traversal of directories up to the file.
removeFileP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m () Source
Same as removeFile
, but uses privileges to carry out the
actions.
labelOfFile :: MonadLIO l m => FilePath -> m l Source
Get the label of a file/director at the supplied file path. The current label is raised to reflect all the traversed directories.
Arguments
:: (MonadLIO l m, PrivDesc l p) | |
=> Priv p | Privileges |
-> FilePath | File to get the label of |
-> m l |
Same as labelOfFile
but uses privilege in traversing
directories.
Directory operations
getDirectoryContents :: MonadLIO l m => FilePath -> m [FilePath] Source
Get the contents of a directory. The current label is raised to the
join of the current label and that of all the directories traversed to
the leaf directory. Note that, unlike the standard Haskell
getDirectoryContents
, we first normalise the path by collapsing all
the ..
's. The function uses unlabelFilePath
when raising the
current label and thus may throw an exception if the clearance is
too low.
Note: The current LIO filesystem does not support links.
Same as getDirectoryContents
, but uses privileges when raising
the current label.
createDirectory :: MonadLIO l m => l -> FilePath -> m () Source
Create a directory at the supplied path with the given label. The
given label must be bounded by the the current label and clearance, as
checked by guardAlloc
. The current label (after traversing the
filesystem to the directory path) must flow to the supplied label,
which must, in turn, flow to the current label as required by
guardWrite
.
Arguments
:: (MonadLIO l m, PrivDesc l p) | |
=> Priv p | Privilege |
-> l | Label of new directory |
-> FilePath | Path of directory |
-> m () |
Same as createDirectory
, but uses privileges when raising the
current label and checking IFC restrictions.
removeDirectory :: MonadLIO l m => FilePath -> m () Source
Same as removeFile
, but removes a directory.
removeDirectoryP :: (MonadLIO l m, PrivDesc l p) => Priv p -> FilePath -> m () Source
Same as removeDirectory
, but uses privileges to carry out the
actions.
Filesystem errors
Filesystem errors
Constructors
FSRootCorrupt | Root structure is corrupt. |
FSRootInvalid | Root is invalid (must be absolute). |
FSRootExists | Root already exists. |
FSRootNoExist | Root does not exists. |
FSRootNeedLabel | Cannot create root, missing label. |
FSObjNeedLabel | FSobjectcannot be created without a label. |
FSLabelCorrupt FilePath | Object label is corrupt. |
FSIllegalFileName | Supplied file name is illegal. |
Misc helpers
cleanUpPath :: CleanUpPath m => FilePath -> m FilePath Source
Cleanup a file path, if it starts out with a ..
, we consider this
invalid as it can be used explore parts of the filesystem that should
otherwise be unaccessible. Similarly, we remove any .
from the path.
Given a pathname to a labeled filesystem object, traverse all the directories up to the object, while correspondingly raising the current label. Note that if the object or a parent-directory does not exist, an exception will be thrown; the label of the exception will be the join of all the directory labels up to the lookup failure.
Note: this function cleans up the path before doing the
lookup, so e.g., path foobar/..
will first be rewritten to /foo
and thus no traversal to bar
. Note that this is a more permissive
behavior than forcing the read of ..
from bar
.
taintObjPath
returns this cleaned up path.
labelDirectoryRecursively :: Label l => l -> FilePath -> IO () Source
Label the directory and every file within recursively with the supplied label. Note this funciton expects a full path.