Safe Haskell | None |
---|
System.Process.Voyeur
Contents
Description
This package provides bindings to libvoyeur, a library for observing the private activity of processes. Libvoyeur observes a child process and all of its descendants, so it works even when the child process calls out to other processes to do the actual work.
To observe a process, use withVoyeur
to create an
VoyeurContext
, then register handlers for the events you want
to observe using functions like observeExec
. When you've
set up all your handlers, use prepareEnvironment
to create a
special environment that will inject libvoyeur code into the
child process, and pass that environment to a function like
runProcess
. Finally, pass the resulting ProcessHandle
or ProcessID
to startObserving
, and your handlers will be
called as events happen.
A simple program that prints a message every time a child process opened a file might look like this:
import Control.Monad import Data.Maybe import System.Environment import System.Process import System.Process.Voyeur main = do (program : args) <- getArgs withVoyeur $ \ctx -> do -- Set up a handler. observeOpen ctx defaultOpenFlags $ \path _ _ _ _ pid -> putStrLn $ show pid ++ " opened " ++ show path -- Set up the environment. curEnv <- getEnvironment newEnv <- prepareEnvironment ctx curEnv when (isJust newEnv) $ do -- Start the child process. handle <- runProcess program args Nothing newEnv Nothing Nothing Nothing -- Observe it! startObserving only returns when the child process -- exits, so we don't need to wait. void $ startObserving ctx handle
A larger example program is included with the source code to this package.
- withVoyeur :: (VoyeurContext -> IO a) -> IO a
- prepareEnvironment :: VoyeurContext -> [(String, String)] -> IO (Maybe [(String, String)])
- startObserving :: HasPid a => VoyeurContext -> a -> IO ExitCode
- data ObserveExecFlags = ObserveExecFlags {
- observeExecCWD :: !Bool
- observeExecEnv :: !Bool
- observeExecPath :: !Bool
- observeExecNoAccess :: !Bool
- defaultExecFlags :: ObserveExecFlags
- type ObserveExecHandler = ByteString -> [ByteString] -> [(ByteString, ByteString)] -> ByteString -> ByteString -> ProcessID -> ProcessID -> IO ()
- observeExec :: VoyeurContext -> ObserveExecFlags -> ObserveExecHandler -> IO ()
- type ObserveExitHandler = ExitCode -> ProcessID -> ProcessID -> IO ()
- observeExit :: VoyeurContext -> ObserveExitHandler -> IO ()
- data ObserveOpenFlags = ObserveOpenFlags {
- observeOpenCWD :: !Bool
- defaultOpenFlags :: ObserveOpenFlags
- type ObserveOpenHandler = ByteString -> Int -> FileMode -> ByteString -> Int -> ProcessID -> IO ()
- observeOpen :: VoyeurContext -> ObserveOpenFlags -> ObserveOpenHandler -> IO ()
- type ObserveCloseHandler = Int -> Int -> ProcessID -> IO ()
- observeClose :: VoyeurContext -> ObserveCloseHandler -> IO ()
- data VoyeurContext
- class HasPid a
Observing a process
withVoyeur :: (VoyeurContext -> IO a) -> IO aSource
Creates a VoyeurContext
and runs an IO action that observes
a process using it.
Arguments
:: VoyeurContext | The context. |
-> [(String, String)] | The environment you want to use. |
-> IO (Maybe [(String, String)]) | A modified version of that
environment, or |
Prepares an environment for a child process you want to observe.
prepareEnvironment
starts the server component of libvoyeur and
adds or modifies environment variables as necessary to inject code
into the child process you're about to create and make sure it can
connect to the server.
Generally after calling prepareEnvironment
, you'll want to start
the child process using the returned environment, and then call
startObserving
to begin receiving events.
If something goes wrong, prepareEnvironment
will return Nothing
.
Arguments
:: HasPid a | |
=> VoyeurContext | The context. |
-> a | The child process to observe. |
-> IO ExitCode | The exit status of the child process. |
Start observing a child process. Your handlers will be called
while the process runs. Note that no handlers will be called if
you didn't start the process with an environment produced by
prepareEnvironment
.
When the child process exits, startObserving
will terminate the
server component of libvoyeur and return. This means that
startObserving
implicitly waits for the child process, so you
don't need to do this on your own.
Observing 'exec' calls
data ObserveExecFlags Source
Flags for observing exec
calls.
Constructors
ObserveExecFlags | |
Fields
|
Instances
defaultExecFlags :: ObserveExecFlagsSource
Default flags which observe the minimum amount of information.
Arguments
= ByteString | The file being executed. |
-> [ByteString] | The arguments. |
-> [(ByteString, ByteString)] | The environment (if requested). |
-> ByteString | The value of |
-> ByteString | The working directory (if requested). |
-> ProcessID | The new process ID. |
-> ProcessID | The parent process ID. |
-> IO () |
A handler for exec
calls.
Arguments
:: VoyeurContext | The context. |
-> ObserveExecFlags | Flags controlling what will be observed. |
-> ObserveExecHandler | A handler for observed 'exec*' events. |
-> IO () |
Observe calls to the exec
and posix_spawn
families of functions.
Observing 'exit' calls
Arguments
= ExitCode | The exit status. |
-> ProcessID | The process ID of the exiting process. |
-> ProcessID | The parent process ID of the exiting process. |
-> IO () |
A handler for 'exit' calls.
Arguments
:: VoyeurContext | The context. |
-> ObserveExitHandler | A handler for observed 'exit' events. |
-> IO () |
Observe calls to the 'exit' family of functions.
Observing 'open' calls
data ObserveOpenFlags Source
Flags for observing 'open' calls.
Constructors
ObserveOpenFlags | |
Fields
|
Instances
defaultOpenFlags :: ObserveOpenFlagsSource
Default flags which observe the minimum amount of information.
Arguments
= ByteString | The file being opened. |
-> Int | The flags used to open the file. |
-> FileMode | The mode. Only meaningful if O_CREAT was specified. |
-> ByteString | The working directory (if requested). |
-> Int | The return value of 'open'. May be a file descriptor or an error value. |
-> ProcessID | The process ID of the observed process. |
-> IO () |
A handler for 'open' calls.
Arguments
:: VoyeurContext | The context. |
-> ObserveOpenFlags | Flags controlling what will be observed. |
-> ObserveOpenHandler | A handler for observed 'open' events. |
-> IO () |
Observe calls to 'open'.
Observing 'close' calls
type ObserveCloseHandlerSource
Arguments
= Int | The file descriptor being closed. |
-> Int | The return value of 'close'. |
-> ProcessID | The process ID of the observed process. |
-> IO () |
A handler for 'close' calls.
Arguments
:: VoyeurContext | The context. |
-> ObserveCloseHandler | A handler for observed 'close' events. |
-> IO () |
Observe calls to 'close'.
Types
data VoyeurContext Source
The context libvoyeur uses to store its state.