| Copyright | (c) 2018 Composewell Technologies | 
|---|---|
| License | BSD-3-Clause | 
| Maintainer | streamly@composewell.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Streamly.Internal.Console.Stdio
Description
Synopsis
- read :: forall (m :: Type -> Type). MonadIO m => Stream m Word8
- readChunks :: forall (m :: Type -> Type). MonadIO m => Stream m (Array Word8)
- readChars :: forall (m :: Type -> Type). MonadIO m => Stream m Char
- reader :: forall (m :: Type -> Type). MonadIO m => Unfold m () Word8
- chunkReader :: forall (m :: Type -> Type). MonadIO m => Unfold m () (Array Word8)
- write :: forall (m :: Type -> Type). MonadIO m => Fold m Word8 ()
- writeChunks :: forall (m :: Type -> Type). MonadIO m => Fold m (Array Word8) ()
- writeErr :: forall (m :: Type -> Type). MonadIO m => Fold m Word8 ()
- writeErrChunks :: forall (m :: Type -> Type). MonadIO m => Fold m (Array Word8) ()
- putBytes :: MonadIO m => Stream m Word8 -> m ()
- putChunks :: MonadIO m => Stream m (Array Word8) -> m ()
- putStringsWith :: MonadIO m => (Stream m Char -> Stream m Word8) -> Stream m String -> m ()
- putChars :: MonadIO m => Stream m Char -> m ()
- putStrings :: MonadIO m => Stream m String -> m ()
- putStringsLn :: MonadIO m => Stream m String -> m ()
Singleton APIs
Stream reads
read :: forall (m :: Type -> Type). MonadIO m => Stream m Word8 Source #
Read a byte stream from standard input.
read = Handle.read stdin read = Stream.unfold Stdio.reader ()
Pre-release
readChunks :: forall (m :: Type -> Type). MonadIO m => Stream m (Array Word8) Source #
Read a stream of chunks from standard input.  The maximum size of a single
 chunk is limited to defaultChunkSize. The actual size read may be less
 than defaultChunkSize.
readChunks = Handle.readChunks stdin readChunks = Stream.unfold Stdio.chunkReader ()
Pre-release
UTF-8 decoded
readChars :: forall (m :: Type -> Type). MonadIO m => Stream m Char Source #
Read a character stream from Utf8 encoded standard input.
readChars = Unicode.decodeUtf8 Stdio.read
Pre-release
Unfolds
reader :: forall (m :: Type -> Type). MonadIO m => Unfold m () Word8 Source #
Unfold standard input into a stream of Word8.
chunkReader :: forall (m :: Type -> Type). MonadIO m => Unfold m () (Array Word8) Source #
Unfolds standard input into a stream of Word8 arrays.
Folds
write :: forall (m :: Type -> Type). MonadIO m => Fold m Word8 () Source #
Fold a stream of Word8 to standard output.
writeChunks :: forall (m :: Type -> Type). MonadIO m => Fold m (Array Word8) () Source #
Fold a stream of Array Word8 to standard output.
writeErr :: forall (m :: Type -> Type). MonadIO m => Fold m Word8 () Source #
Fold a stream of Word8 to standard error.
writeErrChunks :: forall (m :: Type -> Type). MonadIO m => Fold m (Array Word8) () Source #
Fold a stream of Array Word8 to standard error.
Stream writes
putBytes :: MonadIO m => Stream m Word8 -> m () Source #
Write a stream of bytes to standard output.
putBytes = Handle.putBytes stdout putBytes = Stream.fold Stdio.write
Pre-release
putChunks :: MonadIO m => Stream m (Array Word8) -> m () Source #
Write a stream of chunks to standard output.
putChunks = Handle.putChunks stdout putChunks = Stream.fold Stdio.writeChunks
Pre-release
Encoding specific
putStringsWith :: MonadIO m => (Stream m Char -> Stream m Word8) -> Stream m String -> m () Source #
Write a stream of strings to standard output using the supplied encoding. Output is flushed to the device for each string.
Pre-release
UTF-8 encoded
putChars :: MonadIO m => Stream m Char -> m () Source #
Encode a character stream to Utf8 and write it to standard output.
putChars = Stdio.putBytes . Unicode.encodeUtf8
Pre-release
putStrings :: MonadIO m => Stream m String -> m () Source #
Write a stream of strings to standard output using UTF8 encoding. Output is flushed to the device for each string.
Pre-release
putStringsLn :: MonadIO m => Stream m String -> m () Source #
Like putStrings but adds a newline at the end of each string.
XXX This is not portable, on Windows we need to use "rn" instead.
Pre-release