posix-acl-0.2.0.1: Support for Posix ACL

Copyright© 2013-2014 Nicola Squartini
LicenseBSD3
MaintainerNicola Squartini <tensor5@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

System.Posix.ACL.C

Contents

Description

Functions in this module are bindings to the C API defined in IEEE Std 1003.1e. The design goal is to be as low level as possible without having to allocate or deallocate memory, and remaining type-safe. In order to reach this goal, all pointers to opaque C structures are represented by monad transformers representing actions on those pointers. Here is the pointer to monad transformer correspondence:

acl_t         <--> AclT
acl_entry_t   <--> EntryT
acl_permset_t <--> PermsetT

A common usage pattern is to modify the permset of an entry inside an ACL. This is done in three steps:

  1. convert the PermsetT m a modification of permset into an EntryT m a modification of entry;
  2. convert the EntryT m a into an AclT m a modification of ACL;
  3. execute the AclT m a in the base monad m.

For example in

fromText "u::rw,g::r,o::r" $ getEntry 0 $ changePermset $ addPerm Execute

addPerm Execute is the PermsetT that adds the execute permission, changePermset converts PermsetT into EntryT, getEntry 0 modifies the 1st entry of the ACL according to the action contained in EntryT (thus converts EntryT into AclT), and finally fromText "u::rw,g::r,o::r" runs the AclT action on the ACL represented by the short text form u::rw,g::r,o::r. In words, it adds execute permission to the 1st entry of u::rw,g::r,o::r, producing u::rwx,g::r,o::r.

Synopsis

ACL initialization

data AclT m a Source #

Action to be performed on an ACL. The action contained in the transformer AclT can be executed in the base monad using one of the functions newACL, getFdACL, getFileACL, fromExt or fromText.

Instances

MonadTrans AclT Source # 

Methods

lift :: Monad m => m a -> AclT m a #

MonadTransControl AclT Source # 

Associated Types

type StT (AclT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run AclT -> m a) -> AclT m a #

restoreT :: Monad m => m (StT AclT a) -> AclT m a #

MonadBase b m => MonadBase b (AclT m) Source # 

Methods

liftBase :: b α -> AclT m α #

MonadBaseControl b m => MonadBaseControl b (AclT m) Source # 

Associated Types

type StM (AclT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (AclT m) b -> b a) -> AclT m a #

restoreM :: StM (AclT m) a -> AclT m a #

Monad m => Monad (AclT m) Source # 

Methods

(>>=) :: AclT m a -> (a -> AclT m b) -> AclT m b #

(>>) :: AclT m a -> AclT m b -> AclT m b #

return :: a -> AclT m a #

fail :: String -> AclT m a #

Functor m => Functor (AclT m) Source # 

Methods

fmap :: (a -> b) -> AclT m a -> AclT m b #

(<$) :: a -> AclT m b -> AclT m a #

MonadFix m => MonadFix (AclT m) Source # 

Methods

mfix :: (a -> AclT m a) -> AclT m a #

Applicative m => Applicative (AclT m) Source # 

Methods

pure :: a -> AclT m a #

(<*>) :: AclT m (a -> b) -> AclT m a -> AclT m b #

(*>) :: AclT m a -> AclT m b -> AclT m b #

(<*) :: AclT m a -> AclT m b -> AclT m a #

MonadIO m => MonadIO (AclT m) Source # 

Methods

liftIO :: IO a -> AclT m a #

Alternative m => Alternative (AclT m) Source # 

Methods

empty :: AclT m a #

(<|>) :: AclT m a -> AclT m a -> AclT m a #

some :: AclT m a -> AclT m [a] #

many :: AclT m a -> AclT m [a] #

MonadPlus m => MonadPlus (AclT m) Source # 

Methods

mzero :: AclT m a #

mplus :: AclT m a -> AclT m a -> AclT m a #

type StT AclT a Source # 
type StT AclT a
type StM (AclT m) a Source # 
type StM (AclT m) a = ComposeSt AclT m a

newACL :: MonadBaseControl IO m => Int -> AclT m a -> m a Source #

Run the given action on a newly created ACL with enough preallocated memory to hold n entries. Use createEntry to create entries in the preallocated memory.

Call to acl_init().

dupACL Source #

Arguments

:: MonadBaseControl IO m 
=> AclT m a

action to be run on the duplicate

-> AclT m a 

Create a copy of the current ACL and run the given action on the duplicate. For example

fromText "u::rw,g::r,o::r" $ dupACL (calcMask >> toText >>= lift . print) >> toText >>= lift . print

copies the ACL represented by u::rw,g::r,o::r to a new ACL, calculates and sets the permissions of Mask (see calcMask) in the newly created ACL and prints out the result. It also prints out the original ACL.

Call to acl_dup().

ACL entry manipulation

data EntryT m a Source #

Action to be performed on an ACL entry. In order to execute the action contained in the EntryT transformer in the base monad, EntryT must first be converted into AclT using one of the functions createEntry, getEntries or getEntry.

Instances

MonadTrans EntryT Source # 

Methods

lift :: Monad m => m a -> EntryT m a #

MonadTransControl EntryT Source # 

