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 and its kernel documentation.
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
- version1 :: 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
Eq RulesetAttr Source # | |
Defined in System.Landlock (==) :: RulesetAttr -> RulesetAttr -> Bool (/=) :: RulesetAttr -> RulesetAttr -> Bool | |
Show RulesetAttr Source # | |
Defined in System.Landlock showsPrec :: Int -> RulesetAttr -> ShowS show :: RulesetAttr -> String showList :: [RulesetAttr] -> ShowS |
Filesystem Access Flags
Filesystem access flags to sandbox filesystem access.
data AccessFsFlag #
Instances
accessFsFlags :: [(Version, [AccessFsFlag])] #
accessFsFlagIsReadOnly :: AccessFsFlag -> Bool #
Sandboxing Rules
Sandboxing rules to apply.
Instances
Eq (Rule a) | |
Show (Rule a) | |
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 () |
pathBeneath :: Fd -> [AccessFsFlag] -> Rule 'PathBeneath #
Utility Functions
Various utility functions.
isSupported :: IO Bool Source #
Check whether Landlock is supported and enabled on the running system.
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.
Warning: calling this on a system without Landlock support, or with Landlock disabled, will result in an exception.
Opening paths using O_PATH
When creating a pathBeneath
rule, a file descriptor to a directory
or file is needed. These can be safely open
ed using the O_PATH
flag
using the following functions.
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 #
Instances
Eq OpenPathFlags | |
Defined in System.Landlock.OpenPath (==) :: OpenPathFlags -> OpenPathFlags -> Bool (/=) :: OpenPathFlags -> OpenPathFlags -> Bool | |
Show OpenPathFlags | |
Defined in System.Landlock.OpenPath showsPrec :: Int -> OpenPathFlags -> ShowS show :: OpenPathFlags -> String showList :: [OpenPathFlags] -> ShowS |