landlock-0.2.0.1: Haskell bindings for the Linux Landlock API
Copyright(c) Nicolas Trangez 2022
LicenseBSD-3-Clause
Maintainerikke@nicolast.be
Stabilityalpha
PortabilityLinux
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Landlock

Description

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

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)

landlock Source #

Arguments

:: (MonadMask m, MonadIO m) 
=> RulesetAttr

Ruleset attribute passed to landlock_create_ruleset.

-> [CreateRulesetFlag]

Flags passed to landlock_create_ruleset. Since no flags but CreateRulesetVersion (LANDLOCK_CREATE_RULESET_VERSION) are defined, and this flag must not be used when creating an actual ruleset, this should be an empty list.

-> [RestrictSelfFlag]

Flags passed to landlock_restrict_self. Since no flags are defined, this should be an empty list.

-> ((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 landlock_add_rule), given a Rule and a set of AddRuleFlags. However, since no flags are currently defined, this should be an empty list.

-> m a

Result of the given action.

Apply a Landlock sandbox to the current process.

The provided action can be used to register Landlock Rules 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.

Constructors

RulesetAttr 

Fields

Instances

Instances details
Eq RulesetAttr Source # 
Instance details

Defined in System.Landlock

Methods

(==) :: RulesetAttr -> RulesetAttr -> Bool

(/=) :: RulesetAttr -> RulesetAttr -> Bool

Show RulesetAttr Source # 
Instance details

Defined in System.Landlock

Methods

showsPrec :: Int -> RulesetAttr -> ShowS

show :: RulesetAttr -> String

showList :: [RulesetAttr] -> ShowS

Filesystem Access Flags

Filesystem access flags to sandbox filesystem access.

data AccessFsFlag #

Sandboxing Rules

Sandboxing rules to apply.

data Rule (a :: RuleType) #

Instances

Instances details
Eq (Rule a) 
Instance details

Defined in System.Landlock.Rules

Methods

(==) :: Rule a -> Rule a -> Bool

(/=) :: Rule a -> Rule a -> Bool

Show (Rule a) 
Instance details

Defined in System.Landlock.Rules

Methods

showsPrec :: Int -> Rule a -> ShowS

show :: Rule a -> String

showList :: [Rule a] -> ShowS

Storable (Rule 'PathBeneath) 
Instance details

Defined in System.Landlock.Rules

Methods

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.

data Version #

Instances

Instances details
Eq Version 
Instance details

Defined in System.Landlock.Version

Methods

(==) :: Version -> Version -> Bool

(/=) :: Version -> Version -> Bool

Ord Version 
Instance details

Defined in System.Landlock.Version

Methods

compare :: Version -> Version -> Ordering

(<) :: Version -> Version -> Bool

(<=) :: Version -> Version -> Bool

(>) :: Version -> Version -> Bool

(>=) :: Version -> Version -> Bool

max :: Version -> Version -> Version

min :: Version -> Version -> Version

Show Version 
Instance details

Defined in System.Landlock.Version

Methods

showsPrec :: Int -> Version -> ShowS

show :: Version -> String

showList :: [Version] -> ShowS

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.

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 #

Constructors

OpenPathFlags 

Fields

Instances

Instances details
Eq OpenPathFlags 
Instance details

Defined in System.Landlock.OpenPath

Show OpenPathFlags 
Instance details

Defined in System.Landlock.OpenPath

Methods

showsPrec :: Int -> OpenPathFlags -> ShowS

show :: OpenPathFlags -> String

showList :: [OpenPathFlags] -> ShowS