-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Array, vector and text -- -- This package provides array, slice and text operations @package Z-Data @version 0.6.1.0 -- | ASCII Chars utility. module Z.Data.ASCII -- | Conversion between Word8 and Char. Should compile to a -- no-op. w2c :: Word8 -> Char -- | Unsafe conversion between Char and Word8. This is a -- no-op and silently truncates to 8 bits Chars > \255. c2w :: Char -> Word8 -- |
--   \NUL <= w && w <= \DEL
--   
isASCII :: Word8 -> Bool -- |
--   A ~ Z
--   
isUpper :: Word8 -> Bool -- |
--   a ~ z
--   
isLower :: Word8 -> Bool -- | ISO-8859-1 control letter. isControl :: Word8 -> Bool -- | ISO-8859-1 space letter. isSpace :: Word8 -> Bool -- |
--   0 ~ 9
--   
isDigit :: Word8 -> Bool -- |
--   0 ~ 7
--   
isOctDigit :: Word8 -> Bool -- |
--   0 ~ 9, A ~ F, a ~ f
--   
isHexDigit :: Word8 -> Bool -- |
--   \NUL
--   
pattern NUL :: Word8 -- |
--   \t
--   
pattern TAB :: Word8 -- |
--   \n
--   
pattern NEWLINE :: Word8 -- |
--   \v
--   
pattern VERTICAL_TAB :: Word8 -- |
--   \f
--   
pattern FORM_FEED :: Word8 -- |
--   \r
--   
pattern CARRIAGE_RETURN :: Word8 -- |
--   ' '
--   
pattern SPACE :: Word8 -- |
--   !
--   
pattern EXCLAM :: Word8 -- |
--   "
--   
pattern QUOTE_DOUBLE :: Word8 -- |
--   #
--   
pattern HASH :: Word8 -- |
--   #
--   
pattern NUMBER_SIGN :: Word8 -- |
--   $
--   
pattern DOLLAR :: Word8 -- |
--   %
--   
pattern PERCENT :: Word8 -- |
--   &
--   
pattern AMPERSAND :: Word8 -- |
--   &
--   
pattern AND :: Word8 -- |
--   '
--   
pattern QUOTE_SINGLE :: Word8 -- |
--   (
--   
pattern PAREN_LEFT :: Word8 -- |
--   )
--   
pattern PAREN_RIGHT :: Word8 -- |
--   *
--   
pattern ASTERISK :: Word8 -- |
--   +
--   
pattern PLUS :: Word8 -- |
--   ,
--   
pattern COMMA :: Word8 -- |
--   -
--   
pattern HYPHEN :: Word8 -- |
--   -
--   
pattern MINUS :: Word8 -- |
--   .
--   
pattern PERIOD :: Word8 -- |
--   .
--   
pattern DOT :: Word8 -- |
--   /
--   
pattern SLASH :: Word8 pattern DIGIT_0 :: Word8 pattern DIGIT_1 :: Word8 pattern DIGIT_2 :: Word8 pattern DIGIT_3 :: Word8 pattern DIGIT_4 :: Word8 pattern DIGIT_5 :: Word8 pattern DIGIT_6 :: Word8 pattern DIGIT_7 :: Word8 pattern DIGIT_8 :: Word8 pattern DIGIT_9 :: Word8 -- |
--   :
--   
pattern COLON :: Word8 -- |
--   ;
--   
pattern SEMICOLON :: Word8 -- |
--   <
--   
pattern LESS :: Word8 -- |
--   <
--   
pattern ANGLE_LEFT :: Word8 -- |
--   =
--   
pattern EQUAL :: Word8 -- |
--   >
--   
pattern GREATER :: Word8 -- |
--   >
--   
pattern ANGLE_RIGHT :: Word8 -- |
--   ?
--   
pattern QUESTION :: Word8 -- |
--   @
--   
pattern AT :: Word8 pattern LETTER_A :: Word8 pattern LETTER_B :: Word8 pattern LETTER_C :: Word8 pattern LETTER_D :: Word8 pattern LETTER_E :: Word8 pattern LETTER_F :: Word8 pattern LETTER_G :: Word8 pattern LETTER_H :: Word8 pattern LETTER_I :: Word8 pattern LETTER_J :: Word8 pattern LETTER_K :: Word8 pattern LETTER_L :: Word8 pattern LETTER_M :: Word8 pattern LETTER_N :: Word8 pattern LETTER_O :: Word8 pattern LETTER_P :: Word8 pattern LETTER_Q :: Word8 pattern LETTER_R :: Word8 pattern LETTER_S :: Word8 pattern LETTER_T :: Word8 pattern LETTER_U :: Word8 pattern LETTER_V :: Word8 pattern LETTER_W :: Word8 pattern LETTER_X :: Word8 pattern LETTER_Y :: Word8 pattern LETTER_Z :: Word8 -- |
--   [
--   
pattern BRACKET_LEFT :: Word8 -- |
--   [
--   
pattern SQUARE_LEFT :: Word8 -- |
--   \
--   
pattern BACKSLASH :: Word8 -- |
--   ]
--   
pattern BRACKET_RIGHT :: Word8 -- |
--   ]
--   
pattern SQUARE_RIGHT :: Word8 -- |
--   ^
--   
pattern CIRCUM :: Word8 -- |
--   _
--   
pattern UNDERSCORE :: Word8 -- |
--   `
--   
pattern GRAVE :: Word8 pattern LETTER_a :: Word8 pattern LETTER_b :: Word8 pattern LETTER_c :: Word8 pattern LETTER_d :: Word8 pattern LETTER_e :: Word8 pattern LETTER_f :: Word8 pattern LETTER_g :: Word8 pattern LETTER_h :: Word8 pattern LETTER_i :: Word8 pattern LETTER_j :: Word8 pattern LETTER_k :: Word8 pattern LETTER_l :: Word8 pattern LETTER_m :: Word8 pattern LETTER_n :: Word8 pattern LETTER_o :: Word8 pattern LETTER_p :: Word8 pattern LETTER_q :: Word8 pattern LETTER_r :: Word8 pattern LETTER_s :: Word8 pattern LETTER_t :: Word8 pattern LETTER_u :: Word8 pattern LETTER_v :: Word8 pattern LETTER_w :: Word8 pattern LETTER_x :: Word8 pattern LETTER_y :: Word8 pattern LETTER_z :: Word8 -- |
--   {
--   
pattern BRACE_LEFT :: Word8 -- |
--   {
--   
pattern CURLY_LEFT :: Word8 -- |
--   |
--   
pattern BAR :: Word8 -- |
--   |
--   
pattern OR :: Word8 -- |
--   }
--   
pattern BRACE_RIGHT :: Word8 -- |
--   }
--   
pattern CURLY_RIGHT :: Word8 -- |
--   ~
--   
pattern TILDE :: Word8 -- |
--   \DEL
--   
pattern DEL :: Word8 -- | This module is borrowed from basement's Cast module with conditional -- instances removed. The purpose of Cast is to provide primitive -- types which share the same byte size, so that arrays and vectors -- parameterized by them can be safely coerced without breaking the index -- bounds. You can also use it to directly cast primitives just like -- reinterpret_cast. A Coercible based instance is also -- provide for convenience. module Z.Data.Array.Cast -- | Cast between primitive types of the same size. class Cast source destination cast :: Cast source destination => source -> destination instance GHC.Types.Coercible a b => Z.Data.Array.Cast.Cast a b instance Z.Data.Array.Cast.Cast GHC.Int.Int8 GHC.Word.Word8 instance Z.Data.Array.Cast.Cast GHC.Int.Int16 GHC.Word.Word16 instance Z.Data.Array.Cast.Cast GHC.Int.Int32 GHC.Word.Word32 instance Z.Data.Array.Cast.Cast GHC.Int.Int64 GHC.Word.Word64 instance Z.Data.Array.Cast.Cast GHC.Types.Int GHC.Types.Word instance Z.Data.Array.Cast.Cast GHC.Word.Word8 GHC.Int.Int8 instance Z.Data.Array.Cast.Cast GHC.Word.Word16 GHC.Int.Int16 instance Z.Data.Array.Cast.Cast GHC.Word.Word32 GHC.Int.Int32 instance Z.Data.Array.Cast.Cast GHC.Word.Word64 GHC.Int.Int64 instance Z.Data.Array.Cast.Cast GHC.Types.Word GHC.Types.Int instance Z.Data.Array.Cast.Cast GHC.Word.Word64 GHC.Types.Double instance Z.Data.Array.Cast.Cast GHC.Word.Word32 GHC.Types.Float instance Z.Data.Array.Cast.Cast GHC.Types.Double GHC.Word.Word64 instance Z.Data.Array.Cast.Cast GHC.Types.Float GHC.Word.Word32 instance Z.Data.Array.Cast.Cast GHC.Int.Int64 GHC.Types.Double instance Z.Data.Array.Cast.Cast GHC.Int.Int32 GHC.Types.Float instance Z.Data.Array.Cast.Cast GHC.Types.Double GHC.Int.Int64 instance Z.Data.Array.Cast.Cast GHC.Types.Float GHC.Int.Int32 -- | This module implements unaligned element access with ghc primitives -- (> 8.6), which can be used as a simple binary encoding / decoding -- method. module Z.Data.Array.Unaligned newtype UnalignedSize a UnalignedSize :: Int -> UnalignedSize a [getUnalignedSize] :: UnalignedSize a -> Int -- | Primitive types which can be unaligned accessed -- -- It can also be used as a lightweight method to peek/poke value from/to -- C structs when you pass MutableByteArray# to FFI as struct -- pointer, e.g. -- --
--   -- | note the .hsc syntax
--   peekSocketAddrMBA :: HasCallStack => MBA## SocketAddr -> IO SocketAddr
--   peekSocketAddrMBA p = do
--       family <- peekMBA p (#offset struct sockaddr, sa_family)
--       case family :: CSaFamily of
--           (#const AF_INET) -> do
--               addr <- peekMBA p (#offset struct sockaddr_in, sin_addr)
--               port <- peekMBA p (#offset struct sockaddr_in, sin_port)
--               return (SocketAddrInet (PortNumber port) addr)
--           ....
--   
class Unaligned a -- | byte size unalignedSize :: Unaligned a => UnalignedSize a -- | index element off byte array with offset in bytes(maybe unaligned) indexWord8ArrayAs# :: Unaligned a => ByteArray# -> Int# -> a -- | read element from byte array with offset in bytes(maybe unaligned) readWord8ArrayAs# :: Unaligned a => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) -- | write element to byte array with offset in bytes(maybe unaligned) writeWord8ArrayAs# :: Unaligned a => MutableByteArray# s -> Int# -> a -> State# s -> State# s -- | IO version of writeWord8ArrayAs# but more convenient to write -- manually. peekMBA :: Unaligned a => MutableByteArray# RealWorld -> Int -> IO a -- | IO version of readWord8ArrayAs# but more convenient to write -- manually. pokeMBA :: Unaligned a => MutableByteArray# RealWorld -> Int -> a -> IO () -- | index element off byte array with offset in bytes(maybe unaligned) indexBA :: Unaligned a => ByteArray# -> Int -> a -- | Lifted version of writeWord8ArrayAs# writeWord8ArrayAs :: (PrimMonad m, Unaligned a) => MutableByteArray (PrimState m) -> Int -> a -> m () -- | Lifted version of readWord8ArrayAs# readWord8ArrayAs :: (PrimMonad m, Unaligned a) => MutableByteArray (PrimState m) -> Int -> m a -- | Lifted version of indexWord8ArrayAs# indexWord8ArrayAs :: Unaligned a => ByteArray -> Int -> a -- | Lifted version of writeWord8ArrayAs# writePrimWord8ArrayAs :: (PrimMonad m, Unaligned a) => MutablePrimArray (PrimState m) Word8 -> Int -> a -> m () -- | Lifted version of readWord8ArrayAs# readPrimWord8ArrayAs :: (PrimMonad m, Unaligned a) => MutablePrimArray (PrimState m) Word8 -> Int -> m a -- | Lifted version of indexWord8ArrayAs# indexPrimWord8ArrayAs :: Unaligned a => PrimArray Word8 -> Int -> a -- | Encode PrimArray elements in big endian. primArrayToBE :: forall a. (Prim a, Unaligned (BE a)) => PrimArray a -> Int -> Int -> PrimArray Word8 -- | Decode PrimArray elements in big endian. primArrayFromBE :: forall a. (Prim a, Unaligned (BE a)) => PrimArray Word8 -> Int -> Int -> PrimArray a -- | little endianess wrapper newtype LE a LE :: a -> LE a [getLE] :: LE a -> a -- | big endianess wrapper newtype BE a BE :: a -> BE a [getBE] :: BE a -> a instance forall k (a :: k). GHC.Num.Num (Z.Data.Array.Unaligned.UnalignedSize a) instance forall k (a :: k). GHC.Classes.Ord (Z.Data.Array.Unaligned.UnalignedSize a) instance forall k (a :: k). GHC.Classes.Eq (Z.Data.Array.Unaligned.UnalignedSize a) instance forall k (a :: k). GHC.Show.Show (Z.Data.Array.Unaligned.UnalignedSize a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Z.Data.Array.Unaligned.LE a) instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Array.Unaligned.LE a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Z.Data.Array.Unaligned.BE a) instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Array.Unaligned.BE a) instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CChar instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CSChar instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CUChar instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CShort instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CUShort instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CInt instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CUInt instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CLong instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CULong instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CPtrdiff instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CSize instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CWchar instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CSigAtomic instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CLLong instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CULLong instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CBool instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CIntPtr instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CUIntPtr instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CIntMax instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CUIntMax instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CClock instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CTime instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CUSeconds instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CSUSeconds instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CFloat instance Z.Data.Array.Unaligned.Unaligned Foreign.C.Types.CDouble instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Word.Word16) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Word.Word32) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Word.Word64) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Types.Word) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Int.Int16) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Int.Int32) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Int.Int64) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Types.Int) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Types.Float) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Types.Double) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.BE GHC.Types.Char) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Word.Word16) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Word.Word32) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Word.Word64) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Types.Word) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Int.Int16) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Int.Int32) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Int.Int64) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Types.Int) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Types.Float) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Types.Double) instance Z.Data.Array.Unaligned.Unaligned (Z.Data.Array.Unaligned.LE GHC.Types.Char) instance Z.Data.Array.Unaligned.Unaligned GHC.Word.Word8 instance Z.Data.Array.Unaligned.Unaligned GHC.Int.Int8 instance Z.Data.Array.Unaligned.Unaligned GHC.Word.Word16 instance Z.Data.Array.Unaligned.Unaligned GHC.Word.Word32 instance Z.Data.Array.Unaligned.Unaligned GHC.Word.Word64 instance Z.Data.Array.Unaligned.Unaligned GHC.Types.Word instance Z.Data.Array.Unaligned.Unaligned GHC.Int.Int16 instance Z.Data.Array.Unaligned.Unaligned GHC.Int.Int32 instance Z.Data.Array.Unaligned.Unaligned GHC.Int.Int64 instance Z.Data.Array.Unaligned.Unaligned GHC.Types.Int instance Z.Data.Array.Unaligned.Unaligned (GHC.Ptr.Ptr a) instance Z.Data.Array.Unaligned.Unaligned GHC.Types.Float instance Z.Data.Array.Unaligned.Unaligned GHC.Types.Double instance Z.Data.Array.Unaligned.Unaligned GHC.Types.Char instance (Z.Data.Array.Unaligned.Unaligned a, Z.Data.Array.Unaligned.Unaligned b) => Z.Data.Array.Unaligned.Unaligned (a, b) instance (Z.Data.Array.Unaligned.Unaligned a, Z.Data.Array.Unaligned.Unaligned b, Z.Data.Array.Unaligned.Unaligned c) => Z.Data.Array.Unaligned.Unaligned (a, b, c) instance (Z.Data.Array.Unaligned.Unaligned a, Z.Data.Array.Unaligned.Unaligned b, Z.Data.Array.Unaligned.Unaligned c, Z.Data.Array.Unaligned.Unaligned d) => Z.Data.Array.Unaligned.Unaligned (a, b, c, d) instance (Z.Data.Array.Unaligned.Unaligned a, Z.Data.Array.Unaligned.Unaligned b, Z.Data.Array.Unaligned.Unaligned c, Z.Data.Array.Unaligned.Unaligned d, Z.Data.Array.Unaligned.Unaligned e) => Z.Data.Array.Unaligned.Unaligned (a, b, c, d, e) instance (Z.Data.Array.Unaligned.Unaligned a, Z.Data.Array.Unaligned.Unaligned b, Z.Data.Array.Unaligned.Unaligned c, Z.Data.Array.Unaligned.Unaligned d, Z.Data.Array.Unaligned.Unaligned e, Z.Data.Array.Unaligned.Unaligned f) => Z.Data.Array.Unaligned.Unaligned (a, b, c, d, e, f) instance (Z.Data.Array.Unaligned.Unaligned a, Z.Data.Array.Unaligned.Unaligned b, Z.Data.Array.Unaligned.Unaligned c, Z.Data.Array.Unaligned.Unaligned d, Z.Data.Array.Unaligned.Unaligned e, Z.Data.Array.Unaligned.Unaligned f, Z.Data.Array.Unaligned.Unaligned g) => Z.Data.Array.Unaligned.Unaligned (a, b, c, d, e, f, g) instance (Z.Data.Array.Unaligned.Unaligned a, Z.Data.Array.Unaligned.Unaligned b, Z.Data.Array.Unaligned.Unaligned c, Z.Data.Array.Unaligned.Unaligned d, Z.Data.Array.Unaligned.Unaligned e, Z.Data.Array.Unaligned.Unaligned f, Z.Data.Array.Unaligned.Unaligned g, Z.Data.Array.Unaligned.Unaligned h) => Z.Data.Array.Unaligned.Unaligned (a, b, c, d, e, f, g, h) -- | GHC contains three general classes of value types: -- --
    --
  1. Unboxed types: values are machine values made up of fixed numbers -- of bytes
  2. --
  3. Unlifted types: values are pointers, but strictly evaluated
  4. --
  5. Lifted types: values are pointers, lazily evaluated
  6. --
-- -- The first category can be stored in a ByteArray, and this -- allows types in category 3 that are simple wrappers around category 1 -- types to be stored more efficiently using a ByteArray. This -- module provides the same facility for category 2 types. -- -- GHC has two primitive types, ArrayArray# and -- MutableArrayArray#. These are arrays of pointers, but of -- category 2 values, so they are known to not be bottom. This allows -- types that are wrappers around such types to be stored in an array -- without an extra level of indirection. -- -- The way that the ArrayArray# API works is that one can read and -- write ArrayArray# values to the positions. This works because -- all category 2 types share a uniform representation, unlike unboxed -- values which are represented by varying (by type) numbers of bytes. -- However, using the this makes the internal API very unsafe to use, as -- one has to coerce values to and from ArrayArray#. -- -- The API presented by this module is more type safe. -- UnliftedArray and MutableUnliftedArray are parameterized -- by the type of arrays they contain, and the coercions necessary are -- abstracted into a class, PrimUnlifted, of things that are -- eligible to be stored. module Z.Data.Array.UnliftedArray -- | Types with TYPE UnliftedRep, which can be stored / -- retrieved in ArrayArray#. class PrimUnlifted a writeUnliftedArray# :: PrimUnlifted a => MutableArrayArray# s -> Int# -> a -> State# s -> State# s readUnliftedArray# :: PrimUnlifted a => MutableArrayArray# s -> Int# -> State# s -> (# State# s, a #) indexUnliftedArray# :: PrimUnlifted a => ArrayArray# -> Int# -> a -- | Mutable array holding PrimUnlifted values. data MutableUnliftedArray s a MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s a -- | Array holding PrimUnlifted values. data UnliftedArray a UnliftedArray :: ArrayArray# -> UnliftedArray a -- | Creates a new MutableUnliftedArray. This function is unsafe -- because it initializes all elements of the array as pointers to the -- array itself. Attempting to read one of these elements before writing -- to it is in effect an unsafe coercion from the -- MutableUnliftedArray s a to the element type. unsafeNewUnliftedArray :: PrimMonad m => Int -> m (MutableUnliftedArray (PrimState m) a) -- | Creates a new MutableUnliftedArray with the specified value as -- initial contents. This is slower than unsafeNewUnliftedArray, -- but safer. newUnliftedArray :: (PrimMonad m, PrimUnlifted a) => Int -> a -> m (MutableUnliftedArray (PrimState m) a) setUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> Int -> a -> m () -- | Yields the length of an UnliftedArray. sizeofUnliftedArray :: UnliftedArray e -> Int -- | Yields the length of a MutableUnliftedArray. sizeofMutableUnliftedArray :: MutableUnliftedArray s e -> Int writeUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> a -> m () readUnliftedArray :: (PrimMonad m, PrimUnlifted a) => MutableUnliftedArray (PrimState m) a -> Int -> m a indexUnliftedArray :: PrimUnlifted a => UnliftedArray a -> Int -> a -- | Freezes a MutableUnliftedArray, yielding an -- UnliftedArray. This simply marks the array as frozen in place, -- so it should only be used when no further modifications to the mutable -- array will be performed. unsafeFreezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> m (UnliftedArray a) -- | Determines whether two MutableUnliftedArray values are the -- same. This is object/pointer identity, not based on the contents. sameMutableUnliftedArray :: MutableUnliftedArray s a -> MutableUnliftedArray s a -> Bool -- | Copies the contents of an immutable array into a mutable array. copyUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> UnliftedArray a -> Int -> Int -> m () -- | Copies the contents of one mutable array into another. copyMutableUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> MutableUnliftedArray (PrimState m) a -> Int -> Int -> m () -- | Freezes a portion of a MutableUnliftedArray, yielding an -- UnliftedArray. This operation is safe, in that it copies the -- frozen portion, and the existing mutable array may still be used -- afterward. freezeUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> Int -> m (UnliftedArray a) -- | Thaws a portion of an UnliftedArray, yielding a -- MutableUnliftedArray. This copies the thawed portion, so -- mutations will not affect the original array. thawUnliftedArray :: PrimMonad m => UnliftedArray a -> Int -> Int -> m (MutableUnliftedArray (PrimState m) a) -- | Creates a copy of a portion of an UnliftedArray cloneUnliftedArray :: UnliftedArray a -> Int -> Int -> UnliftedArray a -- | Creates a new MutableUnliftedArray containing a copy of a -- portion of another mutable array. cloneMutableUnliftedArray :: PrimMonad m => MutableUnliftedArray (PrimState m) a -> Int -> Int -> m (MutableUnliftedArray (PrimState m) a) instance Z.Data.Array.UnliftedArray.PrimUnlifted (Data.Primitive.PrimArray.PrimArray a) instance Z.Data.Array.UnliftedArray.PrimUnlifted Data.Primitive.ByteArray.ByteArray instance Z.Data.Array.UnliftedArray.PrimUnlifted (Data.Primitive.ByteArray.MutableByteArray s) instance Z.Data.Array.UnliftedArray.PrimUnlifted (Data.Primitive.PrimArray.MutablePrimArray s a) instance Z.Data.Array.UnliftedArray.PrimUnlifted (GHC.MVar.MVar a) instance Z.Data.Array.UnliftedArray.PrimUnlifted (GHC.Conc.Sync.TVar a) instance Z.Data.Array.UnliftedArray.PrimUnlifted (GHC.STRef.STRef s a) instance Z.Data.Array.UnliftedArray.PrimUnlifted (GHC.IORef.IORef a) -- | Unified unboxed and boxed array operations using type family. -- -- All operations are NOT bound checked, if you need checked operations -- please use Z.Data.Array.Checked. It exports exactly same APIs -- so that you can switch between without pain. -- -- Some mnemonics: -- -- module Z.Data.Array -- | A typeclass to unify box & unboxed, mutable & immutable array -- operations. -- -- Most of these functions simply wrap their primitive counterpart, if -- there's no primitive ones, we polyfilled using other operations to get -- the same semantics. -- -- One exception is that shrinkMutableArr only perform closure -- resizing on PrimArray because current RTS support only that, -- shrinkMutableArr will do nothing on other array type. -- -- It's reasonable to trust GHC with specializing & inlining these -- polymorphric functions. They are used across this package and perform -- identical to their monomophric counterpart. class Arr (arr :: * -> *) a where { -- | Mutable version of this array type. type family MArr arr = (mar :: * -> * -> *) | mar -> arr; } -- | Make a new array with given size. -- -- For boxed array, all elements are uninitialized which shall not -- be accessed. For primitive array, elements are just random garbage. newArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => Int -> m (MArr arr s a) -- | Make a new array and fill it with an initial value. newArrWith :: (Arr arr a, PrimMonad m, PrimState m ~ s) => Int -> a -> m (MArr arr s a) -- | Index mutable array in a primitive monad. readArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m a -- | Write mutable array in a primitive monad. writeArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> a -> m () -- | Fill mutable array with a given value. setArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> a -> m () -- | Index immutable array, which is a pure operation. This operation often -- result in an indexing thunk for lifted arrays, use 'indexArr'' or -- indexArrM if that's not desired. indexArr :: Arr arr a => arr a -> Int -> a -- | Index immutable array, pattern match on the unboxed unit tuple to -- force indexing (without forcing the element). indexArr' :: Arr arr a => arr a -> Int -> (# a #) -- | Index immutable array in a primitive monad, this helps in situations -- that you want your indexing result is not a thunk referencing whole -- array. indexArrM :: (Arr arr a, Monad m) => arr a -> Int -> m a -- | Safely freeze mutable array by make a immutable copy of its slice. freezeArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> m (arr a) -- | Safely thaw immutable array by make a mutable copy of its slice. thawArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => arr a -> Int -> Int -> m (MArr arr s a) -- | In place freeze a mutable array, the original mutable array can not be -- used anymore. unsafeFreezeArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> m (arr a) -- | In place thaw a immutable array, the original immutable array can not -- be used anymore. unsafeThawArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => arr a -> m (MArr arr s a) -- | Copy a slice of immutable array to mutable array at given offset. copyArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> arr a -> Int -> Int -> m () -- | Copy a slice of mutable array to mutable array at given offset. The -- two mutable arrays shall no be the same one. copyMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> MArr arr s a -> Int -> Int -> m () -- | Copy a slice of mutable array to mutable array at given offset. The -- two mutable arrays may be the same one. moveArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> MArr arr s a -> Int -> Int -> m () -- | Create immutable copy. cloneArr :: Arr arr a => arr a -> Int -> Int -> arr a -- | Create mutable copy. cloneMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> Int -> m (MArr arr s a) -- | Resize mutable array to given size. resizeMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m (MArr arr s a) -- | Shrink mutable array to given size. This operation only works on -- primitive arrays. For some array types, this is a no-op, e.g. -- sizeOfMutableArr will not change. shrinkMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> Int -> m () -- | Is two mutable array are reference equal. sameMutableArr :: Arr arr a => MArr arr s a -> MArr arr s a -> Bool -- | Size of immutable array. sizeofArr :: Arr arr a => arr a -> Int -- | Size of mutable array. sizeofMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> m Int -- | Is two immutable array are referencing the same one. -- -- Note that sameArr 's result may change depending on compiler's -- optimizations, for example let arr = runST ... in arr -- sameArr arr may return false if compiler decides to inline -- it. -- -- See https://ghc.haskell.org/trac/ghc/ticket/13908 for more -- background. sameArr :: Arr arr a => arr a -> arr a -> Bool singletonArr :: Arr arr a => a -> arr a doubletonArr :: Arr arr a => a -> a -> arr a -- | Modify(strictly) an immutable array's element at given index to -- produce a new array. modifyIndexArr :: Arr arr a => arr a -> Int -> Int -> Int -> (a -> a) -> arr a -- | Insert an immutable array's element at given index to produce a new -- array. insertIndexArr :: Arr arr a => arr a -> Int -> Int -> Int -> a -> arr a -- | Delete an immutable array's element at given index to produce a new -- array. deleteIndexArr :: Arr arr a => arr a -> Int -> Int -> Int -> arr a -- | RealWorld is deeply magical. It is primitive, but it -- is not unlifted (hence ptrArg). We never manipulate -- values of type RealWorld; it's only used in the type system, -- to parameterise State#. data RealWorld -- | Boxed arrays data Array a Array :: Array# a -> Array a [array#] :: Array a -> Array# a -- | Mutable boxed arrays associated with a primitive state token. data MutableArray s a MutableArray :: MutableArray# s a -> MutableArray s a [marray#] :: MutableArray s a -> MutableArray# s a data SmallArray a SmallArray :: SmallArray# a -> SmallArray a data SmallMutableArray s a SmallMutableArray :: SmallMutableArray# s a -> SmallMutableArray s a -- | Bottom value (throw (UndefinedElement -- uninitialized)) for initialize new boxed -- array(Array, SmallArray..). uninitialized :: a -- | Arrays of unboxed elements. This accepts types like Double, -- Char, Int, and Word, as well as their -- fixed-length variants (Word8, Word16, etc.). Since -- the elements are unboxed, a PrimArray is strict in its -- elements. This differs from the behavior of Array, which is -- lazy in its elements. data PrimArray a PrimArray :: ByteArray# -> PrimArray a -- | Mutable primitive arrays associated with a primitive state token. -- These can be written to and read from in a monadic context that -- supports sequencing such as IO or ST. Typically, a -- mutable primitive array will be built and then convert to an immutable -- primitive array using unsafeFreezePrimArray. However, it is -- also acceptable to simply discard a mutable primitive array since it -- lives in managed memory and will be garbage collected when no longer -- referenced. data MutablePrimArray s a MutablePrimArray :: MutableByteArray# s -> MutablePrimArray s a -- | Class of types supporting primitive array operations. This includes -- interfacing with GC-managed memory (functions suffixed with -- ByteArray#) and interfacing with unmanaged memory (functions -- suffixed with Addr#). Endianness is platform-dependent. class Prim a -- | Size of values of type a. The argument is not used. sizeOf# :: Prim a => a -> Int# -- | Alignment of values of type a. The argument is not used. alignment# :: Prim a => a -> Int# -- | Read a value from the array. The offset is in elements of type -- a rather than in bytes. indexByteArray# :: Prim a => ByteArray# -> Int# -> a -- | Read a value from the mutable array. The offset is in elements of type -- a rather than in bytes. readByteArray# :: Prim a => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) -- | Write a value to the mutable array. The offset is in elements of type -- a rather than in bytes. writeByteArray# :: Prim a => MutableByteArray# s -> Int# -> a -> State# s -> State# s -- | Fill a slice of the mutable array with a value. The offset and length -- of the chunk are in elements of type a rather than in bytes. setByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s -- | Read a value from a memory position given by an address and an offset. -- The memory block the address refers to must be immutable. The offset -- is in elements of type a rather than in bytes. indexOffAddr# :: Prim a => Addr# -> Int# -> a -- | Read a value from a memory position given by an address and an offset. -- The offset is in elements of type a rather than in bytes. readOffAddr# :: Prim a => Addr# -> Int# -> State# s -> (# State# s, a #) -- | Write a value to a memory position given by an address and an offset. -- The offset is in elements of type a rather than in bytes. writeOffAddr# :: Prim a => Addr# -> Int# -> a -> State# s -> State# s -- | Fill a memory block given by an address, an offset and a length. The -- offset and length are in elements of type a rather than in -- bytes. setOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s -- | Create a pinned primitive array of the specified size in -- elements. The garbage collector is guaranteed not to move it. newPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) -- | Create a pinned primitive array of the specified size in -- elements and with the alignment given by its Prim instance. The -- garbage collector is guaranteed not to move it. newAlignedPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) -- | Copy a slice of an immutable primitive array to an address. The offset -- and length are given in elements of type a. This function -- assumes that the Prim instance of a agrees with the -- Storable instance. This function is only available when -- building with GHC 7.8 or newer. -- -- Note: this function does not do bounds or overlap checking. copyPrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> PrimArray a -> Int -> Int -> m () -- | Copy a slice of an immutable primitive array to an address. The offset -- and length are given in elements of type a. This function -- assumes that the Prim instance of a agrees with the -- Storable instance. This function is only available when -- building with GHC 7.8 or newer. -- -- Note: this function does not do bounds or overlap checking. copyMutablePrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> MutablePrimArray (PrimState m) a -> Int -> Int -> m () -- | Copy from a pointer to a mutable primitive array. The offset and -- length are given in elements of type a. This function is only -- available when building with GHC 7.8 or newer. copyPtrToMutablePrimArray :: (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m () -- | Yield a pointer to the array's data. This operation is only safe on -- pinned prim arrays allocated by newPinnedByteArray or -- newAlignedPinnedByteArray. primArrayContents :: PrimArray a -> Ptr a -- | Yield a pointer to the array's data. This operation is only safe on -- pinned byte arrays allocated by newPinnedByteArray or -- newAlignedPinnedByteArray. mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b -- | Check whether or not the byte array is pinned. Pinned primitive arrays -- cannot be moved by the garbage collector. It is safe to use -- primArrayContents on such byte arrays. This function is only -- available when compiling with GHC 8.2 or newer. isPrimArrayPinned :: PrimArray a -> Bool -- | Check whether or not the mutable primitive array is pinned. This -- function is only available when compiling with GHC 8.2 or newer. isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool -- | Array holding PrimUnlifted values. data UnliftedArray a UnliftedArray :: ArrayArray# -> UnliftedArray a -- | Mutable array holding PrimUnlifted values. data MutableUnliftedArray s a MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s a -- | Types with TYPE UnliftedRep, which can be stored / -- retrieved in ArrayArray#. class PrimUnlifted a writeUnliftedArray# :: PrimUnlifted a => MutableArrayArray# s -> Int# -> a -> State# s -> State# s readUnliftedArray# :: PrimUnlifted a => MutableArrayArray# s -> Int# -> State# s -> (# State# s, a #) indexUnliftedArray# :: PrimUnlifted a => ArrayArray# -> Int# -> a -- | Exceptions generated by array operations data ArrayException -- | An attempt was made to index an array outside its declared bounds. IndexOutOfBounds :: String -> ArrayException -- | An attempt was made to evaluate an element of an array that had not -- been initialized. UndefinedElement :: String -> ArrayException -- | Cast between primitive types of the same size. class Cast source destination -- | Cast between arrays castArray :: (Arr arr a, Cast a b) => arr a -> arr b -- | Cast between mutable arrays castMutableArray :: (Arr arr a, Cast a b) => MArr arr s a -> MArr arr s b -- | Size of values of type a. The argument is not used. -- -- This function has existed since 0.1, but was moved from -- Primitive to Types in version 0.6.3.0 sizeOf :: Prim a => a -> Int instance Z.Data.Array.Arr Data.Primitive.Array.Array a instance Z.Data.Array.Arr Data.Primitive.SmallArray.SmallArray a instance Data.Primitive.Types.Prim a => Z.Data.Array.Arr Data.Primitive.PrimArray.PrimArray a instance Z.Data.Array.UnliftedArray.PrimUnlifted a => Z.Data.Array.Arr Z.Data.Array.UnliftedArray.UnliftedArray a -- | This module provides functions for writing PrimArray related -- literals QuasiQuote. -- --
--   > :set -XQuasiQuotes
--   > :t [arrASCII|asdfg|]
--   [arrASCII|asdfg|] :: PrimArray GHC.Word.Word8
--   > [arrASCII|asdfg|]
--   fromListN 5 [97,115,100,102,103]
--   > :t [arrI16|1,2,3,4,5|]
--   [arrI16|1,2,3,4,5|] :: PrimArray GHC.Int.Int16
--   > [arrI16|1,2,3,4,5|]
--   fromListN 5 [1,2,3,4,5]
--   
module Z.Data.Array.QQ -- |
--   [arrASCII|asdfg|] :: PrimArray Word8
--   
arrASCII :: QuasiQuoter -- |
--   [arrW8|1,2,3,4,5|] :: PrimArray Word8
--   
arrW8 :: QuasiQuoter -- |
--   [arrW16|1,2,3,4,5|] :: PrimArray Word16
--   
arrW16 :: QuasiQuoter -- |
--   [arrW32|1,2,3,4,5|] :: PrimArray Word32
--   
arrW32 :: QuasiQuoter -- |
--   [arrW64|1,2,3,4,5|] :: PrimArray Word64
--   
arrW64 :: QuasiQuoter -- |
--   [arrWord|1,2,3,4,5|] :: PrimArray Word
--   
arrWord :: QuasiQuoter -- |
--   [arrW8|1,2,3,4,5|] :: PrimArray Int8
--   
arrI8 :: QuasiQuoter -- |
--   [arrI16|1,2,3,4,5|] :: PrimArray Int16
--   
arrI16 :: QuasiQuoter -- |
--   [arrI32|1,2,3,4,5|] :: PrimArray Int32
--   
arrI32 :: QuasiQuoter -- |
--   [arrI64|1,2,3,4,5|] :: PrimArray Int64
--   
arrI64 :: QuasiQuoter -- |
--   [arrInt|1,2,3,4,5|] :: PrimArray Int
--   
arrInt :: QuasiQuoter asciiLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct data with UTF8 encoded literals. -- -- See asciiLiteral utf8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct data with array literals e.g. 1,2,3. arrayLiteral :: ([Integer] -> Q [Word8]) -> (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Word8 with array literals e.g. -- 1,2,3. See asciiLiteral word8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Word16 with array literals e.g. -- 1,2,3. See asciiLiteral word16Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Word32 with array literals e.g. -- 1,2,3. See asciiLiteral word32Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Word64 with array literals e.g. -- 1,2,3. See asciiLiteral word64Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Word with array literals e.g. -- 1,2,3. See asciiLiteral wordLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Int8 with array literals e.g. -- 1,2,3. See asciiLiteral int8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Int16 with array literals e.g. -- 1,2,3. See asciiLiteral int16Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Int32 with array literals e.g. -- 1,2,3. See asciiLiteral int32Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Int64 with array literals e.g. -- 1,2,3. See asciiLiteral int64Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct PrimArray Int with array literals e.g. -- 1,2,3. See asciiLiteral intLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ word8ArrayFromAddr :: Int -> Addr# -> PrimArray Word8 word16ArrayFromAddr :: Int -> Addr# -> PrimArray Word16 word32ArrayFromAddr :: Int -> Addr# -> PrimArray Word32 word64ArrayFromAddr :: Int -> Addr# -> PrimArray Word64 wordArrayFromAddr :: Int -> Addr# -> PrimArray Word int8ArrayFromAddr :: Int -> Addr# -> PrimArray Int8 int16ArrayFromAddr :: Int -> Addr# -> PrimArray Int16 int32ArrayFromAddr :: Int -> Addr# -> PrimArray Int32 int64ArrayFromAddr :: Int -> Addr# -> PrimArray Int64 intArrayFromAddr :: Int -> Addr# -> PrimArray Int -- | This module provides exactly the same API with Z.Data.Array, -- but will throw an IndexOutOfBounds ArrayException on -- bound check failure, it's useful when debugging array algorithms: just -- swap this module with Z.Data.Array, segmentation faults caused -- by out bound access will be turned into exceptions with more -- informations. module Z.Data.Array.Checked -- | A typeclass to unify box & unboxed, mutable & immutable array -- operations. -- -- Most of these functions simply wrap their primitive counterpart, if -- there's no primitive ones, we polyfilled using other operations to get -- the same semantics. -- -- One exception is that shrinkMutableArr only perform closure -- resizing on PrimArray because current RTS support only that, -- shrinkMutableArr will do nothing on other array type. -- -- It's reasonable to trust GHC with specializing & inlining these -- polymorphric functions. They are used across this package and perform -- identical to their monomophric counterpart. class Arr (arr :: * -> *) a -- | Mutable version of this array type. type family MArr arr = (mar :: * -> * -> *) | mar -> arr singletonArr :: Arr arr a => a -> arr a doubletonArr :: Arr arr a => a -> a -> arr a modifyIndexArr :: (Arr arr a, HasCallStack) => arr a -> Int -> Int -> Int -> (a -> a) -> arr a -- | Insert an immutable array's element at given index to produce a new -- array. insertIndexArr :: Arr arr a => arr a -> Int -> Int -> Int -> a -> arr a -- | Drop an immutable array's element at given index to produce a new -- array. deleteIndexArr :: Arr arr a => arr a -> Int -> Int -> Int -> arr a -- | RealWorld is deeply magical. It is primitive, but it -- is not unlifted (hence ptrArg). We never manipulate -- values of type RealWorld; it's only used in the type system, -- to parameterise State#. data RealWorld -- | Boxed arrays data Array a Array :: Array# a -> Array a [array#] :: Array a -> Array# a -- | Mutable boxed arrays associated with a primitive state token. data MutableArray s a MutableArray :: MutableArray# s a -> MutableArray s a [marray#] :: MutableArray s a -> MutableArray# s a data SmallArray a SmallArray :: SmallArray# a -> SmallArray a data SmallMutableArray s a SmallMutableArray :: SmallMutableArray# s a -> SmallMutableArray s a -- | Bottom value (throw (UndefinedElement -- uninitialized)) for initialize new boxed -- array(Array, SmallArray..). uninitialized :: a -- | Arrays of unboxed elements. This accepts types like Double, -- Char, Int, and Word, as well as their -- fixed-length variants (Word8, Word16, etc.). Since -- the elements are unboxed, a PrimArray is strict in its -- elements. This differs from the behavior of Array, which is -- lazy in its elements. data PrimArray a PrimArray :: ByteArray# -> PrimArray a -- | Mutable primitive arrays associated with a primitive state token. -- These can be written to and read from in a monadic context that -- supports sequencing such as IO or ST. Typically, a -- mutable primitive array will be built and then convert to an immutable -- primitive array using unsafeFreezePrimArray. However, it is -- also acceptable to simply discard a mutable primitive array since it -- lives in managed memory and will be garbage collected when no longer -- referenced. data MutablePrimArray s a MutablePrimArray :: MutableByteArray# s -> MutablePrimArray s a -- | Class of types supporting primitive array operations. This includes -- interfacing with GC-managed memory (functions suffixed with -- ByteArray#) and interfacing with unmanaged memory (functions -- suffixed with Addr#). Endianness is platform-dependent. class Prim a -- | Size of values of type a. The argument is not used. sizeOf# :: Prim a => a -> Int# -- | Alignment of values of type a. The argument is not used. alignment# :: Prim a => a -> Int# -- | Read a value from the array. The offset is in elements of type -- a rather than in bytes. indexByteArray# :: Prim a => ByteArray# -> Int# -> a -- | Read a value from the mutable array. The offset is in elements of type -- a rather than in bytes. readByteArray# :: Prim a => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) -- | Write a value to the mutable array. The offset is in elements of type -- a rather than in bytes. writeByteArray# :: Prim a => MutableByteArray# s -> Int# -> a -> State# s -> State# s -- | Fill a slice of the mutable array with a value. The offset and length -- of the chunk are in elements of type a rather than in bytes. setByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s -- | Read a value from a memory position given by an address and an offset. -- The memory block the address refers to must be immutable. The offset -- is in elements of type a rather than in bytes. indexOffAddr# :: Prim a => Addr# -> Int# -> a -- | Read a value from a memory position given by an address and an offset. -- The offset is in elements of type a rather than in bytes. readOffAddr# :: Prim a => Addr# -> Int# -> State# s -> (# State# s, a #) -- | Write a value to a memory position given by an address and an offset. -- The offset is in elements of type a rather than in bytes. writeOffAddr# :: Prim a => Addr# -> Int# -> a -> State# s -> State# s -- | Fill a memory block given by an address, an offset and a length. The -- offset and length are in elements of type a rather than in -- bytes. setOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s newArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => Int -> m (MArr arr s a) newArrWith :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => Int -> a -> m (MArr arr s a) readArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> m a writeArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> a -> m () setArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> Int -> a -> m () indexArr :: (Arr arr a, HasCallStack) => arr a -> Int -> a indexArr' :: (Arr arr a, HasCallStack) => arr a -> Int -> (# a #) indexArrM :: (Arr arr a, Monad m, HasCallStack) => arr a -> Int -> m a freezeArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> Int -> m (arr a) thawArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => arr a -> Int -> Int -> m (MArr arr s a) copyArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> arr a -> Int -> Int -> m () copyMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> MArr arr s a -> Int -> Int -> m () moveArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> MArr arr s a -> Int -> Int -> m () cloneArr :: (Arr arr a, HasCallStack) => arr a -> Int -> Int -> arr a cloneMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> Int -> m (MArr arr s a) resizeMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> m (MArr arr s a) -- | New size should be >= 0, and <= original size. shrinkMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => MArr arr s a -> Int -> m () -- | In place freeze a mutable array, the original mutable array can not be -- used anymore. unsafeFreezeArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> m (arr a) -- | In place thaw a immutable array, the original immutable array can not -- be used anymore. unsafeThawArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => arr a -> m (MArr arr s a) -- | Is two mutable array are reference equal. sameMutableArr :: Arr arr a => MArr arr s a -> MArr arr s a -> Bool -- | Size of immutable array. sizeofArr :: Arr arr a => arr a -> Int -- | Size of mutable array. sizeofMutableArr :: (Arr arr a, PrimMonad m, PrimState m ~ s) => MArr arr s a -> m Int -- | Is two immutable array are referencing the same one. -- -- Note that sameArr 's result may change depending on compiler's -- optimizations, for example let arr = runST ... in arr -- sameArr arr may return false if compiler decides to inline -- it. -- -- See https://ghc.haskell.org/trac/ghc/ticket/13908 for more -- background. sameArr :: Arr arr a => arr a -> arr a -> Bool -- | Create a pinned byte array of the specified size, The garbage -- collector is guaranteed not to move it. newPinnedPrimArray :: (PrimMonad m, Prim a, HasCallStack) => Int -> m (MutablePrimArray (PrimState m) a) -- | Create a pinned primitive array of the specified size and -- respect given primitive type's alignment. The garbage collector is -- guaranteed not to move it. newAlignedPinnedPrimArray :: (PrimMonad m, Prim a, HasCallStack) => Int -> m (MutablePrimArray (PrimState m) a) copyPrimArrayToPtr :: (PrimMonad m, Prim a, HasCallStack) => Ptr a -> PrimArray a -> Int -> Int -> m () copyMutablePrimArrayToPtr :: (PrimMonad m, Prim a, HasCallStack) => Ptr a -> MutablePrimArray (PrimState m) a -> Int -> Int -> m () copyPtrToMutablePrimArray :: (PrimMonad m, Prim a, HasCallStack) => MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m () -- | Yield a pointer to the array's data. This operation is only safe on -- pinned prim arrays allocated by newPinnedByteArray or -- newAlignedPinnedByteArray. primArrayContents :: PrimArray a -> Ptr a -- | Yield a pointer to the array's data. This operation is only safe on -- pinned byte arrays allocated by newPinnedByteArray or -- newAlignedPinnedByteArray. mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b -- | Check whether or not the byte array is pinned. Pinned primitive arrays -- cannot be moved by the garbage collector. It is safe to use -- primArrayContents on such byte arrays. This function is only -- available when compiling with GHC 8.2 or newer. isPrimArrayPinned :: PrimArray a -> Bool -- | Check whether or not the mutable primitive array is pinned. This -- function is only available when compiling with GHC 8.2 or newer. isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool -- | Array holding PrimUnlifted values. data UnliftedArray a UnliftedArray :: ArrayArray# -> UnliftedArray a -- | Mutable array holding PrimUnlifted values. data MutableUnliftedArray s a MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s a -- | Types with TYPE UnliftedRep, which can be stored / -- retrieved in ArrayArray#. class PrimUnlifted a writeUnliftedArray# :: PrimUnlifted a => MutableArrayArray# s -> Int# -> a -> State# s -> State# s readUnliftedArray# :: PrimUnlifted a => MutableArrayArray# s -> Int# -> State# s -> (# State# s, a #) indexUnliftedArray# :: PrimUnlifted a => ArrayArray# -> Int# -> a -- | Exceptions generated by array operations data ArrayException -- | An attempt was made to index an array outside its declared bounds. IndexOutOfBounds :: String -> ArrayException -- | An attempt was made to evaluate an element of an array that had not -- been initialized. UndefinedElement :: String -> ArrayException -- | Cast between primitive types of the same size. class Cast source destination -- | Cast between arrays castArray :: (Arr arr a, Cast a b) => arr a -> arr b -- | Cast between mutable arrays castMutableArray :: (Arr arr a, Cast a b) => MArr arr s a -> MArr arr s b -- | Size of values of type a. The argument is not used. -- -- This function has existed since 0.1, but was moved from -- Primitive to Types in version 0.6.3.0 sizeOf :: Prim a => a -> Int -- | Internal module, provides lookup table for converting numeric value -- into ASCII bytes. module Z.Data.Builder.Numeric.DigitTable decDigitTable :: Ptr Word8 hexDigitTable :: Ptr Word8 hexDigitTableUpper :: Ptr Word8 -- | This module provides a helper class to compute product size via -- Generic instance, e.g. This class is useful during JSON -- deserializing, to decide the array length used to store record KVs. module Z.Data.Generics.Utils -- | type class for calculating product size. class KnownNat (PSize f) => ProductSize (f :: * -> *) where { type family PSize f :: Nat; } productSize :: forall f. KnownNat (PSize f) => Proxy# f -> Int instance Z.Data.Generics.Utils.ProductSize (GHC.Generics.S1 s a) instance (GHC.TypeNats.KnownNat (Z.Data.Generics.Utils.PSize a GHC.TypeNats.+ Z.Data.Generics.Utils.PSize b), Z.Data.Generics.Utils.ProductSize a, Z.Data.Generics.Utils.ProductSize b) => Z.Data.Generics.Utils.ProductSize (a GHC.Generics.:*: b) -- | This package provide fast unboxed references for ST monad. Unboxed -- reference is implemented using single cell MutableByteArray s to -- eliminate indirection overhead which MutVar# s a carry, on the -- otherhand unboxed reference only support limited type(instances of -- Prim class). module Z.Data.PrimRef.PrimSTRef -- | A mutable variable in the ST monad which can hold an instance of -- Prim. newtype PrimSTRef s a PrimSTRef :: MutableByteArray s -> PrimSTRef s a -- | Build a new PrimSTRef newPrimSTRef :: Prim a => a -> ST s (PrimSTRef s a) -- | Read the value of an PrimSTRef readPrimSTRef :: Prim a => PrimSTRef s a -> ST s a -- | Write a new value into an PrimSTRef writePrimSTRef :: Prim a => PrimSTRef s a -> a -> ST s () -- | Mutate the contents of an PrimSTRef. -- -- Unboxed reference is always strict on the value it hold. modifyPrimSTRef :: Prim a => PrimSTRef s a -> (a -> a) -> ST s () -- | This package provide fast unboxed references for IO monad and atomic -- operations for Counter type. Unboxed reference is implemented -- using single cell MutableByteArray s to eliminate indirection overhead -- which MutVar# s a carry, on the otherhand unboxed reference only -- support limited type(instances of Prim class). -- -- Atomic operations on Counter type are implemented using -- fetch-and-add primitives, which is much faster than a CAS -- loop(atomicModifyIORef). Beside basic atomic counter usage, -- you can also leverage idempotence of and 0, or (-1) -- to make a concurrent flag. module Z.Data.PrimRef.PrimIORef -- | A mutable variable in the IO monad which can hold an instance of -- Prim. data PrimIORef a -- | Build a new PrimIORef newPrimIORef :: Prim a => a -> IO (PrimIORef a) -- | Read the value of an PrimIORef readPrimIORef :: Prim a => PrimIORef a -> IO a -- | Write a new value into an PrimIORef writePrimIORef :: Prim a => PrimIORef a -> a -> IO () -- | Mutate the contents of an IORef. -- -- Unboxed reference is always strict on the value it hold. modifyPrimIORef :: Prim a => PrimIORef a -> (a -> a) -> IO () -- | Alias for 'PrimIORef Int' which support several atomic operations. type Counter = PrimIORef Int -- | Build a new Counter newCounter :: Int -> IO Counter -- | Atomically add a Counter, return the value BEFORE added. atomicAddCounter :: Counter -> Int -> IO Int -- | Atomically sub a Counter, return the value BEFORE subbed. atomicSubCounter :: Counter -> Int -> IO Int -- | Atomically and a Counter, return the value BEFORE anded. atomicAndCounter :: Counter -> Int -> IO Int -- | Atomically nand a Counter, return the value BEFORE nanded. atomicNandCounter :: Counter -> Int -> IO Int -- | Atomically or a Counter, return the value BEFORE ored. atomicOrCounter :: Counter -> Int -> IO Int -- | Atomically xor a Counter, return the value BEFORE xored. atomicXorCounter :: Counter -> Int -> IO Int -- | Atomically add a Counter, return the value AFTER added. atomicAddCounter' :: Counter -> Int -> IO Int -- | Atomically sub a Counter, return the value AFTER subbed. atomicSubCounter' :: Counter -> Int -> IO Int -- | Atomically and a Counter, return the value AFTER anded. atomicAndCounter' :: Counter -> Int -> IO Int -- | Atomically nand a Counter, return the value AFTER nanded. atomicNandCounter' :: Counter -> Int -> IO Int -- | Atomically or a Counter, return the value AFTER ored. atomicOrCounter' :: Counter -> Int -> IO Int -- | Atomically xor a Counter, return the value AFTER xored. atomicXorCounter' :: Counter -> Int -> IO Int -- | Atomically add a Counter. atomicAddCounter_ :: Counter -> Int -> IO () -- | Atomically sub a Counter atomicSubCounter_ :: Counter -> Int -> IO () -- | Atomically and a Counter atomicAndCounter_ :: Counter -> Int -> IO () -- | Atomically nand a Counter atomicNandCounter_ :: Counter -> Int -> IO () -- | Atomically or a Counter atomicOrCounter_ :: Counter -> Int -> IO () -- | Atomically xor a Counter atomicXorCounter_ :: Counter -> Int -> IO () -- | This module provide fast unboxed references for ST and IO monad, and -- atomic operations for Counter type. Unboxed reference is -- implemented using single cell MutableByteArray s to eliminate -- indirection overhead which MutVar# s a carry, on the otherhand unboxed -- reference only support limited type(instances of Prim class). module Z.Data.PrimRef -- | A mutable variable in the ST monad which can hold an instance of -- Prim. data PrimSTRef s a -- | Build a new PrimSTRef newPrimSTRef :: Prim a => a -> ST s (PrimSTRef s a) -- | Read the value of an PrimSTRef readPrimSTRef :: Prim a => PrimSTRef s a -> ST s a -- | Write a new value into an PrimSTRef writePrimSTRef :: Prim a => PrimSTRef s a -> a -> ST s () -- | Mutate the contents of an PrimSTRef. -- -- Unboxed reference is always strict on the value it hold. modifyPrimSTRef :: Prim a => PrimSTRef s a -> (a -> a) -> ST s () -- | A mutable variable in the IO monad which can hold an instance of -- Prim. data PrimIORef a -- | Build a new PrimIORef newPrimIORef :: Prim a => a -> IO (PrimIORef a) -- | Read the value of an PrimIORef readPrimIORef :: Prim a => PrimIORef a -> IO a -- | Write a new value into an PrimIORef writePrimIORef :: Prim a => PrimIORef a -> a -> IO () -- | Mutate the contents of an IORef. -- -- Unboxed reference is always strict on the value it hold. modifyPrimIORef :: Prim a => PrimIORef a -> (a -> a) -> IO () -- | Alias for 'PrimIORef Int' which support several atomic operations. type Counter = PrimIORef Int -- | Build a new Counter newCounter :: Int -> IO Counter -- | Atomically add a Counter, return the value BEFORE added. atomicAddCounter :: Counter -> Int -> IO Int -- | Atomically sub a Counter, return the value BEFORE subbed. atomicSubCounter :: Counter -> Int -> IO Int -- | Atomically and a Counter, return the value BEFORE anded. atomicAndCounter :: Counter -> Int -> IO Int -- | Atomically nand a Counter, return the value BEFORE nanded. atomicNandCounter :: Counter -> Int -> IO Int -- | Atomically or a Counter, return the value BEFORE ored. atomicOrCounter :: Counter -> Int -> IO Int -- | Atomically xor a Counter, return the value BEFORE xored. atomicXorCounter :: Counter -> Int -> IO Int -- | Atomically add a Counter, return the value AFTER added. atomicAddCounter' :: Counter -> Int -> IO Int -- | Atomically sub a Counter, return the value AFTER subbed. atomicSubCounter' :: Counter -> Int -> IO Int -- | Atomically and a Counter, return the value AFTER anded. atomicAndCounter' :: Counter -> Int -> IO Int -- | Atomically nand a Counter, return the value AFTER nanded. atomicNandCounter' :: Counter -> Int -> IO Int -- | Atomically or a Counter, return the value AFTER ored. atomicOrCounter' :: Counter -> Int -> IO Int -- | Atomically xor a Counter, return the value AFTER xored. atomicXorCounter' :: Counter -> Int -> IO Int -- | Atomically add a Counter. atomicAddCounter_ :: Counter -> Int -> IO () -- | Atomically sub a Counter atomicSubCounter_ :: Counter -> Int -> IO () -- | Atomically and a Counter atomicAndCounter_ :: Counter -> Int -> IO () -- | Atomically nand a Counter atomicNandCounter_ :: Counter -> Int -> IO () -- | Atomically or a Counter atomicOrCounter_ :: Counter -> Int -> IO () -- | Atomically xor a Counter atomicXorCounter_ :: Counter -> Int -> IO () -- | UTF-8 codecs and helpers. module Z.Data.Text.UTF8Codec -- | Return a codepoint's encoded length in bytes -- -- If the codepoint is invalid, we return 3(encoded bytes length of -- replacement char U+FFFD). encodeCharLength :: Char -> Int -- | Encode a Char into bytes, write replacementChar for -- invalid unicode codepoint. -- -- This function assumed there're enough space for encoded bytes, and -- return the advanced index. encodeChar :: PrimMonad m => MutablePrimArray (PrimState m) Word8 -> Int -> Char -> m Int -- | The unboxed version of encodeChar. -- -- This function is marked as NOINLINE to reduce code size, and -- stop messing up simplifier due to too much branches. encodeChar# :: MutableByteArray# s -> Int# -> Char# -> State# s -> (# State# s, Int# #) -- | Encode a Char into bytes with non-standard UTF-8 encoding(Used -- in Data.CBytes). -- -- \NUL is encoded as two bytes C0 80 , \xD800 -- ~ \xDFFF is encoded as a three bytes normal UTF-8 codepoint. -- This function assumed there're enough space for encoded bytes, and -- return the advanced index. encodeCharModifiedUTF8 :: PrimMonad m => MutablePrimArray (PrimState m) Word8 -> Int -> Char -> m Int -- | The unboxed version of encodeCharModifiedUTF8. encodeCharModifiedUTF8# :: MutableByteArray# s -> Int# -> Char# -> State# s -> (# State# s, Int# #) -- | Decode a Char from bytes -- -- This function assumed all bytes are UTF-8 encoded, and the index param -- point to the beginning of a codepoint, the decoded character and the -- advancing offset are returned. -- -- It's annoying to use unboxed tuple here but we really don't want -- allocation even if GHC can't optimize it away. decodeChar :: PrimArray Word8 -> Int -> (# Char, Int #) decodeChar_ :: PrimArray Word8 -> Int -> Char -- | The unboxed version of decodeChar -- -- This function is marked as NOINLINE to reduce code size, and -- stop messing up simplifier due to too much branches. decodeChar# :: ByteArray# -> Int# -> (# Char#, Int# #) -- | Decode a codepoint's length in bytes -- -- This function assumed all bytes are UTF-8 encoded, and the index param -- point to the beginning of a codepoint. decodeCharLen :: PrimArray Word8 -> Int -> Int -- | The unboxed version of decodeCharLen -- -- This function is marked as NOINLINE to reduce code size, and -- stop messing up simplifier due to too much branches. decodeCharLen# :: ByteArray# -> Int# -> Int# -- | Decode a Char from bytes in rerverse order. -- -- This function assumed all bytes are UTF-8 encoded, and the index param -- point to the end of a codepoint, the decoded character and the -- backward advancing offset are returned. decodeCharReverse :: PrimArray Word8 -> Int -> (# Char, Int #) decodeCharReverse_ :: PrimArray Word8 -> Int -> Char -- | The unboxed version of decodeCharReverse -- -- This function is marked as NOINLINE to reduce code size, and -- stop messing up simplifier due to too much branches. decodeCharReverse# :: ByteArray# -> Int# -> (# Char#, Int# #) -- | Decode a codepoint's length in bytes in reverse order. -- -- This function assumed all bytes are UTF-8 encoded, and the index param -- point to the end of a codepoint. decodeCharLenReverse :: PrimArray Word8 -> Int -> Int -- | The unboxed version of decodeCharLenReverse -- -- This function is marked as NOINLINE to reduce code size, and -- stop messing up simplifier due to too much branches. decodeCharLenReverse# :: ByteArray# -> Int# -> Int# between# :: Word# -> Word# -> Word# -> Bool isContinueByte# :: Word# -> Bool chr1# :: Word# -> Char# chr2# :: Word# -> Word# -> Char# chr3# :: Word# -> Word# -> Word# -> Char# chr4# :: Word# -> Word# -> Word# -> Word# -> Char# -- | Unrolled copy loop for copying a utf8-encoded codepoint from source -- array to target array. copyChar :: Int -> MutablePrimArray s Word8 -> Int -> PrimArray Word8 -> Int -> ST s () -- | Unrolled copy loop for copying a utf8-encoded codepoint from source -- array to target array. copyChar' :: Int -> MutablePrimArray s Word8 -> Int -> MutablePrimArray s Word8 -> Int -> ST s () -- | xFFFD, which will be encoded as 0xEF 0xBF 0xBD 3 -- bytes. replacementChar :: Char -- | INTERNAL MODULE, provides utf8rewind constants module Z.Data.Text.UTF8Rewind -- | Locale for case mapping. type Locale = CSize pattern LocaleDefault :: Locale pattern LocaleLithuanian :: Locale pattern LocaleTurkishAndAzeriLatin :: Locale -- | Get environment locale envLocale :: IO Locale -- | These are the Unicode Normalization Forms: -- --
--   Form                         | Description
--   ---------------------------- | ---------------------------------------------
--   Normalization Form D (NFD)   | Canonical decomposition
--   Normalization Form C (NFC)   | Canonical decomposition, followed by canonical composition
--   Normalization Form KD (NFKD) | Compatibility decomposition
--   Normalization Form KC (NFKC) | Compatibility decomposition, followed by canonical composition
--   
data NormalizeMode NFC :: NormalizeMode NFKC :: NormalizeMode NFD :: NormalizeMode NFKD :: NormalizeMode normalizeModeToFlag :: NormalizeMode -> CSize data NormalizationResult NormalizedYes :: NormalizationResult NormalizedMaybe :: NormalizationResult NormalizedNo :: NormalizationResult toNormalizationResult :: Int -> NormalizationResult -- | Unicode categories. -- -- See isCategory, you can combine categories with bitwise or. type Category = CSize pattern CategoryLetterUppercase :: Category pattern CategoryLetterLowercase :: Category pattern CategoryLetterTitlecase :: Category pattern CategoryLetterOther :: Category pattern CategoryLetter :: Category pattern CategoryCaseMapped :: Category pattern CategoryMarkNonSpacing :: Category pattern CategoryMarkSpacing :: Category pattern CategoryMarkEnclosing :: Category pattern CategoryMark :: Category pattern CategoryNumberDecimal :: Category pattern CategoryNumberLetter :: Category pattern CategoryNumberOther :: Category pattern CategoryNumber :: Category pattern CategoryPunctuationConnector :: Category pattern CategoryPunctuationDash :: Category pattern CategoryPunctuationOpen :: Category pattern CategoryPunctuationClose :: Category pattern CategoryPunctuationInitial :: Category pattern CategoryPunctuationFinal :: Category pattern CategoryPunctuationOther :: Category pattern CategoryPunctuation :: Category pattern CategorySymbolMath :: Category pattern CategorySymbolCurrency :: Category pattern CategorySymbolModifier :: Category pattern CategorySymbolOther :: Category pattern CategorySymbol :: Category pattern CategorySeparatorSpace :: Category pattern CategorySeparatorLine :: Category pattern CategorySeparatorParagraph :: Category pattern CategorySeparator :: Category pattern CategoryControl :: Category pattern CategoryFormat :: Category pattern CategorySurrogate :: Category pattern CategoryPrivateUse :: Category pattern CategoryUnassigned :: Category pattern CategoryCompatibility :: Category pattern CategoryIgnoreGraphemeCluster :: Category pattern CategoryIscntrl :: Category pattern CategoryIsprint :: Category pattern CategoryIsspace :: Category pattern CategoryIsblank :: Category pattern CategoryIsgraph :: Category pattern CategoryIspunct :: Category pattern CategoryIsalnum :: Category pattern CategoryIsalpha :: Category pattern CategoryIsupper :: Category pattern CategoryIslower :: Category pattern CategoryIsdigit :: Category pattern CategoryIsxdigit :: Category instance GHC.Generics.Generic Z.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Classes.Ord Z.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Classes.Eq Z.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Show.Show Z.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Generics.Generic Z.Data.Text.UTF8Rewind.NormalizationResult instance GHC.Classes.Ord Z.Data.Text.UTF8Rewind.NormalizationResult instance GHC.Classes.Eq Z.Data.Text.UTF8Rewind.NormalizationResult instance GHC.Show.Show Z.Data.Text.UTF8Rewind.NormalizationResult -- | This module provides unified vector interface. Conceptually a vector -- is simply a slice of an array, for example this is the definition of -- boxed vector: -- --
--   data Vector a = Vector !(SmallArray a)   !Int    !Int
--                        -- payload           offset  length
--   
-- -- The Vec class unified different type of vectors, and this -- module provide operation over Vec instances, with all the -- internal structures. Be careful on modifying internal slices, -- otherwise segmentation fault await. module Z.Data.Vector.Base -- | Typeclass for box and unboxed vectors, which are created by slicing -- arrays. -- -- Instead of providing a generalized vector with polymorphric array -- field, we use this typeclass so that instances use concrete array type -- can unpack their array payload. -- -- Vector types, e.g. Vector,PrimVector... are obivious -- instances, with O(1) toArr and fromArr, which convert -- slices to (array, offset, length) tuple back and forth. -- -- Array types can also be instances of this class, e.g. Array, -- PrimArray..., in this case toArr will always return -- offset 0 and whole array length, and fromArr is O(n) -- copyArr. class (Arr (IArray v) a) => Vec v a where { -- | Vector's immutable array type type family IArray v :: * -> *; } -- | Get underline array and slice range(offset and length). toArr :: Vec v a => v a -> (IArray v a, Int, Int) -- | Create a vector by slicing an array(with offset and length). fromArr :: Vec v a => IArray v a -> Int -> Int -> v a -- | A pattern synonyms for matching the underline array, offset and -- length. -- -- This is a bidirectional pattern synonyms, but very unsafe if not use -- properly. Make sure your slice is within array's bounds! pattern Vec :: Vec v a => IArray v a -> Int -> Int -> v a -- | Construct a Vec by slicing a whole array. arrVec :: Vec v a => IArray v a -> v a -- | O(1) Index vector's element. -- -- Return Nothing if index is out of bounds. indexMaybe :: Vec v a => v a -> Int -> Maybe a -- | Boxed vector data Vector a Vector :: {-# UNPACK #-} !SmallArray a -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> Vector a -- | Primitive vector data PrimVector a PrimVector :: {-# UNPACK #-} !PrimArray a -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> PrimVector a -- | Bytes is just primitive word8 vectors. type Bytes = PrimVector Word8 -- | O(n), pack an ASCII String, multi-bytes char WILL BE -- CHOPPED! packASCII :: String -> Bytes -- | Create a vector with size N. create :: Vec v a => Int -> (forall s. MArr (IArray v) s a -> ST s ()) -> v a -- | Create a vector with a initial size N array (which may not be the -- final array). create' :: Vec v a => Int -> (forall s. MArr (IArray v) s a -> ST s (IPair (MArr (IArray v) s a))) -> v a -- | Create a vector with a initial size N array, return both the vector -- and the monadic result during creating. -- -- The result is not demanded strictly while the returned vector will be -- in normal form. It this is not desired, use return $! idiom -- in your initialization function. creating :: Vec v a => Int -> (forall s. MArr (IArray v) s a -> ST s b) -> (b, v a) -- | Create a vector with a initial size N array (which may not be the -- final array), return both the vector and the monadic result during -- creating. -- -- The result is not demanded strictly while the returned vector will be -- in normal form. It this is not desired, use return $! idiom -- in your initialization function. creating' :: Vec v a => Int -> (forall s. MArr (IArray v) s a -> ST s (b, IPair (MArr (IArray v) s a))) -> (b, v a) -- | Create a vector up to a specific length. -- -- If the initialization function return a length larger than initial -- size, an IndexOutOfVectorRange will be raised. createN :: (Vec v a, HasCallStack) => Int -> (forall s. MArr (IArray v) s a -> ST s Int) -> v a -- | Create two vector up to a specific length. -- -- If the initialization function return lengths larger than initial -- sizes, an IndexOutOfVectorRange will be raised. createN2 :: (Vec v a, Vec u b, HasCallStack) => Int -> Int -> (forall s. MArr (IArray v) s a -> MArr (IArray u) s b -> ST s (Int, Int)) -> (v a, u b) -- | O(1). The empty vector. empty :: Vec v a => v a -- | O(1). Single element vector. singleton :: Vec v a => a -> v a -- | O(n). Copy a vector from slice. copy :: Vec v a => v a -> v a -- | O(n) Convert a list into a vector -- -- Alias for packN defaultInitSize. pack :: Vec v a => [a] -> v a -- | O(n) Convert a list into a vector with an approximate size. -- -- If the list's length is large than the size given, we simply double -- the buffer size and continue building. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packN :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) Convert a list into a vector with given size. -- -- If the list's length is large than the size given, we drop the rest -- elements. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packN' :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) Alias for packRN defaultInitSize. packR :: Vec v a => [a] -> v a -- | O(n) packN in reverse order. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packRN :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) packN' in reverse order. -- --
--   >>> packRN' 3 [1,2,3,4,5]
--   
--   >>> [3,2,1]
--   
-- -- This function is a good consumer in the sense of build/foldr -- fusion. packRN' :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) Convert vector to a list. -- -- Unpacking is done lazily. i.e. we will retain reference to the array -- until all element are consumed. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpack :: Vec v a => v a -> [a] -- | O(n) Convert vector to a list in reverse order. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpackR :: Vec v a => v a -> [a] -- | O(1) Test whether a vector is empty. null :: Vec v a => v a -> Bool -- | O(1) The length of a vector. length :: Vec v a => v a -> Int -- | O(m+n) -- -- There's no need to guard empty vector because we guard them for you, -- so appending empty vectors are no-ops. append :: Vec v a => v a -> v a -> v a -- | Mapping between vectors (possiblely with two different vector types). -- -- NOTE, the result vector contain thunks in lifted Vector case, -- use map' if that's not desired. -- -- For PrimVector, map and map' are same, since -- PrimVectors never store thunks. map :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b -- | Mapping between vectors (possiblely with two different vector types). -- -- This is the strict version map. Note that the Functor instance -- of lifted Vector is defined with map to statisfy laws, -- which this strict version breaks (map' id arrayContainsBottom /= -- arrayContainsBottom ). map' :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b -- | Strict mapping with index. imap' :: forall u v a b. (Vec u a, Vec v b) => (Int -> a -> b) -> u a -> v b -- | Traverse vector and gather result in another vector, traverseVec :: (Vec v a, Vec u b, Applicative f) => (a -> f b) -> v a -> f (u b) -- | Traverse vector and gather result in another vector, traverseWithIndex :: (Vec v a, Vec u b, Applicative f) => (Int -> a -> f b) -> v a -> f (u b) -- | Traverse vector without gathering result. traverseVec_ :: (Vec v a, Applicative f) => (a -> f b) -> v a -> f () -- | Traverse vector with index. traverseWithIndex_ :: (Vec v a, Applicative f) => (Int -> a -> f b) -> v a -> f () -- | Strict left to right fold. foldl' :: Vec v a => (b -> a -> b) -> b -> v a -> b -- | Strict left to right fold with index. ifoldl' :: Vec v a => (b -> Int -> a -> b) -> b -> v a -> b -- | Strict left to right fold using first element as the initial value. -- -- Throw EmptyVector if vector is empty. foldl1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a -- | Strict left to right fold using first element as the initial value. -- return Nothing when vector is empty. foldl1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a -- | Strict right to left fold foldr' :: Vec v a => (a -> b -> b) -> b -> v a -> b -- | Strict right to left fold with index -- -- NOTE: the index is counting from 0, not backwards ifoldr' :: Vec v a => (Int -> a -> b -> b) -> b -> v a -> b -- | Strict right to left fold using last element as the initial value. -- -- Throw EmptyVector if vector is empty. foldr1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a -- | Strict right to left fold using last element as the initial value, -- return Nothing when vector is empty. foldr1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a -- | O(n) Concatenate a list of vector. -- -- Note: concat have to force the entire list to filter out empty -- vector and calculate the length for allocation. concat :: forall v a. Vec v a => [v a] -> v a -- | Map a function over a vector and concatenate the results concatMap :: Vec v a => (a -> v a) -> v a -> v a -- | O(n) maximum returns the maximum value from a vector -- -- It's defined with foldl1', an EmptyVector exception will -- be thrown in the case of an empty vector. maximum :: (Vec v a, Ord a, HasCallStack) => v a -> a -- | O(n) minimum returns the minimum value from a -- vector -- -- An EmptyVector exception will be thrown in the case of an empty -- vector. minimum :: (Vec v a, Ord a, HasCallStack) => v a -> a -- | O(n) maximum returns the maximum value from a vector, -- return Nothing in the case of an empty vector. maximumMaybe :: (Vec v a, Ord a) => v a -> Maybe a -- | O(n) minimum returns the minimum value from a vector, -- return Nothing in the case of an empty vector. minimumMaybe :: (Vec v a, Ord a) => v a -> Maybe a -- | O(n) sum returns the sum value from a vector sum :: (Vec v a, Num a) => v a -> a -- | O(n) count returns count of an element from a -- vector count :: (Vec v a, Eq a) => a -> v a -> Int -- | O(n) product returns the product value from a vector product :: (Vec v a, Num a) => v a -> a -- | O(n) product returns the product value from a vector -- -- This function will shortcut on zero. Note this behavior change the -- semantics for lifted vector: product [1,0,undefined] /= product' -- [1,0,undefined]. product' :: (Vec v a, Num a, Eq a) => v a -> a -- | O(n) Applied to a predicate and a vector, all determines -- if all elements of the vector satisfy the predicate. all :: Vec v a => (a -> Bool) -> v a -> Bool -- | O(n) Applied to a predicate and a vector, any determines -- if any elements of the vector satisfy the predicate. any :: Vec v a => (a -> Bool) -> v a -> Bool -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a vector, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new list. -- -- Note, this function will only force the result tuple, not the elements -- inside, to prevent creating thunks during mapAccumL, seq -- your accumulator and result with the result tuple. mapAccumL :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a vector, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new vector. -- -- The same strictness property with mapAccumL applys to -- mapAccumR too. mapAccumR :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c) -- | O(n) replicate n x is a vector of length -- n with x the value of every element. -- -- Note: replicate will not force the element in boxed vector -- case. replicate :: Vec v a => Int -> a -> v a -- | O(n*m) cycleN a vector n times. cycleN :: forall v a. Vec v a => Int -> v a -> v a -- | O(n), where n is the length of the result. The -- unfoldr function is analogous to the List 'unfoldr'. -- unfoldr builds a vector from a seed value. The function takes -- the element and returns Nothing if it is done producing the -- vector or returns Just (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]
--   
unfoldr :: Vec u b => (a -> Maybe (b, a)) -> a -> u b -- | O(n) Like unfoldr, unfoldrN builds a vector from -- a seed value. However, the length of the result is limited by the -- first argument to unfoldrN. This function is more efficient -- than unfoldr when the maximum length of the result is known. -- -- The following equation relates unfoldrN and unfoldr: -- --
--   fst (unfoldrN n f s) == take n (unfoldr f s)
--   
unfoldrN :: forall v a b. Vec v b => Int -> (a -> Maybe (b, a)) -> a -> (v b, Maybe a) -- | O(n) elem test if given element is in given vector. elem :: (Vec v a, Eq a) => a -> v a -> Bool -- | O(n) 'not . elem' notElem :: (Vec v a, Eq a) => a -> v a -> Bool -- | O(n) The elemIndex function returns the index of the -- first element in the given vector which is equal to the query element, -- or Nothing if there is no such element. elemIndex :: (Vec v a, Eq a) => a -> v a -> Maybe Int -- | Pair type to help GHC unpack in some loops, useful when write fast -- folds. data IPair a IPair :: {-# UNPACK #-} !Int -> a -> IPair a [ifst] :: IPair a -> {-# UNPACK #-} !Int [isnd] :: IPair a -> a -- | Unlike Functor instance, this mapping evaluate value inside -- IPair strictly. mapIPair' :: (a -> b) -> IPair a -> IPair b fromIPair :: IPair a -> (Int, a) toIPair :: (Int, a) -> IPair a -- | defaultInitSize = 30, used as initialize size when packing -- list of unknown size. defaultInitSize :: Int -- | The memory management overhead. Currently this is tuned for GHC only. chunkOverhead :: Int -- | The chunk size used for I/O. Currently set to 16k - -- chunkOverhead defaultChunkSize :: Int -- | The recommended chunk size. Currently set to 4k - -- chunkOverhead. smallChunkSize :: Int -- | All exception can be throw by using Vec. data VectorException IndexOutOfVectorRange :: {-# UNPACK #-} !Int -> CallStack -> VectorException EmptyVector :: CallStack -> VectorException errorEmptyVector :: HasCallStack => a errorOutRange :: HasCallStack => Int -> a -- | Cast between vectors castVector :: (Vec v a, Cast a b) => v a -> v b c_strcmp :: Addr# -> Addr# -> IO CInt c_memchr :: ByteArray# -> Int -> Word8 -> Int -> Int c_memrchr :: ByteArray# -> Int -> Word8 -> Int -> Int c_strlen :: Addr# -> IO CSize c_ascii_validate_addr :: Addr# -> Int -> IO Int c_fnv_hash_addr :: Addr# -> Int -> Int -> IO Int c_fnv_hash_ba :: ByteArray# -> Int -> Int -> Int -> IO Int instance GHC.Classes.Ord a => GHC.Classes.Ord (Z.Data.Vector.Base.IPair a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Z.Data.Vector.Base.IPair a) instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Vector.Base.IPair a) instance GHC.Show.Show Z.Data.Vector.Base.VectorException instance GHC.Exception.Type.Exception Z.Data.Vector.Base.VectorException instance Test.QuickCheck.Arbitrary.Arbitrary v => Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Vector.Base.IPair v) instance Test.QuickCheck.Arbitrary.CoArbitrary v => Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Vector.Base.IPair v) instance GHC.Base.Functor Z.Data.Vector.Base.IPair instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Z.Data.Vector.Base.IPair a) instance Data.CaseInsensitive.Internal.FoldCase Z.Data.Vector.Base.Bytes instance Data.Primitive.Types.Prim a => Z.Data.Vector.Base.Vec Z.Data.Vector.Base.PrimVector a instance (Data.Primitive.Types.Prim a, GHC.Classes.Eq a) => GHC.Classes.Eq (Z.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, GHC.Classes.Ord a) => GHC.Classes.Ord (Z.Data.Vector.Base.PrimVector a) instance Data.Primitive.Types.Prim a => GHC.Base.Semigroup (Z.Data.Vector.Base.PrimVector a) instance Data.Primitive.Types.Prim a => GHC.Base.Monoid (Z.Data.Vector.Base.PrimVector a) instance Control.DeepSeq.NFData (Z.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, GHC.Show.Show a) => GHC.Show.Show (Z.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, GHC.Read.Read a) => GHC.Read.Read (Z.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, Test.QuickCheck.Arbitrary.Arbitrary a) => Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, Test.QuickCheck.Arbitrary.CoArbitrary a) => Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Vector.Base.PrimVector a) instance (Data.Hashable.Class.Hashable a, Data.Primitive.Types.Prim a) => Data.Hashable.Class.Hashable (Z.Data.Vector.Base.PrimVector a) instance (a GHC.Types.~ GHC.Word.Word8) => Data.String.IsString (Z.Data.Vector.Base.PrimVector a) instance Data.Primitive.Types.Prim a => GHC.Exts.IsList (Z.Data.Vector.Base.PrimVector a) instance Z.Data.Vector.Base.Vec Z.Data.Vector.Base.Vector a instance GHC.Exts.IsList (Z.Data.Vector.Base.Vector a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Z.Data.Vector.Base.Vector a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Z.Data.Vector.Base.Vector a) instance GHC.Base.Semigroup (Z.Data.Vector.Base.Vector a) instance GHC.Base.Monoid (Z.Data.Vector.Base.Vector a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Z.Data.Vector.Base.Vector a) instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Vector.Base.Vector a) instance GHC.Read.Read a => GHC.Read.Read (Z.Data.Vector.Base.Vector a) instance GHC.Base.Functor Z.Data.Vector.Base.Vector instance Data.Foldable.Foldable Z.Data.Vector.Base.Vector instance Data.Traversable.Traversable Z.Data.Vector.Base.Vector instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Vector.Base.Vector a) instance Test.QuickCheck.Arbitrary.CoArbitrary a => Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Vector.Base.Vector a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Z.Data.Vector.Base.Vector a) instance Data.Hashable.Class.Hashable1 Z.Data.Vector.Base.Vector instance Z.Data.Vector.Base.Vec Data.Primitive.Array.Array a instance Z.Data.Vector.Base.Vec Data.Primitive.SmallArray.SmallArray a instance Data.Primitive.Types.Prim a => Z.Data.Vector.Base.Vec Data.Primitive.PrimArray.PrimArray a instance Z.Data.Array.UnliftedArray.PrimUnlifted a => Z.Data.Vector.Base.Vec Z.Data.Array.UnliftedArray.UnliftedArray a -- | This module provides functions for writing vector literals using -- QuasiQuote similar to Z.Data.Array.QQ module. -- --
--   > :set -XQuasiQuotes
--   > :t [vecASCII|asdfg|]
--   [vecASCII|asdfg|] :: Z.Data.Vector.Base.PrimVector GHC.Word.Word8
--   > [vecASCII|asdfg|]
--   [97,115,100,102,103]
--   > :t [vecI16|1,2,3,4,5|]
--   [vecI16|1,2,3,4,5|] :: Z.Data.Vector.Base.PrimVector GHC.Int.Int16
--   > [vecI16|1,2,3,4,5|]
--   [1,2,3,4,5]
--   
module Z.Data.Vector.QQ vecASCII :: QuasiQuoter vecW8 :: QuasiQuoter vecW16 :: QuasiQuoter vecW32 :: QuasiQuoter vecW64 :: QuasiQuoter vecWord :: QuasiQuoter vecI8 :: QuasiQuoter vecI16 :: QuasiQuoter vecI32 :: QuasiQuoter vecI64 :: QuasiQuoter vecInt :: QuasiQuoter -- | This module provides: -- -- module Z.Data.Vector.Search -- | The findIndex function takes a predicate and a vector and -- returns the index of the first element in the vector satisfying the -- predicate. findIndices :: Vec v a => (a -> Bool) -> v a -> [Int] -- | O(n) The elemIndices function extends elemIndex, -- by returning the indices of all elements equal to the query element, -- in ascending order. elemIndices :: (Vec v a, Eq a) => a -> v a -> [Int] -- | O(n) find the first index and element matching the predicate in -- a vector from left to right, if there isn't one, return (length of the -- vector, Nothing). find :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a) -- | O(n) Find the first index and element matching the predicate in -- a vector from right to left, if there isn't one, return '(-1, -- Nothing)'. findR :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a) -- |
--   findIndex f v = fst (find f v)
--   
findIndex :: Vec v a => (a -> Bool) -> v a -> Int -- |
--   findIndexR f v = fst (findR f v)
--   
findIndexR :: Vec v a => (a -> Bool) -> v a -> Int -- | O(n) filter, applied to a predicate and a vector, -- returns a vector containing those elements that satisfy the predicate. filter :: forall v a. Vec v a => (a -> Bool) -> v a -> v a -- | O(n) The partition function takes a predicate, a vector, -- returns a pair of vector with elements which do and do not satisfy the -- predicate, respectively; i.e., -- --
--   partition p vs == (filter p vs, filter (not . p) vs)
--   
partition :: forall v a. Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | O(n+m) Find the offsets of all indices (possibly overlapping) -- of needle within haystack using KMP algorithm. -- -- The KMP algorithm need pre-calculate a shift table in O(m) time -- and space, the worst case time complexity is O(n+m). Partial -- apply this function to reuse pre-calculated table between same -- needles. -- -- Chunked input are support via partial match argument, if set we will -- return an extra negative index in case of partial match at the end of -- input chunk, e.g. -- --
--   indicesOverlapping [ascii|ada|]  [ascii|adadad|] True == [0,2,-2]
--   
-- -- Where -2 is the length of the partial match part ad -- 's negation. -- -- If an empty pattern is supplied, we will return every possible index -- of haystack, e.g. -- --
--   indicesOverlapping "" "abc" = [0,1,2]
--   
-- -- References: -- -- indicesOverlapping :: (Vec v a, Eq a) => v a -> v a -> Bool -> [Int] -- | O(n+m) Find the offsets of all non-overlapping indices of -- needle within haystack using KMP algorithm. -- -- If an empty pattern is supplied, we will return every possible index -- of haystack, e.g. -- --
--   indicesOverlapping "" "abc" = [0,1,2]
--   
indices :: (Vec v a, Eq a) => v a -> v a -> Bool -> [Int] -- | O(n) Special elemIndices for Bytes using -- memchr(3) elemIndicesBytes :: Word8 -> Bytes -> [Int] -- | O(n) Special findByte for Word8 using -- memchr(3) findByte :: Word8 -> Bytes -> (Int, Maybe Word8) -- | O(n) Special findR for Bytes with -- memrchr. findByteR :: Word8 -> Bytes -> (Int, Maybe Word8) -- | O(n/m) Find the offsets of all indices (possibly overlapping) -- of needle within haystack using KMP algorithm, -- combined with simplified sunday's rule to obtain O(n/m) -- complexity in average use case. -- -- The hybrid algorithm need pre-calculate a shift table in O(m) -- time and space, and a bad character bloom filter in O(m) time -- and O(1) space, the worst case time complexity is -- O(n+m). -- -- References: -- -- indicesOverlappingBytes :: Bytes -> Bytes -> Bool -> [Int] -- | O(n/m) Find the offsets of all non-overlapping indices of -- needle within haystack using KMP algorithm, combined -- with simplified sunday's rule to obtain O(m/n) complexity in -- average use case. indicesBytes :: Bytes -> Bytes -> Bool -> [Int] -- | O(m) Calculate the KMP next shift table. -- -- The shifting rules is: when a mismatch between needle[j] and -- haystack[i] is found, check if next[j] == -1, if so -- next search continue with needle[0] and -- haystack[i+1], otherwise continue with -- needle[next[j]] and haystack[i]. kmpNextTable :: (Vec v a, Eq a) => v a -> PrimArray Int -- | O(m) Calculate a simple bloom filter for simplified sunday's -- rule. -- -- The shifting rules is: when a mismatch between needle[j] and -- haystack[i] is found, check if elemSundayBloom bloom -- haystack[i+n-j], where n is the length of needle, if not then -- next search can be safely continued with haystack[i+n-j+1] -- and needle[0], otherwise next searh should continue with -- haystack[i] and needle[0], or fallback to other -- shifting rules such as KMP. -- -- The algorithm is very simple: for a given Word8 w, we -- set the bloom's bit at unsafeShiftL 0x01 (w .&. 0x3f), so -- there're three false positives per bit. This's particularly suitable -- for search UTF-8 bytes since the significant bits of a beginning byte -- is usually the same. sundayBloom :: Bytes -> Word64 -- | O(1) Test if a bloom filter contain a certain Word8. elemSundayBloom :: Word64 -> Word8 -> Bool -- | Various combinators works on Vec class instances. module Z.Data.Vector.Extra -- | O(n) cons is analogous to (:) for lists, but of -- different complexity, as it requires making a copy. cons :: Vec v a => a -> v a -> v a -- | O(n) Append a byte to the end of a vector snoc :: Vec v a => v a -> a -> v a -- | O(1) Extract the head and tail of a vector, return -- Nothing if it is empty. uncons :: Vec v a => v a -> Maybe (a, v a) -- | O(1) Extract the init and last of a vector, return -- Nothing if vector is empty. unsnoc :: Vec v a => v a -> Maybe (v a, a) -- | O(1) Extract the first element of a vector. headMaybe :: Vec v a => v a -> Maybe a -- | O(1) Extract the elements after the head of a vector. -- -- NOTE: tailMayEmpty return empty vector in the case of an empty -- vector. tailMayEmpty :: Vec v a => v a -> v a -- | O(1) Extract the last element of a vector. lastMaybe :: Vec v a => v a -> Maybe a -- | O(1) Extract the elements before of the last one. -- -- NOTE: initMayEmpty return empty vector in the case of an empty -- vector. initMayEmpty :: Vec v a => v a -> v a -- | O(n) Return all initial segments of the given vector, empty -- first. inits :: Vec v a => v a -> [v a] -- | O(n) Return all final segments of the given vector, whole -- vector first. tails :: Vec v a => v a -> [v a] -- | O(1) take n, applied to a vector xs, -- returns the prefix of xs of length n, or xs -- itself if n > length xs. take :: Vec v a => Int -> v a -> v a -- | O(1) drop n xs returns the suffix of -- xs after the first n elements, or [] if -- n > length xs. drop :: Vec v a => Int -> v a -> v a -- | O(1) takeR n, applied to a vector xs, -- returns the suffix of xs of length n, or xs -- itself if n > length xs. takeR :: Vec v a => Int -> v a -> v a -- | O(1) dropR n xs returns the prefix of -- xs before the last n elements, or [] if -- n > length xs. dropR :: Vec v a => Int -> v a -> v a -- | O(1) Extract a sub-range vector with give start index and -- length. -- -- This function is a total function just like 'takedrop', -- indexlength exceeds range will be ingored, e.g. -- --
--   slice 1 3 "hello"   == "ell"
--   slice -1 -1 "hello" == ""
--   slice -2 2 "hello"  == ""
--   slice 2 10 "hello"  == "llo"
--   
-- -- This holds for all x y: slice x y vs == drop x . take (x+y) -- vs slice :: Vec v a => Int -> Int -> v a -> v a -- | O(1) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Vec v a => Int -> v a -> (v a, v a) -- | O(n) Applied to a predicate p and a vector -- vs, returns the longest prefix (possibly empty) of -- vs of elements that satisfy p. takeWhile :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Applied to a predicate p and a vector -- vs, returns the longest suffix (possibly empty) of -- vs of elements that satisfy p. takeWhileR :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Applied to a predicate p and a vector -- vs, returns the suffix (possibly empty) remaining after -- takeWhile p vs. dropWhile :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Applied to a predicate p and a vector -- vs, returns the prefix (possibly empty) remaining before -- takeWhileR p vs. dropWhileR :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) dropAround f = dropWhile f . dropWhileR f dropAround :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Split the vector into the longest prefix of elements that -- do not satisfy the predicate and the rest without copying. -- -- break (==x) will be rewritten using a memchr. break :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | O(n) Split the vector into the longest prefix of elements that -- satisfy the predicate and the rest without copying. -- -- span (/=x) will be rewritten using a memchr. span :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | breakR behaves like break but from the end of the -- vector. -- --
--   breakR p == spanR (not.p)
--   
breakR :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | spanR behaves like span but from the end of the vector. spanR :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | Break a vector on a subvector, returning a pair of the part of the -- vector prior to the match, and the rest of the vector, e.g. -- --
--   break "wor" "hello, world" = ("hello, ", "world")
--   
breakOn :: (Vec v a, Eq a) => v a -> v a -> (v a, v a) group :: (Vec v a, Eq a) => v a -> [v a] groupBy :: forall v a. Vec v a => (a -> a -> Bool) -> v a -> [v a] -- | O(n) The stripPrefix function takes two vectors and -- returns Just the remainder of the second iff the first is its -- prefix, and otherwise Nothing. stripPrefix :: (Vec v a, Eq (v a)) => v a -> v a -> Maybe (v a) -- | O(n) The stripSuffix function takes two vectors and returns -- Just the remainder of the second iff the first is its suffix, and -- otherwise Nothing. stripSuffix :: (Vec v a, Eq (v a)) => v a -> v a -> Maybe (v a) -- | O(n) Break a vector into pieces separated by the delimiter -- element 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 -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- NOTE, this function behavior different with bytestring's. see -- #56. split :: (Vec v a, Eq a) => a -> v a -> [v a] -- | O(n) Splits a vector 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. -- --
--   splitWith (=='a') "aabbaca" == ["","","bb","c",""]
--   splitWith (=='a') []        == [""]
--   
-- -- NOTE, this function behavior different with bytestring's. see -- #56. splitWith :: Vec v a => (a -> Bool) -> v a -> [v a] -- | O(m+n) Break haystack into pieces separated by needle. -- -- Note: An empty needle will essentially split haystack element by -- element. -- -- Examples: -- --
--   >>> splitOn "\r\n" "a\r\nb\r\nd\r\ne"
--   ["a","b","d","e"]
--   
-- --
--   >>> splitOn "aaa"  "aaaXaaaXaaaXaaa"
--   ["","X","X","X",""]
--   
-- --
--   >>> splitOn "x"  "x"
--   ["",""]
--   
-- -- and -- --
--   intercalate s . splitOn s         == id
--   splitOn (singleton c)             == split (==c)
--   
splitOn :: (Vec v a, Eq a) => v a -> v a -> [v a] -- | The isPrefix function returns True if the first -- argument is a prefix of the second. isPrefixOf :: forall v a. (Vec v a, Eq (v a)) => v a -> v a -> Bool -- | O(n) The isSuffixOf function takes two vectors and -- returns True if the first is a suffix of the second. isSuffixOf :: forall v a. (Vec v a, Eq (v a)) => v a -> v a -> Bool -- | Check whether one vector is a subvector of another. -- -- needle isInfixOf haystack === null haystack || indices -- needle haystake /= []. isInfixOf :: (Vec v a, Eq a) => v a -> v a -> Bool -- | O(n) Find the longest non-empty common prefix of two strings -- and return it, along with the suffixes of each string at which they no -- longer match. e.g. -- --
--   >>> commonPrefix "foobar" "fooquux"
--   ("foo","bar","quux")
--   
-- --
--   >>> commonPrefix "veeble" "fetzer"
--   ("","veeble","fetzer")
--   
commonPrefix :: (Vec v a, Eq a) => v a -> v a -> (v a, v a, v a) -- | O(n) Breaks a Bytes up into a list of words, delimited -- by ascii space. words :: Bytes -> [Bytes] -- | O(n) Breaks a Bytes up into a list of lines, delimited -- by ascii n. lines :: Bytes -> [Bytes] -- | O(n) Joins words with ascii space. unwords :: [Bytes] -> Bytes -- | O(n) Joins lines with ascii n. -- -- NOTE: This functions is different from unlines, it DOES NOT add -- a trailing n. unlines :: [Bytes] -> Bytes -- | Add padding to the left so that the whole vector's length is at least -- n. padLeft :: Vec v a => Int -> a -> v a -> v a -- | Add padding to the right so that the whole vector's length is at least -- n. padRight :: Vec v a => Int -> a -> v a -> v a -- | O(n) reverse vs efficiently returns the -- elements of xs in reverse order. reverse :: forall v a. Vec v a => v a -> v a -- | O(n) The intersperse function takes an element and a -- vector and `intersperses' that element between the elements of the -- vector. It is analogous to the intersperse function on Lists. intersperse :: forall v a. Vec v a => a -> v a -> v a -- | O(n) The intercalate function takes a vector and a list -- of vectors and concatenates the list after interspersing the first -- argument between each element of the list. -- -- Note: intercalate will force the entire vector list. intercalate :: Vec v a => v a -> [v a] -> v a -- | O(n) An efficient way to join vector with an element. intercalateElem :: forall v a. Vec v a => a -> [v a] -> v a -- | The transpose function transposes the rows and columns of its -- vector argument. transpose :: Vec v a => [v a] -> [v a] -- | zipWith' zip two vector with a zipping function. -- -- For example, zipWith (+) is applied to two vector to -- produce a vector of corresponding sums, the result will be evaluated -- strictly. zipWith' :: forall v a u b w c. (Vec v a, Vec u b, Vec w c) => (a -> b -> c) -> v a -> u b -> w c -- | unzipWith' disassemble a vector with a disassembling function, -- -- The results inside tuple will be evaluated strictly. unzipWith' :: forall v a u b w c. (Vec v a, Vec u b, Vec w c) => (a -> (b, c)) -> v a -> (u b, w c) -- | scanl' is similar to foldl, 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 -- --
--   lastM (scanl' f z xs) == Just (foldl f z xs).
--   
scanl' :: forall v u a b. (Vec v a, Vec u b) => (b -> a -> b) -> b -> v a -> u b -- | 'scanl1'' is a variant of scanl that has no starting value -- argument. -- --
--   scanl1' f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   scanl1' f [] == []
--   
scanl1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a -- | scanr' is the right-to-left dual of scanl'. scanr' :: forall v u a b. (Vec v a, Vec u b) => (a -> b -> b) -> b -> v a -> u b -- | scanr1' is a variant of scanr that has no starting value -- argument. scanr1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a -- | x' = rangeCut x min max limit x' 's range to -- min ~ max. rangeCut :: Int -> Int -> Int -> Int -- | O(1) Extract the first element of a vector. -- -- Throw EmptyVector if vector is empty. head :: (Vec v a, HasCallStack) => v a -> a -- | O(1) Extract the elements after the head of a vector. -- -- Throw EmptyVector if vector is empty. tail :: (Vec v a, HasCallStack) => v a -> v a -- | O(1) Extract the elements before of the last one. -- -- Throw EmptyVector if vector is empty. init :: (Vec v a, HasCallStack) => v a -> v a -- | O(1) Extract the last element of a vector. -- -- Throw EmptyVector if vector is empty. last :: (Vec v a, HasCallStack) => v a -> a -- | O(1) Index array element. -- -- Throw IndexOutOfVectorRange if index outside of the vector. index :: (Vec v a, HasCallStack) => v a -> Int -> a -- | O(1) Index array element. -- -- Throw IndexOutOfVectorRange if index outside of the vector. indexM :: (Vec v a, Monad m, HasCallStack) => v a -> Int -> m a -- | O(n) Modify vector's element under given index. -- -- Throw IndexOutOfVectorRange if index outside of the vector. modifyIndex :: (Vec v a, HasCallStack) => v a -> Int -> (a -> a) -> v a -- | O(n) Modify vector's element under given index. -- -- Return original vector if index outside of the vector. modifyIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> (a -> a) -> v a -- | O(n) insert element to vector under given index. -- -- Throw IndexOutOfVectorRange if index outside of the vector. insertIndex :: (Vec v a, HasCallStack) => v a -> Int -> a -> v a -- | O(n) insert element to vector under given index. -- -- Return original vector if index outside of the vector. insertIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> a -> v a -- | O(n) Delete vector's element under given index. -- -- Throw IndexOutOfVectorRange if index outside of the vector. deleteIndex :: (Vec v a, HasCallStack) => v a -> Int -> v a -- | O(n) Delete vector's element under given index. -- -- Return original vector if index outside of the vector. deleteIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> v a -- | O(1) Extract the first element of a vector. -- -- Make sure vector is non-empty, otherwise segmentation fault await! unsafeHead :: Vec v a => v a -> a -- | O(1) Extract the elements after the head of a vector. -- -- Make sure vector is non-empty, otherwise segmentation fault await! unsafeTail :: Vec v a => v a -> v a -- | O(1) Extract the elements before of the last one. -- -- Make sure vector is non-empty, otherwise segmentation fault await! unsafeInit :: Vec v a => v a -> v a -- | O(1) Extract the last element of a vector. -- -- Make sure vector is non-empty, otherwise segmentation fault await! unsafeLast :: Vec v a => v a -> a -- | O(1) Index array element. -- -- Make sure index is in bound, otherwise segmentation fault await! unsafeIndex :: Vec v a => v a -> Int -> a -- | O(1) Index array element. -- -- Make sure index is in bound, otherwise segmentation fault await! unsafeIndexM :: (Vec v a, Monad m) => v a -> Int -> m a -- | O(n) Modify vector's element under given index. -- -- Make sure index is in bound, otherwise segmentation fault await! unsafeModifyIndex :: (Vec v a, HasCallStack) => v a -> Int -> (a -> a) -> v a -- | O(n) Insert element to vector under given index. -- -- Make sure index is in bound, otherwise segmentation fault await! unsafeInsertIndex :: (Vec v a, HasCallStack) => v a -> Int -> a -> v a -- | O(n) Delete vector's element under given index. -- -- Make sure index is in bound, otherwise segmentation fault await! unsafeDeleteIndex :: (Vec v a, HasCallStack) => v a -> Int -> v a -- | O(1) take n, applied to a vector xs, -- returns the prefix of xs of length n. -- -- Make sure n is smaller than vector's length, otherwise segmentation -- fault await! unsafeTake :: Vec v a => Int -> v a -> v a -- | O(1) drop n xs returns the suffix of -- xs after the first n elements. -- -- Make sure n is smaller than vector's length, otherwise segmentation -- fault await! unsafeDrop :: Vec v a => Int -> v a -> v a -- | A Text wrap a Bytes which will be interpreted using -- UTF-8 encoding. User should always use validate to construt a -- Text (instead of using construtor directly or coercing), -- otherwise illegal UTF-8 encoded codepoints will cause undefined -- behaviours. module Z.Data.Text.Base -- | Text represented as UTF-8 encoded Bytes newtype Text Text :: Bytes -> Text -- | Extract UTF-8 encoded Bytes from Text [getUTF8Bytes] :: Text -> Bytes -- | O(n) Validate a sequence of bytes is UTF-8 encoded. -- -- Throw InvalidUTF8Exception in case of invalid codepoint. validate :: HasCallStack => Bytes -> Text -- | O(n) Validate a sequence of bytes is all ascii char -- byte(<128). -- -- Throw InvalidASCIIException in case of invalid byte, It's not -- always faster than validate, use it only if you want to -- validate ASCII char sequences. validateASCII :: HasCallStack => Bytes -> Text -- | O(n) Validate a sequence of bytes is UTF-8 encoded. -- -- Return Nothing in case of invalid codepoint. validateMaybe :: Bytes -> Maybe Text -- | O(n) Validate a sequence of bytes is all ascii char -- byte(<128). -- -- Return Nothing in case of invalid byte. validateASCIIMaybe :: Bytes -> Maybe Text -- | O(n) Get the nth codepoint from Text, throw -- IndexOutOfTextRange when out of bound. index :: HasCallStack => Text -> Int -> Char -- | O(n) Get the nth codepoint from Text. indexMaybe :: Text -> Int -> Maybe Char -- | O(n) Find the nth codepoint's byte index (pointing to the nth -- char's begining byte). -- -- The index is only meaningful to the whole byte slice, if there's less -- than n codepoints, the index will point to next byte after the end. charByteIndex :: Text -> Int -> Int -- | O(n) Get the nth codepoint from Text counting from the -- end, throw IndexOutOfVectorRange n callStack when out of -- bound. indexR :: HasCallStack => Text -> Int -> Char -- | O(n) Get the nth codepoint from Text counting from the -- end. indexMaybeR :: Text -> Int -> Maybe Char -- | O(n) Find the nth codepoint's byte index from the end (pointing -- to the previous char's ending byte). -- -- The index is only meaningful to the whole byte slice, if there's less -- than n codepoints, the index will point to previous byte before the -- start. charByteIndexR :: Text -> Int -> Int -- | O(1). Empty text. empty :: Text -- | O(1). Single char text. singleton :: Char -> Text -- | O(n). Copy a text from slice. copy :: Text -> Text -- | O(n) replicate char n time. replicate :: Int -> Char -> Text -- | O(n*m) cycleN a text n times. cycleN :: Int -> Text -> Text -- | O(n) Convert a string into a text -- -- Alias for packN defaultInitSize, will be -- rewritten to a memcpy if possible. pack :: String -> Text -- | O(n) Convert a list into a text with an approximate size(in -- bytes, not codepoints). -- -- If the encoded bytes length is larger than the size given, we simply -- double the buffer size and continue building. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packN :: Int -> String -> Text -- | O(n) Alias for packRN defaultInitSize. packR :: String -> Text -- | O(n) packN in reverse order. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packRN :: Int -> String -> Text -- | O(n) Convert text to a char list. -- -- Unpacking is done lazily. i.e. we will retain reference to the array -- until all element are consumed. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpack :: Text -> String -- | O(n) Convert text to a list in reverse order. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpackR :: Text -> String -- | O(n) convert from a char vector. fromVector :: PrimVector Char -> Text -- | O(n) convert to a char vector. toVector :: Text -> PrimVector Char -- | O(1) Test whether a text is empty. null :: Text -> Bool -- | O(n) The char length of a text. length :: Text -> Int -- | O(m+n) -- -- There's no need to guard empty vector because we guard them for you, -- so appending empty text are no-ops. append :: Text -> Text -> Text -- | O(n) map f t is the Text -- obtained by applying f to each char of t. Performs -- replacement on invalid scalar values. map' :: (Char -> Char) -> Text -> Text -- | Strict mapping with index. imap' :: (Int -> Char -> Char) -> Text -> Text -- | Strict left to right fold. foldl' :: (b -> Char -> b) -> b -> Text -> b -- | Strict left to right fold with index. ifoldl' :: (b -> Int -> Char -> b) -> b -> Text -> b -- | Strict right to left fold foldr' :: (Char -> b -> b) -> b -> Text -> b -- | Strict right to left fold with index -- -- NOTE: the index is counting from 0, not backwards ifoldr' :: (Int -> Char -> b -> b) -> b -> Text -> b -- | O(n) Concatenate a list of text. -- -- Note: concat have to force the entire list to filter out empty -- text and calculate the length for allocation. concat :: [Text] -> Text -- | Map a function over a text and concatenate the results concatMap :: (Char -> Text) -> Text -> Text -- | O(n) count returns count of an element from a text. count :: Char -> Text -> Int -- | O(n) Applied to a predicate and text, all determines if -- all chars of the text satisfy the predicate. all :: (Char -> Bool) -> Text -> Bool -- | O(n) Applied to a predicate and a text, any determines -- if any chars of the text satisfy the predicate. any :: (Char -> Bool) -> Text -> Bool -- | Get the display width of a piece of text. -- -- You shouldn't pass texts with control characters(<0x20, \DEL), -- which are counted with -1 width. -- --
--   >>> displayWidth "你好世界!"
--   
--   >>> 10
--   
--   >>> displayWidth "hello world!"
--   
--   >>> 12
--   
displayWidth :: Text -> Int data NormalizationResult NormalizedYes :: NormalizationResult NormalizedMaybe :: NormalizationResult NormalizedNo :: NormalizationResult -- | These are the Unicode Normalization Forms: -- --
--   Form                         | Description
--   ---------------------------- | ---------------------------------------------
--   Normalization Form D (NFD)   | Canonical decomposition
--   Normalization Form C (NFC)   | Canonical decomposition, followed by canonical composition
--   Normalization Form KD (NFKD) | Compatibility decomposition
--   Normalization Form KC (NFKC) | Compatibility decomposition, followed by canonical composition
--   
data NormalizeMode NFC :: NormalizeMode NFKC :: NormalizeMode NFD :: NormalizeMode NFKD :: NormalizeMode -- | Check if a string is stable in the NFC (Normalization Form C). isNormalized :: Text -> NormalizationResult -- | Check if a string is stable in the specified Unicode Normalization -- Form. -- -- This function can be used as a preprocessing step, before attempting -- to normalize a string. Normalization is a very expensive process, it -- is often cheaper to first determine if the string is unstable in the -- requested normalization form. -- -- The result of the check will be YES if the string is stable and MAYBE -- or NO if it is unstable. If the result is MAYBE, the string does not -- necessarily have to be normalized. -- -- For more information, please review -- <http://www.unicode.org/reports/tr15/ Unicode Standard Annex -- #15 - Unicode Normalization Forms>. isNormalizedTo :: NormalizeMode -> Text -> NormalizationResult -- | Normalize a string to NFC (Normalization Form C). normalize :: Text -> Text -- | Normalize a string to the specified Unicode Normalization Form. -- -- The Unicode standard defines two standards for equivalence between -- characters: canonical and compatibility equivalence. Canonically -- equivalent characters and sequence represent the same abstract -- character and must be rendered with the same appearance and behavior. -- Compatibility equivalent characters have a weaker equivalence and may -- be rendered differently. -- -- Unicode Normalization Forms are formally defined standards that can be -- used to test whether any two strings of characters are equivalent to -- each other. This equivalence may be canonical or compatibility. -- -- The algorithm puts all combining marks into a specified order and uses -- the rules for decomposition and composition to transform the string -- into one of four Unicode Normalization Forms. A binary comparison can -- then be used to determine equivalence. normalizeTo :: NormalizeMode -> Text -> Text -- | Get environment locale envLocale :: IO Locale -- | Remove case distinction from UTF-8 encoded text with default locale. caseFold :: Text -> Text -- | Remove case distinction from UTF-8 encoded text. -- -- Case folding is the process of eliminating differences between code -- points concerning case mapping. It is most commonly used for comparing -- strings in a case-insensitive manner. Conversion is fully compliant -- with the Unicode 7.0 standard. -- -- Although similar to lowercasing text, there are significant -- differences. For one, case folding does _not_ take locale into account -- when converting. In some cases, case folding can be up to 20% faster -- than lowercasing the same text, but the result cannot be treated as -- correct lowercased text. -- -- Only two locale-specific exception are made when case folding text. In -- Turkish, U+0049 LATIN CAPITAL LETTER I maps to U+0131 LATIN SMALL -- LETTER DOTLESS I and U+0130 LATIN CAPITAL LETTER I WITH DOT ABOVE maps -- to U+0069 LATIN SMALL LETTER I. -- -- Although most code points can be case folded without changing length, -- there are notable exceptions. For example, U+0130 (LATIN CAPITAL -- LETTER I WITH DOT ABOVE) maps to "U+0069 U+0307" (LATIN SMALL LETTER I -- and COMBINING DOT ABOVE) when converted to lowercase. -- -- Only a handful of scripts make a distinction between upper- and -- lowercase. In addition to modern scripts, such as Latin, Greek, -- Armenian and Cyrillic, a few historic or archaic scripts have case. -- The vast majority of scripts do not have case distinctions. caseFoldWith :: Locale -> Text -> Text -- | Convert UTF-8 encoded text to lowercase with default locale. toLower :: Text -> Text -- | Convert UTF-8 encoded text to lowercase. -- -- This function allows conversion of UTF-8 encoded strings to lowercase -- without first changing the encoding to UTF-32. Conversion is fully -- compliant with the Unicode 7.0 standard. -- -- Although most code points can be converted to lowercase with changing -- length, there are notable exceptions. For example, U+0130 (LATIN -- CAPITAL LETTER I WITH DOT ABOVE) maps to "U+0069 U+0307" (LATIN SMALL -- LETTER I and COMBINING DOT ABOVE) when converted to lowercase. -- -- Only a handful of scripts make a distinction between upper- and -- lowercase. In addition to modern scripts, such as Latin, Greek, -- Armenian and Cyrillic, a few historic or archaic scripts have case. -- The vast majority of scripts do not have case distinctions. -- -- Case mapping is not reversible. That is, toUpper(toLower(x)) != -- toLower(toUpper(x)). -- -- Certain code points (or combinations of code points) apply rules based -- on the locale. For more information about these exceptional code -- points, please refer to the Unicode standard: -- ftp://ftp.unicode.org/Public/UNIDATA/SpecialCasing.txt toLowerWith :: Locale -> Text -> Text -- | Convert UTF-8 encoded text to uppercase with default locale. toUpper :: Text -> Text -- | Convert UTF-8 encoded text to uppercase. -- -- Conversion is fully compliant with the Unicode 7.0 standard. -- -- Although most code points can be converted without changing length, -- there are notable exceptions. For example, U+00DF (LATIN SMALL LETTER -- SHARP S) maps to "U+0053 U+0053" (LATIN CAPITAL LETTER S and LATIN -- CAPITAL LETTER S) when converted to uppercase. -- -- Only a handful of scripts make a distinction between upper and -- lowercase. In addition to modern scripts, such as Latin, Greek, -- Armenian and Cyrillic, a few historic or archaic scripts have case. -- The vast majority of scripts do not have case distinctions. -- -- Case mapping is not reversible. That is, toUpper(toLower(x)) != -- toLower(toUpper(x)). -- -- Certain code points (or combinations of code points) apply rules based -- on the locale. For more information about these exceptional code -- points, please refer to the Unicode standard: -- ftp://ftp.unicode.org/Public/UNIDATA/SpecialCasing.txt toUpperWith :: Locale -> Text -> Text -- | Convert UTF-8 encoded text to titlecase with default locale. toTitle :: Text -> Text -- | Convert UTF-8 encoded text to titlecase. -- -- This function allows conversion of UTF-8 encoded strings to titlecase. -- Conversion is fully compliant with the Unicode 7.0 standard. -- -- Titlecase requires a bit more explanation than uppercase and -- lowercase, because it is not a common text transformation. Titlecase -- uses uppercase for the first letter of each word and lowercase for the -- rest. Words are defined as "collections of code points with general -- category Lu, Ll, Lt, Lm or Lo according to the Unicode database". -- -- Effectively, any type of punctuation can break up a word, even if this -- is not grammatically valid. This happens because the titlecasing -- algorithm does not and cannot take grammar rules into account. -- --
--   Text                                 | Titlecase
--   -------------------------------------|-------------------------------------
--   The running man                      | The Running Man
--   NATO Alliance                        | Nato Alliance
--   You're amazing at building libraries | You'Re Amazing At Building Libraries
--   
-- -- Although most code points can be converted to titlecase without -- changing length, there are notable exceptions. For example, U+00DF -- (LATIN SMALL LETTER SHARP S) maps to "U+0053 U+0073" (LATIN CAPITAL -- LETTER S and LATIN SMALL LETTER S) when converted to titlecase. -- -- Certain code points (or combinations of code points) apply rules based -- on the locale. For more information about these exceptional code -- points, please refer to the Unicode standard: -- ftp://ftp.unicode.org/Public/UNIDATA/SpecialCasing.txt toTitleWith :: Locale -> Text -> Text -- | Check if the input string conforms to the category specified by the -- flags. -- -- This function can be used to check if the code points in a string are -- part of a category. Valid flags are members of the "list of -- categories". The category for a code point is defined as part of the -- entry in UnicodeData.txt, the data file for the Unicode code point -- database. -- -- By default, the function will treat grapheme clusters as a single code -- point. This means that the following string: -- --
--   Code point | Canonical combining class | General category      | Name
--   ---------- | ------------------------- | --------------------- | ----------------------
--   U+0045     | 0                         | Lu (Uppercase letter) | LATIN CAPITAL LETTER E
--   U+0300     | 230                       | Mn (Non-spacing mark) | COMBINING GRAVE ACCENT
--   
-- -- Will match with CategoryLetterUppercase in its entirety, -- because the COMBINING GRAVE ACCENT is treated as part of the grapheme -- cluster. This is useful when e.g. creating a text parser, because you -- do not have to normalize the text first. -- -- If this is undesired behavior, specify the -- CategoryIgnoreGraphemeCluster flag. -- -- In order to maintain backwards compatibility with POSIX functions like -- isdigit and isspace, compatibility flags have been -- provided. Note, however, that the result is only guaranteed to be -- correct for code points in the Basic Latin range, between U+0000 and -- 0+007F. Combining a compatibility flag with a regular category flag -- will result in undefined behavior. isCategory :: Category -> Text -> Bool -- | Try to match as many code points with the matching category flags as -- possible and return the prefix and suffix. spanCategory :: Category -> Text -> (Text, Text) -- | Locale for case mapping. type Locale = CSize pattern LocaleDefault :: Locale pattern LocaleLithuanian :: Locale pattern LocaleTurkishAndAzeriLatin :: Locale -- | Unicode categories. -- -- See isCategory, you can combine categories with bitwise or. type Category = CSize pattern CategoryLetterUppercase :: Category pattern CategoryLetterLowercase :: Category pattern CategoryLetterTitlecase :: Category pattern CategoryLetterOther :: Category pattern CategoryLetter :: Category pattern CategoryCaseMapped :: Category pattern CategoryMarkNonSpacing :: Category pattern CategoryMarkSpacing :: Category pattern CategoryMarkEnclosing :: Category pattern CategoryMark :: Category pattern CategoryNumberDecimal :: Category pattern CategoryNumberLetter :: Category pattern CategoryNumberOther :: Category pattern CategoryNumber :: Category pattern CategoryPunctuationConnector :: Category pattern CategoryPunctuationDash :: Category pattern CategoryPunctuationOpen :: Category pattern CategoryPunctuationClose :: Category pattern CategoryPunctuationInitial :: Category pattern CategoryPunctuationFinal :: Category pattern CategoryPunctuationOther :: Category pattern CategoryPunctuation :: Category pattern CategorySymbolMath :: Category pattern CategorySymbolCurrency :: Category pattern CategorySymbolModifier :: Category pattern CategorySymbolOther :: Category pattern CategorySymbol :: Category pattern CategorySeparatorSpace :: Category pattern CategorySeparatorLine :: Category pattern CategorySeparatorParagraph :: Category pattern CategorySeparator :: Category pattern CategoryControl :: Category pattern CategoryFormat :: Category pattern CategorySurrogate :: Category pattern CategoryPrivateUse :: Category pattern CategoryUnassigned :: Category pattern CategoryCompatibility :: Category pattern CategoryIgnoreGraphemeCluster :: Category pattern CategoryIscntrl :: Category pattern CategoryIsprint :: Category pattern CategoryIsspace :: Category pattern CategoryIsblank :: Category pattern CategoryIsgraph :: Category pattern CategoryIspunct :: Category pattern CategoryIsalnum :: Category pattern CategoryIsalpha :: Category pattern CategoryIsupper :: Category pattern CategoryIslower :: Category pattern CategoryIsdigit :: Category pattern CategoryIsxdigit :: Category data TextException InvalidUTF8Exception :: CallStack -> TextException InvalidASCIIException :: CallStack -> TextException -- | first payload is invalid char index IndexOutOfTextRange :: Int -> CallStack -> TextException EmptyText :: CallStack -> TextException errorEmptyText :: HasCallStack => a c_utf8_validate_ba :: ByteArray# -> Int# -> Int# -> Int c_utf8_validate_addr :: Addr# -> Int -> IO Int c_ascii_validate_ba :: ByteArray# -> Int# -> Int# -> Int c_ascii_validate_addr :: Addr# -> Int -> IO Int instance GHC.Base.Semigroup Z.Data.Text.Base.Text instance GHC.Base.Monoid Z.Data.Text.Base.Text instance GHC.Show.Show Z.Data.Text.Base.TextException instance GHC.Exception.Type.Exception Z.Data.Text.Base.TextException instance GHC.Exts.IsList Z.Data.Text.Base.Text instance GHC.Classes.Eq Z.Data.Text.Base.Text instance GHC.Classes.Ord Z.Data.Text.Base.Text instance GHC.Show.Show Z.Data.Text.Base.Text instance GHC.Read.Read Z.Data.Text.Base.Text instance Control.DeepSeq.NFData Z.Data.Text.Base.Text instance Test.QuickCheck.Arbitrary.Arbitrary Z.Data.Text.Base.Text instance Test.QuickCheck.Arbitrary.CoArbitrary Z.Data.Text.Base.Text instance Data.Hashable.Class.Hashable Z.Data.Text.Base.Text instance Data.String.IsString Z.Data.Text.Base.Text instance Data.CaseInsensitive.Internal.FoldCase Z.Data.Text.Base.Text module Z.Data.Text.Search -- | O(n) elem test if given char is in given text. elem :: Char -> Text -> Bool -- | O(n) not . elem notElem :: Char -> Text -> Bool -- | find all char index matching the predicate. findIndices :: (Char -> Bool) -> Text -> [Int] -- | find all char's byte index matching the predicate. findBytesIndices :: (Char -> Bool) -> Text -> [Int] -- | O(n) find the first char matching the predicate in a text from -- left to right, if there isn't one, return the text length. find :: (Char -> Bool) -> Text -> (Int, Maybe Char) -- | O(n) find the first char matching the predicate in a text from -- right to left. findR :: (Char -> Bool) -> Text -> (Int, Maybe Char) -- | O(n) find the char index. findIndex :: (Char -> Bool) -> Text -> Int -- | O(n) find the char index in reverse order. findIndexR :: (Char -> Bool) -> Text -> Int -- | O(n) find the char's byte slice index. findBytesIndex :: (Char -> Bool) -> Text -> Int -- | O(n) find the char's byte slice index in reverse order(pointing -- to the right char's first byte). findBytesIndexR :: (Char -> Bool) -> Text -> Int -- | O(n) filter, applied to a predicate and a text, returns -- a text containing those chars that satisfy the predicate. filter :: (Char -> Bool) -> Text -> Text -- | O(n) The partition function takes a predicate, a text, -- returns a pair of text with codepoints which do and do not satisfy the -- predicate, respectively; i.e., -- --
--   partition p txt == (filter p txt, filter (not . p) txt)
--   
partition :: (Char -> Bool) -> Text -> (Text, Text) -- | Various combinators works on Texts. module Z.Data.Text.Extra -- | O(n) cons is analogous to (:) for lists, but of -- different complexity, as it requires making a copy. cons :: Char -> Text -> Text -- | O(n) Append a char to the end of a text. snoc :: Text -> Char -> Text -- | O(1) Extract the head and tail of a text, return Nothing -- if it is empty. uncons :: Text -> Maybe (Char, Text) -- | O(1) Extract the init and last of a text, return Nothing -- if text is empty. unsnoc :: Text -> Maybe (Text, Char) -- | O(1) Extract the first char of a text. headMaybe :: Text -> Maybe Char -- | O(1) Extract the chars after the head of a text. -- -- NOTE: tailMayEmpty return empty text in the case of an empty -- text. tailMayEmpty :: Text -> Text -- | O(1) Extract the last char of a text. lastMaybe :: Text -> Maybe Char -- | O(1) Extract the chars before of the last one. -- -- NOTE: initMayEmpty return empty text in the case of an empty -- text. initMayEmpty :: Text -> Text -- | O(1) Extract the first char of a text. -- -- Throw EmptyText if text is empty. head :: Text -> Char -- | O(1) Extract the chars after the head of a text. -- -- Throw EmptyText if text is empty. tail :: Text -> Text -- | O(1) Extract the last char of a text. -- -- Throw EmptyText if text is empty. last :: Text -> Char -- | O(1) Extract the chars before of the last one. -- -- Throw EmptyText if text is empty. init :: Text -> Text -- | O(n) Return all initial segments of the given text, empty -- first. inits :: Text -> [Text] -- | O(n) Return all final segments of the given text, whole text -- first. tails :: Text -> [Text] -- | O(1) take n, applied to a text xs, -- returns the prefix of xs of length n, or xs -- itself if n > length xs. take :: Int -> Text -> Text -- | O(1) drop n xs returns the suffix of -- xs after the first n char, or [] if n -- > length xs. drop :: Int -> Text -> Text -- | O(1) takeR n, applied to a text xs, -- returns the suffix of xs of length n, or xs -- itself if n > length xs. takeR :: Int -> Text -> Text -- | O(1) dropR n xs returns the prefix of -- xs before the last n char, or [] if n -- > length xs. dropR :: Int -> Text -> Text -- | O(1) Extract a sub-range text with give start index and length. -- -- This function is a total function just like 'takedrop', -- indexlength exceeds range will be ingored, e.g. -- --
--   slice 1 3 "hello"   == "ell"
--   slice -1 -1 "hello" == ""
--   slice -2 2 "hello"  == ""
--   slice 2 10 "hello"  == "llo"
--   
-- -- This holds for all x y: slice x y vs == drop x . take (x+y) -- vs slice :: Int -> Int -> Text -> Text -- | O(n) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Int -> Text -> (Text, Text) -- | O(n) Applied to a predicate p and a text t, -- returns the longest prefix (possibly empty) of t of elements -- that satisfy p. takeWhile :: (Char -> Bool) -> Text -> Text -- | O(n) Applied to a predicate p and a text t, -- returns the longest suffix (possibly empty) of t of elements -- that satisfy p. takeWhileR :: (Char -> Bool) -> Text -> Text -- | O(n) Applied to a predicate p and a text vs, -- returns the suffix (possibly empty) remaining after takeWhile -- p vs. dropWhile :: (Char -> Bool) -> Text -> Text -- | O(n) Applied to a predicate p and a text vs, -- returns the prefix (possibly empty) remaining before takeWhileR -- p vs. dropWhileR :: (Char -> Bool) -> Text -> Text -- | O(n) dropAround f = dropWhile f . dropWhileR f dropAround :: (Char -> Bool) -> Text -> Text -- | O(n) Split the text into the longest prefix of elements that do -- not satisfy the predicate and the rest without copying. break :: (Char -> Bool) -> Text -> (Text, Text) -- | O(n) Split the text into the longest prefix of elements that -- satisfy the predicate and the rest without copying. span :: (Char -> Bool) -> Text -> (Text, Text) -- | breakR behaves like break but from the end of the text. -- --
--   breakR p == spanR (not.p)
--   
breakR :: (Char -> Bool) -> Text -> (Text, Text) -- | spanR behaves like span but from the end of the text. spanR :: (Char -> Bool) -> Text -> (Text, Text) -- | Break a text on a subtext, returning a pair of the part of the text -- prior to the match, and the rest of the text, e.g. -- --
--   break "wor" "hello, world" = ("hello, ", "world")
--   
breakOn :: Text -> Text -> (Text, Text) -- | O(n+m) Find all non-overlapping instances of needle in haystack. Each -- element of the returned list consists of a pair: -- -- -- -- Examples: -- --
--   breakOnAll "::" ""
--   ==> []
--   breakOnAll "" "abc"
--   ==> [("a", "bc"), ("ab", "c"), ("abc", "/")]
--   
-- -- The result list is lazy, search is performed when you force the list. breakOnAll :: Text -> Text -> [(Text, Text)] -- | The group function takes a text and returns a list of texts 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 groupBy, which allows the programmer to -- supply their own equality test. group :: Text -> [Text] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (Char -> Char -> Bool) -> Text -> [Text] -- | O(n) The stripPrefix function takes two texts and -- returns Just the remainder of the second iff the first is its -- prefix, and otherwise Nothing. stripPrefix :: Text -> Text -> Maybe Text -- | O(n) The stripSuffix function takes two texts and returns Just -- the remainder of the second iff the first is its suffix, and otherwise -- Nothing. stripSuffix :: Text -> Text -> Maybe Text -- | O(n) Break a text into pieces separated by the delimiter -- element 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 -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- NOTE, this function behavior different with bytestring's. see -- #56. split :: Char -> Text -> [Text] -- | O(n) Splits a text into components delimited by separators, -- where the predicate returns True for a separator char. The resulting -- components do not contain the separators. Two adjacent separators -- result in an empty component in the output. eg. -- --
--   splitWith (=='a') "aabbaca" == ["","","bb","c",""]
--   splitWith (=='a') []        == [""]
--   
splitWith :: (Char -> Bool) -> Text -> [Text] -- | O(m+n) Break haystack into pieces separated by needle. -- -- Note: An empty needle will essentially split haystack element by -- element. -- -- Examples: -- --
--   >>> splitOn "\r\n" "a\r\nb\r\nd\r\ne"
--   ["a","b","d","e"]
--   
-- --
--   >>> splitOn "aaa"  "aaaXaaaXaaaXaaa"
--   ["","X","X","X",""]
--   
-- --
--   >>> splitOn "x"  "x"
--   ["",""]
--   
-- -- and -- --
--   intercalate s . splitOn s         == id
--   splitOn (singleton c)             == split (==c)
--   
splitOn :: Text -> Text -> [Text] -- | The isPrefix function returns True if the first -- argument is a prefix of the second. isPrefixOf :: Text -> Text -> Bool -- | O(n) The isSuffixOf function takes two text and returns -- True if the first is a suffix of the second. isSuffixOf :: Text -> Text -> Bool -- | Check whether one text is a subtext of another. -- -- needle isInfixOf haystack === null haystack || indices -- needle haystake /= []. isInfixOf :: Text -> Text -> Bool -- | O(n) Find the longest non-empty common prefix of two strings -- and return it, along with the suffixes of each string at which they no -- longer match. e.g. -- --
--   >>> commonPrefix "foobar" "fooquux"
--   ("foo","bar","quux")
--   
-- --
--   >>> commonPrefix "veeble" "fetzer"
--   ("","veeble","fetzer")
--   
commonPrefix :: Text -> Text -> (Text, Text, Text) -- | O(n) Breaks a Bytes up into a list of words, delimited -- by unicode space. words :: Text -> [Text] -- | O(n) Breaks a text up into a list of lines, delimited by ascii -- n. lines :: Text -> [Text] -- | O(n) Joins words with ascii space. unwords :: [Text] -> Text -- | O(n) Joins lines with ascii n. -- -- NOTE: This functions is different from unlines, it DOES NOT add -- a trailing n. unlines :: [Text] -> Text -- | Add padding to the left so that the whole text's length is at least n. padLeft :: Int -> Char -> Text -> Text -- | Add padding to the right so that the whole text's length is at least -- n. padRight :: Int -> Char -> Text -> Text -- | O(n) Reverse the characters of a string. reverse :: Text -> Text -- | O(n) The intersperse function takes a character and -- places it between the characters of a Text. Performs -- replacement on invalid scalar values. intersperse :: Char -> Text -> Text -- | O(n) The intercalate function takes a Text and a -- list of Texts and concatenates the list after interspersing the -- first argument between each element of the list. intercalate :: Text -> [Text] -> Text intercalateElem :: Char -> [Text] -> Text -- | The transpose function transposes the rows and columns of its -- text argument. transpose :: [Text] -> [Text] -- | This module provide internal data types for a simple resumable -- Parser, which is suitable for binary protocol and simple -- textual protocol parsing. Parser extensively works on on -- Bytes, which is same to Text representation. module Z.Data.Parser.Base -- | Simple parsing result, that represent respectively: -- -- data Result a Success :: a -> !Bytes -> Result a Failure :: ParseError -> !Bytes -> Result a Partial :: ParseStep a -> Result a -- | Type alias for error message type ParseError = [Text] -- | A parse step consumes Bytes and produce Result. type ParseStep r = Bytes -> Result r -- | Simple CPSed parser -- -- A parser takes a failure continuation, and a success one, while the -- success continuation is usually composed by Monad instance, the -- failure one is more like a reader part, which can be modified via -- <?>. If you build parsers from ground, a pattern like -- this can be used: -- --
--   xxParser = do
--     ensureN errMsg ...            -- make sure we have some bytes
--     Parser $  kf k inp ->        -- fail continuation, success continuation and input
--       ...
--       ... kf errMsg (if input not OK)
--       ... k ... (if we get something useful for next parser)
--   
--   
newtype Parser a Parser :: (forall r. (ParseError -> ParseStep r) -> (a -> ParseStep r) -> ParseStep r) -> Parser a [runParser] :: Parser a -> forall r. (ParseError -> ParseStep r) -> (a -> ParseStep r) -> ParseStep r () :: Text -> Parser a -> Parser a infixr 0 -- | Parse the complete input, without resupplying, return the rest bytes parse :: Parser a -> Bytes -> (Bytes, Either ParseError a) -- | Parse the complete input, without resupplying parse' :: Parser a -> Bytes -> Either ParseError a -- | Parse an input chunk parseChunk :: Parser a -> Bytes -> Result a -- | Type alias for a streaming parser, draw chunk from Monad m (with a -- initial chunk), return result in Either err x. type ParseChunks m chunk err x = m chunk -> chunk -> m (chunk, Either err x) -- | Run a parser with an initial input string, and a monadic action that -- can supply more input if needed. -- -- Note, once the monadic action return empty bytes, parsers will stop -- drawing more bytes (take it as endOfInput). parseChunks :: Monad m => Parser a -> ParseChunks m Bytes ParseError a -- | Finish parsing and fetch result, feed empty bytes if it's -- Partial result. finishParsing :: Result a -> (Bytes, Either ParseError a) -- | Run a parser and keep track of all the input chunks it consumes. Once -- it's finished, return the final result (always Success or -- Failure) and all consumed chunks. runAndKeepTrack :: Parser a -> Parser (Result a, [Bytes]) -- | Return both the result of a parse and the portion of the input that -- was consumed while it was being parsed. match :: Parser a -> Parser (Bytes, a) -- | Ensure that there are at least n bytes available. If not, the -- computation will escape with Partial. -- -- Since this parser is used in many other parsers, an extra error param -- is provide to attach custom error info. ensureN :: Int -> ParseError -> Parser () -- | Test whether all input has been consumed, i.e. there are no remaining -- undecoded bytes. Fail if not atEnd. endOfInput :: Parser () -- | Test whether all input has been consumed, i.e. there are no remaining -- undecoded bytes. atEnd :: Parser Bool -- | Decode a primitive type in host byte order. decodePrim :: forall a. Unaligned a => Parser a -- | big endianess wrapper newtype BE a BE :: a -> BE a [getBE] :: BE a -> a -- | little endianess wrapper newtype LE a LE :: a -> LE a [getLE] :: LE a -> a -- | Decode a primitive type in little endian. decodePrimLE :: forall a. Unaligned (LE a) => Parser a -- | Decode a primitive type in big endian. decodePrimBE :: forall a. Unaligned (BE a) => Parser a -- | A stateful scanner. The predicate consumes and transforms a state -- argument, and each transformed state is passed to successive -- invocations of the predicate on each byte of the input until one -- returns Nothing or the input ends. -- -- This parser does not fail. It will return an empty string if the -- predicate returns Nothing on the first byte of input. scan :: s -> (s -> Word8 -> Maybe s) -> Parser (Bytes, s) -- | Similar to scan, but working on Bytes chunks, The -- predicate consumes a Bytes chunk and transforms a state -- argument, and each transformed state is passed to successive -- invocations of the predicate on each chunk of the input until one -- chunk got splited to Right (V.Bytes, V.Bytes) or the input -- ends. scanChunks :: forall s. s -> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s) -- | Match any byte, to perform lookahead. Returns Nothing if end of -- input has been reached. Does not consume any input. peekMaybe :: Parser (Maybe Word8) -- | Match any byte, to perform lookahead. Does not consume any input, but -- will fail if end of input has been reached. peek :: Parser Word8 -- | The parser satisfy p succeeds for any byte for which the -- predicate p returns True. Returns the byte that is -- actually parsed. -- --
--   digit = satisfy isDigit
--       where isDigit w = w >= 48 && w <= 57
--   
satisfy :: (Word8 -> Bool) -> Parser Word8 -- | The parser satisfyWith f p transforms a byte, and succeeds if -- the predicate p returns True on the transformed value. -- The parser returns the transformed byte that was parsed. satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a -- | Return a byte, this is an alias to decodePrim Word8@. anyWord8 :: Parser Word8 -- | Match a specific byte. word8 :: Word8 -> Parser () -- | Take a byte and return as a 8bit char. anyChar8 :: Parser Char -- | Match a specific 8bit char. char8 :: Char -> Parser () -- | Skip a byte. skipWord8 :: Parser () -- | Match either a single newline byte '\n', or a carriage return -- followed by a newline byte "\r\n". endOfLine :: Parser () -- | skip N bytes. skip :: Int -> Parser () -- | Skip past input for as long as the predicate returns True. skipWhile :: (Word8 -> Bool) -> Parser () -- | Skip over white space using isSpace. skipSpaces :: Parser () take :: Int -> Parser Bytes -- | Similar to take, but requires the predicate to succeed on next -- N bytes of input, and take N bytes(no matter if N+1 byte satisfy -- predicate or not). takeN :: (Word8 -> Bool) -> Int -> Parser Bytes -- | Consume input as long as the predicate returns False or reach -- the end of input, and return the consumed input. takeTill :: (Word8 -> Bool) -> Parser Bytes -- | Consume input as long as the predicate returns True or reach -- the end of input, and return the consumed input. takeWhile :: (Word8 -> Bool) -> Parser Bytes -- | Similar to takeWhile, but requires the predicate to succeed on -- at least one byte of input: it will fail if the predicate never -- returns True or reach the end of input takeWhile1 :: (Word8 -> Bool) -> Parser Bytes -- | Take all the remaining input chunks and return as Bytes. takeRemaining :: Parser Bytes -- | bytes s parses a sequence of bytes that identically match -- s. bytes :: Bytes -> Parser () -- | Same as bytes but ignoring case. bytesCI :: Bytes -> Parser () -- | text s parses a sequence of UTF8 bytes that identically match -- s. text :: Text -> Parser () -- | Text version of fail. fail' :: Text -> Parser a instance GHC.Base.Functor Z.Data.Parser.Base.Parser instance GHC.Base.Applicative Z.Data.Parser.Base.Parser instance GHC.Base.Monad Z.Data.Parser.Base.Parser instance Control.Monad.Fail.MonadFail Z.Data.Parser.Base.Parser instance GHC.Base.MonadPlus Z.Data.Parser.Base.Parser instance GHC.Base.Alternative Z.Data.Parser.Base.Parser instance GHC.Base.Functor Z.Data.Parser.Base.Result instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Parser.Base.Result a) -- | Textual numeric parsers. module Z.Data.Parser.Numeric -- | Parse and decode an unsigned decimal number. -- -- Will fail in case of overflow. uint :: forall a. (Integral a, Bounded a) => Parser a -- | Parse a decimal number with an optional leading '+' or -- '-' sign character. -- -- This parser will fail if overflow happens. int :: forall a. (Integral a, Bounded a) => Parser a -- | Parser specifically optimized for Integer. integer :: Parser Integer -- | Same with uint, but sliently cast in case of overflow. uint_ :: forall a. (Integral a, Bounded a) => Parser a -- | Same with int, but sliently cast if overflow happens. int_ :: (Integral a, Bounded a) => Parser a -- | Take a single decimal digit and return as Int. digit :: Parser Int -- | Parse and decode an unsigned hex number, fail if input length is -- larger than (bit_size/4). The hex digits 'a' through -- 'f' may be upper or lower case. -- -- This parser does not accept a leading "0x" string, and -- consider sign bit part of the binary hex nibbles, e.g. -- --
--   >>> parse' hex "FF" == Right (-1 :: Int8)
--   
--   >>> parse' hex "7F" == Right (127 :: Int8)
--   
--   >>> parse' hex "7Ft" == Right (127 :: Int8)
--   
--   >>> parse' hex "7FF" == Left ["Z.Data.Parser.Numeric.hex","hex numeric number overflow"]
--   
hex :: forall a. (Integral a, FiniteBits a) => Parser a -- | Same with hex, but only take as many as (bit_size/4) bytes. -- --
--   >>> parse' hex "FF" == Right (-1 :: Int8)
--   
--   >>> parse' hex "7F" == Right (127 :: Int8)
--   
--   >>> parse' hex "7Ft" == Right (127 :: Int8)
--   
--   >>> parse' hex "7FF" == Right (127 :: Int8)
--   
hex' :: forall a. (Integral a, FiniteBits a) => Parser a -- | Same with hex, but silently cast in case of overflow. -- --
--   >>> parse' hex "FF" == Right (-1 :: Int8)
--   
--   >>> parse' hex "7F" == Right (127 :: Int8)
--   
--   >>> parse' hex "7Ft" == Right (127 :: Int8)
--   
--   >>> parse' hex "7FF" == Right (-1 :: Int8)
--   
hex_ :: (Integral a, Bits a) => Parser a -- | Parse a rational number. -- -- The syntax accepted by this parser is the same as for double. -- -- Note: this parser is not safe for use with inputs from -- untrusted sources. An input with a suitably large exponent such as -- "1e1000000000" will cause a huge Integer to be -- allocated, resulting in what is effectively a denial-of-service -- attack. -- -- In most cases, it is better to use double or scientific -- instead. rational :: Fractional a => Parser a -- | Parse a rational number and round to Float. -- -- Single precision version of double. float :: Parser Float -- | Parse a rational number and round to Double. -- -- This parser accepts an optional leading sign character, followed by at -- least one decimal digit. The syntax similar to that accepted by the -- read function, with the exception that a trailing '.' -- or 'e' not followed by a number is not consumed. -- -- Examples with behaviour identical to read: -- --
--   parse' double "3"     == ("", Right 3.0)
--   parse' double "3.1"   == ("", Right 3.1)
--   parse' double "3e4"   == ("", Right 30000.0)
--   parse' double "3.1e4" == ("", Right 31000.0)
--   
-- --
--   parse' double ".3"    == (".3", Left ParserError)
--   parse' double "e3"    == ("e3", Left ParserError)
--   
-- -- Examples of differences from read: -- --
--   parse' double "3.foo" == (".foo", Right 3.0)
--   parse' double "3e"    == ("e",    Right 3.0)
--   parse' double "-3e"   == ("e",    Right -3.0)
--   
-- -- This function does not accept string representations of "NaN" or -- "Infinity". double :: Parser Double -- | Parse a scientific number. -- -- The syntax accepted by this parser is the same as for double. scientific :: Parser Scientific -- | Parse a scientific number and convert to result using a user supply -- function. -- -- The syntax accepted by this parser is the same as for double. scientifically :: (Scientific -> a) -> Parser a -- | Parse a rational number. -- -- The syntax accepted by this parser is the same as for double'. -- -- Note: this parser is not safe for use with inputs from -- untrusted sources. An input with a suitably large exponent such as -- "1e1000000000" will cause a huge Integer to be -- allocated, resulting in what is effectively a denial-of-service -- attack. -- -- In most cases, it is better to use double' or -- scientific' instead. rational' :: Fractional a => Parser a -- | Parse a rational number and round to Float using stricter -- grammer. -- -- Single precision version of double'. float' :: Parser Float -- | More strict number parsing(rfc8259). -- -- scientific support parse 2314. and 21321exyz -- without eating extra dot or e via backtrack, this is not -- allowed in some strict grammer such as JSON, so we make an -- non-backtrack strict number parser separately using LL(1) lookahead. -- This parser also agree with read on extra dot or e handling: -- --
--   parse' double "3.foo" == Left ParseError
--   parse' double "3e"    == Left ParseError
--   
-- -- Leading zeros or + sign is also not allowed: -- --
--   parse' double "+3.14" == Left ParseError
--   parse' double "0014" == Left ParseError
--   
-- -- If you have a similar grammer, you can use this parser to save -- considerable time. -- --
--   number = [ minus ] int [ frac ] [ exp ]
--   decimal-point = %x2E       ; .
--   digit1-9 = %x31-39         ; 1-9
--   e = %x65 / %x45            ; e E
--   exp = e [ minus / plus ] 1*DIGIT
--   frac = decimal-point 1*DIGIT
--   
-- -- This function does not accept string representations of "NaN" or -- "Infinity". reference: -- https://tools.ietf.org/html/rfc8259#section-6 double' :: Parser Double -- | Parse a scientific number. -- -- The syntax accepted by this parser is the same as for double'. scientific' :: Parser Scientific -- | Parse a scientific number and convert to result using a user supply -- function. -- -- The syntax accepted by this parser is the same as for double'. scientifically' :: (Scientific -> a) -> Parser a -- | Convert A ASCII hex digit to Int value. w2iHex :: Integral a => Word8 -> a -- | Convert A ASCII decimal digit to Int value. w2iDec :: Integral a => Word8 -> a -- | decode hex digits sequence within an array. hexLoop :: forall a. (Integral a, Bits a) => a -> Bytes -> a -- | Decode digits sequence within an array. -- -- This function may overflow if result can't fit into type. decLoop :: Integral a => a -> Bytes -> a -- | decode digits sequence within an array. -- -- A fast version to decode Integer using machine word as much as -- possible. decLoopIntegerFast :: Bytes -> Integer -- | This module provide three stable sorting algorithms, which are: -- -- -- -- Sorting is always performed in ascending order. To reverse the order, -- either use XXSortBy or use Down, RadixDown -- newtypes. In general changing comparing functions can be done by -- creating auxiliary newtypes and Ord instances (make sure you -- inline instance's method for performence!). Or Radix instances -- in radixSort case, for example: -- --
--   data Foo = Foo { key :: Int16, ... }
--   
--   instance Radix Foo where
--       -- You should add INLINE pragmas to following methods
--       bucketSize = bucketSize . key
--       passes = passes . key
--       radixLSB = radixLSB . key
--       radix i = radix i . key
--       radixMSB = radixMSB . key
--   
module Z.Data.Vector.Sort -- | O(n*log(n)) Sort vector based on element's Ord instance -- with classic mergesort algorithm. -- -- This is a stable sort, During sorting two O(n) worker arrays are -- needed, one of them will be freezed into the result vector. The merge -- sort only begin at tile size larger than mergeTileSize, each -- tile will be sorted with insertSort, then iteratively merged -- into larger array, until all elements are sorted. mergeSort :: forall v a. (Vec v a, Ord a) => v a -> v a mergeSortBy :: forall v a. Vec v a => (a -> a -> Ordering) -> v a -> v a -- | The mergesort tile size, mergeTileSize = 8. mergeTileSize :: Int -- | O(n^2) Sort vector based on element's Ord instance with -- simple insertion-sort algorithm. -- -- This is a stable sort. O(n) extra space are needed, which will be -- freezed into result vector. insertSort :: (Vec v a, Ord a) => v a -> v a insertSortBy :: Vec v a => (a -> a -> Ordering) -> v a -> v a -- | The Down type allows you to reverse sort order conveniently. A -- value of type Down a contains a value of type -- a (represented as Down a). If a has -- an Ord instance associated with it then comparing two -- values thus wrapped will give you the opposite of their normal sort -- order. This is particularly useful when sorting in generalised list -- comprehensions, as in: then sortWith by Down x newtype Down a Down :: a -> Down a [getDown] :: Down a -> a -- | O(n) Sort vector based on element's Radix instance with -- radix-sort, (Least significant digit radix sorts variation). -- -- This is a stable sort, one or two extra O(n) worker array are need -- depend on how many passes shall be performed, and a -- bucketSize counting bucket are also needed. This sort -- algorithms performed extremly well on small byte size types such as -- Int8 or Word8, while on larger type, constant passes may -- render this algorithm not suitable for small vectors (turning point -- around 2^(2*passes)). radixSort :: forall v a. (Vec v a, Radix a) => v a -> v a -- | Types contain radixs, which can be inspected with radix during -- different passes. -- -- The default instances share a same bucketSize 256, which seems -- to be a good default. class Radix a -- | The size of an auxiliary array, i.e. the counting bucket bucketSize :: Radix a => a -> Int -- | The number of passes necessary to sort an array of es, it equals to -- the key's byte number. passes :: Radix a => a -> Int -- | The radix function used in the first pass, works on the least -- significant bit. radixLSB :: Radix a => a -> Int -- | The radix function parameterized by the current pass (0 < pass < -- passes e-1). radix :: Radix a => Int -> a -> Int -- | The radix function used in the last pass, works on the most -- significant bit. radixMSB :: Radix a => a -> Int -- | Similar to Down newtype for Ord, this newtype can -- inverse the order of a Radix instance when used in -- radixSort. newtype RadixDown a RadixDown :: a -> RadixDown a -- | merge duplicated adjacent element, prefer left element. -- -- Use this function on a sorted vector will have the same effects as -- nub. mergeDupAdjacent :: forall v a. (Vec v a, Eq a) => v a -> v a -- | Merge duplicated adjacent element, prefer left element. mergeDupAdjacentLeft :: forall v a. Vec v a => (a -> a -> Bool) -> v a -> v a -- | Merge duplicated adjacent element, prefer right element. mergeDupAdjacentRight :: forall v a. Vec v a => (a -> a -> Bool) -> v a -> v a -- | Merge duplicated adjacent element, based on a equality tester and a -- merger function. mergeDupAdjacentBy :: forall v a. Vec v a => (a -> a -> Bool) -> (a -> a -> a) -> v a -> v a instance Z.Data.Array.Unaligned.Unaligned a => Z.Data.Array.Unaligned.Unaligned (Z.Data.Vector.Sort.RadixDown a) instance Data.Primitive.Types.Prim a => Data.Primitive.Types.Prim (Z.Data.Vector.Sort.RadixDown a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Z.Data.Vector.Sort.RadixDown a) instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Vector.Sort.RadixDown a) instance Z.Data.Vector.Sort.Radix a => Z.Data.Vector.Sort.Radix (Z.Data.Vector.Sort.RadixDown a) instance Z.Data.Vector.Sort.Radix GHC.Int.Int8 instance Z.Data.Vector.Sort.Radix GHC.Types.Int instance Z.Data.Vector.Sort.Radix GHC.Int.Int16 instance Z.Data.Vector.Sort.Radix GHC.Int.Int32 instance Z.Data.Vector.Sort.Radix GHC.Int.Int64 instance Z.Data.Vector.Sort.Radix GHC.Word.Word8 instance Z.Data.Vector.Sort.Radix GHC.Types.Word instance Z.Data.Vector.Sort.Radix GHC.Word.Word16 instance Z.Data.Vector.Sort.Radix GHC.Word.Word32 instance Z.Data.Vector.Sort.Radix GHC.Word.Word64 -- | This module provides fast boxed and unboxed vector with unified -- interface. The API is similar to bytestring and vector. If you find -- missing functions, please report! -- -- Performance consideration: -- -- -- -- Since all functions works on more general types, inlining and -- specialization are the keys to achieve high performance, e.g. the -- performance gap between running in GHCi and compiled binary may be -- huge due to dictionary passing. If there're cases that GHC fail to -- specialized these functions, it should be regarded as a bug either in -- this library or GHC. module Z.Data.Vector -- | Typeclass for box and unboxed vectors, which are created by slicing -- arrays. -- -- Instead of providing a generalized vector with polymorphric array -- field, we use this typeclass so that instances use concrete array type -- can unpack their array payload. -- -- Vector types, e.g. Vector,PrimVector... are obivious -- instances, with O(1) toArr and fromArr, which convert -- slices to (array, offset, length) tuple back and forth. -- -- Array types can also be instances of this class, e.g. Array, -- PrimArray..., in this case toArr will always return -- offset 0 and whole array length, and fromArr is O(n) -- copyArr. class (Arr (IArray v) a) => Vec v a where { -- | Vector's immutable array type type family IArray v :: * -> *; } -- | Get underline array and slice range(offset and length). toArr :: Vec v a => v a -> (IArray v a, Int, Int) -- | Construct a Vec by slicing a whole array. arrVec :: Vec v a => IArray v a -> v a -- | O(1) Index vector's element. -- -- Return Nothing if index is out of bounds. indexMaybe :: Vec v a => v a -> Int -> Maybe a -- | O(1) Index array element. -- -- Throw IndexOutOfVectorRange if index outside of the vector. index :: (Vec v a, HasCallStack) => v a -> Int -> a -- | O(1) Index array element. -- -- Throw IndexOutOfVectorRange if index outside of the vector. indexM :: (Vec v a, Monad m, HasCallStack) => v a -> Int -> m a -- | O(n) Modify vector's element under given index. -- -- Throw IndexOutOfVectorRange if index outside of the vector. modifyIndex :: (Vec v a, HasCallStack) => v a -> Int -> (a -> a) -> v a -- | O(n) Modify vector's element under given index. -- -- Return original vector if index outside of the vector. modifyIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> (a -> a) -> v a -- | O(n) insert element to vector under given index. -- -- Throw IndexOutOfVectorRange if index outside of the vector. insertIndex :: (Vec v a, HasCallStack) => v a -> Int -> a -> v a -- | O(n) insert element to vector under given index. -- -- Return original vector if index outside of the vector. insertIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> a -> v a -- | O(n) Delete vector's element under given index. -- -- Throw IndexOutOfVectorRange if index outside of the vector. deleteIndex :: (Vec v a, HasCallStack) => v a -> Int -> v a -- | O(n) Delete vector's element under given index. -- -- Return original vector if index outside of the vector. deleteIndexMaybe :: (Vec v a, HasCallStack) => v a -> Int -> v a -- | Boxed vector data Vector a -- | Primitive vector data PrimVector a -- | Bytes is just primitive word8 vectors. type Bytes = PrimVector Word8 -- | O(n), pack an ASCII String, multi-bytes char WILL BE -- CHOPPED! packASCII :: String -> Bytes -- | O(1). The empty vector. empty :: Vec v a => v a -- | O(1). Single element vector. singleton :: Vec v a => a -> v a -- | O(n). Copy a vector from slice. copy :: Vec v a => v a -> v a -- | O(n) Convert a list into a vector -- -- Alias for packN defaultInitSize. pack :: Vec v a => [a] -> v a -- | O(n) Convert a list into a vector with an approximate size. -- -- If the list's length is large than the size given, we simply double -- the buffer size and continue building. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packN :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) Convert a list into a vector with given size. -- -- If the list's length is large than the size given, we drop the rest -- elements. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packN' :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) Alias for packRN defaultInitSize. packR :: Vec v a => [a] -> v a -- | O(n) packN in reverse order. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packRN :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) packN' in reverse order. -- --
--   >>> packRN' 3 [1,2,3,4,5]
--   
--   >>> [3,2,1]
--   
-- -- This function is a good consumer in the sense of build/foldr -- fusion. packRN' :: forall v a. Vec v a => Int -> [a] -> v a -- | O(n) Convert vector to a list. -- -- Unpacking is done lazily. i.e. we will retain reference to the array -- until all element are consumed. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpack :: Vec v a => v a -> [a] -- | O(n) Convert vector to a list in reverse order. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpackR :: Vec v a => v a -> [a] -- | O(1) Test whether a vector is empty. null :: Vec v a => v a -> Bool -- | O(1) The length of a vector. length :: Vec v a => v a -> Int -- | O(m+n) -- -- There's no need to guard empty vector because we guard them for you, -- so appending empty vectors are no-ops. append :: Vec v a => v a -> v a -> v a -- | Mapping between vectors (possiblely with two different vector types). -- -- NOTE, the result vector contain thunks in lifted Vector case, -- use map' if that's not desired. -- -- For PrimVector, map and map' are same, since -- PrimVectors never store thunks. map :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b -- | Mapping between vectors (possiblely with two different vector types). -- -- This is the strict version map. Note that the Functor instance -- of lifted Vector is defined with map to statisfy laws, -- which this strict version breaks (map' id arrayContainsBottom /= -- arrayContainsBottom ). map' :: forall u v a b. (Vec u a, Vec v b) => (a -> b) -> u a -> v b -- | Strict mapping with index. imap' :: forall u v a b. (Vec u a, Vec v b) => (Int -> a -> b) -> u a -> v b -- | Traverse vector and gather result in another vector, traverseVec :: (Vec v a, Vec u b, Applicative f) => (a -> f b) -> v a -> f (u b) -- | Traverse vector and gather result in another vector, traverseWithIndex :: (Vec v a, Vec u b, Applicative f) => (Int -> a -> f b) -> v a -> f (u b) -- | Traverse vector without gathering result. traverseVec_ :: (Vec v a, Applicative f) => (a -> f b) -> v a -> f () -- | Traverse vector with index. traverseWithIndex_ :: (Vec v a, Applicative f) => (Int -> a -> f b) -> v a -> f () -- | Strict left to right fold. foldl' :: Vec v a => (b -> a -> b) -> b -> v a -> b -- | Strict left to right fold with index. ifoldl' :: Vec v a => (b -> Int -> a -> b) -> b -> v a -> b -- | Strict left to right fold using first element as the initial value. -- -- Throw EmptyVector if vector is empty. foldl1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a -- | Strict left to right fold using first element as the initial value. -- return Nothing when vector is empty. foldl1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a -- | Strict right to left fold foldr' :: Vec v a => (a -> b -> b) -> b -> v a -> b -- | Strict right to left fold with index -- -- NOTE: the index is counting from 0, not backwards ifoldr' :: Vec v a => (Int -> a -> b -> b) -> b -> v a -> b -- | Strict right to left fold using last element as the initial value. -- -- Throw EmptyVector if vector is empty. foldr1' :: forall v a. (Vec v a, HasCallStack) => (a -> a -> a) -> v a -> a -- | Strict right to left fold using last element as the initial value, -- return Nothing when vector is empty. foldr1Maybe' :: forall v a. Vec v a => (a -> a -> a) -> v a -> Maybe a -- | O(n) Concatenate a list of vector. -- -- Note: concat have to force the entire list to filter out empty -- vector and calculate the length for allocation. concat :: forall v a. Vec v a => [v a] -> v a -- | Map a function over a vector and concatenate the results concatMap :: Vec v a => (a -> v a) -> v a -> v a -- | O(n) maximum returns the maximum value from a vector -- -- It's defined with foldl1', an EmptyVector exception will -- be thrown in the case of an empty vector. maximum :: (Vec v a, Ord a, HasCallStack) => v a -> a -- | O(n) minimum returns the minimum value from a -- vector -- -- An EmptyVector exception will be thrown in the case of an empty -- vector. minimum :: (Vec v a, Ord a, HasCallStack) => v a -> a -- | O(n) maximum returns the maximum value from a vector, -- return Nothing in the case of an empty vector. maximumMaybe :: (Vec v a, Ord a) => v a -> Maybe a -- | O(n) minimum returns the minimum value from a vector, -- return Nothing in the case of an empty vector. minimumMaybe :: (Vec v a, Ord a) => v a -> Maybe a -- | O(n) sum returns the sum value from a vector sum :: (Vec v a, Num a) => v a -> a -- | O(n) count returns count of an element from a -- vector count :: (Vec v a, Eq a) => a -> v a -> Int -- | O(n) product returns the product value from a vector product :: (Vec v a, Num a) => v a -> a -- | O(n) product returns the product value from a vector -- -- This function will shortcut on zero. Note this behavior change the -- semantics for lifted vector: product [1,0,undefined] /= product' -- [1,0,undefined]. product' :: (Vec v a, Num a, Eq a) => v a -> a -- | O(n) Applied to a predicate and a vector, all determines -- if all elements of the vector satisfy the predicate. all :: Vec v a => (a -> Bool) -> v a -> Bool -- | O(n) Applied to a predicate and a vector, any determines -- if any elements of the vector satisfy the predicate. any :: Vec v a => (a -> Bool) -> v a -> Bool -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a vector, -- passing an accumulating parameter from left to right, and returning a -- final value of this accumulator together with the new list. -- -- Note, this function will only force the result tuple, not the elements -- inside, to prevent creating thunks during mapAccumL, seq -- your accumulator and result with the result tuple. mapAccumL :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a vector, -- passing an accumulating parameter from right to left, and returning a -- final value of this accumulator together with the new vector. -- -- The same strictness property with mapAccumL applys to -- mapAccumR too. mapAccumR :: forall u v a b c. (Vec u b, Vec v c) => (a -> b -> (a, c)) -> a -> u b -> (a, v c) -- | O(n) replicate n x is a vector of length -- n with x the value of every element. -- -- Note: replicate will not force the element in boxed vector -- case. replicate :: Vec v a => Int -> a -> v a -- | O(n*m) cycleN a vector n times. cycleN :: forall v a. Vec v a => Int -> v a -> v a -- | O(n), where n is the length of the result. The -- unfoldr function is analogous to the List 'unfoldr'. -- unfoldr builds a vector from a seed value. The function takes -- the element and returns Nothing if it is done producing the -- vector or returns Just (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]
--   
unfoldr :: Vec u b => (a -> Maybe (b, a)) -> a -> u b -- | O(n) Like unfoldr, unfoldrN builds a vector from -- a seed value. However, the length of the result is limited by the -- first argument to unfoldrN. This function is more efficient -- than unfoldr when the maximum length of the result is known. -- -- The following equation relates unfoldrN and unfoldr: -- --
--   fst (unfoldrN n f s) == take n (unfoldr f s)
--   
unfoldrN :: forall v a b. Vec v b => Int -> (a -> Maybe (b, a)) -> a -> (v b, Maybe a) -- | O(n) cons is analogous to (:) for lists, but of -- different complexity, as it requires making a copy. cons :: Vec v a => a -> v a -> v a -- | O(n) Append a byte to the end of a vector snoc :: Vec v a => v a -> a -> v a -- | O(1) Extract the head and tail of a vector, return -- Nothing if it is empty. uncons :: Vec v a => v a -> Maybe (a, v a) -- | O(1) Extract the init and last of a vector, return -- Nothing if vector is empty. unsnoc :: Vec v a => v a -> Maybe (v a, a) -- | O(1) Extract the first element of a vector. headMaybe :: Vec v a => v a -> Maybe a -- | O(1) Extract the elements after the head of a vector. -- -- NOTE: tailMayEmpty return empty vector in the case of an empty -- vector. tailMayEmpty :: Vec v a => v a -> v a -- | O(1) Extract the last element of a vector. lastMaybe :: Vec v a => v a -> Maybe a -- | O(1) Extract the elements before of the last one. -- -- NOTE: initMayEmpty return empty vector in the case of an empty -- vector. initMayEmpty :: Vec v a => v a -> v a -- | O(1) Extract the first element of a vector. -- -- Throw EmptyVector if vector is empty. head :: (Vec v a, HasCallStack) => v a -> a -- | O(1) Extract the elements after the head of a vector. -- -- Throw EmptyVector if vector is empty. tail :: (Vec v a, HasCallStack) => v a -> v a -- | O(1) Extract the last element of a vector. -- -- Throw EmptyVector if vector is empty. last :: (Vec v a, HasCallStack) => v a -> a -- | O(1) Extract the elements before of the last one. -- -- Throw EmptyVector if vector is empty. init :: (Vec v a, HasCallStack) => v a -> v a -- | O(n) Return all initial segments of the given vector, empty -- first. inits :: Vec v a => v a -> [v a] -- | O(n) Return all final segments of the given vector, whole -- vector first. tails :: Vec v a => v a -> [v a] -- | O(1) take n, applied to a vector xs, -- returns the prefix of xs of length n, or xs -- itself if n > length xs. take :: Vec v a => Int -> v a -> v a -- | O(1) drop n xs returns the suffix of -- xs after the first n elements, or [] if -- n > length xs. drop :: Vec v a => Int -> v a -> v a -- | O(1) takeR n, applied to a vector xs, -- returns the suffix of xs of length n, or xs -- itself if n > length xs. takeR :: Vec v a => Int -> v a -> v a -- | O(1) dropR n xs returns the prefix of -- xs before the last n elements, or [] if -- n > length xs. dropR :: Vec v a => Int -> v a -> v a -- | O(1) Extract a sub-range vector with give start index and -- length. -- -- This function is a total function just like 'takedrop', -- indexlength exceeds range will be ingored, e.g. -- --
--   slice 1 3 "hello"   == "ell"
--   slice -1 -1 "hello" == ""
--   slice -2 2 "hello"  == ""
--   slice 2 10 "hello"  == "llo"
--   
-- -- This holds for all x y: slice x y vs == drop x . take (x+y) -- vs slice :: Vec v a => Int -> Int -> v a -> v a -- | O(1) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Vec v a => Int -> v a -> (v a, v a) -- | O(n) Applied to a predicate p and a vector -- vs, returns the longest prefix (possibly empty) of -- vs of elements that satisfy p. takeWhile :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Applied to a predicate p and a vector -- vs, returns the longest suffix (possibly empty) of -- vs of elements that satisfy p. takeWhileR :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Applied to a predicate p and a vector -- vs, returns the suffix (possibly empty) remaining after -- takeWhile p vs. dropWhile :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Applied to a predicate p and a vector -- vs, returns the prefix (possibly empty) remaining before -- takeWhileR p vs. dropWhileR :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) dropAround f = dropWhile f . dropWhileR f dropAround :: Vec v a => (a -> Bool) -> v a -> v a -- | O(n) Split the vector into the longest prefix of elements that -- do not satisfy the predicate and the rest without copying. -- -- break (==x) will be rewritten using a memchr. break :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | O(n) Split the vector into the longest prefix of elements that -- satisfy the predicate and the rest without copying. -- -- span (/=x) will be rewritten using a memchr. span :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | breakR behaves like break but from the end of the -- vector. -- --
--   breakR p == spanR (not.p)
--   
breakR :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | spanR behaves like span but from the end of the vector. spanR :: Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | Break a vector on a subvector, returning a pair of the part of the -- vector prior to the match, and the rest of the vector, e.g. -- --
--   break "wor" "hello, world" = ("hello, ", "world")
--   
breakOn :: (Vec v a, Eq a) => v a -> v a -> (v a, v a) group :: (Vec v a, Eq a) => v a -> [v a] groupBy :: forall v a. Vec v a => (a -> a -> Bool) -> v a -> [v a] -- | O(n) The stripPrefix function takes two vectors and -- returns Just the remainder of the second iff the first is its -- prefix, and otherwise Nothing. stripPrefix :: (Vec v a, Eq (v a)) => v a -> v a -> Maybe (v a) -- | O(n) The stripSuffix function takes two vectors and returns -- Just the remainder of the second iff the first is its suffix, and -- otherwise Nothing. stripSuffix :: (Vec v a, Eq (v a)) => v a -> v a -> Maybe (v a) -- | O(n) Break a vector into pieces separated by the delimiter -- element 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 -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- NOTE, this function behavior different with bytestring's. see -- #56. split :: (Vec v a, Eq a) => a -> v a -> [v a] -- | O(n) Splits a vector 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. -- --
--   splitWith (=='a') "aabbaca" == ["","","bb","c",""]
--   splitWith (=='a') []        == [""]
--   
-- -- NOTE, this function behavior different with bytestring's. see -- #56. splitWith :: Vec v a => (a -> Bool) -> v a -> [v a] -- | O(m+n) Break haystack into pieces separated by needle. -- -- Note: An empty needle will essentially split haystack element by -- element. -- -- Examples: -- --
--   >>> splitOn "\r\n" "a\r\nb\r\nd\r\ne"
--   ["a","b","d","e"]
--   
-- --
--   >>> splitOn "aaa"  "aaaXaaaXaaaXaaa"
--   ["","X","X","X",""]
--   
-- --
--   >>> splitOn "x"  "x"
--   ["",""]
--   
-- -- and -- --
--   intercalate s . splitOn s         == id
--   splitOn (singleton c)             == split (==c)
--   
splitOn :: (Vec v a, Eq a) => v a -> v a -> [v a] -- | The isPrefix function returns True if the first -- argument is a prefix of the second. isPrefixOf :: forall v a. (Vec v a, Eq (v a)) => v a -> v a -> Bool -- | O(n) The isSuffixOf function takes two vectors and -- returns True if the first is a suffix of the second. isSuffixOf :: forall v a. (Vec v a, Eq (v a)) => v a -> v a -> Bool -- | Check whether one vector is a subvector of another. -- -- needle isInfixOf haystack === null haystack || indices -- needle haystake /= []. isInfixOf :: (Vec v a, Eq a) => v a -> v a -> Bool -- | O(n) Find the longest non-empty common prefix of two strings -- and return it, along with the suffixes of each string at which they no -- longer match. e.g. -- --
--   >>> commonPrefix "foobar" "fooquux"
--   ("foo","bar","quux")
--   
-- --
--   >>> commonPrefix "veeble" "fetzer"
--   ("","veeble","fetzer")
--   
commonPrefix :: (Vec v a, Eq a) => v a -> v a -> (v a, v a, v a) -- | O(n) Breaks a Bytes up into a list of words, delimited -- by ascii space. words :: Bytes -> [Bytes] -- | O(n) Breaks a Bytes up into a list of lines, delimited -- by ascii n. lines :: Bytes -> [Bytes] -- | O(n) Joins words with ascii space. unwords :: [Bytes] -> Bytes -- | O(n) Joins lines with ascii n. -- -- NOTE: This functions is different from unlines, it DOES NOT add -- a trailing n. unlines :: [Bytes] -> Bytes -- | Add padding to the left so that the whole vector's length is at least -- n. padLeft :: Vec v a => Int -> a -> v a -> v a -- | Add padding to the right so that the whole vector's length is at least -- n. padRight :: Vec v a => Int -> a -> v a -> v a -- | O(n) reverse vs efficiently returns the -- elements of xs in reverse order. reverse :: forall v a. Vec v a => v a -> v a -- | O(n) The intersperse function takes an element and a -- vector and `intersperses' that element between the elements of the -- vector. It is analogous to the intersperse function on Lists. intersperse :: forall v a. Vec v a => a -> v a -> v a -- | O(n) The intercalate function takes a vector and a list -- of vectors and concatenates the list after interspersing the first -- argument between each element of the list. -- -- Note: intercalate will force the entire vector list. intercalate :: Vec v a => v a -> [v a] -> v a -- | O(n) An efficient way to join vector with an element. intercalateElem :: forall v a. Vec v a => a -> [v a] -> v a -- | The transpose function transposes the rows and columns of its -- vector argument. transpose :: Vec v a => [v a] -> [v a] -- | zipWith' zip two vector with a zipping function. -- -- For example, zipWith (+) is applied to two vector to -- produce a vector of corresponding sums, the result will be evaluated -- strictly. zipWith' :: forall v a u b w c. (Vec v a, Vec u b, Vec w c) => (a -> b -> c) -> v a -> u b -> w c -- | unzipWith' disassemble a vector with a disassembling function, -- -- The results inside tuple will be evaluated strictly. unzipWith' :: forall v a u b w c. (Vec v a, Vec u b, Vec w c) => (a -> (b, c)) -> v a -> (u b, w c) -- | scanl' is similar to foldl, 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 -- --
--   lastM (scanl' f z xs) == Just (foldl f z xs).
--   
scanl' :: forall v u a b. (Vec v a, Vec u b) => (b -> a -> b) -> b -> v a -> u b -- | 'scanl1'' is a variant of scanl that has no starting value -- argument. -- --
--   scanl1' f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   scanl1' f [] == []
--   
scanl1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a -- | scanr' is the right-to-left dual of scanl'. scanr' :: forall v u a b. (Vec v a, Vec u b) => (a -> b -> b) -> b -> v a -> u b -- | scanr1' is a variant of scanr that has no starting value -- argument. scanr1' :: forall v a. Vec v a => (a -> a -> a) -> v a -> v a -- | O(n) elem test if given element is in given vector. elem :: (Vec v a, Eq a) => a -> v a -> Bool -- | O(n) 'not . elem' notElem :: (Vec v a, Eq a) => a -> v a -> Bool -- | O(n) The elemIndex function returns the index of the -- first element in the given vector which is equal to the query element, -- or Nothing if there is no such element. elemIndex :: (Vec v a, Eq a) => a -> v a -> Maybe Int -- | O(n) find the first index and element matching the predicate in -- a vector from left to right, if there isn't one, return (length of the -- vector, Nothing). find :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a) -- | O(n) Find the first index and element matching the predicate in -- a vector from right to left, if there isn't one, return '(-1, -- Nothing)'. findR :: Vec v a => (a -> Bool) -> v a -> (Int, Maybe a) -- | The findIndex function takes a predicate and a vector and -- returns the index of the first element in the vector satisfying the -- predicate. findIndices :: Vec v a => (a -> Bool) -> v a -> [Int] -- | O(n) The elemIndices function extends elemIndex, -- by returning the indices of all elements equal to the query element, -- in ascending order. elemIndices :: (Vec v a, Eq a) => a -> v a -> [Int] -- | O(n) filter, applied to a predicate and a vector, -- returns a vector containing those elements that satisfy the predicate. filter :: forall v a. Vec v a => (a -> Bool) -> v a -> v a -- | O(n) The partition function takes a predicate, a vector, -- returns a pair of vector with elements which do and do not satisfy the -- predicate, respectively; i.e., -- --
--   partition p vs == (filter p vs, filter (not . p) vs)
--   
partition :: forall v a. Vec v a => (a -> Bool) -> v a -> (v a, v a) -- | O(n+m) Find the offsets of all indices (possibly overlapping) -- of needle within haystack using KMP algorithm. -- -- The KMP algorithm need pre-calculate a shift table in O(m) time -- and space, the worst case time complexity is O(n+m). Partial -- apply this function to reuse pre-calculated table between same -- needles. -- -- Chunked input are support via partial match argument, if set we will -- return an extra negative index in case of partial match at the end of -- input chunk, e.g. -- --
--   indicesOverlapping [ascii|ada|]  [ascii|adadad|] True == [0,2,-2]
--   
-- -- Where -2 is the length of the partial match part ad -- 's negation. -- -- If an empty pattern is supplied, we will return every possible index -- of haystack, e.g. -- --
--   indicesOverlapping "" "abc" = [0,1,2]
--   
-- -- References: -- -- indicesOverlapping :: (Vec v a, Eq a) => v a -> v a -> Bool -> [Int] -- | O(n+m) Find the offsets of all non-overlapping indices of -- needle within haystack using KMP algorithm. -- -- If an empty pattern is supplied, we will return every possible index -- of haystack, e.g. -- --
--   indicesOverlapping "" "abc" = [0,1,2]
--   
indices :: (Vec v a, Eq a) => v a -> v a -> Bool -> [Int] -- | O(n*log(n)) Sort vector based on element's Ord instance -- with classic mergesort algorithm. -- -- This is a stable sort, During sorting two O(n) worker arrays are -- needed, one of them will be freezed into the result vector. The merge -- sort only begin at tile size larger than mergeTileSize, each -- tile will be sorted with insertSort, then iteratively merged -- into larger array, until all elements are sorted. mergeSort :: forall v a. (Vec v a, Ord a) => v a -> v a mergeSortBy :: forall v a. Vec v a => (a -> a -> Ordering) -> v a -> v a -- | The mergesort tile size, mergeTileSize = 8. mergeTileSize :: Int -- | O(n^2) Sort vector based on element's Ord instance with -- simple insertion-sort algorithm. -- -- This is a stable sort. O(n) extra space are needed, which will be -- freezed into result vector. insertSort :: (Vec v a, Ord a) => v a -> v a insertSortBy :: Vec v a => (a -> a -> Ordering) -> v a -> v a -- | The Down type allows you to reverse sort order conveniently. A -- value of type Down a contains a value of type -- a (represented as Down a). If a has -- an Ord instance associated with it then comparing two -- values thus wrapped will give you the opposite of their normal sort -- order. This is particularly useful when sorting in generalised list -- comprehensions, as in: then sortWith by Down x newtype Down a Down :: a -> Down a [getDown] :: Down a -> a -- | O(n) Sort vector based on element's Radix instance with -- radix-sort, (Least significant digit radix sorts variation). -- -- This is a stable sort, one or two extra O(n) worker array are need -- depend on how many passes shall be performed, and a -- bucketSize counting bucket are also needed. This sort -- algorithms performed extremly well on small byte size types such as -- Int8 or Word8, while on larger type, constant passes may -- render this algorithm not suitable for small vectors (turning point -- around 2^(2*passes)). radixSort :: forall v a. (Vec v a, Radix a) => v a -> v a -- | Types contain radixs, which can be inspected with radix during -- different passes. -- -- The default instances share a same bucketSize 256, which seems -- to be a good default. class Radix a -- | The size of an auxiliary array, i.e. the counting bucket bucketSize :: Radix a => a -> Int -- | The number of passes necessary to sort an array of es, it equals to -- the key's byte number. passes :: Radix a => a -> Int -- | The radix function used in the first pass, works on the least -- significant bit. radixLSB :: Radix a => a -> Int -- | The radix function parameterized by the current pass (0 < pass < -- passes e-1). radix :: Radix a => Int -> a -> Int -- | The radix function used in the last pass, works on the most -- significant bit. radixMSB :: Radix a => a -> Int -- | Similar to Down newtype for Ord, this newtype can -- inverse the order of a Radix instance when used in -- radixSort. newtype RadixDown a RadixDown :: a -> RadixDown a vecASCII :: QuasiQuoter vecW8 :: QuasiQuoter vecW16 :: QuasiQuoter vecW32 :: QuasiQuoter vecW64 :: QuasiQuoter vecWord :: QuasiQuoter vecI8 :: QuasiQuoter vecI16 :: QuasiQuoter vecI32 :: QuasiQuoter vecI64 :: QuasiQuoter vecInt :: QuasiQuoter -- | Pair type to help GHC unpack in some loops, useful when write fast -- folds. data IPair a IPair :: {-# UNPACK #-} !Int -> a -> IPair a [ifst] :: IPair a -> {-# UNPACK #-} !Int [isnd] :: IPair a -> a -- | Unlike Functor instance, this mapping evaluate value inside -- IPair strictly. mapIPair' :: (a -> b) -> IPair a -> IPair b -- | defaultInitSize = 30, used as initialize size when packing -- list of unknown size. defaultInitSize :: Int -- | The memory management overhead. Currently this is tuned for GHC only. chunkOverhead :: Int -- | The chunk size used for I/O. Currently set to 16k - -- chunkOverhead defaultChunkSize :: Int -- | The recommended chunk size. Currently set to 4k - -- chunkOverhead. smallChunkSize :: Int -- | All exception can be throw by using Vec. data VectorException IndexOutOfVectorRange :: {-# UNPACK #-} !Int -> CallStack -> VectorException EmptyVector :: CallStack -> VectorException -- | Cast between vectors castVector :: (Vec v a, Cast a b) => v a -> v b -- | Parsers for parsing dates and times. module Z.Data.Parser.Time -- | Parse a date of the form [+,-]YYYY-MM-DD. day :: Parser Day -- | Parse a date and time, of the form YYYY-MM-DD -- HH:MM[:SS[.SSS]]. The space may be replaced with a T. -- The number of seconds is optional and may be followed by a fractional -- component. localTime :: Parser LocalTime -- | Parse a time of the form HH:MM[:SS[.SSS]]. timeOfDay :: Parser TimeOfDay -- | Parse a time zone, and return Nothing if the offset from UTC is -- zero. (This makes some speedups possible.) timeZone :: Parser (Maybe TimeZone) -- | Behaves as zonedTime, but converts any time zone offset into a -- -- UTC time. utcTime :: Parser UTCTime -- | Parse a date with time zone info. Acceptable formats: -- --
--   YYYY-MM-DD HH:MM Z
--   YYYY-MM-DD HH:MM:SS Z
--   YYYY-MM-DD HH:MM:SS.SSS Z
--   
-- -- The first space may instead be a T, and the second space is -- optional. The Z represents UTC. The Z may be -- replaced with a time zone offset of the form +0000 or -- -08:00, where the first two digits are hours, the : -- is optional and the second two digits (also optional) are minutes. zonedTime :: Parser ZonedTime -- | This module provide a simple resumable Parser, which is -- suitable for binary protocol and simple textual protocol parsing. Both -- binary parsers (decodePrim ,etc) and textual parsers are -- provided, and they all work on Bytes. -- -- You can use Alternative instance to do backtracking, each -- branch will either succeed and may consume some input, or fail without -- consume anything. It's recommend to use peek or -- peekMaybe to avoid backtracking if possible to get high -- performance. -- -- Error message can be attached using <?>, which have very -- small overhead, so it's recommended to attach a message in front of a -- composed parser like xPacket = "Foo.Bar.xPacket" ? do -- ..., following is an example message when parsing an integer -- failed: -- --
--   >parse int "foo"
--   ([102,111,111],Left ["Z.Data.Parser.Numeric.int","Std.Data.Parser.Base.takeWhile1: no satisfied byte"])
--   -- It's easy to see we're trying to match a leading sign or digit here
--   
-- -- Use parser-combinators to get combinators based on -- Applicative or Monad instance, such as -- manyTill, sepBy, etc. module Z.Data.Parser -- | Simple parsing result, that represent respectively: -- -- data Result a Success :: a -> !Bytes -> Result a Failure :: ParseError -> !Bytes -> Result a Partial :: ParseStep a -> Result a -- | Type alias for error message type ParseError = [Text] -- | Simple CPSed parser -- -- A parser takes a failure continuation, and a success one, while the -- success continuation is usually composed by Monad instance, the -- failure one is more like a reader part, which can be modified via -- <?>. If you build parsers from ground, a pattern like -- this can be used: -- --
--   xxParser = do
--     ensureN errMsg ...            -- make sure we have some bytes
--     Parser $  kf k inp ->        -- fail continuation, success continuation and input
--       ...
--       ... kf errMsg (if input not OK)
--       ... k ... (if we get something useful for next parser)
--   
--   
data Parser a () :: Text -> Parser a -> Parser a infixr 0 -- | Parse the complete input, without resupplying, return the rest bytes parse :: Parser a -> Bytes -> (Bytes, Either ParseError a) -- | Parse the complete input, without resupplying parse' :: Parser a -> Bytes -> Either ParseError a -- | Parse an input chunk parseChunk :: Parser a -> Bytes -> Result a -- | Type alias for a streaming parser, draw chunk from Monad m (with a -- initial chunk), return result in Either err x. type ParseChunks m chunk err x = m chunk -> chunk -> m (chunk, Either err x) -- | Run a parser with an initial input string, and a monadic action that -- can supply more input if needed. -- -- Note, once the monadic action return empty bytes, parsers will stop -- drawing more bytes (take it as endOfInput). parseChunks :: Monad m => Parser a -> ParseChunks m Bytes ParseError a -- | Finish parsing and fetch result, feed empty bytes if it's -- Partial result. finishParsing :: Result a -> (Bytes, Either ParseError a) -- | Run a parser and keep track of all the input chunks it consumes. Once -- it's finished, return the final result (always Success or -- Failure) and all consumed chunks. runAndKeepTrack :: Parser a -> Parser (Result a, [Bytes]) -- | Return both the result of a parse and the portion of the input that -- was consumed while it was being parsed. match :: Parser a -> Parser (Bytes, a) -- | Ensure that there are at least n bytes available. If not, the -- computation will escape with Partial. -- -- Since this parser is used in many other parsers, an extra error param -- is provide to attach custom error info. ensureN :: Int -> ParseError -> Parser () -- | Test whether all input has been consumed, i.e. there are no remaining -- undecoded bytes. Fail if not atEnd. endOfInput :: Parser () -- | Test whether all input has been consumed, i.e. there are no remaining -- undecoded bytes. atEnd :: Parser Bool -- | Decode a primitive type in host byte order. decodePrim :: forall a. Unaligned a => Parser a -- | big endianess wrapper newtype BE a BE :: a -> BE a [getBE] :: BE a -> a -- | little endianess wrapper newtype LE a LE :: a -> LE a [getLE] :: LE a -> a -- | Decode a primitive type in little endian. decodePrimLE :: forall a. Unaligned (LE a) => Parser a -- | Decode a primitive type in big endian. decodePrimBE :: forall a. Unaligned (BE a) => Parser a -- | A stateful scanner. The predicate consumes and transforms a state -- argument, and each transformed state is passed to successive -- invocations of the predicate on each byte of the input until one -- returns Nothing or the input ends. -- -- This parser does not fail. It will return an empty string if the -- predicate returns Nothing on the first byte of input. scan :: s -> (s -> Word8 -> Maybe s) -> Parser (Bytes, s) -- | Similar to scan, but working on Bytes chunks, The -- predicate consumes a Bytes chunk and transforms a state -- argument, and each transformed state is passed to successive -- invocations of the predicate on each chunk of the input until one -- chunk got splited to Right (V.Bytes, V.Bytes) or the input -- ends. scanChunks :: forall s. s -> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s) -- | Match any byte, to perform lookahead. Returns Nothing if end of -- input has been reached. Does not consume any input. peekMaybe :: Parser (Maybe Word8) -- | Match any byte, to perform lookahead. Does not consume any input, but -- will fail if end of input has been reached. peek :: Parser Word8 -- | The parser satisfy p succeeds for any byte for which the -- predicate p returns True. Returns the byte that is -- actually parsed. -- --
--   digit = satisfy isDigit
--       where isDigit w = w >= 48 && w <= 57
--   
satisfy :: (Word8 -> Bool) -> Parser Word8 -- | The parser satisfyWith f p transforms a byte, and succeeds if -- the predicate p returns True on the transformed value. -- The parser returns the transformed byte that was parsed. satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a -- | Return a byte, this is an alias to decodePrim Word8@. anyWord8 :: Parser Word8 -- | Match a specific byte. word8 :: Word8 -> Parser () -- | Take a byte and return as a 8bit char. anyChar8 :: Parser Char -- | Match a specific 8bit char. char8 :: Char -> Parser () -- | Skip a byte. skipWord8 :: Parser () -- | Match either a single newline byte '\n', or a carriage return -- followed by a newline byte "\r\n". endOfLine :: Parser () -- | skip N bytes. skip :: Int -> Parser () -- | Skip past input for as long as the predicate returns True. skipWhile :: (Word8 -> Bool) -> Parser () -- | Skip over white space using isSpace. skipSpaces :: Parser () take :: Int -> Parser Bytes -- | Consume input as long as the predicate returns False or reach -- the end of input, and return the consumed input. takeTill :: (Word8 -> Bool) -> Parser Bytes -- | Consume input as long as the predicate returns True or reach -- the end of input, and return the consumed input. takeWhile :: (Word8 -> Bool) -> Parser Bytes -- | Similar to takeWhile, but requires the predicate to succeed on -- at least one byte of input: it will fail if the predicate never -- returns True or reach the end of input takeWhile1 :: (Word8 -> Bool) -> Parser Bytes -- | Take all the remaining input chunks and return as Bytes. takeRemaining :: Parser Bytes -- | bytes s parses a sequence of bytes that identically match -- s. bytes :: Bytes -> Parser () -- | Same as bytes but ignoring case. bytesCI :: Bytes -> Parser () -- | text s parses a sequence of UTF8 bytes that identically match -- s. text :: Text -> Parser () -- | Parse and decode an unsigned decimal number. -- -- Will fail in case of overflow. uint :: forall a. (Integral a, Bounded a) => Parser a -- | Parse a decimal number with an optional leading '+' or -- '-' sign character. -- -- This parser will fail if overflow happens. int :: forall a. (Integral a, Bounded a) => Parser a -- | Parser specifically optimized for Integer. integer :: Parser Integer -- | Same with uint, but sliently cast in case of overflow. uint_ :: forall a. (Integral a, Bounded a) => Parser a -- | Same with int, but sliently cast if overflow happens. int_ :: (Integral a, Bounded a) => Parser a -- | Take a single decimal digit and return as Int. digit :: Parser Int -- | Parse and decode an unsigned hex number, fail if input length is -- larger than (bit_size/4). The hex digits 'a' through -- 'f' may be upper or lower case. -- -- This parser does not accept a leading "0x" string, and -- consider sign bit part of the binary hex nibbles, e.g. -- --
--   >>> parse' hex "FF" == Right (-1 :: Int8)
--   
--   >>> parse' hex "7F" == Right (127 :: Int8)
--   
--   >>> parse' hex "7Ft" == Right (127 :: Int8)
--   
--   >>> parse' hex "7FF" == Left ["Z.Data.Parser.Numeric.hex","hex numeric number overflow"]
--   
hex :: forall a. (Integral a, FiniteBits a) => Parser a -- | Same with hex, but only take as many as (bit_size/4) bytes. -- --
--   >>> parse' hex "FF" == Right (-1 :: Int8)
--   
--   >>> parse' hex "7F" == Right (127 :: Int8)
--   
--   >>> parse' hex "7Ft" == Right (127 :: Int8)
--   
--   >>> parse' hex "7FF" == Right (127 :: Int8)
--   
hex' :: forall a. (Integral a, FiniteBits a) => Parser a -- | Same with hex, but silently cast in case of overflow. -- --
--   >>> parse' hex "FF" == Right (-1 :: Int8)
--   
--   >>> parse' hex "7F" == Right (127 :: Int8)
--   
--   >>> parse' hex "7Ft" == Right (127 :: Int8)
--   
--   >>> parse' hex "7FF" == Right (-1 :: Int8)
--   
hex_ :: (Integral a, Bits a) => Parser a -- | Parse a rational number. -- -- The syntax accepted by this parser is the same as for double. -- -- Note: this parser is not safe for use with inputs from -- untrusted sources. An input with a suitably large exponent such as -- "1e1000000000" will cause a huge Integer to be -- allocated, resulting in what is effectively a denial-of-service -- attack. -- -- In most cases, it is better to use double or scientific -- instead. rational :: Fractional a => Parser a -- | Parse a rational number and round to Float. -- -- Single precision version of double. float :: Parser Float -- | Parse a rational number and round to Double. -- -- This parser accepts an optional leading sign character, followed by at -- least one decimal digit. The syntax similar to that accepted by the -- read function, with the exception that a trailing '.' -- or 'e' not followed by a number is not consumed. -- -- Examples with behaviour identical to read: -- --
--   parse' double "3"     == ("", Right 3.0)
--   parse' double "3.1"   == ("", Right 3.1)
--   parse' double "3e4"   == ("", Right 30000.0)
--   parse' double "3.1e4" == ("", Right 31000.0)
--   
-- --
--   parse' double ".3"    == (".3", Left ParserError)
--   parse' double "e3"    == ("e3", Left ParserError)
--   
-- -- Examples of differences from read: -- --
--   parse' double "3.foo" == (".foo", Right 3.0)
--   parse' double "3e"    == ("e",    Right 3.0)
--   parse' double "-3e"   == ("e",    Right -3.0)
--   
-- -- This function does not accept string representations of "NaN" or -- "Infinity". double :: Parser Double -- | Parse a scientific number. -- -- The syntax accepted by this parser is the same as for double. scientific :: Parser Scientific -- | Parse a scientific number and convert to result using a user supply -- function. -- -- The syntax accepted by this parser is the same as for double. scientifically :: (Scientific -> a) -> Parser a -- | Parse a rational number. -- -- The syntax accepted by this parser is the same as for double'. -- -- Note: this parser is not safe for use with inputs from -- untrusted sources. An input with a suitably large exponent such as -- "1e1000000000" will cause a huge Integer to be -- allocated, resulting in what is effectively a denial-of-service -- attack. -- -- In most cases, it is better to use double' or -- scientific' instead. rational' :: Fractional a => Parser a -- | Parse a rational number and round to Float using stricter -- grammer. -- -- Single precision version of double'. float' :: Parser Float -- | More strict number parsing(rfc8259). -- -- scientific support parse 2314. and 21321exyz -- without eating extra dot or e via backtrack, this is not -- allowed in some strict grammer such as JSON, so we make an -- non-backtrack strict number parser separately using LL(1) lookahead. -- This parser also agree with read on extra dot or e handling: -- --
--   parse' double "3.foo" == Left ParseError
--   parse' double "3e"    == Left ParseError
--   
-- -- Leading zeros or + sign is also not allowed: -- --
--   parse' double "+3.14" == Left ParseError
--   parse' double "0014" == Left ParseError
--   
-- -- If you have a similar grammer, you can use this parser to save -- considerable time. -- --
--   number = [ minus ] int [ frac ] [ exp ]
--   decimal-point = %x2E       ; .
--   digit1-9 = %x31-39         ; 1-9
--   e = %x65 / %x45            ; e E
--   exp = e [ minus / plus ] 1*DIGIT
--   frac = decimal-point 1*DIGIT
--   
-- -- This function does not accept string representations of "NaN" or -- "Infinity". reference: -- https://tools.ietf.org/html/rfc8259#section-6 double' :: Parser Double -- | Parse a scientific number. -- -- The syntax accepted by this parser is the same as for double'. scientific' :: Parser Scientific -- | Parse a scientific number and convert to result using a user supply -- function. -- -- The syntax accepted by this parser is the same as for double'. scientifically' :: (Scientific -> a) -> Parser a -- | Parse a date of the form [+,-]YYYY-MM-DD. day :: Parser Day -- | Parse a date and time, of the form YYYY-MM-DD -- HH:MM[:SS[.SSS]]. The space may be replaced with a T. -- The number of seconds is optional and may be followed by a fractional -- component. localTime :: Parser LocalTime -- | Parse a time of the form HH:MM[:SS[.SSS]]. timeOfDay :: Parser TimeOfDay -- | Parse a time zone, and return Nothing if the offset from UTC is -- zero. (This makes some speedups possible.) timeZone :: Parser (Maybe TimeZone) -- | Behaves as zonedTime, but converts any time zone offset into a -- -- UTC time. utcTime :: Parser UTCTime -- | Parse a date with time zone info. Acceptable formats: -- --
--   YYYY-MM-DD HH:MM Z
--   YYYY-MM-DD HH:MM:SS Z
--   YYYY-MM-DD HH:MM:SS.SSS Z
--   
-- -- The first space may instead be a T, and the second space is -- optional. The Z represents UTC. The Z may be -- replaced with a time zone offset of the form +0000 or -- -08:00, where the first two digits are hours, the : -- is optional and the second two digits (also optional) are minutes. zonedTime :: Parser ZonedTime -- | Text version of fail. fail' :: Text -> Parser a -- | This module provide functions for using PrimArray and -- PrimVector with GHC FFI(Foreign function interface), Some -- functions are designed to be used with UnliftedFFITypes -- extension. -- -- GHC runtime is garbaged collected, there're two types of primitive -- array in GHC, with the objective to minimize overall memory management -- cost: -- -- -- -- Beside the pinned/unpinned difference, we have two types of -- FFI calls in GHC: -- -- -- -- Base on above analysis, we have following FFI strategy table. -- -- TODO: table -- -- In this module, we separate safe and unsafe FFI handling due to the -- strategy difference: if the user can guarantee a FFI call is unsafe, -- we can save an extra copy and pinned allocation. Mistakenly using -- unsafe function with safe FFI will result in segfault. module Z.Foreign -- | Pass primitive array to unsafe FFI as pointer. -- -- Enable UnliftedFFITypes extension in your haskell code, use -- proper pointer type and HsInt to marshall ByteArray# -- and Int arguments on C side. -- -- The second Int arguement is the element size not the bytes -- size. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. withPrimArrayUnsafe :: Prim a => PrimArray a -> (BA# a -> Int -> IO b) -> IO b -- | Allocate some bytes and pass to FFI as pointer, freeze result into a -- PrimArray. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. allocPrimArrayUnsafe :: forall a b. Prim a => Int -> (MBA# a -> IO b) -> IO (PrimArray a, b) -- | Pass PrimVector to unsafe FFI as pointer -- -- The PrimVector version of withPrimArrayUnsafe. -- -- The second Int arguement is the first element offset, the third -- Int argument is the element length. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. withPrimVectorUnsafe :: Prim a => PrimVector a -> (BA# a -> Int -> Int -> IO b) -> IO b -- | Allocate a prim array and pass to FFI as pointer, freeze result into a -- PrimVector. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. allocPrimVectorUnsafe :: forall a b. Prim a => Int -> (MBA# a -> IO b) -> IO (PrimVector a, b) -- | Allocate some bytes and pass to FFI as pointer, freeze result into a -- Bytes. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. allocBytesUnsafe :: Int -> (MBA# a -> IO b) -> IO (Bytes, b) -- | Create an one element primitive array and use it as a pointer to the -- primitive element. -- -- Return the element and the computation result. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. withPrimUnsafe :: Prim a => a -> (MBA# a -> IO b) -> IO (a, b) -- | like withPrimUnsafe, but don't write initial value. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. allocPrimUnsafe :: Prim a => (MBA# a -> IO b) -> IO (a, b) -- | Pass primitive array list to unsafe FFI as StgArrBytes**. -- -- Enable UnliftedFFITypes extension in your haskell code, use -- StgArrBytes**(>=8.10) or StgMutArrPtrs*(<8.10) -- pointer type and HsInt to marshall BAArray# and -- Int arguments on C side, check the example with -- BAArray#. -- -- The second Int arguement is the list size. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. withPrimArrayListUnsafe :: [PrimArray a] -> (BAArray# a -> Int -> IO b) -> IO b -- | Pass primitive array to safe FFI as pointer. -- -- Use proper pointer type and HsInt to marshall Ptr a -- and Int arguments on C side. The memory pointed by 'Ptr a' -- will not moved during call. After call returned, pointer is no longer -- valid. -- -- The second Int arguement is the element size not the bytes -- size. -- -- Don't pass a forever loop to this function, see #14346. withPrimArraySafe :: Prim a => PrimArray a -> (Ptr a -> Int -> IO b) -> IO b -- | Allocate a prim array and pass to FFI as pointer, freeze result into a -- PrimVector. allocPrimArraySafe :: forall a b. Prim a => Int -> (Ptr a -> IO b) -> IO (PrimArray a, b) -- | Pass PrimVector to safe FFI as pointer -- -- The PrimVector version of withPrimArraySafe. The -- Ptr is already pointed to the first element, thus no offset is -- provided. After call returned, pointer is no longer valid. -- -- Don't pass a forever loop to this function, see #14346. withPrimVectorSafe :: forall a b. Prim a => PrimVector a -> (Ptr a -> Int -> IO b) -> IO b -- | Allocate a prim array and pass to FFI as pointer, freeze result into a -- PrimVector. allocPrimVectorSafe :: forall a b. Prim a => Int -> (Ptr a -> IO b) -> IO (PrimVector a, b) -- | Allocate some bytes and pass to FFI as pointer, freeze result into a -- PrimVector. allocBytesSafe :: Int -> (Ptr Word8 -> IO b) -> IO (Bytes, b) -- | Create an one element primitive array and use it as a pointer to the -- primitive element. -- -- Don't pass a forever loop to this function, see #14346. withPrimSafe :: forall a b. Prim a => a -> (Ptr a -> IO b) -> IO (a, b) -- | like withPrimSafe, but don't write initial value. allocPrimSafe :: forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b) -- | Pass primitive array list to safe FFI as pointer. -- -- Use proper pointer type and HsInt to marshall Ptr (Ptr -- a) and Int arguments on C side. The memory pointed by -- 'Ptr a' will not moved during call. After call returned, pointer is no -- longer valid. -- -- The second Int arguement is the list size. -- -- Don't pass a forever loop to this function, see #14346. withPrimArrayListSafe :: Prim a => [PrimArray a] -> (Ptr (Ptr a) -> Int -> IO b) -> IO b -- | Convert a PrimArray to a pinned one(memory won't moved by GC) -- if necessary. pinPrimArray :: Prim a => PrimArray a -> IO (PrimArray a) -- | Convert a PrimVector to a pinned one(memory won't moved by GC) -- if necessary. pinPrimVector :: Prim a => PrimVector a -> IO (PrimVector a) -- | Type alias for ByteArray#. -- -- Describe a ByteArray# which we are going to pass across FFI. -- Use this type with UnliftedFFITypes extension, At C side you -- should use a proper const pointer type. -- -- Don't cast BA# to Addr# since the heap object offset is -- hard-coded in code generator: Note [Unlifted boxed arguments to -- foreign calls] -- -- In haskell side we use type system to distinguish immutable / mutable -- arrays, but in C side we can't. So it's users' responsibility to make -- sure the array content is not mutated (a const pointer type may help). -- -- USE THIS TYPE WITH UNSAFE FFI CALL ONLY. A ByteArray# COULD BE -- MOVED BY GC DURING SAFE FFI CALL. type BA# a = ByteArray# -- | Type alias for MutableByteArray# RealWorld. -- -- Describe a MutableByteArray# which we are going to pass across -- FFI. Use this type with UnliftedFFITypes extension, At C side -- you should use a proper pointer type. -- -- Don't cast MBA# to Addr# since the heap object offset is -- hard-coded in code generator: Note [Unlifted boxed arguments to -- foreign calls] -- -- USE THIS TYPE WITH UNSAFE FFI CALL ONLY. A MutableByteArray# -- COULD BE MOVED BY GC DURING SAFE FFI CALL. type MBA# a = MutableByteArray# RealWorld -- | Type alias for ArrayArray#. -- -- Describe a array of ByteArray# which we are going to pass -- across FFI. Use this type with UnliftedFFITypes extension, At -- C side you should use StgArrBytes**(>=8.10) or -- StgMutArrPtrs*(<8.10) type from "Rts.h", example code -- modified from GHC manual: -- --
--   // C source, must include the RTS to make the struct StgArrBytes
--   // available along with its fields: ptrs and payload.
--   #include "Rts.h"
--   // GHC 8.10 changes the way how ArrayArray# is passed to C, so...
--   #if __GLASGOW_HASKELL__ < 810
--   HsInt sum_first (StgMutArrPtrs *arr, HsInt len) {
--     StgArrBytes **bufs = (StgArrBytes**)arr->payload;
--   #else
--   HsInt sum_first (StgArrBytes **bufs, HsInt len) {
--   #endif
--     int res = 0;
--     for(StgWord ix = 0;ix < len;ix++) {
--        // payload pointer type is StgWord*, cast it before use!
--        res = res + ((HsInt*)(bufs[ix]->payload))[0];
--     }
--     return res;
--   }
--   
--   -- Haskell source, all elements in the argument array must be
--   -- either ByteArray# or MutableByteArray#. This is not enforced
--   -- by the type system in this example since ArrayArray is untyped.
--   foreign import ccall unsafe "sum_first" sumFirst :: BAArray# Int -> Int -> IO CInt
--   
type BAArray# a = ArrayArray# -- | Clear MBA# with given length to zero. clearMBA :: MBA# a -> Int -> IO () -- | Zero a structure. -- -- There's no Storable or Prim constraint on a -- type, the length should be given in bytes. clearPtr :: Ptr a -> Int -> IO () -- | The castPtr function casts a pointer from one type to another. castPtr :: Ptr a -> Ptr b -- | Copy some bytes from a null terminated pointer(without copying the -- null terminator). -- -- You should consider using CBytes type for storing NULL -- terminated bytes first, This method is provided if you really need to -- read Bytes, there's no encoding guarantee, result could be any -- bytes sequence. fromNullTerminated :: Ptr a -> IO Bytes -- | Copy some bytes from a pointer. -- -- There's no encoding guarantee, result could be any bytes sequence. fromPtr :: Ptr a -> Int -> IO Bytes -- | Copy some bytes from a pointer. -- -- There's no encoding guarantee, result could be any bytes sequence. fromPrimPtr :: forall a. Prim a => Ptr a -> Int -> IO (PrimVector a) -- | std::string Pointer tag. data StdString -- | Run FFI in bracket and marshall std::string* result into -- Haskell heap bytes, memory pointed by std::string* will be -- delete ed. fromStdString :: IO (Ptr StdString) -> IO Bytes -- | O(n), Convert from ByteString. fromByteString :: ByteString -> Bytes -- | O(n), Convert tp ByteString. toByteString :: Bytes -> ByteString -- | RealWorld is deeply magical. It is primitive, but it -- is not unlifted (hence ptrArg). We never manipulate -- values of type RealWorld; it's only used in the type system, -- to parameterise State#. data RealWorld touch :: PrimMonad m => a -> m () hs_std_string_size :: Ptr StdString -> IO Int hs_copy_std_string :: Ptr StdString -> Int -> MBA# Word8 -> IO () hs_delete_std_string :: Ptr StdString -> IO () -- | A Builder records a buffer writing function, which can be -- mappend in O(1) via composition. -- -- -- -- Most of the time using combinators from this module to build -- Builder s is enough, but in case of rolling something shining -- from the ground, keep an eye on correct BuildResult handling. module Z.Data.Builder.Base -- | Builder is a monad to help compose BuilderStep. With -- next BuilderStep continuation, we can do interesting things -- like perform some action, or interleave the build process. -- -- Notes on IsString instance: Builder ()'s -- IsString instance use stringModifiedUTF8, which is -- different from stringUTF8 in that it DOES NOT PROVIDE UTF8 -- GUARANTEES! : -- -- newtype Builder a Builder :: ((a -> BuildStep) -> BuildStep) -> Builder a [runBuilder] :: Builder a -> (a -> BuildStep) -> BuildStep append :: Builder a -> Builder b -> Builder b -- | Helper type to help ghc unpack data Buffer Buffer :: {-# UNPACK #-} !MutablePrimArray RealWorld Word8 -> {-# UNPACK #-} !Int -> Buffer -- | Freeze buffer and return a Bytes. -- -- Note the mutable buffer array will be shrinked with -- shrinkMutablePrimArray, which may not able to be reused. freezeBuffer :: Buffer -> IO Bytes -- | BuildSignals abstract signals to the caller of a -- BuildStep. There are three signals: Done, -- BufferFull, or InsertBytes signals data BuildResult Done :: {-# UNPACK #-} !Buffer -> BuildResult BufferFull :: {-# UNPACK #-} !Buffer -> {-# UNPACK #-} !Int -> BuildStep -> BuildResult InsertBytes :: {-# UNPACK #-} !Buffer -> Bytes -> BuildStep -> BuildResult -- | BuilderStep is a function that fill buffer under given -- conditions. type BuildStep = Buffer -> IO BuildResult -- | Shortcut to buildWith defaultInitSize. build :: Builder a -> Bytes -- | Run Builder with doubling buffer strategy, which is suitable for -- building short bytes. buildWith :: Int -> Builder a -> Bytes -- | Shortcut to buildChunksWith defaultChunkSize. buildChunks :: Builder a -> [Bytes] -- | Run Builder with inserting chunk strategy, which is suitable for -- building a list of bytes chunks and processing them in a streaming -- ways. -- -- Note the building process is lazy, building happens when list chunks -- are consumed. buildChunksWith :: Int -> Int -> Builder a -> [Bytes] -- | Build some bytes and validate if it's UTF8 bytes. buildText :: HasCallStack => Builder a -> Text -- | Build some bytes assuming it's UTF8 encoding. -- -- Be carefully use this function because you could constrcut illegal -- Text values. Check ShowT for UTF8 encoding builders. -- This functions is intended to be used in debug only. unsafeBuildText :: Builder a -> Text -- | Write a Bytes. bytes :: Bytes -> Builder () ensureN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO Int) -> Builder () writeN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO ()) -> Builder () -- | Write a primitive type in host byte order. -- --
--   > encodePrim (256 :: Word16, BE 256 :: BE Word16)
--   > [0,1,1,0]
--   
encodePrim :: forall a. Unaligned a => a -> Builder () -- | big endianess wrapper newtype BE a BE :: a -> BE a [getBE] :: BE a -> a -- | little endianess wrapper newtype LE a LE :: a -> LE a [getLE] :: LE a -> a -- | Write a primitive type with little endianess. encodePrimLE :: forall a. Unaligned (LE a) => a -> Builder () -- | Write a primitive type with big endianess. encodePrimBE :: forall a. Unaligned (BE a) => a -> Builder () -- | Encode string with modified UTF-8 encoding, will be rewritten to a -- memcpy if possible. stringModifiedUTF8 :: String -> Builder () -- | Turn Char into Builder with Modified UTF8 encoding -- -- \NUL is encoded as two bytes C0 80 , \xD800 -- ~ \xDFFF is encoded as a three bytes normal UTF-8 codepoint. charModifiedUTF8 :: Char -> Builder () -- | Turn String into Builder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. -- -- This is different from writing string literals builders via -- OverloadedStrings, because string literals do not provide -- UTF8 guarantees. -- -- This function will be rewritten into a memcpy if possible, (running a -- fast UTF-8 validation at runtime first). stringUTF8 :: String -> Builder () -- | Turn Char into Builder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. charUTF8 :: Char -> Builder () -- | Turn String into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. string7 :: String -> Builder () -- | Turn Char into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. char7 :: Char -> Builder () -- | Turn Word8 into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. word7 :: Word8 -> Builder () -- | Turn String into Builder with ASCII8 encoding -- -- Codepoints beyond 'xFF' will be chopped. Note, this encoding -- is NOT compatible with UTF8 encoding, i.e. bytes written by this -- builder may not be legal UTF8 encoding bytes. string8 :: String -> Builder () -- | Turn Char into Builder with ASCII8 encoding -- -- Codepoints beyond 'xFF' will be chopped. Note, this encoding -- is NOT compatible with UTF8 encoding, i.e. bytes written by this -- builder may not be legal UTF8 encoding bytes. char8 :: Char -> Builder () -- | Turn Word8 into Builder with ASCII8 encoding, (alias to -- encodePrim). -- -- Note, this encoding is NOT compatible with UTF8 encoding, i.e. bytes -- written by this builder may not be legal UTF8 encoding bytes. word8 :: Word8 -> Builder () -- | Faster version of replicateM x . word8 by using -- memset. -- -- Note, this encoding is NOT compatible with UTF8 encoding, i.e. bytes -- written by this builder may not be legal UTF8 encoding bytes. word8N :: Int -> Word8 -> Builder () -- | Write UTF8 encoded Text using Builder. -- -- Note, if you're trying to write string literals builders, please open -- OverloadedStrings and use Builders IsString -- instance, it will be rewritten into a memcpy. text :: Text -> Builder () -- | add (...) to original builder. paren :: Builder () -> Builder () -- | add {...} to original builder. curly :: Builder () -> Builder () -- | add [...] to original builder. square :: Builder () -> Builder () -- | add <...> to original builder. angle :: Builder () -> Builder () -- | add "..." to original builder. quotes :: Builder () -> Builder () -- | add '...' to original builder. squotes :: Builder () -> Builder () -- | write an ASCII : colon :: Builder () -- | write an ASCII , comma :: Builder () -- | Use separator to connect a vector of builders. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Z.Data.Vector  as V
--   
--   > T.validate . B.build $ B.intercalateVec "," B.int (V.pack [1,2,3,4] :: V.PrimVector Int)
--   "1,2,3,4"
--   
intercalateVec :: Vec v a => Builder () -> (a -> Builder ()) -> v a -> Builder () -- | Use separator to connect list of builders. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Z.Data.Vector  as V
--   
--   T.validate . B.build $ B.intercalateList "," B.int ([1,2,3,4] :: [Int])
--   "1,2,3,4"
--   
intercalateList :: Builder () -> (a -> Builder ()) -> [a] -> Builder () instance GHC.Show.Show (Z.Data.Builder.Base.Builder a) instance GHC.Base.Functor Z.Data.Builder.Base.Builder instance GHC.Base.Applicative Z.Data.Builder.Base.Builder instance GHC.Base.Monad Z.Data.Builder.Base.Builder instance GHC.Base.Semigroup (Z.Data.Builder.Base.Builder ()) instance GHC.Base.Monoid (Z.Data.Builder.Base.Builder ()) instance (a GHC.Types.~ ()) => Data.String.IsString (Z.Data.Builder.Base.Builder a) instance Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Builder.Base.Builder ()) instance Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Builder.Base.Builder ()) -- | This module provides base64 encoding & decoding tools, as well as -- Base64Bytes newtype with base64 textual instances. module Z.Data.Vector.Base64 -- | Encode Bytes using base64 encoding. base64Encode :: Bytes -> Bytes -- | Return the encoded length of a given input length, always a multipler -- of 4. base64EncodeLength :: Int -> Int -- | Text version of base64Encode. base64EncodeText :: Bytes -> Text -- | Builder version of base64Encode. base64EncodeBuilder :: Bytes -> Builder () -- | Decode a base64 encoding string, return Nothing on illegal bytes or -- incomplete input. base64Decode :: Bytes -> Maybe Bytes -- | Decode a base64 encoding string, throw Base64DecodeException on -- error. base64Decode' :: HasCallStack => Bytes -> Bytes -- | Return the upper bound of decoded length of a given input length , -- return -1 if illegal(not a multipler of 4). base64DecodeLength :: Int -> Int -- | Exception during base64 decoding. data Base64DecodeException IllegalBase64Bytes :: Bytes -> CallStack -> Base64DecodeException IncompleteBase64Bytes :: Bytes -> CallStack -> Base64DecodeException hs_base64_encode :: MBA# Word8 -> Int -> BA# Word8 -> Int -> Int -> IO () hs_base64_decode :: MBA# Word8 -> BA# Word8 -> Int -> Int -> IO Int instance GHC.Show.Show Z.Data.Vector.Base64.Base64DecodeException instance GHC.Exception.Type.Exception Z.Data.Vector.Base64.Base64DecodeException -- | Textual numeric builders. module Z.Data.Builder.Numeric -- | Integral formatting options. data IFormat IFormat :: Int -> Padding -> Bool -> IFormat -- | total width, only effective with padding options [width] :: IFormat -> Int -- | padding options [padding] :: IFormat -> Padding -- | show + when the number is positive [posSign] :: IFormat -> Bool -- |
--   defaultIFormat = IFormat 0 NoPadding False
--   
defaultIFormat :: IFormat data Padding NoPadding :: Padding RightSpacePadding :: Padding LeftSpacePadding :: Padding ZeroPadding :: Padding -- |
--   int = intWith defaultIFormat
--   
int :: (Integral a, Bounded a) => a -> Builder () -- | Format a Bounded Integral type like Int or -- Word16 into decimal ASCII digits. -- --
--   import Z.Data.Builder as B
--   
--   > B.buildText $ B.intWith defaultIFormat  (12345 :: Int)
--   "12345"
--   > B.buildText $ B.intWith defaultIFormat{width=10, padding=RightSpacePadding} (12345 :: Int)
--   "12345     "
--   > B.buildText $ B.intWith defaultIFormat{width=10, padding=ZeroPadding} (12345 :: Int)
--   "0000012345"
--   
intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder () -- | Format a Integer into decimal ASCII digits. integer :: Integer -> Builder () -- | Format a FiniteBits Integral type into hex nibbles. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Data.Word
--   import Data.Int
--   
--   > T.validate . B.buildBytes $ B.hex (125 :: Int8)
--   "7d"
--   > T.validate . B.buildBytes $ B.hex (-1 :: Int8)
--   "ff"
--   > T.validate . B.buildBytes $ B.hex (125 :: Word16)
--   "007d"
--   
hex :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | The UPPERCASED version of hex. hexUpper :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | Control the rendering of floating point numbers. data FFormat -- | Scientific notation (e.g. 2.3e123). Exponent :: FFormat -- | Standard decimal notation. Fixed :: FFormat -- | Use decimal notation for values between 0.1 and -- 9,999,999, and scientific notation otherwise. Generic :: FFormat -- | Decimal encoding of an IEEE Double. -- -- Using standard decimal notation for arguments whose absolute value -- lies between 0.1 and 9,999,999, and scientific -- notation otherwise. double :: Double -> Builder () -- | Format double-precision float using drisu3 with dragon4 fallback. doubleWith :: FFormat -> Maybe Int -> Double -> Builder () -- | Decimal encoding of an IEEE Float. -- -- Using standard decimal notation for arguments whose absolute value -- lies between 0.1 and 9,999,999, and scientific -- notation otherwise. float :: Float -> Builder () -- | Format single-precision float using drisu3 with dragon4 fallback. floatWith :: FFormat -> Maybe Int -> Float -> Builder () -- | A Builder which renders a scientific number to full -- precision, using standard decimal notation for arguments whose -- absolute value lies between 0.1 and 9,999,999, and -- scientific notation otherwise. scientific :: Scientific -> Builder () -- | Like scientific but provides rendering options. scientificWith :: FFormat -> Maybe Int -> Scientific -> Builder () -- | Decimal encoding of a Double, note grisu only handles strictly -- positive finite numbers. grisu3 :: Double -> ([Int], Int) -- | Decimal encoding of a Float, note grisu3_sp only handles -- strictly positive finite numbers. grisu3_sp :: Float -> ([Int], Int) -- | Decimal digit to ASCII digit. i2wDec :: Integral a => a -> Word8 -- | Hexadecimal digit to ASCII char. i2wHex :: Integral a => a -> Word8 -- | Hexadecimal digit to UPPERCASED ASCII char. i2wHexUpper :: Integral a => a -> Word8 -- | Count how many decimal digits an integer has. countDigits :: Integral a => a -> Int -- | Internal formatting backed by C FFI, it must be used with type smaller -- than Word64. -- -- We use rewrite rules to rewrite most of the integral types formatting -- to this function. c_intWith :: (Integral a, Bits a) => IFormat -> a -> Builder () -- | Internal formatting in haskell, it can be used with any bounded -- integral type. -- -- Other than provide fallback for the c version, this function is also -- used to check the c version's formatting result. hs_intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder () instance GHC.Enum.Enum Z.Data.Builder.Numeric.Padding instance GHC.Classes.Ord Z.Data.Builder.Numeric.Padding instance GHC.Classes.Eq Z.Data.Builder.Numeric.Padding instance GHC.Show.Show Z.Data.Builder.Numeric.Padding instance GHC.Classes.Ord Z.Data.Builder.Numeric.IFormat instance GHC.Classes.Eq Z.Data.Builder.Numeric.IFormat instance GHC.Show.Show Z.Data.Builder.Numeric.IFormat instance GHC.Show.Show Z.Data.Builder.Numeric.FFormat instance GHC.Read.Read Z.Data.Builder.Numeric.FFormat instance GHC.Enum.Enum Z.Data.Builder.Numeric.FFormat instance Test.QuickCheck.Arbitrary.Arbitrary Z.Data.Builder.Numeric.IFormat instance Test.QuickCheck.Arbitrary.CoArbitrary Z.Data.Builder.Numeric.IFormat instance Test.QuickCheck.Arbitrary.Arbitrary Z.Data.Builder.Numeric.Padding instance Test.QuickCheck.Arbitrary.CoArbitrary Z.Data.Builder.Numeric.Padding -- | This module re-exports some UTF8 compatible textual builders from -- Builder. -- -- We also provide a faster alternative to Show class, i.e. -- Print, which can be deriving using Generic. For example -- to use Print class: -- --
--   import qualified Z.Data.Text.Print as T
--   
--   data Foo = Bar Bytes | Qux Text Int deriving Generic
--                                       deriving anyclass T.Print
--   
module Z.Data.Text.Print -- | A class similar to Show, serving the purpose that quickly -- convert a data type to a Text value. -- -- You can use newtype or generic deriving to implement instance of this -- class quickly: -- --
--    {-# LANGUAGE GeneralizedNewtypeDeriving #-}
--    {-# LANGUAGE DeriveAnyClass #-}
--    {-# LANGUAGE DeriveGeneric #-}
--    {-# LANGUAGE DerivingStrategies #-}
--   
--    import GHC.Generics
--   
--    newtype FooInt = FooInt Int deriving (Generic)
--                              deriving anyclass Print
--   
--   > toText (FooInt 3)
--   > "FooInt 3"
--   
--    newtype FooInt = FooInt Int deriving (Generic)
--                              deriving newtype Print
--   
--   > toText (FooInt 3)
--   > "3"
--   
class Print a -- | Convert data to Builder with precendence. -- -- You should return a Builder writing in UTF8 encoding only, i.e. -- --
--   Z.Data.Text.validateMaybe (Z.Data.Builder.buildBytes (toUTF8BuilderP p a)) /= Nothing
--   
toUTF8BuilderP :: Print a => Int -> a -> Builder () -- | Convert data to Builder with precendence. -- -- You should return a Builder writing in UTF8 encoding only, i.e. -- --
--   Z.Data.Text.validateMaybe (Z.Data.Builder.buildBytes (toUTF8BuilderP p a)) /= Nothing
--   
toUTF8BuilderP :: (Print a, Generic a, GToText (Rep a)) => Int -> a -> Builder () -- | Convert data to Text. toText :: Print a => a -> Text -- | Convert data to String, faster show replacement. toString :: Print a => a -> String -- | Convert data to Builder. toUTF8Builder :: Print a => a -> Builder () -- | Convert data to Bytes in UTF8 encoding. toUTF8Bytes :: Print a => a -> Bytes -- | Escape text using JSON string escaping rules and add double quotes, -- escaping rules: -- --
--   '\b':  "\b"
--   '\f':  "\f"
--   '\n':  "\n"
--   '\r':  "\r"
--   '\t':  "\t"
--   '"':  "\""
--   '\':  "\\"
--   other chars <= 0x1F: "\u00XX"
--   
escapeTextJSON :: Text -> Builder () -- | Turn String into Builder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. -- -- This is different from writing string literals builders via -- OverloadedStrings, because string literals do not provide -- UTF8 guarantees. -- -- This function will be rewritten into a memcpy if possible, (running a -- fast UTF-8 validation at runtime first). stringUTF8 :: String -> Builder () -- | Turn Char into Builder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. charUTF8 :: Char -> Builder () -- | Turn String into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. string7 :: String -> Builder () -- | Turn Char into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. char7 :: Char -> Builder () -- | Write UTF8 encoded Text using Builder. -- -- Note, if you're trying to write string literals builders, please open -- OverloadedStrings and use Builders IsString -- instance, it will be rewritten into a memcpy. text :: Text -> Builder () -- | Integral formatting options. data IFormat IFormat :: Int -> Padding -> Bool -> IFormat -- | total width, only effective with padding options [width] :: IFormat -> Int -- | padding options [padding] :: IFormat -> Padding -- | show + when the number is positive [posSign] :: IFormat -> Bool -- |
--   defaultIFormat = IFormat 0 NoPadding False
--   
defaultIFormat :: IFormat data Padding NoPadding :: Padding RightSpacePadding :: Padding LeftSpacePadding :: Padding ZeroPadding :: Padding -- |
--   int = intWith defaultIFormat
--   
int :: (Integral a, Bounded a) => a -> Builder () -- | Format a Bounded Integral type like Int or -- Word16 into decimal ASCII digits. -- --
--   import Z.Data.Builder as B
--   
--   > B.buildText $ B.intWith defaultIFormat  (12345 :: Int)
--   "12345"
--   > B.buildText $ B.intWith defaultIFormat{width=10, padding=RightSpacePadding} (12345 :: Int)
--   "12345     "
--   > B.buildText $ B.intWith defaultIFormat{width=10, padding=ZeroPadding} (12345 :: Int)
--   "0000012345"
--   
intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder () -- | Format a Integer into decimal ASCII digits. integer :: Integer -> Builder () -- | Format a FiniteBits Integral type into hex nibbles. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Data.Word
--   import Data.Int
--   
--   > T.validate . B.buildBytes $ B.hex (125 :: Int8)
--   "7d"
--   > T.validate . B.buildBytes $ B.hex (-1 :: Int8)
--   "ff"
--   > T.validate . B.buildBytes $ B.hex (125 :: Word16)
--   "007d"
--   
hex :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | The UPPERCASED version of hex. hexUpper :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | Control the rendering of floating point numbers. data FFormat -- | Scientific notation (e.g. 2.3e123). Exponent :: FFormat -- | Standard decimal notation. Fixed :: FFormat -- | Use decimal notation for values between 0.1 and -- 9,999,999, and scientific notation otherwise. Generic :: FFormat -- | Decimal encoding of an IEEE Double. -- -- Using standard decimal notation for arguments whose absolute value -- lies between 0.1 and 9,999,999, and scientific -- notation otherwise. double :: Double -> Builder () -- | Format double-precision float using drisu3 with dragon4 fallback. doubleWith :: FFormat -> Maybe Int -> Double -> Builder () -- | Decimal encoding of an IEEE Float. -- -- Using standard decimal notation for arguments whose absolute value -- lies between 0.1 and 9,999,999, and scientific -- notation otherwise. float :: Float -> Builder () -- | Format single-precision float using drisu3 with dragon4 fallback. floatWith :: FFormat -> Maybe Int -> Float -> Builder () -- | A Builder which renders a scientific number to full -- precision, using standard decimal notation for arguments whose -- absolute value lies between 0.1 and 9,999,999, and -- scientific notation otherwise. scientific :: Scientific -> Builder () -- | Like scientific but provides rendering options. scientificWith :: FFormat -> Maybe Int -> Scientific -> Builder () -- | add (...) to original builder. paren :: Builder () -> Builder () -- | add {...} to original builder. curly :: Builder () -> Builder () -- | add [...] to original builder. square :: Builder () -> Builder () -- | add <...> to original builder. angle :: Builder () -> Builder () -- | add "..." to original builder. quotes :: Builder () -> Builder () -- | add '...' to original builder. squotes :: Builder () -> Builder () -- | write an ASCII : colon :: Builder () -- | write an ASCII , comma :: Builder () -- | Use separator to connect a vector of builders. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Z.Data.Vector  as V
--   
--   > T.validate . B.build $ B.intercalateVec "," B.int (V.pack [1,2,3,4] :: V.PrimVector Int)
--   "1,2,3,4"
--   
intercalateVec :: Vec v a => Builder () -> (a -> Builder ()) -> v a -> Builder () -- | Use separator to connect list of builders. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Z.Data.Vector  as V
--   
--   T.validate . B.build $ B.intercalateList "," B.int ([1,2,3,4] :: [Int])
--   "1,2,3,4"
--   
intercalateList :: Builder () -> (a -> Builder ()) -> [a] -> Builder () -- | Add "(..)" around builders when condition is met, otherwise add -- nothing. -- -- This is useful when defining Print instances. parenWhen :: Bool -> Builder () -> Builder () instance Z.Data.Text.Print.Print Foreign.C.Types.CChar instance Z.Data.Text.Print.Print Foreign.C.Types.CSChar instance Z.Data.Text.Print.Print Foreign.C.Types.CUChar instance Z.Data.Text.Print.Print Foreign.C.Types.CShort instance Z.Data.Text.Print.Print Foreign.C.Types.CUShort instance Z.Data.Text.Print.Print Foreign.C.Types.CInt instance Z.Data.Text.Print.Print Foreign.C.Types.CUInt instance Z.Data.Text.Print.Print Foreign.C.Types.CLong instance Z.Data.Text.Print.Print Foreign.C.Types.CULong instance Z.Data.Text.Print.Print Foreign.C.Types.CPtrdiff instance Z.Data.Text.Print.Print Foreign.C.Types.CSize instance Z.Data.Text.Print.Print Foreign.C.Types.CWchar instance Z.Data.Text.Print.Print Foreign.C.Types.CSigAtomic instance Z.Data.Text.Print.Print Foreign.C.Types.CLLong instance Z.Data.Text.Print.Print Foreign.C.Types.CULLong instance Z.Data.Text.Print.Print Foreign.C.Types.CBool instance Z.Data.Text.Print.Print Foreign.C.Types.CIntPtr instance Z.Data.Text.Print.Print Foreign.C.Types.CUIntPtr instance Z.Data.Text.Print.Print Foreign.C.Types.CIntMax instance Z.Data.Text.Print.Print Foreign.C.Types.CUIntMax instance Z.Data.Text.Print.Print Foreign.C.Types.CClock instance Z.Data.Text.Print.Print Foreign.C.Types.CTime instance Z.Data.Text.Print.Print Foreign.C.Types.CUSeconds instance Z.Data.Text.Print.Print Foreign.C.Types.CSUSeconds instance Z.Data.Text.Print.Print Foreign.C.Types.CFloat instance Z.Data.Text.Print.Print Foreign.C.Types.CDouble instance Z.Data.Text.Print.Print GHC.IO.Exception.ExitCode instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Semigroup.Min a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Semigroup.Max a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Semigroup.First a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Semigroup.Last a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Semigroup.WrappedMonoid a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Semigroup.Internal.Dual a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Monoid.First a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Monoid.Last a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (GHC.Base.NonEmpty a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Functor.Identity.Identity a) instance forall k a (b :: k). Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Functor.Const.Const a b) instance forall k (a :: k). Z.Data.Text.Print.Print (Data.Proxy.Proxy a) instance forall k b (a :: k). Z.Data.Text.Print.Print b => Z.Data.Text.Print.Print (Data.Tagged.Tagged a b) instance forall k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1). Z.Data.Text.Print.Print (f (g a)) => Z.Data.Text.Print.Print (Data.Functor.Compose.Compose f g a) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (Z.Data.Text.Print.Print (f a), Z.Data.Text.Print.Print (g a)) => Z.Data.Text.Print.Print (Data.Functor.Product.Product f g a) instance (Z.Data.Text.Print.Print (f a), Z.Data.Text.Print.Print (g a), Z.Data.Text.Print.Print a) => Z.Data.Text.Print.Print (Data.Functor.Sum.Sum f g a) instance forall k (a :: k -> *) (b :: k -> *). (Z.Data.Text.Print.GFieldToText a, Z.Data.Text.Print.GFieldToText b) => Z.Data.Text.Print.GFieldToText (a GHC.Generics.:*: b) instance forall k (f :: k -> *) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). Z.Data.Text.Print.GToText f => Z.Data.Text.Print.GFieldToText (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance forall k (f :: k -> *) (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). (Z.Data.Text.Print.GToText f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Z.Data.Text.Print.GFieldToText (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance forall k (sc :: GHC.Generics.Meta) (f :: k -> *) (c :: GHC.Generics.Meta). (Z.Data.Text.Print.GFieldToText (GHC.Generics.S1 sc f), GHC.Generics.Constructor c) => Z.Data.Text.Print.GToText (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance forall k (a :: k -> *) (b :: k -> *) (c :: GHC.Generics.Meta). (Z.Data.Text.Print.GFieldToText (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Z.Data.Text.Print.GToText (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.GToText (GHC.Generics.K1 i a) instance Z.Data.Text.Print.Print GHC.Types.Bool instance Z.Data.Text.Print.Print GHC.Types.Char instance Z.Data.Text.Print.Print GHC.Types.Double instance Z.Data.Text.Print.Print GHC.Types.Float instance Z.Data.Text.Print.Print GHC.Types.Int instance Z.Data.Text.Print.Print GHC.Int.Int8 instance Z.Data.Text.Print.Print GHC.Int.Int16 instance Z.Data.Text.Print.Print GHC.Int.Int32 instance Z.Data.Text.Print.Print GHC.Int.Int64 instance Z.Data.Text.Print.Print GHC.Types.Word instance Z.Data.Text.Print.Print GHC.Word.Word8 instance Z.Data.Text.Print.Print GHC.Word.Word16 instance Z.Data.Text.Print.Print GHC.Word.Word32 instance Z.Data.Text.Print.Print GHC.Word.Word64 instance Z.Data.Text.Print.Print GHC.Integer.Type.Integer instance Z.Data.Text.Print.Print GHC.Natural.Natural instance Z.Data.Text.Print.Print GHC.Types.Ordering instance Z.Data.Text.Print.Print () instance Z.Data.Text.Print.Print Data.Version.Version instance Z.Data.Text.Print.Print Z.Data.Text.Base.Text instance Z.Data.Text.Print.Print Data.Scientific.Scientific instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print [a] instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Primitive.Array.Array a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Data.Primitive.SmallArray.SmallArray a) instance (Z.Data.Array.UnliftedArray.PrimUnlifted a, Z.Data.Text.Print.Print a) => Z.Data.Text.Print.Print (Z.Data.Array.UnliftedArray.UnliftedArray a) instance (Data.Primitive.Types.Prim a, Z.Data.Text.Print.Print a) => Z.Data.Text.Print.Print (Data.Primitive.PrimArray.PrimArray a) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (Z.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Z.Data.Text.Print.Print a) => Z.Data.Text.Print.Print (Z.Data.Vector.Base.PrimVector a) instance (Z.Data.Text.Print.Print a, Z.Data.Text.Print.Print b) => Z.Data.Text.Print.Print (a, b) instance (Z.Data.Text.Print.Print a, Z.Data.Text.Print.Print b, Z.Data.Text.Print.Print c) => Z.Data.Text.Print.Print (a, b, c) instance (Z.Data.Text.Print.Print a, Z.Data.Text.Print.Print b, Z.Data.Text.Print.Print c, Z.Data.Text.Print.Print d) => Z.Data.Text.Print.Print (a, b, c, d) instance (Z.Data.Text.Print.Print a, Z.Data.Text.Print.Print b, Z.Data.Text.Print.Print c, Z.Data.Text.Print.Print d, Z.Data.Text.Print.Print e) => Z.Data.Text.Print.Print (a, b, c, d, e) instance (Z.Data.Text.Print.Print a, Z.Data.Text.Print.Print b, Z.Data.Text.Print.Print c, Z.Data.Text.Print.Print d, Z.Data.Text.Print.Print e, Z.Data.Text.Print.Print f) => Z.Data.Text.Print.Print (a, b, c, d, e, f) instance (Z.Data.Text.Print.Print a, Z.Data.Text.Print.Print b, Z.Data.Text.Print.Print c, Z.Data.Text.Print.Print d, Z.Data.Text.Print.Print e, Z.Data.Text.Print.Print f, Z.Data.Text.Print.Print g) => Z.Data.Text.Print.Print (a, b, c, d, e, f, g) instance Z.Data.Text.Print.Print a => Z.Data.Text.Print.Print (GHC.Maybe.Maybe a) instance (Z.Data.Text.Print.Print a, Z.Data.Text.Print.Print b) => Z.Data.Text.Print.Print (Data.Either.Either a b) instance (Z.Data.Text.Print.Print a, GHC.Real.Integral a) => Z.Data.Text.Print.Print (GHC.Real.Ratio a) instance forall k (a :: k). Data.Fixed.HasResolution a => Z.Data.Text.Print.Print (Data.Fixed.Fixed a) instance Z.Data.Text.Print.Print GHC.Stack.Types.CallStack instance Z.Data.Text.Print.Print (GHC.Ptr.Ptr a) instance Z.Data.Text.Print.Print (GHC.ForeignPtr.ForeignPtr a) instance Z.Data.Text.Print.GToText GHC.Generics.V1 instance forall k (f :: k -> *) (g :: k -> *). (Z.Data.Text.Print.GToText f, Z.Data.Text.Print.GToText g) => Z.Data.Text.Print.GToText (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Z.Data.Text.Print.GToText (GHC.Generics.C1 c GHC.Generics.U1) instance forall k (f :: k -> *) (c :: GHC.Generics.Meta). Z.Data.Text.Print.GToText f => Z.Data.Text.Print.GToText (GHC.Generics.D1 c f) -- | This module provides a simple value set based on sorted vector and -- binary search. It's particularly suitable for small sized value -- collections such as deserializing intermediate representation. But can -- also used in various place where insertion and deletion is rare but -- require fast elem. module Z.Data.Vector.FlatSet data FlatSet v sortedValues :: FlatSet v -> Vector v size :: FlatSet v -> Int null :: FlatSet v -> Bool -- | O(1) empty flat set. empty :: FlatSet v -- | Mapping values of within a set, the result size may change if there're -- duplicated values after mapping. map' :: forall v. Ord v => (v -> v) -> FlatSet v -> FlatSet v -- | O(N*logN) Pack list of values, on duplication prefer left one. pack :: Ord v => [v] -> FlatSet v -- | O(N*logN) Pack list of values with suggested size, on -- duplication prefer left one. packN :: Ord v => Int -> [v] -> FlatSet v -- | O(N*logN) Pack list of values, on duplication prefer right one. packR :: Ord v => [v] -> FlatSet v -- | O(N*logN) Pack list of values with suggested size, on -- duplication prefer right one. packRN :: Ord v => Int -> [v] -> FlatSet v -- | O(N) Unpack a set of values to a list s in ascending order. -- -- This function works with foldr/build fusion in base. unpack :: FlatSet v -> [v] -- | O(N) Unpack a set of values to a list s in descending order. -- -- This function works with foldr/build fusion in base. unpackR :: FlatSet v -> [v] -- | O(N*logN) Pack vector of values, on duplication prefer left -- one. packVector :: Ord v => Vector v -> FlatSet v -- | O(N*logN) Pack vector of values, on duplication prefer right -- one. packVectorR :: Ord v => Vector v -> FlatSet v -- | O(logN) Binary search on flat set. elem :: Ord v => v -> FlatSet v -> Bool -- | O(N) Delete a value from set. delete :: Ord v => v -> FlatSet v -> FlatSet v -- | O(N) Insert new value into set. insert :: Ord v => v -> FlatSet v -> FlatSet v -- | O(n+m) Merge two FlatSet, prefer right value on value -- duplication. merge :: forall v. Ord v => FlatSet v -> FlatSet v -> FlatSet v -- | Find the value's index in the vector, if value exists return -- Right, otherwise Left, i.e. the insert index -- -- This function only works on ascending sorted vectors. binarySearch :: Ord v => Vector v -> v -> Either Int Int instance Data.Foldable.Foldable Z.Data.Vector.FlatSet.FlatSet instance GHC.Classes.Ord v => GHC.Classes.Ord (Z.Data.Vector.FlatSet.FlatSet v) instance GHC.Classes.Eq v => GHC.Classes.Eq (Z.Data.Vector.FlatSet.FlatSet v) instance GHC.Show.Show v => GHC.Show.Show (Z.Data.Vector.FlatSet.FlatSet v) instance Z.Data.Text.Print.Print v => Z.Data.Text.Print.Print (Z.Data.Vector.FlatSet.FlatSet v) instance GHC.Classes.Ord v => GHC.Base.Semigroup (Z.Data.Vector.FlatSet.FlatSet v) instance GHC.Classes.Ord v => GHC.Base.Monoid (Z.Data.Vector.FlatSet.FlatSet v) instance Control.DeepSeq.NFData v => Control.DeepSeq.NFData (Z.Data.Vector.FlatSet.FlatSet v) instance (GHC.Classes.Ord v, Test.QuickCheck.Arbitrary.Arbitrary v) => Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Vector.FlatSet.FlatSet v) instance Test.QuickCheck.Arbitrary.CoArbitrary v => Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Vector.FlatSet.FlatSet v) -- | This module provides a simple key value map based on sorted vector and -- binary search. It's particularly suitable for small sized key value -- collections such as deserializing intermediate representation. But can -- also used in various place where insertion and deletion is rare but -- require fast lookup. module Z.Data.Vector.FlatMap data FlatMap k v sortedKeyValues :: FlatMap k v -> Vector (k, v) size :: FlatMap k v -> Int null :: FlatMap k v -> Bool -- | O(1) empty flat map. empty :: FlatMap k v map' :: (v -> v') -> FlatMap k v -> FlatMap k v' kmap' :: (k -> v -> v') -> FlatMap k v -> FlatMap k v' -- | O(N*logN) Pack list of key values, on key duplication prefer -- left one. pack :: Ord k => [(k, v)] -> FlatMap k v -- | O(N*logN) Pack list of key values with suggested size, on key -- duplication prefer left one. packN :: Ord k => Int -> [(k, v)] -> FlatMap k v -- | O(N*logN) Pack list of key values, on key duplication prefer -- right one. packR :: Ord k => [(k, v)] -> FlatMap k v -- | O(N*logN) Pack list of key values with suggested size, on key -- duplication prefer right one. packRN :: Ord k => Int -> [(k, v)] -> FlatMap k v -- | O(N) Unpack key value pairs to a list sorted by keys in -- ascending order. -- -- This function works with foldr/build fusion in base. unpack :: FlatMap k v -> [(k, v)] -- | O(N) Unpack key value pairs to a list sorted by keys in -- descending order. -- -- This function works with foldr/build fusion in base. unpackR :: FlatMap k v -> [(k, v)] -- | O(N*logN) Pack vector of key values, on key duplication prefer -- left one. packVector :: Ord k => Vector (k, v) -> FlatMap k v -- | O(N*logN) Pack vector of key values, on key duplication prefer -- right one. packVectorR :: Ord k => Vector (k, v) -> FlatMap k v -- | O(logN) Binary search on flat map. lookup :: Ord k => k -> FlatMap k v -> Maybe v -- | O(N) Delete a key value pair by key. delete :: Ord k => k -> FlatMap k v -> FlatMap k v -- | O(N) Insert new key value into map, replace old one if key -- exists. insert :: Ord k => k -> v -> FlatMap k v -> FlatMap k v -- | O(N) Modify a value by key. -- -- The value is evaluated to WHNF before writing into map. adjust' :: Ord k => (v -> v) -> k -> FlatMap k v -> FlatMap k v -- | O(n+m) Merge two FlatMap, prefer right value on key -- duplication. merge :: forall k v. Ord k => FlatMap k v -> FlatMap k v -> FlatMap k v -- | O(n+m) Merge two FlatMap with a merge function. mergeWithKey' :: forall k v. Ord k => (k -> v -> v -> v) -> FlatMap k v -> FlatMap k v -> FlatMap k v -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding k is in descending order. foldrWithKey :: (k -> v -> a -> a) -> a -> FlatMap k v -> a -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding k is in descending order. foldrWithKey' :: (k -> v -> a -> a) -> a -> FlatMap k v -> a -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding k is in ascending order. foldlWithKey :: (a -> k -> v -> a) -> a -> FlatMap k v -> a -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding k is in ascending order. foldlWithKey' :: (a -> k -> v -> a) -> a -> FlatMap k v -> a -- | O(n). -- -- traverseWithKey f s == pack <$> -- traverse ((k, v) -> (,) k <$> f k v) (unpack -- m) That is, behaves exactly like a regular traverse except -- that the traversing function also has access to the key associated -- with a value. traverseWithKey :: Applicative t => (k -> a -> t b) -> FlatMap k a -> t (FlatMap k b) -- | Find the key's index in the vector slice, if key exists return -- Right, otherwise Left, i.e. the insert index -- -- This function only works on ascending sorted vectors. binarySearch :: Ord k => Vector (k, v) -> k -> Either Int Int instance (GHC.Classes.Ord k, GHC.Classes.Ord v) => GHC.Classes.Ord (Z.Data.Vector.FlatMap.FlatMap k v) instance (GHC.Classes.Eq k, GHC.Classes.Eq v) => GHC.Classes.Eq (Z.Data.Vector.FlatMap.FlatMap k v) instance (GHC.Show.Show k, GHC.Show.Show v) => GHC.Show.Show (Z.Data.Vector.FlatMap.FlatMap k v) instance (Z.Data.Text.Print.Print k, Z.Data.Text.Print.Print v) => Z.Data.Text.Print.Print (Z.Data.Vector.FlatMap.FlatMap k v) instance (GHC.Classes.Ord k, Test.QuickCheck.Arbitrary.Arbitrary k, Test.QuickCheck.Arbitrary.Arbitrary v) => Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Vector.FlatMap.FlatMap k v) instance (Test.QuickCheck.Arbitrary.CoArbitrary k, Test.QuickCheck.Arbitrary.CoArbitrary v) => Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Vector.FlatMap.FlatMap k v) instance GHC.Classes.Ord k => GHC.Base.Semigroup (Z.Data.Vector.FlatMap.FlatMap k v) instance GHC.Classes.Ord k => GHC.Base.Monoid (Z.Data.Vector.FlatMap.FlatMap k v) instance (Control.DeepSeq.NFData k, Control.DeepSeq.NFData v) => Control.DeepSeq.NFData (Z.Data.Vector.FlatMap.FlatMap k v) instance GHC.Base.Functor (Z.Data.Vector.FlatMap.FlatMap k) instance Data.Foldable.Foldable (Z.Data.Vector.FlatMap.FlatMap k) instance Data.Traversable.Traversable (Z.Data.Vector.FlatMap.FlatMap k) -- | This module provides a simple int set based on sorted vector and -- binary search. It's particularly suitable for small sized value -- collections such as deserializing intermediate representation. But can -- also used in various place where insertion and deletion is rare but -- require fast elem. module Z.Data.Vector.FlatIntSet data FlatIntSet sortedValues :: FlatIntSet -> PrimVector Int size :: FlatIntSet -> Int null :: FlatIntSet -> Bool -- | O(1) empty flat set. empty :: FlatIntSet -- | Mapping values of within a set, the result size may change if there're -- duplicated values after mapping. map' :: (Int -> Int) -> FlatIntSet -> FlatIntSet -- | O(N*logN) Pack list of values, on duplication prefer left one. pack :: [Int] -> FlatIntSet -- | O(N*logN) Pack list of values with suggested size, on -- duplication prefer left one. packN :: Int -> [Int] -> FlatIntSet -- | O(N*logN) Pack list of values, on duplication prefer right one. packR :: [Int] -> FlatIntSet -- | O(N*logN) Pack list of values with suggested size, on -- duplication prefer right one. packRN :: Int -> [Int] -> FlatIntSet -- | O(N) Unpack a set of values to a list s in ascending order. -- -- This function works with foldr/build fusion in base. unpack :: FlatIntSet -> [Int] -- | O(N) Unpack a set of values to a list s in descending order. -- -- This function works with foldr/build fusion in base. unpackR :: FlatIntSet -> [Int] -- | O(N*logN) Pack vector of values, on duplication prefer left -- one. packVector :: PrimVector Int -> FlatIntSet -- | O(N*logN) Pack vector of values, on duplication prefer right -- one. packVectorR :: PrimVector Int -> FlatIntSet -- | O(logN) Binary search on flat set. elem :: Int -> FlatIntSet -> Bool -- | O(N) Delete a value. delete :: Int -> FlatIntSet -> FlatIntSet -- | O(N) Insert new value into set. insert :: Int -> FlatIntSet -> FlatIntSet -- | O(n+m) Merge two FlatIntSet, prefer right value on value -- duplication. merge :: FlatIntSet -> FlatIntSet -> FlatIntSet -- | Find the value's index in the vector slice, if value exists return -- Right, otherwise Left, i.e. the insert index -- -- This function only works on ascending sorted vectors. binarySearch :: PrimVector Int -> Int -> Either Int Int instance GHC.Classes.Ord Z.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Classes.Eq Z.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Show.Show Z.Data.Vector.FlatIntSet.FlatIntSet instance Z.Data.Text.Print.Print Z.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Base.Semigroup Z.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Base.Monoid Z.Data.Vector.FlatIntSet.FlatIntSet instance Control.DeepSeq.NFData Z.Data.Vector.FlatIntSet.FlatIntSet instance Test.QuickCheck.Arbitrary.Arbitrary Z.Data.Vector.FlatIntSet.FlatIntSet instance Test.QuickCheck.Arbitrary.CoArbitrary Z.Data.Vector.FlatIntSet.FlatIntSet -- | This module provides a simple int key value map based on sorted vector -- and binary search. It's particularly suitable for small sized key -- value collections such as deserializing intermediate representation. -- But can also used in various place where insertion and deletion is -- rare but require fast lookup. module Z.Data.Vector.FlatIntMap data FlatIntMap v sortedKeyValues :: FlatIntMap v -> Vector (IPair v) size :: FlatIntMap v -> Int null :: FlatIntMap v -> Bool -- | O(1) empty flat map. empty :: FlatIntMap v map' :: (v -> v') -> FlatIntMap v -> FlatIntMap v' imap' :: (Int -> v -> v') -> FlatIntMap v -> FlatIntMap v' -- | O(N*logN) Pack list of key values, on key duplication prefer -- left one. pack :: [IPair v] -> FlatIntMap v -- | O(N*logN) Pack list of key values with suggested size, on key -- duplication prefer left one. packN :: Int -> [IPair v] -> FlatIntMap v -- | O(N*logN) Pack list of key values, on key duplication prefer -- right one. packR :: [IPair v] -> FlatIntMap v -- | O(N*logN) Pack list of key values with suggested size, on key -- duplication prefer right one. packRN :: Int -> [IPair v] -> FlatIntMap v -- | O(N) Unpack key value pairs to a list sorted by keys in -- ascending order. -- -- This function works with foldr/build fusion in base. unpack :: FlatIntMap v -> [IPair v] -- | O(N) Unpack key value pairs to a list sorted by keys in -- descending order. -- -- This function works with foldr/build fusion in base. unpackR :: FlatIntMap v -> [IPair v] -- | O(N*logN) Pack vector of key values, on key duplication prefer -- left one. packVector :: Vector (IPair v) -> FlatIntMap v -- | O(N*logN) Pack vector of key values, on key duplication prefer -- right one. packVectorR :: Vector (IPair v) -> FlatIntMap v -- | O(logN) Binary search on flat map. lookup :: Int -> FlatIntMap v -> Maybe v -- | O(N) Delete a key value pair by key. delete :: Int -> FlatIntMap v -> FlatIntMap v -- | O(N) Insert new key value into map, replace old one if key -- exists. insert :: Int -> v -> FlatIntMap v -> FlatIntMap v -- | O(N) Modify a value by key. -- -- The value is evaluated to WHNF before writing into map. adjust' :: (v -> v) -> Int -> FlatIntMap v -> FlatIntMap v -- | O(n+m) Merge two FlatIntMap, prefer right value on key -- duplication. merge :: forall v. FlatIntMap v -> FlatIntMap v -> FlatIntMap v -- | O(n+m) Merge two FlatIntMap with a merge function. mergeWithKey' :: forall v. (Int -> v -> v -> v) -> FlatIntMap v -> FlatIntMap v -> FlatIntMap v -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding k is in descending order. foldrWithKey :: (Int -> v -> a -> a) -> a -> FlatIntMap v -> a -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding Int is in descending order. foldrWithKey' :: (Int -> v -> a -> a) -> a -> FlatIntMap v -> a -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding Int is in ascending order. foldlWithKey :: (a -> Int -> v -> a) -> a -> FlatIntMap v -> a -- | O(n) Reduce this map by applying a binary operator to all -- elements, using the given starting value (typically the right-identity -- of the operator). -- -- During folding Int is in ascending order. foldlWithKey' :: (a -> Int -> v -> a) -> a -> FlatIntMap v -> a -- | O(n). -- -- traverseWithKey f s == pack <$> -- traverse ((k, v) -> (,) k <$> f k v) (unpack -- m) That is, behaves exactly like a regular traverse except -- that the traversing function also has access to the key associated -- with a value. traverseWithKey :: Applicative t => (Int -> a -> t b) -> FlatIntMap a -> t (FlatIntMap b) -- | Find the key's index in the vector slice, if key exists return -- Right, otherwise Left, i.e. the insert index -- -- This function only works on ascending sorted vectors. binarySearch :: Vector (IPair v) -> Int -> Either Int Int instance GHC.Classes.Ord v => GHC.Classes.Ord (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Classes.Eq v => GHC.Classes.Eq (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Show.Show v => GHC.Show.Show (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance Z.Data.Text.Print.Print v => Z.Data.Text.Print.Print (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance Test.QuickCheck.Arbitrary.Arbitrary v => Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance Test.QuickCheck.Arbitrary.CoArbitrary v => Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Base.Semigroup (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Base.Monoid (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance Control.DeepSeq.NFData v => Control.DeepSeq.NFData (Z.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Base.Functor Z.Data.Vector.FlatIntMap.FlatIntMap instance Data.Foldable.Foldable Z.Data.Vector.FlatIntMap.FlatIntMap instance Data.Traversable.Traversable Z.Data.Vector.FlatIntMap.FlatIntMap -- | Binding to google's RE2, microsoft did a nice job on RE2 regex -- syntaxs: -- https://docs.microsoft.com/en-us/deployedge/edge-learnmore-regex. -- Note GHC string literals need \ to be escaped, e.g. -- --
--   >>> match (regex "([a-z0-9_\\.-]+)@([\\da-z\\.-]+)\\.([a-z\\.]{2,6})") "please end email to hello@world.com, foo@bar.com"
--   
--   >>> ("hello@world.com",[Just "hello",Just "world",Just "com"],", foo@bar.com")
--   
module Z.Data.Text.Regex -- | A compiled RE2 regex. data Regex -- | Compile a regex pattern, throw InvalidRegexPattern in case of -- illegal patterns. regex :: HasCallStack => Text -> Regex -- | RE2 Regex options. -- -- The options are (defaultRegexOpts in parentheses): -- --
--   posix_syntax     (false) restrict regexps to POSIX egrep syntax
--   longest_match    (false) search for longest match, not first match
--   log_errors       (true)  log syntax and execution errors to ERROR
--   max_mem          (8<<20)  approx. max memory footprint of RE2
--   literal          (false) interpret string as literal, not regexp
--   never_nl         (false) never match \n, even if it is in regexp
--   dot_nl           (false) dot matches everything including new line
--   never_capture    (false) parse all parens as non-capturing
--   case_sensitive   (true)  match is case-sensitive (regexp can override
--                              with (?i) unless in posix_syntax mode)
--   
-- -- The following options are only consulted when posix_syntax == true. -- When posix_syntax == false, these features are always enabled and -- cannot be turned off; to perform multi-line matching in that case, -- begin the regexp with (?m). -- --
--   perl_classes     (false) allow Perl's \d \s \w \D \S \W
--   word_boundary    (false) allow Perl's \b \B (word boundary and not)
--   one_line         (false) ^ and $ only match beginning and end of text
--   
data RegexOpts RegexOpts :: Bool -> Bool -> {-# UNPACK #-} !Int64 -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> Bool -> RegexOpts [posix_syntax] :: RegexOpts -> Bool [longest_match] :: RegexOpts -> Bool [max_mem] :: RegexOpts -> {-# UNPACK #-} !Int64 [literal] :: RegexOpts -> Bool [never_nl] :: RegexOpts -> Bool [dot_nl] :: RegexOpts -> Bool [never_capture] :: RegexOpts -> Bool [case_sensitive] :: RegexOpts -> Bool [perl_classes] :: RegexOpts -> Bool [word_boundary] :: RegexOpts -> Bool [one_line] :: RegexOpts -> Bool -- | Default regex options, see RegexOpts. defaultRegexOpts :: RegexOpts -- | Compile a regex pattern withOptions, throw InvalidRegexPattern -- in case of illegal patterns. regexOpts :: HasCallStack => RegexOpts -> Text -> Regex -- | Escape a piece of text literal so that it can be safely used in regex -- pattern. -- --
--   >>> escape "(\\d+)"
--   
--   >>> "\\(\\\\d\\+\\)"
--   
escape :: Text -> Text -- | capturing group number(including \0) regexCaptureNum :: Regex -> Int -- | Get back regex's pattern. regexPattern :: Regex -> Text -- | Exception thrown when using regex. data RegexException InvalidRegexPattern :: Text -> CallStack -> RegexException -- | Check if text matched regex pattern. test :: Regex -> Text -> Bool -- | Check if text matched regex pattern, if so return matched part, all -- capturing groups(from \1) and the text after matched part. -- -- Nothing indicate a non-matching capturing group, e.g. -- --
--   >>> match (regex "(foo)|(bar)baz") "barbazbla"
--   
--   >>> ("barbaz",[Nothing,Just "bar"], "bla")
--   
match :: Regex -> Text -> (Text, [Maybe Text], Text) -- | Replace matched part in input with a rewrite pattern. If no matched -- part found, return the original input. -- --
--   >>> replace (regex "red") False "A red fox with red fur" "yellow"
--   
--   >>> "A yellow fox with red fur"
--   
--   >>> replace (regex "red") True  "A red fox with red fur" "yellow"
--   
--   >>> "A yellow fox with yellow fur"
--   
replace :: Regex -> Bool -> Text -> Text -> Text -- | Extract capturing group to an extract pattern. If no matched capturing -- group found, return an empty string. -- --
--   >>> extract (regex "(\\d{4})-(\\d{2})-(\\d{2})") "Today is 2020-12-15" "month: \\2, date: \\3"
--   
--   >>> "month: 12, date: 15"
--   
extract :: Regex -> Text -> Text -> Text instance Z.Data.Text.Print.Print Z.Data.Text.Regex.Regex instance GHC.Generics.Generic Z.Data.Text.Regex.Regex instance GHC.Show.Show Z.Data.Text.Regex.Regex instance Z.Data.Text.Print.Print Z.Data.Text.Regex.RegexOpts instance GHC.Generics.Generic Z.Data.Text.Regex.RegexOpts instance GHC.Show.Show Z.Data.Text.Regex.RegexOpts instance GHC.Classes.Ord Z.Data.Text.Regex.RegexOpts instance GHC.Classes.Eq Z.Data.Text.Regex.RegexOpts instance GHC.Show.Show Z.Data.Text.Regex.RegexException instance GHC.Exception.Type.Exception Z.Data.Text.Regex.RegexException -- | A Text wrap a Bytes which will be interpreted using -- UTF-8 encoding. User should always use validate / -- validateMaybe to construt a Text (instead of using -- construtor directly or coercing), otherwise illegal UTF-8 encoded -- codepoints will cause undefined behaviours. -- -- This library also provide simple unicode processing based on -- utf8rewind, see normalize, caseFold (current -- using unicode 13 databases). module Z.Data.Text -- | Text represented as UTF-8 encoded Bytes data Text -- | Extract UTF-8 encoded Bytes from Text getUTF8Bytes :: Text -> Bytes -- | O(n) Validate a sequence of bytes is UTF-8 encoded. -- -- Throw InvalidUTF8Exception in case of invalid codepoint. validate :: HasCallStack => Bytes -> Text -- | O(n) Validate a sequence of bytes is all ascii char -- byte(<128). -- -- Throw InvalidASCIIException in case of invalid byte, It's not -- always faster than validate, use it only if you want to -- validate ASCII char sequences. validateASCII :: HasCallStack => Bytes -> Text -- | O(n) Validate a sequence of bytes is UTF-8 encoded. -- -- Return Nothing in case of invalid codepoint. validateMaybe :: Bytes -> Maybe Text -- | O(n) Validate a sequence of bytes is all ascii char -- byte(<128). -- -- Return Nothing in case of invalid byte. validateASCIIMaybe :: Bytes -> Maybe Text data TextException InvalidUTF8Exception :: CallStack -> TextException InvalidASCIIException :: CallStack -> TextException -- | first payload is invalid char index IndexOutOfTextRange :: Int -> CallStack -> TextException EmptyText :: CallStack -> TextException -- | O(n) Get the nth codepoint from Text, throw -- IndexOutOfTextRange when out of bound. index :: HasCallStack => Text -> Int -> Char -- | O(n) Get the nth codepoint from Text. indexMaybe :: Text -> Int -> Maybe Char -- | O(n) Get the nth codepoint from Text counting from the -- end, throw IndexOutOfVectorRange n callStack when out of -- bound. indexR :: HasCallStack => Text -> Int -> Char -- | O(n) Get the nth codepoint from Text counting from the -- end. indexMaybeR :: Text -> Int -> Maybe Char -- | O(1). Empty text. empty :: Text -- | O(1). Single char text. singleton :: Char -> Text -- | O(n). Copy a text from slice. copy :: Text -> Text -- | O(n) replicate char n time. replicate :: Int -> Char -> Text -- | O(n*m) cycleN a text n times. cycleN :: Int -> Text -> Text -- | O(n) Convert a string into a text -- -- Alias for packN defaultInitSize, will be -- rewritten to a memcpy if possible. pack :: String -> Text -- | O(n) Convert a list into a text with an approximate size(in -- bytes, not codepoints). -- -- If the encoded bytes length is larger than the size given, we simply -- double the buffer size and continue building. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packN :: Int -> String -> Text -- | O(n) Alias for packRN defaultInitSize. packR :: String -> Text -- | O(n) packN in reverse order. -- -- This function is a good consumer in the sense of build/foldr -- fusion. packRN :: Int -> String -> Text -- | O(n) Convert text to a char list. -- -- Unpacking is done lazily. i.e. we will retain reference to the array -- until all element are consumed. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpack :: Text -> String -- | O(n) Convert text to a list in reverse order. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpackR :: Text -> String -- | O(n) convert from a char vector. fromVector :: PrimVector Char -> Text -- | O(n) convert to a char vector. toVector :: Text -> PrimVector Char -- | A class similar to Show, serving the purpose that quickly -- convert a data type to a Text value. -- -- You can use newtype or generic deriving to implement instance of this -- class quickly: -- --
--    {-# LANGUAGE GeneralizedNewtypeDeriving #-}
--    {-# LANGUAGE DeriveAnyClass #-}
--    {-# LANGUAGE DeriveGeneric #-}
--    {-# LANGUAGE DerivingStrategies #-}
--   
--    import GHC.Generics
--   
--    newtype FooInt = FooInt Int deriving (Generic)
--                              deriving anyclass Print
--   
--   > toText (FooInt 3)
--   > "FooInt 3"
--   
--    newtype FooInt = FooInt Int deriving (Generic)
--                              deriving newtype Print
--   
--   > toText (FooInt 3)
--   > "3"
--   
class Print a -- | Convert data to Builder with precendence. -- -- You should return a Builder writing in UTF8 encoding only, i.e. -- --
--   Z.Data.Text.validateMaybe (Z.Data.Builder.buildBytes (toUTF8BuilderP p a)) /= Nothing
--   
toUTF8BuilderP :: Print a => Int -> a -> Builder () -- | Convert data to Builder with precendence. -- -- You should return a Builder writing in UTF8 encoding only, i.e. -- --
--   Z.Data.Text.validateMaybe (Z.Data.Builder.buildBytes (toUTF8BuilderP p a)) /= Nothing
--   
toUTF8BuilderP :: (Print a, Generic a, GToText (Rep a)) => Int -> a -> Builder () -- | Convert data to Text. toText :: Print a => a -> Text -- | Convert data to String, faster show replacement. toString :: Print a => a -> String -- | Convert data to Builder. toUTF8Builder :: Print a => a -> Builder () -- | Convert data to Bytes in UTF8 encoding. toUTF8Bytes :: Print a => a -> Bytes -- | O(1) Test whether a text is empty. null :: Text -> Bool -- | O(n) The char length of a text. length :: Text -> Int -- | O(m+n) -- -- There's no need to guard empty vector because we guard them for you, -- so appending empty text are no-ops. append :: Text -> Text -> Text -- | O(n) map f t is the Text -- obtained by applying f to each char of t. Performs -- replacement on invalid scalar values. map' :: (Char -> Char) -> Text -> Text -- | Strict mapping with index. imap' :: (Int -> Char -> Char) -> Text -> Text -- | Strict left to right fold. foldl' :: (b -> Char -> b) -> b -> Text -> b -- | Strict left to right fold with index. ifoldl' :: (b -> Int -> Char -> b) -> b -> Text -> b -- | Strict right to left fold foldr' :: (Char -> b -> b) -> b -> Text -> b -- | Strict right to left fold with index -- -- NOTE: the index is counting from 0, not backwards ifoldr' :: (Int -> Char -> b -> b) -> b -> Text -> b -- | O(n) Concatenate a list of text. -- -- Note: concat have to force the entire list to filter out empty -- text and calculate the length for allocation. concat :: [Text] -> Text -- | Map a function over a text and concatenate the results concatMap :: (Char -> Text) -> Text -> Text -- | O(n) count returns count of an element from a text. count :: Char -> Text -> Int -- | O(n) Applied to a predicate and text, all determines if -- all chars of the text satisfy the predicate. all :: (Char -> Bool) -> Text -> Bool -- | O(n) Applied to a predicate and a text, any determines -- if any chars of the text satisfy the predicate. any :: (Char -> Bool) -> Text -> Bool -- | Get the display width of a piece of text. -- -- You shouldn't pass texts with control characters(<0x20, \DEL), -- which are counted with -1 width. -- --
--   >>> displayWidth "你好世界!"
--   
--   >>> 10
--   
--   >>> displayWidth "hello world!"
--   
--   >>> 12
--   
displayWidth :: Text -> Int -- | O(n) cons is analogous to (:) for lists, but of -- different complexity, as it requires making a copy. cons :: Char -> Text -> Text -- | O(n) Append a char to the end of a text. snoc :: Text -> Char -> Text -- | O(1) Extract the head and tail of a text, return Nothing -- if it is empty. uncons :: Text -> Maybe (Char, Text) -- | O(1) Extract the init and last of a text, return Nothing -- if text is empty. unsnoc :: Text -> Maybe (Text, Char) -- | O(1) Extract the first char of a text. headMaybe :: Text -> Maybe Char -- | O(1) Extract the chars after the head of a text. -- -- NOTE: tailMayEmpty return empty text in the case of an empty -- text. tailMayEmpty :: Text -> Text -- | O(1) Extract the last char of a text. lastMaybe :: Text -> Maybe Char -- | O(1) Extract the chars before of the last one. -- -- NOTE: initMayEmpty return empty text in the case of an empty -- text. initMayEmpty :: Text -> Text -- | O(1) Extract the first char of a text. -- -- Throw EmptyText if text is empty. head :: Text -> Char -- | O(1) Extract the chars after the head of a text. -- -- Throw EmptyText if text is empty. tail :: Text -> Text -- | O(1) Extract the last char of a text. -- -- Throw EmptyText if text is empty. last :: Text -> Char -- | O(1) Extract the chars before of the last one. -- -- Throw EmptyText if text is empty. init :: Text -> Text -- | O(n) Return all initial segments of the given text, empty -- first. inits :: Text -> [Text] -- | O(n) Return all final segments of the given text, whole text -- first. tails :: Text -> [Text] -- | O(1) take n, applied to a text xs, -- returns the prefix of xs of length n, or xs -- itself if n > length xs. take :: Int -> Text -> Text -- | O(1) drop n xs returns the suffix of -- xs after the first n char, or [] if n -- > length xs. drop :: Int -> Text -> Text -- | O(1) takeR n, applied to a text xs, -- returns the suffix of xs of length n, or xs -- itself if n > length xs. takeR :: Int -> Text -> Text -- | O(1) dropR n xs returns the prefix of -- xs before the last n char, or [] if n -- > length xs. dropR :: Int -> Text -> Text -- | O(1) Extract a sub-range text with give start index and length. -- -- This function is a total function just like 'takedrop', -- indexlength exceeds range will be ingored, e.g. -- --
--   slice 1 3 "hello"   == "ell"
--   slice -1 -1 "hello" == ""
--   slice -2 2 "hello"  == ""
--   slice 2 10 "hello"  == "llo"
--   
-- -- This holds for all x y: slice x y vs == drop x . take (x+y) -- vs slice :: Int -> Int -> Text -> Text -- | O(n) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Int -> Text -> (Text, Text) -- | O(n) Applied to a predicate p and a text t, -- returns the longest prefix (possibly empty) of t of elements -- that satisfy p. takeWhile :: (Char -> Bool) -> Text -> Text -- | O(n) Applied to a predicate p and a text t, -- returns the longest suffix (possibly empty) of t of elements -- that satisfy p. takeWhileR :: (Char -> Bool) -> Text -> Text -- | O(n) Applied to a predicate p and a text vs, -- returns the suffix (possibly empty) remaining after takeWhile -- p vs. dropWhile :: (Char -> Bool) -> Text -> Text -- | O(n) Applied to a predicate p and a text vs, -- returns the prefix (possibly empty) remaining before takeWhileR -- p vs. dropWhileR :: (Char -> Bool) -> Text -> Text -- | O(n) dropAround f = dropWhile f . dropWhileR f dropAround :: (Char -> Bool) -> Text -> Text -- | O(n) Split the text into the longest prefix of elements that do -- not satisfy the predicate and the rest without copying. break :: (Char -> Bool) -> Text -> (Text, Text) -- | O(n) Split the text into the longest prefix of elements that -- satisfy the predicate and the rest without copying. span :: (Char -> Bool) -> Text -> (Text, Text) -- | breakR behaves like break but from the end of the text. -- --
--   breakR p == spanR (not.p)
--   
breakR :: (Char -> Bool) -> Text -> (Text, Text) -- | spanR behaves like span but from the end of the text. spanR :: (Char -> Bool) -> Text -> (Text, Text) -- | Break a text on a subtext, returning a pair of the part of the text -- prior to the match, and the rest of the text, e.g. -- --
--   break "wor" "hello, world" = ("hello, ", "world")
--   
breakOn :: Text -> Text -> (Text, Text) -- | O(n+m) Find all non-overlapping instances of needle in haystack. Each -- element of the returned list consists of a pair: -- -- -- -- Examples: -- --
--   breakOnAll "::" ""
--   ==> []
--   breakOnAll "" "abc"
--   ==> [("a", "bc"), ("ab", "c"), ("abc", "/")]
--   
-- -- The result list is lazy, search is performed when you force the list. breakOnAll :: Text -> Text -> [(Text, Text)] -- | The group function takes a text and returns a list of texts 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 groupBy, which allows the programmer to -- supply their own equality test. group :: Text -> [Text] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (Char -> Char -> Bool) -> Text -> [Text] -- | O(n) The stripPrefix function takes two texts and -- returns Just the remainder of the second iff the first is its -- prefix, and otherwise Nothing. stripPrefix :: Text -> Text -> Maybe Text -- | O(n) The stripSuffix function takes two texts and returns Just -- the remainder of the second iff the first is its suffix, and otherwise -- Nothing. stripSuffix :: Text -> Text -> Maybe Text -- | O(n) Break a text into pieces separated by the delimiter -- element 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 -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- NOTE, this function behavior different with bytestring's. see -- #56. split :: Char -> Text -> [Text] -- | O(n) Splits a text into components delimited by separators, -- where the predicate returns True for a separator char. The resulting -- components do not contain the separators. Two adjacent separators -- result in an empty component in the output. eg. -- --
--   splitWith (=='a') "aabbaca" == ["","","bb","c",""]
--   splitWith (=='a') []        == [""]
--   
splitWith :: (Char -> Bool) -> Text -> [Text] -- | O(m+n) Break haystack into pieces separated by needle. -- -- Note: An empty needle will essentially split haystack element by -- element. -- -- Examples: -- --
--   >>> splitOn "\r\n" "a\r\nb\r\nd\r\ne"
--   ["a","b","d","e"]
--   
-- --
--   >>> splitOn "aaa"  "aaaXaaaXaaaXaaa"
--   ["","X","X","X",""]
--   
-- --
--   >>> splitOn "x"  "x"
--   ["",""]
--   
-- -- and -- --
--   intercalate s . splitOn s         == id
--   splitOn (singleton c)             == split (==c)
--   
splitOn :: Text -> Text -> [Text] -- | The isPrefix function returns True if the first -- argument is a prefix of the second. isPrefixOf :: Text -> Text -> Bool -- | O(n) The isSuffixOf function takes two text and returns -- True if the first is a suffix of the second. isSuffixOf :: Text -> Text -> Bool -- | Check whether one text is a subtext of another. -- -- needle isInfixOf haystack === null haystack || indices -- needle haystake /= []. isInfixOf :: Text -> Text -> Bool -- | O(n) Find the longest non-empty common prefix of two strings -- and return it, along with the suffixes of each string at which they no -- longer match. e.g. -- --
--   >>> commonPrefix "foobar" "fooquux"
--   ("foo","bar","quux")
--   
-- --
--   >>> commonPrefix "veeble" "fetzer"
--   ("","veeble","fetzer")
--   
commonPrefix :: Text -> Text -> (Text, Text, Text) -- | O(n) Breaks a Bytes up into a list of words, delimited -- by unicode space. words :: Text -> [Text] -- | O(n) Breaks a text up into a list of lines, delimited by ascii -- n. lines :: Text -> [Text] -- | O(n) Joins words with ascii space. unwords :: [Text] -> Text -- | O(n) Joins lines with ascii n. -- -- NOTE: This functions is different from unlines, it DOES NOT add -- a trailing n. unlines :: [Text] -> Text -- | Add padding to the left so that the whole text's length is at least n. padLeft :: Int -> Char -> Text -> Text -- | Add padding to the right so that the whole text's length is at least -- n. padRight :: Int -> Char -> Text -> Text -- | O(n) Reverse the characters of a string. reverse :: Text -> Text -- | O(n) The intersperse function takes a character and -- places it between the characters of a Text. Performs -- replacement on invalid scalar values. intersperse :: Char -> Text -> Text -- | O(n) The intercalate function takes a Text and a -- list of Texts and concatenates the list after interspersing the -- first argument between each element of the list. intercalate :: Text -> [Text] -> Text intercalateElem :: Char -> [Text] -> Text -- | The transpose function transposes the rows and columns of its -- text argument. transpose :: [Text] -> [Text] -- | O(n) elem test if given char is in given text. elem :: Char -> Text -> Bool -- | O(n) not . elem notElem :: Char -> Text -> Bool -- | O(n) find the first char matching the predicate in a text from -- left to right, if there isn't one, return the text length. find :: (Char -> Bool) -> Text -> (Int, Maybe Char) -- | O(n) find the first char matching the predicate in a text from -- right to left. findR :: (Char -> Bool) -> Text -> (Int, Maybe Char) -- | O(n) filter, applied to a predicate and a text, returns -- a text containing those chars that satisfy the predicate. filter :: (Char -> Bool) -> Text -> Text -- | O(n) The partition function takes a predicate, a text, -- returns a pair of text with codepoints which do and do not satisfy the -- predicate, respectively; i.e., -- --
--   partition p txt == (filter p txt, filter (not . p) txt)
--   
partition :: (Char -> Bool) -> Text -> (Text, Text) data NormalizationResult NormalizedYes :: NormalizationResult NormalizedMaybe :: NormalizationResult NormalizedNo :: NormalizationResult -- | These are the Unicode Normalization Forms: -- --
--   Form                         | Description
--   ---------------------------- | ---------------------------------------------
--   Normalization Form D (NFD)   | Canonical decomposition
--   Normalization Form C (NFC)   | Canonical decomposition, followed by canonical composition
--   Normalization Form KD (NFKD) | Compatibility decomposition
--   Normalization Form KC (NFKC) | Compatibility decomposition, followed by canonical composition
--   
data NormalizeMode NFC :: NormalizeMode NFKC :: NormalizeMode NFD :: NormalizeMode NFKD :: NormalizeMode -- | Check if a string is stable in the NFC (Normalization Form C). isNormalized :: Text -> NormalizationResult -- | Check if a string is stable in the specified Unicode Normalization -- Form. -- -- This function can be used as a preprocessing step, before attempting -- to normalize a string. Normalization is a very expensive process, it -- is often cheaper to first determine if the string is unstable in the -- requested normalization form. -- -- The result of the check will be YES if the string is stable and MAYBE -- or NO if it is unstable. If the result is MAYBE, the string does not -- necessarily have to be normalized. -- -- For more information, please review -- <http://www.unicode.org/reports/tr15/ Unicode Standard Annex -- #15 - Unicode Normalization Forms>. isNormalizedTo :: NormalizeMode -> Text -> NormalizationResult -- | Normalize a string to NFC (Normalization Form C). normalize :: Text -> Text -- | Normalize a string to the specified Unicode Normalization Form. -- -- The Unicode standard defines two standards for equivalence between -- characters: canonical and compatibility equivalence. Canonically -- equivalent characters and sequence represent the same abstract -- character and must be rendered with the same appearance and behavior. -- Compatibility equivalent characters have a weaker equivalence and may -- be rendered differently. -- -- Unicode Normalization Forms are formally defined standards that can be -- used to test whether any two strings of characters are equivalent to -- each other. This equivalence may be canonical or compatibility. -- -- The algorithm puts all combining marks into a specified order and uses -- the rules for decomposition and composition to transform the string -- into one of four Unicode Normalization Forms. A binary comparison can -- then be used to determine equivalence. normalizeTo :: NormalizeMode -> Text -> Text -- | Get environment locale envLocale :: IO Locale -- | Remove case distinction from UTF-8 encoded text with default locale. caseFold :: Text -> Text -- | Remove case distinction from UTF-8 encoded text. -- -- Case folding is the process of eliminating differences between code -- points concerning case mapping. It is most commonly used for comparing -- strings in a case-insensitive manner. Conversion is fully compliant -- with the Unicode 7.0 standard. -- -- Although similar to lowercasing text, there are significant -- differences. For one, case folding does _not_ take locale into account -- when converting. In some cases, case folding can be up to 20% faster -- than lowercasing the same text, but the result cannot be treated as -- correct lowercased text. -- -- Only two locale-specific exception are made when case folding text. In -- Turkish, U+0049 LATIN CAPITAL LETTER I maps to U+0131 LATIN SMALL -- LETTER DOTLESS I and U+0130 LATIN CAPITAL LETTER I WITH DOT ABOVE maps -- to U+0069 LATIN SMALL LETTER I. -- -- Although most code points can be case folded without changing length, -- there are notable exceptions. For example, U+0130 (LATIN CAPITAL -- LETTER I WITH DOT ABOVE) maps to "U+0069 U+0307" (LATIN SMALL LETTER I -- and COMBINING DOT ABOVE) when converted to lowercase. -- -- Only a handful of scripts make a distinction between upper- and -- lowercase. In addition to modern scripts, such as Latin, Greek, -- Armenian and Cyrillic, a few historic or archaic scripts have case. -- The vast majority of scripts do not have case distinctions. caseFoldWith :: Locale -> Text -> Text -- | Convert UTF-8 encoded text to lowercase with default locale. toLower :: Text -> Text -- | Convert UTF-8 encoded text to lowercase. -- -- This function allows conversion of UTF-8 encoded strings to lowercase -- without first changing the encoding to UTF-32. Conversion is fully -- compliant with the Unicode 7.0 standard. -- -- Although most code points can be converted to lowercase with changing -- length, there are notable exceptions. For example, U+0130 (LATIN -- CAPITAL LETTER I WITH DOT ABOVE) maps to "U+0069 U+0307" (LATIN SMALL -- LETTER I and COMBINING DOT ABOVE) when converted to lowercase. -- -- Only a handful of scripts make a distinction between upper- and -- lowercase. In addition to modern scripts, such as Latin, Greek, -- Armenian and Cyrillic, a few historic or archaic scripts have case. -- The vast majority of scripts do not have case distinctions. -- -- Case mapping is not reversible. That is, toUpper(toLower(x)) != -- toLower(toUpper(x)). -- -- Certain code points (or combinations of code points) apply rules based -- on the locale. For more information about these exceptional code -- points, please refer to the Unicode standard: -- ftp://ftp.unicode.org/Public/UNIDATA/SpecialCasing.txt toLowerWith :: Locale -> Text -> Text -- | Convert UTF-8 encoded text to uppercase with default locale. toUpper :: Text -> Text -- | Convert UTF-8 encoded text to uppercase. -- -- Conversion is fully compliant with the Unicode 7.0 standard. -- -- Although most code points can be converted without changing length, -- there are notable exceptions. For example, U+00DF (LATIN SMALL LETTER -- SHARP S) maps to "U+0053 U+0053" (LATIN CAPITAL LETTER S and LATIN -- CAPITAL LETTER S) when converted to uppercase. -- -- Only a handful of scripts make a distinction between upper and -- lowercase. In addition to modern scripts, such as Latin, Greek, -- Armenian and Cyrillic, a few historic or archaic scripts have case. -- The vast majority of scripts do not have case distinctions. -- -- Case mapping is not reversible. That is, toUpper(toLower(x)) != -- toLower(toUpper(x)). -- -- Certain code points (or combinations of code points) apply rules based -- on the locale. For more information about these exceptional code -- points, please refer to the Unicode standard: -- ftp://ftp.unicode.org/Public/UNIDATA/SpecialCasing.txt toUpperWith :: Locale -> Text -> Text -- | Convert UTF-8 encoded text to titlecase with default locale. toTitle :: Text -> Text -- | Convert UTF-8 encoded text to titlecase. -- -- This function allows conversion of UTF-8 encoded strings to titlecase. -- Conversion is fully compliant with the Unicode 7.0 standard. -- -- Titlecase requires a bit more explanation than uppercase and -- lowercase, because it is not a common text transformation. Titlecase -- uses uppercase for the first letter of each word and lowercase for the -- rest. Words are defined as "collections of code points with general -- category Lu, Ll, Lt, Lm or Lo according to the Unicode database". -- -- Effectively, any type of punctuation can break up a word, even if this -- is not grammatically valid. This happens because the titlecasing -- algorithm does not and cannot take grammar rules into account. -- --
--   Text                                 | Titlecase
--   -------------------------------------|-------------------------------------
--   The running man                      | The Running Man
--   NATO Alliance                        | Nato Alliance
--   You're amazing at building libraries | You'Re Amazing At Building Libraries
--   
-- -- Although most code points can be converted to titlecase without -- changing length, there are notable exceptions. For example, U+00DF -- (LATIN SMALL LETTER SHARP S) maps to "U+0053 U+0073" (LATIN CAPITAL -- LETTER S and LATIN SMALL LETTER S) when converted to titlecase. -- -- Certain code points (or combinations of code points) apply rules based -- on the locale. For more information about these exceptional code -- points, please refer to the Unicode standard: -- ftp://ftp.unicode.org/Public/UNIDATA/SpecialCasing.txt toTitleWith :: Locale -> Text -> Text -- | Check if the input string conforms to the category specified by the -- flags. -- -- This function can be used to check if the code points in a string are -- part of a category. Valid flags are members of the "list of -- categories". The category for a code point is defined as part of the -- entry in UnicodeData.txt, the data file for the Unicode code point -- database. -- -- By default, the function will treat grapheme clusters as a single code -- point. This means that the following string: -- --
--   Code point | Canonical combining class | General category      | Name
--   ---------- | ------------------------- | --------------------- | ----------------------
--   U+0045     | 0                         | Lu (Uppercase letter) | LATIN CAPITAL LETTER E
--   U+0300     | 230                       | Mn (Non-spacing mark) | COMBINING GRAVE ACCENT
--   
-- -- Will match with CategoryLetterUppercase in its entirety, -- because the COMBINING GRAVE ACCENT is treated as part of the grapheme -- cluster. This is useful when e.g. creating a text parser, because you -- do not have to normalize the text first. -- -- If this is undesired behavior, specify the -- CategoryIgnoreGraphemeCluster flag. -- -- In order to maintain backwards compatibility with POSIX functions like -- isdigit and isspace, compatibility flags have been -- provided. Note, however, that the result is only guaranteed to be -- correct for code points in the Basic Latin range, between U+0000 and -- 0+007F. Combining a compatibility flag with a regular category flag -- will result in undefined behavior. isCategory :: Category -> Text -> Bool -- | Try to match as many code points with the matching category flags as -- possible and return the prefix and suffix. spanCategory :: Category -> Text -> (Text, Text) -- | Locale for case mapping. type Locale = CSize pattern LocaleDefault :: Locale pattern LocaleLithuanian :: Locale pattern LocaleTurkishAndAzeriLatin :: Locale -- | Unicode categories. -- -- See isCategory, you can combine categories with bitwise or. type Category = CSize pattern CategoryLetterUppercase :: Category pattern CategoryLetterLowercase :: Category pattern CategoryLetterTitlecase :: Category pattern CategoryLetterOther :: Category pattern CategoryLetter :: Category pattern CategoryCaseMapped :: Category pattern CategoryMarkNonSpacing :: Category pattern CategoryMarkSpacing :: Category pattern CategoryMarkEnclosing :: Category pattern CategoryMark :: Category pattern CategoryNumberDecimal :: Category pattern CategoryNumberLetter :: Category pattern CategoryNumberOther :: Category pattern CategoryNumber :: Category pattern CategoryPunctuationConnector :: Category pattern CategoryPunctuationDash :: Category pattern CategoryPunctuationOpen :: Category pattern CategoryPunctuationClose :: Category pattern CategoryPunctuationInitial :: Category pattern CategoryPunctuationFinal :: Category pattern CategoryPunctuationOther :: Category pattern CategoryPunctuation :: Category pattern CategorySymbolMath :: Category pattern CategorySymbolCurrency :: Category pattern CategorySymbolModifier :: Category pattern CategorySymbolOther :: Category pattern CategorySymbol :: Category pattern CategorySeparatorSpace :: Category pattern CategorySeparatorLine :: Category pattern CategorySeparatorParagraph :: Category pattern CategorySeparator :: Category pattern CategoryControl :: Category pattern CategoryFormat :: Category pattern CategorySurrogate :: Category pattern CategoryPrivateUse :: Category pattern CategoryUnassigned :: Category pattern CategoryCompatibility :: Category pattern CategoryIgnoreGraphemeCluster :: Category pattern CategoryIscntrl :: Category pattern CategoryIsprint :: Category pattern CategoryIsspace :: Category pattern CategoryIsblank :: Category pattern CategoryIsgraph :: Category pattern CategoryIspunct :: Category pattern CategoryIsalnum :: Category pattern CategoryIsalpha :: Category pattern CategoryIsupper :: Category pattern CategoryIslower :: Category pattern CategoryIsdigit :: Category pattern CategoryIsxdigit :: Category -- | This module provides definition and parsers for JSON Values, a -- Haskell JSON representation. The parsers is designed to comply with -- rfc8258, notable pitfalls are: -- -- -- -- Note that rfc8258 doesn't enforce unique key in objects, it's up to -- users to decided how to deal with key duplication, e.g. prefer first -- or last key, see withFlatMap or withFlatMapR for -- example. -- -- There's no lazy parsers here, every pieces of JSON document will be -- parsed into a normal form Value. Object and -- Arrays payloads are packed into Vectors to avoid -- accumulating lists in memory. Read more about why no lazy parsing -- is needed. module Z.Data.JSON.Value -- | A JSON value represented as a Haskell value. -- -- The Object's payload is a key-value vector instead of a map, -- which parsed directly from JSON document. This design choice has -- following advantages: -- -- data Value Object :: {-# UNPACK #-} !Vector (Text, Value) -> Value Array :: {-# UNPACK #-} !Vector Value -> Value String :: {-# UNPACK #-} !Text -> Value Number :: {-# UNPACK #-} !Scientific -> Value Bool :: !Bool -> Value Null :: Value -- | Lense for Object element -- --
    --
  1. return Null if Value is not an Object or key -- not exist.
  2. --
  3. Modify will have no effect if Value is not an Object -- or key not exist.
  4. --
  5. On duplicated keys prefer the last one.
  6. --
key :: Functor f => Text -> (Value -> f Value) -> Value -> f Value -- | Lense for Array element. -- --
    --
  1. return Null if Value is not an Array or index -- not exist.
  2. --
  3. Modify will have no effect if Value is not an Array -- or index not exist.
  4. --
nth :: Functor f => Int -> (Value -> f Value) -> Value -> f Value -- | Parse Value without consuming trailing bytes. parseValue :: Bytes -> (Bytes, Either ParseError Value) -- | Parse Value, and consume all trailing JSON white spaces, if -- there're bytes left, parsing will fail. parseValue' :: Bytes -> Either ParseError Value -- | Increamental parse Value without consuming trailing bytes. parseValueChunks :: Monad m => ParseChunks m Bytes ParseError Value -- | JSON Value parser. value :: Parser Value -- | parse json array with leading 123. object :: Parser (Vector (Text, Value)) -- | parse json array with leading 91. array :: Parser (Vector Value) string :: Parser Text -- | The only valid whitespace in a JSON document is space, newline, -- carriage pure, and tab. skipSpaces :: Parser () -- | Convert IEEE float to scientific notition. floatToScientific :: Float -> Scientific -- | Convert IEEE double to scientific notition. doubleToScientific :: Double -> Scientific instance Z.Data.Text.Print.Print Z.Data.JSON.Value.Value instance GHC.Generics.Generic Z.Data.JSON.Value.Value instance GHC.Show.Show Z.Data.JSON.Value.Value instance GHC.Classes.Ord Z.Data.JSON.Value.Value instance GHC.Classes.Eq Z.Data.JSON.Value.Value instance Control.DeepSeq.NFData Z.Data.JSON.Value.Value instance Test.QuickCheck.Arbitrary.Arbitrary Z.Data.JSON.Value.Value -- | Builders for dates and times. module Z.Data.Builder.Time -- | YYYY-mm-dd. day :: Day -> Builder () -- | HH-MM-SS. timeOfDay :: TimeOfDay -> Builder () -- | Timezone format in +HH:MM, with single letter Z for -- +00:00. timeZone :: TimeZone -> Builder () -- | Write UTCTime in ISO8061 YYYY-MM-DDTHH:MM:SS.SSSZ(time -- zone will always be Z). utcTime :: UTCTime -> Builder () -- | Write LocalTime in ISO8061 YYYY-MM-DDTHH:MM:SS.SSS. localTime :: LocalTime -> Builder () -- | Write ZonedTime in ISO8061 YYYY-MM-DD HH:MM:SS.SSSZ. zonedTime :: ZonedTime -> Builder () -- | A Builder records a buffer writing function, which can be -- mappend in O(1) via composition. This module provides many -- functions to turn basic data types into Builders, which can -- used to build strict Bytes or list of Bytes chunks. module Z.Data.Builder -- | Builder is a monad to help compose BuilderStep. With -- next BuilderStep continuation, we can do interesting things -- like perform some action, or interleave the build process. -- -- Notes on IsString instance: Builder ()'s -- IsString instance use stringModifiedUTF8, which is -- different from stringUTF8 in that it DOES NOT PROVIDE UTF8 -- GUARANTEES! : -- -- data Builder a append :: Builder a -> Builder b -> Builder b -- | Shortcut to buildWith defaultInitSize. build :: Builder a -> Bytes -- | Run Builder with doubling buffer strategy, which is suitable for -- building short bytes. buildWith :: Int -> Builder a -> Bytes -- | Shortcut to buildChunksWith defaultChunkSize. buildChunks :: Builder a -> [Bytes] -- | Run Builder with inserting chunk strategy, which is suitable for -- building a list of bytes chunks and processing them in a streaming -- ways. -- -- Note the building process is lazy, building happens when list chunks -- are consumed. buildChunksWith :: Int -> Int -> Builder a -> [Bytes] -- | Build some bytes and validate if it's UTF8 bytes. buildText :: HasCallStack => Builder a -> Text -- | Build some bytes assuming it's UTF8 encoding. -- -- Be carefully use this function because you could constrcut illegal -- Text values. Check ShowT for UTF8 encoding builders. -- This functions is intended to be used in debug only. unsafeBuildText :: Builder a -> Text -- | Write a Bytes. bytes :: Bytes -> Builder () ensureN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO Int) -> Builder () writeN :: Int -> (MutablePrimArray RealWorld Word8 -> Int -> IO ()) -> Builder () -- | Write a primitive type in host byte order. -- --
--   > encodePrim (256 :: Word16, BE 256 :: BE Word16)
--   > [0,1,1,0]
--   
encodePrim :: forall a. Unaligned a => a -> Builder () -- | big endianess wrapper newtype BE a BE :: a -> BE a [getBE] :: BE a -> a -- | little endianess wrapper newtype LE a LE :: a -> LE a [getLE] :: LE a -> a -- | Write a primitive type with little endianess. encodePrimLE :: forall a. Unaligned (LE a) => a -> Builder () -- | Write a primitive type with big endianess. encodePrimBE :: forall a. Unaligned (BE a) => a -> Builder () -- | Encode string with modified UTF-8 encoding, will be rewritten to a -- memcpy if possible. stringModifiedUTF8 :: String -> Builder () -- | Turn Char into Builder with Modified UTF8 encoding -- -- \NUL is encoded as two bytes C0 80 , \xD800 -- ~ \xDFFF is encoded as a three bytes normal UTF-8 codepoint. charModifiedUTF8 :: Char -> Builder () -- | Turn String into Builder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. -- -- This is different from writing string literals builders via -- OverloadedStrings, because string literals do not provide -- UTF8 guarantees. -- -- This function will be rewritten into a memcpy if possible, (running a -- fast UTF-8 validation at runtime first). stringUTF8 :: String -> Builder () -- | Turn Char into Builder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. charUTF8 :: Char -> Builder () -- | Turn String into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. string7 :: String -> Builder () -- | Turn Char into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. char7 :: Char -> Builder () -- | Turn Word8 into Builder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. word7 :: Word8 -> Builder () -- | Turn String into Builder with ASCII8 encoding -- -- Codepoints beyond 'xFF' will be chopped. Note, this encoding -- is NOT compatible with UTF8 encoding, i.e. bytes written by this -- builder may not be legal UTF8 encoding bytes. string8 :: String -> Builder () -- | Turn Char into Builder with ASCII8 encoding -- -- Codepoints beyond 'xFF' will be chopped. Note, this encoding -- is NOT compatible with UTF8 encoding, i.e. bytes written by this -- builder may not be legal UTF8 encoding bytes. char8 :: Char -> Builder () -- | Turn Word8 into Builder with ASCII8 encoding, (alias to -- encodePrim). -- -- Note, this encoding is NOT compatible with UTF8 encoding, i.e. bytes -- written by this builder may not be legal UTF8 encoding bytes. word8 :: Word8 -> Builder () -- | Faster version of replicateM x . word8 by using -- memset. -- -- Note, this encoding is NOT compatible with UTF8 encoding, i.e. bytes -- written by this builder may not be legal UTF8 encoding bytes. word8N :: Int -> Word8 -> Builder () -- | Write UTF8 encoded Text using Builder. -- -- Note, if you're trying to write string literals builders, please open -- OverloadedStrings and use Builders IsString -- instance, it will be rewritten into a memcpy. text :: Text -> Builder () -- | Integral formatting options. data IFormat IFormat :: Int -> Padding -> Bool -> IFormat -- | total width, only effective with padding options [width] :: IFormat -> Int -- | padding options [padding] :: IFormat -> Padding -- | show + when the number is positive [posSign] :: IFormat -> Bool -- |
--   defaultIFormat = IFormat 0 NoPadding False
--   
defaultIFormat :: IFormat data Padding NoPadding :: Padding RightSpacePadding :: Padding LeftSpacePadding :: Padding ZeroPadding :: Padding -- |
--   int = intWith defaultIFormat
--   
int :: (Integral a, Bounded a) => a -> Builder () -- | Format a Bounded Integral type like Int or -- Word16 into decimal ASCII digits. -- --
--   import Z.Data.Builder as B
--   
--   > B.buildText $ B.intWith defaultIFormat  (12345 :: Int)
--   "12345"
--   > B.buildText $ B.intWith defaultIFormat{width=10, padding=RightSpacePadding} (12345 :: Int)
--   "12345     "
--   > B.buildText $ B.intWith defaultIFormat{width=10, padding=ZeroPadding} (12345 :: Int)
--   "0000012345"
--   
intWith :: (Integral a, Bounded a) => IFormat -> a -> Builder () -- | Format a Integer into decimal ASCII digits. integer :: Integer -> Builder () -- | Format a FiniteBits Integral type into hex nibbles. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Data.Word
--   import Data.Int
--   
--   > T.validate . B.buildBytes $ B.hex (125 :: Int8)
--   "7d"
--   > T.validate . B.buildBytes $ B.hex (-1 :: Int8)
--   "ff"
--   > T.validate . B.buildBytes $ B.hex (125 :: Word16)
--   "007d"
--   
hex :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | The UPPERCASED version of hex. hexUpper :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | Control the rendering of floating point numbers. data FFormat -- | Scientific notation (e.g. 2.3e123). Exponent :: FFormat -- | Standard decimal notation. Fixed :: FFormat -- | Use decimal notation for values between 0.1 and -- 9,999,999, and scientific notation otherwise. Generic :: FFormat -- | Decimal encoding of an IEEE Double. -- -- Using standard decimal notation for arguments whose absolute value -- lies between 0.1 and 9,999,999, and scientific -- notation otherwise. double :: Double -> Builder () -- | Format double-precision float using drisu3 with dragon4 fallback. doubleWith :: FFormat -> Maybe Int -> Double -> Builder () -- | Decimal encoding of an IEEE Float. -- -- Using standard decimal notation for arguments whose absolute value -- lies between 0.1 and 9,999,999, and scientific -- notation otherwise. float :: Float -> Builder () -- | Format single-precision float using drisu3 with dragon4 fallback. floatWith :: FFormat -> Maybe Int -> Float -> Builder () -- | A Builder which renders a scientific number to full -- precision, using standard decimal notation for arguments whose -- absolute value lies between 0.1 and 9,999,999, and -- scientific notation otherwise. scientific :: Scientific -> Builder () -- | Like scientific but provides rendering options. scientificWith :: FFormat -> Maybe Int -> Scientific -> Builder () -- | add (...) to original builder. paren :: Builder () -> Builder () -- | add {...} to original builder. curly :: Builder () -> Builder () -- | add [...] to original builder. square :: Builder () -> Builder () -- | add <...> to original builder. angle :: Builder () -> Builder () -- | add "..." to original builder. quotes :: Builder () -> Builder () -- | add '...' to original builder. squotes :: Builder () -> Builder () -- | write an ASCII : colon :: Builder () -- | write an ASCII , comma :: Builder () -- | Use separator to connect a vector of builders. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Z.Data.Vector  as V
--   
--   > T.validate . B.build $ B.intercalateVec "," B.int (V.pack [1,2,3,4] :: V.PrimVector Int)
--   "1,2,3,4"
--   
intercalateVec :: Vec v a => Builder () -> (a -> Builder ()) -> v a -> Builder () -- | Use separator to connect list of builders. -- --
--   import Z.Data.Builder as B
--   import Z.Data.Text    as T
--   import Z.Data.Vector  as V
--   
--   T.validate . B.build $ B.intercalateList "," B.int ([1,2,3,4] :: [Int])
--   "1,2,3,4"
--   
intercalateList :: Builder () -> (a -> Builder ()) -> [a] -> Builder () -- | YYYY-mm-dd. day :: Day -> Builder () -- | HH-MM-SS. timeOfDay :: TimeOfDay -> Builder () -- | Timezone format in +HH:MM, with single letter Z for -- +00:00. timeZone :: TimeZone -> Builder () -- | Write UTCTime in ISO8061 YYYY-MM-DDTHH:MM:SS.SSSZ(time -- zone will always be Z). utcTime :: UTCTime -> Builder () -- | Write LocalTime in ISO8061 YYYY-MM-DDTHH:MM:SS.SSS. localTime :: LocalTime -> Builder () -- | Write ZonedTime in ISO8061 YYYY-MM-DD HH:MM:SS.SSSZ. zonedTime :: ZonedTime -> Builder () -- | This module provides builders for JSON Values, a Haskell JSON -- representation. These builders are designed to comply with -- rfc8258. Only control characters are escaped, other unicode -- codepoints are directly written instead of being escaped. module Z.Data.JSON.Builder -- | Encode a Value, you can use this function with toValue -- to get encodeJSON with a small overhead. value :: Value -> Builder () object :: Vector (Text, Value) -> Builder () object' :: (a -> Builder ()) -> Vector (Text, a) -> Builder () array :: Vector Value -> Builder () array' :: (a -> Builder ()) -> Vector a -> Builder () -- | Escape text into JSON string and add double quotes, escaping rules: -- --
--   '\b':  "\b"
--   '\f':  "\f"
--   '\n':  "\n"
--   '\r':  "\r"
--   '\t':  "\t"
--   '"':  "\""
--   '\':  "\\"
--   'DEL':  "\u007f"
--   other chars <= 0x1F: "\u00XX"
--   
string :: Text -> Builder () -- | This builder try to render integer when (0 <= e < 16), and -- scientific notation otherwise. scientific :: Scientific -> Builder () -- | 'ValuePretty'' with 4 spaces indentation per level, e.g. -- --
--   {
--       "results":
--       [
--           {
--               "from_user_id_str":"80430860",
--               "profile_image_url":"http://a2.twimg.com/profile_images/536455139/icon32_normal.png",
--               "created_at":"Wed, 26 Jan 2011 07:07:02 +0000",
--               "from_user":"kazu_yamamoto",
--               "id_str":"30159761706061824",
--               "metadata":
--               {
--                   "result_type":"recent"
--               },
--               "to_user_id":null,
--               "text":"Haskell Server Pages って、まだ続いていたのか!",
--               "id":30159761706061824,
--               "from_user_id":80430860,
--               "geo":null,
--               "iso_language_code":"no",
--               "to_user_id_str":null,
--               "source":"&lt;a href=&quot;http:/twitter.com&quot;&gt;web&lt;/a&gt;"
--           }
--       ],
--       "max_id":30159761706061824,
--       "since_id":0,
--       "refresh_url":"?since_id=30159761706061824&q=haskell",
--       "next_page":"?page=2&max_id=30159761706061824&rpp=1&q=haskell",
--       "results_per_page":1,
--       "page":1,
--       "completed_in":1.2606e-2,
--       "since_id_str":"0",
--       "max_id_str":"30159761706061824",
--       "query":"haskell"
--   }
--   
prettyValue :: Value -> Builder () -- | Encode a Value with indentation and linefeed. prettyValue' :: Int -> Int -> Value -> Builder () -- | Use : as separator to connect a label(no escape, only add -- quotes) with field builders. -- -- Don't use chars which need escaped in label. kv :: Text -> Builder () -> Builder () -- | Use : as separator to connect a label(escape the label and -- add quotes) with field builders. kv' :: Text -> Builder () -> Builder () -- | A JSON value represented as a Haskell value. -- -- The Object's payload is a key-value vector instead of a map, -- which parsed directly from JSON document. This design choice has -- following advantages: -- -- data Value Object :: {-# UNPACK #-} !Vector (Text, Value) -> Value Array :: {-# UNPACK #-} !Vector Value -> Value String :: {-# UNPACK #-} !Text -> Value Number :: {-# UNPACK #-} !Scientific -> Value Bool :: !Bool -> Value Null :: Value -- | This module provides tools for converting protocol IR (e.g. -- Value) to Haskell ADTs: module Z.Data.JSON.Converter -- | Run a Converter with input value. convert :: (a -> Converter r) -> a -> Either ConvertError r -- | Elements of a (JSON) Value path used to describe the location of an -- error. data PathElement -- | Path element of a key into an object, "object.key". Key :: {-# UNPACK #-} !Text -> PathElement -- | Path element of an index into an array, "array[index]". Index :: {-# UNPACK #-} !Int -> PathElement -- | path of a embedded (JSON) String Embedded :: PathElement -- | Error info with (JSON) Path info. data ConvertError ConvertError :: [PathElement] -> Text -> ConvertError [errPath] :: ConvertError -> [PathElement] [errMsg] :: ConvertError -> Text -- | Converter provides a monadic interface to convert protocol IR -- (e.g.Value) to Haskell ADT. newtype Converter a Converter :: (forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r) -> Converter a [runConverter] :: Converter a -> forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r -- | Text version of fail. fail' :: Text -> Converter a -- | Add (JSON) Path context to a converter -- -- When converting a complex structure, it helps to annotate -- (sub)converters with context, so that if an error occurs, you can find -- its location. -- --
--   withFlatMapR "Person" $ \o ->
--     Person
--       <$> o .: "name" <?> Key "name"
--       <*> o .: "age" <?> Key "age"
--   
-- -- (Standard methods like (.:) already do this.) -- -- With such annotations, if an error occurs, you will get a (JSON) Path -- location of that error. () :: Converter a -> PathElement -> Converter a infixl 9 -- | Add context to a failure message, indicating the name of the structure -- being converted. -- --
--   prependContext "MyType" (fail "[error message]")
--   -- Error: "converting MyType failed, [error message]"
--   
prependContext :: Text -> Converter a -> Converter a instance Control.DeepSeq.NFData Z.Data.JSON.Converter.PathElement instance GHC.Generics.Generic Z.Data.JSON.Converter.PathElement instance GHC.Classes.Ord Z.Data.JSON.Converter.PathElement instance GHC.Show.Show Z.Data.JSON.Converter.PathElement instance GHC.Classes.Eq Z.Data.JSON.Converter.PathElement instance Control.DeepSeq.NFData Z.Data.JSON.Converter.ConvertError instance GHC.Generics.Generic Z.Data.JSON.Converter.ConvertError instance GHC.Classes.Ord Z.Data.JSON.Converter.ConvertError instance GHC.Classes.Eq Z.Data.JSON.Converter.ConvertError instance GHC.Base.Functor Z.Data.JSON.Converter.Converter instance GHC.Base.Applicative Z.Data.JSON.Converter.Converter instance GHC.Base.Alternative Z.Data.JSON.Converter.Converter instance GHC.Base.MonadPlus Z.Data.JSON.Converter.Converter instance GHC.Base.Monad Z.Data.JSON.Converter.Converter instance Control.Monad.Fail.MonadFail Z.Data.JSON.Converter.Converter instance GHC.Show.Show Z.Data.JSON.Converter.ConvertError instance Z.Data.Text.Print.Print Z.Data.JSON.Converter.ConvertError -- | This module provides Converter to convert Value to -- haskell data types, and various tools to help user define JSON -- instance. It's recommended to use Z.Data.JSON instead since it -- contain more instances. module Z.Data.JSON.Base -- | Type class for encode & decode JSON. class JSON a fromValue :: JSON a => Value -> Converter a fromValue :: (JSON a, Generic a, GFromValue (Rep a)) => Value -> Converter a toValue :: JSON a => a -> Value toValue :: (JSON a, Generic a, GToValue (Rep a)) => a -> Value encodeJSON :: JSON a => a -> Builder () encodeJSON :: (JSON a, Generic a, GEncodeJSON (Rep a)) => a -> Builder () -- | A JSON value represented as a Haskell value. -- -- The Object's payload is a key-value vector instead of a map, -- which parsed directly from JSON document. This design choice has -- following advantages: -- -- data Value Object :: {-# UNPACK #-} !Vector (Text, Value) -> Value Array :: {-# UNPACK #-} !Vector Value -> Value String :: {-# UNPACK #-} !Text -> Value Number :: {-# UNPACK #-} !Scientific -> Value Bool :: !Bool -> Value Null :: Value -- |
--   Settings T.pack T.pack False
--   
defaultSettings :: Settings -- | Generic encode/decode Settings -- -- There should be no control characters in formatted texts since we -- don't escaping those field names or constructor names -- (defaultSettings relys on Haskell's lexical property). -- Otherwise encodeJSON will output illegal JSON string. data Settings Settings :: (String -> Text) -> (String -> Text) -> Bool -> Settings -- | format field labels [fieldFmt] :: Settings -> String -> Text -- | format constructor names [constrFmt] :: Settings -> String -> Text -- | take missing field as Null? [missingKeyAsNull] :: Settings -> Bool type DecodeError = Either ParseError ConvertError -- | Decode a JSON bytes, return any trailing bytes. decode :: JSON a => Bytes -> (Bytes, Either DecodeError a) -- | Decode a JSON doc, only trailing JSON whitespace are allowed. decode' :: JSON a => Bytes -> Either DecodeError a -- | Decode a JSON text, return any trailing text. decodeText :: JSON a => Text -> (Text, Either DecodeError a) -- | Decode a JSON doc, only trailing JSON whitespace are allowed. decodeText' :: JSON a => Text -> Either DecodeError a -- | Type alias for a streaming parser, draw chunk from Monad m (with a -- initial chunk), return result in Either err x. type ParseChunks m chunk err x = m chunk -> chunk -> m (chunk, Either err x) -- | Decode JSON doc chunks, return trailing bytes. decodeChunks :: (JSON a, Monad m) => ParseChunks m Bytes DecodeError a -- | Directly encode data to JSON bytes. encode :: JSON a => a -> Bytes -- | Encode data to JSON bytes chunks. encodeChunks :: JSON a => a -> [Bytes] -- | Text version encode. encodeText :: JSON a => a -> Text -- | Directly encode data to JSON bytes. prettyJSON :: JSON a => a -> Builder () -- | 'ValuePretty'' with 4 spaces indentation per level, e.g. -- --
--   {
--       "results":
--       [
--           {
--               "from_user_id_str":"80430860",
--               "profile_image_url":"http://a2.twimg.com/profile_images/536455139/icon32_normal.png",
--               "created_at":"Wed, 26 Jan 2011 07:07:02 +0000",
--               "from_user":"kazu_yamamoto",
--               "id_str":"30159761706061824",
--               "metadata":
--               {
--                   "result_type":"recent"
--               },
--               "to_user_id":null,
--               "text":"Haskell Server Pages って、まだ続いていたのか!",
--               "id":30159761706061824,
--               "from_user_id":80430860,
--               "geo":null,
--               "iso_language_code":"no",
--               "to_user_id_str":null,
--               "source":"&lt;a href=&quot;http:/twitter.com&quot;&gt;web&lt;/a&gt;"
--           }
--       ],
--       "max_id":30159761706061824,
--       "since_id":0,
--       "refresh_url":"?since_id=30159761706061824&q=haskell",
--       "next_page":"?page=2&max_id=30159761706061824&rpp=1&q=haskell",
--       "results_per_page":1,
--       "page":1,
--       "completed_in":1.2606e-2,
--       "since_id_str":"0",
--       "max_id_str":"30159761706061824",
--       "query":"haskell"
--   }
--   
prettyValue :: Value -> Builder () -- | Parse Value without consuming trailing bytes. parseValue :: Bytes -> (Bytes, Either ParseError Value) -- | Parse Value, and consume all trailing JSON white spaces, if -- there're bytes left, parsing will fail. parseValue' :: Bytes -> Either ParseError Value -- | Increamental parse Value without consuming trailing bytes. parseValueChunks :: Monad m => ParseChunks m Bytes ParseError Value gToValue :: GToValue f => Settings -> f a -> Value gFromValue :: GFromValue f => Settings -> Value -> Converter (f a) gEncodeJSON :: GEncodeJSON f => Settings -> f a -> Builder () -- | Run a Converter with input value. convertValue :: JSON a => Value -> Either ConvertError a -- | Converter provides a monadic interface to convert protocol IR -- (e.g.Value) to Haskell ADT. newtype Converter a Converter :: (forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r) -> Converter a [runConverter] :: Converter a -> forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r -- | Text version of fail. fail' :: Text -> Converter a -- | Add (JSON) Path context to a converter -- -- When converting a complex structure, it helps to annotate -- (sub)converters with context, so that if an error occurs, you can find -- its location. -- --
--   withFlatMapR "Person" $ \o ->
--     Person
--       <$> o .: "name" <?> Key "name"
--       <*> o .: "age" <?> Key "age"
--   
-- -- (Standard methods like (.:) already do this.) -- -- With such annotations, if an error occurs, you will get a (JSON) Path -- location of that error. () :: Converter a -> PathElement -> Converter a infixl 9 -- | Add context to a failure message, indicating the name of the structure -- being converted. -- --
--   prependContext "MyType" (fail "[error message]")
--   -- Error: "converting MyType failed, [error message]"
--   
prependContext :: Text -> Converter a -> Converter a -- | Elements of a (JSON) Value path used to describe the location of an -- error. data PathElement -- | Path element of a key into an object, "object.key". Key :: {-# UNPACK #-} !Text -> PathElement -- | Path element of an index into an array, "array[index]". Index :: {-# UNPACK #-} !Int -> PathElement -- | path of a embedded (JSON) String Embedded :: PathElement -- | Error info with (JSON) Path info. data ConvertError ConvertError :: [PathElement] -> Text -> ConvertError [errPath] :: ConvertError -> [PathElement] [errMsg] :: ConvertError -> Text -- | Produce an error message like converting XXX failed, expected XXX, -- encountered XXX. typeMismatch :: Text -> Text -> Value -> Converter a fromNull :: Text -> a -> Value -> Converter a withBool :: Text -> (Bool -> Converter a) -> Value -> Converter a -- | withScientific name f value applies f to the -- Scientific number when value is a Number and -- fails using typeMismatch otherwise. -- -- Warning: If you are converting from a scientific to an -- unbounded type such as Integer you may want to add a -- restriction on the size of the exponent (see -- withBoundedScientific) to prevent malicious input from filling -- up the memory of the target system. -- --

Error message example

-- --
--   withScientific "MyType" f (String "oops")
--   -- Error: "converting MyType failed, expected Number, but encountered String"
--   
withScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a -- | withBoundedScientific name f value applies f -- to the Scientific number when value is a Number -- with exponent less than or equal to 1024. withBoundedScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a -- | @withRealFloat try to convert floating number with following -- rules: -- -- withRealFloat :: RealFloat a => Text -> (a -> Converter r) -> Value -> Converter r -- | withBoundedScientific name f value applies f -- to the Scientific number when value is a Number -- and value is within minBound ~ maxBound. withBoundedIntegral :: (Bounded a, Integral a) => Text -> (a -> Converter r) -> Value -> Converter r withText :: Text -> (Text -> Converter a) -> Value -> Converter a withArray :: Text -> (Vector Value -> Converter a) -> Value -> Converter a -- | Directly use Object as key-values for further converting. withKeyValues :: Text -> (Vector (Text, Value) -> Converter a) -> Value -> Converter a -- | Take a Object as an 'FM.FlatMap T.Text Value', on key -- duplication prefer first one. withFlatMap :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a -- | Take a Object as an 'FM.FlatMap T.Text Value', on key -- duplication prefer last one. withFlatMapR :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a -- | Take a Object as an 'HM.HashMap T.Text Value', on key -- duplication prefer first one. withHashMap :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a -- | Take a Object as an 'HM.HashMap T.Text Value', on key -- duplication prefer last one. withHashMapR :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a -- | Decode a nested JSON-encoded string. withEmbeddedJSON :: Text -> (Value -> Converter a) -> Value -> Converter a -- | Retrieve the value associated with the given key of an Object. -- The result is empty if the key is not present or the value -- cannot be converted to the desired type. -- -- This accessor is appropriate if the key and value must be -- present in an object for it to be valid. If the key and value are -- optional, use .:? instead. (.:) :: JSON a => FlatMap Text Value -> Text -> Converter a -- | Retrieve the value associated with the given key of an Object. -- The result is Nothing if the key is not present or if its value -- is Null, or fail if the value cannot be converted to the -- desired type. -- -- This accessor is most useful if the key and value can be absent from -- an object without affecting its validity. If the key and value are -- mandatory, use .: instead. (.:?) :: JSON a => FlatMap Text Value -> Text -> Converter (Maybe a) -- | Retrieve the value associated with the given key of an Object. -- The result is Nothing if the key is not present or fail if the -- value cannot be converted to the desired type. -- -- This differs from .:? by attempting to convert Null the -- same as any other JSON value, instead of interpreting it as -- Nothing. (.:!) :: JSON a => FlatMap Text Value -> Text -> Converter (Maybe a) convertField :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter a -- | Variant of .:? with explicit converter function. convertFieldMaybe :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a) -- | Variant of .:! with explicit converter function. convertFieldMaybe' :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a) -- | Connect key and value to a tuple to be used with object. (.=) :: JSON v => Text -> v -> (Text, Value) infixr 8 .= -- | Alias for Object . pack. object :: [(Text, Value)] -> Value -- | Connect key and value to a KVItem using colon, key will -- be escaped. (.!) :: JSON v => Text -> v -> KVItem infixr 8 .! -- | Add curly for comma connected KVItems. object' :: KVItem -> Builder () -- | A newtype for Builder, whose semigroup's instance is to connect -- two builder with comma. data KVItem -- | Use : as separator to connect a label(no escape, only add -- quotes) with field builders. -- -- Don't use chars which need escaped in label. kv :: Text -> Builder () -> Builder () -- | Use : as separator to connect a label(escape the label and -- add quotes) with field builders. kv' :: Text -> Builder () -> Builder () -- | Escape text into JSON string and add double quotes, escaping rules: -- --
--   '\b':  "\b"
--   '\f':  "\f"
--   '\n':  "\n"
--   '\r':  "\r"
--   '\t':  "\t"
--   '"':  "\""
--   '\':  "\\"
--   'DEL':  "\u007f"
--   other chars <= 0x1F: "\u00XX"
--   
string :: Text -> Builder () -- | add {...} to original builder. curly :: Builder () -> Builder () -- | add [...] to original builder. square :: Builder () -> Builder () -- | Use , as separator to connect list of builders. commaSepList :: JSON a => [a] -> Builder () -- | Use , as separator to connect a vector of builders. commaSepVec :: (JSON a, Vec v a) => v a -> Builder () instance Z.Data.JSON.Base.GConstrFromValue GHC.Generics.V1 instance forall k (f :: k -> *) (g :: k -> *). (Z.Data.JSON.Base.GConstrFromValue f, Z.Data.JSON.Base.GConstrFromValue g) => Z.Data.JSON.Base.GConstrFromValue (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Z.Data.JSON.Base.GConstrFromValue (GHC.Generics.C1 c GHC.Generics.U1) instance forall k (c :: GHC.Generics.Meta) (sc :: GHC.Generics.Meta) (f :: k -> *). (GHC.Generics.Constructor c, Z.Data.JSON.Base.GFromValue (GHC.Generics.S1 sc f)) => Z.Data.JSON.Base.GConstrFromValue (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance (Z.Data.Generics.Utils.ProductSize (a GHC.Generics.:*: b), Z.Data.JSON.Base.GFromFields (a GHC.Generics.:*: b), Z.Data.JSON.Base.GBuildLookup (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Z.Data.JSON.Base.GConstrFromValue (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance forall k (f :: k -> *) (c :: GHC.Generics.Meta). Z.Data.JSON.Base.GConstrFromValue f => Z.Data.JSON.Base.GFromValue (GHC.Generics.D1 c f) instance forall k (a :: k -> *) (b :: k -> *). (Z.Data.JSON.Base.GBuildLookup a, Z.Data.JSON.Base.GBuildLookup b) => Z.Data.JSON.Base.GBuildLookup (a GHC.Generics.:*: b) instance forall k (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness) (f :: k -> *). Z.Data.JSON.Base.GBuildLookup (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance forall k (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness) (f :: k -> *). Z.Data.JSON.Base.GBuildLookup (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance (Z.Data.Generics.Utils.ProductSize a, Z.Data.JSON.Base.GFromFields a, Z.Data.JSON.Base.GFromFields b, Z.Data.JSON.Base.LookupTable a GHC.Types.~ Z.Data.JSON.Base.LookupTable b) => Z.Data.JSON.Base.GFromFields (a GHC.Generics.:*: b) instance forall k (f :: k -> *) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). Z.Data.JSON.Base.GFromValue f => Z.Data.JSON.Base.GFromFields (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance forall k (f :: k -> *) (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). (Z.Data.JSON.Base.GFromValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Z.Data.JSON.Base.GFromFields (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.GToValue (GHC.Generics.K1 i a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.K1 i a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.GFromValue (GHC.Generics.K1 i a) instance Z.Data.JSON.Base.JSON Z.Data.JSON.Value.Value instance Z.Data.JSON.Base.JSON Z.Data.Text.Base.Text instance Z.Data.JSON.Base.JSON Data.Scientific.Scientific instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Z.Data.Vector.FlatMap.FlatMap Z.Data.Text.Base.Text a) instance (GHC.Classes.Ord a, Z.Data.JSON.Base.JSON a) => Z.Data.JSON.Base.JSON (Z.Data.Vector.FlatSet.FlatSet a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.HashMap.Internal.HashMap Z.Data.Text.Base.Text a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Map.Internal.Map Z.Data.Text.Base.Text a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Z.Data.Vector.FlatIntMap.FlatIntMap a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.IntMap.Internal.IntMap a) instance Z.Data.JSON.Base.JSON Z.Data.Vector.FlatIntSet.FlatIntSet instance Z.Data.JSON.Base.JSON Data.IntSet.Internal.IntSet instance (GHC.Classes.Ord a, Z.Data.JSON.Base.JSON a) => Z.Data.JSON.Base.JSON (Data.Set.Internal.Set a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Sequence.Internal.Seq a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Tree.Tree a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Primitive.Array.Array a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Primitive.SmallArray.SmallArray a) instance (Data.Primitive.Types.Prim a, Z.Data.JSON.Base.JSON a) => Z.Data.JSON.Base.JSON (Data.Primitive.PrimArray.PrimArray a) instance Z.Data.JSON.Base.JSON Data.Primitive.ByteArray.ByteArray instance (Z.Data.Array.UnliftedArray.PrimUnlifted a, Z.Data.JSON.Base.JSON a) => Z.Data.JSON.Base.JSON (Z.Data.Array.UnliftedArray.UnliftedArray a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Z.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Z.Data.JSON.Base.JSON a) => Z.Data.JSON.Base.JSON (Z.Data.Vector.Base.PrimVector a) instance Z.Data.JSON.Base.JSON Z.Data.Vector.Base.Bytes instance (GHC.Classes.Eq a, Data.Hashable.Class.Hashable a, Z.Data.JSON.Base.JSON a) => Z.Data.JSON.Base.JSON (Data.HashSet.Internal.HashSet a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON [a] instance Z.Data.JSON.Base.JSON [GHC.Types.Char] instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (GHC.Base.NonEmpty a) instance Z.Data.JSON.Base.JSON GHC.Types.Bool instance Z.Data.JSON.Base.JSON GHC.Types.Char instance Z.Data.JSON.Base.JSON GHC.Types.Double instance Z.Data.JSON.Base.JSON GHC.Types.Float instance Z.Data.JSON.Base.JSON GHC.Types.Int instance Z.Data.JSON.Base.JSON GHC.Int.Int8 instance Z.Data.JSON.Base.JSON GHC.Int.Int16 instance Z.Data.JSON.Base.JSON GHC.Int.Int32 instance Z.Data.JSON.Base.JSON GHC.Int.Int64 instance Z.Data.JSON.Base.JSON GHC.Types.Word instance Z.Data.JSON.Base.JSON GHC.Word.Word8 instance Z.Data.JSON.Base.JSON GHC.Word.Word16 instance Z.Data.JSON.Base.JSON GHC.Word.Word32 instance Z.Data.JSON.Base.JSON GHC.Word.Word64 instance Z.Data.JSON.Base.JSON GHC.Integer.Type.Integer instance Z.Data.JSON.Base.JSON GHC.Natural.Natural instance Z.Data.JSON.Base.JSON GHC.Types.Ordering instance Z.Data.JSON.Base.JSON () instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (GHC.Maybe.Maybe a) instance (Z.Data.JSON.Base.JSON a, GHC.Real.Integral a) => Z.Data.JSON.Base.JSON (GHC.Real.Ratio a) instance forall k (a :: k). Data.Fixed.HasResolution a => Z.Data.JSON.Base.JSON (Data.Fixed.Fixed a) instance forall k (f :: k -> *) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). Z.Data.JSON.Base.GFromValue f => Z.Data.JSON.Base.GFromValue (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance forall k (f :: k -> *) (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). (Z.Data.JSON.Base.GFromValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Z.Data.JSON.Base.GFromValue (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Z.Data.JSON.Base.GConstrEncodeJSON GHC.Generics.V1 instance forall k (f :: k -> *) (g :: k -> *). (Z.Data.JSON.Base.GConstrEncodeJSON f, Z.Data.JSON.Base.GConstrEncodeJSON g) => Z.Data.JSON.Base.GConstrEncodeJSON (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Z.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c GHC.Generics.U1) instance forall k (c :: GHC.Generics.Meta) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness) (f :: k -> *). (GHC.Generics.Constructor c, Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f)) => Z.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f)) instance forall k (c :: GHC.Generics.Meta) (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness) (f :: k -> *). (GHC.Generics.Constructor c, Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f)) => Z.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f)) instance (Z.Data.JSON.Base.GEncodeJSON (a GHC.Generics.:*: b), Z.Data.JSON.Base.GAddPunctuation (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Z.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance forall k (f :: k -> *) (c :: GHC.Generics.Meta). Z.Data.JSON.Base.GConstrEncodeJSON f => Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.D1 c f) instance Z.Data.JSON.Base.GAddPunctuation a => Z.Data.JSON.Base.GAddPunctuation (a GHC.Generics.:*: b) instance Z.Data.JSON.Base.GAddPunctuation (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance Z.Data.JSON.Base.GAddPunctuation (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance forall k (f :: k -> *) (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). (Z.Data.JSON.Base.GEncodeJSON f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance forall k (f :: k -> *) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). Z.Data.JSON.Base.GEncodeJSON f => Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance forall k (a :: k -> *) (b :: k -> *). (Z.Data.JSON.Base.GEncodeJSON a, Z.Data.JSON.Base.GEncodeJSON b) => Z.Data.JSON.Base.GEncodeJSON (a GHC.Generics.:*: b) instance Z.Data.JSON.Base.GConstrToValue GHC.Generics.V1 instance forall k (f :: k -> *) (g :: k -> *). (Z.Data.JSON.Base.GConstrToValue f, Z.Data.JSON.Base.GConstrToValue g) => Z.Data.JSON.Base.GConstrToValue (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Z.Data.JSON.Base.GConstrToValue (GHC.Generics.C1 c GHC.Generics.U1) instance forall k (c :: GHC.Generics.Meta) (sc :: GHC.Generics.Meta) (f :: k -> *). (GHC.Generics.Constructor c, Z.Data.JSON.Base.GToValue (GHC.Generics.S1 sc f)) => Z.Data.JSON.Base.GConstrToValue (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance (Z.Data.Generics.Utils.ProductSize (a GHC.Generics.:*: b), Z.Data.JSON.Base.GWriteFields (a GHC.Generics.:*: b), Z.Data.JSON.Base.GMergeFields (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Z.Data.JSON.Base.GConstrToValue (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance forall k (f :: k -> *) (c :: GHC.Generics.Meta). Z.Data.JSON.Base.GConstrToValue f => Z.Data.JSON.Base.GToValue (GHC.Generics.D1 c f) instance forall k (a :: k -> *) (b :: k -> *). Z.Data.JSON.Base.GMergeFields a => Z.Data.JSON.Base.GMergeFields (a GHC.Generics.:*: b) instance forall k (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness) (f :: k -> *). Z.Data.JSON.Base.GMergeFields (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance forall k (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness) (f :: k -> *). Z.Data.JSON.Base.GMergeFields (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance (Z.Data.Generics.Utils.ProductSize a, Z.Data.JSON.Base.GWriteFields a, Z.Data.JSON.Base.GWriteFields b, Z.Data.JSON.Base.Field a GHC.Types.~ Z.Data.JSON.Base.Field b) => Z.Data.JSON.Base.GWriteFields (a GHC.Generics.:*: b) instance forall k (f :: k -> *) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). Z.Data.JSON.Base.GToValue f => Z.Data.JSON.Base.GWriteFields (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance forall k (f :: k -> *) (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). (Z.Data.JSON.Base.GToValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Z.Data.JSON.Base.GWriteFields (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance forall k (f :: k -> *) (l :: GHC.Types.Symbol) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). (Z.Data.JSON.Base.GToValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Z.Data.JSON.Base.GToValue (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance forall k (f :: k -> *) (u :: GHC.Generics.SourceUnpackedness) (ss :: GHC.Generics.SourceStrictness) (ds :: GHC.Generics.DecidedStrictness). Z.Data.JSON.Base.GToValue f => Z.Data.JSON.Base.GToValue (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance GHC.Base.Semigroup Z.Data.JSON.Base.KVItem -- | Types and functions for working efficiently with JSON data, the design -- is quite similar to aeson or json: -- -- -- -- Note this module also provides many (orphan)instances to reduce the -- compilation stress of a gaint Base module. module Z.Data.JSON -- | Type class for encode & decode JSON. class JSON a fromValue :: JSON a => Value -> Converter a fromValue :: (JSON a, Generic a, GFromValue (Rep a)) => Value -> Converter a toValue :: JSON a => a -> Value toValue :: (JSON a, Generic a, GToValue (Rep a)) => a -> Value encodeJSON :: JSON a => a -> Builder () encodeJSON :: (JSON a, Generic a, GEncodeJSON (Rep a)) => a -> Builder () -- | A JSON value represented as a Haskell value. -- -- The Object's payload is a key-value vector instead of a map, -- which parsed directly from JSON document. This design choice has -- following advantages: -- -- data Value Object :: {-# UNPACK #-} !Vector (Text, Value) -> Value Array :: {-# UNPACK #-} !Vector Value -> Value String :: {-# UNPACK #-} !Text -> Value Number :: {-# UNPACK #-} !Scientific -> Value Bool :: !Bool -> Value Null :: Value -- |
--   Settings T.pack T.pack False
--   
defaultSettings :: Settings -- | Generic encode/decode Settings -- -- There should be no control characters in formatted texts since we -- don't escaping those field names or constructor names -- (defaultSettings relys on Haskell's lexical property). -- Otherwise encodeJSON will output illegal JSON string. data Settings Settings :: (String -> Text) -> (String -> Text) -> Bool -> Settings -- | format field labels [fieldFmt] :: Settings -> String -> Text -- | format constructor names [constrFmt] :: Settings -> String -> Text -- | take missing field as Null? [missingKeyAsNull] :: Settings -> Bool -- | Snake casing a pascal cased constructor name or camel cased field -- name, words are always lower cased and separated by an underscore. snakeCase :: String -> Text -- | Train casing a pascal cased constructor name or camel cased field -- name, words are always lower cased and separated by a hyphen. trainCase :: String -> Text type DecodeError = Either ParseError ConvertError -- | Decode a JSON bytes, return any trailing bytes. decode :: JSON a => Bytes -> (Bytes, Either DecodeError a) -- | Decode a JSON doc, only trailing JSON whitespace are allowed. decode' :: JSON a => Bytes -> Either DecodeError a -- | Decode a JSON text, return any trailing text. decodeText :: JSON a => Text -> (Text, Either DecodeError a) -- | Decode a JSON doc, only trailing JSON whitespace are allowed. decodeText' :: JSON a => Text -> Either DecodeError a -- | Type alias for a streaming parser, draw chunk from Monad m (with a -- initial chunk), return result in Either err x. type ParseChunks m chunk err x = m chunk -> chunk -> m (chunk, Either err x) -- | Decode JSON doc chunks, return trailing bytes. decodeChunks :: (JSON a, Monad m) => ParseChunks m Bytes DecodeError a -- | Directly encode data to JSON bytes. encode :: JSON a => a -> Bytes -- | Encode data to JSON bytes chunks. encodeChunks :: JSON a => a -> [Bytes] -- | Text version encode. encodeText :: JSON a => a -> Text -- | Directly encode data to JSON bytes. prettyJSON :: JSON a => a -> Builder () -- | 'ValuePretty'' with 4 spaces indentation per level, e.g. -- --
--   {
--       "results":
--       [
--           {
--               "from_user_id_str":"80430860",
--               "profile_image_url":"http://a2.twimg.com/profile_images/536455139/icon32_normal.png",
--               "created_at":"Wed, 26 Jan 2011 07:07:02 +0000",
--               "from_user":"kazu_yamamoto",
--               "id_str":"30159761706061824",
--               "metadata":
--               {
--                   "result_type":"recent"
--               },
--               "to_user_id":null,
--               "text":"Haskell Server Pages って、まだ続いていたのか!",
--               "id":30159761706061824,
--               "from_user_id":80430860,
--               "geo":null,
--               "iso_language_code":"no",
--               "to_user_id_str":null,
--               "source":"&lt;a href=&quot;http:/twitter.com&quot;&gt;web&lt;/a&gt;"
--           }
--       ],
--       "max_id":30159761706061824,
--       "since_id":0,
--       "refresh_url":"?since_id=30159761706061824&q=haskell",
--       "next_page":"?page=2&max_id=30159761706061824&rpp=1&q=haskell",
--       "results_per_page":1,
--       "page":1,
--       "completed_in":1.2606e-2,
--       "since_id_str":"0",
--       "max_id_str":"30159761706061824",
--       "query":"haskell"
--   }
--   
prettyValue :: Value -> Builder () -- | Parse Value without consuming trailing bytes. parseValue :: Bytes -> (Bytes, Either ParseError Value) -- | Parse Value, and consume all trailing JSON white spaces, if -- there're bytes left, parsing will fail. parseValue' :: Bytes -> Either ParseError Value -- | Increamental parse Value without consuming trailing bytes. parseValueChunks :: Monad m => ParseChunks m Bytes ParseError Value gToValue :: GToValue f => Settings -> f a -> Value gFromValue :: GFromValue f => Settings -> Value -> Converter (f a) gEncodeJSON :: GEncodeJSON f => Settings -> f a -> Builder () -- | Run a Converter with input value. convertValue :: JSON a => Value -> Either ConvertError a -- | Converter provides a monadic interface to convert protocol IR -- (e.g.Value) to Haskell ADT. newtype Converter a Converter :: (forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r) -> Converter a [runConverter] :: Converter a -> forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r -- | Text version of fail. fail' :: Text -> Converter a -- | Add (JSON) Path context to a converter -- -- When converting a complex structure, it helps to annotate -- (sub)converters with context, so that if an error occurs, you can find -- its location. -- --
--   withFlatMapR "Person" $ \o ->
--     Person
--       <$> o .: "name" <?> Key "name"
--       <*> o .: "age" <?> Key "age"
--   
-- -- (Standard methods like (.:) already do this.) -- -- With such annotations, if an error occurs, you will get a (JSON) Path -- location of that error. () :: Converter a -> PathElement -> Converter a infixl 9 -- | Add context to a failure message, indicating the name of the structure -- being converted. -- --
--   prependContext "MyType" (fail "[error message]")
--   -- Error: "converting MyType failed, [error message]"
--   
prependContext :: Text -> Converter a -> Converter a -- | Elements of a (JSON) Value path used to describe the location of an -- error. data PathElement -- | Path element of a key into an object, "object.key". Key :: {-# UNPACK #-} !Text -> PathElement -- | Path element of an index into an array, "array[index]". Index :: {-# UNPACK #-} !Int -> PathElement -- | path of a embedded (JSON) String Embedded :: PathElement -- | Error info with (JSON) Path info. data ConvertError ConvertError :: [PathElement] -> Text -> ConvertError [errPath] :: ConvertError -> [PathElement] [errMsg] :: ConvertError -> Text -- | Produce an error message like converting XXX failed, expected XXX, -- encountered XXX. typeMismatch :: Text -> Text -> Value -> Converter a fromNull :: Text -> a -> Value -> Converter a withBool :: Text -> (Bool -> Converter a) -> Value -> Converter a -- | withScientific name f value applies f to the -- Scientific number when value is a Number and -- fails using typeMismatch otherwise. -- -- Warning: If you are converting from a scientific to an -- unbounded type such as Integer you may want to add a -- restriction on the size of the exponent (see -- withBoundedScientific) to prevent malicious input from filling -- up the memory of the target system. -- --

Error message example

-- --
--   withScientific "MyType" f (String "oops")
--   -- Error: "converting MyType failed, expected Number, but encountered String"
--   
withScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a -- | withBoundedScientific name f value applies f -- to the Scientific number when value is a Number -- with exponent less than or equal to 1024. withBoundedScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a -- | @withRealFloat try to convert floating number with following -- rules: -- -- withRealFloat :: RealFloat a => Text -> (a -> Converter r) -> Value -> Converter r -- | withBoundedScientific name f value applies f -- to the Scientific number when value is a Number -- and value is within minBound ~ maxBound. withBoundedIntegral :: (Bounded a, Integral a) => Text -> (a -> Converter r) -> Value -> Converter r withText :: Text -> (Text -> Converter a) -> Value -> Converter a withArray :: Text -> (Vector Value -> Converter a) -> Value -> Converter a -- | Directly use Object as key-values for further converting. withKeyValues :: Text -> (Vector (Text, Value) -> Converter a) -> Value -> Converter a -- | Take a Object as an 'FM.FlatMap T.Text Value', on key -- duplication prefer first one. withFlatMap :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a -- | Take a Object as an 'FM.FlatMap T.Text Value', on key -- duplication prefer last one. withFlatMapR :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a -- | Take a Object as an 'HM.HashMap T.Text Value', on key -- duplication prefer first one. withHashMap :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a -- | Take a Object as an 'HM.HashMap T.Text Value', on key -- duplication prefer last one. withHashMapR :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a -- | Decode a nested JSON-encoded string. withEmbeddedJSON :: Text -> (Value -> Converter a) -> Value -> Converter a -- | Retrieve the value associated with the given key of an Object. -- The result is empty if the key is not present or the value -- cannot be converted to the desired type. -- -- This accessor is appropriate if the key and value must be -- present in an object for it to be valid. If the key and value are -- optional, use .:? instead. (.:) :: JSON a => FlatMap Text Value -> Text -> Converter a -- | Retrieve the value associated with the given key of an Object. -- The result is Nothing if the key is not present or if its value -- is Null, or fail if the value cannot be converted to the -- desired type. -- -- This accessor is most useful if the key and value can be absent from -- an object without affecting its validity. If the key and value are -- mandatory, use .: instead. (.:?) :: JSON a => FlatMap Text Value -> Text -> Converter (Maybe a) -- | Retrieve the value associated with the given key of an Object. -- The result is Nothing if the key is not present or fail if the -- value cannot be converted to the desired type. -- -- This differs from .:? by attempting to convert Null the -- same as any other JSON value, instead of interpreting it as -- Nothing. (.:!) :: JSON a => FlatMap Text Value -> Text -> Converter (Maybe a) convertField :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter a -- | Variant of .:? with explicit converter function. convertFieldMaybe :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a) -- | Variant of .:! with explicit converter function. convertFieldMaybe' :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a) -- | Connect key and value to a tuple to be used with object. (.=) :: JSON v => Text -> v -> (Text, Value) infixr 8 .= -- | Alias for Object . pack. object :: [(Text, Value)] -> Value -- | Connect key and value to a KVItem using colon, key will -- be escaped. (.!) :: JSON v => Text -> v -> KVItem infixr 8 .! -- | Add curly for comma connected KVItems. object' :: KVItem -> Builder () -- | A newtype for Builder, whose semigroup's instance is to connect -- two builder with comma. data KVItem instance forall k k1 (f :: k -> *) (g :: k1 -> k) (a :: k1). Z.Data.JSON.Base.JSON (f (g a)) => Z.Data.JSON.Base.JSON (Data.Functor.Compose.Compose f g a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Semigroup.Min a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Semigroup.Max a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Semigroup.First a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Semigroup.Last a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Semigroup.WrappedMonoid a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Semigroup.Internal.Dual a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Monoid.First a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Monoid.Last a) instance Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Functor.Identity.Identity a) instance forall k a (b :: k). Z.Data.JSON.Base.JSON a => Z.Data.JSON.Base.JSON (Data.Functor.Const.Const a b) instance forall k b (a :: k). Z.Data.JSON.Base.JSON b => Z.Data.JSON.Base.JSON (Data.Tagged.Tagged a b) instance Z.Data.JSON.Base.JSON Foreign.C.Types.CChar instance Z.Data.JSON.Base.JSON Foreign.C.Types.CSChar instance Z.Data.JSON.Base.JSON Foreign.C.Types.CUChar instance Z.Data.JSON.Base.JSON Foreign.C.Types.CShort instance Z.Data.JSON.Base.JSON Foreign.C.Types.CUShort instance Z.Data.JSON.Base.JSON Foreign.C.Types.CInt instance Z.Data.JSON.Base.JSON Foreign.C.Types.CUInt instance Z.Data.JSON.Base.JSON Foreign.C.Types.CLong instance Z.Data.JSON.Base.JSON Foreign.C.Types.CULong instance Z.Data.JSON.Base.JSON Foreign.C.Types.CPtrdiff instance Z.Data.JSON.Base.JSON Foreign.C.Types.CSize instance Z.Data.JSON.Base.JSON Foreign.C.Types.CWchar instance Z.Data.JSON.Base.JSON Foreign.C.Types.CSigAtomic instance Z.Data.JSON.Base.JSON Foreign.C.Types.CLLong instance Z.Data.JSON.Base.JSON Foreign.C.Types.CULLong instance Z.Data.JSON.Base.JSON Foreign.C.Types.CBool instance Z.Data.JSON.Base.JSON Foreign.C.Types.CIntPtr instance Z.Data.JSON.Base.JSON Foreign.C.Types.CUIntPtr instance Z.Data.JSON.Base.JSON Foreign.C.Types.CIntMax instance Z.Data.JSON.Base.JSON Foreign.C.Types.CUIntMax instance Z.Data.JSON.Base.JSON Foreign.C.Types.CClock instance Z.Data.JSON.Base.JSON Foreign.C.Types.CTime instance Z.Data.JSON.Base.JSON Foreign.C.Types.CUSeconds instance Z.Data.JSON.Base.JSON Foreign.C.Types.CSUSeconds instance Z.Data.JSON.Base.JSON Foreign.C.Types.CFloat instance Z.Data.JSON.Base.JSON Foreign.C.Types.CDouble instance (Z.Data.JSON.Base.JSON (f a), Z.Data.JSON.Base.JSON (g a), Z.Data.JSON.Base.JSON a) => Z.Data.JSON.Base.JSON (Data.Functor.Sum.Sum f g a) instance (Z.Data.JSON.Base.JSON a, Z.Data.JSON.Base.JSON b) => Z.Data.JSON.Base.JSON (Data.Either.Either a b) instance forall k (f :: k -> *) (a :: k) (g :: k -> *). (Z.Data.JSON.Base.JSON (f a), Z.Data.JSON.Base.JSON (g a)) => Z.Data.JSON.Base.JSON (Data.Functor.Product.Product f g a) instance (Z.Data.JSON.Base.JSON a, Z.Data.JSON.Base.JSON b) => Z.Data.JSON.Base.JSON (a, b) instance (Z.Data.JSON.Base.JSON a, Z.Data.JSON.Base.JSON b, Z.Data.JSON.Base.JSON c) => Z.Data.JSON.Base.JSON (a, b, c) instance (Z.Data.JSON.Base.JSON a, Z.Data.JSON.Base.JSON b, Z.Data.JSON.Base.JSON c, Z.Data.JSON.Base.JSON d) => Z.Data.JSON.Base.JSON (a, b, c, d) instance (Z.Data.JSON.Base.JSON a, Z.Data.JSON.Base.JSON b, Z.Data.JSON.Base.JSON c, Z.Data.JSON.Base.JSON d, Z.Data.JSON.Base.JSON e) => Z.Data.JSON.Base.JSON (a, b, c, d, e) instance (Z.Data.JSON.Base.JSON a, Z.Data.JSON.Base.JSON b, Z.Data.JSON.Base.JSON c, Z.Data.JSON.Base.JSON d, Z.Data.JSON.Base.JSON e, Z.Data.JSON.Base.JSON f) => Z.Data.JSON.Base.JSON (a, b, c, d, e, f) instance (Z.Data.JSON.Base.JSON a, Z.Data.JSON.Base.JSON b, Z.Data.JSON.Base.JSON c, Z.Data.JSON.Base.JSON d, Z.Data.JSON.Base.JSON e, Z.Data.JSON.Base.JSON f, Z.Data.JSON.Base.JSON g) => Z.Data.JSON.Base.JSON (a, b, c, d, e, f, g) instance Z.Data.JSON.Base.JSON GHC.IO.Exception.ExitCode instance Z.Data.JSON.Base.JSON Data.Version.Version instance Z.Data.JSON.Base.JSON Data.Time.Clock.Internal.UTCTime.UTCTime instance Z.Data.JSON.Base.JSON Data.Time.LocalTime.Internal.ZonedTime.ZonedTime instance Z.Data.JSON.Base.JSON Data.Time.Calendar.Days.Day instance Z.Data.JSON.Base.JSON Data.Time.LocalTime.Internal.LocalTime.LocalTime instance Z.Data.JSON.Base.JSON Data.Time.LocalTime.Internal.TimeOfDay.TimeOfDay instance Z.Data.JSON.Base.JSON Data.Time.Clock.Internal.NominalDiffTime.NominalDiffTime instance Z.Data.JSON.Base.JSON Data.Time.Clock.Internal.DiffTime.DiffTime instance Z.Data.JSON.Base.JSON Data.Time.Clock.Internal.SystemTime.SystemTime instance Z.Data.JSON.Base.JSON Data.Time.LocalTime.Internal.CalendarDiffTime.CalendarDiffTime instance Z.Data.JSON.Base.JSON Data.Time.Calendar.CalendarDiffDays.CalendarDiffDays instance Z.Data.JSON.Base.JSON Data.Time.Calendar.Week.DayOfWeek instance forall k (a :: k). Z.Data.JSON.Base.JSON (Data.Proxy.Proxy a) -- | This module provides hex encoding & decoding tools, as well as -- HexBytes newtype with hex textual instances. module Z.Data.Vector.Hex -- | New type wrapper for Bytes with hex encoding(uppercase) -- Show/JSON instances. newtype HexBytes HexBytes :: Bytes -> HexBytes [unHexBytes] :: HexBytes -> Bytes -- | Encode Bytes using hex(base16) encoding. hexEncode :: Bool -> Bytes -> Bytes -- | Text version of hexEncode. hexEncodeText :: Bool -> Bytes -> Text -- | Builder version of hexEncode. hexEncodeBuilder :: Bool -> Bytes -> Builder () -- | Decode a hex encoding string, return Nothing on illegal bytes or -- incomplete input. hexDecode :: Bytes -> Maybe Bytes -- | Decode a hex encoding string, throw HexDecodeException on -- error. hexDecode' :: HasCallStack => Bytes -> Bytes -- | Exception during hex decoding. data HexDecodeException IllegalHexBytes :: Bytes -> CallStack -> HexDecodeException IncompleteHexBytes :: Bytes -> CallStack -> HexDecodeException hs_hex_encode :: MBA# Word8 -> Int -> BA# Word8 -> Int -> Int -> IO () hs_hex_encode_upper :: MBA# Word8 -> Int -> BA# Word8 -> Int -> Int -> IO () hs_hex_decode :: MBA# Word8 -> BA# Word8 -> Int -> Int -> IO Int instance Data.Hashable.Class.Hashable Z.Data.Vector.Hex.HexBytes instance GHC.Base.Semigroup Z.Data.Vector.Hex.HexBytes instance GHC.Base.Monoid Z.Data.Vector.Hex.HexBytes instance GHC.Classes.Ord Z.Data.Vector.Hex.HexBytes instance GHC.Classes.Eq Z.Data.Vector.Hex.HexBytes instance GHC.Show.Show Z.Data.Vector.Hex.HexDecodeException instance GHC.Exception.Type.Exception Z.Data.Vector.Hex.HexDecodeException instance GHC.Show.Show Z.Data.Vector.Hex.HexBytes instance Z.Data.Text.Print.Print Z.Data.Vector.Hex.HexBytes instance Z.Data.JSON.Base.JSON Z.Data.Vector.Hex.HexBytes -- | This module provides CBytes with some useful instances / tools -- for retrieving, storing or processing short byte sequences, such as -- file path, environment variables, etc. module Z.Data.CBytes -- | A efficient wrapper for short immutable null-terminated byte sequences -- which can be automatically freed by ghc garbage collector. -- -- The main use case of this type is to ease the bridging of C FFI APIs, -- since most of the unix APIs use null-terminated string. On windows -- you're encouraged to use a compatibility layer like -- 'WideCharToMultiByte/MultiByteToWideChar' and keep the same interface, -- e.g. libuv do this when deal with file paths. -- -- CBytes don't support O(1) slicing, it's not suitable to use it -- to store large byte chunk, If you need advance editing, convert -- CBytes to/from Bytes with CB pattern or -- toBytes / fromBytes, then use vector combinators. -- -- When textual represatation is needed e.g. converting to String, -- Text, Show instance, etc., we assume CBytes using -- UTF-8 encodings, CBytes can be used with -- OverloadedString, literal encoding is UTF-8 with some -- modifications: \NUL is encoded to 'C0 80', and -- \xD800 ~ \xDFFF is encoded as a three bytes normal -- utf-8 codepoint. -- -- Note most of the unix API is not unicode awared though, you may find a -- scandir call return a filename which is not proper encoded in -- any unicode encoding at all. But still, UTF-8 is recommanded to be -- used when text represatation is needed. data CBytes -- | Use this pattern to match or construct CBytes, result will be -- trimmed down to first \NUL byte if there's any. pattern CB :: Bytes -> CBytes -- | Convert to a \NUL terminated PrimArray, -- -- There's an invariance that this array never contains extra -- \NUL except terminator. rawPrimArray :: CBytes -> PrimArray Word8 -- | Constuctor a CBytes from arbitrary array, result will be -- trimmed down to first \NUL byte if there's any. fromPrimArray :: PrimArray Word8 -> CBytes -- | O(1), convert to Bytes, which can be processed by vector -- combinators. toBytes :: CBytes -> Bytes -- | O(n), convert from Bytes -- -- Result will be trimmed down to first \NUL byte if there's -- any. fromBytes :: Bytes -> CBytes -- | O(n), convert to Text using UTF8 encoding assumption. -- -- Throw InvalidUTF8Exception in case of invalid codepoint. toText :: HasCallStack => CBytes -> Text -- | O(n), convert to Text using UTF8 encoding assumption. -- -- Return Nothing in case of invalid codepoint. toTextMaybe :: CBytes -> Maybe Text -- | O(n), convert from Text, -- -- Result will be trimmed down to first \NUL byte if there's -- any. fromText :: Text -> CBytes -- | Write CBytes 's byte sequence to buffer. -- -- This function is different from Print instance in that it -- directly write byte sequence without checking if it's UTF8 encoded. toBuilder :: CBytes -> Builder () -- | Build a CBytes with builder, result will be trimmed down to -- first \NUL byte if there's any. buildCBytes :: Builder a -> CBytes -- | Pack a String into CBytes. -- -- \NUL is encoded as two bytes C0 80 , \xD800 -- ~ \xDFFF is encoded as a three bytes normal UTF-8 codepoint. pack :: String -> CBytes -- | O(n) Convert cbytes to a char list using UTF8 encoding -- assumption. -- -- This function is much tolerant than toText, it simply decoding -- codepoints using UTF8 decodeChar without checking errors such -- as overlong or invalid range. -- -- Unpacking is done lazily. i.e. we will retain reference to the array -- until all element are consumed. -- -- This function is a good producer in the sense of build/foldr -- fusion. unpack :: CBytes -> String -- | Return True if CBytes is empty. null :: CBytes -> Bool -- | O(1), Return the BTYE length of CBytes. length :: CBytes -> Int -- | Empty CBytes empty :: CBytes -- | Singleton CBytes. singleton :: Word8 -> CBytes -- | Concatenate two CBytes. append :: CBytes -> CBytes -> CBytes -- | O(n) Concatenate a list of CBytes. concat :: [CBytes] -> CBytes -- | O(n) The intercalate function takes a CBytes and -- a list of CBytes s and concatenates the list after -- interspersing the first argument between each element of the list. -- -- Note: intercalate will force the entire CBytes list. intercalate :: CBytes -> [CBytes] -> CBytes -- | O(n) An efficient way to join CByte s with a byte. -- -- Intercalate bytes list with \NUL will effectively leave the -- first bytes in the list. intercalateElem :: Word8 -> [CBytes] -> CBytes -- | Copy a CString type into a CBytes, return empty -- if the pointer is NULL. -- -- After copying you're free to free the CString 's memory. fromCString :: CString -> IO CBytes -- | Same with fromCString, but only take at most N bytes. -- -- Result will be trimmed down to first \NUL byte if there's -- any. fromCStringN :: CString -> Int -> IO CBytes -- | Run FFI in bracket and marshall std::string* result into -- CBytes, memory pointed by std::string* will be -- delete ed. fromStdString :: IO (Ptr StdString) -> IO CBytes -- | Pass CBytes to foreign function as a const char*. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. withCBytesUnsafe :: CBytes -> (BA# Word8 -> IO a) -> IO a -- | Pass CBytes to foreign function as a const char*. -- -- Don't pass a forever loop to this function, see #14346. withCBytes :: CBytes -> (Ptr Word8 -> IO a) -> IO a -- | Create a CBytes with IO action. -- -- If (<=0) capacity is provided, a pointer pointing to \NUL -- is passed to initialize function and empty will be returned. -- This behavior is different from allocCBytes, which may cause -- trouble for some FFI functions. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. allocCBytesUnsafe :: HasCallStack => Int -> (MBA# Word8 -> IO a) -> IO (CBytes, a) -- | Create a CBytes with IO action. -- -- If (<=0) capacity is provided, a nullPtr is passed to -- initialize function and empty will be returned. Other than -- that, User have to make sure a \NUL ternimated string will be -- written. allocCBytes :: HasCallStack => Int -> (CString -> IO a) -> IO (CBytes, a) -- | Pass CBytes list to foreign function as a -- StgArrBytes**. -- -- Enable UnliftedFFITypes extension in your haskell code, use -- StgArrBytes**(>=8.10) or StgMutArrPtrs*(<8.10) -- pointer type and HsInt to marshall BAArray# and -- Int arguments on C side, check the example with -- BAArray#. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. withCBytesListUnsafe :: [CBytes] -> (BAArray# Word8 -> Int -> IO a) -> IO a -- | Pass CBytes list to foreign function as a const -- char**. -- -- Check Z.Foreign module for more detail on how to marshall -- params in C side. withCBytesList :: [CBytes] -> (Ptr (Ptr Word8) -> Int -> IO a) -> IO a -- | Poke CBytes with \NUL terminator. pokeMBACBytes :: MBA# Word8 -> Int -> CBytes -> IO () -- | Poke CBytes until a \NUL terminator(or to the end of the array -- if there's none). peekMBACBytes :: MBA# Word8 -> Int -> IO CBytes indexBACBytes :: BA# Word8 -> Int -> CBytes -- | A C string is a reference to an array of C characters terminated by -- NUL. type CString = Ptr CChar instance GHC.Show.Show Z.Data.CBytes.CBytes instance GHC.Read.Read Z.Data.CBytes.CBytes instance Control.DeepSeq.NFData Z.Data.CBytes.CBytes instance GHC.Classes.Eq Z.Data.CBytes.CBytes instance GHC.Classes.Ord Z.Data.CBytes.CBytes instance GHC.Base.Semigroup Z.Data.CBytes.CBytes instance GHC.Base.Monoid Z.Data.CBytes.CBytes instance Data.Hashable.Class.Hashable Z.Data.CBytes.CBytes instance Test.QuickCheck.Arbitrary.Arbitrary Z.Data.CBytes.CBytes instance Test.QuickCheck.Arbitrary.CoArbitrary Z.Data.CBytes.CBytes instance Z.Data.Text.Print.Print Z.Data.CBytes.CBytes instance Z.Data.JSON.Base.JSON Z.Data.CBytes.CBytes instance Data.String.IsString Z.Data.CBytes.CBytes