heftia-effects-0.7.0.0: higher-order algebraic effects done right
Copyright(c) 2024 Sayo contributors
(c) The University of Glasgow 2004-2008
LicenseMPL-2.0 (see the LICENSE file) AND BSD-3-Clause
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Control.Monad.Hefty.Concurrent.Subprocess

Description

Effects for well-typed subprocess.

Synopsis

Documentation

data CreateProcess (p :: SubprocMode) where Source #

Constructors

CreateProcess 

Fields

  • :: forall (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle). { cmdspec :: CmdSpec

    Executable & arguments, or shell command. If cwd is Nothing, relative paths are resolved with respect to the current working directory. If cwd is provided, it is implementation-dependent whether relative paths are resolved with respect to cwd or the current working directory, so absolute paths should be used to ensure portability.

  •    , stdin :: StdStream i

    How to determine stdin

  •    , stdout :: StdStream o

    How to determine stdout

  •    , stderr :: StdStream e

    How to determine stderr

  •    , subprocLifecycle :: LifecycleMode lp

    Whether to kill the subprocess or wait when the scope's computation finishes first.

  •    , scopeLifecycle :: LifecycleMode ls

    Whether to cancel the scope's computation or wait when the subprocess finishes first.

  •    , cwd :: Maybe FilePath

    Optional path to the working directory for the new process

  •    , env :: Maybe [(String, String)]

    Optional environment (otherwise inherit from the current process)

  •    , closeFds :: Bool

    Close all file descriptors except stdin, stdout and stderr in the new process (on Windows, only works if std_in, std_out, and std_err are all Inherit). This implementation will call close on every fd from 3 to the maximum of open files, which can be slow for high maximum of open files. XXX verify what happens with fds in nodejs child processes

  •    , createGroup :: Bool

    Create a new process group. On JavaScript this also creates a new session.

  •    , delegateCtlc :: Bool

    Delegate control-C handling. Use this for interactive console processes to let them handle control-C themselves (see below for details).

  •    , detachConsole :: Bool

    Use the windows DETACHED_PROCESS flag when creating the process; does nothing on other platforms.

  •    , createNewConsole :: Bool

    Use the windows CREATE_NEW_CONSOLE flag when creating the process; does nothing on other platforms.

  •    , newSession :: Bool

    Use posix setsid to start the new process in a new session; starts process in a new session on JavaScript; does nothing on other platforms.

  •    , childGroup :: Maybe GroupID

    Use posix setgid to set child process's group id; works for JavaScript when system running nodejs is posix. does nothing on other platforms.

  •    , childUser :: Maybe UserID

    Use posix setuid to set child process's user id; works for JavaScript when system running nodejs is posix. does nothing on other platforms.

  •    , useProcessJobs :: Bool

    On Windows systems this flag indicates that we should wait for the entire process tree to finish before unblocking. On POSIX systems this flag is ignored. See $exec-on-windows for details.

  •    } -> CreateProcess ('SubprocMode i o e lp ls)
     

data Lifecycle Source #

Constructors

Kill 
Wait 

data StdStream (s :: StreamMode) where Source #

Constructors

CreatePipe 

Fields

  • :: StdStream 'Piped

    Create a new pipe. The returned Handle will use the default encoding and newline translation mode (just like Handles created by openFile).

Inherit 

Fields

UseHandle 

Fields

NoStream 

Fields

  • :: StdStream 'NoPipe

    Close the stream's file descriptor without passing a Handle. On POSIX systems this may lead to strange behavior in the child process because attempting to read or write after the file has been closed throws an error. This should only be used with child processes that don't use the file descriptor at all. If you wish to ignore the child process's output you should either create a pipe and drain it manually or pass a Handle that writes to /dev/null.

data Subprocess (p :: SubprocMode) (a :: Type -> Type) b where Source #

Constructors

WriteStdin :: forall (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (a :: Type -> Type). ByteString -> Subprocess ('SubprocMode 'Piped o e lp 'Kill) a () 
TryWriteStdin :: forall (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) (a :: Type -> Type). ByteString -> Subprocess ('SubprocMode 'Piped o e lp ls) a Bool 
ReadStdout :: forall (i :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) (a :: Type -> Type). Subprocess ('SubprocMode i 'Piped e lp ls) a ByteString 
ReadStderr :: forall (i :: StreamMode) (o :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) (a :: Type -> Type). Subprocess ('SubprocMode i o 'Piped lp ls) a ByteString 
PollSubproc :: forall (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (a :: Type -> Type). Subprocess ('SubprocMode i o e lp 'Wait) a (Maybe ExitCode) 

Instances

Instances details
FirstOrder (Subprocess p) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

PolyHFunctor (Subprocess p) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

HFunctor (Subprocess p) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

Methods

hfmap :: (forall x. f x -> g x) -> Subprocess p f a -> Subprocess p g a #

type FormOf (Subprocess p) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

type LabelOf (Subprocess p) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

type OrderOf (Subprocess p) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

data StreamMode Source #

Constructors

Piped 
NoPipe 

data SubprocResult (p :: SubprocMode) a where Source #

Constructors

RaceResult :: forall a (i :: StreamMode) (o :: StreamMode) (e :: StreamMode). Either ExitCode a -> SubprocResult ('SubprocMode i o e 'Kill 'Kill) a 
SubprocResult :: forall a (i :: StreamMode) (o :: StreamMode) (e :: StreamMode). ExitCode -> Maybe a -> SubprocResult ('SubprocMode i o e 'Wait 'Kill) a 
ScopeResult :: forall a (i :: StreamMode) (o :: StreamMode) (e :: StreamMode). Maybe ExitCode -> a -> SubprocResult ('SubprocMode i o e 'Kill 'Wait) a 
SubprocScopeResult :: forall a (i :: StreamMode) (o :: StreamMode) (e :: StreamMode). ExitCode -> a -> SubprocResult ('SubprocMode i o e 'Wait 'Wait) a 

Instances

Instances details
Show a => Show (SubprocResult p a) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

Eq a => Eq (SubprocResult p a) Source # 
Instance details

Defined in Control.Monad.Hefty.Concurrent.Subprocess

Methods

(==) :: SubprocResult p a -> SubprocResult p a -> Bool #

(/=) :: SubprocResult p a -> SubprocResult p a -> Bool #

runSubprocIO :: forall (es :: [Effect]) a. (UnliftIO :> es, Emb IO :> es, Emb IO :> RemoveExps es, WeakenExps es) => Eff (SubprocProvider (RemoveExps es) ': es) a -> Eff es a Source #

commandWith :: forall (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle). CmdSpec -> StdStream i -> StdStream o -> StdStream e -> LifecycleMode lp -> LifecycleMode ls -> CreateProcess ('SubprocMode i o e lp ls) Source #

toRawStdStream :: forall (pipe :: StreamMode). StdStream pipe -> StdStream Source #

writeStdin :: forall (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Subprocess ('SubprocMode 'Piped o e lp 'Kill) :> es) => ByteString -> f () Source #

writeStdin' :: forall {k} (key :: k) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Subprocess ('SubprocMode 'Piped o e lp 'Kill)) es) => ByteString -> f () Source #

writeStdin'' :: forall {k} (tag :: k) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Subprocess ('SubprocMode 'Piped o e lp 'Kill)) :> es) => ByteString -> f () Source #

writeStdin'_ :: forall (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Subprocess ('SubprocMode 'Piped o e lp 'Kill)) es) => ByteString -> f () Source #

tryWriteStdin :: forall (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Subprocess ('SubprocMode 'Piped o e lp ls) :> es) => ByteString -> f Bool Source #

tryWriteStdin' :: forall {k} (key :: k) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Subprocess ('SubprocMode 'Piped o e lp ls)) es) => ByteString -> f Bool Source #

tryWriteStdin'' :: forall {k} (tag :: k) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Subprocess ('SubprocMode 'Piped o e lp ls)) :> es) => ByteString -> f Bool Source #

tryWriteStdin'_ :: forall (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Subprocess ('SubprocMode 'Piped o e lp ls)) es) => ByteString -> f Bool Source #

readStdout :: forall (i :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Subprocess ('SubprocMode i 'Piped e lp ls) :> es) => f ByteString Source #

readStdout' :: forall {k} (key :: k) (i :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Subprocess ('SubprocMode i 'Piped e lp ls)) es) => f ByteString Source #

readStdout'' :: forall {k} (tag :: k) (i :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Subprocess ('SubprocMode i 'Piped e lp ls)) :> es) => f ByteString Source #

readStdout'_ :: forall (i :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Subprocess ('SubprocMode i 'Piped e lp ls)) es) => f ByteString Source #

readStderr :: forall (i :: StreamMode) (o :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Subprocess ('SubprocMode i o 'Piped lp ls) :> es) => f ByteString Source #

readStderr' :: forall {k} (key :: k) (i :: StreamMode) (o :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Subprocess ('SubprocMode i o 'Piped lp ls)) es) => f ByteString Source #

readStderr'' :: forall {k} (tag :: k) (i :: StreamMode) (o :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Subprocess ('SubprocMode i o 'Piped lp ls)) :> es) => f ByteString Source #

readStderr'_ :: forall (i :: StreamMode) (o :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Subprocess ('SubprocMode i o 'Piped lp ls)) es) => f ByteString Source #

pollSubproc :: forall (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Subprocess ('SubprocMode i o e lp 'Wait) :> es) => f (Maybe ExitCode) Source #

pollSubproc' :: forall {k} (key :: k) (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (Subprocess ('SubprocMode i o e lp 'Wait)) es) => f (Maybe ExitCode) Source #

pollSubproc'' :: forall {k} (tag :: k) (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (Subprocess ('SubprocMode i o e lp 'Wait)) :> es) => f (Maybe ExitCode) Source #

pollSubproc'_ :: forall (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (Subprocess ('SubprocMode i o e lp 'Wait)) es) => f (Maybe ExitCode) Source #

data CmdSpec #

Constructors

ShellCommand String

A command line to execute using the shell

RawCommand FilePath [String]

The name of an executable with a list of arguments

The FilePath argument names the executable, and is interpreted according to the platform's standard policy for searching for executables. Specifically:

  • on Unix systems the execvp(3) semantics is used, where if the executable filename does not contain a slash (/) then the PATH environment variable is searched for the executable.
  • on Windows systems the Win32 CreateProcess semantics is used. Briefly: if the filename does not contain a path, then the directory containing the parent executable is searched, followed by the current directory, then some standard locations, and finally the current PATH. An .exe extension is added if the filename does not already have an extension. For full details see the documentation for the Windows SearchPath API.

Windows does not have a mechanism for passing multiple arguments. When using RawCommand on Windows, the command line is serialised into a string, with arguments quoted separately. Command line parsing is up individual programs, so the default behaviour may not work for some programs. If you are not getting the desired results, construct the command line yourself and use ShellCommand.

Instances

Instances details
IsString CmdSpec

construct a ShellCommand from a string literal

Since: process-1.2.1.0

Instance details

Defined in System.Process.Common

Methods

fromString :: String -> CmdSpec #

Show CmdSpec 
Instance details

Defined in System.Process.Common

Eq CmdSpec 
Instance details

Defined in System.Process.Common

Methods

(==) :: CmdSpec -> CmdSpec -> Bool #

(/=) :: CmdSpec -> CmdSpec -> Bool #

type GroupID = CGid #

type UserID = CUid #

data Handle #

Haskell defines operations to read and write characters from and to files, represented by values of type Handle. Each value of this type is a handle: a record used by the Haskell run-time system to manage I/O with file system objects. A handle has at least the following properties:

  • whether it manages input or output or both;
  • whether it is open, closed or semi-closed;
  • whether the object is seekable;
  • whether buffering is disabled, or enabled on a line or block basis;
  • a buffer (whose length may be zero).

Most handles will also have a current I/O position indicating where the next input or output operation will occur. A handle is readable if it manages only input or both input and output; likewise, it is writable if it manages only output or both input and output. A handle is open when first allocated. Once it is closed it can no longer be used for either input or output, though an implementation cannot re-use its storage while references remain to it. Handles are in the Show and Eq classes. The string produced by showing a handle is system dependent; it should include enough information to identify the handle for debugging. A handle is equal according to == only to itself; no attempt is made to compare the internal state of different handles for equality.

Instances

Instances details
Show Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Eq Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Methods

(==) :: Handle -> Handle -> Bool #

(/=) :: Handle -> Handle -> Bool #

data ExitCode #

Defines the exit codes that a program can return.

Instances

Instances details
Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

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)))

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Read ExitCode 
Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

