Process.hsc 1005 B

1234567891011121314151617181920212223242526272829303132
  1. {-# LANGUAGE Safe #-}
  2. module System.OpenBSD.Process ( pledge ) where
  3. import Foreign
  4. import Foreign.C
  5. import System.Posix.Internals ( withFilePath )
  6. -- | This function provides an interface to the OpenBSD
  7. -- <http://man.openbsd.org/OpenBSD-current/man2/pledge.2 pledge(2)>
  8. -- system call.
  9. --
  10. -- Passing 'Nothing' to the promises or paths arguments has the same
  11. -- effect as passing NULL to the corresponding arguments of the system
  12. -- call (i.e. not changing the current value).
  13. pledge :: Maybe String -> Maybe [FilePath] -> IO ()
  14. pledge promises paths =
  15. maybeWith withCString promises $ \cproms ->
  16. maybeWith withPaths2Array0 paths $ \paths_arr ->
  17. throwErrnoIfMinus1_ "pledge" (c_pledge cproms paths_arr)
  18. withPaths2Array0 :: [FilePath] -> (Ptr (Ptr CChar) -> IO a) -> IO a
  19. withPaths2Array0 paths f =
  20. withMany withFilePath paths $ \cstrs ->
  21. withArray0 nullPtr cstrs $ \paths_arr ->
  22. f paths_arr
  23. foreign import ccall unsafe "unistd.h pledge"
  24. c_pledge :: CString -> Ptr CString -> IO CInt