Console stdio changes

This commit is contained in:
Harendra Kumar 2022-10-26 04:23:46 +05:30
parent 7d2863b0a1
commit 0b4606d571
4 changed files with 828 additions and 40 deletions

View File

@ -6,50 +6,114 @@
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
--
-- This module works only with UTF-8 encoding.
--
-- The stream writing APIs are polymorphic on types that belong to the 'ToUTF8'
-- type class. This allows us to simply use the same APIs for streams, lists
-- and arrays.
--
-- Note that when using the buffered reading APIs keep in mind that these APIs
-- buffer outside the stdin Handle, therefore, if the stream is consumed
-- partially, the data in the buffer may be discarded. If we read from the
-- handle again we would have lost some data. Therefore, these APIs can only be
-- used if you want to process the full stream using the API. You cannot stop
-- the stream and start reading from the Handle again.
--
--
-- Plan:
--
-- Keep stdin stream in a global mutable reference.
-- Parse objects from stdin stream, splice back the leftover
-- The stream is binary, Unicode parsers decode it as utf8 first
-- Binary parsers directly parse objects from it
-- Can use parseBreak or consume entire stream directly
-- Cannot use the Handle backing the stream, directly.
-- Each output type can have its own module - String, Utf8, Text
-- The basic module could keep just binary stream stuff
-- Multiple threads reading from stdin?
module Streamly.Internal.Console.Stdio
(
-- * Streams
read
, readChars
-- * Standard Input
{-
-- ** Singleton reads
getC -- getChar, and change getChars => getCharStream
-- , getS -- cannot be implemented outside the stdin Handle
, getL
, getChunk -- Single raw chunk
-- ** Unfolds
, read
, readChunks
-- , getChunksLn
-- ** Raw Streams
, getBytes
, getChunks
-- ** UTF-8 Char Streams
, getChars
-- These cannot be implemented outside the stdin handle
-- , getStringsWith -- get strings using the supplied decoding
-- , getStrings -- get strings of complete chars,
-- leave any partial chars for next string
-- , getStringsLn -- get lines decoded as char strings
-- , getStrings -- get character chunks as they become available
-- , getLineChunks -- get line chunks as they become available
, getLines -- get single lines decoded as char strings
-- * Unfolds
, reader
, chunkReader
-- * Standard Output
-- ** Singleton writes
-- Since these are commonly used it is desirable that the names are short,
-- are not visually similar to plural names etc (e.g. putChar) and do not
-- conflict with Prelude (putStr).
--
-- Note: We can extend these to use encoding from the environment.
--
, putC -- same as System.IO.putChar
, putS -- Ubuffered char chunk (echo -n)
, putL -- Unbuffered line (echo)
, putChunk -- Single raw chunk
-- * Folds
-- ** Folds
, write
, writeChunks
-- * Raw Streams
, putBytes -- Buffered (32K) raw bytes
, putChunks -- raw chunks
-- ** Char Streams
, putStringsWith
-- putCharsWith
-- putChunksWith
-- ** UTF-8 Char Streams
-- Multi APIs
, putChars -- Buffered utf8 chars
, putStrings -- utf8 char chunks
, putLines -- utf8 lines
-- * Standard Error
, writeErr
, writeErrChunks
-}
-- * Stream writes
, putBytes -- Buffered (32K)
, putChars
, putChunks -- Unbuffered
, putStringsWith
, putStrings
, putStringsLn
-- Note: We can use putErr* for writing streams to stderr
)
where
#include "inline.hs"
import Control.Monad.Catch (MonadThrow, MonadCatch)
import Control.Monad.IO.Class (MonadIO(..))
import Data.IORef
import Data.Word (Word8)
import System.IO (stdin, stdout, stderr)
import Prelude hiding (read)
import Streamly.Internal.Data.Array.Type (Array(..))
import Streamly.Internal.Data.Stream (Stream)
import Streamly.Internal.Data.Unfold (Unfold)
import Streamly.Internal.Data.Fold (Fold)
-- import Streamly.Internal.Data.Stream.ToStream (IsFold(..), IsUnfold(..))
import System.IO.Unsafe (unsafePerformIO)
import qualified Streamly.Internal.Data.Array as Array
import qualified Streamly.Internal.Data.Stream as Stream
@ -57,11 +121,105 @@ import qualified Streamly.Internal.Data.Stream as Stream
import qualified Streamly.Internal.Data.Unfold as Unfold
import qualified Streamly.Internal.FileSystem.Handle as Handle
import qualified Streamly.Internal.Unicode.Stream as Unicode
import qualified System.IO as IO
-------------------------------------------------------------------------------
-- Reads
-------------------------------------------------------------------------------
-- | 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@.
--
-- > getChunks = Handle.getChunks stdin
-- > getChunks = Stream.unfold Stdio.readChunks ()
--
-- /Pre-release/
--
{-# INLINE stdin #-}
stdin :: MonadIO m => SerialT m (Array Word8)
stdin = Handle.getChunks IO.stdin
{-# NOINLINE stdinM #-}
stdinM :: MonadIO m => IORef (SerialT m (Array Word8))
stdinM = unsafePerformIO (newIORef stdin)
{-# INLINE getStdin #-}
getStdin :: MonadIO m => m (SerialT m (Array Word8))
getStdin = liftIO $ readIORef stdinM
-- XXX Need locking for multithreaded access
withStdin :: MonadIO m =>
(SerialT m (Array Word8) -> m (a, SerialT m (Array Word8)))
-> m a
withStdin f = do
r <- getStdin
(res, str) <- f r
liftIO $ writeIORef stdinM str
return res
{-
-- stdin as a stream of chunks.
-- We can concat it if we want to read a stream of chars
-- However, after concating how do we go back to reading it as a stream of
-- chunks if we want to do so?
-- | Read a byte array from standard input.
--
-- >>> getChunk n = Handle.getChunk n stdin
--
-- /Pre-release/
--
{-# INLINE getChunk #-}
getChunk :: MonadIO m => Int -> m (Array Word8)
getChunk n = Handle.getChunk n IO.stdin
-}
-- XXX We could use a global mutable ref for stdin to avoid passing it around
-- in all the routines below.
type Stdin m = SerialT m (Array Word8)
-- | Read a character from console.
--
-- >>> getC = liftIO getChar
--
-- /Pre-release/
--
{-# INLINE getChr #-}
getChr :: (MonadIO m, MonadCatch m) =>
SerialT m (Array Word8) -> m (Char, SerialT m (Array Word8))
getChr =
ArrStream.parseBreak
(Unicode.parseCharUtf8With Unicode.ErrorOnCodingFailure)
{-# INLINE getChrM #-}
getChrM :: (MonadIO m, MonadCatch m) => m Char
getChrM = withStdin getChr
{-
{-# INLINE getLStr #-}
getLStr :: MonadIO m => m String
getLStr = liftIO getLine
-}
-- XXX It may be more efficient if the handle returns a raw line Array Word8 or
-- even an Array Char.
--
-- | Read a line from console.
--
-- /Pre-release/
--
{-
{-# INLINE_EARLY getLn #-}
getLn :: forall m a. (MonadIO m, IsFold m Char a) => m a
getLn =
liftIO getLine
>>= (Stream.fold eliminator . (Stream.fromList :: String -> SerialT m Char))
{-# RULES "getLStr" getL = getLStr #-}
-- XXX Instead of unfolding () we should use getBytes
-- | Unfold standard input into a stream of 'Word8'.
--
{-# INLINE reader #-}
@ -77,7 +235,7 @@ reader = Unfold.lmap (\() -> stdin) Handle.reader
--
{-# INLINE read #-}
read :: MonadIO m => Stream m Word8
read = Handle.read stdin
read = Handle.read IO.stdin
-- | Read a character stream from Utf8 encoded standard input.
--
@ -89,11 +247,13 @@ read = Handle.read stdin
readChars :: MonadIO m => Stream m Char
readChars = Unicode.decodeUtf8 read
-- XXX Instead of unfolding () we should use getChunks
-- | Unfolds standard input into a stream of 'Word8' arrays.
--
{-# INLINE chunkReader #-}
chunkReader :: MonadIO m => Unfold m () (Array Word8)
chunkReader = Unfold.lmap (\() -> stdin) Handle.chunkReader
chunkReader = Unfold.lmap (\() -> IO.stdin) Handle.chunkReader
-- | 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
@ -109,6 +269,11 @@ readChunks :: MonadIO m => Stream m (Array Word8)
readChunks = Handle.readChunks stdin
{-
{-
-- This implementation may not work if we want to terminate getLines and then
-- want to read again from the handle. Since we are buffering outside the
-- handle we will lose the buffer on termination of the stream.
--
-- | Read UTF8 encoded lines from standard input.
--
-- You may want to process the input byte stream directly using appropriate
@ -116,9 +281,9 @@ readChunks = Handle.readChunks stdin
--
-- /Pre-release/
--
{-# INLINE getChunksLn #-}
getChunksLn :: MonadIO m => Stream m (Array Word8)
getChunksLn = (Stream.splitWithSuffix (== '\n') f) getChars
{-# INLINE getLines #-}
getLines :: MonadIO m => Stream m (Array Word8)
getLines = (Stream.splitWithSuffix (== '\n') f) getChars
-- XXX Need to implement Fold.unfoldMany, should be easy for
-- non-terminating folds, but may be tricky for terminating folds. See
@ -126,21 +291,96 @@ getChunksLn = (Stream.splitWithSuffix (== '\n') f) getChars
where f = Fold.unfoldMany Unicode.readCharUtf8 Array.write
-}
{-# INLINE getLinesStr #-}
getLinesStr :: MonadAsync m => SerialT m String
getLinesStr = Stream.repeatM (liftIO getLine)
-- XXX Instead of using a typeclass use a Fold argument? Like we do for many
-- other operations?
--
-- We can specialize to getStrLn, getArrLn, getUtf8Ln
--
-- XXX Remove MonadAsync, by using Serial verison of repeatM.
--
-- | Read UTF8 encoded lines from standard input.
--
-- This API uses the buffering of the stdin handle, therefore, the stream can
-- be consumed partially without any issues.
--
-- You may want to process the input byte stream directly using appropriate
-- folds for more efficient processing.
--
-- /Pre-release/
--
{-# INLINE_EARLY getLines #-}
getLines :: forall m a. (MonadAsync m, IsFold m Char a) => SerialT m a
getLines =
Stream.mapM
(Stream.fold eliminator . (Stream.fromList :: String -> SerialT m Char))
(Stream.repeatM (liftIO getLine) :: SerialT m String)
{-# RULES "getLinesStr" getLines = getLinesStr #-}
-}
-------------------------------------------------------------------------------
-- Writes
-------------------------------------------------------------------------------
-- | Write a byte array to standard output.
--
-- >>> putChunk = Handle.putChunk stdout
--
-- /Pre-release/
--
{-# INLINE putChunk #-}
putChunk :: MonadIO m => Array Word8 -> m ()
putChunk = Handle.putChunk IO.stdout
{-
-- We can specialize to putStream, putArr, putString
--
-- | Write a character string on console.
--
-- It works on @t m Char@, 'String' ([Char]) or an @Array Char@ type.
--
-- /Pre-release/
--
{-# INLINE putS #-}
putS :: (MonadIO m, IsUnfold m a Char) => a -> m ()
putS x = putChunk =<< Array.fromStream (Unicode.encodeUtf8 $ Stream.unfold generator x)
-- | Write a character on console.
--
-- >>> putC = liftIO . putChar
--
-- /Pre-release/
--
{-# INLINE putC #-}
putC :: MonadIO m => Char -> m ()
putC = liftIO . putChar
-- | Write a character string on console followed by a newline character.
--
-- >>> putL x = putS x >> putC '\n'
--
-- /Pre-release/
--
{-# INLINE putL #-}
putL :: (MonadIO m, IsUnfold m a Char) => a -> m ()
putL x = putS x >> putC '\n'
-}
-- | Fold a stream of 'Word8' to standard output.
--
{-# INLINE write #-}
write :: MonadIO m => Fold m Word8 ()
write = Handle.write stdout
write = Handle.write IO.stdout
-- | Fold a stream of 'Word8' to standard error.
--
{-# INLINE writeErr #-}
writeErr :: MonadIO m => Fold m Word8 ()
writeErr = Handle.write stderr
writeErr = Handle.write IO.stderr
-- | Write a stream of bytes to standard output.
--
@ -151,29 +391,33 @@ writeErr = Handle.write stderr
--
{-# INLINE putBytes #-}
putBytes :: MonadIO m => Stream m Word8 -> m ()
putBytes = Handle.putBytes stdout
putBytes = Handle.putBytes IO.stdout
{-
-- XXX putCharsWith unfold
--
-- | Encode a character stream to Utf8 and write it to standard output.
--
-- > putChars = Stdio.putBytes . Unicode.encodeUtf8
-- >>> putChars = Stdio.putBytes . Unicode.encodeUtf8 . ToStream.toStream
--
-- /Pre-release/
--
{-# INLINE putChars #-}
putChars :: MonadIO m => Stream m Char -> m ()
putChars = putBytes . Unicode.encodeUtf8
putChars :: (MonadIO m, IsUnfold m a Char) => a -> m ()
putChars = putBytes . Unicode.encodeUtf8 . Stream.unfold generator
-}
-- | Fold a stream of @Array Word8@ to standard output.
--
{-# INLINE writeChunks #-}
writeChunks :: MonadIO m => Fold m (Array Word8) ()
writeChunks = Handle.writeChunks stdout
writeChunks = Handle.writeChunks IO.stdout
-- | Fold a stream of @Array Word8@ to standard error.
--
{-# INLINE writeErrChunks #-}
writeErrChunks :: MonadIO m => Fold m (Array Word8) ()
writeErrChunks = Handle.writeChunks stderr
writeErrChunks = Handle.writeChunks IO.stderr
-- | Write a stream of chunks to standard output.
--
@ -184,12 +428,13 @@ writeErrChunks = Handle.writeChunks stderr
--
{-# INLINE putChunks #-}
putChunks :: MonadIO m => Stream m (Array Word8) -> m ()
putChunks = Handle.putChunks stdout
putChunks = Handle.putChunks IO.stdout
-------------------------------------------------------------------------------
-- Line buffered
-------------------------------------------------------------------------------
{-
-- XXX We need to write transformations as pipes so that they can be applied to
-- folds as well as unfolds/streams. Non-backtracking (one-to-one, one-to-many,
-- filters, reducers) transformations may be easy so we can possibly start with
@ -201,17 +446,20 @@ putChunks = Handle.putChunks stdout
-- /Pre-release/
--
{-# INLINE putStringsWith #-}
putStringsWith :: MonadIO m
=> (Stream m Char -> Stream m Word8) -> Stream m String -> m ()
putStringsWith encode = putChunks . Unicode.encodeStrings encode
putStringsWith :: (MonadIO m, IsUnfold m a Char)
=> (Stream m Char -> Stream m Word8) -> Stream m a -> m ()
putStringsWith encode =
putChunks . Stream.mapM (Array.fromStream . encode . Stream.unfold generator)
-- | Write a stream of strings to standard output using UTF8 encoding. Output
-- is flushed to the device for each string.
--
-- >>> putStrings = putStringsWith Unicode.encodeUtf8
--
-- /Pre-release/
--
{-# INLINE putStrings #-}
putStrings :: MonadIO m => Stream m String -> m ()
putStrings :: (MonadIO m, IsUnfold m a Char) => Stream m a -> m ()
putStrings = putStringsWith Unicode.encodeUtf8
-- | Like 'putStrings' but adds a newline at the end of each string.
@ -220,9 +468,10 @@ putStrings = putStringsWith Unicode.encodeUtf8
--
-- /Pre-release/
--
{-# INLINE putStringsLn #-}
putStringsLn :: MonadIO m => Stream m String -> m ()
putStringsLn =
{-# INLINE putLines #-}
putLines :: (MonadIO m, IsUnfold m a Char) => Stream m a -> m ()
putLines =
putChunks
. Stream.intersperseMSuffix (return $ Array.fromList [10])
. Unicode.encodeStrings Unicode.encodeUtf8
-}

View File

@ -0,0 +1,382 @@
-- |
-- Module : Streamly.Internal.Console.Stream
-- Copyright : (c) 2018 Composewell Technologies
--
-- License : BSD-3-Clause
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
--
-- This module works only with UTF-8 encoding.
--
-- The stream writing APIs are polymorphic on types that belong to the 'ToUTF8'
-- type class. This allows us to simply use the same APIs for streams, lists
-- and arrays.
--
-- Note that when using the buffered reading APIs keep in mind that these APIs
-- buffer outside the stdin Handle, therefore if the stream is consumed
-- partially, the data in the buffer may be discarded. Therefore, if we read
-- from the handle again we would have lost some data. Therefore, these APIs
-- can only be used if you want to process the full stream using the API. You
-- cannot stop the stream and start reading again.
-- NOTES: Breaking a stream incurs a cost because of CPS and breaking of
-- fusion. For consuming a stream of chunks efficiently, the basic principle
-- is to use element folds on the chunk stream so that we can keep the source
-- as a chunk stream. If we convert the chunk stream into element stream and
-- then break it then we need to pay the cost of breaking per element rather
-- than per chunk. So we have two options:
--
-- 1. Consume the original chunk stream using element folds. In this case we
-- cannot use stream expansion combinators as we are working on folds and we do
-- not have an efficient/fusible expansion facility in folds, as there is no
-- Skip input facility. We can use the fold composition facilities (fold Monad)
-- to compose folds. We can use foldBreak on the stream and then consume the
-- rest of the stream in an arbitrary way. We can also do the same inside fold
-- monad.
--
-- Basically expansion and merge will have to be supported by folds as well if
-- we want an entire gamut of operations.
--
-- 2. Make the original stream return the remaining stream (Stream a m r). A
-- concatMap or unfoldMany (using a producer type) can be used to expand the
-- stream. When the stream ends we will need to compose the result of the
-- internal stream with the external stream to return the remaining stream.
-- For example, if we are expanding a stream of Array Word8 into a stream of
-- Word8, the inner stream will have a leftover array which will need to be
-- added back to the outer array of streams. In case of parsers, it will be
-- even more complicated because we may even have leftover elements which may
-- have to be converted back to array.
--
-- 3. When combining a stream with a fold we can return the remaining stream if
-- the stream is leftover, or return a fold if it wants more input. So a
-- generalised fold runner would return "Either Stream Fold". Then we can use
-- the base monad to drive the computation incrementally using one chunk at a
-- time. In this case we do not have the problem of breaking the stream as it
-- is already broken. We are using a fundamentally broken-stream/fold paradigm.
--
-- For example, to process a stream of "Array Word8" we uncons one Array from
-- the parent stream. This array is unfolded to a stream of Word8 and we drive
-- a Word8 fold using the resulting stream. The fold would return either an
-- unfinished fold or the leftover stream. If the stream is leftover we can
-- either consume it using another fold or convert it back to an array using an
-- Array write fold.
--
module Streamly.Internal.Console.Stream
(
-- * Standard Input
single
, byteLine
, foldBytes
, line
, foldChars
, foldLines
{-
-- * Standard Output
-- ** Singleton writes
-- Since these are commonly used it is desirable that the names are short,
-- are not visually similar to plural names etc (e.g. putChar) and do not
-- conflict with Prelude (putStr).
--
-- Note: We can extend these to use encoding from the environment.
--
, putC -- same as System.IO.putChar
, putS -- Ubuffered char chunk (echo -n)
, putL -- Unbuffered line (echo)
, putChunk -- Single raw chunk
-- ** Folds
, write
, writeChunks
-- * Raw Streams
, putBytes -- Buffered (32K) raw bytes
, putChunks -- raw chunks
-- ** Char Streams
, putStringsWith
-- putCharsWith
-- putChunksWith
-- ** UTF-8 Char Streams
-- Multi APIs
, putChars -- Buffered utf8 chars
, putStrings -- utf8 char chunks
, putLines -- utf8 lines
-- * Standard Error
, writeErr
, writeErrChunks
-}
-- Note: We can use putErr* for writing streams to stderr
)
where
#include "inline.hs"
import Control.Monad.Catch (MonadThrow, MonadCatch)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Maybe (fromJust)
import Data.Word (Word8)
import Prelude hiding (read)
import Streamly.Internal.Control.Concurrent (MonadAsync)
import Streamly.Internal.Data.Array.Foreign.Type (Array(..))
import Streamly.Internal.Data.Stream.Serial (SerialT)
import Streamly.Internal.Data.Unfold (Unfold)
import Streamly.Internal.Data.Fold (Fold)
import Streamly.Internal.Data.Parser (Parser)
-- import Streamly.Internal.Data.Stream.ToStream (IsFold(..), IsUnfold(..))
import System.IO.Unsafe (unsafePerformIO)
import qualified Streamly.Internal.Data.Stream.Serial as Serial
import qualified Streamly.Internal.Data.Array.Foreign as Array
import qualified Streamly.Internal.Data.Array.Stream.Foreign as ArrStream
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Stream.IsStream as Stream
import qualified Streamly.Internal.Data.Unfold as Unfold
import qualified Streamly.Internal.FileSystem.Handle as Handle
import qualified Streamly.Internal.Unicode.Stream as Unicode
import qualified System.IO as IO
-- XXX These are general routines and are not specific to stdin/out. These can
-- go in appropriate general modules.
-- XXX Important we cannot mix these routines with any other IO routines e.g.
-- reading directly using the base System.IO routines.
-------------------------------------------------------------------------------
-- Reads
-------------------------------------------------------------------------------
-- XXX Partial function, should not fail for stdin stream
{-# INLINE single #-}
single :: Monad m => Fold m a a
single = fmap fromJust Fold.one
-- | Consume at most one line.
{-# INLINE byteLine #-}
byteLine :: Monad m => Fold m Word8 b -> Fold m Word8 b
byteLine = Fold.takeEndBy_ (== 10)
-- | Consume bytes from a stream.
--
-- > foldBytes single
-- > foldBytes (byteLine Fold.toList)
--
-- /Pre-release/
--
{-# INLINE foldBytes #-}
foldBytes :: MonadIO m =>
Fold m Word8 b -> SerialT m (Array Word8) -> m (b, SerialT m (Array Word8))
foldBytes = ArrStream.foldBreak
-- XXX We can write "line" as a scanner or as Fold -> Fold combinator.
{-# INLINE line #-}
line :: Monad m => Fold m Char b -> Fold m Char b
line = Fold.takeEndBy_ (== '\n')
{-# INLINE decodeUtf8 #-}
decodeUtf8 :: MonadThrow m => Fold m Char b -> Fold m Word8 b
decodeUtf8 = Fold.many Unicode.writeCharUtf8'
-- | Consume a character stream from Utf8 encoded bytearray stream.
--
-- > foldChars single
-- > foldChars (line Fold.toList)
--
{-# INLINE foldChars #-}
foldChars :: (MonadIO m, MonadCatch m) =>
Fold m Char b -> SerialT m (Array Word8) -> m (b, SerialT m (Array Word8))
foldChars f = ArrStream.foldBreak (decodeUtf8 f)
-- XXX Check fusion issues due to nested "many" combinator.
-- | decodeLines lineProducer lineConsumer
{-# INLINE decodeLines #-}
decodeLines :: MonadThrow m => Fold m Char b -> Fold m b c -> Fold m Word8 c
decodeLines ln = Fold.many (Fold.many Unicode.writeCharUtf8' (line ln))
-- | Consume a line stream from Utf8 encoded bytearray stream.
--
-- > foldLines Fold.toList (Fold.take 2 Fold.toList))
--
{-# INLINE foldLines #-}
foldLines :: (MonadIO m, MonadCatch m) =>
Fold m Char b
-> Fold m b c
-> SerialT m (Array Word8)
-> m (c, SerialT m (Array Word8))
foldLines ln f = ArrStream.foldBreak (decodeLines ln f)
-- | Consume bytearrays from a bytearray stream.
--
-- > foldChunks single
-- > foldChunks (Fold.take 2)
--
-- /Pre-release/
--
{-# INLINE foldChunks #-}
foldChunks :: MonadIO m =>
Fold m (Array Word8) b
-> SerialT m (Array Word8)
-> m (b, SerialT m (Array Word8))
foldChunks = Stream.foldBreak
-------------------------------------------------------------------------------
-- Writes
-------------------------------------------------------------------------------
{-
-- | Write a byte array to standard output.
--
-- >>> putChunk = Handle.putChunk stdout
--
-- /Pre-release/
--
{-# INLINE putChunk #-}
putChunk :: MonadIO m => Array Word8 -> m ()
putChunk = Handle.putChunk IO.stdout
-- We can specialize to putStream, putArr, putString
--
-- | Write a character string on console.
--
-- It works on @t m Char@, 'String' ([Char]) or an @Array Char@ type.
--
-- /Pre-release/
--
{-# INLINE putS #-}
putS :: (MonadIO m, IsUnfold m a Char) => a -> m ()
putS x = putChunk =<< Array.fromStream (Unicode.encodeUtf8 $ Stream.unfold generator x)
-- | Write a character on console.
--
-- >>> putC = liftIO . putChar
--
-- /Pre-release/
--
{-# INLINE putC #-}
putC :: MonadIO m => Char -> m ()
putC = liftIO . putChar
-- | Write a character string on console followed by a newline character.
--
-- >>> putL x = putS x >> putC '\n'
--
-- /Pre-release/
--
{-# INLINE putL #-}
putL :: (MonadIO m, IsUnfold m a Char) => a -> m ()
putL x = putS x >> putC '\n'
-- | Fold a stream of 'Word8' to standard output.
--
-- @since 0.8.0
{-# INLINE write #-}
write :: MonadIO m => Fold m Word8 ()
write = Handle.write IO.stdout
-- | Fold a stream of 'Word8' to standard error.
--
-- @since 0.8.0
{-# INLINE writeErr #-}
writeErr :: MonadIO m => Fold m Word8 ()
writeErr = Handle.write IO.stderr
-- | Write a stream of bytes to standard output.
--
-- > putBytes = Handle.putBytes stdout
-- > putBytes = Stream.fold Stdio.write
--
-- /Pre-release/
--
{-# INLINE putBytes #-}
putBytes :: MonadIO m => SerialT m Word8 -> m ()
putBytes = Handle.putBytes IO.stdout
-- XXX putCharsWith unfold
--
-- | Encode a character stream to Utf8 and write it to standard output.
--
-- >>> putChars = Stdio.putBytes . Unicode.encodeUtf8 . ToStream.toStream
--
-- /Pre-release/
--
{-# INLINE putChars #-}
putChars :: (MonadIO m, IsUnfold m a Char) => a -> m ()
putChars = putBytes . Unicode.encodeUtf8 . Stream.unfold generator
-}
-- | Fold a stream of @Array Word8@ to standard output.
--
-- @since 0.8.0
{-# INLINE writeChunks #-}
writeChunks :: MonadIO m => Fold m (Array Word8) ()
writeChunks = Handle.writeChunks IO.stdout
{-
-- | Fold a stream of @Array Word8@ to standard error.
--
-- @since 0.8.0
{-# INLINE writeErrChunks #-}
writeErrChunks :: MonadIO m => Fold m (Array Word8) ()
writeErrChunks = Handle.writeChunks IO.stderr
-- | Write a stream of chunks to standard output.
--
-- > putChunks = Handle.putChunks stdout
-- > putChunks = Stream.fold Stdio.writeChunks
--
-- /Pre-release/
--
{-# INLINE putChunks #-}
putChunks :: MonadIO m => SerialT m (Array Word8) -> m ()
putChunks = Handle.putChunks IO.stdout
-------------------------------------------------------------------------------
-- Line buffered
-------------------------------------------------------------------------------
-- XXX We need to write transformations as pipes so that they can be applied to
-- folds as well as unfolds/streams. Non-backtracking (one-to-one, one-to-many,
-- filters, reducers) transformations may be easy so we can possibly start with
-- those.
--
-- | Write a stream of strings to standard output using the supplied encoding.
-- Output is flushed to the device for each string.
--
-- /Pre-release/
--
{-# INLINE putStringsWith #-}
putStringsWith :: (MonadIO m, IsUnfold m a Char)
=> (SerialT m Char -> SerialT m Word8) -> SerialT m a -> m ()
putStringsWith encode =
putChunks . Serial.mapM (Array.fromStream . encode . Stream.unfold generator)
-- | Write a stream of strings to standard output using UTF8 encoding. Output
-- is flushed to the device for each string.
--
-- >>> putStrings = putStringsWith Unicode.encodeUtf8
--
-- /Pre-release/
--
{-# INLINE putStrings #-}
putStrings :: (MonadIO m, IsUnfold m a Char) => SerialT m a -> m ()
putStrings = putStringsWith Unicode.encodeUtf8
-- | Like 'putStrings' but adds a newline at the end of each string.
--
-- XXX This is not portable, on Windows we need to use "\r\n" instead.
--
-- /Pre-release/
--
{-# INLINE putLines #-}
putLines :: (MonadIO m, IsUnfold m a Char) => SerialT m a -> m ()
putLines =
putChunks
. Stream.intersperseSuffix (return $ Array.fromList [10])
. Serial.mapM (Array.fromStream . Unicode.encodeUtf8 . Stream.unfold generator)
-}

View File

@ -0,0 +1,155 @@
-- |
-- Module : Streamly.Internal.Data.Stream.ToStream
-- Copyright : (c) 2021 Composewell Technologies
-- License : BSD-3-Clause
-- Maintainer : streamly@composewell.com
-- Stability : pre-release
-- Portability : GHC
--
-- These type classes allow use to use the same APIs to perform UTF-8 encoding
-- decoding using three common container types namely, Streams, Lists and
-- Arrays.
--
-- These type classes are not exact inverse of each other. The reason is as
-- follows. When a monadic stream is converted to a list we get a @m []@
-- instead of a @[]@ type. On the other hand when we convert a list to a stream
-- we can work with a pure type. There we have two separate type classes
-- 'ToChars' and 'FromChars' so that we can allow this difference in usage. We
-- can unify these if we accept @m []@ type in 'FromChars' APIs but that would
-- be a tad incovnenient.
module Streamly.Internal.Data.Stream.ToStream
( {- ToStream (..)
, FromStream (..)
, IsFold(..)
, IsUnfold(..)
-}
)
where
{-
import Control.Monad.IO.Class (MonadIO)
import Streamly.Data.Array.Foreign (Array)
import Streamly.Prelude (SerialT) -- , IsStream) -- , adapt)
import Foreign.Storable (Storable)
import Streamly.Internal.Data.Unfold (Unfold)
import Streamly.Internal.Data.Fold (Fold)
import qualified Streamly.Internal.Data.Array.Foreign as Array
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Unfold as Unfold
import qualified Streamly.Prelude as Stream
-- XXX Instead of ToChars use ToString and FromString to convert a type to
-- SerialT m Char.
-------------------------------------------------------------------------------
-- ToStream
-------------------------------------------------------------------------------
-- If we have a ToStream type class then we can define a generic instance for
-- 't Char' given that 't Char' is an instance of ToStream.
-- unfold
-- XXX Should we rather use Unfolds here instead of streams?
class ToStream m a b where
toStream :: (Monad m, Storable b) => a -> SerialT m b
instance ToStream m (SerialT m a) a where
toStream = id
instance ToStream m [a] a where
toStream = Stream.fromList
instance ToStream m (Array a) a where
toStream = Array.toStream
class IsUnfold m a b where
generator :: (Monad m, Storable b) => Unfold m a b
instance IsUnfold m (SerialT m a) a where
-- XXX Fold.toStream uses two different monads for the fold and the stream,
-- so we could detach the stream monad from the folds monad and that way we
-- can remove the monad parameter from the IsFold type class. But that is
-- not the case for unfolds. We cannot detach the two monads in
-- Unfold.fromStream. Is it possible? We can use "SerialT Identity a"
-- though.
generator = Unfold.fromStream
instance IsUnfold m [a] a where
generator = Unfold.fromList
instance IsUnfold m (Array a) a where
generator = Array.read
-- fold
-- XXX should we rather use Folds here instead of streams?
class FromStream m a b where
-- The MonadIO constraint is for Array.fromStream
fromStream :: (MonadIO m, Storable a) => SerialT m a -> m b
-- XXX It is possible to just return the stream if we parameterize the type
-- class with Monad m. However, if we remove the monad parameter we could fold
-- the stream to a stream in any monad, but that will be reconstructing the
-- stream, perf?
instance FromStream m a (SerialT m a) where
fromStream = return -- Stream.fold Fold.toStream
instance FromStream m a [a] where
fromStream = Stream.toList
instance FromStream m a (Array a) where
fromStream = Array.fromStream
class IsFold m a b where
-- The MonadIO constraint is for Array.fromStream
eliminator :: (MonadIO m, Storable a) => Fold m a b
instance IsFold m a (SerialT m a) where
eliminator = Fold.toStream
instance IsFold m a [a] where
eliminator = Fold.toList
instance IsFold m a (Array a) where
eliminator = Array.write
{-
-------------------------------------------------------------------------------
-- ToChars
-------------------------------------------------------------------------------
-- | Types (@t@) that can be encoded to a UTF-8 byte stream under 'Monad' @m@.
class ToChars m a where
toChars :: Monad m => a -> SerialT m Char
instance ToChars m (SerialT m Char) where
toChars = id
instance ToChars m [Char] where
toChars = Stream.fromList
instance ToChars m (Array Char) where
toChars = Array.toStream
-- XXX DList and Mutable arrays can also be added for builder use case.
-------------------------------------------------------------------------------
-- FromChars
-------------------------------------------------------------------------------
-- | Types (@t@) that can be created by decoding a UTF-8 byte stream under
-- 'Monad' @m@.
class FromChars m a where
-- The MonadIO constraint is for Array.fromStream
fromChars :: MonadIO m => SerialT m Char -> a
instance FromChars m (SerialT m Char) where
fromChars = id
instance FromChars m (m [Char]) where
fromChars = Stream.toList
instance FromChars m (m (Array Char)) where
fromChars = Array.fromStream
-}
-}

View File

@ -419,6 +419,8 @@ library
, Streamly.Internal.Data.Stream.IsStream
, Streamly.Internal.Data.Stream.ToStream
if !impl(ghcjs) && flag(dev)
other-modules:
Streamly.Internal.System.IOVec.Type