io-streams-1.5.1.0: Simple, composable, and easy-to-use stream I/O

Safe HaskellNone
LanguageHaskell2010

System.IO.Streams.Vector

Contents

Description

Vector conversions and utilities.

Synopsis

Vector conversions

fromVector :: Vector v a => v a -> IO (InputStream a) Source #

Transforms a vector into an InputStream that yields each of the values in the vector in turn.

ghci> import Control.Monad
ghci> import qualified System.IO.Streams as Streams
ghci> import qualified Data.Vector as V
ghci> let v = V.fromList [1, 2]
ghci> is <- Streams.fromVector v
ghci> replicateM 3 (Streams.read is)
[Just 1,Just 2,Nothing]

toVector :: Vector v a => InputStream a -> IO (v a) Source #

Drains an InputStream, converting it to a vector. Note that this function reads the entire InputStream strictly into memory and as such is not recommended for streaming applications or where the size of the input is not bounded or known.

ghci> is <- Streams.fromList [(1::Int)..4]
ghci> Streams.toVector is :: IO (V.Vector Int)
fromList [1,2,3,4]

toVectorSized :: Vector v a => Int -> InputStream a -> IO (v a) Source #

Like toVector, but allows control over how large the vector buffer is to start with.

outputToVector :: Vector v a => (OutputStream a -> IO b) -> IO (v a) Source #

Given an IO action that requires an OutputStream, creates one and captures all the output the action sends to it as a vector.

Example:

ghci> ((connect $ fromList [1, 2, 3]) >>= outputToVector)
          :: IO (Vector Int)
fromList [1,2,3]

outputToVectorSized :: Vector v a => Int -> (OutputStream a -> IO b) -> IO (v a) Source #

Like outputToVector, but allows control over how large the vector buffer is to start with.

toMutableVector :: MVector v a => InputStream a -> IO (v (PrimState IO) a) Source #

Drains an InputStream, converting it to a mutable vector. Note that this function reads the entire InputStream strictly into memory and as such is not recommended for streaming applications or where the size of the input is not bounded or known.

toMutableVectorSized Source #

Arguments

:: MVector v a 
=> Int

initial size of the vector buffer

-> InputStream a 
-> IO (v (PrimState IO) a) 

Like toMutableVector, but allows control over how large the vector buffer is to start with.

outputToMutableVector :: MVector v a => (OutputStream a -> IO b) -> IO (v (PrimState IO) a) Source #

Given an IO action that requires an OutputStream, creates one and captures all the output the action sends to it as a mutable vector.

Example:

ghci> import Control.Applicative
ghci> (connect <$> fromList [1, 2, 3::Int])
       >>= outputToMutableVector
       >>= V.freeze
fromList [1,2,3]

outputToMutableVectorSized :: MVector v a => Int -> (OutputStream a -> IO b) -> IO (v (PrimState IO) a) Source #

Like outputToMutableVector, but allows control over how large the vector buffer is to start with.

writeVector :: Vector v a => v a -> OutputStream a -> IO () Source #

Feeds a vector to an OutputStream. Does not write an end-of-stream to the stream.

ghci> let v = V.fromList [1..4] :: V.Vector Int
ghci> os <- Streams.unlines Streams.stdout >>= Streams.contramap (S.pack . show) :: IO (OutputStream Int)
ghci> Streams.writeVector v os
1
2
3
4

Utility

chunkVector :: Vector v a => Int -> InputStream a -> IO (InputStream (v a)) Source #

Splits an input stream into chunks of at most size n.

Example:

ghci> (fromList [1..14::Int] >>= chunkVector 4 >>= toList)
         :: IO [Vector Int]
[fromList [1,2,3,4],fromList [5,6,7,8],fromList [9,10,11,12],fromList [13,14]]

vectorOutputStream :: Vector v c => IO (OutputStream c, IO (v c)) Source #

vectorOutputStream returns an OutputStream which stores values fed into it and an action which flushes all stored values to a vector.

The flush action resets the store.

Note that this function will buffer any input sent to it on the heap. Please don't use this unless you're sure that the amount of input provided is bounded and will fit in memory without issues.

ghci> (os, flush) <- Streams.vectorOutputStream :: IO (OutputStream Int, IO (V.Vector Int))
ghci> Streams.write (Just 1) os
ghci> Streams.write (Just 2) os
ghci> flush
fromList [1,2]
ghci> Streams.write (Just 3) os
ghci> Streams.write Nothing  os
ghci> Streams.write (Just 4) os
ghci> flush
fromList [3]

vectorOutputStreamSized :: Vector v c => Int -> IO (OutputStream c, IO (v c)) Source #

Like vectorOutputStream, but allows control over how large the vector buffer is to start with.

mutableVectorOutputStream :: MVector v c => IO (OutputStream c, IO (v (PrimState IO) c)) Source #

mutableVectorOutputStream returns an OutputStream which stores values fed into it and an action which flushes all stored values to a vector.

The flush action resets the store.

Note that this function will buffer any input sent to it on the heap. Please don't use this unless you're sure that the amount of input provided is bounded and will fit in memory without issues.

mutableVectorOutputStreamSized :: MVector v c => Int -> IO (OutputStream c, IO (v (PrimState IO) c)) Source #

Like mutableVectorOutputStream, but allows control over how large the vector buffer is to start with.