Z-IO-0.3.0.0: Simple and high performance IO toolkit for Haskell
Copyright(c) Dong Han 2018-2020
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.Process

Description

This module provides process utilities.

import Control.Concurrent.MVar
import Z.IO.Process

> readProcessText defaultProcessOptions{processFile = "cat"} "hello world"
("hello world","",ExitSuccess)
Synopsis

Documentation

initProcess :: ProcessOptions -> Resource (Maybe UVStream, Maybe UVStream, Maybe UVStream, TVar ProcessState) Source #

Resource spawn processes.

Return a resource spawn processes, when initiated return the (stdin, stdout, stderr, pstate) tuple, std streams are created when pass ProcessCreate option, otherwise will be Nothing, pstate will be updated to ProcessExited automatically when the process exits.

A cleanup thread will be started when you finish using the process resource, to close any std stream created during spawn.

initProcess defaultProcessOptions{
      processFile="your program"
  ,   processStdStreams = (ProcessCreate, ProcessCreate, ProcessCreate)
  } $ (stdin, stdout, stderr, pstate) -> do
  ... -- read or write from child process's std stream, will clean up automatically
  waitProcessExit pstate  -- wait for process exit on current thread.

readProcess Source #

Arguments

:: HasCallStack 
=> ProcessOptions

processStdStreams options are ignored

-> Bytes

stdin

-> IO (Bytes, Bytes, ExitCode)

stdout, stderr, exit code

Spawn a processe with given input.

Child process's stdout and stderr output are collected, return with exit code.

readProcessText Source #

Arguments

:: HasCallStack 
=> ProcessOptions

processStdStreams options are ignored

-> Text

stdin

-> IO (Text, Text, ExitCode)

stdout, stderr, exit code

Spawn a processe with given UTF8 textual input.

Child process's stdout and stderr output are collected as UTF8 bytes, return with exit code.

data ProcessOptions Source #

Constructors

ProcessOptions 

Fields

Instances

Instances details
Eq ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Read ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Show ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep ProcessOptions :: Type -> Type #

ToValue ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

Print ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep ProcessOptions Source # 
Instance details

Defined in Z.IO.UV.FFI

defaultProcessOptions :: ProcessOptions Source #

Default process options, start "./main" with no arguments, redirect all std streams to /dev/null.

data ProcessStdStream Source #

Constructors

ProcessIgnore

redirect process std stream to /dev/null

ProcessCreate

create a new std stream

ProcessInherit FD

pass an existing FD to child process as std stream

Instances

Instances details
Eq ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Read ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Show ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep ProcessStdStream :: Type -> Type #

ToValue ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

EncodeJSON ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

FromValue ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