Associated Types

type StT (EntryT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run EntryT -> m a) -> EntryT m a #

restoreT :: Monad m => m (StT EntryT a) -> EntryT m a #

MonadBase b m => MonadBase b (EntryT m) Source # 

Methods

liftBase :: b α -> EntryT m α #

MonadBaseControl b m => MonadBaseControl b (EntryT m) Source # 

Associated Types

type StM (EntryT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (EntryT m) b -> b a) -> EntryT m a #

restoreM :: StM (EntryT m) a -> EntryT m a #

Monad m => Monad (EntryT m) Source # 

Methods

(>>=) :: EntryT m a -> (a -> EntryT m b) -> EntryT m b #

(>>) :: EntryT m a -> EntryT m b -> EntryT m b #

return :: a -> EntryT m a #

fail :: String -> EntryT m a #

Functor m => Functor (EntryT m) Source # 

Methods

fmap :: (a -> b) -> EntryT m a -> EntryT m b #

(<$) :: a -> EntryT m b -> EntryT m a #

MonadFix m => MonadFix (EntryT m) Source # 

Methods

mfix :: (a -> EntryT m a) -> EntryT m a #

Applicative m => Applicative (EntryT m) Source # 

Methods

pure :: a -> EntryT m a #

(<*>) :: EntryT m (a -> b) -> EntryT m a -> EntryT m b #

(*>) :: EntryT m a -> EntryT m b -> EntryT m b #

(<*) :: EntryT m a -> EntryT m b -> EntryT m a #

MonadIO m => MonadIO (EntryT m) Source # 

Methods

liftIO :: IO a -> EntryT m a #

Alternative m => Alternative (EntryT m) Source # 

Methods

empty :: EntryT m a #

(<|>) :: EntryT m a -> EntryT m a -> EntryT m a #

some :: EntryT m a -> EntryT m [a] #

many :: EntryT m a -> EntryT m [a] #

MonadPlus m => MonadPlus (EntryT m) Source # 

Methods

mzero :: EntryT m a #

mplus :: EntryT m a -> EntryT m a -> EntryT m a #

type StT EntryT a Source # 
type StT EntryT a
type StM (EntryT m) a Source # 
type StM (EntryT m) a = ComposeSt EntryT m a

createEntry :: MonadBase IO m => EntryT m a -> AclT m a Source #

Create a new entry in the ACL an run the given action on it. If necessary, the ACL will allocate memory for the new entry.

Call to acl_create_entry().

getEntries :: MonadBase IO m => [EntryT m a] -> ListT (AclT m) a Source #

Run the list of given actions on the list of entries of the ACL.

Warning: using setTag as one of the EntryTs of getEntries is not recommended, as it may rearrange the list of entries inside the ACL, yielding unexpected results.

Call to acl_get_entry().

getEntry :: MonadBase IO m => Int -> EntryT m a -> AclT m a Source #

Run the given action on the n-th entry of the ACL (entry enumeration begins from 0).

Call to acl_get_entry().

copyEntry :: MonadBase IO m => EntryT (EntryT m) () Source #

Copy the contents of an ACL entry to an existing ACL entry of a possibly different ACL. For example

fromText "u::rw,u:2:rwx,g::r,m:rwx,o::r" $ getEntry 1 $ fromText "u::rw,u:1:rw,u:8:rw,g::r,m:rwxo::r" (getEntry 2 copyEntry >> toText)

copies the 2nd entry of u::rw,u:2:rwx,g::r,m:rwx,o::r (namely u:2:rwx) into the 3rd entry of u::rw,u:1:rw,u:8:rw,g::r,m:rwxo::r (namely u:8:rw) and prints the result.

Call to acl_copy_entry().

deleteEntry :: MonadBase IO m => EntryT m () Source #

Delete the entry.

Call to acl_delete_entry().

Warning: no further action should be performed on this entry.

valid :: MonadBase IO m => AclT m Bool Source #

Run a validity check on the ACL (see acl_valid() in section 23.4.28 of IEEE Std 1003.1e).

Call to acl_valid().

data PermsetT m a Source #

Action to be performed on the permission set of an ACL entry. In order to execute the action contained in the PermsetT transformer in the base monad, PermsetT must first be converted into EntryT using changePermset, and then into AclT.

Instances

MonadTrans PermsetT Source # 

Methods

lift :: Monad m => m a -> PermsetT m a #

MonadTransControl PermsetT Source # 

Associated Types

type StT (PermsetT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run PermsetT -> m a) -> PermsetT m a #

restoreT :: Monad m => m (StT PermsetT a) -> PermsetT m a #

MonadBase b m => MonadBase b (PermsetT m) Source # 

Methods

liftBase :: b α -> PermsetT m α #

MonadBaseControl b m => MonadBaseControl b (PermsetT m) Source # 

Associated Types

type StM (PermsetT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (PermsetT m) b -> b a) -> PermsetT m a #

restoreM :: StM (PermsetT m) a -> PermsetT m a #

Monad m => Monad (PermsetT m) Source # 

Methods

(>>=) :: PermsetT m a -> (a -> PermsetT m b) -> PermsetT m b #

