Copyright | (c) Nicolas Trangez 2022 |
---|---|
License | BSD-3-Clause |
Maintainer | ikke@nicolast.be |
Stability | alpha |
Portability | Linux |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This library exposes Haskell bindings for the Linux kernel Landlock API.
The Linux kernel Landlock API provides unprivileged access control. The goal of Landlock is to enable to restrict ambient rights (e.g. global filesystem access) for a set of processes. Because Landlock is a stackable LSM, it makes possible to create safe security sandboxes as new security layers in addition to the existing system-wide access-controls. This kind of sandbox is expected to help mitigate the security impact of bugs or unexpected/malicious behaviors in user space applications. Landlock empowers any process, including unprivileged ones, to securely restrict themselves.
For more information, see the Landlock homepage, its kernel documentation and its manual page.
Synopsis
- landlock :: (MonadMask m, MonadIO m) => RulesetAttr -> [CreateRulesetFlag] -> [RestrictSelfFlag] -> ((Storable (Rule r) => Rule r -> [AddRuleFlag] -> m ()) -> m a) -> m a
- data RulesetAttr = RulesetAttr {}
- data AccessFsFlag
- accessFsFlags :: [(Version, [AccessFsFlag])]
- accessFsFlagIsReadOnly :: AccessFsFlag -> Bool
- data Rule (a :: RuleType)
- pathBeneath :: Fd -> [AccessFsFlag] -> Rule 'PathBeneath
- isSupported :: IO Bool
- abiVersion :: IO Version
- data Version
- getVersion :: Version -> Word
- version1 :: Version
- version2 :: Version
- version3 :: Version
- withOpenPath :: (MonadIO m, MonadMask m) => FilePath -> OpenPathFlags -> (Fd -> m a) -> m a
- withOpenPathAt :: (MonadIO m, MonadMask m) => Fd -> FilePath -> OpenPathFlags -> (Fd -> m a) -> m a
- data OpenPathFlags = OpenPathFlags {}
- defaultOpenPathFlags :: OpenPathFlags
Core API
Use landlock
to sandbox a process.
Example usage:
-- Retrieve the Landlock ABI version abi <- abiVersion -- Calculate access flag sets -- Note: in production code, find the highest matching version or similar let Just flags = lookup abi accessFsFlags readOnlyFlags = filter accessFsFlagIsReadOnly flags -- Sandbox the process landlock (RulesetAttr flags) [] [] $ \addRule -> do -- Allow read-only access to the /usr hierarchy withOpenPath "/usr" defaultOpenPathFlags{ directory = True } $ \fd -> addRule (pathBeneath fd readOnlyFlags) [] -- Allow read access to my public key withOpenPath "/home/nicolas/.ssh/id_ed25519.pub" defaultOpenPathFlags $ \fd -> addRule (pathBeneath fd [AccessFsReadFile]) [] withFile "/home/nicolas/.ssh/id_ed25519.pub" ReadMode (\fd -> putStrLn "Success") -- Success withFile "/usr/bin/ghc" ReadMode (\fd -> putStrLn "Success") -- Success openFile "/home/nicolas/.ssh/id_ed25519" ReadMode -- *** Exception: /home/nicolas/.ssh/id_ed25519: openFile: permission denied (Permission denied)
:: (MonadMask m, MonadIO m) | |
=> RulesetAttr | Ruleset attribute passed to
|
-> [CreateRulesetFlag] | Flags passed to
|
-> [RestrictSelfFlag] | Flags passed to
|
-> ((Storable (Rule r) => Rule r -> [AddRuleFlag] -> m ()) -> m a) | Action that will be called before the Landlock sandbox is
enforced. The provided function can be used to register
sandboxing rules (internally using
|
-> m a | Result of the given action. |
Apply a Landlock sandbox to the current process.
The provided action can be used to register Landlock Rule
s on the given
instance (see addRule
).
Once this returns, the Landlock sandbox will be in effect (see
landlock_restrict_self
),
and no privileged processes can be spawned
(prctl(PR_SET_NO_NEW_PRIVS, 1, 0, 0, 0)
has been invoked).
Warning: calling this on a system without Landlock support, or with Landlock disabled, will result in an exception.
data RulesetAttr Source #
Ruleset attributes.
This represents a struct landlock_ruleset_attr
as passed to
landlock_create_ruleset
.
RulesetAttr | |
|
Instances
Show RulesetAttr Source # | |
Defined in System.Landlock showsPrec :: Int -> RulesetAttr -> ShowS # show :: RulesetAttr -> String # showList :: [RulesetAttr] -> ShowS # | |
Eq RulesetAttr Source # | |
Defined in System.Landlock (==) :: RulesetAttr -> RulesetAttr -> Bool # (/=) :: RulesetAttr -> RulesetAttr -> Bool # |
Filesystem Access Flags
Filesystem access flags to sandbox filesystem access.
data AccessFsFlag #
Filesystem flags.
These flags enable to restrict a sandboxed process to a set of actions on files and directories. Files or directories opened before the sandboxing are not subject to these restrictions.
A file can only receive these access rights:
A directory can receive access rights related to files or directories. The following access right is applied to the directory itself, and the directories beneath it:
However, the following access rights only apply to the content of a directory, not the directory itself:
AccessFsRemoveDir
AccessFsRemoveFile
AccessFsMakeChar
AccessFsMakeDir
AccessFsMakeReg
AccessFsMakeSock
AccessFsMakeFifo
AccessFsMakeBlock
AccessFsMakeSym
AccessFsRefer
Warning: It is currently not possible to restrict some file-related
actions acessible through these syscall families:
chdir
,
stat
,
flock
,
chmod
,
chown
,
setxattr
,
utime
,
ioctl
,
fcntl
,
access
.
Future Landlock evolutions will enable to restrict them.
AccessFsExecute | Execute a file
( |
AccessFsWriteFile | Open a file with write access
( Note that you might additionally need the |
AccessFsReadFile | Open a file with read access
( |
AccessFsReadDir | Open a directory or list its content
( |
AccessFsRemoveDir | Remove an empty directory or rename one
( |
AccessFsRemoveFile | Unlink (or rename) a file
( |
AccessFsMakeChar | Create (or rename or link) a character device
( |
AccessFsMakeDir | Create (or rename) a directory
( |
AccessFsMakeReg | Create (or rename or link) a regular file
( |
AccessFsMakeSock | Create (or rename or link) a UNIX domain socket
( |
AccessFsMakeFifo | Create (or rename or link) a named pipe
( |
AccessFsMakeBlock | Create (or rename or link) a block device
( |
AccessFsMakeSym | Create (or rename or link) a symbolic link
( |
AccessFsRefer | Link or rename a file from or to a different
directory (i.e. reparent a file hierarchy). This access right is
available since the second version of the Landlock ABI. This is also the
only access right which is always considered handled by any ruleset in
such a way that reparenting a file hierarchy is always denied by default.
To avoid privilege escalation, it is not enough to add a rule with this
access right. When linking or renaming a file, the destination directory
hierarchy must also always have the same or a superset of restrictions of
the source hierarchy. If it is not the case, or if the domain doesn't
handle this access right, such actions are denied by default with
|
AccessFsTruncate | Truncate a file with
|
Instances
accessFsFlags :: [(Version, [AccessFsFlag])] #
All AccessFsFlag
flags keyed by a Landlock ABI Version
.
accessFsFlagIsReadOnly :: AccessFsFlag -> Bool #
Predicate for read-only AccessFsFlag
flags.
Sandboxing Rules
Sandboxing rules to apply.
A rule enforced by Landlock, to be registered using addRule
.
Rule
s can be constructed using the relevant functions, like pathBeneath
.
Instances
Storable (Rule 'PathBeneath) | |
Defined in System.Landlock.Rules sizeOf :: Rule 'PathBeneath -> Int # alignment :: Rule 'PathBeneath -> Int # peekElemOff :: Ptr (Rule 'PathBeneath) -> Int -> IO (Rule 'PathBeneath) # pokeElemOff :: Ptr (Rule 'PathBeneath) -> Int -> Rule 'PathBeneath -> IO () # peekByteOff :: Ptr b -> Int -> IO (Rule 'PathBeneath) # pokeByteOff :: Ptr b -> Int -> Rule 'PathBeneath -> IO () # peek :: Ptr (Rule 'PathBeneath) -> IO (Rule 'PathBeneath) # poke :: Ptr (Rule 'PathBeneath) -> Rule 'PathBeneath -> IO () # | |
Show (Rule a) | |
Eq (Rule a) | |
:: Fd | File descriptor, preferably opened with
|
-> [AccessFsFlag] | Allowed actions for this file hierarchy
(cf. |
-> Rule 'PathBeneath |
Construct a path hierarchy rule definition.
This corresponds to a rule of type
LANDLOCK_RULE_PATH_BENEATH
,
with attributes defined in a struct landlock_path_beneath_attr
.
Utility Functions
Various utility functions.
isSupported :: IO Bool Source #
Check whether Landlock is supported and enabled on the running system.
This calls abiVersion
, catching relevant exceptions to return False
when
applicable.
Landlock ABI Version
Retrieve and handle the kernel's Landlock ABI version.
abiVersion :: IO Version Source #
Retrieve the Landlock ABI version of the running system.
This invokes
landlock_create_ruleset
with the
LANDLOCK_CREATE_RULESET_VERSION
option.
Warning: calling this on a system without Landlock support, or with Landlock disabled, will result in an exception.
Representation of a Landlock ABI version as reported by the kernel.
getVersion :: Version -> Word #
Get the numerical version.
Opening paths using O_PATH
When creating a pathBeneath
rule, a file descriptor to a directory
or file is needed. These can be safely opened using the
O_PATH
flag using the
following functions.
:: (MonadIO m, MonadMask m) | |
=> FilePath | Path to open. |
-> OpenPathFlags | Flag settings to pass. |
-> (Fd -> m a) | Action to call with a file descriptor to the given path. |
-> m a | Result of the invoked action. |
:: (MonadIO m, MonadMask m) | |
=> Fd |
|
-> FilePath | Path to open. |
-> OpenPathFlags | Flag settings to pass. |
-> (Fd -> m a) | Action to call with a file descriptor to the given path. |
-> m a | Result of the invoked action. |
Perform an action with a path
openat
ed using
O_PATH
.
Like withOpenPath
, exposing the
openat
dirfd
argument.
The file descriptor provided to the action will be
close
d when the
function returns.
This internally calls
openat
with the
O_PATH
and
O_RDONLY
flags
set, next to any flags specified in the OpenPathFlags
argument.
data OpenPathFlags #
Extra flags used by withOpenPathAt
in the call to
openat
.
OpenPathFlags | |
|
Instances
Show OpenPathFlags | |
Defined in System.Landlock.OpenPath showsPrec :: Int -> OpenPathFlags -> ShowS # show :: OpenPathFlags -> String # showList :: [OpenPathFlags] -> ShowS # | |
Eq OpenPathFlags | |
Defined in System.Landlock.OpenPath (==) :: OpenPathFlags -> OpenPathFlags -> Bool # (/=) :: OpenPathFlags -> OpenPathFlags -> Bool # |
defaultOpenPathFlags :: OpenPathFlags #
Default OpenPathFlags
: