Z-IO-0.1.4.0: Simple and high performance IO toolkit for Haskell

Copyright(c) Dong Han 2018~2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.IO.StdStream

Contents

Description

This module provides stdin/stderr/stdout reading and writings. Usually you don't have to use stderr or stderrBuf directly, Logger provides more logging utilities through stderr. While stdinBuf and stdoutBuf is useful when you write interactive programs, Buffered module provide many reading and writing operations. Example:

import Control.Concurrent.MVar
import Z.IO.LowResTimer
import Z.IO.Buffered
import Z.IO.StdStream
import qualified Z.Data.Vector as V
import qualified Z.Data.Builder as B
main = do
    -- read by '\n'
    b1 <- readLineStd
    -- read whatever user input in 3s, otherwise get Nothing
    b2 <- timeoutLowRes 30 $ withMVar stdinBuf readBuffer
    ...
    putStd "hello world!"

    -- Raw mode
    setStdinTTYMode UV_TTY_MODE_RAW
    forever $ do
        withMVar stdinBuf $  i -> withMVar stdoutBuf $  o -> do
            bs <- readBuffer i
            let Just key = V.headMaybe bs
            writeBuilder o (B.hex key)
            flushBuffer o
Synopsis

Standard input & output streams

data StdStream Source #

Standard input and output streams

We support both regular file and TTY based streams, when initialized uv_guess_handle is called to decide which type of devices are connected to standard streams.

Note StdStream is not thread safe, you shouldn't use them without lock. For the same reason you shouldn't use stderr directly, use Logger module instead.

Instances
Output StdStream Source # 
Instance details

Defined in Z.IO.StdStream

Methods

writeOutput :: StdStream -> Ptr Word8 -> Int -> IO () Source #

Input StdStream Source # 
Instance details

Defined in Z.IO.StdStream

data TTYMode where Source #

Terminal mode.

When in UV_TTY_MODE_RAW mode, input is always available character-by-character, not including modifiers. Additionally, all special processing of characters by the terminal is disabled, including echoing input characters. Note that CTRL+C will no longer cause a SIGINT when in this mode.

Bundled Patterns

pattern TTY_MODE_NORMAL :: TTYMode 
pattern TTY_MODE_RAW :: TTYMode 
Instances
Eq TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

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

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

Num TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Ord TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Show TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Generic TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Associated Types

type Rep TTYMode :: Type -> Type #

Methods

from :: TTYMode -> Rep TTYMode x #

to :: Rep TTYMode x -> TTYMode #

FiniteBits TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ToValue TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

toValue :: TTYMode -> Value #

EncodeJSON TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Methods

encodeJSON :: TTYMode -> Builder () #

FromValue TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

ShowT TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Unaligned TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Storable TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

Bits TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep TTYMode Source # 
Instance details

Defined in Z.IO.UV.FFI

type Rep TTYMode = D1 (MetaData "TTYMode" "Z.IO.UV.FFI" "Z-IO-0.1.4.0-IfRX4KH4mesBaX238HlX2d" True) (C1 (MetaCons "TTYMode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CInt)))

setStdinTTYMode :: TTYMode -> IO () Source #

Change terminal's mode if stdin is connected to a terminal.

getStdoutWinSize :: HasCallStack => IO (CInt, CInt) Source #

Get terminal's output window size in (width, height) format, return (-1, -1) if stdout is a file.

stdin :: StdStream Source #

The global stdin stream.

stdout :: StdStream Source #

The global stdout stream.

| If you want to write logs, don't use stdout directly, use Logger instead.

stderr :: StdStream Source #

The global stderr stream.

| If you want to write logs, don't use stderr directly, use Logger instead.

stdinBuf :: MVar (BufferedInput StdStream) Source #

A global buffered stdin stream protected by MVar.

stdoutBuf :: MVar (BufferedOutput StdStream) Source #

A global buffered stdout stream protected by MVar.

| If you want to write logs, don't use stdoutBuf directly, use Logger instead.

stderrBuf :: MVar (BufferedOutput StdStream) Source #

A global buffered stderr stream protected by MVar.

| If you want to write logs, don't use stderrBuf directly, use Logger instead.

utils

printStd :: HasCallStack => ShowT a => a -> IO () Source #

print a ShowT and flush to stdout.

readLineStd :: HasCallStack => IO Bytes Source #

read a line from stdin

putStd :: HasCallStack => Builder a -> IO () Source #

print a Builder and flush to stdout.

putLineStd :: HasCallStack => Builder a -> IO () Source #

print a Builder and flush to stdout, with a linefeed.