Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- readArchive :: MonadIO m => Unfold m (ReadOptions m Header -> ReadOptions m a, FilePath) (Either a ByteString)
- data ReadOptions m a
- mapHeaderMaybe :: (Header -> m (Maybe a)) -> ReadOptions m Header -> ReadOptions m a
- groupByLeft :: Monad m => Fold m (Either a b) c -> Stream m (Either a b) -> Stream m c
- eitherByLeft :: Monad m => Stream m (Either a b) -> Stream m (a, b)
- chunkOn :: Monad m => Word8 -> Stream m (Either a ByteString) -> Stream m (Either a ByteString)
- chunkOnFold :: Monad m => Word8 -> Fold m (Either a ByteString) b -> Fold m (Either a ByteString) b
- data Header
- data FileType
- headerFileType :: Header -> IO (Maybe FileType)
- headerPathName :: Header -> IO (Maybe ByteString)
- headerPathNameUtf8 :: Header -> IO (Maybe ByteString)
- headerSize :: Header -> IO (Maybe Int)
Read
readArchive :: MonadIO m => Unfold m (ReadOptions m Header -> ReadOptions m a, FilePath) (Either a ByteString) Source #
Read options
data ReadOptions m a Source #
mapHeaderMaybe :: (Header -> m (Maybe a)) -> ReadOptions m Header -> ReadOptions m a Source #
If this returns Just
for a header, that header (mapped to a different value if desired) and
any following ByteString
chunks are included in the readArchive
unfold. If this returns
Nothing
for a header, that header and any following ByteString
chunks are excluded from the
readArchive
unfold.
By default, all entries are included with unaltered headers.
Utility functions
Various utility functions that some might find useful.
groupByLeft :: Monad m => Fold m (Either a b) c -> Stream m (Either a b) -> Stream m c Source #
Groups a stream of Either
s by the Left
s. The provided Fold
processes a single Left
followed by any subsequent (zero or more) Right
s.
eitherByLeft :: Monad m => Stream m (Either a b) -> Stream m (a, b) Source #
Associates each Right
in a stream with the latest Left
that came before it.
>>>
l = [Right 10, Left "a", Right 1, Right 2, Left "b", Left "c", Right 20]
>>>
S.fold F.toList . eitherByLeft . S.fromList $ l
[("a",1),("a",2),("c",20)]
chunkOn :: Monad m => Word8 -> Stream m (Either a ByteString) -> Stream m (Either a ByteString) Source #
Chunks up the bytestrings following each Left
by the given word, discarding the given word.
(For instance, the word could be 10
(newline), which gives us lines as the chunks.) The
bytestrings in the resulting stream are the desired chunks.
chunkOnFold :: Monad m => Word8 -> Fold m (Either a ByteString) b -> Fold m (Either a ByteString) b Source #
Chunks up the bytestrings following each Left
by the given word, discarding the given word.
(For instance, the word could be 10
(newline), which gives us lines as the chunks.) The
bytestrings in the provided fold are the desired chunks.
Header
FileTypeRegular | |
FileTypeSymlink | |
FileTypeSocket | |
FileTypeCharDevice | |
FileTypeBlockDevice | |
FileTypeDirectory | |
FileTypeNamedPipe |
headerPathName :: Header -> IO (Maybe ByteString) Source #
headerPathNameUtf8 :: Header -> IO (Maybe ByteString) Source #