| Copyright | © 2013-2014 Nicola Squartini |
|---|---|
| License | BSD3 |
| Maintainer | Nicola Squartini <tensor5@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
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 <-->AclTacl_entry_t <-->EntryTacl_permset_t <-->PermsetT
A common usage pattern is to modify the permset of an entry inside an ACL. This is done in three steps:
- convert the
modification of permset into anPermsetTm amodification of entry;EntryTm a - convert the
into anEntryTm amodification of ACL;AclTm a - execute the
in the base monadAclTm am.
For example in
fromText"u::rw,g::r,o::r" $getEntry0 $changePermset$addPermExecute
is the addPerm Execute that adds the execute permission,
PermsetT converts changePermset into PermsetT, EntryT
modifies the 1st entry of the ACL according to the action contained in
getEntry 0 (thus converts EntryT into EntryT), and finally AclT runs the fromText
"u::rw,g::r,o::r" action on the ACL represented by the
short text form AclTu::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.
- data AclT m a
- newACL :: MonadBaseControl IO m => Int -> AclT m a -> m a
- dupACL :: MonadBaseControl IO m => AclT m a -> AclT m a
- data EntryT m a
- createEntry :: MonadBase IO m => EntryT m a -> AclT m a
- getEntries :: MonadBase IO m => [EntryT m a] -> ListT (AclT m) a
- getEntry :: MonadBase IO m => Int -> EntryT m a -> AclT m a
- copyEntry :: MonadBase IO m => EntryT (EntryT m) ()
- deleteEntry :: MonadBase IO m => EntryT m ()
- valid :: MonadBase IO m => AclT m Bool
- data PermsetT m a
- data Perm
- changePermset :: MonadBase IO m => PermsetT m a -> EntryT m a
- addPerm :: MonadBase IO m => Perm -> PermsetT m ()
- calcMask :: MonadBase IO m => AclT m ()
- clearPerms :: MonadBase IO m => PermsetT m ()
- deletePerm :: MonadBase IO m => Perm -> PermsetT m ()
- data Tag
- getTag :: MonadBase IO m => EntryT m Tag
- setTag :: MonadBase IO m => Tag -> EntryT m ()
- data Type
- deleteDefaultACL :: FilePath -> IO ()
- getFdACL :: MonadBaseControl IO m => Fd -> AclT m a -> m a
- getFileACL :: MonadBaseControl IO m => FilePath -> Type -> AclT m a -> m a
- setFdACL :: MonadBase IO m => Fd -> AclT m ()
- setFileACL :: MonadBase IO m => FilePath -> Type -> AclT m ()
- data ExtRepr
- copyExt :: MonadBase IO m => AclT m ExtRepr
- fromExt :: MonadBaseControl IO m => ExtRepr -> AclT m a -> m a
- fromText :: MonadBaseControl IO m => String -> AclT m a -> m a
- toText :: MonadBase IO m => AclT m String
ACL initialization
Action to be performed on an ACL. The action contained in the transformer
can be executed in the base monad using one of the functions
AclT, newACL, getFdACL, getFileACL or fromExt.fromText
Instances
| MonadTrans AclT Source # | |
| MonadTransControl AclT Source # | |
| MonadBase b m => MonadBase b (AclT m) Source # | |
| MonadBaseControl b m => MonadBaseControl b (AclT m) Source # | |
| Monad m => Monad (AclT m) Source # | |
| Functor m => Functor (AclT m) Source # | |
| MonadFix m => MonadFix (AclT m) Source # | |
| Applicative m => Applicative (AclT m) Source # | |
| MonadIO m => MonadIO (AclT m) Source # | |
| Alternative m => Alternative (AclT m) Source # | |
| MonadPlus m => MonadPlus (AclT m) Source # | |
| type StT AclT a Source # | |
| type StM (AclT m) a Source # | |
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 to create entries in the
preallocated memory.createEntry
Call to acl_init().
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.toText>>=lift.
copies the ACL represented by u::rw,g::r,o::r to a new ACL, calculates and
sets the permissions of (see Mask) in the newly created ACL
and prints out the result. It also prints out the original ACL.calcMask
Call to acl_dup().
ACL entry manipulation
Action to be performed on an ACL entry. In order to execute the action
contained in the transformer in the base monad, EntryT must
first be converted into EntryT using one of the functions AclT,
createEntry or getEntries.getEntry
Instances
| MonadTrans EntryT Source # | |
| MonadTransControl EntryT Source # | |
| MonadBase b m => MonadBase b (EntryT m) Source # | |
| MonadBaseControl b m => MonadBaseControl b (EntryT m) Source # | |
| Monad m => Monad (EntryT m) Source # | |
| Functor m => Functor (EntryT m) Source # | |
| MonadFix m => MonadFix (EntryT m) Source # | |
| Applicative m => Applicative (EntryT m) Source # | |
| MonadIO m => MonadIO (EntryT m) Source # | |
| Alternative m => Alternative (EntryT m) Source # | |
| MonadPlus m => MonadPlus (EntryT m) Source # | |
| type StT EntryT a Source # | |
| type StM (EntryT m) a Source # | |
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 as one of the setTags of EntryT is
not recommended, as it may rearrange the list of entries inside the ACL,
yielding unexpected results.getEntries
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" $getEntry1 $fromText"u::rw,u:1:rw,u:8:rw,g::r,m:rwxo::r" (getEntry2copyEntry>>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().
Action to be performed on the permission set of an ACL entry. In order to
execute the action contained in the transformer in the base
monad, PermsetT must first be converted into PermsetT using
EntryT, and then into changePermset.AclT
Instances
| MonadTrans PermsetT Source # | |
| MonadTransControl PermsetT Source # | |
| MonadBase b m => MonadBase b (PermsetT m) Source # | |
| MonadBaseControl b m => MonadBaseControl b (PermsetT m) Source # | |
| Monad m => Monad (PermsetT m) Source # | |
| Functor m => Functor (PermsetT m) Source # | |
| MonadFix m => MonadFix (PermsetT m) Source # | |
| Applicative m => Applicative (PermsetT m) Source # | |
| MonadIO m => MonadIO (PermsetT m) Source # | |
| Alternative m => Alternative (PermsetT m) Source # | |
| MonadPlus m => MonadPlus (PermsetT m) Source # | |
| type StT PermsetT a Source # | |
| type StM (PermsetT m) a Source # | |
A single permission.
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 ACL entry of
the ACL. The value of the new permissions is the union of the permissions
granted by all entries of tag type Mask, Group, or GroupObj. If
the ACL already contains a User entry, its permissions are overwritten;
if it does not contain a Mask entry, one is added.Mask
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().
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 may rearrange the list of entries inside the ACL,
yielding unexpected results when used together with setTag.getEntries
Get, set and delete ACLs from a file
The type of an ACL (see section 23.1.3 of IEEE Std 1003.1e).
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 of the given file.Type
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 of the given file.Type
Call to acl_set_file().
ACL format translation
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().