-- 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.1.0.0 -- | 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). module Z.Data.Array.UnalignedAccess newtype UnalignedSize a UnalignedSize :: Int -> UnalignedSize a [getUnalignedSize] :: UnalignedSize a -> Int -- | Primitive types which can be unaligned accessed class UnalignedAccess a unalignedSize :: UnalignedAccess a => UnalignedSize a writeWord8ArrayAs :: UnalignedAccess a => MutableByteArray# s -> Int# -> a -> State# s -> State# s readWord8ArrayAs :: UnalignedAccess a => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) indexWord8ArrayAs :: UnalignedAccess a => ByteArray# -> Int# -> 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 GHC.Classes.Eq (Z.Data.Array.UnalignedAccess.UnalignedSize a) instance GHC.Show.Show (Z.Data.Array.UnalignedAccess.UnalignedSize a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Z.Data.Array.UnalignedAccess.LE a) instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Array.UnalignedAccess.LE a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Z.Data.Array.UnalignedAccess.BE a) instance GHC.Show.Show a => GHC.Show.Show (Z.Data.Array.UnalignedAccess.BE a) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Word.Word16) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Word.Word32) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Word.Word64) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Types.Word) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Int.Int16) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Int.Int32) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Int.Int64) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Types.Int) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Types.Float) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Types.Double) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.BE GHC.Types.Char) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Word.Word16) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Word.Word32) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Word.Word64) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Types.Word) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Int.Int16) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Int.Int32) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Int.Int64) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Types.Int) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Types.Float) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Types.Double) instance Z.Data.Array.UnalignedAccess.UnalignedAccess (Z.Data.Array.UnalignedAccess.LE GHC.Types.Char) instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Word.Word8 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Int.Int8 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Word.Word16 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Word.Word32 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Word.Word64 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Types.Word instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Int.Int16 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Int.Int32 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Int.Int64 instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Types.Int instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Types.Float instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Types.Double instance Z.Data.Array.UnalignedAccess.UnalignedAccess GHC.Types.Char module Z.Data.Array.UnliftedArray 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 data MutableUnliftedArray s a MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s a 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.STRef.STRef s a) instance Z.Data.Array.UnliftedArray.PrimUnlifted (GHC.IORef.IORef a) -- | Unified unboxed and boxed array operations using functional -- dependencies. -- -- 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 -- | 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 data Array a Array :: Array# a -> Array a [array#] :: Array a -> Array# a 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 -- "Data.Array.uninitialized")) for initialize new boxed -- array(Array, SmallArray..). uninitialized :: a data PrimArray a PrimArray :: ByteArray# -> PrimArray a data MutablePrimArray s a MutablePrimArray :: MutableByteArray# s -> MutablePrimArray s a class Prim a sizeOf# :: Prim a => a -> Int# alignment# :: Prim a => a -> Int# indexByteArray# :: Prim a => ByteArray# -> Int# -> a readByteArray# :: Prim a => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) writeByteArray# :: Prim a => MutableByteArray# s -> Int# -> a -> State# s -> State# s setByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s indexOffAddr# :: Prim a => Addr# -> Int# -> a readOffAddr# :: Prim a => Addr# -> Int# -> State# s -> (# State# s, a #) writeOffAddr# :: Prim a => Addr# -> Int# -> a -> State# s -> State# s setOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s newPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) newAlignedPinnedPrimArray :: (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) copyPrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> PrimArray a -> Int -> Int -> m () copyMutablePrimArrayToPtr :: (PrimMonad m, Prim a) => Ptr a -> MutablePrimArray (PrimState m) a -> Int -> Int -> m () copyPtrToMutablePrimArray :: (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -> Ptr a -> Int -> m () primArrayContents :: PrimArray a -> Ptr a 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 isPrimArrayPinned :: PrimArray a -> Bool isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool data UnliftedArray a UnliftedArray :: ArrayArray# -> UnliftedArray a data MutableUnliftedArray s a MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s a 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 arrays castMutableArray :: (Arr arr a, Cast a b) => MArr arr s a -> MArr arr s b 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 -- | 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 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 data Array a Array :: Array# a -> Array a [array#] :: Array a -> Array# a 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 -- "Data.Array.uninitialized")) for initialize new boxed -- array(Array, SmallArray..). uninitialized :: a data PrimArray a PrimArray :: ByteArray# -> PrimArray a data MutablePrimArray s a MutablePrimArray :: MutableByteArray# s -> MutablePrimArray s a -- | 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 () primArrayContents :: PrimArray a -> Ptr a 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 isPrimArrayPinned :: PrimArray a -> Bool isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool data UnliftedArray a UnliftedArray :: ArrayArray# -> UnliftedArray a data MutableUnliftedArray s a MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s a 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 module Z.Data.Builder.Numeric.DigitTable decDigitTable :: Ptr Word8 hexDigitTable :: Ptr Word8 hexDigitTableUpper :: Ptr Word8 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 :: MutablePrimArray s Word8 -> Int -> Char -> ST s 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. newtype Locale Locale :: CSize -> Locale localeDefault :: Locale localeLithuanian :: Locale localeTurkishAndAzeriLatin :: Locale -- | see NormalizeMode in Z.Data.Text.Base normalizeCompose :: CSize normalizeDecompose :: CSize normalizeCompatibility :: CSize -- | 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. newtype Category Category :: CSize -> Category categoryLetterUppercase :: Category categoryLetterLowercase :: Category categoryLetterTitlecase :: Category categoryLetterOther :: Category categoryLetter :: Category categoryCaseMapped :: Category categoryMarkNonSpacing :: Category categoryMarkSpacing :: Category categoryMarkEnclosing :: Category categoryMark :: Category categoryNumberDecimal :: Category categoryNumberLetter :: Category categoryNumberOther :: Category categoryNumber :: Category categoryPunctuationConnector :: Category categoryPunctuationDash :: Category categoryPunctuationOpen :: Category categoryPunctuationClose :: Category categoryPunctuationInitial :: Category categoryPunctuationFinal :: Category categoryPunctuationOther :: Category categoryPunctuation :: Category categorySymbolMath :: Category categorySymbolCurrency :: Category categorySymbolModifier :: Category categorySymbolOther :: Category categorySymbol :: Category categorySeparatorSpace :: Category categorySeparatorLine :: Category categorySeparatorParagraph :: Category categorySeparator :: Category categoryControl :: Category categoryFormat :: Category categorySurrogate :: Category categoryPrivateUse :: Category categoryUnassigned :: Category categoryCompatibility :: Category categoryIgnoreGraphemeCluste :: Category categoryIscntrl :: Category categoryIsprint :: Category categoryIsspace :: Category categoryIsblank :: Category categoryIsgraph :: Category categoryIspunct :: Category categoryIsalnum :: Category categoryIsalpha :: Category categoryIsupper :: Category categoryIslower :: Category categoryIsdigit :: Category categoryIsxdigit :: Category utf8envlocale :: IO Category instance GHC.Generics.Generic Z.Data.Text.UTF8Rewind.Locale instance GHC.Classes.Ord Z.Data.Text.UTF8Rewind.Locale instance GHC.Classes.Eq Z.Data.Text.UTF8Rewind.Locale instance GHC.Show.Show Z.Data.Text.UTF8Rewind.Locale 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 instance GHC.Generics.Generic Z.Data.Text.UTF8Rewind.Category instance Data.Bits.FiniteBits Z.Data.Text.UTF8Rewind.Category instance Data.Bits.Bits Z.Data.Text.UTF8Rewind.Category instance GHC.Classes.Ord Z.Data.Text.UTF8Rewind.Category instance GHC.Classes.Eq Z.Data.Text.UTF8Rewind.Category instance GHC.Show.Show Z.Data.Text.UTF8Rewind.Category -- | 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. 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 -- | O(1) Index array 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 -- | 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'. It is -- provided as convenience for PrimVector construction. c2w :: Char -> Word8 -- | 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) 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) 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 traverseVec :: (Vec v a, Vec u b, Applicative f) => (a -> f b) -> v a -> f (u b) traverseWithIndex :: (Vec v a, Vec u b, Applicative f) => (Int -> a -> f b) -> v a -> f (u b) traverseVec_ :: (Vec v a, Applicative f) => (a -> f b) -> v a -> f () 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 -- | 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 -- 32k-chunkOverhead defaultChunkSize :: Int -- | The recommended chunk size. Currently set to 4k - -- chunkOverhead. smallChunkSize :: Int 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 Data.Data.Data a => Data.Data.Data (Z.Data.Vector.Base.Vector a) 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 Z.Data.Vector.Base.Vec 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. module Z.Data.Vector.QQ ascii :: 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 handle roll bit -- twiddling. 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 :: 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' :: (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' :: (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(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(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 data InvalidUTF8Exception InvalidUTF8Exception :: CallStack -> InvalidUTF8Exception validateMaybe :: Bytes -> Maybe 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) 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. 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) 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 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. -- -- If the result is unstable, the offset parameter is set to the offset -- for the first unstable code point. If the string is stable, the offset -- is equivalent to the length of the string in bytes. -- -- For more information, please review 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 -- | Locale for case mapping. data Locale localeDefault :: Locale localeLithuanian :: Locale localeTurkishAndAzeriLatin :: 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.orgPublicUNIDATASpecialCasing.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.orgPublicUNIDATASpecialCasing.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.orgPublicUNIDATASpecialCasing.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 -- UTF8_CATEGORY_IGNORE_GRAPHEME_CLUSTER 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) -- | Unicode categories. See isCategory, you can combine categories -- with bitwise or. data Category categoryLetterUppercase :: Category categoryLetterLowercase :: Category categoryLetterTitlecase :: Category categoryLetterOther :: Category categoryLetter :: Category categoryCaseMapped :: Category categoryMarkNonSpacing :: Category categoryMarkSpacing :: Category categoryMarkEnclosing :: Category categoryMark :: Category categoryNumberDecimal :: Category categoryNumberLetter :: Category categoryNumberOther :: Category categoryNumber :: Category categoryPunctuationConnector :: Category categoryPunctuationDash :: Category categoryPunctuationOpen :: Category categoryPunctuationClose :: Category categoryPunctuationInitial :: Category categoryPunctuationFinal :: Category categoryPunctuationOther :: Category categoryPunctuation :: Category categorySymbolMath :: Category categorySymbolCurrency :: Category categorySymbolModifier :: Category categorySymbolOther :: Category categorySymbol :: Category categorySeparatorSpace :: Category categorySeparatorLine :: Category categorySeparatorParagraph :: Category categorySeparator :: Category categoryControl :: Category categoryFormat :: Category categorySurrogate :: Category categoryPrivateUse :: Category categoryUnassigned :: Category categoryCompatibility :: Category categoryIgnoreGraphemeCluste :: Category categoryIscntrl :: Category categoryIsprint :: Category categoryIsspace :: Category categoryIsblank :: Category categoryIsgraph :: Category categoryIspunct :: Category categoryIsalnum :: Category categoryIsalpha :: Category categoryIsupper :: Category categoryIslower :: Category categoryIsdigit :: Category categoryIsxdigit :: Category c_utf8_validate_ba :: ByteArray# -> Int# -> Int# -> Int c_utf8_validate_addr :: Addr# -> Int -> IO Int instance GHC.Base.Monoid Z.Data.Text.Base.Text instance GHC.Base.Semigroup Z.Data.Text.Base.Text instance GHC.Show.Show Z.Data.Text.Base.InvalidUTF8Exception instance GHC.Exception.Type.Exception Z.Data.Text.Base.InvalidUTF8Exception 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 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 findIndices :: (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 index point to the end -- of the byte slice. find :: (Char -> Bool) -> Text -> (Int, Int, Maybe Char) -- | O(n) find the first char matching the predicate in a text from -- right to left, if there isn't one, return the index point to the start -- of the byte slice. findR :: (Char -> Bool) -> Text -> (Int, Int, Maybe Char) -- | O(n) find the index of the byte slice. findIndex :: (Char -> Bool) -> Text -> Int -- | O(n) find the index of the byte slice in reverse order. findIndexR :: (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(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)] -- | Overlapping version of breakOnAll. breakOnAllOverlapping :: 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] -- | A Text simply wraps a Bytes that are UTF-8 encoded -- codepoints, you can use validate / validateMaybe to -- construct a Text. 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 validateMaybe :: Bytes -> Maybe Text -- | 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 -- | 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) 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(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) find the first char matching the predicate in a text from -- left to right, if there isn't one, return the index point to the end -- of the byte slice. find :: (Char -> Bool) -> Text -> (Int, Int, Maybe Char) -- | O(n) find the first char matching the predicate in a text from -- right to left, if there isn't one, return the index point to the start -- of the byte slice. findR :: (Char -> Bool) -> Text -> (Int, 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. -- -- If the result is unstable, the offset parameter is set to the offset -- for the first unstable code point. If the string is stable, the offset -- is equivalent to the length of the string in bytes. -- -- For more information, please review 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 -- | Locale for case mapping. data Locale localeDefault :: Locale localeLithuanian :: Locale localeTurkishAndAzeriLatin :: 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.orgPublicUNIDATASpecialCasing.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.orgPublicUNIDATASpecialCasing.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.orgPublicUNIDATASpecialCasing.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 -- UTF8_CATEGORY_IGNORE_GRAPHEME_CLUSTER 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) -- | Unicode categories. See isCategory, you can combine categories -- with bitwise or. data Category categoryLetterUppercase :: Category categoryLetterLowercase :: Category categoryLetterTitlecase :: Category categoryLetterOther :: Category categoryLetter :: Category categoryCaseMapped :: Category categoryMarkNonSpacing :: Category categoryMarkSpacing :: Category categoryMarkEnclosing :: Category categoryMark :: Category categoryNumberDecimal :: Category categoryNumberLetter :: Category categoryNumberOther :: Category categoryNumber :: Category categoryPunctuationConnector :: Category categoryPunctuationDash :: Category categoryPunctuationOpen :: Category categoryPunctuationClose :: Category categoryPunctuationInitial :: Category categoryPunctuationFinal :: Category categoryPunctuationOther :: Category categoryPunctuation :: Category categorySymbolMath :: Category categorySymbolCurrency :: Category categorySymbolModifier :: Category categorySymbolOther :: Category categorySymbol :: Category categorySeparatorSpace :: Category categorySeparatorLine :: Category categorySeparatorParagraph :: Category categorySeparator :: Category categoryControl :: Category categoryFormat :: Category categorySurrogate :: Category categoryPrivateUse :: Category categoryUnassigned :: Category categoryCompatibility :: Category categoryIgnoreGraphemeCluste :: Category categoryIscntrl :: Category categoryIsprint :: Category categoryIsspace :: Category categoryIsblank :: Category categoryIsgraph :: Category categoryIspunct :: Category categoryIsalnum :: Category categoryIsalpha :: Category categoryIsupper :: Category categoryIslower :: Category categoryIsdigit :: Category categoryIsxdigit :: Category -- | This module provide CBytes with some useful instances / -- functions, A CBytes is a wrapper for immutable null-terminated -- string. The main design target 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. -- -- We neither guarantee to store length info, nor support O(1) slice for -- CBytes: This will defeat the purpose of null-terminated string -- which is to save memory, We do save the length if it's created on GHC -- heap though. If you need advance editing, convert a CBytes to -- Bytes with toBytes and use vector combinators. Use -- fromBytes to convert it back. -- -- It can be used with OverloadedString, literal encoding is -- UTF-8 with some modifications: NUL char is encoded to 'C0 -- 80', and 'xD800' ~ 'xDFFF' is encoded as a three bytes normal utf-8 -- codepoint. This is also how ghc compile string literal into binaries, -- thus we can use rewrite-rules to construct CBytes value in O(1) -- without wasting runtime heap. -- -- 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 everywhere, and we use UTF-8 assumption in various places, such -- as displaying CBytes and literals encoding above. module Z.Data.CBytes -- | A efficient wrapper for immutable null-terminated string which can be -- automatically freed by ghc garbage collector. data CBytes -- | Create a CBytes with IO action. -- -- User only have to do content initialization and return the content -- length, create takes the responsibility to add the 'NUL' -- ternimator. create :: HasCallStack => Int -> (CString -> IO Int) -> IO CBytes -- | Pack a String into null-terminated CBytes. -- -- 'NUL' is encoded as two bytes C0 80 , 'xD800' ~ 'xDFFF' is -- encoded as a three bytes normal UTF-8 codepoint. pack :: String -> CBytes unpack :: CBytes -> String null :: CBytes -> Bool length :: CBytes -> Int empty :: CBytes append :: CBytes -> CBytes -> 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. intercalateElem :: Word8 -> [CBytes] -> CBytes -- | O(1), (O(n) in case of literal), convert to -- Bytes, which can be processed by vector combinators. -- -- NOTE: the 'NUL' ternimator is not included. toBytes :: CBytes -> Bytes -- | O(n), convert from Bytes, allocate pinned memory and add -- the 'NUL' ternimator fromBytes :: Bytes -> CBytes -- | O(n), convert to Text using UTF8 encoding assumption. -- -- Throw InvalidUTF8Exception in case of invalid codepoint. toText :: 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, allocate pinned memory and add -- the 'NUL' ternimator fromText :: Text -> CBytes -- | Copy a CString type into a CBytes, return Nothing if the -- pointer is NULL. -- -- After copying you're free to free the CString 's memory. fromCStringMaybe :: HasCallStack => CString -> IO (Maybe CBytes) -- | Same with fromCStringMaybe, but throw -- NullPointerException when meet a null pointer. fromCString :: HasCallStack => CString -> IO CBytes -- | Same with fromCString, but only take N bytes (and append a null -- byte as terminator). fromCStringN :: HasCallStack => CString -> Int -> IO CBytes -- | Pass CBytes to foreign function as a const char*. -- -- Don't pass a forever loop to this function, see #14346. withCBytes :: CBytes -> (CString -> IO a) -> IO a -- | 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'. It is -- provided as convenience for PrimVector construction. c2w :: Char -> Word8 data NullPointerException NullPointerException :: CallStack -> NullPointerException instance GHC.Show.Show Z.Data.CBytes.NullPointerException instance GHC.Exception.Type.Exception Z.Data.CBytes.NullPointerException 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 Data.String.IsString Z.Data.CBytes.CBytes -- | 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
--   
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 -- | 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 -> m Bytes -> Bytes -> m (Bytes, Either 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 decodePrim :: forall a. UnalignedAccess a => Parser a decodePrimLE :: forall a. UnalignedAccess (LE a) => Parser a decodePrimBE :: forall a. UnalignedAccess (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 :: 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 -- | Match a specific byte. word8 :: Word8 -> Parser () -- | 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 -- | 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 () -- |
--   isSpace w = w == 32 || w - 9 <= 4 || w == 0xA0
--   
isSpace :: Word8 -> Bool 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) -- | 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 :: (Vec v a, Eq a) => v a -> v a -- | Merge duplicated adjacent element, prefer left element. mergeDupAdjacentLeft :: Vec v a => (a -> a -> Bool) -> v a -> v a -- | Merge duplicated adjacent element, prefer right element. mergeDupAdjacentRight :: Vec v a => (a -> a -> Bool) -> v a -> v a -- | Merge duplicated adjacent element, based on a equality tester and a -- merger function. mergeDupAdjacentBy :: Vec v a => (a -> a -> Bool) -> (a -> a -> a) -> v a -> v 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 provide 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. class (Arr (IArray v) a) => Vec v a where { -- | Vector's immutable array type type family IArray v :: * -> *; } -- | 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) 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) 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 traverseVec :: (Vec v a, Vec u b, Applicative f) => (a -> f b) -> v a -> f (u b) traverseWithIndex :: (Vec v a, Vec u b, Applicative f) => (Int -> a -> f b) -> v a -> f (u b) traverseVec_ :: (Vec v a, Applicative f) => (a -> f b) -> v a -> f () 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, -- 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 -- | 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 :: 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' :: (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' :: (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) 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 ascii :: 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 data VectorException IndexOutOfVectorRange :: {-# UNPACK #-} !Int -> CallStack -> VectorException EmptyVector :: CallStack -> VectorException -- | Cast between vectors castVector :: (Vec v a, Cast a b) => v a -> v b -- | A Builder records a buffer writing function, which can be -- mappend in O(1) via composition. In stdio a Builder are -- designed to deal with different AllocateStrategy, it affects -- how Builder react when writing across buffer boundaries: -- -- -- -- 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 AllocateStrategy -- handling. module Z.Data.Builder.Base -- | AllocateStrategy will decide how each BuildStep proceed -- when previous buffer is not enough. data AllocateStrategy s DoubleBuffer :: AllocateStrategy s InsertChunk :: {-# UNPACK #-} !Int -> AllocateStrategy s OneShotAction :: (Bytes -> ST s ()) -> AllocateStrategy s -- | Helper type to help ghc unpack data Buffer s Buffer :: {-# UNPACK #-} !MutablePrimArray s Word8 -> {-# UNPACK #-} !Int -> Buffer s -- | BuilderStep is a function that fill buffer under given -- conditions. type BuildStep s = Buffer s -> ST s [Bytes] -- | 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 :: (forall s. AllocateStrategy s -> (a -> BuildStep s) -> BuildStep s) -> Builder a [runBuilder] :: Builder a -> forall s. AllocateStrategy s -> (a -> BuildStep s) -> BuildStep s append :: Builder a -> Builder b -> Builder b -- | shortcut to buildBytesWith defaultInitSize. buildBytes :: Builder a -> Bytes -- | run Builder with DoubleBuffer strategy, which is suitable for -- building short bytes. buildBytesWith :: Int -> Builder a -> Bytes -- | shortcut to buildBytesListWith defaultChunkSize. buildBytesList :: Builder a -> [Bytes] -- | run Builder with InsertChunk strategy, which is suitable for -- building lazy bytes chunks. buildBytesListWith :: Int -> Int -> Builder a -> [Bytes] -- | shortcut to buildAndRunWith defaultChunkSize. buildAndRun :: (Bytes -> IO ()) -> Builder a -> IO () -- | run Builder with OneShotAction strategy, which is suitable for -- doing effects while building. buildAndRunWith :: Int -> (Bytes -> IO ()) -> Builder a -> IO () -- | Write a Bytes. bytes :: Bytes -> Builder () -- | Ensure that there are at least n many elements available. ensureN :: Int -> Builder () atMost :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int) -> Builder () writeN :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s ()) -> Builder () doubleBuffer :: Int -> BuildStep s -> BuildStep s insertChunk :: Int -> Int -> BuildStep s -> BuildStep s oneShotAction :: (Bytes -> ST s ()) -> Int -> BuildStep s -> BuildStep s -- | write primitive types in host byte order. encodePrim :: forall a. UnalignedAccess a => a -> Builder () -- | write primitive types with little endianess. encodePrimLE :: forall a. UnalignedAccess (LE a) => a -> Builder () -- | write primitive types with big endianess. encodePrimBE :: forall a. UnalignedAccess (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. -- -- Note, if you're trying to write string literals builders, and you know -- it doen't contain 'NUL' or surrgate codepoints, then you can open -- OverloadedStrings and use Builder's IsString -- instance, it can save an extra UTF-8 validation. -- -- 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 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 () -- | 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. intercalateVec :: Vec v a => Builder () -> (a -> Builder ()) -> v a -> Builder () -- | Use separator to connect list of builders. 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 provide functions for using PrimArray and -- PrimVector with GHC FFI(Foreign function interface). Since GHC -- runtime is garbaged collected, we have a quite complex story when -- passing primitive arrays to FFI. We have two types of primitive array -- in GHC, with the objective to minimize overall memory management cost: -- -- -- -- Beside the pinned/unpinned difference, we also 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 the FFI are 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 CSize/CSsize to marshall -- ByteArray# and Int arguments on C side. -- -- The second Int arguement is the element size not the bytes -- size. -- -- Don't cast ByteArray# to Addr# since the heap object -- offset is hard-coded in code generator: -- https://github.com/ghc/ghc/blob/master/compiler/codeGen/StgCmmForeign.hs#L520 -- -- 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 FUNCTION WITH UNSAFE FFI CALL ONLY. withPrimArrayUnsafe :: Prim a => PrimArray a -> (BA# a -> Int -> IO b) -> IO b -- | Pass mutable primitive array to unsafe FFI as pointer. -- -- The mutable version of withPrimArrayUnsafe. -- -- USE THIS FUNCTION WITH UNSAFE FFI CALL ONLY. withMutablePrimArrayUnsafe :: Prim a => MutablePrimArray RealWorld a -> (MBA# a -> Int -> IO b) -> IO b allocMutableByteArrayUnsafe :: Int -> (MBA# a -> IO b) -> IO 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 -- | 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) allocPrimUnsafe :: Prim a => (MBA# a -> IO b) -> IO (a, b) -- | Pass primitive array to safe FFI as pointer. -- -- Use proper pointer type and CSize/CSsize to marshall Ptr -- a and Int arguments on C side. The memory pointed by -- 'Ptr a' will not moved. -- -- 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 -- | Pass mutable primitive array to unsafe FFI as pointer. -- -- The mutable version of withPrimArraySafe. -- -- Don't pass a forever loop to this function, see #14346. withMutablePrimArraySafe :: Prim a => MutablePrimArray RealWorld a -> (Ptr a -> Int -> IO b) -> IO b allocMutablePrimArraySafe :: Prim a => Int -> (Ptr a -> IO b) -> IO b -- | Pass PrimVector to unsafe FFI as pointer -- -- The PrimVector version of withPrimArraySafe. The -- Ptr is already pointed to the first element, thus no offset is -- provided. -- -- 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 -- | 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) allocPrimSafe :: forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b) -- | Type alias for ByteArray#. -- -- Since we can't newtype an unlifted type yet, type alias is the best we -- can get to describe a ByteArray# which we are going to pass -- across FFI. 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: -- https://github.com/ghc/ghc/blob/master/compiler/codeGen/StgCmmForeign.hs#L520 -- -- 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. -- -- Since we can't newtype an unlifted type yet, type alias is the best we -- can get to describe a MutableByteArray# which we are going to -- pass across FFI. 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: -- https://github.com/ghc/ghc/blob/master/compiler/codeGen/StgCmmForeign.hs#L520 -- -- USE THIS TYPE WITH UNSAFE FFI CALL ONLY. A MutableByteArray# -- COULD BE MOVED BY GC DURING SAFE FFI CALL. type MBA# a = MutableByteArray# RealWorld -- | Zero a structure. -- -- There's no Storable or Prim constraint on a -- type, thus 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 -- | 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. 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. hex :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | The UPPERCASED version of hex. heX :: 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. i2wHeX :: 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 -- | Textual numeric parsers. module Z.Data.Parser.Numeric -- | Parse and decode an unsigned decimal number. uint :: Integral a => Parser a -- | Parse a decimal number with an optional leading '+' or -- '-' sign character. int :: Integral a => Parser a -- | Parse and decode an unsigned hex number. 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, i.e. 'parse hex -- "0xFF" == 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 -- | decode hex digits sequence within an array. hexLoop :: (Integral a, Bits a) => a -> Bytes -> a -- | decode digits sequence within an array. 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 -- | A fast digit predicate. isHexDigit :: Word8 -> Bool -- | A fast digit predicate. isDigit :: Word8 -> Bool floatToScientific :: Float -> Scientific doubleToScientific :: Double -> Scientific -- | This module provide a simple resumable Parser, which is -- suitable for binary protocol and simple textual protocol parsing. -- -- 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 to avoid -- backtracking if possible to get high performance. 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 -- | 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 -> m Bytes -> Bytes -> m (Bytes, Either 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 decodePrim :: forall a. UnalignedAccess a => Parser a decodePrimLE :: forall a. UnalignedAccess (LE a) => Parser a decodePrimBE :: forall a. UnalignedAccess (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 :: 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 -- | Match a specific byte. word8 :: Word8 -> Parser () -- | 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 -- | 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. uint :: Integral a => Parser a -- | Parse a decimal number with an optional leading '+' or -- '-' sign character. int :: Integral a => Parser a -- | Parse and decode an unsigned hex number. 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, i.e. 'parse hex -- "0xFF" == 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 -- |
--   isSpace w = w == 32 || w - 9 <= 4 || w == 0xA0
--   
isSpace :: Word8 -> Bool -- | A fast digit predicate. isHexDigit :: Word8 -> Bool -- | A fast digit predicate. isDigit :: Word8 -> Bool -- | 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 buildBytesWith defaultInitSize. buildBytes :: Builder a -> Bytes -- | run Builder with DoubleBuffer strategy, which is suitable for -- building short bytes. buildBytesWith :: Int -> Builder a -> Bytes -- | shortcut to buildBytesListWith defaultChunkSize. buildBytesList :: Builder a -> [Bytes] -- | run Builder with InsertChunk strategy, which is suitable for -- building lazy bytes chunks. buildBytesListWith :: Int -> Int -> Builder a -> [Bytes] -- | shortcut to buildAndRunWith defaultChunkSize. buildAndRun :: (Bytes -> IO ()) -> Builder a -> IO () -- | run Builder with OneShotAction strategy, which is suitable for -- doing effects while building. buildAndRunWith :: Int -> (Bytes -> IO ()) -> Builder a -> IO () -- | Write a Bytes. bytes :: Bytes -> Builder () -- | Ensure that there are at least n many elements available. ensureN :: Int -> Builder () atMost :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s Int) -> Builder () writeN :: Int -> (forall s. MutablePrimArray s Word8 -> Int -> ST s ()) -> Builder () -- | write primitive types in host byte order. encodePrim :: forall a. UnalignedAccess a => a -> Builder () -- | write primitive types with little endianess. encodePrimLE :: forall a. UnalignedAccess (LE a) => a -> Builder () -- | write primitive types with big endianess. encodePrimBE :: forall a. UnalignedAccess (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. -- -- Note, if you're trying to write string literals builders, and you know -- it doen't contain 'NUL' or surrgate codepoints, then you can open -- OverloadedStrings and use Builder's IsString -- instance, it can save an extra UTF-8 validation. -- -- 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 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 () -- | 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. 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. hex :: forall a. (FiniteBits a, Integral a) => a -> Builder () -- | The UPPERCASED version of hex. heX :: 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. intercalateVec :: Vec v a => Builder () -> (a -> Builder ()) -> v a -> Builder () -- | Use separator to connect list of builders. intercalateList :: Builder () -> (a -> Builder ()) -> [a] -> Builder () -- | Base on UTF8 compatible textual builders from Builder, we -- provide a newtype wrapper TextBuilder which can be directly -- used to build Text. -- -- We also provide faster alternative to Show class, i.e. -- ToText, which also provides Generic based instances -- deriving. module Z.Data.Text.Builder -- | A class similar to Show, serving the purpose that quickly -- convert a data type to a Text value. class ToText a toTextBuilder :: ToText a => Int -> a -> TextBuilder () toTextBuilder :: (ToText a, Generic a, GToText (Rep a)) => Int -> a -> TextBuilder () -- | Directly convert data to Text. toText :: ToText a => a -> Text -- | Directly convert data to Builder. toBuilder :: ToText a => a -> Builder () -- | Directly convert data to Bytes. toBytes :: ToText a => a -> Bytes -- | Faster show replacement. toString :: ToText a => a -> String -- | Newtype wrapper for [Char] to provide textual instances. -- -- To encourage using Text as the textual representation, we -- didn't provide special treatment to differentiate instances between -- [a] and [Char] in various places. This newtype is -- therefore to provide instances similar to T.Text, in case you -- really need to wrap a String. newtype Str Str :: [Char] -> Str [chrs] :: Str -> [Char] -- | Buidlers which guarantee UTF-8 encoding, thus can be used to build -- text directly. -- -- Notes on IsString instance: It's recommended to use -- IsString instance, there's a rewrite rule to turn encoding loop -- into a memcpy, which is much faster (the same rule also apply to -- stringUTF8). Different from Builder (), -- TextBuilder ()'s IsString instance will give you -- desired UTF8 guarantees: -- -- data TextBuilder a getBuilder :: TextBuilder a -> Builder a -- | Unsafely turn a Builder into TextBuilder, thus it's -- user's responsibility to ensure only UTF-8 complied bytes are written. unsafeFromBuilder :: Builder a -> TextBuilder a -- | Build a Text using TextBuilder, which provide UTF-8 -- encoding guarantee. buildText :: TextBuilder a -> Text -- | Turn String into TextBuilder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. This -- function will be rewritten into a memcpy if possible, (running a fast -- UTF-8 validation at runtime first). stringUTF8 :: String -> TextBuilder () -- | Turn Char into TextBuilder with UTF8 encoding -- -- Illegal codepoints will be written as replacementChars. charUTF8 :: Char -> TextBuilder () -- | Turn String into TextBuilder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. string7 :: String -> TextBuilder () -- | Turn Char into TextBuilder with ASCII7 encoding -- -- Codepoints beyond 'x7F' will be chopped. char7 :: Char -> TextBuilder () -- | 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 -> TextBuilder () -- | 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 -> TextBuilder () -- | Format a Bounded Integral type like Int or -- Word16 into decimal ascii digits. intWith :: (Integral a, Bounded a) => IFormat -> a -> TextBuilder () -- | Format a Integer into decimal ascii digits. integer :: Integer -> TextBuilder () -- | Format a FiniteBits Integral type into hex nibbles. hex :: (FiniteBits a, Integral a) => a -> TextBuilder () -- | The UPPERCASED version of hex. heX :: (FiniteBits a, Integral a) => a -> TextBuilder () -- | 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 -> TextBuilder () -- | Format double-precision float using drisu3 with dragon4 fallback. doubleWith :: FFormat -> Maybe Int -> Double -> TextBuilder () -- | 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 -> TextBuilder () -- | Format single-precision float using drisu3 with dragon4 fallback. floatWith :: FFormat -> Maybe Int -> Float -> TextBuilder () -- | 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 -> TextBuilder () -- | Like scientific but provides rendering options. scientificWith :: FFormat -> Maybe Int -> Scientific -> TextBuilder () -- | add (...) to original builder. paren :: TextBuilder () -> TextBuilder () -- | Add "(..)" around builders when condition is met, otherwise add -- nothing. -- -- This is useful when defining ToText instances. parenWhen :: Bool -> TextBuilder () -> TextBuilder () -- | add {...} to original builder. curly :: TextBuilder () -> TextBuilder () -- | add [...] to original builder. square :: TextBuilder () -> TextBuilder () -- | add ... to original builder. angle :: TextBuilder () -> TextBuilder () -- | add "..." to original builder. quotes :: TextBuilder () -> TextBuilder () -- | add ... to original builder. squotes :: TextBuilder () -> TextBuilder () -- | write an ASCII : colon :: TextBuilder () -- | write an ASCII , comma :: TextBuilder () -- | Use separator to connect a vector of builders. intercalateVec :: Vec v a => TextBuilder () -> (a -> TextBuilder ()) -> v a -> TextBuilder () -- | Use separator to connect a list of builders. intercalateList :: TextBuilder () -> (a -> TextBuilder ()) -> [a] -> TextBuilder () instance GHC.Base.Monad Z.Data.Text.Builder.TextBuilder instance GHC.Base.Applicative Z.Data.Text.Builder.TextBuilder instance GHC.Base.Functor Z.Data.Text.Builder.TextBuilder instance GHC.Generics.Generic Z.Data.Text.Builder.Str instance Data.Data.Data Z.Data.Text.Builder.Str instance GHC.Classes.Ord Z.Data.Text.Builder.Str instance GHC.Classes.Eq Z.Data.Text.Builder.Str instance GHC.Base.Semigroup (Z.Data.Text.Builder.TextBuilder ()) instance GHC.Base.Monoid (Z.Data.Text.Builder.TextBuilder ()) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Semigroup.Min a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Semigroup.Max a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Semigroup.First a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Semigroup.Last a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Semigroup.WrappedMonoid a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Semigroup.Internal.Dual a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Monoid.First a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Monoid.Last a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (GHC.Base.NonEmpty a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Functor.Identity.Identity a) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Data.Functor.Const.Const a b) instance Z.Data.Text.Builder.ToText (Data.Proxy.Proxy a) instance Z.Data.Text.Builder.ToText b => Z.Data.Text.Builder.ToText (Data.Tagged.Tagged a b) instance Z.Data.Text.Builder.ToText (f (g a)) => Z.Data.Text.Builder.ToText (Data.Functor.Compose.Compose f g a) instance (Z.Data.Text.Builder.ToText (f a), Z.Data.Text.Builder.ToText (g a)) => Z.Data.Text.Builder.ToText (Data.Functor.Product.Product f g a) instance (Z.Data.Text.Builder.ToText (f a), Z.Data.Text.Builder.ToText (g a), Z.Data.Text.Builder.ToText a) => Z.Data.Text.Builder.ToText (Data.Functor.Sum.Sum f g a) instance (Z.Data.Text.Builder.GFieldToText a, Z.Data.Text.Builder.GFieldToText b) => Z.Data.Text.Builder.GFieldToText (a GHC.Generics.:*: b) instance Z.Data.Text.Builder.GToText f => Z.Data.Text.Builder.GFieldToText (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance (Z.Data.Text.Builder.GToText f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Z.Data.Text.Builder.GFieldToText (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance (Z.Data.Text.Builder.GFieldToText (GHC.Generics.S1 sc f), GHC.Generics.Constructor c) => Z.Data.Text.Builder.GToText (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance (Z.Data.Text.Builder.GFieldToText (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Z.Data.Text.Builder.GToText (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance Z.Data.Text.Builder.ToText (Z.Data.Text.Builder.TextBuilder a) instance Z.Data.Text.Builder.ToText Z.Data.Text.Builder.Str instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.GToText (GHC.Generics.K1 i a) instance Z.Data.Text.Builder.ToText GHC.Types.Bool instance Z.Data.Text.Builder.ToText GHC.Types.Char instance Z.Data.Text.Builder.ToText GHC.Types.Double instance Z.Data.Text.Builder.ToText GHC.Types.Float instance Z.Data.Text.Builder.ToText GHC.Types.Int instance Z.Data.Text.Builder.ToText GHC.Int.Int8 instance Z.Data.Text.Builder.ToText GHC.Int.Int16 instance Z.Data.Text.Builder.ToText GHC.Int.Int32 instance Z.Data.Text.Builder.ToText GHC.Int.Int64 instance Z.Data.Text.Builder.ToText GHC.Types.Word instance Z.Data.Text.Builder.ToText GHC.Word.Word8 instance Z.Data.Text.Builder.ToText GHC.Word.Word16 instance Z.Data.Text.Builder.ToText GHC.Word.Word32 instance Z.Data.Text.Builder.ToText GHC.Word.Word64 instance Z.Data.Text.Builder.ToText GHC.Integer.Type.Integer instance Z.Data.Text.Builder.ToText GHC.Natural.Natural instance Z.Data.Text.Builder.ToText GHC.Types.Ordering instance Z.Data.Text.Builder.ToText () instance Z.Data.Text.Builder.ToText Data.Version.Version instance Z.Data.Text.Builder.ToText Z.Data.Text.Base.Text instance Z.Data.Text.Builder.ToText Data.Scientific.Scientific instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText [a] instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (Z.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Z.Data.Text.Builder.ToText a) => Z.Data.Text.Builder.ToText (Z.Data.Vector.Base.PrimVector a) instance (Z.Data.Text.Builder.ToText a, Z.Data.Text.Builder.ToText b) => Z.Data.Text.Builder.ToText (a, b) instance (Z.Data.Text.Builder.ToText a, Z.Data.Text.Builder.ToText b, Z.Data.Text.Builder.ToText c) => Z.Data.Text.Builder.ToText (a, b, c) instance (Z.Data.Text.Builder.ToText a, Z.Data.Text.Builder.ToText b, Z.Data.Text.Builder.ToText c, Z.Data.Text.Builder.ToText d) => Z.Data.Text.Builder.ToText (a, b, c, d) instance (Z.Data.Text.Builder.ToText a, Z.Data.Text.Builder.ToText b, Z.Data.Text.Builder.ToText c, Z.Data.Text.Builder.ToText d, Z.Data.Text.Builder.ToText e) => Z.Data.Text.Builder.ToText (a, b, c, d, e) instance (Z.Data.Text.Builder.ToText a, Z.Data.Text.Builder.ToText b, Z.Data.Text.Builder.ToText c, Z.Data.Text.Builder.ToText d, Z.Data.Text.Builder.ToText e, Z.Data.Text.Builder.ToText f) => Z.Data.Text.Builder.ToText (a, b, c, d, e, f) instance (Z.Data.Text.Builder.ToText a, Z.Data.Text.Builder.ToText b, Z.Data.Text.Builder.ToText c, Z.Data.Text.Builder.ToText d, Z.Data.Text.Builder.ToText e, Z.Data.Text.Builder.ToText f, Z.Data.Text.Builder.ToText g) => Z.Data.Text.Builder.ToText (a, b, c, d, e, f, g) instance Z.Data.Text.Builder.ToText a => Z.Data.Text.Builder.ToText (GHC.Maybe.Maybe a) instance (Z.Data.Text.Builder.ToText a, Z.Data.Text.Builder.ToText b) => Z.Data.Text.Builder.ToText (Data.Either.Either a b) instance (Z.Data.Text.Builder.ToText a, GHC.Real.Integral a) => Z.Data.Text.Builder.ToText (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Z.Data.Text.Builder.ToText (Data.Fixed.Fixed a) instance Z.Data.Text.Builder.GToText GHC.Generics.V1 instance (Z.Data.Text.Builder.GToText f, Z.Data.Text.Builder.GToText g) => Z.Data.Text.Builder.GToText (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Z.Data.Text.Builder.GToText (GHC.Generics.C1 c GHC.Generics.U1) instance Z.Data.Text.Builder.GToText f => Z.Data.Text.Builder.GToText (GHC.Generics.D1 c f) instance GHC.Show.Show Z.Data.Text.Builder.Str instance GHC.Read.Read Z.Data.Text.Builder.Str instance (a GHC.Types.~ ()) => Data.String.IsString (Z.Data.Text.Builder.TextBuilder a) instance Test.QuickCheck.Arbitrary.Arbitrary (Z.Data.Text.Builder.TextBuilder ()) instance Test.QuickCheck.Arbitrary.CoArbitrary (Z.Data.Text.Builder.TextBuilder ()) instance GHC.Show.Show (Z.Data.Text.Builder.TextBuilder a) -- | 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 slice, 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 Control.DeepSeq.NFData v => Control.DeepSeq.NFData (Z.Data.Vector.FlatSet.FlatSet v) 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.Builder.ToText v => Z.Data.Text.Builder.ToText (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 (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 -- | linear scan search from left to right, return the first one if exist. linearSearch :: Ord k => Vector (k, v) -> k -> Maybe v -- | linear scan search from right to left, return the first one if exist. linearSearchR :: Ord k => Vector (k, v) -> k -> Maybe v 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.Builder.ToText k, Z.Data.Text.Builder.ToText v) => Z.Data.Text.Builder.ToText (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 Control.DeepSeq.NFData Z.Data.Vector.FlatIntSet.FlatIntSet 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.Builder.ToText Z.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Base.Semigroup Z.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Base.Monoid 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 -- | linear scan search from left to right, return the first one if exist. linearSearch :: Vector (IPair v) -> Int -> Maybe v -- | linear scan search from right to left, return the first one if exist. linearSearchR :: Vector (IPair v) -> Int -> Maybe v 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.Builder.ToText v => Z.Data.Text.Builder.ToText (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 -- | 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 -- | 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 => m Bytes -> Bytes -> m (Bytes, Either ParseError Value) -- | Increamental parse Value and consume all trailing JSON white -- spaces, if there're bytes left, parsing will fail. parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either 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 () instance Z.Data.Text.Builder.ToText 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.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 -- | 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"
--   '"':  "\""
--   '\':  "\\"
--   '/':  "\/"
--   other chars <= 0x1F: "\u00XX"
--   
string :: Text -> Builder () -- | Use : as separator to connect a label(no need to escape, only -- add quotes) with field builders. kv :: Text -> Builder () -> Builder () -- | Use : as separator to connect a label(escaped 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 Converter to convert Value to -- haskell data types, and various tools to help user define -- FromValue, ToValue and EncodeJSON instance. module Z.Data.JSON.Base type DecodeError = Either ParseError ConvertError -- | Decode a JSON bytes, return any trailing bytes. decode :: FromValue a => Bytes -> (Bytes, Either DecodeError a) -- | Decode a JSON doc, only trailing JSON whitespace are allowed. decode' :: FromValue a => Bytes -> Either DecodeError a -- | Decode JSON doc chunks, return trailing bytes. decodeChunks :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Bytes, Either DecodeError a) -- | Decode JSON doc chunks, consuming trailing JSON whitespaces (other -- trailing bytes are not allowed). decodeChunks' :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Either DecodeError a) -- | Directly encode data to JSON bytes. encodeBytes :: EncodeJSON a => a -> Bytes -- | Text version encodeBytes. encodeText :: EncodeJSON a => a -> Text -- | JSON Docs are guaranteed to be valid UTF-8 texts, so we provide this. encodeTextBuilder :: EncodeJSON a => a -> TextBuilder () -- | 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 -- | 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 => m Bytes -> Bytes -> m (Bytes, Either ParseError Value) -- | Increamental parse Value and consume all trailing JSON white -- spaces, if there're bytes left, parsing will fail. parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either ParseError Value) -- | Run a Converter with input value. convert :: (a -> Converter r) -> a -> Either ConvertError r -- | Run a Converter with input value. convert' :: FromValue a => Value -> Either ConvertError a -- | Converter for convert result from JSON Value. -- -- This is intended to be named differently from Parser to clear -- confusions. 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 data ConvertError -- | 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. (.:) :: FromValue 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 empty 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. (.:?) :: FromValue 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 empty -- 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. (.:!) :: FromValue 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) defaultSettings :: Settings -- | Generic encode/decode Settings -- -- There should be no control charactors 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) -> Settings -- | format field labels [fieldFmt] :: Settings -> String -> Text -- | format constructor names. [constrFmt] :: Settings -> String -> Text -- | Typeclass for converting to JSON Value. class ToValue a toValue :: ToValue a => a -> Value toValue :: (ToValue a, Generic a, GToValue (Rep a)) => a -> Value class GToValue f gToValue :: GToValue f => Settings -> f a -> Value class FromValue a fromValue :: FromValue a => Value -> Converter a fromValue :: (FromValue a, Generic a, GFromValue (Rep a)) => Value -> Converter a class GFromValue f gFromValue :: GFromValue f => Settings -> Value -> Converter (f a) class EncodeJSON a encodeJSON :: EncodeJSON a => a -> Builder () encodeJSON :: (EncodeJSON a, Generic a, GEncodeJSON (Rep a)) => a -> Builder () class GEncodeJSON f gEncodeJSON :: GEncodeJSON f => Settings -> f a -> Builder () type family Field f class GWriteFields f gWriteFields :: GWriteFields f => Settings -> SmallMutableArray s (Field f) -> Int -> f a -> ST s () class GMergeFields f gMergeFields :: GMergeFields f => Proxy# f -> SmallMutableArray s (Field f) -> ST s Value class GConstrToValue f gConstrToValue :: GConstrToValue f => Bool -> Settings -> f a -> Value type family LookupTable f class GFromFields f gFromFields :: GFromFields f => Settings -> LookupTable f -> Int -> Converter (f a) class GBuildLookup f gBuildLookup :: GBuildLookup f => Proxy# f -> Int -> Text -> Value -> Converter (LookupTable f) class GConstrFromValue f gConstrFromValue :: GConstrFromValue f => Bool -> Settings -> Value -> Converter (f a) class GAddPunctuation (f :: * -> *) gAddPunctuation :: GAddPunctuation f => Proxy# f -> Builder () -> Builder () class GConstrEncodeJSON f gConstrEncodeJSON :: GConstrEncodeJSON f => Bool -> Settings -> f a -> Builder () instance Control.DeepSeq.NFData Z.Data.JSON.Base.PathElement instance GHC.Generics.Generic Z.Data.JSON.Base.PathElement instance GHC.Classes.Ord Z.Data.JSON.Base.PathElement instance GHC.Show.Show Z.Data.JSON.Base.PathElement instance GHC.Classes.Eq Z.Data.JSON.Base.PathElement instance Control.DeepSeq.NFData Z.Data.JSON.Base.ConvertError instance GHC.Generics.Generic Z.Data.JSON.Base.ConvertError instance GHC.Classes.Ord Z.Data.JSON.Base.ConvertError instance GHC.Classes.Eq Z.Data.JSON.Base.ConvertError instance Z.Data.JSON.Base.FromValue (f (g a)) => Z.Data.JSON.Base.FromValue (Data.Functor.Compose.Compose f g a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Semigroup.Min a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Semigroup.Max a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Semigroup.First a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Semigroup.Last a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Semigroup.WrappedMonoid a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Semigroup.Internal.Dual a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Monoid.First a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Monoid.Last a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Functor.Identity.Identity a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.Functor.Const.Const a b) instance Z.Data.JSON.Base.FromValue b => Z.Data.JSON.Base.FromValue (Data.Tagged.Tagged a b) instance Z.Data.JSON.Base.ToValue (f (g a)) => Z.Data.JSON.Base.ToValue (Data.Functor.Compose.Compose f g a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Semigroup.Min a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Semigroup.Max a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Semigroup.First a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Semigroup.Last a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Semigroup.WrappedMonoid a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Semigroup.Internal.Dual a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Monoid.First a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Monoid.Last a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Functor.Identity.Identity a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.Functor.Const.Const a b) instance Z.Data.JSON.Base.ToValue b => Z.Data.JSON.Base.ToValue (Data.Tagged.Tagged a b) instance Z.Data.JSON.Base.EncodeJSON (f (g a)) => Z.Data.JSON.Base.EncodeJSON (Data.Functor.Compose.Compose f g a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Semigroup.Min a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Semigroup.Max a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Semigroup.First a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Semigroup.Last a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Semigroup.WrappedMonoid a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Semigroup.Internal.Dual a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Monoid.First a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Monoid.Last a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Functor.Identity.Identity a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.Functor.Const.Const a b) instance Z.Data.JSON.Base.EncodeJSON b => Z.Data.JSON.Base.EncodeJSON (Data.Tagged.Tagged a b) instance (Z.Data.JSON.Base.FromValue (f a), Z.Data.JSON.Base.FromValue (g a), Z.Data.JSON.Base.FromValue a) => Z.Data.JSON.Base.FromValue (Data.Functor.Sum.Sum f g a) instance (Z.Data.JSON.Base.FromValue a, Z.Data.JSON.Base.FromValue b) => Z.Data.JSON.Base.FromValue (Data.Either.Either a b) instance (Z.Data.JSON.Base.FromValue (f a), Z.Data.JSON.Base.FromValue (g a)) => Z.Data.JSON.Base.FromValue (Data.Functor.Product.Product f g a) instance (Z.Data.JSON.Base.FromValue a, Z.Data.JSON.Base.FromValue b) => Z.Data.JSON.Base.FromValue (a, b) instance (Z.Data.JSON.Base.FromValue a, Z.Data.JSON.Base.FromValue b, Z.Data.JSON.Base.FromValue c) => Z.Data.JSON.Base.FromValue (a, b, c) instance (Z.Data.JSON.Base.FromValue a, Z.Data.JSON.Base.FromValue b, Z.Data.JSON.Base.FromValue c, Z.Data.JSON.Base.FromValue d) => Z.Data.JSON.Base.FromValue (a, b, c, d) instance (Z.Data.JSON.Base.FromValue a, Z.Data.JSON.Base.FromValue b, Z.Data.JSON.Base.FromValue c, Z.Data.JSON.Base.FromValue d, Z.Data.JSON.Base.FromValue e) => Z.Data.JSON.Base.FromValue (a, b, c, d, e) instance (Z.Data.JSON.Base.FromValue a, Z.Data.JSON.Base.FromValue b, Z.Data.JSON.Base.FromValue c, Z.Data.JSON.Base.FromValue d, Z.Data.JSON.Base.FromValue e, Z.Data.JSON.Base.FromValue f) => Z.Data.JSON.Base.FromValue (a, b, c, d, e, f) instance (Z.Data.JSON.Base.FromValue a, Z.Data.JSON.Base.FromValue b, Z.Data.JSON.Base.FromValue c, Z.Data.JSON.Base.FromValue d, Z.Data.JSON.Base.FromValue e, Z.Data.JSON.Base.FromValue f, Z.Data.JSON.Base.FromValue g) => Z.Data.JSON.Base.FromValue (a, b, c, d, e, f, g) instance (Z.Data.JSON.Base.ToValue (f a), Z.Data.JSON.Base.ToValue (g a), Z.Data.JSON.Base.ToValue a) => Z.Data.JSON.Base.ToValue (Data.Functor.Sum.Sum f g a) instance (Z.Data.JSON.Base.ToValue a, Z.Data.JSON.Base.ToValue b) => Z.Data.JSON.Base.ToValue (Data.Either.Either a b) instance (Z.Data.JSON.Base.ToValue (f a), Z.Data.JSON.Base.ToValue (g a)) => Z.Data.JSON.Base.ToValue (Data.Functor.Product.Product f g a) instance (Z.Data.JSON.Base.ToValue a, Z.Data.JSON.Base.ToValue b) => Z.Data.JSON.Base.ToValue (a, b) instance (Z.Data.JSON.Base.ToValue a, Z.Data.JSON.Base.ToValue b, Z.Data.JSON.Base.ToValue c) => Z.Data.JSON.Base.ToValue (a, b, c) instance (Z.Data.JSON.Base.ToValue a, Z.Data.JSON.Base.ToValue b, Z.Data.JSON.Base.ToValue c, Z.Data.JSON.Base.ToValue d) => Z.Data.JSON.Base.ToValue (a, b, c, d) instance (Z.Data.JSON.Base.ToValue a, Z.Data.JSON.Base.ToValue b, Z.Data.JSON.Base.ToValue c, Z.Data.JSON.Base.ToValue d, Z.Data.JSON.Base.ToValue e) => Z.Data.JSON.Base.ToValue (a, b, c, d, e) instance (Z.Data.JSON.Base.ToValue a, Z.Data.JSON.Base.ToValue b, Z.Data.JSON.Base.ToValue c, Z.Data.JSON.Base.ToValue d, Z.Data.JSON.Base.ToValue e, Z.Data.JSON.Base.ToValue f) => Z.Data.JSON.Base.ToValue (a, b, c, d, e, f) instance (Z.Data.JSON.Base.ToValue a, Z.Data.JSON.Base.ToValue b, Z.Data.JSON.Base.ToValue c, Z.Data.JSON.Base.ToValue d, Z.Data.JSON.Base.ToValue e, Z.Data.JSON.Base.ToValue f, Z.Data.JSON.Base.ToValue g) => Z.Data.JSON.Base.ToValue (a, b, c, d, e, f, g) instance (Z.Data.JSON.Base.EncodeJSON (f a), Z.Data.JSON.Base.EncodeJSON (g a), Z.Data.JSON.Base.EncodeJSON a) => Z.Data.JSON.Base.EncodeJSON (Data.Functor.Sum.Sum f g a) instance (Z.Data.JSON.Base.EncodeJSON a, Z.Data.JSON.Base.EncodeJSON b) => Z.Data.JSON.Base.EncodeJSON (Data.Either.Either a b) instance (Z.Data.JSON.Base.EncodeJSON (f a), Z.Data.JSON.Base.EncodeJSON (g a)) => Z.Data.JSON.Base.EncodeJSON (Data.Functor.Product.Product f g a) instance (Z.Data.JSON.Base.EncodeJSON a, Z.Data.JSON.Base.EncodeJSON b) => Z.Data.JSON.Base.EncodeJSON (a, b) instance (Z.Data.JSON.Base.EncodeJSON a, Z.Data.JSON.Base.EncodeJSON b, Z.Data.JSON.Base.EncodeJSON c) => Z.Data.JSON.Base.EncodeJSON (a, b, c) instance (Z.Data.JSON.Base.EncodeJSON a, Z.Data.JSON.Base.EncodeJSON b, Z.Data.JSON.Base.EncodeJSON c, Z.Data.JSON.Base.EncodeJSON d) => Z.Data.JSON.Base.EncodeJSON (a, b, c, d) instance (Z.Data.JSON.Base.EncodeJSON a, Z.Data.JSON.Base.EncodeJSON b, Z.Data.JSON.Base.EncodeJSON c, Z.Data.JSON.Base.EncodeJSON d, Z.Data.JSON.Base.EncodeJSON e) => Z.Data.JSON.Base.EncodeJSON (a, b, c, d, e) instance (Z.Data.JSON.Base.EncodeJSON a, Z.Data.JSON.Base.EncodeJSON b, Z.Data.JSON.Base.EncodeJSON c, Z.Data.JSON.Base.EncodeJSON d, Z.Data.JSON.Base.EncodeJSON e, Z.Data.JSON.Base.EncodeJSON f) => Z.Data.JSON.Base.EncodeJSON (a, b, c, d, e, f) instance (Z.Data.JSON.Base.EncodeJSON a, Z.Data.JSON.Base.EncodeJSON b, Z.Data.JSON.Base.EncodeJSON c, Z.Data.JSON.Base.EncodeJSON d, Z.Data.JSON.Base.EncodeJSON e, Z.Data.JSON.Base.EncodeJSON f, Z.Data.JSON.Base.EncodeJSON g) => Z.Data.JSON.Base.EncodeJSON (a, b, c, d, e, f, g) instance Z.Data.JSON.Base.GConstrFromValue GHC.Generics.V1 instance (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 (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 Z.Data.JSON.Base.GConstrFromValue f => Z.Data.JSON.Base.GFromValue (GHC.Generics.D1 c f) instance (Z.Data.JSON.Base.GBuildLookup a, Z.Data.JSON.Base.GBuildLookup b) => Z.Data.JSON.Base.GBuildLookup (a GHC.Generics.:*: b) instance Z.Data.JSON.Base.GBuildLookup (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance 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 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 (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.FromValue a => Z.Data.JSON.Base.GFromValue (GHC.Generics.K1 i a) instance Z.Data.JSON.Base.FromValue (Data.Proxy.Proxy a) instance Z.Data.JSON.Base.FromValue Z.Data.JSON.Value.Value instance Z.Data.JSON.Base.FromValue Z.Data.Text.Base.Text instance Z.Data.JSON.Base.FromValue Z.Data.Text.Builder.Str instance Z.Data.JSON.Base.FromValue Data.Scientific.Scientific instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Z.Data.Vector.FlatMap.FlatMap Z.Data.Text.Base.Text a) instance (GHC.Classes.Ord a, Z.Data.JSON.Base.FromValue a) => Z.Data.JSON.Base.FromValue (Z.Data.Vector.FlatSet.FlatSet a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Data.HashMap.Internal.HashMap Z.Data.Text.Base.Text a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Z.Data.Vector.FlatIntMap.FlatIntMap a) instance Z.Data.JSON.Base.FromValue Z.Data.Vector.FlatIntSet.FlatIntSet instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (Z.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Z.Data.JSON.Base.FromValue a) => Z.Data.JSON.Base.FromValue (Z.Data.Vector.Base.PrimVector a) instance (GHC.Classes.Eq a, Data.Hashable.Class.Hashable a, Z.Data.JSON.Base.FromValue a) => Z.Data.JSON.Base.FromValue (Data.HashSet.Internal.HashSet a) instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue [a] instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (GHC.Base.NonEmpty a) instance Z.Data.JSON.Base.FromValue GHC.Types.Bool instance Z.Data.JSON.Base.FromValue GHC.Types.Char instance Z.Data.JSON.Base.FromValue GHC.Types.Double instance Z.Data.JSON.Base.FromValue GHC.Types.Float instance Z.Data.JSON.Base.FromValue GHC.Types.Int instance Z.Data.JSON.Base.FromValue GHC.Int.Int8 instance Z.Data.JSON.Base.FromValue GHC.Int.Int16 instance Z.Data.JSON.Base.FromValue GHC.Int.Int32 instance Z.Data.JSON.Base.FromValue GHC.Int.Int64 instance Z.Data.JSON.Base.FromValue GHC.Types.Word instance Z.Data.JSON.Base.FromValue GHC.Word.Word8 instance Z.Data.JSON.Base.FromValue GHC.Word.Word16 instance Z.Data.JSON.Base.FromValue GHC.Word.Word32 instance Z.Data.JSON.Base.FromValue GHC.Word.Word64 instance Z.Data.JSON.Base.FromValue GHC.Integer.Type.Integer instance Z.Data.JSON.Base.FromValue GHC.Natural.Natural instance Z.Data.JSON.Base.FromValue GHC.Types.Ordering instance Z.Data.JSON.Base.FromValue () instance Z.Data.JSON.Base.FromValue Data.Version.Version instance Z.Data.JSON.Base.FromValue a => Z.Data.JSON.Base.FromValue (GHC.Maybe.Maybe a) instance (Z.Data.JSON.Base.FromValue a, GHC.Real.Integral a) => Z.Data.JSON.Base.FromValue (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Z.Data.JSON.Base.FromValue (Data.Fixed.Fixed a) instance 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 (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 (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 (GHC.Generics.Constructor c, Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 sc f)) => Z.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c (GHC.Generics.S1 sc 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 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 Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.GEncodeJSON (GHC.Generics.K1 i a) instance Z.Data.JSON.Base.EncodeJSON (Data.Proxy.Proxy a) instance Z.Data.JSON.Base.EncodeJSON Z.Data.JSON.Value.Value instance Z.Data.JSON.Base.EncodeJSON Z.Data.Text.Base.Text instance Z.Data.JSON.Base.EncodeJSON Z.Data.Text.Builder.Str instance Z.Data.JSON.Base.EncodeJSON Data.Scientific.Scientific instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Z.Data.Vector.FlatMap.FlatMap Z.Data.Text.Base.Text a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Z.Data.Vector.FlatSet.FlatSet a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.HashMap.Internal.HashMap Z.Data.Text.Base.Text a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Z.Data.Vector.FlatIntMap.FlatIntMap a) instance Z.Data.JSON.Base.EncodeJSON Z.Data.Vector.FlatIntSet.FlatIntSet instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Z.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Z.Data.JSON.Base.EncodeJSON a) => Z.Data.JSON.Base.EncodeJSON (Z.Data.Vector.Base.PrimVector a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (Data.HashSet.Internal.HashSet a) instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON [a] instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (GHC.Base.NonEmpty a) instance Z.Data.JSON.Base.EncodeJSON GHC.Types.Bool instance Z.Data.JSON.Base.EncodeJSON GHC.Types.Char instance Z.Data.JSON.Base.EncodeJSON GHC.Types.Float instance Z.Data.JSON.Base.EncodeJSON GHC.Types.Double instance Z.Data.JSON.Base.EncodeJSON GHC.Types.Int instance Z.Data.JSON.Base.EncodeJSON GHC.Int.Int8 instance Z.Data.JSON.Base.EncodeJSON GHC.Int.Int16 instance Z.Data.JSON.Base.EncodeJSON GHC.Int.Int32 instance Z.Data.JSON.Base.EncodeJSON GHC.Int.Int64 instance Z.Data.JSON.Base.EncodeJSON GHC.Types.Word instance Z.Data.JSON.Base.EncodeJSON GHC.Word.Word8 instance Z.Data.JSON.Base.EncodeJSON GHC.Word.Word16 instance Z.Data.JSON.Base.EncodeJSON GHC.Word.Word32 instance Z.Data.JSON.Base.EncodeJSON GHC.Word.Word64 instance Z.Data.JSON.Base.EncodeJSON GHC.Integer.Type.Integer instance Z.Data.JSON.Base.EncodeJSON GHC.Natural.Natural instance Z.Data.JSON.Base.EncodeJSON GHC.Types.Ordering instance Z.Data.JSON.Base.EncodeJSON () instance Z.Data.JSON.Base.EncodeJSON Data.Version.Version instance Z.Data.JSON.Base.EncodeJSON a => Z.Data.JSON.Base.EncodeJSON (GHC.Maybe.Maybe a) instance (Z.Data.JSON.Base.EncodeJSON a, GHC.Real.Integral a) => Z.Data.JSON.Base.EncodeJSON (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Z.Data.JSON.Base.EncodeJSON (Data.Fixed.Fixed a) instance (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 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 (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 (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 (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 Z.Data.JSON.Base.GConstrToValue f => Z.Data.JSON.Base.GToValue (GHC.Generics.D1 c f) instance Z.Data.JSON.Base.GMergeFields a => Z.Data.JSON.Base.GMergeFields (a GHC.Generics.:*: b) instance Z.Data.JSON.Base.GMergeFields (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance 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 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 (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 Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.GToValue (GHC.Generics.K1 i a) instance Z.Data.JSON.Base.ToValue (Data.Proxy.Proxy a) instance Z.Data.JSON.Base.ToValue Z.Data.JSON.Value.Value instance Z.Data.JSON.Base.ToValue Z.Data.Text.Base.Text instance Z.Data.JSON.Base.ToValue Z.Data.Text.Builder.Str instance Z.Data.JSON.Base.ToValue Data.Scientific.Scientific instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Z.Data.Vector.FlatMap.FlatMap Z.Data.Text.Base.Text a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Z.Data.Vector.FlatSet.FlatSet a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.HashMap.Internal.HashMap Z.Data.Text.Base.Text a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Z.Data.Vector.FlatIntMap.FlatIntMap a) instance Z.Data.JSON.Base.ToValue Z.Data.Vector.FlatIntSet.FlatIntSet instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Z.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Z.Data.JSON.Base.ToValue a) => Z.Data.JSON.Base.ToValue (Z.Data.Vector.Base.PrimVector a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (Data.HashSet.Internal.HashSet a) instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue [a] instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (GHC.Base.NonEmpty a) instance Z.Data.JSON.Base.ToValue GHC.Types.Bool instance Z.Data.JSON.Base.ToValue GHC.Types.Char instance Z.Data.JSON.Base.ToValue GHC.Types.Float instance Z.Data.JSON.Base.ToValue GHC.Types.Double instance Z.Data.JSON.Base.ToValue GHC.Types.Int instance Z.Data.JSON.Base.ToValue GHC.Int.Int8 instance Z.Data.JSON.Base.ToValue GHC.Int.Int16 instance Z.Data.JSON.Base.ToValue GHC.Int.Int32 instance Z.Data.JSON.Base.ToValue GHC.Int.Int64 instance Z.Data.JSON.Base.ToValue GHC.Types.Word instance Z.Data.JSON.Base.ToValue GHC.Word.Word8 instance Z.Data.JSON.Base.ToValue GHC.Word.Word16 instance Z.Data.JSON.Base.ToValue GHC.Word.Word32 instance Z.Data.JSON.Base.ToValue GHC.Word.Word64 instance Z.Data.JSON.Base.ToValue GHC.Integer.Type.Integer instance Z.Data.JSON.Base.ToValue GHC.Natural.Natural instance Z.Data.JSON.Base.ToValue GHC.Types.Ordering instance Z.Data.JSON.Base.ToValue () instance Z.Data.JSON.Base.ToValue Data.Version.Version instance Z.Data.JSON.Base.ToValue a => Z.Data.JSON.Base.ToValue (GHC.Maybe.Maybe a) instance (Z.Data.JSON.Base.ToValue a, GHC.Real.Integral a) => Z.Data.JSON.Base.ToValue (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Z.Data.JSON.Base.ToValue (Data.Fixed.Fixed a) instance (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 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.Functor Z.Data.JSON.Base.Converter instance GHC.Base.Applicative Z.Data.JSON.Base.Converter instance GHC.Base.Alternative Z.Data.JSON.Base.Converter instance GHC.Base.MonadPlus Z.Data.JSON.Base.Converter instance GHC.Base.Monad Z.Data.JSON.Base.Converter instance Control.Monad.Fail.MonadFail Z.Data.JSON.Base.Converter instance GHC.Show.Show Z.Data.JSON.Base.ConvertError -- | Types and functions for working efficiently with JSON data, the design -- is quite similar to aeson or json: -- -- -- --

How to use this module.

-- -- This module is intended to be used qualified, e.g. -- --
--   import qualified Z.Data.JSON as JSON
--   import           Z.Data.JSON ((.:), ToValue(..), FromValue(..), EncodeJSON(..))
--   
-- -- The easiest way to use the library is to define target data type, -- deriving Generic and following instances: -- -- -- -- The Generic instances convert(encode) Haskell data with -- following rules: -- -- -- -- These rules apply to user defined ADTs, but some built-in instances -- have different behaviour, namely: -- -- -- -- There're some modifying options if you providing a custom -- Settings, which allow you to modify field name or constructor -- name, but please don't produce control characters during your -- modification, since we assume field labels and constructor name won't -- contain them, thus we can save an extra escaping pass. To use constom -- Settings just write: -- --
--   data T = T {fooBar :: Int, fooQux :: [Int]} deriving (Generic)
--   instance ToValue T where toValue = JSON.gToValue JSON.defaultSettings{ JSON.fieldFmt = JSON.snakeCase } . from
--   
--   > JSON.toValue (T 0 [1,2,3])
--   Object [("foo_bar",Number 0.0),("bar_qux",Array [Number 1.0,Number 2.0,Number 3.0])]
--   
-- --

Write instances manually.

-- -- You can write ToValue and FromValue instances by hand if -- the Generic based one doesn't suit you. Here is an example -- similar to aeson's. -- --
--   import qualified Z.Data.Text          as T
--   import qualified Z.Data.Vector        as V
--   import qualified Z.Data.Builder       as B
--   
--   data Person = Person { name :: T.Text , age  :: Int } deriving Show
--   
--   instance FromValue Person where
--       fromValue = JSON.withFlatMapR "Person" $ \ v -> Person
--                       <$> v .: "name"
--                       <*> v .: "age"
--   
--   instance ToValue Person where
--       toValue (Person n a) = JSON.Object $ V.pack [("name", toValue n),("age", toValue a)]
--   
--   instance EncodeJSON Person where
--       encodeJSON (Person n a) = B.curly $ do
--           B.quotes "name" >> B.colon >> encodeJSON n
--           B.comma
--           B.quotes "age" >> B.colon >> encodeJSON a
--   
--   > toValue (Person "Joe" 12)
--   Object [("name",String "Joe"),("age",Number 12.0)]
--   > JSON.convert' @Person . JSON.Object $ V.pack [("name",JSON.String "Joe"),("age",JSON.Number 12.0)]
--   Right (Person {name = "Joe", age = 12})
--   > JSON.encodeText (Person "Joe" 12)
--   "{"name":"Joe","age":12}"
--   
-- -- The Value type is different from aeson's one in that we use -- Vector (Text, Value) to represent JSON objects, thus we can -- choose different strategies on key duplication, the lookup map type, -- etc. so instead of a single withObject, we provide -- withHashMap, withHashMapR, withHashMap and -- withHashMapR which use different lookup map type, and different -- key order piority. Most of time FlatMap is faster than -- HashMap since we only use the lookup map once, the cost of -- constructing a HashMap is higher. If you want to directly -- working on key-values, withKeyValues provide key-values vector -- access. -- -- There're some useful tools to help write encoding code in -- Z.Data.JSON.Builder module, such as JSON string escaping tool, -- etc. If you don't particularly care for fast encoding, you can also -- use toValue together with value builder, the overhead is -- usually very small. module Z.Data.JSON type DecodeError = Either ParseError ConvertError -- | Decode a JSON bytes, return any trailing bytes. decode :: FromValue a => Bytes -> (Bytes, Either DecodeError a) -- | Decode a JSON doc, only trailing JSON whitespace are allowed. decode' :: FromValue a => Bytes -> Either DecodeError a -- | Decode JSON doc chunks, return trailing bytes. decodeChunks :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Bytes, Either DecodeError a) -- | Decode JSON doc chunks, consuming trailing JSON whitespaces (other -- trailing bytes are not allowed). decodeChunks' :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Either DecodeError a) -- | Directly encode data to JSON bytes. encodeBytes :: EncodeJSON a => a -> Bytes -- | Text version encodeBytes. encodeText :: EncodeJSON a => a -> Text -- | JSON Docs are guaranteed to be valid UTF-8 texts, so we provide this. encodeTextBuilder :: EncodeJSON a => a -> TextBuilder () -- | 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 -- | 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 => m Bytes -> Bytes -> m (Bytes, Either ParseError Value) -- | Increamental parse Value and consume all trailing JSON white -- spaces, if there're bytes left, parsing will fail. parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either ParseError Value) -- | Run a Converter with input value. convert :: (a -> Converter r) -> a -> Either ConvertError r -- | Run a Converter with input value. convert' :: FromValue a => Value -> Either ConvertError a -- | Converter for convert result from JSON Value. -- -- This is intended to be named differently from Parser to clear -- confusions. 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 data ConvertError -- | 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. (.:) :: FromValue 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 empty 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. (.:?) :: FromValue 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 empty -- 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. (.:!) :: FromValue 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) -- | Typeclass for converting to JSON Value. class ToValue a toValue :: ToValue a => a -> Value toValue :: (ToValue a, Generic a, GToValue (Rep a)) => a -> Value class FromValue a fromValue :: FromValue a => Value -> Converter a fromValue :: (FromValue a, Generic a, GFromValue (Rep a)) => Value -> Converter a class EncodeJSON a encodeJSON :: EncodeJSON a => a -> Builder () encodeJSON :: (EncodeJSON a, Generic a, GEncodeJSON (Rep a)) => a -> Builder () defaultSettings :: Settings -- | Generic encode/decode Settings -- -- There should be no control charactors 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) -> Settings -- | format field labels [fieldFmt] :: Settings -> String -> Text -- | format constructor names. [constrFmt] :: Settings -> String -> Text -- | 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 gToValue :: GToValue f => Settings -> f a -> Value gFromValue :: GFromValue f => Settings -> Value -> Converter (f a) gEncodeJSON :: GEncodeJSON f => Settings -> f a -> Builder ()