NFData ExitCode

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ExitCode -> () #

Eq ExitCode 
Instance details

Defined in GHC.IO.Exception

Ord ExitCode 
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)))

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Data ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal.Type

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal.Type

Associated Types

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Read ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Show ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Methods

rnf :: ByteString -> () #

Eq ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Ixed ByteString 
Instance details

Defined in Control.Lens.At

Lift ByteString

Since: bytestring-0.11.2.0

Instance details

Defined in Data.ByteString.Internal.Type

Methods

lift :: Quote m => ByteString -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString #

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

type Index ByteString 
Instance details

Defined in Control.Lens.At

type IxValue ByteString 
Instance details

Defined in Control.Lens.At

hPut :: Handle -> ByteString -> IO () #

Outputs a ByteString to the specified Handle.

hGet :: Handle -> Int -> IO ByteString #

Read a ByteString directly from the specified Handle. This is far more efficient than reading the characters into a String and then using pack. First argument is the Handle to read from, and the second is the number of bytes to read. It returns the bytes read, up to n, or empty if EOF has been reached.

hGet is implemented in terms of hGetBuf.

If the handle is a pipe or socket, and the writing end is closed, hGet will behave as if EOF was reached.

hGetNonBlocking :: Handle -> Int -> IO ByteString #

hGetNonBlocking is similar to hGet, except that it will never block waiting for data to become available, instead it returns only whatever data is available. If there is no data available to be read, hGetNonBlocking returns empty.

Note: on Windows and with Haskell implementation other than GHC, this function does not work correctly; it behaves identically to hGet.