!"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`abcdefghijklmnopqrstuvwxyz{|}~      !"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`abcdefghijklmnopqrstuvwxyz{|}~                                                                02010-2011 Simon Meier, 2010 Jasper van der JeugtBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>unstable, privateGHCUnsafeVHlA builder primitive that always results in sequence of bytes that is no longer than a pre-determined bound.`A builder primitive that always results in a sequence of bytes of a pre-determined, fixed size.0The type used for sizes and sizeBounds of sizes.6Type-constructors supporting lifting of type-products.!Contravariant functors as in the  contravariant package.IA fmap-like operator for builder primitives, both bounded and fixed size.Builder primitives are contravariant so it's like the normal fmap, but backwards (look at the type). (If it helps to remember, the operator symbol is like ( $) but backwards.)QWe can use it for example to prepend and/or append fixed values to an primitive. nshowEncoding ((\x -> ('\'', (x, '\''))) >$< fixed3) 'x' = "'x'" where fixed3 = char7 >*< char7 >*< char7Note that the rather verbose syntax for composition stems from the requirement to be able to compute the size / size bound at compile time.VA pairing/concatenation operator for builder primitives, both bounded and fixed size. For example, ?toLazyByteString (primFixed (char7 >*< char7) ('x','y')) = "xy")We can combine multiple primitives using  multiple times. PtoLazyByteString (primFixed (char7 >*< char7 >*< char7) ('x',('y','z'))) = "xyz"5The size of the sequences of bytes generated by this .The 1 that always results in the zero-length sequence.LEncode a pair by encoding its first component and then its second component.VChange a primitives such that it first applies a function to the value to be encoded.Note that primitives are Contrafunctors  0http://hackage.haskell.org/package/contravariant". Hence, the following laws hold. CcontramapF id = id contramapF f . contramapF g = contramapF (g . f) Convert a  to a .Lift a  to a . >The bound on the size of sequences of bytes generated by this .  Change a C such that it first applies a function to the value to be encoded. Note that s are Contrafunctors  0http://hackage.haskell.org/package/contravariant". Hence, the following laws hold. CcontramapB id = id contramapB f . contramapB g = contramapB (g . f)The 1 that always results in the zero-length sequence. LEncode a pair by encoding its first component and then its second component. Encode an   value using the first  for   values and the second  for  values.Note that the functions ,  , and   (written below using ) suffice to construct :s for all non-recursive algebraic datatypes. For example, YmaybeB :: BoundedPrim () -> BoundedPrim a -> BoundedPrim (Maybe a) maybeB nothing just =  (Left ()) Right  eitherB nothing just Conditionally select a y. For example, we can implement the ASCII primitive that drops characters with Unicode codepoints above 127 as follows. charASCIIDrop =  (< '\128') (fromF char7)     45 (c) 2010 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com> experimentalGHC TrustworthyVN  Encode a  using a  encoding. PRE: The / encoding must have a size of at least 4 bytes. Encode a  using a  encoding. PRE: The / encoding must have a size of at least 8 bytes. (c) 2010 Simon Meier Original serialization code from 'Data.Binary.Builder': (c) Lennart Kolmodin, Ross PattersonBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>GHCUnsafeDURight-shift of a .Right-shift of a .Right-shift of a . Right-shift of a .!6Select an implementation depending on the bit-size of ms. Currently, it produces a runtime failure if the bitsize is different. This is detected by the testsuite. !(c) 2010-2011 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>GHC Trustworthys %Encoding single unsigned bytes as-is.  Encoding s in big endian format.  Encoding s in little endian format.  Encoding s in big endian format.  Encoding s in little endian format. Encoding s in big endian format. Encoding s in little endian format.Encode a single native machine . The cs is encoded in host order, host endian form, for the machine you are on. On a 64 bit machine the  is an 8 byte value, on a 32 bit machine, 4 bytes. Values encoded this way are not portable to different endian or word sized machines, without conversion. Encoding +s in native host order and host endianness. Encoding +s in native host order and host endianness. Encoding +s in native host order and host endianness.#Encoding single signed bytes as-is. Encoding "s in big endian format. Encoding "s in little endian format. Encoding #s in big endian format. Encoding #s in little endian format. Encoding $s in big endian format. Encoding $s in little endian format.Encode a single native machine %. The %cs is encoded in host order, host endian form, for the machine you are on. On a 64 bit machine the % is an 8 byte value, on a 32 bit machine, 4 bytes. Values encoded this way are not portable to different endian or integer sized machines, without conversion. Encoding "+s in native host order and host endianness. Encoding #+s in native host order and host endianness. Encoding $+s in native host order and host endianness. Encode a  in big endian format.  Encode a  in little endian format.! Encode a  in big endian format." Encode a  in little endian format.# Encode a  in native host order and host endianness. Values written this way are not portable to different endian machines, without conversion.$ Encode a * in native host order and host endianness.  !"#$D(c) Don Stewart 2006-2008 (c) Duncan Coutts 2006-2012 BSD-style.dons00@gmail.com, duncan@community.haskell.orgunstable non-portableUnsafe 1D%&A space-efficient representation of a &/ vector, supporting many efficient operations.A %8 contains 8-bit bytes, or by using the operations from Data.ByteString.Char87 it can be interpreted as containing 8-bit characters.&O(n) Pack a null-terminated sequence of bytes, pointed to by an Addr# (an arbitrary machine address assumed to point outside the garbage-collected heap) into a  ByteString. A much faster way to create an Addr# is with an unboxed string literal, than to pack a boxed string. A unboxed string literal is compiled to a static char []C by GHC. Establishing the length of the string requires a call to  strlen(3)l, so the Addr# must point to a null-terminated buffer (as is the case with "string"# literals in GHC). Use unsafePackAddressLen2 if you know the length of the string statically. An example: (literalFS = unsafePackAddress "literal"#This function is unsafes. If you modify the buffer pointed to by the original Addr# this modification will be reflected in the resulting  ByteString$, breaking referential transparency.5Note this also won't work if your Addr# has embedded '\0' characters in the string, as strlen will return too short a length.'5The 0 pointer. Used to indicate the empty Bytestring.(O(1)& Build a ByteString from a ForeignPtr.EIf you do not need the offset parameter then you do should be using  or  instead.)O(1)+ Deconstruct a ForeignPtr from a ByteString*8A way of creating ByteStrings outside the IO monad. The Int2 argument gives the final size of the ByteString.+Like * but instead of giving the final size of the ByteString, it is just an upper bound. The inner action returns the actual size. Unlike ,V the ByteString is not reallocated if the final size is less than the estimated size.-Create ByteString of size l and use action f to fill it's contents..%Create ByteString of up to size size l and use action f4 to fill it's contents which returns its true size./ Create ByteString of up to size l and use action f3 to fill it's contents which returns its true size.,lGiven the maximum size needed and a function to make the contents of a ByteString, createAndTrim makes the %. The generating function is required to return the actual final size (<= the maximum size), and the resulting byte array is realloced to this size.createAndTrim is the main mechanism for creating custom, efficient ByteString functions, using Haskell or C functions to fill the space.0 Wrapper of mallocForeignPtrBytes# with faster implementation for GHC1 still needed25Add two non-negative numbers. Errors out on overflow.3Conversion between & and 4. Should compile to a no-op.5Unsafe conversion between 4 and &<. This is a no-op and silently truncates to 8 bits Chars > '\255'=. It is provided as convenience for ByteString construction.6aSelects words corresponding to white-space characters in the Latin-1 range ordered by frequency.73Selects white-space characters in the Latin-1 range80This "function" has a superficial similarity to unsafePerformIO[ but it is in fact a malevolent agent of chaos. It unpicks the seams of reality (and the 9 monad) so that the normal rules no longer apply. It lulls you into thinking it is reasonable, but when you are not looking it stabs you in the back and aliases all of your mutable buffers. The carcass of many a seasoned Haskell programmer lie strewn at its feet.!Witness the trail of destruction: Uhttps://github.com/haskell/bytestring/commit/71c4b438c675aa360c79d79acc9a491e7bbc26e7 Uhttps://github.com/haskell/bytestring/commit/210c656390ae617d9ee3b8bcff5c88dd17cef8da ,https://ghc.haskell.org/trac/ghc/ticket/3486 ,https://ghc.haskell.org/trac/ghc/ticket/3487 ,https://ghc.haskell.org/trac/ghc/ticket/72707Do not talk about "safe"! You do not know what is safe!_Yield not to its blasphemous call! Flee traveller! Flee or you will be corrupted and devoured!(OffsetLength)(ptr, offset, length)+%:;<=>?@ABCDE&FGHIJKLM'()*+-.,N0235678OPQRS(c) Duncan Coutts 2012-2013 BSD-styleduncan@community.haskell.orgstableghc onlyUnsafe 1DQVǯ 'A compact representation of a & vector.&It has a lower memory overhead than a %W and and does not contribute to heap fragmentation. It can be converted to or from a %R (at the cost of copying the string data). It supports very few other operations.wIt is suitable for use as an internal representation for code that needs to keep many short strings in memory, but it  should not` be used as an interchange type. That is, it should not generally be used in public APIs. The %v type is usually more suitable for use in interfaces; it is more flexible and it supports a wide range of operations.(O(1) . The empty '.)O(1) The length of a '.*O(1) Test whether a ' is empty.+O(1) '. index (subscript) operator, starting from 0. ,O(n) . Convert a % into a '.7This makes a copy, so does not retain the input string.-O(n) . Convert a ' into a %..O(n). Convert a list into a '/O(n) . Convert a ' into a list.T source dataoffset into source destinationnumber of bytes to copyU source datanumber of bytes to copy 'V()*+W,-./TU(c) Duncan Coutts 2012-2013 BSD-styleduncan@community.haskell.orgstableghc only Trustworthy{ '()*+,-./ ',-./(*)+D(c) Don Stewart 2006-2008 (c) Duncan Coutts 2006-2011 BSD-style.dons00@gmail.com, duncan@community.haskell.org provisional non-portableUnsafeD,0 A variety of X for non-empty ByteStrings. 0 omits the check for the empty case, so there is an obligation on the programmer to provide a proof that the ByteString is non-empty.1 A variety of Y for non-empty ByteStrings. 1. omits the check for the empty case. As with 0Q, the programmer must provide a separate proof that the ByteString is non-empty.2 A variety of Z for non-empty ByteStrings. 2. omits the check for the empty case. As with 0Q, the programmer must provide a separate proof that the ByteString is non-empty.3 A variety of [ for non-empty ByteStrings. 3. omits the check for the empty case. As with 0Q, the programmer must provide a separate proof that the ByteString is non-empty.4Unsafe %: index (subscript) operator, starting from 0, returning a & This omits the bounds check, which means there is an accompanying obligation on the programmer to ensure the bounds are checked in some other way.5 A variety of \ which omits the checks on nF so there is an obligation on the programmer to provide a proof that  0 <= n <= ] xs.6 A variety of ^ which omits the checks on nF so there is an obligation on the programmer to provide a proof that  0 <= n <= ] xs.7O(1) 7) provides constant-time construction of %Ls, which is ideal for string literals. It packs a sequence of bytes into a  ByteString, given a raw _. to the string, and the length of the string.This function is unsafe in two ways:the length argument is assumed to be correct. If the length argument is incorrect, it is possible to overstep the end of the byte array.Vif the underying Addr# is later modified, this change will be reflected in resulting  ByteString%, breaking referential transparency.%If in doubt, don't use this function.8O(1) Construct a %~ given a Ptr Word8 to a buffer, a length, and an IO action representing a finalizer. This function is not available on Hugs.This function is unsafe, it is possible to break referential transparency by modifying the underlying buffer pointed to by the first argument. Any changes to the original buffer will be reflected in the resulting  ByteString.9/Explicitly run the finaliser associated with a %W. References to this value after finalisation may generate invalid memory references.This function is unsafe, as there may be other  ByteStringsj referring to the same underlying pages. If you use this, you need to have a proof of some kind that all %Ds ever generated from the underlying byte array are no longer live.:O(n) Build a  ByteString from a CString. This value will have now finalizer associated to it, and will not be garbage collected by Haskell. The ByteString length is calculated using  strlen(3) , and thus the complexity is a O(n).This function is unsafe . If the CStringD is later modified, this change will be reflected in the resulting  ByteString%, breaking referential transparency.;O(1) Build a  ByteString from a  CStringLen. This value will have noa finalizer associated with it, and will not be garbage collected by Haskell. This operation has O(1)6 complexity as we already know the final size, so no  strlen(3) is required.This function is unsafe. If the original  CStringLenD is later modified, this change will be reflected in the resulting  ByteString%, breaking referential transparency.<O(n) Build a  ByteString from a malloced CString. This value will have a free(3) finalizer associated to it.This function is unsafe. If the original CStringD is later modified, this change will be reflected in the resulting  ByteString%, breaking referential transparency.VThis function is also unsafe if you call its finalizer twice, which will result in a  double free8 error, or if you pass it a CString not allocated with malloc.=O(1) Build a  ByteString from a malloced  CStringLen. This value will have a free(3) finalizer associated to it.This function is unsafe. If the original CStringD is later modified, this change will be reflected in the resulting  ByteString%, breaking referential transparency.VThis function is also unsafe if you call its finalizer twice, which will result in a  double free8 error, or if you pass it a CString not allocated with malloc.>O(1) construction Use a  ByteString with a function requiring a CString.6This function does zero copying, and merely unwraps a  ByteString to appear as a CString. It is unsafe in two ways: After calling this function the CString6 shares the underlying byte buffer with the original  ByteString. Thus modifying the CString>, either in C, or using poke, will cause the contents of the  ByteString6 to change, breaking referential transparency. Other  ByteStrings0 created by sharing (such as those produced via \ or ^1) will also reflect these changes. Modifying the CString; will break referential transparency. To avoid this, use  useAsCString%, which makes a copy of the original  ByteString.CStringsY are often passed to functions that require them to be null-terminated. If the original  ByteString+ wasn't null terminated, neither will the CStringA be. It is the programmers responsibility to guarantee that the  ByteString. is indeed null terminated. If in doubt, use  useAsCString.The memory may freed at any point after the subcomputation terminates, so the pointer to the storage must *not* be used after this.?O(1) construction Use a  ByteString with a function requiring a  CStringLen.6This function does zero copying, and merely unwraps a  ByteString to appear as a  CStringLen. It is unsafe: After calling this function the  CStringLen6 shares the underlying byte buffer with the original  ByteString. Thus modifying the  CStringLen>, either in C, or using poke, will cause the contents of the  ByteString6 to change, breaking referential transparency. Other  ByteStrings0 created by sharing (such as those produced via \ or ^1) will also reflect these changes. Modifying the  CStringLen; will break referential transparency. To avoid this, use useAsCStringLen%, which makes a copy of the original  ByteString.&0123456789:;<=>?0123456>?:;<=&789(c) The University of Glasgow 2001, (c) David Roundy 2003-2005, (c) Simon Marlow 2005, (c) Bjorn Bringert 2006, (c) Don Stewart 2005-2008, (c) Duncan Coutts 2006-2013 BSD-style.dons00@gmail.com, duncan@community.haskell.orgstableportable Trustworthy$D7m@O(1) The empty %AO(1) Convert a & into a %BO(n) Convert a [&] into a %.For applications with large numbers of string literals, pack can be a bottleneck. In such cases, consider using packAddress (GHC only).CO(n) Converts a % to a [&].DO(1)$ Test whether a ByteString is empty.EO(1) E* returns the length of a ByteString as an %.FO(n) F[ is analogous to (:) for lists, but of different complexity, as it requires making a copy.GO(n) Append a byte to the end of a %HO(1) Extract the first element of a ByteString, which must be non-empty. An exception will be thrown in the case of an empty ByteString.IO(1) Extract the elements after the head of a ByteString, which must be non-empty. An exception will be thrown in the case of an empty ByteString.JO(1)N Extract the head and tail of a ByteString, returning Nothing if it is empty.KO(1) Extract the last element of a ByteString, which must be finite and non-empty. An exception will be thrown in the case of an empty ByteString.LO(1) Return all the elements of a %V except the last one. An exception will be thrown in the case of an empty ByteString.MO(1) Extract the L and K4 of a ByteString, returning Nothing if it is empty.NO(n) Append two ByteStringsOO(n) O f xs( is the ByteString obtained by applying f to each element of xs.PO(n) P xs% efficiently returns the elements of xs in reverse order.QO(n) The Q function takes a & and a %; and `intersperses' that byte between the elements of the %9. It is analogous to the intersperse function on Lists.RThe R2 function transposes the rows and columns of its % argument.SS, applied to a binary operator, a starting value (typically the left-identity of the operator), and a ByteString, reduces the ByteString using the binary operator, from left to right.TT is like S , but strict in the accumulator.UU, applied to a binary operator, a starting value (typically the right-identity of the operator), and a ByteString, reduces the ByteString using the binary operator, from right to left.VV is like U , but strict in the accumulator.WW is a variant of SM that has no starting value argument, and thus must be applied to non-empty  ByteStringsB. An exception will be thrown in the case of an empty ByteString.X 'foldl1\'' is like Wa, but strict in the accumulator. An exception will be thrown in the case of an empty ByteString.YY is a variant of UM that has no starting value argument, and thus must be applied to non-empty %Bs An exception will be thrown in the case of an empty ByteString.Z 'foldr1\'' is a variant of Y$, but is strict in the accumulator.[O(n)# Concatenate a list of ByteStrings.\Map a function over a % and concatenate the results]O(n)* Applied to a predicate and a ByteString, ]# determines if any element of the % satisfies the predicate.^O(n) Applied to a predicate and a %, ^$ determines if all elements of the % satisfy the predicate._O(n) _" returns the maximum value from a %[ This function will fuse. An exception will be thrown in the case of an empty ByteString.`O(n) `" returns the minimum value from a %[ This function will fuse. An exception will be thrown in the case of an empty ByteString.aThe a( function behaves like a combination of O and S; it applies a function to each element of a ByteString, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new list.bThe b( function behaves like a combination of O and U; it applies a function to each element of a ByteString, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new ByteString.cc is similar to SZ, but returns a list of successive reduced values from the left. This function will fuse. @scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] Note that $last (scanl f z xs) == foldl f z xs.dd is a variant of c? that has no starting value argument. This function will fuse. .scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]e)scanr is the right-to-left dual of scanl.ff is a variant of e% that has no starting value argument.gO(n) g n x is a ByteString of length n with x2 the value of every element. The following holds: .replicate w c = unfoldr w (\u -> Just (u,u)) cThis implemenation uses  memset(3)hO(n), where n# is the length of the result. The h0 function is analogous to the List 'unfoldr'. hV builds a ByteString from a seed value. The function takes the element and returns `4 if it is done producing the ByteString or returns a (a,b), in which case, a& is the next byte in the string, and b* is the seed value for further production. Examples: [ unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0 == pack [0, 1, 2, 3, 4, 5]iO(n) Like h, iq builds a ByteString from a seed value. However, the length of the result is limited by the first argument to i(. This function is more efficient than h1 when the maximum length of the result is known.The following equation relates i and h: ,fst (unfoldrN n f s) == take n (unfoldr f s)jO(1) j n, applied to a ByteString xs, returns the prefix of xs of length n, or xs itself if n > E xs.kO(1) k n xs returns the suffix of xs after the first n elements, or [] if n > E xs.lO(1) l n xs is equivalent to (j n xs, k n xs).mm, applied to a predicate p and a ByteString xs2, returns the longest prefix (possibly empty) of xs of elements that satisfy p.nn p xs$ returns the suffix remaining after m p xs.oo p is equivalent to r (b . p).^Under GHC, a rewrite rule will transform break (==) into a call to the specialised breakByte: 6break ((==) x) = breakByte x break (==x) = breakByte xppi breaks its ByteString argument at the first occurence of the specified byte. It is more efficient than o as it is implemented with  memchr(3). I.e. ,break (=='c') "abcd" == breakByte 'c' "abcd"qq behaves like o but from the end of the %breakEnd p == spanEnd (not.p)rr p xs? breaks the ByteString into two segments. It is equivalent to (m p xs, n p xs)cc breaks its ByteString argument at the first occurence of a byte other than its argument. It is more efficient than 'span (==)' +span (=='c') "abcd" == spanByte 'c' "abcd"ss behaves like r but from the end of the % . We have -spanEnd (not.isSpace) "x y z" == ("x y ","z")and fspanEnd (not . isSpace) ps == let (x,y) = span (not.isSpace) (reverse ps) in (reverse y, reverse x)tO(n) Splits a % into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg. TsplitWith (=='a') "aabbaca" == ["","","bb","c",""] splitWith (=='a') [] == []uO(n) Break a %K into pieces separated by the byte argument, consuming the delimiter. I.e. ~split '\n' "a\nb\nd\ne" == ["a","b","d","e"] split 'a' "aXaXaXa" == ["","X","X","X",""] split 'x' "x" == ["",""]and 9intercalate [c] . split c == id split == splitWith . (==)tAs for all splitting functions in this library, this function does not copy the substrings, it just constructs new  ByteStrings" that are slices of the original.vThe v function takes a ByteString and returns a list of ByteStrings such that the concatenation of the result is equal to the argument. Moreover, each sublist in the result contains only equal elements. For example, :group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]It is a special case of w_, which allows the programmer to supply their own equality test. It is about 40% faster than  groupBy (==)wThe w+ function is the non-overloaded version of v.xO(n) The x function takes a % and a list of %es and concatenates the list after interspersing the first argument between each element of the list.dO(n) intercalateWithByte. An efficient way to join to two ByteStrings with a char. Around 4 times faster than the generalised join.yO(1) %- index (subscript) operator, starting from 0.zO(n) The z? function returns the index of the first element in the given %* which is equal to the query element, or `B if there is no such element. This implementation uses memchr(3).{O(n) The {> function returns the last index of the element in the given %* which is equal to the query element, or `3 if there is no such element. The following holds: HelemIndexEnd c xs == (-) (length xs - 1) `fmap` elemIndex c (reverse xs)|O(n) The | function extends z, by returning the indices of all elements equal to the query element, in ascending order. This implementation uses memchr(3).}Hcount returns the number of times its argument appears in the ByteString count = length . elemIndices@But more efficiently than using length on the intermediate list.~The ~" function takes a predicate and a %Y and returns the index of the first element in the ByteString satisfying the predicate.The  function extends ~Y, by returning the indices of all elements satisfying the predicate, in ascending order.O(n)  is the % membership predicate.O(n)  is the inverse of O(n) y, applied to a predicate and a ByteString, returns a ByteString containing those characters that satisfy the predicate.O(n) The k function takes a predicate and a ByteString, and returns the first element in matching the predicate, or ` if there is no such element. Ffind f p = case findIndex f p of Just n -> Just (p ! n) ; _ -> NothingO(n) The  function takes a predicate a ByteString and returns the pair of ByteStrings with elements which do and do not satisfy the predicate, respectively; i.e., 4partition p bs == (filter p xs, filter (not . p) xs)O(n) The , function takes two ByteStrings and returns e) if the first is a prefix of the second. O(n) The , function takes two ByteStrings and returns aJ the remainder of the second iff the first is its prefix, and otherwise `.O(n) The , function takes two ByteStrings and returns e* iff the first is a suffix of the second.The following holds: 2isSuffixOf x y == reverse x `isPrefixOf` reverse ynHowever, the real implemenation uses memcmp to compare the end of the string only, with no reverse required..O(n) The , function takes two ByteStrings and returns aJ the remainder of the second iff the first is its suffix, and otherwise `.4Check whether one string is a substring of another. isInfixOf p s is equivalent to not (null (findSubstrings p s)).zBreak a string on a substring, returning a pair of the part of the string prior to the match, and the rest of the string.!The following relationships hold: 0break (== c) l == breakSubstring (singleton c) land: findSubstring s l == if null s then Just 0 else case breakSubstring s l of (x,y) | null y -> Nothing | otherwise -> Just (length x)7For example, to tokenise a string, dropping delimiters: mtokenise x y = h : if null t then [] else tokenise x (drop (length x) t) where (h,t) = breakSubstring x y+To skip to the first occurence of a string: snd (breakSubstring x y)1To take the parts of a string before a delimiter: fst (breakSubstring x y)Note that calling `breakSubstring x` does some preprocessing work, so you should avoid unnecessarily duplicating breakSubstring calls with the same pattern.<Get the first index of a substring in another string, or ` if the string is not found. findSubstring p s is equivalent to  listToMaybe (findSubstrings p s).VFind the indexes of all (possibly overlapping) occurances of a substring in a string.O(n)  takes two ByteStrings and returns a list of corresponding pairs of bytes. If one input ByteString is short, excess elements of the longer ByteString are discarded. This is equivalent to a pair of C operations. generalises j by zipping with the function given as the first argument, instead of a tupling function. For example,  (+)J is applied to two ByteStrings to produce the list of corresponding sums.fA specialised version of zipWith for the common case of a simultaneous map over two bytestrings, to build a 3rd. Rewrite rules are used to automatically covert zipWith into zipWith' when a pack is performed on the result of zipWith.O(n) ^ transforms a list of pairs of bytes into a pair of ByteStrings. Note that this performs two B operations.O(n)* Return all initial segments of the given %, shortest first.O(n)( Return all final segments of the given %, longest first.O(n)4 Sort a ByteString efficiently, using counting sort.O(n) construction Use a  ByteString. with a function requiring a null-terminated CString. The CStringn is a copy and will be freed automatically; it must not be stored or used after the subcomputation finishes.O(n) construction Use a  ByteString with a function requiring a  CStringLen . As for  useAsCString, this function makes a copy of the original  ByteStringC. It must not be stored or used after the subcomputation finishes.O(n). Construct a new  ByteString from a CString. The resulting  ByteString' is an immutable copy of the original CString4, and is managed on the Haskell heap. The original CString must be null terminated.O(n). Construct a new  ByteString from a  CStringLen. The resulting  ByteString& is an immutable copy of the original  CStringLen. The  ByteStringD is a normal Haskell value and will be managed on the Haskell heap.O(n) Make a copy of the %_ with its own storage. This is mainly useful to allow the rest of the data pointed to by the % to be garbage collected, for example if a large string has been read in, and only a small part of it is needed in the rest of the program.Read a line from stdin.Read a line from a handle Outputs a % to the specified g. Similar to j except that it will never block. Instead it returns any tail that did not get written. This tail may be @ in the case that the whole string was written, or the whole original string if nothing was written. Partial writes are also possible.Note: on Windows and with Haskell implementation other than GHC, this function does not work correctly; it behaves identically to .A synonym for hPut, for compatibility8Write a ByteString to a handle, appending a newline byteWrite a ByteString to stdout6Write a ByteString to stdout, appending a newline byteRead a % directly from the specified gB. This is far more efficient than reading the characters into a h and then using B. First argument is the Handle to read from, and the second is the number of bytes to read. It returns the bytes read, up to n, or @ if EOF has been reached. is implemented in terms of i.CIf the handle is a pipe or socket, and the writing end is closed, # will behave as if EOF was reached.hGetNonBlocking is similar to , except that it will never block waiting for data to become available, instead it returns only whatever data is available. If there is no data available to be read,  returns @.Note: on Windows and with Haskell implementation other than GHC, this function does not work correctly; it behaves identically to .Like , except that a shorter %f may be returned if there are not enough bytes immediately available to satisfy the whole request. N only blocks if there is no data available, and EOF has not yet been reached.0Read a handle's entire contents strictly into a %.This function reads chunks at a time, increasing the chunk size on each read. The final string is then realloced to the appropriate size. For files > half of available memory, this may lead to memory exhaustion. Consider using  in this case.UThe Handle is closed once the contents have been read, or if an exception is thrown.HgetContents. Read stdin strictly. Equivalent to hGetContents stdin The g- is closed after the contents have been read./The interact function takes a function of type ByteString -> ByteString as its argument. The entire input from the standard input device is passed to this function as its argument, and the resulting string is output on the standard output device.$Read an entire file strictly into a %.Write a % to a file. Append a % to a file.jjo is a variant of findIndex, that returns the length of the string if no element is found, rather than Nothing.String to search forString to search in+Head and tail of string broken at substringString to search for.String to seach in.String to search for.String to seach in.kfirst read sizeinitial buffer size incrementj%@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`abcdefghijklmnopqrstuvwxyz{|}~j%@ABCFGNHJMKILDEOPQxRSTWXUVYZ[\]^_`cdefabghijklmnrsoqvwutyz|{~}pF5G5D(c) Don Stewart 2006-2008 (c) Duncan Coutts 2006-2011 BSD-style.dons00@gmail.com, duncan@community.haskell.orgunstable non-portableUnsafe1LF &A space-efficient representation of a &/ vector, supporting many efficient operations.A lazy 8 contains 8-bit bytes, or by using the operations from Data.ByteString.Lazy.Char87 it can be interpreted as containing 8-bit characters.l5The data type invariant: Every ByteString is either m or consists of non-null %Ls. All functions must preserve this, and the QC properties must check this.n+In a form that checks the invariant lazily.oSmart constructor for p%. Guarantees the data type invariant.BConsume the chunks of a lazy ByteString with a natural right fold._Consume the chunks of a lazy ByteString with a strict, tail-recursive, accumulating left fold.VThe chunk size used for I/O. Currently set to 32k, less the memory management overheadTThe recommended chunk size. Currently set to 4k, less the memory management overheadqEThe memory management overhead. Currently this is tuned for GHC only.pmrstulnoq?(c) Don Stewart 2006 (c) Duncan Coutts 2006-2011 BSD-style.dons00@gmail.com, duncan@community.haskell.orgstableportable Trustworthy_O(1) The empty O(1) Convert a & into a O(n) Convert a '[Word8]' into a .O(n) Converts a  to a '[Word8]'.O(c) Convert a list of strict  into a lazy O(c) Convert a lazy  into a list of strict O(1) Convert a strict  into a lazy .O(n) Convert a lazy  into a strict .Note that this is an  expensive operation that forces the whole lazy ByteString into memory and then copies all the data. If possible, try to avoid converting back and forth between strict and lazy bytestrings.O(1)$ Test whether a ByteString is empty.O(n/c) * returns the length of a ByteString as an $O(1) ! is analogous to '(:)' for lists.O(1) Unlike , 'cons\'' is strict in the ByteString that we are consing onto. More precisely, it forces the head and the first chunk. It does this because, for space efficiency, it may coalesce the new byte onto the first 'chunk' rather than starting a new 'chunk'.CSo that means you can't use a lazy recursive contruction like this: let xs = cons\' c xs in xsYou can however use  , as well as  and &, to build infinite lazy ByteStrings.O(n/c) Append a byte to the end of a O(1)D Extract the first element of a ByteString, which must be non-empty.O(1)N Extract the head and tail of a ByteString, returning Nothing if it is empty.O(1)O Extract the elements after the head of a ByteString, which must be non-empty.O(n/c)O Extract the last element of a ByteString, which must be finite and non-empty.O(n/c) Return all the elements of a  except the last one.O(n/c) Extract the  and 4 of a ByteString, returning Nothing if it is empty.It is no faster than using  and O(n/c) Append two ByteStringsO(n)  f xs( is the ByteString obtained by applying f to each element of xs.O(n)  xs returns the elements of xs in reverse order.The  function takes a & and a ; and `intersperses' that byte between the elements of the 8. It is analogous to the intersperse function on Lists.The 2 function transposes the rows and columns of its  argument., applied to a binary operator, a starting value (typically the left-identity of the operator), and a ByteString, reduces the ByteString using the binary operator, from left to right. 'foldl\'' is like  , but strict in the accumulator., applied to a binary operator, a starting value (typically the right-identity of the operator), and a ByteString, reduces the ByteString using the binary operator, from right to left. is a variant of M that has no starting value argument, and thus must be applied to non-empty  ByteStrings. 'foldl1\'' is like  , but strict in the accumulator. is a variant of M that has no starting value argument, and thus must be applied to non-empty sO(n)# Concatenate a list of ByteStrings.Map a function over a  and concatenate the resultsO(n)* Applied to a predicate and a ByteString, # determines if any element of the  satisfies the predicate.O(n) Applied to a predicate and a , $ determines if all elements of the  satisfy the predicate.O(n) " returns the maximum value from a O(n) " returns the minimum value from a The ( function behaves like a combination of  and ; it applies a function to each element of a ByteString, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new ByteString.The ( function behaves like a combination of  and ; it applies a function to each element of a ByteString, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new ByteString. is similar to Z, but returns a list of successive reduced values from the left. This function will fuse. @scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] Note that $last (scanl f z xs) == foldl f z xs. f x= returns an infinite ByteString of repeated applications of f to x: %iterate f x == [x, f x, f (f x), ...] x! is an infinite ByteString, with x the value of every element.O(n)  n x is a ByteString of length n with x the value of every element.t ties a finite ByteString into a circular one, or equivalently, the infinite repetition of the original ByteString.O(n) The / function is analogous to the List 'unfoldr'. U builds a ByteString from a seed value. The function takes the element and returns `4 if it is done producing the ByteString or returns a (a,b), in which case, a( is a prepending to the ByteString and b2 is used as the next element in a recursive call.O(n/c)  n, applied to a ByteString xs, returns the prefix of xs of length n, or xs itself if n >  xs.O(n/c)  n xs returns the suffix of xs after the first n elements, or [] if n >  xs.O(n/c)  n xs is equivalent to ( n xs,  n xs)., applied to a predicate p and a ByteString xs2, returns the longest prefix (possibly empty) of xs of elements that satisfy p. p xs$ returns the suffix remaining after  p xs. p is equivalent to  (b . p). p xs? breaks the ByteString into two segments. It is equivalent to ( p xs,  p xs)O(n) Splits a  into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg. TsplitWith (=='a') "aabbaca" == ["","","bb","c",""] splitWith (=='a') [] == []O(n) Break a K into pieces separated by the byte argument, consuming the delimiter. I.e. ~split '\n' "a\nb\nd\ne" == ["a","b","d","e"] split 'a' "aXaXaXa" == ["","X","X","X",""] split 'x' "x" == ["",""]and 9intercalate [c] . split c == id split == splitWith . (==)tAs for all splitting functions in this library, this function does not copy the substrings, it just constructs new  ByteStrings" that are slices of the original.The  function takes a ByteString and returns a list of ByteStrings such that the concatenation of the result is equal to the argument. Moreover, each sublist in the result contains only equal elements. For example, :group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]It is a special case of A, which allows the programmer to supply their own equality test.The + function is the non-overloaded version of .O(n) The  function takes a  and a list of es and concatenates the list after interspersing the first argument between each element of the list.O(c) - index (subscript) operator, starting from 0.O(n) The ? function returns the index of the first element in the given * which is equal to the query element, or `B if there is no such element. This implementation uses memchr(3). O(n) The > function returns the last index of the element in the given * which is equal to the query element, or `3 if there is no such element. The following holds: HelemIndexEnd c xs == (-) (length xs - 1) `fmap` elemIndex c (reverse xs)O(n) The  function extends , by returning the indices of all elements equal to the query element, in ascending order. This implementation uses memchr(3).Hcount returns the number of times its argument appears in the ByteString count = length . elemIndices@But more efficiently than using length on the intermediate list.The " function takes a predicate and a Y and returns the index of the first element in the ByteString satisfying the predicate.O(n) The k function takes a predicate and a ByteString, and returns the first element in matching the predicate, or ` if there is no such element. Ffind f p = case findIndex f p of Just n -> Just (p ! n) ; _ -> NothingThe  function extends Y, by returning the indices of all elements satisfying the predicate, in ascending order.O(n)  is the  membership predicate.O(n)  is the inverse of O(n) y, applied to a predicate and a ByteString, returns a ByteString containing those characters that satisfy the predicate.O(n) The  function takes a predicate a ByteString and returns the pair of ByteStrings with elements which do and do not satisfy the predicate, respectively; i.e., 4partition p bs == (filter p xs, filter (not . p) xs)O(n) The , function takes two ByteStrings and returns e* iff the first is a prefix of the second. O(n) The , function takes two ByteStrings and returns aJ the remainder of the second iff the first is its prefix, and otherwise `.O(n) The , function takes two ByteStrings and returns e* iff the first is a suffix of the second.The following holds: 2isSuffixOf x y == reverse x `isPrefixOf` reverse yO(n) The , function takes two ByteStrings and returns aJ the remainder of the second iff the first is its suffix, and otherwise `.O(n)  takes two ByteStrings and returns a list of corresponding pairs of bytes. If one input ByteString is short, excess elements of the longer ByteString are discarded. This is equivalent to a pair of  operations. generalises j by zipping with the function given as the first argument, instead of a tupling function. For example,  (+)J is applied to two ByteStrings to produce the list of corresponding sums.O(n) ^ transforms a list of pairs of bytes into a pair of ByteStrings. Note that this performs two  operations.O(n)* Return all initial segments of the given , shortest first.O(n)( Return all final segments of the given , longest first.O(n) Make a copy of the c with its own storage. This is mainly useful to allow the rest of the data pointed to by the  to be garbage collected, for example if a large string has been read in, and only a small part of it is needed in the rest of the program.vRead entire handle contents lazily into a ). Chunks are read on demand, in at most k6-sized chunks. It does not block waiting for a whole k-sized chunk, so if less than kP bytes are available then they will be returned immediately as a smaller chunk.The handle is closed on EOF. Note: the g' should be placed in binary mode with  for v to work correctly.wRead n bytes into a , directly from the specified g, in chunks of size k.xhGetNonBlockingN is similar to v, except that it will never block waiting for data to become available, instead it returns only whatever data is available. Chunks are read on demand, in k-sized chunks.Read entire handle contents lazily into a ;. Chunks are read on demand, using the default chunk size..Once EOF is encountered, the Handle is closed. Note: the g' should be placed in binary mode with  for  to work correctly.Read n bytes into a , directly from the specified g.hGetNonBlocking is similar to , except that it will never block waiting for data to become available, instead it returns only whatever data is available. If there is no data available to be read,  returns .Note: on Windows and with Haskell implementation other than GHC, this function does not work correctly; it behaves identically to .Read an entire file lazily into a 9. The Handle will be held open until EOF is encountered.Write a  to a file. Append a  to a file.9getContents. Equivalent to hGetContents stdin. Will read lazily Outputs a  to the specified gN. The chunks will be written one at a time. Other threads might write to the g between the writes, and hence 3 alone might not be suitable for concurrent writes. Similar to j except that it will never block. Instead it returns any tail that did not get written. This tail may be  in the case that the whole string was written, or the whole original string if nothing was written. Partial writes are also possible.Note: on Windows and with Haskell implementation other than GHC, this function does not work correctly; it behaves identically to .A synonym for hPut, for compatibilityWrite a ByteString to stdout6Write a ByteString to stdout, appending a newline byte/The interact function takes a function of type ByteString -> ByteString as its argument. The entire input from the standard input device is passed to this function as its argument, and the resulting string is output on the standard output device.yyo is a variant of findIndex, that returns the length of the string if no element is found, rather than Nothing.^^555D(c) Don Stewart 2006-2008 (c) Duncan Coutts 2006-2011 BSD-style.dons00@gmail.com, duncan@community.haskell.orgstableportable Trustworthy59 O(1) Convert a 4 into a  O(n) Convert a h into a .  O(n) Converts a  to a h. O(1)  ! is analogous to '(:)' for lists. O(1) Unlike  , 'cons\'' is strict in the ByteString that we are consing onto. More precisely, it forces the head and the first chunk. It does this because, for space efficiency, it may coalesce the new byte onto the first 'chunk' rather than starting a new 'chunk'.CSo that means you can't use a lazy recursive contruction like this: let xs = cons\' c xs in xsYou can however use   , as well as $ and &, to build infinite lazy ByteStrings.O(n) Append a Char to the end of a . Similar to  ", this function performs a memcpy.O(1)D Extract the first element of a ByteString, which must be non-empty.O(1)N Extract the head and tail of a ByteString, returning Nothing if it is empty.O(n/c) Extract the  and 4 of a ByteString, returning Nothing if it is empty.O(1)F Extract the last element of a packed string, which must be non-empty.O(n)  f xs( is the ByteString obtained by applying f to each element of xsO(n) The  function takes a Char and a < and `intersperses' that Char between the elements of the 8. It is analogous to the intersperse function on Lists., applied to a binary operator, a starting value (typically the left-identity of the operator), and a ByteString, reduces the ByteString using the binary operator, from left to right. 'foldl\''. is like foldl, but strict in the accumulator., applied to a binary operator, a starting value (typically the right-identity of the operator), and a packed string, reduces the packed string using the binary operator, from right to left. is a variant of M that has no starting value argument, and thus must be applied to non-empty  ByteStrings. 'foldl1\'' is like  , but strict in the accumulator. is a variant of M that has no starting value argument, and thus must be applied to non-empty sMap a function over a  and concatenate the results)Applied to a predicate and a ByteString, # determines if any element of the  satisfies the predicate.Applied to a predicate and a , $ determines if all elements of the  satisfy the predicate." returns the maximum value from a " returns the minimum value from a    is similar to Z, but returns a list of successive reduced values from the left. This function will fuse. @scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] Note that $last (scanl f z xs) == foldl f z xs.!The !( function behaves like a combination of  and ; it applies a function to each element of a ByteString, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new ByteString."The "( function behaves like a combination of  and ; it applies a function to each element of a ByteString, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new ByteString.## f x= returns an infinite ByteString of repeated applications of f to x: %iterate f x == [x, f x, f (f x), ...]$$ x! is an infinite ByteString, with x the value of every element.%O(n) % n x is a ByteString of length n with x the value of every element.&O(n) The &/ function is analogous to the List 'unfoldr'. &U builds a ByteString from a seed value. The function takes the element and returns `4 if it is done producing the ByteString or returns a (a,b), in which case, a( is a prepending to the ByteString and b2 is used as the next element in a recursive call.'', applied to a predicate p and a ByteString xs2, returns the longest prefix (possibly empty) of xs of elements that satisfy p.(( p xs$ returns the suffix remaining after ' p xs.)) p is equivalent to * (b . p).** p xs? breaks the ByteString into two segments. It is equivalent to (' p xs, ( p xs)+O(n) Break a K into pieces separated by the byte argument, consuming the delimiter. I.e. {split '\n' "a\nb\nd\ne" == ["a","b","d","e"] split 'a' "aXaXaXa" == ["","X","X","X"] split 'x' "x" == ["",""]and 9intercalate [c] . split c == id split == splitWith . (==)tAs for all splitting functions in this library, this function does not copy the substrings, it just constructs new  ByteStrings" that are slices of the original.,O(n) Splits a  into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg. 2splitWith (=='a') "aabbaca" == ["","","bb","c",""]-The -+ function is the non-overloaded version of ..O(1) - index (subscript) operator, starting from 0./O(n) The /? function returns the index of the first element in the given 6 which is equal (by memchr) to the query element, or ` if there is no such element.0O(n) The 0 function extends /[, by returning the indices of all elements equal to the query element, in ascending order.1The 1" function takes a predicate and a X and returns the index of the first element in the ByteString satisfying the predicate.2The 2 function extends 1Y, by returning the indices of all elements satisfying the predicate, in ascending order.3Hcount returns the number of times its argument appears in the ByteString ?count == length . elemIndices count '\n' == length . lines@But more efficiently than using length on the intermediate list.4O(n) 4 is the 1 membership predicate. This implementation uses  memchr(3).5O(n) 5 is the inverse of 46O(n) 6y, applied to a predicate and a ByteString, returns a ByteString containing those characters that satisfy the predicate.7O(n) The 7k function takes a predicate and a ByteString, and returns the first element in matching the predicate, or ` if there is no such element.8O(n) 8 takes two ByteStrings and returns a list of corresponding pairs of Chars. If one input ByteString is short, excess elements of the longer ByteString are discarded. This is equivalent to a pair of  L operations, and so space usage may be large for multi-megabyte ByteStrings99 generalises 8j by zipping with the function given as the first argument, instead of a tupling function. For example, 9 (+)J is applied to two ByteStrings to produce the list of corresponding sums.::t breaks a ByteString up into a list of ByteStrings at newline Chars. The resulting strings do not contain newlines.KAs of bytestring 0.9.0.3, this function is stricter than its list cousin.;; is an inverse operation to :B. It joins lines, after appending a terminating newline to each.<<j breaks a ByteString up into a list of words, which were delimited by Chars representing white space. And tokens isSpace = words=The = function is analogous to the ; function, on words.>readInt reads an Int from the beginning of the ByteString. If there is no integer at the beginning of the string, it returns Nothing, otherwise it just returns the int read, and the rest of the string.?readInteger reads an Integer from the beginning of the ByteString. If there is no integer at the beginning of the string, it returns Nothing, otherwise it just returns the int read, and the rest of the string.@8Write a ByteString to a handle, appending a newline byteA6Write a ByteString to stdout, appending a newline byte`      !"#$%&'()*+,-./0123456789:;<=>?@A`      !"$%#&'(*)-+,:<;=4576./012389>?A@ 5 55D(c) Don Stewart 2006-2008 (c) Duncan Coutts 2006-2011 BSD-style.dons00@gmail.com, duncan@community.haskell.orgstableportable TrustworthyDtDBO(1) Convert a 4 into a %CO(n) Convert a h into a %RFor applications with large numbers of string literals, pack can be a bottleneck.DO(n) Converts a % to a h.EO(n) EV is analogous to (:) for lists, but of different complexity, as it requires a memcpy.FO(n) Append a Char to the end of a %. Similar to E", this function performs a memcpy.GO(1)N Extract the head and tail of a ByteString, returning Nothing if it is empty.HO(1) Extract the L and J4 of a ByteString, returning Nothing if it is empty.IO(1)D Extract the first element of a ByteString, which must be non-empty.JO(1)F Extract the last element of a packed string, which must be non-empty.KO(n) K f xs( is the ByteString obtained by applying f to each element of xsLO(n) The L function takes a Char and a %< and `intersperses' that Char between the elements of the %8. It is analogous to the intersperse function on Lists.MM, applied to a binary operator, a starting value (typically the left-identity of the operator), and a ByteString, reduces the ByteString using the binary operator, from left to right.N 'foldl\''. is like foldl, but strict in the accumulator.OO, applied to a binary operator, a starting value (typically the right-identity of the operator), and a packed string, reduces the packed string using the binary operator, from right to left.P 'foldr\'' is a strict variant of foldrQQ is a variant of MM that has no starting value argument, and thus must be applied to non-empty  ByteStrings.RA strict version of QSS is a variant of OM that has no starting value argument, and thus must be applied to non-empty %sTA strict variant of foldr1UMap a function over a % and concatenate the resultsV)Applied to a predicate and a ByteString, V# determines if any element of the % satisfies the predicate.WApplied to a predicate and a %, W$ determines if all elements of the % satisfy the predicate.XX" returns the maximum value from a %YY" returns the minimum value from a %ZThe Z( function behaves like a combination of K and M; it applies a function to each element of a ByteString, passing an accumulating parameter from left to right, and returning a final value of this accumulator together with the new list.[The [( function behaves like a combination of K and O; it applies a function to each element of a ByteString, passing an accumulating parameter from right to left, and returning a final value of this accumulator together with the new ByteString.\\ is similar to MA, but returns a list of successive reduced values from the left: @scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] Note that $last (scanl f z xs) == foldl f z xs.]] is a variant of \% that has no starting value argument: .scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]^)scanr is the right-to-left dual of scanl.__ is a variant of ^% that has no starting value argument.`O(n) ` n x is a ByteString of length n with x2 the value of every element. The following holds: .replicate w c = unfoldr w (\u -> Just (u,u)) cThis implemenation uses  memset(3)aO(n), where n# is the length of the result. The a0 function is analogous to the List 'unfoldr'. aV builds a ByteString from a seed value. The function takes the element and returns `4 if it is done producing the ByteString or returns a (a,b), in which case, a+ is the next character in the string, and b* is the seed value for further production. Examples: Runfoldr (\x -> if x <= '9' then Just (x, succ x) else Nothing) '0' == "0123456789"bO(n) Like a, bq builds a ByteString from a seed value. However, the length of the result is limited by the first argument to b(. This function is more efficient than a1 when the maximum length of the result is known.The following equation relates b and a: &unfoldrN n f s == take n (unfoldr f s)cc, applied to a predicate p and a ByteString xs2, returns the longest prefix (possibly empty) of xs of elements that satisfy p.dd p xs$ returns the suffix remaining after c p xs.ee p is equivalent to f (b . p).zzi breaks its ByteString argument at the first occurence of the specified char. It is more efficient than e as it is implemented with  memchr(3). I.e. ,break (=='c') "abcd" == breakChar 'c' "abcd"ff p xs? breaks the ByteString into two segments. It is equivalent to (c p xs, d p xs)gg behaves like f but from the end of the % . We have -spanEnd (not.isSpace) "x y z" == ("x y ","z")and fspanEnd (not . isSpace) ps == let (x,y) = span (not.isSpace) (reverse ps) in (reverse y, reverse x)hh behaves like e but from the end of the %breakEnd p == spanEnd (not.p)iO(n) Break a %K into pieces separated by the byte argument, consuming the delimiter. I.e. ~split '\n' "a\nb\nd\ne" == ["a","b","d","e"] split 'a' "aXaXaXa" == ["","X","X","X",""] split 'x' "x" == ["",""]and 9intercalate [c] . split c == id split == splitWith . (==)tAs for all splitting functions in this library, this function does not copy the substrings, it just constructs new  ByteStrings" that are slices of the original.jO(n) Splits a % into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg. 2splitWith (=='a') "aabbaca" == ["","","bb","c",""]kThe k+ function is the non-overloaded version of v.lO(1) %- index (subscript) operator, starting from 0.mO(n) The m? function returns the index of the first element in the given %6 which is equal (by memchr) to the query element, or ` if there is no such element.nO(n) The n> function returns the last index of the element in the given %* which is equal to the query element, or `3 if there is no such element. The following holds: HelemIndexEnd c xs == (-) (length xs - 1) `fmap` elemIndex c (reverse xs)oO(n) The o function extends m[, by returning the indices of all elements equal to the query element, in ascending order.pThe p" function takes a predicate and a %X and returns the index of the first element in the ByteString satisfying the predicate.qThe q function extends pY, by returning the indices of all elements satisfying the predicate, in ascending order.rHcount returns the number of times its argument appears in the ByteString count = length . elemIndicesAlso count '\n' == length . lines@But more efficiently than using length on the intermediate list.sO(n) s is the %1 membership predicate. This implementation uses  memchr(3).tO(n) t is the inverse of suO(n) uy, applied to a predicate and a ByteString, returns a ByteString containing those characters that satisfy the predicate.vO(n) The vk function takes a predicate and a ByteString, and returns the first element in matching the predicate, or ` if there is no such element.wO(n) w takes two ByteStrings and returns a list of corresponding pairs of Chars. If one input ByteString is short, excess elements of the longer ByteString are discarded. This is equivalent to a pair of DL operations, and so space usage may be large for multi-megabyte ByteStringsxx generalises wj by zipping with the function given as the first argument, instead of a tupling function. For example, x (+)J is applied to two ByteStrings to produce the list of corresponding sums.yy^ transforms a list of pairs of Chars into a pair of ByteStrings. Note that this performs two C operations.{ A variety of I for non-empty ByteStrings. { omits the check for the empty case, which is good for performance, but there is an obligation on the programmer to provide a proof that the ByteString is non-empty.||` returns the pair of ByteStrings when the argument is broken at the first whitespace byte. I.e. break isSpace == breakSpace}} efficiently returns the % argument with white space Chars removed from the front. It is more efficient than calling dropWhile for removing whitespace. I.e. dropWhile isSpace == dropSpacezzt breaks a ByteString up into a list of ByteStrings at newline Chars. The resulting strings do not contain newlines.{{ is an inverse operation to zB. It joins lines, after appending a terminating newline to each.||f breaks a ByteString up into a list of words, which were delimited by Chars representing white space.}The } function is analogous to the { function, on words.~readInt reads an Int from the beginning of the ByteString. If there is no integer at the beginning of the string, it returns Nothing, otherwise it just returns the int read, and the rest of the string.readInteger reads an Integer from the beginning of the ByteString. If there is no integer at the beginning of the string, it returns Nothing, otherwise it just returns the int read, and the rest of the string.8Write a ByteString to a handle, appending a newline byte6Write a ByteString to stdout, appending a newline byten%@DEILNPR[jklvxBCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`abcdefghijklmnopqrstuvwxyz{|}~n%@BCDEFNIGHJILDEKPLxRMNQROPST[UVWXY\]^_Z[`abjklcdfgehvkijz|{}stvulmonpqrwxy~E5F5(c) 2011 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com> experimentalGHC Trustworthy(~&An encoding table for Base16 encoding.VThe encoding table for hexadecimal values with lower-case characters; e.g., deadbeef.Encode an octet as 16bit word comprising both encoded nibbles ordered according to the host endianness. Writing these 16bit to memory will write the nibbles in the correct order (i.e. big-endian).~J(c) 2010 Jasper Van der Jeugt (c) 2010 - 2011 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>GHC Trustworthy V8Encode the least 7-bits of a 4 using the ASCII encoding.Decimal encoding of an .Decimal encoding of an ".Decimal encoding of an #.Decimal encoding of an $.Decimal encoding of an %.Decimal encoding of a &.Decimal encoding of a .Decimal encoding of a .Decimal encoding of a .Decimal encoding of a .Hexadecimal encoding of a &.Hexadecimal encoding of a .Hexadecimal encoding of a .Hexadecimal encoding of a .Hexadecimal encoding of a . Encode a && using 2 nibbles (hexadecimal digits). Encode a  using 4 nibbles. Encode a  using 8 nibbles. Encode a  using 16 nibbles. Encode a & using 2 nibbles (hexadecimal digits). Encode a " using 4 nibbles. Encode a # using 8 nibbles. Encode a $ using 16 nibbles.Encode an IEEE  using 8 nibbles.Encode an IEEE  using 16 nibbles.(c) 2010 - 2011 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>unstable, privateGHCUnsafeQV8+A buffer allocation strategy for executing s.A Z action denotes a computation of a value that writes a stream of bytes as a side-effect. |s are strict in their side-effect; i.e., the stream of bytes will always be written before the computed value is returned.s are a generalization of js. The typical use case is the implementation of an encoding that might fail (e.g., an interface to the zlibW compression library or the conversion from Base64 encoded data to 8-bit data). For a I, the only way to handle and report such a failure is ignore it or call . In contrast, a actions are expressive enough to allow reportng and handling such a failure in a pure fashion. () actions are isomorphic to s. The functions  and B convert between these two types. Where possible, you should use ;s, as sequencing them is slightly cheaper than sequencing 4s because they do not carry around a computed value.'s denote sequences of bytes. They are  s where $ is the zero-length sequence and ! is concatenation, which runs in O(1).&s abstract signals to the caller of a . There are three signals: , , or 'insertChunks signalsMs may be called *multiple times* and they must not rise an async. exception./A stream of chunks that are constructed in the 9 monad.VThis datatype serves as the common interface for the buffer-by-buffer execution of a  by '. Typical users of this interface are # or iteratee-style libraries like  enumerator.:The partially filled last buffer together with the result.Yield a  non-empty strict %.A  together with the U of free bytes. The filled space starts at offset 0 and ends at the first free byte.zA range of bytes in a buffer represented by the pointer to the first byte of the range and the pointer to the first byte after the range.9Combined size of the filled and free space in the buffer.(Allocate a new buffer of the given size.Convert the filled part of a  to a strict %.Prepend the filled part of a  to a lazy  trimming it if necessary.RA smart constructor for yielding one chunk that ignores the chunk if it is empty. Convert a  () to a lazy  using . Convert a 0 to a lazy tuple of the result and the written  using .Signal that the current " is done and has computed a value.'Signal that the current buffer is full.Signal that a %# chunk should be inserted directly.Fill a  using a . Construct a . In contrast to s, !s are referentially transparent.&The final build step that returns the  signal.Run a  with the .Run a .The k denoting a zero-length sequence of bytes. This function is only exported for use in rewriting rules. Use  otherwise.Concatenate two Cs. This function is only exported for use in rewriting rules. Use  otherwise.;Flush the current buffer. This introduces a chunk boundary. Construct a  action. In contrast to s, Gs are referentially transparent in the sense that sequencing the same L multiple times yields every time the same value with the same side-effect.Run a . Synonym for  from ; used in rewriting rules. Synonym for  from  and  from ; used in rewriting rules.Run a  as a side-effect of a  () action. Convert a  () action to a .Run a - action redirecting the produced output to a g.!The output is buffered using the gMs associated buffer. If this buffer is too small to execute one step of the 9 action, then it is replaced with a large enough buffer. Execute a X and return the computed result and the bytes written during the computation as a lazy .hThis function is strict in the computed result and lazy in the writing of the bytes. For example, given EinfinitePut = sequence_ (repeat (putBuilder (word8 1))) >> return 0 evaluating the expression 'fst $ putToLazyByteString infinitePut 3does not terminate, while evaluating the expression 0L.head $ snd $ putToLazyByteString infinitePut $does terminate and yields the value  1 :: Word8.cAn illustrative example for these strictness properties is the implementation of Base64 decoding ( #http://en.wikipedia.org/wiki/Base64). *type DecodingState = ... decodeBase64 :: % -> DecodingState -> + (Maybe DecodingState) decodeBase64 = ... "The above function takes a strict % supposed to represent Base64 encoded data and the current decoding state. It writes the decoded bytes as the side-effect of the I and returns the new decoding state, if the decoding of all data in the %- was successful. The checking if the strict % represents Base64 encoded data and the actual decoding are fused. This makes the common case, where all data represents Base64 encoded data, more efficient. It also implies that all data must be decoded before the final decoding state can be returned. s are intended for implementing such fused checking and decoding/encoding, which is reflected in their strictness properties. Execute a E with a buffer-allocation strategy and a continuation. For example,  is implemented as follows. putToLazyByteString =  (  ) (x -> (x, L.empty)) Ensure that there are at least n free bytes for the following .Copy the bytes from a  into the output stream. Construct a  that copies the strict %Js, if it is smaller than the treshold, and inserts it directly otherwise. For example, byteStringThreshold 1024 copies strict %s whose size is less or equal to 1kb, and inserts them directly otherwise. This implies that the average chunk-size of the generated lazy { may be as low as 513 bytes, as there could always be just a single byte between the directly inserted 1025 byte, strict %s. Construct a  that copies the strict %.Use this function to create s from smallish (<= 4kb) %'s or if you need to guarantee that the %1 is not shared with the chunks generated by the . Construct a  that always inserts the strict % directly as a chunk.kThis implies flushing the output buffer, even if it contains just a single byte. You should therefore use  only for large (> 8kb) %^s. Otherwise, the generated chunks are too fragmented to be processed efficiently afterwards. Construct a  that copies the .Copy the bytes from a  into the output stream. Construct a ( that uses the thresholding strategy of  for each chunk of the lazy . Construct a  that copies the lazy . Construct a % that inserts all chunks of the lazy  directly. Create a 2 denoting the same sequence of bytes as a strict %. The  inserts large %\s directly, but copies small ones to ensure that the generated chunks are large on average. Create a 0 denoting the same sequence of bytes as a lazy %. The " inserts large chunks of the lazy \ directly, but copies small ones to ensure that the generated chunks are large on average.The maximal size of a % that is copied. 2 * - to guarantee that on average a chunk is of .6Create a custom allocation strategy. See the code for  and  for examples.>Sanitize a buffer size; i.e., make it at least the size of an %.&Use this strategy for generating lazy s whose chunks are discarded right after they are generated. For example, if you just generate them to write them to a network socket.&Use this strategy for generating lazy s whose chunks are likely to survive one garbage collection. This strategy trims buffers that are filled less than half in order to avoid spilling too much memory.Heavy inlining. Execute a " with custom execution parameters.}This function is inlined despite its heavy code-size to allow fusing with the allocation strategy. For example, the default  execution function toLazyByteString is defined as follows. M{-# NOINLINE toLazyByteString #-} toLazyByteString = toLazyByteStringWith (   ) L.empty where L.empty is the zero-length lazy .&In most cases, the parameters used by toLazyByteString2 give good performance. A sub-performing case of toLazyByteString" is executing short (<128 bytes) }s. In this case, the allocation overhead for the first 4kb buffer and the trimming cost dominate the cost of executing the ". You can avoid this problem using >toLazyByteStringWith (safeStrategy 128 smallChunkSize) L.emptyEThis reduces the allocation and trimming overhead, as all generated zs fit into the first buffer and there is no trimming required, if more than 64 bytes and less than 128 bytes are written. Convert a  to a  stream by executing it on #s allocated according to the given .Next free byte in current Computed valueMinimal size of next .Next free byte in current . to run on the next . This & may assume that it is called with a B of at least the required minimal size; i.e., the caller of this  must guarantee this.Next free byte in current Chunk to insert. to run on next "Build step to use for filling the . Handling the  signal Handling the  signal Handling the  signalBuffer range to fill."Value computed while filling this .A function that fills a +, calls the continuation with the updated = once its done, and signals its caller how to proceed using , , or .eThis function must be referentially transparent; i.e., calling it multiple times with equally sized s must result in the same sequence of bytes being written. If you need mutable state, then you must allocate it anew upon each call of this function. Moroever, this function must call the continuation once its done. Otherwise, concatenation of zs does not work. Finally, this function must write to all bytes that it claims it has written. Otherwise, the resulting R is not guaranteed to be referentially transparent and sensitive data might leak. to run& that writes the byte stream of this  and signals  upon completion. to run Continuation A function that fills a +, calls the continuation with the updated T and its computed value once its done, and signals its caller how to proceed using , , or  signals.eThis function must be referentially transparent; i.e., calling it multiple times with equally sized  s must result in the same sequence of bytes being written and the same value being computed. If you need mutable state, then you must allocate it anew upon each call of this function. Moroever, this function must call the continuation once its done. Otherwise, monadic sequencing of ys does not work. Finally, this function must write to all bytes that it claims it has written. Otherwise, the resulting S is not guaranteed to be referentially transparent and sensitive data might leak. Put to run, that first writes the byte stream of this / and then yields the computed value using the  signal. to executeResult and lazy  written as its side-effect!Buffer allocation strategy to usehContinuation to use for computing the final result and the tail of its side-effect (the written bytes). to executeResulting lazy Input .Input .Buffer allocation function. If `< is given, then a new first buffer should be allocated. If a (oldBuf, minSize), is given, then a buffer with minimal size minSize/ must be returned. The strategy may reuse the  oldBuffer?, if it can guarantee that this referentially transparent and  oldBuffer is large enough.Default buffer size. A predicate trim used allocated returning e9, if the buffer should be trimmed before it is returned.Size of the first bufferSize of successive buffersdAn allocation strategy that does not trim any of the filled buffers before converting it to a chunkSize of first bufferSize of successive buffershAn allocation strategy that guarantees that at least half of the allocated memory is used for live data!Buffer allocation strategy to useLazy + to use as the tail of the generated lazy  to executeResulting lazy !Buffer allocation strategy to use to execute6qM(c) 2010-2011 Simon Meier (c) 2010 Jasper van der JeugtBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>GHC TrustworthyV$4 Encode a value with a .2Encode a list of values from left-to-right with a .*Encode a list of values represented as an  with a .Heavy inlining. Encode all bytes of a strict % from left-to-right with a O. This function is quite versatile. For example, we can use it to construct a D that maps every byte before copying it to the buffer to be filled. wmapToBuilder :: (Word8 -> Word8) -> S.ByteString -> Builder mapToBuilder f = encodeByteStringWithF (contramapF f word8)*We can also use it to hex-encode a strict % as shown by the  byteStringHex example above.Heavy inlining. Encode all bytes of a lazy  from left-to-right with a . Create a $ that encodes values with the given .We rewrite consecutive uses of 4 such that the bound-checks are fused. For example, 9primBounded (word32 c1) `mappend` primBounded (word32 c2)%is rewritten such that the resulting O checks only once, if ther are at 8 free bytes, instead of checking twice, if there are 4 free bytes. This optimization is not observationally equivalent in a strict sense, as it influences the boundaries of the generated chunks. However, for a user of this library it is observationally equivalent, as chunk boundaries of a lazy ! can only be observed through the internal interface. Morevoer, we expect that all primitives write much fewer than 4kb (the default short buffer size). Hence, it is safe to ignore the additional memory spilled due to the more agressive buffer wrapping introduced by this optimization. Create a 6 that encodes a list of values consecutively using a F for each element. This function is more efficient than the canonical Zfilter p = B.toLazyByteString . E.encodeLazyByteStringWithF (E.ifF p E.word8) E.emptyF)  mconcat . map (primBounded w)or foldMap (primBounded w)9because it moves several variables out of the inner loop. Create a > that encodes a sequence generated from a seed value using a  for each sequence element. Create a  that encodes each & of a strict % using a . For example, we can write a  that filters a strict % as follows. >import Data.ByteString.Builder.Primas P (word8, condB, emptyB) 'filterBS p = P.condB p P.word8 P.emptyBChunk-wise application of .Char8 encode a 4.UTF-8 encode a 4.Encode a Unicode character to another datatype, using UTF-8. This function acts as an abstract way of encoding characters, as it is unaware of what needs to happen with the resulting bytes: you have to specify functions to deal with those. 1-byte UTF-8 2-byte UTF-8 3-byte UTF-8 4-byte UTF-8Input 4ResultK  !"#$K  !  "#$K(c) 2010 Jasper Van der Jeugt (c) 2010-2011 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>GHC TrustworthyQAfter running a ; action there are three possibilities for what comes next:EThis means we're all done. All the builder data has now been written.LThis indicates that there may be more data to write. It gives you the next X action. You should call that action with an appropriate buffer. The int indicates the minimum# buffer size required by the next 3 action. That is, if you call the next action you must6 supply it with a buffer length of at least this size.LIn addition to the data that has just been written into your buffer by the 9 action, it gives you a pre-existing chunk of data as a %". It also gives you the following  action. It is safe to run this following action using a buffer with as much free space as was left by the previous run action.A $ represents the result of running a N. It unfolds as a sequence of chunks of data. These chunks come in two forms:San IO action for writing the Builder's data into a user-supplied memory buffer.6a pre-existing chunks of data represented by a strict  ByteStringfWhile this is rather low level, it provides you with full flexibility in how the data is written out.The  itself is an IO action: you supply it with a buffer (as a pointer and length) and it will write data into the buffer. It returns a number indicating how many bytes were actually written (which can be 0). It also returns a " which describes what comes next.Turn a  into its initial  action.Encode a single native machine %. The %a is encoded in host order, host endian form, for the machine you're on. On a 64 bit machine the % is an 8 byte value, on a 32 bit machine, 4 bytes. Values encoded this way are not portable to different endian or int sized machines, without conversion. Encode a "* in native host order and host endianness. Encode a #* in native host order and host endianness. Encode a $* in native host order and host endianness.Encode a single native machine . The a is encoded in host order, host endian form, for the machine you're on. On a 64 bit machine the  is an 8 byte value, on a 32 bit machine, 4 bytes. Values encoded this way are not portable to different endian or word sized machines, without conversion. Encode a * in native host order and host endianness. Encode a * in native host order and host endianness. Encode a * in native host order and host endianness. Encode a r in native host order. Values encoded this way are not portable to different endian machines, without conversion. Encode a  in native host order.SafeR,(c) 2010 - 2011 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>GHC Trustworthy DVq  Encode a h using .Decimal encoding of an  using the ASCII digits.e.g. MtoLazyByteString (int8Dec 42) = "42" toLazyByteString (int8Dec (-1)) = "-1"Decimal encoding of an " using the ASCII digits.Decimal encoding of an # using the ASCII digits.Decimal encoding of an $ using the ASCII digits.Decimal encoding of an % using the ASCII digits.Decimal encoding of a & using the ASCII digits.Decimal encoding of a  using the ASCII digits.Decimal encoding of a  using the ASCII digits.Decimal encoding of a  using the ASCII digits.Decimal encoding of a  using the ASCII digits.Currently slow. Decimal encoding of an IEEE .Currently slow. Decimal encoding of an IEEE .#Shortest hexadecimal encoding of a & using lower-case characters.#Shortest hexadecimal encoding of a  using lower-case characters.#Shortest hexadecimal encoding of a  using lower-case characters.#Shortest hexadecimal encoding of a  using lower-case characters.#Shortest hexadecimal encoding of a  using lower-case characters. Encode a & using 2 nibbles (hexadecimal digits). Encode a " using 4 nibbles. Encode a # using 8 nibbles. Encode a $ using 16 nibbles. Encode a && using 2 nibbles (hexadecimal digits). Encode a  using 4 nibbles. Encode a  using 8 nibbles. Encode a  using 16 nibbles.Encode an IEEE  using 8 nibbles.Encode an IEEE  using 16 nibbles.Encode each byte of a %$ using its fixed-width hex encoding.Encode each byte of a lazy $ using its fixed-width hex encoding.$Maximal power of 10 fitting into an % without using the MSB. 10 ^ 9 for 32 bit ints (31 * log 2 / log 10 = 9.33) 10 ^ 18 for 64 bit ints (63 * log 2 / log 10 = 18.96)2FIXME: Think about also using the MSB. For 64 bit %s this makes a difference.Decimal encoding of an  using the ASCII digits. L(c) 2010 Jasper Van der Jeugt (c) 2010 - 2011 Simon MeierBSD3-style (see LICENSE) Simon Meier <iridcode@gmail.com>GHC Trustworthy~ Execute a + and return the generated chunks as a lazy C. The work is performed lazy, i.e., only when a chunk of the lazy  is forced. Output a  to a g. The + is executed directly on the buffer of the g`. If the buffer is too small (or not present), then it is replaced with a large enough buffer.It is recommended that the g is set to binary and BlockBuffering mode. See hSetBinaryMode and  hSetBuffering.%This function is more efficient than hPut . s because in many cases no buffer allocation has to be done. Moreover, the results of several executions of short s are concatenated in the g9s buffer, therefore avoiding unnecessary buffer flushes."Encode a single signed byte as-is.$Encode a single unsigned byte as-is. Encode an " in little endian format. Encode an # in little endian format. Encode an $ in little endian format. Encode a  in little endian format. Encode a  in little endian format. Encode a  in little endian format. Encode a  in little endian format. Encode a  in little endian format. Encode an " in big endian format. Encode an # in big endian format. Encode an $ in big endian format. Encode a  in big endian format. Encode a  in big endian format. Encode a  in big endian format. Encode a  in big endian format. Encode a  in big endian format.Char7 encode a 4.Char7 encode a h.Char8 encode a 4.Char8 encode a h.UTF-8 encode a 4.UTF-8 encode a h.<< Safe>Safe<   ! " # $ % &'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZE[KLGF\]^_`abcdefghijklmnopqrstuvwxyz{|}~HCE[KLGF\]^`_abcdefghijkmnoqrstuvwxy}~H[KL\]^`caegijkmnorstuvywx}~H[KL\]`c^aegijklmnoprstuvwxyz{|}~H  9:;<./01AB      2 ' 4 6 8 ) + - > @ 3 5 7 ( * , = ?                  !"#$"#%"#&"'( ) * + , - ./01"23 4/05"26 7/08 9"2: ; < =">?">@">A/0B"2CDEFGHIJKLMNOP/0QRSTU/0VWXYZ[\]^_`abcdefghijklmnopqrsQ"t^"t_"tb"ta"t"uF"t/vw"xy"xz/{|}~/0""x"_`efM">""x"x"x" Ed"x"x"x"x"x"~bytestring-0.10.8.2-inplaceData.ByteString.Builder.PrimData.ByteStringData.ByteString.UnsafeData.ByteString.ShortData.ByteString.LazyData.ByteString.Builder.ExtraData.ByteString.Lazy.Char8Data.ByteString.Char8Data.ByteString.Builder"Data.ByteString.Lazy.Builder.ASCII%Data.ByteString.Builder.Prim.Internal.Data.ByteString.Builder.Prim.Internal.Floating5Data.ByteString.Builder.Prim.Internal.UncheckedShifts#Data.ByteString.Builder.Prim.BinaryData.ByteString.InternalunsafePackCStringLenunsafePackCStringFinalizerData.ByteString.Short.InternalData.ByteString.Lazy.Internal System.IOhSetBinaryMode,Data.ByteString.Builder.Prim.Internal.Base16"Data.ByteString.Builder.Prim.ASCII Data.ByteString.Builder.InternalSHShortByteString#Data.ByteString.Lazy.Builder.ExtrasData.ByteString.Builder.ASCIIData.ByteString.Lazy.Builder BoundedPrim FixedPrim>$<>*<emptyFliftFixedToBoundedemptyBeitherBcondBword8word16BEword16LEword32BEword32LEword64BEword64LEwordHost word16Host word32Host word64Hostint8int16BEint16LEint32BEint32LEint64BEint64LEintHost int16Host int32Host int64HostfloatBEfloatLEdoubleBEdoubleLE floatHost doubleHost ByteStringunsafePackAddressemptylengthnullindextoShort fromShortpackunpack unsafeHead unsafeTail unsafeInit unsafeLast unsafeIndex unsafeTake unsafeDropunsafePackAddressLenunsafeFinalizeunsafePackCStringunsafePackMallocCStringunsafePackMallocCStringLenunsafeUseAsCStringunsafeUseAsCStringLen singletonconssnocheadtailunconslastinitunsnocappendmapreverse intersperse transposefoldlfoldl'foldrfoldr'foldl1foldl1'foldr1foldr1'concat concatMapanyallmaximumminimum mapAccumL mapAccumRscanlscanl1scanrscanr1 replicateunfoldrunfoldrNtakedropsplitAt takeWhile dropWhilebreak breakBytebreakEndspanspanEnd splitWithsplitgroupgroupBy intercalate elemIndex elemIndexEnd elemIndicescount findIndex findIndiceselemnotElemfilterfind partition isPrefixOf stripPrefix isSuffixOf stripSuffix isInfixOfbreakSubstring findSubstringfindSubstringszipzipWithunzipinitstailssort useAsCStringuseAsCStringLen packCStringpackCStringLencopygetLinehGetLinehPuthPutNonBlockinghPutStr hPutStrLnputStrputStrLnhGethGetNonBlockinghGetSome hGetContents getContentsinteractreadFile writeFile appendFile foldrChunks foldlChunksdefaultChunkSizesmallChunkSize fromChunkstoChunks fromStricttoStrictcons'iteraterepeatcyclelinesunlineswordsunwordsreadInt readIntegerchar7int8Decint16Decint32Decint64DecintDecword8Dec word16Dec word32Dec word64DecwordDecword8Hex word16Hex word32Hex word64HexwordHex word8HexFixedword16HexFixedword32HexFixedword64HexFixed int8HexFixed int16HexFixed int32HexFixed int64HexFixed floatHexFixeddoubleHexFixedAllocationStrategyBuilderflushbyteStringThresholdbyteStringCopybyteStringInsertshortByteStringlazyByteStringThresholdlazyByteStringCopylazyByteStringInsert byteStringlazyByteStringuntrimmedStrategy safeStrategytoLazyByteStringWith primFixedprimMapListFixedprimUnfoldrFixedprimMapByteStringFixedprimMapLazyByteStringFixed primBoundedprimMapListBoundedprimUnfoldrBoundedprimMapByteStringBoundedprimMapLazyByteStringBoundedchar8charUtf8NextDoneMoreChunk BufferWriter runBuilderfloatDec doubleDec byteStringHexlazyByteStringHex integerDectoLazyByteString hPutBuilderstring7string8 stringUtf8$fIsStringBuilderbyteStringHexFixedlazyByteStringHexFixedSizeMonoidal ContravariantsizepairF contramapFtoB sizeBound contramapBpairBbase Data.EitherEitherLeftRight Data.Maybemaybe fixedPrimrunF storableToF boudedPrimrunBencodeFloatViaWord32Fghc-prim GHC.TypesFloatGHC.WordWord32encodeDoubleViaWord64FDoubleWord64shiftr_wWord shiftr_w16Word16 shiftr_w32 shiftr_w64caseWordSize_32_64GHC.IntInt16Int32Int64IntWord8nullForeignPtrfromForeignPtr toForeignPtr unsafeCreateunsafeCreateUptoN createAndTrimcreate createUptoN createUptoN'mallocByteStringeq checkedAddw2cCharc2w isSpaceWord8 isSpaceChar8accursedUnutterablePerformIOIOPSc_count c_minimum c_maximum c_intersperse c_reversec_free_finalizerc_strlen packBytes packCharsunsafePackLenBytesunsafePackLenCharspackUptoLenBytespackUptoLenChars unpackBytes unpackCharsunpackAppendBytesLazyunpackAppendCharsLazyunpackAppendBytesStrictunpackAppendCharsStrictcreateAndTrim'inlinePerformIOmemchrmemcmpmemcpymemset copyToPtr createFromPtrSBSGHC.List Data.FoldableGHC.PrimAddr#GHC.BaseNothingJust GHC.ClassesnotspanByteintercalateWithByteTruezipWith'GHC.IO.Handle.TypesHandleStringGHC.IO.Handle.TexthGetBuffindIndexOrEndhGetContentsSizeHint invariantEmptycheckInvariantchunk chunkOverhead hGetContentsNhGetNhGetNonBlockingN breakChar breakSpace dropSpace EncodingTable lowerTableencode8_as_16hInt8PutGHC.Errerror putBuilderfromPutMonoidmemptymappend BuildSignal BuildStepdone bufferFull ChunkIOStreambuildStepToCIOSciosToLazyByteStringFinishedYield1Buffer BufferRange bufferSize newBufferbyteStringFromBuffertrimmedChunkFromBufferyield1ciosUnitToLazyByteString GHC.IO.UnsafeunsafeDupablePerformIO insertChunkfillWithBuildStepbuilderfinalBuildSteprunBuilderWithputrunPutap_l<* Applicativeap_r*>>>MonadputToLazyByteStringputToLazyByteStringWith ensureFreewrappedBytesCopyStepshortByteStringCopyStepmaximalCopySizecustomStrategysanitize Data.OldListencodeCharUtf8maxPow10 integer-gmpGHC.Integer.TypeInteger