(>>) :: PermsetT m a -> PermsetT m b -> PermsetT m b #

return :: a -> PermsetT m a #

fail :: String -> PermsetT m a #

Functor m => Functor (PermsetT m) Source # 

Methods

fmap :: (a -> b) -> PermsetT m a -> PermsetT m b #

(<$) :: a -> PermsetT m b -> PermsetT m a #

MonadFix m => MonadFix (PermsetT m) Source # 

Methods

mfix :: (a -> PermsetT m a) -> PermsetT m a #

Applicative m => Applicative (PermsetT m) Source # 

Methods

pure :: a -> PermsetT m a #

(<*>) :: PermsetT m (a -> b) -> PermsetT m a -> PermsetT m b #

(*>) :: PermsetT m a -> PermsetT m b -> PermsetT m b #

(<*) :: PermsetT m a -> PermsetT m b -> PermsetT m a #

MonadIO m => MonadIO (PermsetT m) Source # 

Methods

liftIO :: IO a -> PermsetT m a #

Alternative m => Alternative (PermsetT m) Source # 

Methods

empty :: PermsetT m a #

(<|>) :: PermsetT m a -> PermsetT m a -> PermsetT m a #

some :: PermsetT m a -> PermsetT m [a] #

many :: PermsetT m a -> PermsetT m [a] #

MonadPlus m => MonadPlus (PermsetT m) Source # 

Methods

mzero :: PermsetT m a #

mplus :: PermsetT m a -> PermsetT m a -> PermsetT m a #

type StT PermsetT a Source # 
type StT PermsetT a
type StM (PermsetT m) a Source # 
type StM (PermsetT m) a = ComposeSt PermsetT m a

data Perm Source #

A single permission.

Constructors

Read 
Write 
Execute 

changePermset :: MonadBase IO m => PermsetT m a -> EntryT m a Source #

Change the permission set of the entry.

Call to acl_get_permset() and acl_set_permset().

addPerm :: MonadBase IO m => Perm -> PermsetT m () Source #

Add a specific permission.

Call to acl_add_perm().

calcMask :: MonadBase IO m => AclT m () Source #

Calculate and set the permissions associated with the Mask ACL entry of the ACL. The value of the new permissions is the union of the permissions granted by all entries of tag type Group, GroupObj, or User. If the ACL already contains a Mask entry, its permissions are overwritten; if it does not contain a Mask entry, one is added.

Call to acl_calc_mask().

clearPerms :: MonadBase IO m => PermsetT m () Source #

Clear all permissions from the permission set.

Call to acl_clear_perms().

deletePerm :: MonadBase IO m => Perm -> PermsetT m () Source #

Remove a specific permission.

Call to acl_delete_perm().

data Tag Source #

Tag type and qualifier of an ACL.

Constructors

UserObj 
User 

Fields

GroupObj 
Group 

Fields

Mask 
Other 
Undefined 

Instances

getTag :: MonadBase IO m => EntryT m Tag Source #

Get the entry's tag.

Call to acl_get_tag_type() and possibly acl_get_qualifier().

setTag :: MonadBase IO m => Tag -> EntryT m () Source #

Set the tag of the entry.

Call to acl_set_tag_type() and possibly acl_set_qualifier().

Warning: using setTag may rearrange the list of entries inside the ACL, yielding unexpected results when used together with getEntries.

Get, set and delete ACLs from a file

data Type Source #

The type of an ACL (see section 23.1.3 of IEEE Std 1003.1e).

Constructors

Access 
Default 

deleteDefaultACL :: FilePath -> IO () Source #

Delete the default ACL from a directory.

Call to acl_delete_def_file().

getFdACL :: MonadBaseControl IO m => Fd -> AclT m a -> m a Source #

Run the action on the ACL of the given file descriptor.

Call to acl_get_fd().

getFileACL :: MonadBaseControl IO m => FilePath -> Type -> AclT m a -> m a Source #

Run the action on the ACL of type Type of the given file.

Call to acl_get_file().

setFdACL :: MonadBase IO m => Fd -> AclT m () Source #

Set the ACL of the given file descriptor.

Call to acl_set_fd().

setFileACL :: MonadBase IO m => FilePath -> Type -> AclT m () Source #

Set the ACL of type Type of the given file.

Call to acl_set_file().

ACL format translation

data ExtRepr Source #

The external representation of an ACL is an unspecified binary format stored in a contiguous portion of memory.

copyExt :: MonadBase IO m => AclT m ExtRepr Source #

Return the external representation of the ACL.

Call to acl_copy_ext() and acl_size().

fromExt :: MonadBaseControl IO m => ExtRepr -> AclT m a -> m a Source #

Run the given action on an ACL created according to the given external representation.

Call to acl_copy_int().

fromText :: MonadBaseControl IO m => String -> AclT m a -> m a Source #

Run the given action on an ACL created according to the given textual representation (both the Long Text Form and Short Text Form are accepted).

Call to acl_from_text().

toText :: MonadBase IO m => AclT m String Source #

Return the Long Text Form of the ACL (section 23.3.1 of IEEE Std 1003.1e).

Call to acl_to_text().