DPutils-0.0.2.0: utilities for DP

Safe HaskellNone
LanguageHaskell2010

Pipes.Split.ByteString

Description

Split incombing bytestrings based on bytestrings.

Synopsis

Documentation

type Lens' a b = forall f. Functor f => (b -> f b) -> a -> f a Source #

splitKeepEnd :: Monad m => ByteString -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Splits bytestrings after each pattern pat. Tries to minimize the number of intermediate bytestring constructors.

The following function ske expects a string str and a pattern pat and then returns a tuple with the splitted bytestrings in fst and the return value in snd.

The inner parser parse uses zoom to draw the full inner producer, which should contain just one bytestring, namely one of the split off ones. parse doesn't do anything with the inner producer, except returning the contained bytestring.

parse returns Right $ concat xs on a correct parse, and Left [] once the input has been exhausted.

ske :: ByteString -> ByteString -> ([ByteString],[ByteString],[ByteString])
ske pat str | BS.null pat || BS.null str = ([],[],[])
ske pat str =
  let parse = do
        xs <- zoom (splitKeepEnd pat) PP.drawAll
        case xs of
          [] -> return $ Left []
          xs -> return $ Right $ BS.concat xs
      (a,(b,p)) = runIdentity . P.toListM' $ PP.parsed parse $ PP.yield str
  in (a,b, fst . runIdentity . P.toListM' $ p)

splitKeepStart :: Monad m => ByteString -> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x)) Source #

Split a string into substrings, where each substring starts with pat and continues until just before the next pat (or until there is no more input).

Any prefix that does not start with the substring is kept!

Since each substring is supposed to start with pat, there is a small problem. What about a header that prefixes the string we are interested in?

splitGeneric Source #

Arguments

:: Monad m 
=> (ByteString -> Int -> Int -> Int -> (ByteString, ByteString))

splitter function

-> ByteString

pattern to split on

-> Lens' (Producer ByteString m x) (Producer ByteString m (Producer ByteString m x))

lens into the individual split off bytestrings

Generic splitting function. Takes a bytestring [a,b,c] (where a,b,c are substrings of the bytestring!) and performs the split.