Print ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep ProcessStdStream Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep ProcessStdStream = D1 ('MetaData "ProcessStdStream" "Z.IO.UV.FFI" "Z-IO-0.3.0.0-8xea6on533JEAR14LdkAE6" 'False) (C1 ('MetaCons "ProcessIgnore" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ProcessCreate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ProcessInherit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FD))))

data ProcessState Source #

Process state

Instances

Instances details
Eq ProcessState Source # 
Instance details

Defined in Z.IO.Process

Ord ProcessState Source # 
Instance details

Defined in Z.IO.Process

Show ProcessState Source # 
Instance details

Defined in Z.IO.Process

Generic ProcessState Source # 
Instance details

Defined in Z.IO.Process

Associated Types

type Rep ProcessState :: Type -> Type #

ToValue ProcessState Source # 
Instance details

Defined in Z.IO.Process

EncodeJSON ProcessState Source # 
Instance details

Defined in Z.IO.Process

FromValue ProcessState Source # 
Instance details

Defined in Z.IO.Process

Print ProcessState Source # 
Instance details

Defined in Z.IO.Process

type Rep ProcessState Source # 
Instance details

Defined in Z.IO.Process

type Rep ProcessState = D1 ('MetaData "ProcessState" "Z.IO.Process" "Z-IO-0.3.0.0-8xea6on533JEAR14LdkAE6" 'False) (C1 ('MetaCons "ProcessRunning" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PID)) :+: C1 ('MetaCons "ProcessExited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExitCode)))

data ExitCode #

Defines the exit codes that a program can return.

Constructors

ExitSuccess

indicates successful termination;

ExitFailure Int

indicates program failure with an exit code. The exact interpretation of the code is operating-system dependent. In particular, some values may be prohibited (e.g. 0 on a POSIX-compliant system).

Instances

Instances details
Eq ExitCode 
Instance details

Defined in GHC.IO.Exception

Ord ExitCode 
Instance details

Defined in GHC.IO.Exception

Read ExitCode 
Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

ToValue ExitCode 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: ExitCode -> Value #

EncodeJSON ExitCode 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: ExitCode -> Builder () #

FromValue ExitCode 
Instance details

Defined in Z.Data.JSON.Base

Print ExitCode 
Instance details

Defined in Z.Data.Text.Print

Methods

toUTF8BuilderP :: Int -> ExitCode -> Builder () #

Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

type Rep ExitCode 
Instance details

Defined in GHC.IO.Exception

type Rep ExitCode = D1 ('MetaData "ExitCode" "GHC.IO.Exception" "base" 'False) (C1 ('MetaCons "ExitSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExitFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

waitProcessExit :: TVar ProcessState -> IO ExitCode Source #

Wait until process exit and return the ExitCode.

getProcessPID :: TVar ProcessState -> IO (Maybe PID) Source #

Get process PID if process is running.

killPID :: HasCallStack => PID -> Signal -> IO () Source #

Send signals to process.

getPriority :: HasCallStack => PID -> IO Priority Source #

Retrieves the scheduling priority of the process specified by pid.

The returned value of priority is between -20 (high priority) and 19 (low priority). On Windows, the returned priority will equal one of the PRIORITY constants.

setPriority :: HasCallStack => PID -> Priority -> IO () Source #

Sets the scheduling priority of the process specified by pid.

The priority value range is between -20 (high priority) and 19 (low priority). The constants PRIORITY_LOW, PRIORITY_BELOW_NORMAL, PRIORITY_NORMAL, PRIORITY_ABOVE_NORMAL, PRIORITY_HIGH, and PRIORITY_HIGHEST are also provided for convenience.

internal

spawn :: HasCallStack => ProcessOptions -> IO (Maybe UVStream, Maybe UVStream, Maybe UVStream, TVar ProcessState) Source #

Spawn a new thread

Please manually close child process's std stream(if any) after process exits.

Constant

ProcessFlag

pattern PROCESS_SETUID :: ProcessFlag Source #

Set the child process' user id.

This is not supported on Windows, uv_spawn() will fail and set the error to UV_ENOTSUP.

pattern PROCESS_SETGID :: ProcessFlag Source #

Set the child process' user id.

This is not supported on Windows, uv_spawn() will fail and set the error to UV_ENOTSUP.

pattern PROCESS_WINDOWS_VERBATIM_ARGUMENTS :: ProcessFlag Source #

Do not wrap any arguments in quotes, or perform any other escaping, when converting the argument list into a command line string.

This option is only meaningful on Windows systems. On Unix it is silently ignored.

pattern PROCESS_DETACHED :: ProcessFlag Source #

Spawn the child process in a detached state

This will make it a process group leader, and will effectively enable the child to keep running after the parent exits.

pattern PROCESS_WINDOWS_HIDE_CONSOLE :: ProcessFlag Source #

Hide the subprocess console window that would normally be created.

This option is only meaningful on Windows systems. On Unix it is silently ignored.

pattern PROCESS_WINDOWS_HIDE_GUI :: ProcessFlag Source #

Hide the subprocess GUI window that would normally be created.

This option is only meaningful on Windows systems. On Unix it is silently ignored.

Signal

type Signal = CInt #

pattern SIGTERM :: Signal Source #

pattern SIGINT :: Signal Source #

pattern SIGKILL :: Signal Source #

pattern SIGHUP :: Signal Source #

Priority