Copyright | (c) 2024 Sayo contributors (c) The University of Glasgow 2004-2008 |
---|---|
License | MPL-2.0 (see the LICENSE file) AND BSD-3-Clause |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Control.Monad.Hefty.Concurrent.Subprocess
Description
Effects for well-typed subprocess.
Synopsis
- process :: FilePath -> [String] -> CreateProcess ('SubprocMode 'NoPipe 'NoPipe 'NoPipe 'Wait 'Wait)
- data CreateProcess (p :: SubprocMode) where
- CreateProcess :: forall (i :: StreamMode) (o :: StreamMode) (e :: StreamMode) (lp :: Lifecycle) (ls :: Lifecycle). {..} -> CreateProcess ('SubprocMode i o e lp ls)
- data Lifecycle
- shell :: String -> CreateProcess ('SubprocMode 'NoPipe 'NoPipe 'NoPipe 'Wait 'Wait)
- data StdStream (s :: StreamMode) where
- data Subprocess (p :: SubprocMode) (a :: Type -> Type) b where
- 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)
- data SubprocMode = SubprocMode StreamMode StreamMode StreamMode Lifecycle Lifecycle
- data StreamMode
- type SubprocProvider (es :: [Effect]) = Scoped Freer SubprocResult CreateProcess '[Subprocess] es
- data SubprocResult (p :: SubprocMode) a where
- 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
- 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
- toRawCreateProcess :: forall (stdio :: SubprocMode). CreateProcess stdio -> CreateProcess
- hRead :: Handle -> IO ByteString
- data LifecycleMode (t :: Lifecycle) where
- chunkSize :: Int
- command :: CmdSpec -> CreateProcess ('SubprocMode 'NoPipe 'NoPipe 'NoPipe 'Wait 'Wait)
- 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)
- toRawStdStream :: forall (pipe :: StreamMode). StdStream pipe -> StdStream
- 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 ()
- 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 ()
- 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 ()
- 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 ()
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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
- 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)
- 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)
- 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)
- 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)
- data SubprocessLabel
- module Control.Monad.Hefty.Provider
- data CmdSpec
- type GroupID = CGid
- type UserID = CUid
- data Handle
- data ExitCode
- data ByteString
- hPut :: Handle -> ByteString -> IO ()
- hGet :: Handle -> Int -> IO ByteString
- hGetNonBlocking :: Handle -> Int -> IO ByteString
Documentation
process :: FilePath -> [String] -> CreateProcess ('SubprocMode 'NoPipe 'NoPipe 'NoPipe 'Wait 'Wait) Source #
data CreateProcess (p :: SubprocMode) where Source #
Constructors
CreateProcess | |
Fields
|
data StdStream (s :: StreamMode) where Source #
Constructors
CreatePipe | |
Inherit | |
UseHandle | |
NoStream | |
Fields
|
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
FirstOrder (Subprocess p) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Subprocess | |
PolyHFunctor (Subprocess p) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Subprocess | |
HFunctor (Subprocess p) Source # | |
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 # | |
Defined in Control.Monad.Hefty.Concurrent.Subprocess | |
type LabelOf (Subprocess p) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Subprocess | |
type OrderOf (Subprocess p) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Subprocess |
data SubprocMode Source #
Constructors
SubprocMode StreamMode StreamMode StreamMode Lifecycle Lifecycle |
data StreamMode Source #
type SubprocProvider (es :: [Effect]) = Scoped Freer SubprocResult CreateProcess '[Subprocess] es Source #
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
Show a => Show (SubprocResult p a) Source # | |
Defined in Control.Monad.Hefty.Concurrent.Subprocess Methods showsPrec :: Int -> SubprocResult p a -> ShowS # show :: SubprocResult p a -> String # showList :: [SubprocResult p a] -> ShowS # | |
Eq a => Eq (SubprocResult p a) Source # | |
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 #
toRawCreateProcess :: forall (stdio :: SubprocMode). CreateProcess stdio -> CreateProcess Source #
data LifecycleMode (t :: Lifecycle) where Source #
Constructors
KillMode :: LifecycleMode 'Kill | |
WaitMode :: LifecycleMode 'Wait |
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 SubprocessLabel Source #
module Control.Monad.Hefty.Provider
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
Windows does not have a mechanism for passing multiple arguments.
When using |
Instances
IsString CmdSpec | construct a Since: process-1.2.1.0 |
Defined in System.Process.Common Methods fromString :: String -> CmdSpec # | |
Show CmdSpec | |
Eq CmdSpec | |
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
Defines the exit codes that a program can return.
Instances
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
Data ByteString | |||||
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: | ||||
Defined in Data.ByteString.Internal.Type Methods fromString :: String -> ByteString # | |||||
Monoid ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |||||
Semigroup ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |||||
IsList ByteString | Since: bytestring-0.10.12.0 | ||||
Defined in Data.ByteString.Internal.Type Associated Types
Methods fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |||||
Read ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |||||
Show ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods showsPrec :: Int -> ByteString -> ShowS # show :: ByteString -> String # showList :: [ByteString] -> ShowS # | |||||
NFData ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods rnf :: ByteString -> () # | |||||
Eq ByteString | |||||
Defined in Data.ByteString.Internal.Type | |||||
Ord ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods compare :: ByteString -> ByteString -> Ordering # (<) :: ByteString -> ByteString -> Bool # (<=) :: ByteString -> ByteString -> Bool # (>) :: ByteString -> ByteString -> Bool # (>=) :: ByteString -> ByteString -> Bool # max :: ByteString -> ByteString -> ByteString # min :: ByteString -> ByteString -> ByteString # | |||||
Hashable ByteString | |||||
Defined in Data.Hashable.Class | |||||
Ixed ByteString | |||||
Defined in Control.Lens.At Methods ix :: Index ByteString -> Traversal' ByteString (IxValue ByteString) # | |||||
Lift ByteString | Since: bytestring-0.11.2.0 | ||||
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 | |||||
Defined in Data.ByteString.Internal.Type | |||||
type Index ByteString | |||||
Defined in Control.Lens.At | |||||
type IxValue ByteString | |||||
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
.