-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A simple and high performance IO toolkit for Haskell -- -- This package provides a simple and high performance IO toolkit for -- Haskell, including packed vectors, unicode texts, socket, file system, -- timers and more! @package stdio @version 0.2.0.0 module Std.Data.Builder.Numeric.DigitTable decDigitTable :: Addr hexDigitTable :: Addr hexDigitTableUpper :: Addr module Std.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 Std.Data.Generics.Utils.ProductSize (GHC.Generics.S1 s a) instance (GHC.TypeNats.KnownNat (Std.Data.Generics.Utils.PSize a GHC.TypeNats.+ Std.Data.Generics.Utils.PSize b), Std.Data.Generics.Utils.ProductSize a, Std.Data.Generics.Utils.ProductSize b) => Std.Data.Generics.Utils.ProductSize (a GHC.Generics.:*: b) -- | This module implement some bit twiddling with ghc primitives. -- -- We currently didn't use all functions from this module though: the -- performance is not catching up c version yet. But this module and -- relevant benchmarks are kept in hope that once we have fully SIMD -- support in GHC, we might optimize these functions further to compete -- with c. -- -- Reference: -- -- module Std.Data.PrimArray.BitTwiddle isOffsetAligned# :: Int# -> Bool mkMask# :: Word# -> Word# nullByteMagic# :: Word# -> Word# -- | Search a word8 in array. -- -- Currently this function is ~4 times slow than c version, so we didn't -- use it. memchr :: PrimArray Word8 -> Word8 -> Int -> Int -> Int -- | The unboxed version of memchr memchr# :: ByteArray# -> Word# -> Int# -> Int# -> Int# -- | Search a word8 array in reverse order. -- -- This function is used in elemIndexEnd, since there's no c -- equivalent (memrchr) on OSX. memchrReverse :: PrimArray Word8 -> Word8 -> Int -> Int -> Int -- | The unboxed version of memchrReverse memchrReverse# :: ByteArray# -> Word# -> Int# -> Int# -> Int# c_memchr :: ByteArray# -> Int -> Word8 -> Int -> Int -- | 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 Std.Data.PrimArray.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 => Std.Data.PrimArray.Cast.Cast a b instance Std.Data.PrimArray.Cast.Cast GHC.Int.Int8 GHC.Word.Word8 instance Std.Data.PrimArray.Cast.Cast GHC.Int.Int16 GHC.Word.Word16 instance Std.Data.PrimArray.Cast.Cast GHC.Int.Int32 GHC.Word.Word32 instance Std.Data.PrimArray.Cast.Cast GHC.Int.Int64 GHC.Word.Word64 instance Std.Data.PrimArray.Cast.Cast GHC.Types.Int GHC.Types.Word instance Std.Data.PrimArray.Cast.Cast GHC.Word.Word8 GHC.Int.Int8 instance Std.Data.PrimArray.Cast.Cast GHC.Word.Word16 GHC.Int.Int16 instance Std.Data.PrimArray.Cast.Cast GHC.Word.Word32 GHC.Int.Int32 instance Std.Data.PrimArray.Cast.Cast GHC.Word.Word64 GHC.Int.Int64 instance Std.Data.PrimArray.Cast.Cast GHC.Types.Word GHC.Types.Int instance Std.Data.PrimArray.Cast.Cast GHC.Word.Word64 GHC.Types.Double instance Std.Data.PrimArray.Cast.Cast GHC.Word.Word32 GHC.Types.Float instance Std.Data.PrimArray.Cast.Cast GHC.Types.Double GHC.Word.Word64 instance Std.Data.PrimArray.Cast.Cast GHC.Types.Float GHC.Word.Word32 instance Std.Data.PrimArray.Cast.Cast GHC.Int.Int64 GHC.Types.Double instance Std.Data.PrimArray.Cast.Cast GHC.Int.Int32 GHC.Types.Float instance Std.Data.PrimArray.Cast.Cast GHC.Types.Double GHC.Int.Int64 instance Std.Data.PrimArray.Cast.Cast GHC.Types.Float GHC.Int.Int32 -- | Unified unboxed and boxed array operations using functional -- dependencies. -- -- All operations are NOT bound checked, if you need checked operations -- please use Std.Data.Array.Checked. It exports exactly same APIs -- so that you can switch between without pain. -- -- Some mnemonics: -- -- module Std.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 (marr :: * -> * -> *) (arr :: * -> *) a | arr -> marr, marr -> arr where { type family IArr marr = (ar :: * -> *) | ar -> marr; 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 marr arr a, PrimMonad m, PrimState m ~ s) => Int -> m (marr s a) -- | Make a new array and fill it with an initial value. newArrWith :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => Int -> a -> m (marr s a) -- | Index mutable array in a primitive monad. readArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> m a -- | Write mutable array in a primitive monad. writeArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> a -> m () -- | Fill mutable array with a given value. setArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr 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 marr 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 marr 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 marr arr a, Monad m) => arr a -> Int -> m a -- | Safely freeze mutable array by make a immutable copy of its slice. freezeArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> Int -> m (arr a) -- | Safely thaw immutable array by make a mutable copy of its slice. thawArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => arr a -> Int -> Int -> m (marr s a) -- | In place freeze a mutable array, the original mutable array can not be -- used anymore. unsafeFreezeArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> m (arr a) -- | In place thaw a immutable array, the original immutable array can not -- be used anymore. unsafeThawArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => arr a -> m (marr s a) -- | Copy a slice of immutable array to mutable array at given offset. copyArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr 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 marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> marr 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 marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> marr s a -> Int -> Int -> m () -- | Create immutable copy. cloneArr :: Arr marr arr a => arr a -> Int -> Int -> arr a -- | Create mutable copy. cloneMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> Int -> m (marr s a) -- | Resize mutable array to given size. resizeMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> m (marr s a) -- | Shrink mutable array to given size. This operation only works on -- primitive arrays. For boxed array, this is a no-op, e.g. -- sizeOfMutableArr will not change. shrinkMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> Int -> m () -- | Is two mutable array are reference equal. sameMutableArr :: Arr marr arr a => marr s a -> marr s a -> Bool -- | Size of immutable array. sizeofArr :: Arr marr arr a => arr a -> Int -- | Size of mutable array. sizeofMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr 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 marr 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 :: Type 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..). -- -- NOTE: These functions may segfault when used with indices which are -- out of bounds. 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 -- | Create a pinned byte array of the specified size, The garbage -- collector is guaranteed not to move it. newPinnedPrimArray :: forall m a. (PrimMonad m, Prim a) => 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 :: forall m a. (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 () -- | Yield a pointer to the array's data. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray, and you have to make sure the -- PrimArray can outlive the Ptr. primArrayContents :: PrimArray a -> Ptr a -- | Yield a pointer to the array's data. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. and you have to make sure the -- PrimArray can outlive the Ptr. mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b -- | Check if a primitive array is pinned. isPrimArrayPinned :: PrimArray a -> Bool -- | Check if a mutable primitive array is pinned. isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool data UnliftedArray e UnliftedArray :: ArrayArray# -> UnliftedArray e data MutableUnliftedArray s e MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s e class PrimUnlifted a toArrayArray# :: PrimUnlifted a => a -> ArrayArray# fromArrayArray# :: PrimUnlifted a => ArrayArray# -> 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 arrays castArray :: (Arr marr arr a, Cast a b) => arr a -> arr b castMutableArray :: (Arr marr arr a, Cast a b) => marr s a -> marr s b instance Std.Data.Array.Arr Data.Primitive.Array.MutableArray Data.Primitive.Array.Array a instance Std.Data.Array.Arr Data.Primitive.SmallArray.SmallMutableArray Data.Primitive.SmallArray.SmallArray a instance Data.Primitive.Types.Prim a => Std.Data.Array.Arr Data.Primitive.PrimArray.MutablePrimArray Data.Primitive.PrimArray.PrimArray a instance Data.Primitive.UnliftedArray.PrimUnlifted a => Std.Data.Array.Arr Data.Primitive.UnliftedArray.MutableUnliftedArray Data.Primitive.UnliftedArray.UnliftedArray a -- | This module provides exactly the same API with Std.Data.Array, -- but will throw an IndexOutOfBounds ArrayException on -- bound check failure, it's useful when debugging array algorithms: just -- swap this module with Std.Data.Array, segmentation faults -- caused by out bound access will be turned into exceptions with more -- informations. module Std.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 (marr :: * -> * -> *) (arr :: * -> *) a | arr -> marr, marr -> arr -- | 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 :: Type newArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => Int -> m (marr s a) newArrWith :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => Int -> a -> m (marr s a) readArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> m a writeArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> a -> m () setArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> Int -> a -> m () indexArr :: (Arr marr arr a, HasCallStack) => arr a -> Int -> a indexArr' :: (Arr marr arr a, HasCallStack) => arr a -> Int -> (# a #) indexArrM :: (Arr marr arr a, Monad m, HasCallStack) => arr a -> Int -> m a freezeArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> Int -> m (arr a) thawArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => arr a -> Int -> Int -> m (marr s a) copyArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> arr a -> Int -> Int -> m () copyMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> marr s a -> Int -> Int -> m () moveArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> marr s a -> Int -> Int -> m () cloneArr :: (Arr marr arr a, HasCallStack) => arr a -> Int -> Int -> arr a cloneMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> Int -> m (marr s a) resizeMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> m (marr s a) -- | New size should be >= 0, and <= original size. shrinkMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s, HasCallStack) => marr s a -> Int -> m () -- | In place freeze a mutable array, the original mutable array can not be -- used anymore. unsafeFreezeArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr s a -> m (arr a) -- | In place thaw a immutable array, the original immutable array can not -- be used anymore. unsafeThawArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => arr a -> m (marr s a) -- | Is two mutable array are reference equal. sameMutableArr :: Arr marr arr a => marr s a -> marr s a -> Bool -- | Size of immutable array. sizeofArr :: Arr marr arr a => arr a -> Int -- | Size of mutable array. sizeofMutableArr :: (Arr marr arr a, PrimMonad m, PrimState m ~ s) => marr 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 marr 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..). -- -- NOTE: These functions may segfault when used with indices which are -- out of bounds. 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 () -- | Yield a pointer to the array's data. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray, and you have to make sure the -- PrimArray can outlive the Ptr. primArrayContents :: PrimArray a -> Ptr a -- | Yield a pointer to the array's data. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. and you have to make sure the -- PrimArray can outlive the Ptr. mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withPrimArrayContents :: PrimArray a -> (Ptr a -> IO b) -> IO b -- | Yield a pointer to the array's data and do computation with it. -- -- This operation is only safe on pinned primitive arrays -- allocated by newPinnedPrimArray or -- newAlignedPinnedPrimArray. -- -- Don't pass a forever loop to this function, see #14346. withMutablePrimArrayContents :: MutablePrimArray RealWorld a -> (Ptr a -> IO b) -> IO b -- | Check if a primitive array is pinned. isPrimArrayPinned :: PrimArray a -> Bool -- | Check if a mutable primitive array is pinned. isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool data UnliftedArray e UnliftedArray :: ArrayArray# -> UnliftedArray e data MutableUnliftedArray s e MutableUnliftedArray :: MutableArrayArray# s -> MutableUnliftedArray s e class PrimUnlifted a toArrayArray# :: PrimUnlifted a => a -> ArrayArray# fromArrayArray# :: PrimUnlifted a => ArrayArray# -> 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 -- | This module provides functions for writing PrimArray related -- literals QuasiQuote. module Std.Data.PrimArray.QQ arrASCII :: QuasiQuoter arrW8 :: QuasiQuoter arrW16 :: QuasiQuoter arrW32 :: QuasiQuoter arrW64 :: QuasiQuoter arrWord :: QuasiQuoter arrI8 :: QuasiQuoter arrI16 :: QuasiQuoter arrI32 :: QuasiQuoter arrI64 :: QuasiQuoter arrInt :: QuasiQuoter -- | Construct data with ASCII encoded literals. -- -- Example usage: -- --
--   arrASCII :: QuasiQuoter
--   arrASCII = QuasiQuoter
--       (asciiLiteral $  len addr -> [| word8ArrayFromAddr $(len) $(addr) |])
--       ...
--   
--   word8ArrayFromAddr :: Int -> Addr# -> PrimArray Word8
--   {--}
--   word8ArrayFromAddr l addr# = runST $ do
--       mba <- newPrimArray (I# l)
--       copyPtrToMutablePrimArray mba 0 (Ptr addr#) l
--       unsafeFreezePrimArray mba
--   
asciiLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ -- | Construct data with UTF-8 encoded literals. -- -- Smiliar to asciIILiteral, the utf8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ word8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ word16Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ word32Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ word64Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ wordLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ int8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ int16Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ int32Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ int64Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ 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 implements unaligned element access with ghc primitives -- (> 8.6). module Std.Data.PrimArray.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 a => GHC.Classes.Eq (Std.Data.PrimArray.UnalignedAccess.BE a) instance GHC.Show.Show a => GHC.Show.Show (Std.Data.PrimArray.UnalignedAccess.BE a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Std.Data.PrimArray.UnalignedAccess.LE a) instance GHC.Show.Show a => GHC.Show.Show (Std.Data.PrimArray.UnalignedAccess.LE a) instance GHC.Classes.Eq (Std.Data.PrimArray.UnalignedAccess.UnalignedSize a) instance GHC.Show.Show (Std.Data.PrimArray.UnalignedAccess.UnalignedSize a) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Word.Word16) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Word.Word32) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Word.Word64) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Word) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Int.Int16) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Int.Int32) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Int.Int64) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Int) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Float) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Double) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Char) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Word.Word16) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Word.Word32) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Word.Word64) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Types.Word) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Int.Int16) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Int.Int32) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Int.Int64) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Types.Int) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Types.Float) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Types.Double) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess (Std.Data.PrimArray.UnalignedAccess.LE GHC.Types.Char) instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Word.Word8 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Int.Int8 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Word.Word16 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Word.Word32 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Word.Word64 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Types.Word instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Int.Int16 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Int.Int32 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Int.Int64 instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Types.Int instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Types.Float instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Types.Double instance Std.Data.PrimArray.UnalignedAccess.UnalignedAccess GHC.Types.Char -- | Internal module for PrimSTRef and PrimIORef. module Std.Data.PrimSTRef.Base -- | 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 module 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 Std.Data.PrimSTRef -- | 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 () -- | 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 Std.Data.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 () -- | UTF-8 codecs and helpers. module Std.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 Std.Data.Text.UTF8Rewind -- | Locale for case mapping. newtype Locale Locale :: CSize -> Locale localeDefault :: Locale localeLithuanian :: Locale localeTurkishAndAzeriLatin :: Locale -- | see NormalizeMode in Std.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 Std.Data.Text.UTF8Rewind.Category instance Data.Bits.FiniteBits Std.Data.Text.UTF8Rewind.Category instance Data.Bits.Bits Std.Data.Text.UTF8Rewind.Category instance GHC.Classes.Ord Std.Data.Text.UTF8Rewind.Category instance GHC.Classes.Eq Std.Data.Text.UTF8Rewind.Category instance GHC.Show.Show Std.Data.Text.UTF8Rewind.Category instance GHC.Generics.Generic Std.Data.Text.UTF8Rewind.NormalizationResult instance GHC.Classes.Ord Std.Data.Text.UTF8Rewind.NormalizationResult instance GHC.Classes.Eq Std.Data.Text.UTF8Rewind.NormalizationResult instance GHC.Show.Show Std.Data.Text.UTF8Rewind.NormalizationResult instance GHC.Generics.Generic Std.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Classes.Ord Std.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Classes.Eq Std.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Show.Show Std.Data.Text.UTF8Rewind.NormalizeMode instance GHC.Generics.Generic Std.Data.Text.UTF8Rewind.Locale instance GHC.Classes.Ord Std.Data.Text.UTF8Rewind.Locale instance GHC.Classes.Eq Std.Data.Text.UTF8Rewind.Locale instance GHC.Show.Show Std.Data.Text.UTF8Rewind.Locale -- | 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 Std.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 (MArray v) (IArray v) a) => Vec v a where { -- | Vector's mutable array type type family MArray v = (marr :: * -> * -> *) | marr -> v; -- | Vector's immutable array type type family IArray v = (iarr :: * -> *) | iarr -> 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, HasCallStack) => 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 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. MArray 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. MArray v s a -> ST s (IPair (MArray 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. MArray 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. MArray v s a -> ST s (b, IPair (MArray 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. MArray 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. MArray v s a -> MArray 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 -- | Index 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_strlen :: Addr# -> IO CSize c_ascii_validate_addr :: Addr# -> Int -> IO Int c_fnv_hash_addr :: Addr# -> Int -> Int -> IO Int c_fnv_hash_ba :: ByteArray# -> Int -> Int -> Int -> IO Int instance GHC.Show.Show Std.Data.Vector.Base.VectorException instance GHC.Classes.Ord a => GHC.Classes.Ord (Std.Data.Vector.Base.IPair a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Std.Data.Vector.Base.IPair a) instance GHC.Show.Show a => GHC.Show.Show (Std.Data.Vector.Base.IPair a) instance Data.Data.Data a => Data.Data.Data (Std.Data.Vector.Base.Vector a) instance GHC.Exception.Type.Exception Std.Data.Vector.Base.VectorException instance Test.QuickCheck.Arbitrary.Arbitrary v => Test.QuickCheck.Arbitrary.Arbitrary (Std.Data.Vector.Base.IPair v) instance Test.QuickCheck.Arbitrary.CoArbitrary v => Test.QuickCheck.Arbitrary.CoArbitrary (Std.Data.Vector.Base.IPair v) instance GHC.Base.Functor Std.Data.Vector.Base.IPair instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Std.Data.Vector.Base.IPair a) instance Data.CaseInsensitive.Internal.FoldCase Std.Data.Vector.Base.Bytes instance Data.Primitive.Types.Prim a => Std.Data.Vector.Base.Vec Std.Data.Vector.Base.PrimVector a instance (Data.Primitive.Types.Prim a, GHC.Classes.Eq a) => GHC.Classes.Eq (Std.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, GHC.Classes.Ord a) => GHC.Classes.Ord (Std.Data.Vector.Base.PrimVector a) instance Data.Primitive.Types.Prim a => GHC.Base.Semigroup (Std.Data.Vector.Base.PrimVector a) instance Data.Primitive.Types.Prim a => GHC.Base.Monoid (Std.Data.Vector.Base.PrimVector a) instance Control.DeepSeq.NFData (Std.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, GHC.Show.Show a) => GHC.Show.Show (Std.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, GHC.Read.Read a) => GHC.Read.Read (Std.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, Test.QuickCheck.Arbitrary.Arbitrary a) => Test.QuickCheck.Arbitrary.Arbitrary (Std.Data.Vector.Base.PrimVector a) instance (Data.Primitive.Types.Prim a, Test.QuickCheck.Arbitrary.CoArbitrary a) => Test.QuickCheck.Arbitrary.CoArbitrary (Std.Data.Vector.Base.PrimVector a) instance (Data.Hashable.Class.Hashable a, Data.Primitive.Types.Prim a) => Data.Hashable.Class.Hashable (Std.Data.Vector.Base.PrimVector a) instance (a Data.Type.Equality.~ GHC.Word.Word8) => Data.String.IsString (Std.Data.Vector.Base.PrimVector a) instance Std.Data.Vector.Base.Vec Std.Data.Vector.Base.Vector a instance GHC.Classes.Eq a => GHC.Classes.Eq (Std.Data.Vector.Base.Vector a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Std.Data.Vector.Base.Vector a) instance GHC.Base.Semigroup (Std.Data.Vector.Base.Vector a) instance GHC.Base.Monoid (Std.Data.Vector.Base.Vector a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Std.Data.Vector.Base.Vector a) instance GHC.Show.Show a => GHC.Show.Show (Std.Data.Vector.Base.Vector a) instance GHC.Read.Read a => GHC.Read.Read (Std.Data.Vector.Base.Vector a) instance GHC.Base.Functor Std.Data.Vector.Base.Vector instance Data.Foldable.Foldable Std.Data.Vector.Base.Vector instance Data.Traversable.Traversable Std.Data.Vector.Base.Vector instance Test.QuickCheck.Arbitrary.Arbitrary a => Test.QuickCheck.Arbitrary.Arbitrary (Std.Data.Vector.Base.Vector a) instance Test.QuickCheck.Arbitrary.CoArbitrary a => Test.QuickCheck.Arbitrary.CoArbitrary (Std.Data.Vector.Base.Vector a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Std.Data.Vector.Base.Vector a) instance Data.Hashable.Class.Hashable1 Std.Data.Vector.Base.Vector -- | This module provides functions for writing vector literals using -- QuasiQuote. module Std.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 Std.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 Std.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 'take/drop', index/length -- 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 :: 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 :: (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 :: (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. 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 -- | 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 Std.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 -- | 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 (Std.Data.Vector.Sort.RadixDown a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Std.Data.Vector.Sort.RadixDown a) instance GHC.Show.Show a => GHC.Show.Show (Std.Data.Vector.Sort.RadixDown a) instance Std.Data.Vector.Sort.Radix a => Std.Data.Vector.Sort.Radix (Std.Data.Vector.Sort.RadixDown a) instance Std.Data.Vector.Sort.Radix GHC.Int.Int8 instance Std.Data.Vector.Sort.Radix GHC.Types.Int instance Std.Data.Vector.Sort.Radix GHC.Int.Int16 instance Std.Data.Vector.Sort.Radix GHC.Int.Int32 instance Std.Data.Vector.Sort.Radix GHC.Int.Int64 instance Std.Data.Vector.Sort.Radix GHC.Word.Word8 instance Std.Data.Vector.Sort.Radix GHC.Types.Word instance Std.Data.Vector.Sort.Radix GHC.Word.Word16 instance Std.Data.Vector.Sort.Radix GHC.Word.Word32 instance Std.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 Std.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 (MArray v) (IArray v) a) => Vec v a where { -- | Vector's mutable array type type family MArray v = (marr :: * -> * -> *) | marr -> v; -- | Vector's immutable array type type family IArray v = (iarr :: * -> *) | iarr -> v; } -- | Boxed vector data Vector a -- | Primitive vector data PrimVector a -- | Bytes is just primitive word8 vectors. type Bytes = PrimVector Word8 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 'take/drop', index/length -- 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 :: 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 :: (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 :: (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. 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 -- | 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 -- | Index 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 -- | INTERNAL MODULE, provides all libuv errno. module Std.IO.UV.Errno uvStdError :: CInt -> IO String uv_strerror :: CInt -> IO CString uvErrName :: CInt -> IO String uv_err_name :: CInt -> IO CString -- | argument list too long pattern UV_E2BIG :: CInt -- | permission denied pattern UV_EACCES :: CInt -- | address already in use pattern UV_EADDRINUSE :: CInt -- | address not available pattern UV_EADDRNOTAVAIL :: CInt -- | address family not supported pattern UV_EAFNOSUPPORT :: CInt -- | resource temporarily unavailable pattern UV_EAGAIN :: CInt -- | address family not supported pattern UV_EAI_ADDRFAMILY :: CInt -- | temporary failure pattern UV_EAI_AGAIN :: CInt -- | bad ai_flags value pattern UV_EAI_BADFLAGS :: CInt -- | invalid value for hints pattern UV_EAI_BADHINTS :: CInt -- | request canceled pattern UV_EAI_CANCELED :: CInt -- | permanent failure pattern UV_EAI_FAIL :: CInt -- | ai_family not supported pattern UV_EAI_FAMILY :: CInt -- | out of memory pattern UV_EAI_MEMORY :: CInt -- | no address pattern UV_EAI_NODATA :: CInt -- | unknown node or service pattern UV_EAI_NONAME :: CInt -- | argument buffer overflow pattern UV_EAI_OVERFLOW :: CInt -- | resolved protocol is unknown pattern UV_EAI_PROTOCOL :: CInt -- | service not available for socket type pattern UV_EAI_SERVICE :: CInt -- | socket type not supported pattern UV_EAI_SOCKTYPE :: CInt -- | connection already in progress pattern UV_EALREADY :: CInt -- | bad file descriptor pattern UV_EBADF :: CInt -- | resource busy or locked pattern UV_EBUSY :: CInt -- | operation canceled pattern UV_ECANCELED :: CInt -- | invalid Unicode character pattern UV_ECHARSET :: CInt -- | software caused connection abort pattern UV_ECONNABORTED :: CInt -- | connection refused pattern UV_ECONNREFUSED :: CInt -- | connection reset by peer pattern UV_ECONNRESET :: CInt -- | destination address required pattern UV_EDESTADDRREQ :: CInt -- | file already exists pattern UV_EEXIST :: CInt -- | bad address in system call argument pattern UV_EFAULT :: CInt -- | file too large pattern UV_EFBIG :: CInt -- | host is unreachable pattern UV_EHOSTUNREACH :: CInt -- | interrupted system call pattern UV_EINTR :: CInt -- | invalid argument pattern UV_EINVAL :: CInt -- | i/o error pattern UV_EIO :: CInt -- | socket is already connected pattern UV_EISCONN :: CInt -- | illegal operation on a directory pattern UV_EISDIR :: CInt -- | too many symbolic links encountered pattern UV_ELOOP :: CInt -- | too many open files pattern UV_EMFILE :: CInt -- | message too long pattern UV_EMSGSIZE :: CInt -- | name too long pattern UV_ENAMETOOLONG :: CInt -- | network is down pattern UV_ENETDOWN :: CInt -- | network is unreachable pattern UV_ENETUNREACH :: CInt -- | file table overflow pattern UV_ENFILE :: CInt -- | no buffer space available pattern UV_ENOBUFS :: CInt -- | no such device pattern UV_ENODEV :: CInt -- | no such file or directory pattern UV_ENOENT :: CInt -- | not enough memory pattern UV_ENOMEM :: CInt -- | machine is not on the network pattern UV_ENONET :: CInt -- | protocol not available pattern UV_ENOPROTOOPT :: CInt -- | no space left on device pattern UV_ENOSPC :: CInt -- | function not implemented pattern UV_ENOSYS :: CInt -- | socket is not connected pattern UV_ENOTCONN :: CInt -- | not a directory pattern UV_ENOTDIR :: CInt -- | directory not empty pattern UV_ENOTEMPTY :: CInt -- | socket operation on non-socket pattern UV_ENOTSOCK :: CInt -- | operation not supported on socket pattern UV_ENOTSUP :: CInt -- | operation not permitted pattern UV_EPERM :: CInt -- | broken pipe pattern UV_EPIPE :: CInt -- | protocol error pattern UV_EPROTO :: CInt -- | protocol not supported pattern UV_EPROTONOSUPPORT :: CInt -- | protocol wrong type for socket pattern UV_EPROTOTYPE :: CInt -- | result too large pattern UV_ERANGE :: CInt -- | read-only file system pattern UV_EROFS :: CInt -- | cannot send after transport endpoint shutdown pattern UV_ESHUTDOWN :: CInt -- | invalid seek pattern UV_ESPIPE :: CInt -- | no such process pattern UV_ESRCH :: CInt -- | connection timed out pattern UV_ETIMEDOUT :: CInt -- | text file is busy pattern UV_ETXTBSY :: CInt -- | cross-device link not permitted pattern UV_EXDEV :: CInt -- | unknown error pattern UV_UNKNOWN :: CInt -- | end of file pattern UV_EOF :: CInt -- | no such device or address pattern UV_ENXIO :: CInt -- | too many links pattern UV_EMLINK :: CInt -- | This module implemented extensible io exception following approach -- described in /An Extensible Dynamically-Typed Hierarchy of Exceptions/ -- by Simon Marlow. The implementation in this module has simplified to -- meet common need. User who want to catch certain type of exceptions -- can directly use exception types this module provide, which are -- modeled after IOErrorType from GHC.IO.Exception. -- -- Functions from this package will throw exceptions from this module -- only instead of the old IOError on IO exceptions. Exceptions -- from this module contain IOEInfo which is pretty detailed, but -- this also require user of this module do some extra work to keep error -- message's quality(provide CallStack, device informations, etc.). New -- defined IO exceptions are encouraged to include a IOEInfo, -- since it helps a lot when debugging. -- -- Example for library author defining new io exception: -- --
--   data MyNetworkException = MyNetworkException IOEInfo ... deriving (Show, Typeable)
--   instance Exception MyNetworkException where
--         toException = ioExceptionToException
--         fromException = ioExceptionFromException
--   
-- -- If you're dealing with OS's errno directly, you should convert the -- errno to libuv's errno in C side with uv_translate_sys_error -- from hs_uv.h, then use 'throwUVIfMinus/throwUVError' from -- this module. module Std.IO.Exception -- | The root type of all io exceptions, you can catch all io exception by -- catching this root type. data SomeIOException SomeIOException :: e -> SomeIOException ioExceptionToException :: Exception e => e -> SomeException ioExceptionFromException :: Exception e => SomeException -> Maybe e -- | IO exceptions informations. data IOEInfo IOEInfo :: String -> String -> CallStack -> IOEInfo -- | the errno name, e.g. EADDRINUSE, etc. empty if no errno. [ioeName] :: IOEInfo -> String -- | description for this io error, can be errno description, or some -- custom description if no errno. [ioeDescription] :: IOEInfo -> String -- | lightweight partial call-stack [ioeCallStack] :: IOEInfo -> CallStack data AlreadyExists AlreadyExists :: IOEInfo -> AlreadyExists data NoSuchThing NoSuchThing :: IOEInfo -> NoSuchThing data ResourceBusy ResourceBusy :: IOEInfo -> ResourceBusy data ResourceExhausted ResourceExhausted :: IOEInfo -> ResourceExhausted data EOF EOF :: IOEInfo -> EOF data IllegalOperation IllegalOperation :: IOEInfo -> IllegalOperation data PermissionDenied PermissionDenied :: IOEInfo -> PermissionDenied data UnsatisfiedConstraints UnsatisfiedConstraints :: IOEInfo -> UnsatisfiedConstraints data SystemError SystemError :: IOEInfo -> SystemError data ProtocolError ProtocolError :: IOEInfo -> ProtocolError data OtherError OtherError :: IOEInfo -> OtherError data InvalidArgument InvalidArgument :: IOEInfo -> InvalidArgument data InappropriateType InappropriateType :: IOEInfo -> InappropriateType data HardwareFault HardwareFault :: IOEInfo -> HardwareFault data UnsupportedOperation UnsupportedOperation :: IOEInfo -> UnsupportedOperation data TimeExpired TimeExpired :: IOEInfo -> TimeExpired data ResourceVanished ResourceVanished :: IOEInfo -> ResourceVanished data Interrupted Interrupted :: IOEInfo -> Interrupted -- | Throw ResourceExhausted if allocation return a nullPtr. throwOOMIfNull :: HasCallStack => IO (Ptr a) -> IO (Ptr a) -- | Throw appropriate IO exception if return value < 0 (libuv's -- convention). throwUVIfMinus :: (HasCallStack, Integral a) => IO a -> IO a -- | Throw appropriate IO exception if return value < 0, otherwise -- ignore the result. throwUVIfMinus_ :: (HasCallStack, Integral a) => IO a -> IO () -- | Throw ResourceVanished with name ECLOSED and -- description 'resource is closed'. throwECLOSED :: HasCallStack => IO a throwECLOSEDSTM :: HasCallStack => STM a throwUVError :: CInt -> IOEInfo -> IO a -- | If the first argument evaluates to True, then the result is the -- second argument. Otherwise an AssertionFailed exception is -- raised, containing a String with the source file and line -- number of the call to assert. -- -- Assertions can normally be turned on or off with a compiler flag (for -- GHC, assertions are normally on unless optimisation is turned on with -- -O or the -fignore-asserts option is given). When -- assertions are turned off, the first argument to assert is -- ignored, and the second argument is returned as the result. assert :: () => Bool -> a -> a -- | When invoked inside mask, this function allows a masked -- asynchronous exception to be raised, if one exists. It is equivalent -- to performing an interruptible operation (see #interruptible), but -- does not involve any actual blocking. -- -- When called outside mask, or inside uninterruptibleMask, -- this function has no effect. allowInterrupt :: IO () -- | Sometimes you want to catch two different sorts of exception. You -- could do something like -- --
--   f = expr `catch` \ (ex :: ArithException) -> handleArith ex
--            `catch` \ (ex :: IOException)    -> handleIO    ex
--   
-- -- However, there are a couple of problems with this approach. The first -- is that having two exception handlers is inefficient. However, the -- more serious issue is that the second exception handler will catch -- exceptions in the first, e.g. in the example above, if -- handleArith throws an IOException then the second -- exception handler will catch it. -- -- Instead, we provide a function catches, which would be used -- thus: -- --
--   f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex),
--                       Handler (\ (ex :: IOException)    -> handleIO    ex)]
--   
catches :: () => IO a -> [Handler a] -> IO a -- | You need this when using catches. data Handler a [Handler] :: forall a e. Exception e => (e -> IO a) -> Handler a -- | Like bracket, but only performs the final action if there was -- an exception raised by the in-between computation. bracketOnError :: () => IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | A variant of bracket where the return value from the first -- computation is not required. bracket_ :: () => IO a -> IO b -> IO c -> IO c -- | A specialised variant of bracket with just a computation to run -- afterward. finally :: () => IO a -> IO b -> IO a -- | When you want to acquire a resource, do some work with it, and then -- release the resource, it is a good idea to use bracket, because -- bracket will install the necessary exception handler to release -- the resource in the event that an exception is raised during the -- computation. If an exception is raised, then bracket will -- re-raise the exception (after performing the release). -- -- A common example is opening a file: -- --
--   bracket
--     (openFile "filename" ReadMode)
--     (hClose)
--     (\fileHandle -> do { ... })
--   
-- -- The arguments to bracket are in this order so that we can -- partially apply it, e.g.: -- --
--   withFile name mode = bracket (openFile name mode) hClose
--   
bracket :: () => IO a -> (a -> IO b) -> (a -> IO c) -> IO c -- | Like finally, but only performs the final action if there was -- an exception raised by the computation. onException :: () => IO a -> IO b -> IO a -- | A variant of try that takes an exception predicate to select -- which exceptions are caught (c.f. catchJust). If the exception -- does not match the predicate, it is re-thrown. tryJust :: Exception e => (e -> Maybe b) -> IO a -> IO (Either b a) -- | Similar to catch, but returns an Either result which is -- (Right a) if no exception of type e was -- raised, or (Left ex) if an exception of type -- e was raised and its value is ex. If any other type -- of exception is raised than it will be propogated up to the next -- enclosing exception handler. -- --
--   try a = catch (Right `liftM` a) (return . Left)
--   
try :: Exception e => IO a -> IO (Either e a) -- | This function maps one exception into another as proposed in the paper -- "A semantics for imprecise exceptions". mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a -- | A version of catchJust with the arguments swapped around (see -- handle). handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a -- | A version of catch with the arguments swapped around; useful in -- situations where the code for the handler is shorter. For example: -- --
--   do handle (\NonTermination -> exitWith (ExitFailure 1)) $
--      ...
--   
handle :: Exception e => (e -> IO a) -> IO a -> IO a -- | The function catchJust is like catch, but it takes an -- extra argument which is an exception predicate, a function -- which selects which type of exceptions we're interested in. -- --
--   catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing)
--             (readFile f)
--             (\_ -> do hPutStrLn stderr ("No such file: " ++ show f)
--                       return "")
--   
-- -- Any other exceptions which are not matched by the predicate are -- re-raised, and may be caught by an enclosing catch, -- catchJust, etc. catchJust :: Exception e => (e -> Maybe b) -> IO a -> (b -> IO a) -> IO a -- | A pattern match failed. The String gives information about -- the source location of the pattern. newtype PatternMatchFail PatternMatchFail :: String -> PatternMatchFail -- | A record selector was applied to a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record selector. newtype RecSelError RecSelError :: String -> RecSelError -- | An uninitialised record field was used. The String gives -- information about the source location where the record was -- constructed. newtype RecConError RecConError :: String -> RecConError -- | A record update was performed on a constructor without the appropriate -- field. This can only happen with a datatype with multiple -- constructors, where some fields are in one constructor but not -- another. The String gives information about the source -- location of the record update. newtype RecUpdError RecUpdError :: String -> RecUpdError -- | A class method without a definition (neither a default definition, nor -- a definition in the appropriate instance) was called. The -- String gives information about which method it was. newtype NoMethodError NoMethodError :: String -> NoMethodError -- | An expression that didn't typecheck during compile time was called. -- This is only possible with -fdefer-type-errors. The String -- gives details about the failed type check. newtype TypeError TypeError :: String -> TypeError -- | Thrown when the runtime system detects that the computation is -- guaranteed not to terminate. Note that there is no guarantee that the -- runtime system will notice whether any given computation is guaranteed -- to terminate or not. data NonTermination NonTermination :: NonTermination -- | Thrown when the program attempts to call atomically, from the -- stm package, inside another call to atomically. data NestedAtomically NestedAtomically :: NestedAtomically -- | throwTo raises an arbitrary exception in the target thread (GHC -- only). -- -- Exception delivery synchronizes between the source and target thread: -- throwTo does not return until the exception has been raised in -- the target thread. The calling thread can thus be certain that the -- target thread has received the exception. Exception delivery is also -- atomic with respect to other exceptions. Atomicity is a useful -- property to have when dealing with race conditions: e.g. if there are -- two threads that can kill each other, it is guaranteed that only one -- of the threads will get to kill the other. -- -- Whatever work the target thread was doing when the exception was -- raised is not lost: the computation is suspended until required by -- another thread. -- -- If the target thread is currently making a foreign call, then the -- exception will not be raised (and hence throwTo will not -- return) until the call has completed. This is the case regardless of -- whether the call is inside a mask or not. However, in GHC a -- foreign call can be annotated as interruptible, in which case -- a throwTo will cause the RTS to attempt to cause the call to -- return; see the GHC documentation for more details. -- -- Important note: the behaviour of throwTo differs from that -- described in the paper "Asynchronous exceptions in Haskell" -- (http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm). -- In the paper, throwTo is non-blocking; but the library -- implementation adopts a more synchronous design in which -- throwTo does not return until the exception is received by the -- target thread. The trade-off is discussed in Section 9 of the paper. -- Like any blocking operation, throwTo is therefore interruptible -- (see Section 5.3 of the paper). Unlike other interruptible operations, -- however, throwTo is always interruptible, even if it -- does not actually block. -- -- There is no guarantee that the exception will be delivered promptly, -- although the runtime will endeavour to ensure that arbitrary delays -- don't occur. In GHC, an exception can only be raised when a thread -- reaches a safe point, where a safe point is where memory -- allocation occurs. Some loops do not perform any memory allocation -- inside the loop and therefore cannot be interrupted by a -- throwTo. -- -- If the target of throwTo is the calling thread, then the -- behaviour is the same as throwIO, except that the exception is -- thrown as an asynchronous exception. This means that if there is an -- enclosing pure computation, which would be the case if the current IO -- operation is inside unsafePerformIO or -- unsafeInterleaveIO, that computation is not permanently -- replaced by the exception, but is suspended as if it had received an -- asynchronous exception. -- -- Note that if throwTo is called with the current thread as the -- target, the exception will be thrown even if the thread is currently -- inside mask or uninterruptibleMask. throwTo :: Exception e => ThreadId -> e -> IO () -- | Raise an IOException in the IO monad. ioError :: () => IOError -> IO a asyncExceptionFromException :: Exception e => SomeException -> Maybe e asyncExceptionToException :: Exception e => e -> SomeException -- | The thread is blocked on an MVar, but there are no other -- references to the MVar so it can't ever continue. data BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar :: BlockedIndefinitelyOnMVar -- | The thread is waiting to retry an STM transaction, but there are no -- other references to any TVars involved, so it can't ever -- continue. data BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM :: BlockedIndefinitelyOnSTM -- | There are no runnable threads, so the program is deadlocked. The -- Deadlock exception is raised in the main thread only. data Deadlock Deadlock :: Deadlock -- | This thread has exceeded its allocation limit. See -- setAllocationCounter and enableAllocationLimit. data AllocationLimitExceeded AllocationLimitExceeded :: AllocationLimitExceeded -- | Compaction found an object that cannot be compacted. Functions cannot -- be compacted, nor can mutable objects or pinned objects. See -- compact. newtype CompactionFailed CompactionFailed :: String -> CompactionFailed -- | assert was applied to False. newtype AssertionFailed AssertionFailed :: String -> AssertionFailed -- | Superclass for asynchronous exceptions. data SomeAsyncException [SomeAsyncException] :: forall e. Exception e => e -> SomeAsyncException -- | Asynchronous exceptions. data AsyncException -- | The current thread's stack exceeded its limit. Since an exception has -- been raised, the thread's stack will certainly be below its limit -- again, but the programmer should take remedial action immediately. StackOverflow :: AsyncException -- | The program's heap is reaching its limit, and the program should take -- action to reduce the amount of live data it has. Notes: -- -- HeapOverflow :: AsyncException -- | This exception is raised by another thread calling killThread, -- or by the system if it needs to terminate the thread for some reason. ThreadKilled :: AsyncException -- | This exception is raised by default in the main thread of the program -- when the user requests to terminate the program via the usual -- mechanism(s) (e.g. Control-C in the console). UserInterrupt :: AsyncException -- | 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 -- | Evaluate the argument to weak head normal form. -- -- evaluate is typically used to uncover any exceptions that a -- lazy value may contain, and possibly handle them. -- -- evaluate only evaluates to weak head normal form. If -- deeper evaluation is needed, the force function from -- Control.DeepSeq may be handy: -- --
--   evaluate $ force x
--   
-- -- There is a subtle difference between evaluate x and -- return $! x, analogous to the difference -- between throwIO and throw. If the lazy value x -- throws an exception, return $! x will fail to -- return an IO action and will throw an exception instead. -- evaluate x, on the other hand, always produces an -- IO action; that action will throw an exception upon -- execution iff x throws an exception upon -- evaluation. -- -- The practical implication of this difference is that due to the -- imprecise exceptions semantics, -- --
--   (return $! error "foo") >> error "bar"
--   
-- -- may throw either "foo" or "bar", depending on the -- optimizations performed by the compiler. On the other hand, -- --
--   evaluate (error "foo") >> error "bar"
--   
-- -- is guaranteed to throw "foo". -- -- The rule of thumb is to use evaluate to force or handle -- exceptions in lazy values. If, on the other hand, you are forcing a -- lazy value for efficiency reasons only and do not care about -- exceptions, you may use return $! x. evaluate :: () => a -> IO a -- | Like mask, but the masked computation is not interruptible (see -- Control.Exception#interruptible). THIS SHOULD BE USED WITH -- GREAT CARE, because if a thread executing in -- uninterruptibleMask blocks for any reason, then the thread (and -- possibly the program, if this is the main thread) will be unresponsive -- and unkillable. This function should only be necessary if you need to -- mask exceptions around an interruptible operation, and you can -- guarantee that the interruptible operation will only block for a short -- period of time. uninterruptibleMask :: () => ((forall a. () => IO a -> IO a) -> IO b) -> IO b -- | Like uninterruptibleMask, but does not pass a restore -- action to the argument. uninterruptibleMask_ :: () => IO a -> IO a -- | Executes an IO computation with asynchronous exceptions masked. -- That is, any thread which attempts to raise an exception in the -- current thread with throwTo will be blocked until asynchronous -- exceptions are unmasked again. -- -- The argument passed to mask is a function that takes as its -- argument another function, which can be used to restore the prevailing -- masking state within the context of the masked computation. For -- example, a common way to use mask is to protect the acquisition -- of a resource: -- --
--   mask $ \restore -> do
--       x <- acquire
--       restore (do_something_with x) `onException` release
--       release
--   
-- -- This code guarantees that acquire is paired with -- release, by masking asynchronous exceptions for the critical -- parts. (Rather than write this code yourself, it would be better to -- use bracket which abstracts the general pattern). -- -- Note that the restore action passed to the argument to -- mask does not necessarily unmask asynchronous exceptions, it -- just restores the masking state to that of the enclosing context. Thus -- if asynchronous exceptions are already masked, mask cannot be -- used to unmask exceptions again. This is so that if you call a library -- function with exceptions masked, you can be sure that the library call -- will not be able to unmask exceptions again. If you are writing -- library code and need to use asynchronous exceptions, the only way is -- to create a new thread; see forkIOWithUnmask. -- -- Asynchronous exceptions may still be received while in the masked -- state if the masked thread blocks in certain ways; see -- Control.Exception#interruptible. -- -- Threads created by forkIO inherit the MaskingState from -- the parent; that is, to start a thread in the -- MaskedInterruptible state, use mask_ $ forkIO .... -- This is particularly useful if you need to establish an exception -- handler in the forked thread before any asynchronous exceptions are -- received. To create a new thread in an unmasked state use -- forkIOWithUnmask. mask :: () => ((forall a. () => IO a -> IO a) -> IO b) -> IO b -- | Like mask, but does not pass a restore action to the -- argument. mask_ :: () => IO a -> IO a -- | Returns the MaskingState for the current thread. getMaskingState :: IO MaskingState -- | Allow asynchronous exceptions to be raised even inside mask, -- making the operation interruptible (see the discussion of -- "Interruptible operations" in Exception). -- -- When called outside mask, or inside uninterruptibleMask, -- this function has no effect. interruptible :: () => IO a -> IO a -- | A variant of throw that can only be used within the IO -- monad. -- -- Although throwIO has a type that is an instance of the type of -- throw, the two functions are subtly different: -- --
--   throw e   `seq` x  ===> throw e
--   throwIO e `seq` x  ===> x
--   
-- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | This is the simplest of the exception-catching functions. It takes a -- single argument, runs it, and if an exception is raised the "handler" -- is executed, with the value of the exception passed as an argument. -- Otherwise, the result is returned as normal. For example: -- --
--   catch (readFile f)
--         (\e -> do let err = show (e :: IOException)
--                   hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err)
--                   return "")
--   
-- -- Note that we have to give a type signature to e, or the -- program will not typecheck as the type is ambiguous. While it is -- possible to catch exceptions of any type, see the section "Catching -- all exceptions" (in Control.Exception) for an explanation of -- the problems with doing so. -- -- For catching exceptions in pure (non-IO) expressions, see the -- function evaluate. -- -- Note that due to Haskell's unspecified evaluation order, an expression -- may throw one of several possible exceptions: consider the expression -- (error "urk") + (1 `div` 0). Does the expression throw -- ErrorCall "urk", or DivideByZero? -- -- The answer is "it might throw either"; the choice is -- non-deterministic. If you are catching any type of exception then you -- might catch either. If you are calling catch with type IO -- Int -> (ArithException -> IO Int) -> IO Int then the -- handler may get run with DivideByZero as an argument, or an -- ErrorCall "urk" exception may be propogated further up. If -- you call it again, you might get a the opposite behaviour. This is ok, -- because catch is an IO computation. catch :: Exception e => IO a -> (e -> IO a) -> IO a -- | Describes the behaviour of a thread when an asynchronous exception is -- received. data MaskingState -- | asynchronous exceptions are unmasked (the normal state) Unmasked :: MaskingState -- | the state during mask: asynchronous exceptions are masked, but -- blocking operations may still be interrupted MaskedInterruptible :: MaskingState -- | the state during uninterruptibleMask: asynchronous exceptions -- are masked, and blocking operations may not be interrupted MaskedUninterruptible :: MaskingState -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. throw :: Exception e => e -> a -- | This is thrown when the user calls error. The first -- String is the argument given to error, second -- String is the location. data ErrorCall ErrorCallWithLocation :: String -> String -> ErrorCall pattern ErrorCall :: () => () => String -> ErrorCall -- | Any type that you wish to throw or catch as an exception must be an -- instance of the Exception class. The simplest case is a new -- exception type directly below the root: -- --
--   data MyException = ThisException | ThatException
--       deriving Show
--   
--   instance Exception MyException
--   
-- -- The default method definitions in the Exception class do what -- we need in this case. You can now throw and catch -- ThisException and ThatException as exceptions: -- --
--   *Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
--   Caught ThisException
--   
-- -- In more complicated examples, you may wish to define a whole hierarchy -- of exceptions: -- --
--   ---------------------------------------------------------------------
--   -- Make the root exception type for all the exceptions in a compiler
--   
--   data SomeCompilerException = forall e . Exception e => SomeCompilerException e
--   
--   instance Show SomeCompilerException where
--       show (SomeCompilerException e) = show e
--   
--   instance Exception SomeCompilerException
--   
--   compilerExceptionToException :: Exception e => e -> SomeException
--   compilerExceptionToException = toException . SomeCompilerException
--   
--   compilerExceptionFromException :: Exception e => SomeException -> Maybe e
--   compilerExceptionFromException x = do
--       SomeCompilerException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make a subhierarchy for exceptions in the frontend of the compiler
--   
--   data SomeFrontendException = forall e . Exception e => SomeFrontendException e
--   
--   instance Show SomeFrontendException where
--       show (SomeFrontendException e) = show e
--   
--   instance Exception SomeFrontendException where
--       toException = compilerExceptionToException
--       fromException = compilerExceptionFromException
--   
--   frontendExceptionToException :: Exception e => e -> SomeException
--   frontendExceptionToException = toException . SomeFrontendException
--   
--   frontendExceptionFromException :: Exception e => SomeException -> Maybe e
--   frontendExceptionFromException x = do
--       SomeFrontendException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make an exception type for a particular frontend compiler exception
--   
--   data MismatchedParentheses = MismatchedParentheses
--       deriving Show
--   
--   instance Exception MismatchedParentheses where
--       toException   = frontendExceptionToException
--       fromException = frontendExceptionFromException
--   
-- -- We can now catch a MismatchedParentheses exception as -- MismatchedParentheses, SomeFrontendException or -- SomeCompilerException, but not other types, e.g. -- IOException: -- --
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException))
--   *** Exception: MismatchedParentheses
--   
class (Typeable e, Show e) => Exception e toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: Exception e => e -> String -- | Arithmetic exceptions. data ArithException Overflow :: ArithException Underflow :: ArithException LossOfPrecision :: ArithException DivideByZero :: ArithException Denormal :: ArithException RatioZeroDenominator :: ArithException -- | The SomeException type is the root of the exception type -- hierarchy. When an exception of type e is thrown, behind the -- scenes it is encapsulated in a SomeException. data SomeException [SomeException] :: forall e. Exception e => e -> SomeException -- | Request a CallStack. -- -- NOTE: The implicit parameter ?callStack :: CallStack is an -- implementation detail and should not be considered part of the -- CallStack API, we may decide to change the implementation in -- the future. type HasCallStack = ?callStack :: CallStack -- | CallStacks are a lightweight method of obtaining a partial -- call-stack at any point in the program. -- -- A function can request its call-site with the HasCallStack -- constraint. For example, we can define -- --
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   
-- -- as a variant of putStrLn that will get its call-site and -- print it, along with the string given as argument. We can access the -- call-stack inside putStrLnWithCallStack with -- callStack. -- --
--   putStrLnWithCallStack :: HasCallStack => String -> IO ()
--   putStrLnWithCallStack msg = do
--     putStrLn msg
--     putStrLn (prettyCallStack callStack)
--   
-- -- Thus, if we call putStrLnWithCallStack we will get a -- formatted call-stack alongside our string. -- --
--   >>> putStrLnWithCallStack "hello"
--   hello
--   CallStack (from HasCallStack):
--     putStrLnWithCallStack, called at <interactive>:2:1 in interactive:Ghci1
--   
-- -- GHC solves HasCallStack constraints in three steps: -- --
    --
  1. If there is a CallStack in scope -- i.e. the enclosing -- function has a HasCallStack constraint -- GHC will append the -- new call-site to the existing CallStack.
  2. --
  3. If there is no CallStack in scope -- e.g. in the GHCi -- session above -- and the enclosing definition does not have an -- explicit type signature, GHC will infer a HasCallStack -- constraint for the enclosing definition (subject to the monomorphism -- restriction).
  4. --
  5. If there is no CallStack in scope and the enclosing -- definition has an explicit type signature, GHC will solve the -- HasCallStack constraint for the singleton CallStack -- containing just the current call-site.
  6. --
-- -- CallStacks do not interact with the RTS and do not require -- compilation with -prof. On the other hand, as they are built -- up explicitly via the HasCallStack constraints, they will -- generally not contain as much information as the simulated call-stacks -- maintained by the RTS. -- -- A CallStack is a [(String, SrcLoc)]. The -- String is the name of function that was called, the -- SrcLoc is the call-site. The list is ordered with the most -- recently called function at the head. -- -- NOTE: The intrepid user may notice that HasCallStack is just an -- alias for an implicit parameter ?callStack :: CallStack. This -- is an implementation detail and should not be considered part -- of the CallStack API, we may decide to change the -- implementation in the future. data CallStack -- | Return the current CallStack. -- -- Does *not* include the call-site of callStack. callStack :: HasCallStack -> CallStack instance GHC.Show.Show Std.IO.Exception.AlreadyExists instance GHC.Show.Show Std.IO.Exception.NoSuchThing instance GHC.Show.Show Std.IO.Exception.ResourceBusy instance GHC.Show.Show Std.IO.Exception.ResourceExhausted instance GHC.Show.Show Std.IO.Exception.EOF instance GHC.Show.Show Std.IO.Exception.IllegalOperation instance GHC.Show.Show Std.IO.Exception.PermissionDenied instance GHC.Show.Show Std.IO.Exception.UnsatisfiedConstraints instance GHC.Show.Show Std.IO.Exception.SystemError instance GHC.Show.Show Std.IO.Exception.ProtocolError instance GHC.Show.Show Std.IO.Exception.OtherError instance GHC.Show.Show Std.IO.Exception.InvalidArgument instance GHC.Show.Show Std.IO.Exception.InappropriateType instance GHC.Show.Show Std.IO.Exception.HardwareFault instance GHC.Show.Show Std.IO.Exception.UnsupportedOperation instance GHC.Show.Show Std.IO.Exception.TimeExpired instance GHC.Show.Show Std.IO.Exception.ResourceVanished instance GHC.Show.Show Std.IO.Exception.Interrupted instance GHC.Exception.Type.Exception Std.IO.Exception.AlreadyExists instance GHC.Exception.Type.Exception Std.IO.Exception.NoSuchThing instance GHC.Exception.Type.Exception Std.IO.Exception.ResourceBusy instance GHC.Exception.Type.Exception Std.IO.Exception.ResourceExhausted instance GHC.Exception.Type.Exception Std.IO.Exception.EOF instance GHC.Exception.Type.Exception Std.IO.Exception.IllegalOperation instance GHC.Exception.Type.Exception Std.IO.Exception.PermissionDenied instance GHC.Exception.Type.Exception Std.IO.Exception.UnsatisfiedConstraints instance GHC.Exception.Type.Exception Std.IO.Exception.SystemError instance GHC.Exception.Type.Exception Std.IO.Exception.ProtocolError instance GHC.Exception.Type.Exception Std.IO.Exception.OtherError instance GHC.Exception.Type.Exception Std.IO.Exception.InvalidArgument instance GHC.Exception.Type.Exception Std.IO.Exception.InappropriateType instance GHC.Exception.Type.Exception Std.IO.Exception.HardwareFault instance GHC.Exception.Type.Exception Std.IO.Exception.UnsupportedOperation instance GHC.Exception.Type.Exception Std.IO.Exception.TimeExpired instance GHC.Exception.Type.Exception Std.IO.Exception.ResourceVanished instance GHC.Exception.Type.Exception Std.IO.Exception.Interrupted instance GHC.Show.Show Std.IO.Exception.IOEInfo instance GHC.Show.Show Std.IO.Exception.SomeIOException instance GHC.Exception.Type.Exception Std.IO.Exception.SomeIOException -- | This module provide low resolution (0.1s) timers using a timing wheel -- of size 128 per capability, each timer thread will automatically -- started or stopped based on demannd. register or cancel a timeout is -- O(1), and each step only need scan n/128 items given timers are -- registered in an even fashion. -- -- This timer is particularly suitable for high concurrent approximated -- IO timeout scheduling. You should not rely on it to provide timing -- information since it's very inaccurate. -- -- Reference: -- -- module Std.IO.LowResTimer -- | Register a new timer on current capability's timer manager, start the -- timing wheel if it's not turning. -- -- If the action could block, you may want to run it in another thread. -- Example to kill a thread after 10s: -- --
--   registerLowResTimer 100 (forkIO $ killThread tid)
--   
registerLowResTimer :: Int -> IO () -> IO LowResTimer -- | void (registerLowResTimer t action) registerLowResTimer_ :: Int -> IO () -> IO () -- | Same as registerLowResTimer, but allow you choose timer -- manager. registerLowResTimerOn :: LowResTimerManager -> Int -> IO () -> IO LowResTimer -- | Timer registered by registerLowResTimer or -- registerLowResTimerOn. data LowResTimer -- | Query how many seconds remain before timer firing. -- -- A return value <= 0 indictate the timer is firing or fired. queryLowResTimer :: LowResTimer -> IO Int -- | Cancel a timer, return the remaining ticks. -- -- This function have no effect after the timer is fired. cancelLowResTimer :: LowResTimer -> IO Int -- |
--   void . cancelLowResTimer
--   
cancelLowResTimer_ :: LowResTimer -> IO () -- | similar to timeout, this function put a limit on time which an -- IO can consume. -- -- Note timeoutLowRes is also implemented with Exception -- underhood, which can have some surprising effects on some devices, -- e.g. use timeoutLowRes with reading or writing on -- UVStreams will close the UVStream once a reading or -- writing is not able to be done in time. timeoutLowRes :: Int -> IO a -> IO (Maybe a) -- | similar to timeoutLowRes, but raise a TimeOutException -- instead of return Nothing if timeout. timeoutLowResEx :: HasCallStack => Int -> IO a -> IO a -- | Cache result of an IO action for give time t. -- -- This combinator is useful when you want to share IO result within a -- period, the action will be called on demand, and the result will be -- cached for t milliseconds. -- -- One common way to get a shared periodical updated value is to start a -- seperate thread and do calculation periodically, but doing that will -- stop system from being idle, which stop idle GC from running, and in -- turn disable deadlock detection, which is too bad. This function -- solves that. throttle :: Int -> IO a -> IO (IO a) -- | Throttle an IO action without caching result. -- -- The IO action will run at leading edge. i.e. once run, during -- following (t/10)s throttled action will no-ops. -- -- Note the action will run in the calling thread. throttle_ :: Int -> IO () -> IO (IO ()) -- | Similar to throttle_ but run action in trailing edge -- -- The IO action will run at trailing edge. i.e. no matter how many times -- throttled action are called, original action will run only once after -- (t/10)s. -- -- Note the action will be run in a new created thread. throttleTrailing_ :: Int -> IO () -> IO (IO ()) data LowResTimerManager -- | Get a LowResTimerManager for current thread. getLowResTimerManager :: IO LowResTimerManager -- | Check if a timer manager's wheel is turning -- -- This is mostly for testing purpose. isLowResTimerManagerRunning :: LowResTimerManager -> IO Bool -- | Create new low resolution timer manager on capability change. -- -- Since low resolution timer manager is not hooked into RTS, you're -- responsible to call this function after you call -- setNumCapabilities to match timer manager array size with new -- capability number. -- -- This is not a must though, when we fetch timer manager we always take -- a modulo. lowResTimerManagerCapabilitiesChanged :: IO () instance GHC.Show.Show Std.IO.LowResTimer.TimeOutException instance GHC.Exception.Type.Exception Std.IO.LowResTimer.TimeOutException -- | This module also implements Gabriel Gonzalez'd idea on Resource -- applicative: -- http://www.haskellforall.com/2013/06/the-resource-applicative.html. -- The Applicative and Monad instance is especially useful -- when you want safely combine multiple resources. -- -- A high performance resource pool based on STM is also provided. module Std.IO.Resource -- | A Resource is an IO action which acquires some resource -- of type a and also returns a finalizer of type IO () that releases the -- resource. -- -- The only safe way to use a Resource is withResource / -- 'withResource\'', You should not use the acquire field -- directly, unless you want to implement your own resource management. -- In the later case, you should always use mask_ since some -- resource initializations may assume async exceptions are masked. -- -- MonadIO instance is provided so that you can lift IO -- computation inside Resource, this is convenient for propagating -- Resource around since many IO computations carry -- finalizers. -- -- A convention in stdio is that functions returning a Resource -- should be named in initXXX format, users are strongly -- recommended to follow this convention. -- -- There're two additional guarantees we made in stdio: -- -- -- -- Library authors providing initXXX are also encouraged to -- provide these guarantees. newtype Resource a Resource :: (HasCallStack => IO (a, IO ())) -> Resource a [acquire] :: Resource a -> HasCallStack => IO (a, IO ()) -- | Create Resource from create and release action. -- -- Note, resource doesn't open resource itself, resource is -- created when you use with / with'. initResource :: IO a -> (a -> IO ()) -> Resource a -- | Create Resource from create and release action. -- -- This function is useful when you want to add some initialization and -- clean up action inside Resource monad. initResource_ :: IO () -> IO () -> Resource () -- | Create a new resource and run some computation, resource is guarantee -- to be closed. -- -- Be care don't leak the resource through computation return value, -- because after the computation finishes, the resource is closed -- already. withResource :: (MonadMask m, MonadIO m, HasCallStack) => Resource a -> (a -> m b) -> m b -- | Create a new resource and run some computation, resource is guarantee -- to be closed. -- -- The difference from with is that the computation will receive -- an extra close action, which can be used to close the resource early -- before the whole computation finished, the close action can be called -- multiple times, only the first call will clean up the resource. withResource' :: (MonadMask m, MonadIO m, HasCallStack) => Resource a -> (a -> m () -> m b) -> m b -- | A high performance resource pool based on STM. -- -- We choose to not divide pool into strips due to the difficults in -- resource balancing. If there is a high contention on resource (see -- statPool), just increase the maximum number of resources can be -- opened. data Pool a data PoolState PoolClosed :: PoolState PoolScanning :: PoolState PoolEmpty :: PoolState -- | Initialize a resource pool with given Resource -- -- Like other initXXX functions, this function won't open a resource pool -- until you use withResource. And this resource pool follow the -- same resource management pattern like other resources. initPool :: Resource a -> Int -> Int -> Resource (Pool a) -- | Get a resource pool's PoolState -- -- This function is useful when debug, under load lots of -- PoolEmpty may indicate contention on resources, i.e. the limit -- on maximum number of resources can be opened should be adjusted to a -- higher number. On the otherhand, lots of PoolScanning may -- indicate there're too much free resources. statPool :: Pool a -> IO PoolState -- | Obtain the pooled resource inside a given resource pool. -- -- You shouldn't use withResource with this resource after you -- closed the pool, an ResourceVanished with EPOOLCLOSED -- name will be thrown. initInPool :: Pool a -> Resource a instance GHC.Show.Show Std.IO.Resource.PoolState instance GHC.Classes.Eq Std.IO.Resource.PoolState instance GHC.Base.Functor Std.IO.Resource.Resource instance GHC.Base.Applicative Std.IO.Resource.Resource instance GHC.Base.Monad Std.IO.Resource.Resource instance Control.Monad.IO.Class.MonadIO Std.IO.Resource.Resource -- | 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. -- -- For convention you should always use `Ptr a` as the tagged pointer -- type, and Addr as the raw address type, use -- `addrToPtr/ptrToAddr` to cast between them if needed. module Std.Foreign.PrimArray -- | 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 withMutableByteArrayUnsafe :: Int -> (MBA# Word8 -> 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) withPrimUnsafe' :: 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 withMutableByteArraySafe :: Int -> (Ptr Word8 -> 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) withPrimSafe' :: 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. 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. 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 () -- | Cast between raw address and tagged pointer. addrToPtr :: Addr -> Ptr a -- | Cast between tagged pointer and raw address. ptrToAddr :: Ptr a -> Addr -- | The castPtr function casts a pointer from one type to another. castPtr :: () => Ptr a -> Ptr b -- | 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 Std.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 error in case of invalid codepoint. validate :: HasCallStack => Bytes -> Text 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 :: BA# Word8 -> Int# -> Int# -> Int c_utf8_validate_addr :: Addr# -> Int -> IO Int instance GHC.Base.Monoid Std.Data.Text.Base.Text instance GHC.Base.Semigroup Std.Data.Text.Base.Text instance GHC.Classes.Eq Std.Data.Text.Base.Text instance GHC.Classes.Ord Std.Data.Text.Base.Text instance GHC.Show.Show Std.Data.Text.Base.Text instance GHC.Read.Read Std.Data.Text.Base.Text instance Control.DeepSeq.NFData Std.Data.Text.Base.Text instance Test.QuickCheck.Arbitrary.Arbitrary Std.Data.Text.Base.Text instance Test.QuickCheck.Arbitrary.CoArbitrary Std.Data.Text.Base.Text instance Data.Hashable.Class.Hashable Std.Data.Text.Base.Text instance Data.String.IsString Std.Data.Text.Base.Text module Std.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 end -- 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 Std.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 'take/drop', index/length -- 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. 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 Std.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 error 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 'take/drop', index/length -- 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. 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 end -- 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 -- | 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 Std.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 (Std.Data.Builder.Base.Builder a) instance GHC.Base.Functor Std.Data.Builder.Base.Builder instance GHC.Base.Applicative Std.Data.Builder.Base.Builder instance GHC.Base.Monad Std.Data.Builder.Base.Builder instance GHC.Base.Semigroup (Std.Data.Builder.Base.Builder ()) instance GHC.Base.Monoid (Std.Data.Builder.Base.Builder ()) instance (a Data.Type.Equality.~ ()) => Data.String.IsString (Std.Data.Builder.Base.Builder a) instance Test.QuickCheck.Arbitrary.Arbitrary (Std.Data.Builder.Base.Builder ()) instance Test.QuickCheck.Arbitrary.CoArbitrary (Std.Data.Builder.Base.Builder ()) -- | Textual numeric builders. module Std.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 [postiveSign] :: 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.Show.Show Std.Data.Builder.Numeric.FFormat instance GHC.Read.Read Std.Data.Builder.Numeric.FFormat instance GHC.Enum.Enum Std.Data.Builder.Numeric.FFormat instance GHC.Classes.Ord Std.Data.Builder.Numeric.IFormat instance GHC.Classes.Eq Std.Data.Builder.Numeric.IFormat instance GHC.Show.Show Std.Data.Builder.Numeric.IFormat instance GHC.Enum.Enum Std.Data.Builder.Numeric.Padding instance GHC.Classes.Ord Std.Data.Builder.Numeric.Padding instance GHC.Classes.Eq Std.Data.Builder.Numeric.Padding instance GHC.Show.Show Std.Data.Builder.Numeric.Padding instance Test.QuickCheck.Arbitrary.Arbitrary Std.Data.Builder.Numeric.IFormat instance Test.QuickCheck.Arbitrary.Arbitrary Std.Data.Builder.Numeric.Padding -- | 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 Std.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 [postiveSign] :: 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 Std.Data.TextBuilder -- | 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 [postiveSign] :: 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.Generics.Generic Std.Data.TextBuilder.Str instance Data.Data.Data Std.Data.TextBuilder.Str instance GHC.Classes.Ord Std.Data.TextBuilder.Str instance GHC.Classes.Eq Std.Data.TextBuilder.Str instance GHC.Base.Monad Std.Data.TextBuilder.TextBuilder instance GHC.Base.Applicative Std.Data.TextBuilder.TextBuilder instance GHC.Base.Functor Std.Data.TextBuilder.TextBuilder instance GHC.Base.Semigroup (Std.Data.TextBuilder.TextBuilder ()) instance GHC.Base.Monoid (Std.Data.TextBuilder.TextBuilder ()) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Semigroup.Min a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Semigroup.Max a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Semigroup.First a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Semigroup.Last a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Semigroup.WrappedMonoid a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Semigroup.Internal.Dual a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Monoid.First a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Monoid.Last a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (GHC.Base.NonEmpty a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Functor.Identity.Identity a) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Data.Functor.Const.Const a b) instance Std.Data.TextBuilder.ToText (Data.Proxy.Proxy a) instance Std.Data.TextBuilder.ToText b => Std.Data.TextBuilder.ToText (Data.Tagged.Tagged a b) instance Std.Data.TextBuilder.ToText (f (g a)) => Std.Data.TextBuilder.ToText (Data.Functor.Compose.Compose f g a) instance (Std.Data.TextBuilder.ToText (f a), Std.Data.TextBuilder.ToText (g a)) => Std.Data.TextBuilder.ToText (Data.Functor.Product.Product f g a) instance (Std.Data.TextBuilder.ToText (f a), Std.Data.TextBuilder.ToText (g a), Std.Data.TextBuilder.ToText a) => Std.Data.TextBuilder.ToText (Data.Functor.Sum.Sum f g a) instance (Std.Data.TextBuilder.GFieldToText a, Std.Data.TextBuilder.GFieldToText b) => Std.Data.TextBuilder.GFieldToText (a GHC.Generics.:*: b) instance Std.Data.TextBuilder.GToText f => Std.Data.TextBuilder.GFieldToText (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance (Std.Data.TextBuilder.GToText f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Std.Data.TextBuilder.GFieldToText (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance (Std.Data.TextBuilder.GFieldToText (GHC.Generics.S1 sc f), GHC.Generics.Constructor c) => Std.Data.TextBuilder.GToText (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance (Std.Data.TextBuilder.GFieldToText (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Std.Data.TextBuilder.GToText (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance Std.Data.TextBuilder.ToText (Std.Data.TextBuilder.TextBuilder a) instance Std.Data.TextBuilder.ToText Std.Data.TextBuilder.Str instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.GToText (GHC.Generics.K1 i a) instance Std.Data.TextBuilder.ToText GHC.Types.Bool instance Std.Data.TextBuilder.ToText GHC.Types.Char instance Std.Data.TextBuilder.ToText GHC.Types.Double instance Std.Data.TextBuilder.ToText GHC.Types.Float instance Std.Data.TextBuilder.ToText GHC.Types.Int instance Std.Data.TextBuilder.ToText GHC.Int.Int8 instance Std.Data.TextBuilder.ToText GHC.Int.Int16 instance Std.Data.TextBuilder.ToText GHC.Int.Int32 instance Std.Data.TextBuilder.ToText GHC.Int.Int64 instance Std.Data.TextBuilder.ToText GHC.Types.Word instance Std.Data.TextBuilder.ToText GHC.Word.Word8 instance Std.Data.TextBuilder.ToText GHC.Word.Word16 instance Std.Data.TextBuilder.ToText GHC.Word.Word32 instance Std.Data.TextBuilder.ToText GHC.Word.Word64 instance Std.Data.TextBuilder.ToText GHC.Integer.Type.Integer instance Std.Data.TextBuilder.ToText GHC.Natural.Natural instance Std.Data.TextBuilder.ToText GHC.Types.Ordering instance Std.Data.TextBuilder.ToText () instance Std.Data.TextBuilder.ToText Data.Version.Version instance Std.Data.TextBuilder.ToText Std.Data.Text.Base.Text instance Std.Data.TextBuilder.ToText Data.Scientific.Scientific instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText [a] instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (Std.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Std.Data.TextBuilder.ToText a) => Std.Data.TextBuilder.ToText (Std.Data.Vector.Base.PrimVector a) instance (Std.Data.TextBuilder.ToText a, Std.Data.TextBuilder.ToText b) => Std.Data.TextBuilder.ToText (a, b) instance (Std.Data.TextBuilder.ToText a, Std.Data.TextBuilder.ToText b, Std.Data.TextBuilder.ToText c) => Std.Data.TextBuilder.ToText (a, b, c) instance (Std.Data.TextBuilder.ToText a, Std.Data.TextBuilder.ToText b, Std.Data.TextBuilder.ToText c, Std.Data.TextBuilder.ToText d) => Std.Data.TextBuilder.ToText (a, b, c, d) instance (Std.Data.TextBuilder.ToText a, Std.Data.TextBuilder.ToText b, Std.Data.TextBuilder.ToText c, Std.Data.TextBuilder.ToText d, Std.Data.TextBuilder.ToText e) => Std.Data.TextBuilder.ToText (a, b, c, d, e) instance (Std.Data.TextBuilder.ToText a, Std.Data.TextBuilder.ToText b, Std.Data.TextBuilder.ToText c, Std.Data.TextBuilder.ToText d, Std.Data.TextBuilder.ToText e, Std.Data.TextBuilder.ToText f) => Std.Data.TextBuilder.ToText (a, b, c, d, e, f) instance (Std.Data.TextBuilder.ToText a, Std.Data.TextBuilder.ToText b, Std.Data.TextBuilder.ToText c, Std.Data.TextBuilder.ToText d, Std.Data.TextBuilder.ToText e, Std.Data.TextBuilder.ToText f, Std.Data.TextBuilder.ToText g) => Std.Data.TextBuilder.ToText (a, b, c, d, e, f, g) instance Std.Data.TextBuilder.ToText a => Std.Data.TextBuilder.ToText (GHC.Maybe.Maybe a) instance (Std.Data.TextBuilder.ToText a, Std.Data.TextBuilder.ToText b) => Std.Data.TextBuilder.ToText (Data.Either.Either a b) instance (Std.Data.TextBuilder.ToText a, GHC.Real.Integral a) => Std.Data.TextBuilder.ToText (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Std.Data.TextBuilder.ToText (Data.Fixed.Fixed a) instance Std.Data.TextBuilder.GToText GHC.Generics.V1 instance (Std.Data.TextBuilder.GToText f, Std.Data.TextBuilder.GToText g) => Std.Data.TextBuilder.GToText (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Std.Data.TextBuilder.GToText (GHC.Generics.C1 c GHC.Generics.U1) instance Std.Data.TextBuilder.GToText f => Std.Data.TextBuilder.GToText (GHC.Generics.D1 c f) instance GHC.Show.Show Std.Data.TextBuilder.Str instance GHC.Read.Read Std.Data.TextBuilder.Str instance (a Data.Type.Equality.~ ()) => Data.String.IsString (Std.Data.TextBuilder.TextBuilder a) instance Test.QuickCheck.Arbitrary.Arbitrary (Std.Data.TextBuilder.TextBuilder ()) instance Test.QuickCheck.Arbitrary.CoArbitrary (Std.Data.TextBuilder.TextBuilder ()) instance GHC.Show.Show (Std.Data.TextBuilder.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 Std.Data.Vector.FlatSet data FlatSet v sortedValues :: FlatSet v -> Vector v size :: FlatSet v -> Int null :: FlatSet v -> Bool -- | O(1) empty flat map. 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 key values, on key duplication prefer -- left one. pack :: Ord v => [v] -> FlatSet v -- | O(N*logN) Pack list of key values with suggested size, on key -- duplication prefer left one. packN :: Ord v => Int -> [v] -> FlatSet v -- | O(N*logN) Pack list of key values, on key duplication prefer -- right one. packR :: Ord v => [v] -> FlatSet v -- | O(N*logN) Pack list of key values with suggested size, on key -- 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 key values, on key duplication prefer -- left one. packVector :: Ord v => Vector v -> FlatSet v -- | O(N*logN) Pack vector of key values, on key duplication prefer -- right one. packVectorR :: Ord v => Vector v -> FlatSet v -- | O(logN) Binary search on flat map. elem :: Ord v => v -> FlatSet v -> Bool -- | O(N) Delete a key value pair by key. delete :: Ord v => v -> FlatSet v -> FlatSet v -- | O(N) Insert new key value into map, replace old one if key -- exists. 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 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 v => Vector v -> v -> Either Int Int instance Control.DeepSeq.NFData v => Control.DeepSeq.NFData (Std.Data.Vector.FlatSet.FlatSet v) instance Data.Foldable.Foldable Std.Data.Vector.FlatSet.FlatSet instance GHC.Classes.Ord v => GHC.Classes.Ord (Std.Data.Vector.FlatSet.FlatSet v) instance GHC.Classes.Eq v => GHC.Classes.Eq (Std.Data.Vector.FlatSet.FlatSet v) instance GHC.Show.Show v => GHC.Show.Show (Std.Data.Vector.FlatSet.FlatSet v) instance Std.Data.TextBuilder.ToText v => Std.Data.TextBuilder.ToText (Std.Data.Vector.FlatSet.FlatSet v) instance GHC.Classes.Ord v => GHC.Base.Semigroup (Std.Data.Vector.FlatSet.FlatSet v) instance GHC.Classes.Ord v => GHC.Base.Monoid (Std.Data.Vector.FlatSet.FlatSet v) instance (GHC.Classes.Ord v, Test.QuickCheck.Arbitrary.Arbitrary v) => Test.QuickCheck.Arbitrary.Arbitrary (Std.Data.Vector.FlatSet.FlatSet v) instance Test.QuickCheck.Arbitrary.CoArbitrary v => Test.QuickCheck.Arbitrary.CoArbitrary (Std.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 Std.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 (Std.Data.Vector.FlatMap.FlatMap k v) instance (GHC.Classes.Eq k, GHC.Classes.Eq v) => GHC.Classes.Eq (Std.Data.Vector.FlatMap.FlatMap k v) instance (GHC.Show.Show k, GHC.Show.Show v) => GHC.Show.Show (Std.Data.Vector.FlatMap.FlatMap k v) instance (Std.Data.TextBuilder.ToText k, Std.Data.TextBuilder.ToText v) => Std.Data.TextBuilder.ToText (Std.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 (Std.Data.Vector.FlatMap.FlatMap k v) instance (Test.QuickCheck.Arbitrary.CoArbitrary k, Test.QuickCheck.Arbitrary.CoArbitrary v) => Test.QuickCheck.Arbitrary.CoArbitrary (Std.Data.Vector.FlatMap.FlatMap k v) instance GHC.Classes.Ord k => GHC.Base.Semigroup (Std.Data.Vector.FlatMap.FlatMap k v) instance GHC.Classes.Ord k => GHC.Base.Monoid (Std.Data.Vector.FlatMap.FlatMap k v) instance (Control.DeepSeq.NFData k, Control.DeepSeq.NFData v) => Control.DeepSeq.NFData (Std.Data.Vector.FlatMap.FlatMap k v) instance GHC.Base.Functor (Std.Data.Vector.FlatMap.FlatMap k) instance Data.Foldable.Foldable (Std.Data.Vector.FlatMap.FlatMap k) instance Data.Traversable.Traversable (Std.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 Std.Data.Vector.FlatIntSet data FlatIntSet sortedValues :: FlatIntSet -> PrimVector Int size :: FlatIntSet -> Int null :: FlatIntSet -> Bool -- | O(1) empty flat map. 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 key values, on key duplication prefer -- left one. pack :: [Int] -> FlatIntSet -- | O(N*logN) Pack list of key values with suggested size, on key -- duplication prefer left one. packN :: Int -> [Int] -> FlatIntSet -- | O(N*logN) Pack list of key values, on key duplication prefer -- right one. packR :: [Int] -> FlatIntSet -- | O(N*logN) Pack list of key values with suggested size, on key -- 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 key values, on key duplication prefer -- left one. packVector :: PrimVector Int -> FlatIntSet -- | O(N*logN) Pack vector of key values, on key duplication prefer -- right one. packVectorR :: PrimVector Int -> FlatIntSet -- | O(logN) Binary search on flat map. elem :: Int -> FlatIntSet -> Bool -- | O(N) Delete a key value pair by key. delete :: Int -> FlatIntSet -> FlatIntSet -- | O(N) Insert new key value into map, replace old one if key -- exists. insert :: Int -> FlatIntSet -> FlatIntSet -- | O(n+m) Merge two FlatIntSet, prefer right value on value -- duplication. merge :: FlatIntSet -> FlatIntSet -> FlatIntSet -- | 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 :: PrimVector Int -> Int -> Either Int Int instance Control.DeepSeq.NFData Std.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Classes.Ord Std.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Classes.Eq Std.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Show.Show Std.Data.Vector.FlatIntSet.FlatIntSet instance Std.Data.TextBuilder.ToText Std.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Base.Semigroup Std.Data.Vector.FlatIntSet.FlatIntSet instance GHC.Base.Monoid Std.Data.Vector.FlatIntSet.FlatIntSet instance Test.QuickCheck.Arbitrary.Arbitrary Std.Data.Vector.FlatIntSet.FlatIntSet instance Test.QuickCheck.Arbitrary.CoArbitrary Std.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 Std.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 (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Classes.Eq v => GHC.Classes.Eq (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Show.Show v => GHC.Show.Show (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance Std.Data.TextBuilder.ToText v => Std.Data.TextBuilder.ToText (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance Test.QuickCheck.Arbitrary.Arbitrary v => Test.QuickCheck.Arbitrary.Arbitrary (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance Test.QuickCheck.Arbitrary.CoArbitrary v => Test.QuickCheck.Arbitrary.CoArbitrary (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Base.Semigroup (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Base.Monoid (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance Control.DeepSeq.NFData v => Control.DeepSeq.NFData (Std.Data.Vector.FlatIntMap.FlatIntMap v) instance GHC.Base.Functor Std.Data.Vector.FlatIntMap.FlatIntMap instance Data.Foldable.Foldable Std.Data.Vector.FlatIntMap.FlatIntMap instance Data.Traversable.Traversable Std.Data.Vector.FlatIntMap.FlatIntMap -- | 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 ["Std.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 Std.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 Std.Data.Parser.Base.Parser instance GHC.Base.Applicative Std.Data.Parser.Base.Parser instance GHC.Base.Monad Std.Data.Parser.Base.Parser instance Control.Monad.Fail.MonadFail Std.Data.Parser.Base.Parser instance GHC.Base.MonadPlus Std.Data.Parser.Base.Parser instance GHC.Base.Alternative Std.Data.Parser.Base.Parser instance GHC.Base.Functor Std.Data.Parser.Base.Result instance GHC.Show.Show a => GHC.Show.Show (Std.Data.Parser.Base.Result a) -- | Textual numeric parsers. module Std.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 Std.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 -- | This module provide buffered IO interface. module Std.IO.Buffered -- | Input device -- -- Laws: readInput should return 0 on EOF. -- -- Note: readInput is considered not thread-safe, e.g. A -- Input device can only be used with a single -- BufferedInput, If multiple BufferedInput s are opened on -- a same Input device, the behaviour will be undefined. class Input i readInput :: (Input i, HasCallStack) => i -> Ptr Word8 -> Int -> IO Int -- | Output device -- -- Laws: writeOutput should not return until all data are written -- (may not necessarily flushed to hardware, that should be done in -- device specific way). class Output o writeOutput :: (Output o, HasCallStack) => o -> Ptr Word8 -> Int -> IO () -- | Input device with buffer, NOT THREAD SAFE! data BufferedInput i newBufferedInput :: input -> Int -> IO (BufferedInput input) -- | Request bytes from BufferedInput. -- -- The buffering logic is quite simple: -- -- If we have pushed back bytes, directly return it, otherwise we read -- using buffer size. If we read N bytes, and N is larger than half of -- the buffer size, then we freeze buffer and return, otherwise we copy -- buffer into result and reuse buffer afterward. readBuffer :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes -- | Push bytes back into buffer unReadBuffer :: (HasCallStack, Input i) => Bytes -> BufferedInput i -> IO () -- | Read buffer and parse with Parser. readParser :: (HasCallStack, Input i) => Parser a -> BufferedInput i -> IO (Bytes, Either ParseError a) -- | Read exactly N bytes -- -- If EOF reached before N bytes read, a ShortReadException will -- be thrown readExactly :: (HasCallStack, Input i) => Int -> BufferedInput i -> IO Bytes -- | Read until reach a magic bytes -- -- If EOF is reached before meet a magic byte, partial bytes are -- returned. readToMagic :: (HasCallStack, Input i) => Word8 -> BufferedInput i -> IO Bytes -- | Read until reach a magic bytes -- -- If EOF is reached before meet a magic byte, a -- ShortReadException will be thrown. readToMagic' :: (HasCallStack, Input i) => Word8 -> BufferedInput i -> IO Bytes -- | Read to a linefeed ('\n' or '\r\n'), return Bytes before it. -- -- If EOF is reached before meet a magic byte, partial line is returned. readLine :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes -- | Read to a linefeed ('\n' or '\r\n'), return Bytes before it. -- -- If EOF reached before meet a '\n', a ShortReadException will be -- thrown. readLine' :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes -- | Read all chunks from a BufferedInput. readAll :: (HasCallStack, Input i) => BufferedInput i -> IO [Bytes] -- | Read all chunks from a BufferedInput, and concat chunks -- together. readAll' :: (HasCallStack, Input i) => BufferedInput i -> IO Bytes -- | Output device with buffer, NOT THREAD SAFE! data BufferedOutput o newBufferedOutput :: output -> Int -> IO (BufferedOutput output) -- | Write Bytes into buffered handle. -- -- Copy Bytes to buffer if it can hold, otherwise write both -- buffer(if not empty) and Bytes. writeBuffer :: Output o => BufferedOutput o -> Bytes -> IO () -- | Write Bytes into buffered handle. -- -- Copy Bytes to buffer if it can hold, otherwise write both -- buffer(if not empty) and Bytes. writeBuilder :: Output o => BufferedOutput o -> Builder a -> IO () -- | Flush the buffer(if not empty). flushBuffer :: Output f => BufferedOutput f -> IO () data ShortReadException ShortReadException :: IOEInfo -> ShortReadException -- | 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 instance GHC.Show.Show Std.IO.Buffered.ShortReadException instance GHC.Exception.Type.Exception Std.IO.Buffered.ShortReadException -- | 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 Std.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 Std.Data.TextBuilder.ToText Std.Data.JSON.Value.Value instance GHC.Generics.Generic Std.Data.JSON.Value.Value instance GHC.Show.Show Std.Data.JSON.Value.Value instance GHC.Classes.Eq Std.Data.JSON.Value.Value instance Control.DeepSeq.NFData Std.Data.JSON.Value.Value instance Test.QuickCheck.Arbitrary.Arbitrary Std.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 Std.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 Std.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 Std.Data.JSON.Base.ConvertError instance GHC.Generics.Generic Std.Data.JSON.Base.ConvertError instance GHC.Classes.Ord Std.Data.JSON.Base.ConvertError instance GHC.Classes.Eq Std.Data.JSON.Base.ConvertError instance Control.DeepSeq.NFData Std.Data.JSON.Base.PathElement instance GHC.Generics.Generic Std.Data.JSON.Base.PathElement instance GHC.Classes.Ord Std.Data.JSON.Base.PathElement instance GHC.Show.Show Std.Data.JSON.Base.PathElement instance GHC.Classes.Eq Std.Data.JSON.Base.PathElement instance Std.Data.JSON.Base.FromValue (f (g a)) => Std.Data.JSON.Base.FromValue (Data.Functor.Compose.Compose f g a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Semigroup.Min a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Semigroup.Max a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Semigroup.First a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Semigroup.Last a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Semigroup.WrappedMonoid a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Semigroup.Internal.Dual a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Monoid.First a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Monoid.Last a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Functor.Identity.Identity a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.Functor.Const.Const a b) instance Std.Data.JSON.Base.FromValue b => Std.Data.JSON.Base.FromValue (Data.Tagged.Tagged a b) instance Std.Data.JSON.Base.ToValue (f (g a)) => Std.Data.JSON.Base.ToValue (Data.Functor.Compose.Compose f g a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Semigroup.Min a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Semigroup.Max a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Semigroup.First a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Semigroup.Last a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Semigroup.WrappedMonoid a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Semigroup.Internal.Dual a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Monoid.First a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Monoid.Last a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Functor.Identity.Identity a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.Functor.Const.Const a b) instance Std.Data.JSON.Base.ToValue b => Std.Data.JSON.Base.ToValue (Data.Tagged.Tagged a b) instance Std.Data.JSON.Base.EncodeJSON (f (g a)) => Std.Data.JSON.Base.EncodeJSON (Data.Functor.Compose.Compose f g a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Semigroup.Min a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Semigroup.Max a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Semigroup.First a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Semigroup.Last a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Semigroup.WrappedMonoid a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Semigroup.Internal.Dual a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Monoid.First a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Monoid.Last a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Functor.Identity.Identity a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.Functor.Const.Const a b) instance Std.Data.JSON.Base.EncodeJSON b => Std.Data.JSON.Base.EncodeJSON (Data.Tagged.Tagged a b) instance (Std.Data.JSON.Base.FromValue (f a), Std.Data.JSON.Base.FromValue (g a), Std.Data.JSON.Base.FromValue a) => Std.Data.JSON.Base.FromValue (Data.Functor.Sum.Sum f g a) instance (Std.Data.JSON.Base.FromValue a, Std.Data.JSON.Base.FromValue b) => Std.Data.JSON.Base.FromValue (Data.Either.Either a b) instance (Std.Data.JSON.Base.FromValue (f a), Std.Data.JSON.Base.FromValue (g a)) => Std.Data.JSON.Base.FromValue (Data.Functor.Product.Product f g a) instance (Std.Data.JSON.Base.FromValue a, Std.Data.JSON.Base.FromValue b) => Std.Data.JSON.Base.FromValue (a, b) instance (Std.Data.JSON.Base.FromValue a, Std.Data.JSON.Base.FromValue b, Std.Data.JSON.Base.FromValue c) => Std.Data.JSON.Base.FromValue (a, b, c) instance (Std.Data.JSON.Base.FromValue a, Std.Data.JSON.Base.FromValue b, Std.Data.JSON.Base.FromValue c, Std.Data.JSON.Base.FromValue d) => Std.Data.JSON.Base.FromValue (a, b, c, d) instance (Std.Data.JSON.Base.FromValue a, Std.Data.JSON.Base.FromValue b, Std.Data.JSON.Base.FromValue c, Std.Data.JSON.Base.FromValue d, Std.Data.JSON.Base.FromValue e) => Std.Data.JSON.Base.FromValue (a, b, c, d, e) instance (Std.Data.JSON.Base.FromValue a, Std.Data.JSON.Base.FromValue b, Std.Data.JSON.Base.FromValue c, Std.Data.JSON.Base.FromValue d, Std.Data.JSON.Base.FromValue e, Std.Data.JSON.Base.FromValue f) => Std.Data.JSON.Base.FromValue (a, b, c, d, e, f) instance (Std.Data.JSON.Base.FromValue a, Std.Data.JSON.Base.FromValue b, Std.Data.JSON.Base.FromValue c, Std.Data.JSON.Base.FromValue d, Std.Data.JSON.Base.FromValue e, Std.Data.JSON.Base.FromValue f, Std.Data.JSON.Base.FromValue g) => Std.Data.JSON.Base.FromValue (a, b, c, d, e, f, g) instance (Std.Data.JSON.Base.ToValue (f a), Std.Data.JSON.Base.ToValue (g a), Std.Data.JSON.Base.ToValue a) => Std.Data.JSON.Base.ToValue (Data.Functor.Sum.Sum f g a) instance (Std.Data.JSON.Base.ToValue a, Std.Data.JSON.Base.ToValue b) => Std.Data.JSON.Base.ToValue (Data.Either.Either a b) instance (Std.Data.JSON.Base.ToValue (f a), Std.Data.JSON.Base.ToValue (g a)) => Std.Data.JSON.Base.ToValue (Data.Functor.Product.Product f g a) instance (Std.Data.JSON.Base.ToValue a, Std.Data.JSON.Base.ToValue b) => Std.Data.JSON.Base.ToValue (a, b) instance (Std.Data.JSON.Base.ToValue a, Std.Data.JSON.Base.ToValue b, Std.Data.JSON.Base.ToValue c) => Std.Data.JSON.Base.ToValue (a, b, c) instance (Std.Data.JSON.Base.ToValue a, Std.Data.JSON.Base.ToValue b, Std.Data.JSON.Base.ToValue c, Std.Data.JSON.Base.ToValue d) => Std.Data.JSON.Base.ToValue (a, b, c, d) instance (Std.Data.JSON.Base.ToValue a, Std.Data.JSON.Base.ToValue b, Std.Data.JSON.Base.ToValue c, Std.Data.JSON.Base.ToValue d, Std.Data.JSON.Base.ToValue e) => Std.Data.JSON.Base.ToValue (a, b, c, d, e) instance (Std.Data.JSON.Base.ToValue a, Std.Data.JSON.Base.ToValue b, Std.Data.JSON.Base.ToValue c, Std.Data.JSON.Base.ToValue d, Std.Data.JSON.Base.ToValue e, Std.Data.JSON.Base.ToValue f) => Std.Data.JSON.Base.ToValue (a, b, c, d, e, f) instance (Std.Data.JSON.Base.ToValue a, Std.Data.JSON.Base.ToValue b, Std.Data.JSON.Base.ToValue c, Std.Data.JSON.Base.ToValue d, Std.Data.JSON.Base.ToValue e, Std.Data.JSON.Base.ToValue f, Std.Data.JSON.Base.ToValue g) => Std.Data.JSON.Base.ToValue (a, b, c, d, e, f, g) instance (Std.Data.JSON.Base.EncodeJSON (f a), Std.Data.JSON.Base.EncodeJSON (g a), Std.Data.JSON.Base.EncodeJSON a) => Std.Data.JSON.Base.EncodeJSON (Data.Functor.Sum.Sum f g a) instance (Std.Data.JSON.Base.EncodeJSON a, Std.Data.JSON.Base.EncodeJSON b) => Std.Data.JSON.Base.EncodeJSON (Data.Either.Either a b) instance (Std.Data.JSON.Base.EncodeJSON (f a), Std.Data.JSON.Base.EncodeJSON (g a)) => Std.Data.JSON.Base.EncodeJSON (Data.Functor.Product.Product f g a) instance (Std.Data.JSON.Base.EncodeJSON a, Std.Data.JSON.Base.EncodeJSON b) => Std.Data.JSON.Base.EncodeJSON (a, b) instance (Std.Data.JSON.Base.EncodeJSON a, Std.Data.JSON.Base.EncodeJSON b, Std.Data.JSON.Base.EncodeJSON c) => Std.Data.JSON.Base.EncodeJSON (a, b, c) instance (Std.Data.JSON.Base.EncodeJSON a, Std.Data.JSON.Base.EncodeJSON b, Std.Data.JSON.Base.EncodeJSON c, Std.Data.JSON.Base.EncodeJSON d) => Std.Data.JSON.Base.EncodeJSON (a, b, c, d) instance (Std.Data.JSON.Base.EncodeJSON a, Std.Data.JSON.Base.EncodeJSON b, Std.Data.JSON.Base.EncodeJSON c, Std.Data.JSON.Base.EncodeJSON d, Std.Data.JSON.Base.EncodeJSON e) => Std.Data.JSON.Base.EncodeJSON (a, b, c, d, e) instance (Std.Data.JSON.Base.EncodeJSON a, Std.Data.JSON.Base.EncodeJSON b, Std.Data.JSON.Base.EncodeJSON c, Std.Data.JSON.Base.EncodeJSON d, Std.Data.JSON.Base.EncodeJSON e, Std.Data.JSON.Base.EncodeJSON f) => Std.Data.JSON.Base.EncodeJSON (a, b, c, d, e, f) instance (Std.Data.JSON.Base.EncodeJSON a, Std.Data.JSON.Base.EncodeJSON b, Std.Data.JSON.Base.EncodeJSON c, Std.Data.JSON.Base.EncodeJSON d, Std.Data.JSON.Base.EncodeJSON e, Std.Data.JSON.Base.EncodeJSON f, Std.Data.JSON.Base.EncodeJSON g) => Std.Data.JSON.Base.EncodeJSON (a, b, c, d, e, f, g) instance Std.Data.JSON.Base.GConstrFromValue GHC.Generics.V1 instance (Std.Data.JSON.Base.GConstrFromValue f, Std.Data.JSON.Base.GConstrFromValue g) => Std.Data.JSON.Base.GConstrFromValue (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Std.Data.JSON.Base.GConstrFromValue (GHC.Generics.C1 c GHC.Generics.U1) instance (GHC.Generics.Constructor c, Std.Data.JSON.Base.GFromValue (GHC.Generics.S1 sc f)) => Std.Data.JSON.Base.GConstrFromValue (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance (Std.Data.Generics.Utils.ProductSize (a GHC.Generics.:*: b), Std.Data.JSON.Base.GFromFields (a GHC.Generics.:*: b), Std.Data.JSON.Base.GBuildLookup (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Std.Data.JSON.Base.GConstrFromValue (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance Std.Data.JSON.Base.GConstrFromValue f => Std.Data.JSON.Base.GFromValue (GHC.Generics.D1 c f) instance (Std.Data.JSON.Base.GBuildLookup a, Std.Data.JSON.Base.GBuildLookup b) => Std.Data.JSON.Base.GBuildLookup (a GHC.Generics.:*: b) instance Std.Data.JSON.Base.GBuildLookup (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance Std.Data.JSON.Base.GBuildLookup (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance (Std.Data.Generics.Utils.ProductSize a, Std.Data.JSON.Base.GFromFields a, Std.Data.JSON.Base.GFromFields b, Std.Data.JSON.Base.LookupTable a Data.Type.Equality.~ Std.Data.JSON.Base.LookupTable b) => Std.Data.JSON.Base.GFromFields (a GHC.Generics.:*: b) instance Std.Data.JSON.Base.GFromValue f => Std.Data.JSON.Base.GFromFields (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance (Std.Data.JSON.Base.GFromValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Std.Data.JSON.Base.GFromFields (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.GFromValue (GHC.Generics.K1 i a) instance Std.Data.JSON.Base.FromValue (Data.Proxy.Proxy a) instance Std.Data.JSON.Base.FromValue Std.Data.JSON.Value.Value instance Std.Data.JSON.Base.FromValue Std.Data.Text.Base.Text instance Std.Data.JSON.Base.FromValue Std.Data.TextBuilder.Str instance Std.Data.JSON.Base.FromValue Data.Scientific.Scientific instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Std.Data.Vector.FlatMap.FlatMap Std.Data.Text.Base.Text a) instance (GHC.Classes.Ord a, Std.Data.JSON.Base.FromValue a) => Std.Data.JSON.Base.FromValue (Std.Data.Vector.FlatSet.FlatSet a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Data.HashMap.Base.HashMap Std.Data.Text.Base.Text a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Std.Data.Vector.FlatIntMap.FlatIntMap a) instance Std.Data.JSON.Base.FromValue Std.Data.Vector.FlatIntSet.FlatIntSet instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (Std.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Std.Data.JSON.Base.FromValue a) => Std.Data.JSON.Base.FromValue (Std.Data.Vector.Base.PrimVector a) instance (GHC.Classes.Eq a, Data.Hashable.Class.Hashable a, Std.Data.JSON.Base.FromValue a) => Std.Data.JSON.Base.FromValue (Data.HashSet.Base.HashSet a) instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue [a] instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (GHC.Base.NonEmpty a) instance Std.Data.JSON.Base.FromValue GHC.Types.Bool instance Std.Data.JSON.Base.FromValue GHC.Types.Char instance Std.Data.JSON.Base.FromValue GHC.Types.Double instance Std.Data.JSON.Base.FromValue GHC.Types.Float instance Std.Data.JSON.Base.FromValue GHC.Types.Int instance Std.Data.JSON.Base.FromValue GHC.Int.Int8 instance Std.Data.JSON.Base.FromValue GHC.Int.Int16 instance Std.Data.JSON.Base.FromValue GHC.Int.Int32 instance Std.Data.JSON.Base.FromValue GHC.Int.Int64 instance Std.Data.JSON.Base.FromValue GHC.Types.Word instance Std.Data.JSON.Base.FromValue GHC.Word.Word8 instance Std.Data.JSON.Base.FromValue GHC.Word.Word16 instance Std.Data.JSON.Base.FromValue GHC.Word.Word32 instance Std.Data.JSON.Base.FromValue GHC.Word.Word64 instance Std.Data.JSON.Base.FromValue GHC.Integer.Type.Integer instance Std.Data.JSON.Base.FromValue GHC.Natural.Natural instance Std.Data.JSON.Base.FromValue GHC.Types.Ordering instance Std.Data.JSON.Base.FromValue () instance Std.Data.JSON.Base.FromValue Data.Version.Version instance Std.Data.JSON.Base.FromValue a => Std.Data.JSON.Base.FromValue (GHC.Maybe.Maybe a) instance (Std.Data.JSON.Base.FromValue a, GHC.Real.Integral a) => Std.Data.JSON.Base.FromValue (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Std.Data.JSON.Base.FromValue (Data.Fixed.Fixed a) instance Std.Data.JSON.Base.GFromValue f => Std.Data.JSON.Base.GFromValue (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance (Std.Data.JSON.Base.GFromValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Std.Data.JSON.Base.GFromValue (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Std.Data.JSON.Base.GConstrEncodeJSON GHC.Generics.V1 instance (Std.Data.JSON.Base.GConstrEncodeJSON f, Std.Data.JSON.Base.GConstrEncodeJSON g) => Std.Data.JSON.Base.GConstrEncodeJSON (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Std.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c GHC.Generics.U1) instance (GHC.Generics.Constructor c, Std.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 sc f)) => Std.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance (Std.Data.JSON.Base.GEncodeJSON (a GHC.Generics.:*: b), Std.Data.JSON.Base.GAddPunctuation (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Std.Data.JSON.Base.GConstrEncodeJSON (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance Std.Data.JSON.Base.GConstrEncodeJSON f => Std.Data.JSON.Base.GEncodeJSON (GHC.Generics.D1 c f) instance Std.Data.JSON.Base.GAddPunctuation a => Std.Data.JSON.Base.GAddPunctuation (a GHC.Generics.:*: b) instance Std.Data.JSON.Base.GAddPunctuation (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance Std.Data.JSON.Base.GAddPunctuation (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.GEncodeJSON (GHC.Generics.K1 i a) instance Std.Data.JSON.Base.EncodeJSON (Data.Proxy.Proxy a) instance Std.Data.JSON.Base.EncodeJSON Std.Data.JSON.Value.Value instance Std.Data.JSON.Base.EncodeJSON Std.Data.Text.Base.Text instance Std.Data.JSON.Base.EncodeJSON Std.Data.TextBuilder.Str instance Std.Data.JSON.Base.EncodeJSON Data.Scientific.Scientific instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Std.Data.Vector.FlatMap.FlatMap Std.Data.Text.Base.Text a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Std.Data.Vector.FlatSet.FlatSet a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.HashMap.Base.HashMap Std.Data.Text.Base.Text a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Std.Data.Vector.FlatIntMap.FlatIntMap a) instance Std.Data.JSON.Base.EncodeJSON Std.Data.Vector.FlatIntSet.FlatIntSet instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Std.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Std.Data.JSON.Base.EncodeJSON a) => Std.Data.JSON.Base.EncodeJSON (Std.Data.Vector.Base.PrimVector a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (Data.HashSet.Base.HashSet a) instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON [a] instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (GHC.Base.NonEmpty a) instance Std.Data.JSON.Base.EncodeJSON GHC.Types.Bool instance Std.Data.JSON.Base.EncodeJSON GHC.Types.Char instance Std.Data.JSON.Base.EncodeJSON GHC.Types.Float instance Std.Data.JSON.Base.EncodeJSON GHC.Types.Double instance Std.Data.JSON.Base.EncodeJSON GHC.Types.Int instance Std.Data.JSON.Base.EncodeJSON GHC.Int.Int8 instance Std.Data.JSON.Base.EncodeJSON GHC.Int.Int16 instance Std.Data.JSON.Base.EncodeJSON GHC.Int.Int32 instance Std.Data.JSON.Base.EncodeJSON GHC.Int.Int64 instance Std.Data.JSON.Base.EncodeJSON GHC.Types.Word instance Std.Data.JSON.Base.EncodeJSON GHC.Word.Word8 instance Std.Data.JSON.Base.EncodeJSON GHC.Word.Word16 instance Std.Data.JSON.Base.EncodeJSON GHC.Word.Word32 instance Std.Data.JSON.Base.EncodeJSON GHC.Word.Word64 instance Std.Data.JSON.Base.EncodeJSON GHC.Integer.Type.Integer instance Std.Data.JSON.Base.EncodeJSON GHC.Natural.Natural instance Std.Data.JSON.Base.EncodeJSON GHC.Types.Ordering instance Std.Data.JSON.Base.EncodeJSON () instance Std.Data.JSON.Base.EncodeJSON Data.Version.Version instance Std.Data.JSON.Base.EncodeJSON a => Std.Data.JSON.Base.EncodeJSON (GHC.Maybe.Maybe a) instance (Std.Data.JSON.Base.EncodeJSON a, GHC.Real.Integral a) => Std.Data.JSON.Base.EncodeJSON (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Std.Data.JSON.Base.EncodeJSON (Data.Fixed.Fixed a) instance (Std.Data.JSON.Base.GEncodeJSON f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Std.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Std.Data.JSON.Base.GEncodeJSON f => Std.Data.JSON.Base.GEncodeJSON (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance (Std.Data.JSON.Base.GEncodeJSON a, Std.Data.JSON.Base.GEncodeJSON b) => Std.Data.JSON.Base.GEncodeJSON (a GHC.Generics.:*: b) instance Std.Data.JSON.Base.GConstrToValue GHC.Generics.V1 instance (Std.Data.JSON.Base.GConstrToValue f, Std.Data.JSON.Base.GConstrToValue g) => Std.Data.JSON.Base.GConstrToValue (f GHC.Generics.:+: g) instance GHC.Generics.Constructor c => Std.Data.JSON.Base.GConstrToValue (GHC.Generics.C1 c GHC.Generics.U1) instance (GHC.Generics.Constructor c, Std.Data.JSON.Base.GToValue (GHC.Generics.S1 sc f)) => Std.Data.JSON.Base.GConstrToValue (GHC.Generics.C1 c (GHC.Generics.S1 sc f)) instance (Std.Data.Generics.Utils.ProductSize (a GHC.Generics.:*: b), Std.Data.JSON.Base.GWriteFields (a GHC.Generics.:*: b), Std.Data.JSON.Base.GMergeFields (a GHC.Generics.:*: b), GHC.Generics.Constructor c) => Std.Data.JSON.Base.GConstrToValue (GHC.Generics.C1 c (a GHC.Generics.:*: b)) instance Std.Data.JSON.Base.GConstrToValue f => Std.Data.JSON.Base.GToValue (GHC.Generics.D1 c f) instance Std.Data.JSON.Base.GMergeFields a => Std.Data.JSON.Base.GMergeFields (a GHC.Generics.:*: b) instance Std.Data.JSON.Base.GMergeFields (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance Std.Data.JSON.Base.GMergeFields (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance (Std.Data.Generics.Utils.ProductSize a, Std.Data.JSON.Base.GWriteFields a, Std.Data.JSON.Base.GWriteFields b, Std.Data.JSON.Base.Field a Data.Type.Equality.~ Std.Data.JSON.Base.Field b) => Std.Data.JSON.Base.GWriteFields (a GHC.Generics.:*: b) instance Std.Data.JSON.Base.GToValue f => Std.Data.JSON.Base.GWriteFields (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance (Std.Data.JSON.Base.GToValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Std.Data.JSON.Base.GWriteFields (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.GToValue (GHC.Generics.K1 i a) instance Std.Data.JSON.Base.ToValue (Data.Proxy.Proxy a) instance Std.Data.JSON.Base.ToValue Std.Data.JSON.Value.Value instance Std.Data.JSON.Base.ToValue Std.Data.Text.Base.Text instance Std.Data.JSON.Base.ToValue Std.Data.TextBuilder.Str instance Std.Data.JSON.Base.ToValue Data.Scientific.Scientific instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Std.Data.Vector.FlatMap.FlatMap Std.Data.Text.Base.Text a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Std.Data.Vector.FlatSet.FlatSet a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.HashMap.Base.HashMap Std.Data.Text.Base.Text a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Std.Data.Vector.FlatIntMap.FlatIntMap a) instance Std.Data.JSON.Base.ToValue Std.Data.Vector.FlatIntSet.FlatIntSet instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Std.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Std.Data.JSON.Base.ToValue a) => Std.Data.JSON.Base.ToValue (Std.Data.Vector.Base.PrimVector a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (Data.HashSet.Base.HashSet a) instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue [a] instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (GHC.Base.NonEmpty a) instance Std.Data.JSON.Base.ToValue GHC.Types.Bool instance Std.Data.JSON.Base.ToValue GHC.Types.Char instance Std.Data.JSON.Base.ToValue GHC.Types.Float instance Std.Data.JSON.Base.ToValue GHC.Types.Double instance Std.Data.JSON.Base.ToValue GHC.Types.Int instance Std.Data.JSON.Base.ToValue GHC.Int.Int8 instance Std.Data.JSON.Base.ToValue GHC.Int.Int16 instance Std.Data.JSON.Base.ToValue GHC.Int.Int32 instance Std.Data.JSON.Base.ToValue GHC.Int.Int64 instance Std.Data.JSON.Base.ToValue GHC.Types.Word instance Std.Data.JSON.Base.ToValue GHC.Word.Word8 instance Std.Data.JSON.Base.ToValue GHC.Word.Word16 instance Std.Data.JSON.Base.ToValue GHC.Word.Word32 instance Std.Data.JSON.Base.ToValue GHC.Word.Word64 instance Std.Data.JSON.Base.ToValue GHC.Integer.Type.Integer instance Std.Data.JSON.Base.ToValue GHC.Natural.Natural instance Std.Data.JSON.Base.ToValue GHC.Types.Ordering instance Std.Data.JSON.Base.ToValue () instance Std.Data.JSON.Base.ToValue Data.Version.Version instance Std.Data.JSON.Base.ToValue a => Std.Data.JSON.Base.ToValue (GHC.Maybe.Maybe a) instance (Std.Data.JSON.Base.ToValue a, GHC.Real.Integral a) => Std.Data.JSON.Base.ToValue (GHC.Real.Ratio a) instance Data.Fixed.HasResolution a => Std.Data.JSON.Base.ToValue (Data.Fixed.Fixed a) instance (Std.Data.JSON.Base.GToValue f, GHC.Generics.Selector ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds)) => Std.Data.JSON.Base.GToValue (GHC.Generics.S1 ('GHC.Generics.MetaSel ('GHC.Maybe.Just l) u ss ds) f) instance Std.Data.JSON.Base.GToValue f => Std.Data.JSON.Base.GToValue (GHC.Generics.S1 ('GHC.Generics.MetaSel 'GHC.Maybe.Nothing u ss ds) f) instance GHC.Base.Functor Std.Data.JSON.Base.Converter instance GHC.Base.Applicative Std.Data.JSON.Base.Converter instance GHC.Base.Alternative Std.Data.JSON.Base.Converter instance GHC.Base.MonadPlus Std.Data.JSON.Base.Converter instance GHC.Base.Monad Std.Data.JSON.Base.Converter instance Control.Monad.Fail.MonadFail Std.Data.JSON.Base.Converter instance GHC.Show.Show Std.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 Std.Data.JSON as JSON
--   import           Std.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 Std.Data.Text          as T
--   import qualified Std.Data.Vector        as V
--   import qualified Std.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 -- Std.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 Std.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 () -- | 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 Std.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(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 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 InvalidArgument -- 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 instance GHC.Show.Show Std.Data.CBytes.CBytes instance GHC.Read.Read Std.Data.CBytes.CBytes instance Control.DeepSeq.NFData Std.Data.CBytes.CBytes instance GHC.Classes.Eq Std.Data.CBytes.CBytes instance GHC.Classes.Ord Std.Data.CBytes.CBytes instance GHC.Base.Semigroup Std.Data.CBytes.CBytes instance GHC.Base.Monoid Std.Data.CBytes.CBytes instance Data.Hashable.Class.Hashable Std.Data.CBytes.CBytes instance Data.String.IsString Std.Data.CBytes.CBytes -- | This module provides necessary types and constant for low level socket -- operation. module Std.IO.SockAddr -- | IPv4 or IPv6 socket address, i.e. the sockaddr_in or -- sockaddr_in6 struct. data SockAddr SockAddrInet :: {-# UNPACK #-} !PortNumber -> {-# UNPACK #-} !InetAddr -> SockAddr SockAddrInet6 :: {-# UNPACK #-} !PortNumber -> {-# UNPACK #-} !FlowInfo -> {-# UNPACK #-} !Inet6Addr -> {-# UNPACK #-} !ScopeID -> SockAddr sockAddrFamily :: SockAddr -> SocketFamily peekSockAddr :: HasCallStack => Ptr SockAddr -> IO SockAddr withSockAddr :: SockAddr -> (Ptr SockAddr -> IO a) -> IO a withSockAddrStorage :: (Ptr SockAddr -> Ptr CInt -> IO ()) -> IO SockAddr -- | Independent of endianness. For example 127.0.0.1 is stored as -- (127, 0, 0, 1). -- -- For direct manipulation prefer inetAddrToTuple and -- tupleToInetAddr. data InetAddr -- |
--   0.0.0.0
--   
inetAny :: InetAddr -- |
--   255.255.255.255
--   
inetBroadcast :: InetAddr -- |
--   255.255.255.255
--   
inetNone :: InetAddr -- |
--   127.0.0.1
--   
inetLoopback :: InetAddr -- |
--   224.0.0.0
--   
inetUnspecificGroup :: InetAddr -- |
--   224.0.0.1
--   
inetAllHostsGroup :: InetAddr -- |
--   224.0.0.255
--   
inetMaxLocalGroup :: InetAddr -- | Converts HostAddress to representation-independent IPv4 -- quadruple. For example for 127.0.0.1 the function will return -- (127, 0, 0, 1) regardless of host endianness. inetAddrToTuple :: InetAddr -> (Word8, Word8, Word8, Word8) -- | Converts IPv4 quadruple to HostAddress. tupleToInetAddr :: (Word8, Word8, Word8, Word8) -> InetAddr -- | Independent of endianness. For example ::1 is stored as -- (0, 0, 0, 1). -- -- For direct manipulation prefer inet6AddrToTuple and -- tupleToInet6Addr. data Inet6Addr -- |
--   ::
--   
inet6Any :: Inet6Addr -- |
--   ::1
--   
inet6Loopback :: Inet6Addr inet6AddrToTuple :: Inet6Addr -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) tupleToInet6Addr :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> Inet6Addr type FlowInfo = Word32 type ScopeID = Word32 -- | Use the Num instance (i.e. use a literal or -- fromIntegral) to create a PortNumber value with the -- correct network-byte-ordering. -- --
--   >>> 1 :: PortNumber
--   1
--   
--   >>> read "1" :: PortNumber
--   1
--   
data PortNumber aNY_PORT :: PortNumber htons :: Word16 -> Word16 ntohs :: Word16 -> Word16 ntohl :: Word32 -> Word32 htonl :: Word32 -> Word32 newtype SocketFamily SocketFamily :: CInt -> SocketFamily -- | unspecified pattern AF_UNSPEC :: SocketFamily -- | internetwork: UDP, TCP, etc pattern AF_INET :: SocketFamily -- | Internet Protocol version 6 pattern AF_INET6 :: SocketFamily newtype SocketType SocketType :: CInt -> SocketType pattern SOCK_DGRAM :: SocketType pattern SOCK_STREAM :: SocketType pattern SOCK_SEQPACKET :: SocketType pattern SOCK_RAW :: SocketType pattern SOCK_RDM :: SocketType newtype SocketProtocol SocketProtocol :: CInt -> SocketProtocol pattern IPPROTO_TCP :: SocketProtocol pattern IPPROTO_UDP :: SocketProtocol instance GHC.Classes.Ord Std.IO.SockAddr.SocketProtocol instance GHC.Classes.Eq Std.IO.SockAddr.SocketProtocol instance GHC.Read.Read Std.IO.SockAddr.SocketProtocol instance GHC.Show.Show Std.IO.SockAddr.SocketProtocol instance GHC.Classes.Ord Std.IO.SockAddr.SocketType instance GHC.Classes.Eq Std.IO.SockAddr.SocketType instance GHC.Read.Read Std.IO.SockAddr.SocketType instance GHC.Show.Show Std.IO.SockAddr.SocketType instance GHC.Classes.Ord Std.IO.SockAddr.SocketFamily instance GHC.Classes.Eq Std.IO.SockAddr.SocketFamily instance GHC.Read.Read Std.IO.SockAddr.SocketFamily instance GHC.Show.Show Std.IO.SockAddr.SocketFamily instance GHC.Classes.Ord Std.IO.SockAddr.SockAddr instance GHC.Classes.Eq Std.IO.SockAddr.SockAddr instance GHC.Show.Show Std.IO.SockAddr.SockAddr instance GHC.Classes.Ord Std.IO.SockAddr.PortNumber instance GHC.Classes.Eq Std.IO.SockAddr.PortNumber instance GHC.Classes.Ord Std.IO.SockAddr.Inet6Addr instance GHC.Classes.Eq Std.IO.SockAddr.Inet6Addr instance GHC.Classes.Ord Std.IO.SockAddr.InetAddr instance GHC.Classes.Eq Std.IO.SockAddr.InetAddr instance Foreign.Storable.Storable Std.IO.SockAddr.SocketProtocol instance Foreign.Storable.Storable Std.IO.SockAddr.SocketType instance Foreign.Storable.Storable Std.IO.SockAddr.SocketFamily instance GHC.Show.Show Std.IO.SockAddr.PortNumber instance GHC.Read.Read Std.IO.SockAddr.PortNumber instance GHC.Enum.Enum Std.IO.SockAddr.PortNumber instance GHC.Num.Num Std.IO.SockAddr.PortNumber instance GHC.Real.Real Std.IO.SockAddr.PortNumber instance GHC.Real.Integral Std.IO.SockAddr.PortNumber instance Foreign.Storable.Storable Std.IO.SockAddr.PortNumber instance GHC.Show.Show Std.IO.SockAddr.Inet6Addr instance Foreign.Storable.Storable Std.IO.SockAddr.Inet6Addr instance GHC.Show.Show Std.IO.SockAddr.InetAddr instance Foreign.Storable.Storable Std.IO.SockAddr.InetAddr -- | LEON (Little Endian first Object Notation) -- is an efficiently serialization using simple binary encoding. As -- suggested by its name, default instances use little endian encoding, -- i.e. "Intel convention". We do provide instances for BE type -- which explicitly write wrapped value in big endian though. encoded -- data should be portable across machine endianness, word size, or -- compiler version within one major version. For example, data encoded -- using the LEON class could be written on any machine, and read -- back on any another using stdio packages with the same major -- version. module Std.Data.LEON -- | LEON, Little Endian Object Notation. class LEON a encode :: LEON a => a -> Builder () decode :: LEON a => Parser a encode :: (LEON a, Generic a, GLEONEncode (Rep a)) => a -> Builder () decode :: (LEON a, Generic a, GLEONDecode (Rep a)) => Parser a -- | big endianess wrapper newtype BE a BE :: a -> BE a [getBE] :: BE a -> a instance (Std.Data.LEON.GSumEncode a, Std.Data.LEON.GSumEncode b, Std.Data.LEON.SumSize a, Std.Data.LEON.SumSize b) => Std.Data.LEON.GLEONEncode (a GHC.Generics.:+: b) instance (Std.Data.LEON.GSumDecode a, Std.Data.LEON.GSumDecode b, Std.Data.LEON.SumSize a, Std.Data.LEON.SumSize b) => Std.Data.LEON.GLEONDecode (a GHC.Generics.:+: b) instance (Std.Data.LEON.SumSize a, Std.Data.LEON.SumSize b) => Std.Data.LEON.SumSize (a GHC.Generics.:+: b) instance Std.Data.LEON.SumSize (GHC.Generics.C1 c a) instance (Std.Data.LEON.GSumEncode a, Std.Data.LEON.GSumEncode b) => Std.Data.LEON.GSumEncode (a GHC.Generics.:+: b) instance Std.Data.LEON.GLEONEncode a => Std.Data.LEON.GSumEncode (GHC.Generics.C1 c a) instance (Std.Data.LEON.GSumDecode a, Std.Data.LEON.GSumDecode b) => Std.Data.LEON.GSumDecode (a GHC.Generics.:+: b) instance Std.Data.LEON.GLEONDecode a => Std.Data.LEON.GSumDecode (GHC.Generics.C1 c a) instance Std.Data.LEON.LEON GHC.Natural.Natural instance Std.Data.LEON.LEON GHC.Integer.Type.Integer instance Std.Data.LEON.LEON GHC.Word.Word8 instance Std.Data.LEON.LEON GHC.Types.Word instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Word) instance Std.Data.LEON.LEON GHC.Int.Int8 instance Std.Data.LEON.LEON GHC.Types.Int instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Int) instance Std.Data.LEON.LEON GHC.Types.Bool instance Std.Data.LEON.LEON GHC.Types.Ordering instance Std.Data.LEON.LEON GHC.Word.Word16 instance Std.Data.LEON.LEON GHC.Word.Word32 instance Std.Data.LEON.LEON GHC.Word.Word64 instance Std.Data.LEON.LEON GHC.Int.Int16 instance Std.Data.LEON.LEON GHC.Int.Int32 instance Std.Data.LEON.LEON GHC.Int.Int64 instance Std.Data.LEON.LEON GHC.Types.Float instance Std.Data.LEON.LEON GHC.Types.Double instance Std.Data.LEON.LEON GHC.Types.Char instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Word.Word16) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Word.Word32) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Word.Word64) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Int.Int16) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Int.Int32) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Int.Int64) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Float) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Double) instance Std.Data.LEON.LEON (Std.Data.PrimArray.UnalignedAccess.BE GHC.Types.Char) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Std.Data.Vector.Base.Vector a) instance (Data.Primitive.Types.Prim a, Std.Data.LEON.LEON a) => Std.Data.LEON.LEON (Std.Data.Vector.Base.PrimVector a) instance Std.Data.LEON.LEON Std.Data.Text.Base.Text instance Std.Data.LEON.LEON Std.Data.CBytes.CBytes instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON [a] instance Std.Data.LEON.LEON () instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b) => Std.Data.LEON.LEON (a, b) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c) => Std.Data.LEON.LEON (a, b, c) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c, Std.Data.LEON.LEON d) => Std.Data.LEON.LEON (a, b, c, d) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c, Std.Data.LEON.LEON d, Std.Data.LEON.LEON e) => Std.Data.LEON.LEON (a, b, c, d, e) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c, Std.Data.LEON.LEON d, Std.Data.LEON.LEON e, Std.Data.LEON.LEON f) => Std.Data.LEON.LEON (a, b, c, d, e, f) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c, Std.Data.LEON.LEON d, Std.Data.LEON.LEON e, Std.Data.LEON.LEON f, Std.Data.LEON.LEON g) => Std.Data.LEON.LEON (a, b, c, d, e, f, g) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c, Std.Data.LEON.LEON d, Std.Data.LEON.LEON e, Std.Data.LEON.LEON f, Std.Data.LEON.LEON g, Std.Data.LEON.LEON h) => Std.Data.LEON.LEON (a, b, c, d, e, f, g, h) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c, Std.Data.LEON.LEON d, Std.Data.LEON.LEON e, Std.Data.LEON.LEON f, Std.Data.LEON.LEON g, Std.Data.LEON.LEON h, Std.Data.LEON.LEON i) => Std.Data.LEON.LEON (a, b, c, d, e, f, g, h, i) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b, Std.Data.LEON.LEON c, Std.Data.LEON.LEON d, Std.Data.LEON.LEON e, Std.Data.LEON.LEON f, Std.Data.LEON.LEON g, Std.Data.LEON.LEON h, Std.Data.LEON.LEON i, Std.Data.LEON.LEON j) => Std.Data.LEON.LEON (a, b, c, d, e, f, g, h, i, j) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Functor.Identity.Identity a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (GHC.Maybe.Maybe a) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b) => Std.Data.LEON.LEON (Data.Either.Either a b) instance Std.Data.LEON.LEON GHC.Fingerprint.Type.Fingerprint instance Std.Data.LEON.LEON Data.Version.Version instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.Internal.Dual a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.Internal.Sum a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.Internal.Product a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Monoid.First a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Monoid.Last a) instance Std.Data.LEON.LEON Data.Semigroup.Internal.All instance Std.Data.LEON.LEON Data.Semigroup.Internal.Any instance Std.Data.LEON.LEON (f a) => Std.Data.LEON.LEON (Data.Semigroup.Internal.Alt f a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.Min a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.Max a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.First a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.Last a) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (Data.Semigroup.Option a) instance Std.Data.LEON.LEON m => Std.Data.LEON.LEON (Data.Semigroup.WrappedMonoid m) instance (Std.Data.LEON.LEON a, Std.Data.LEON.LEON b) => Std.Data.LEON.LEON (Data.Semigroup.Arg a b) instance Std.Data.LEON.LEON a => Std.Data.LEON.LEON (GHC.Base.NonEmpty a) instance Std.Data.LEON.LEON a => Std.Data.LEON.GLEONEncode (GHC.Generics.K1 i a) instance Std.Data.LEON.LEON a => Std.Data.LEON.GLEONDecode (GHC.Generics.K1 i a) instance Std.Data.LEON.GLEONDecode GHC.Generics.V1 instance Std.Data.LEON.GLEONDecode GHC.Generics.U1 instance (Std.Data.LEON.GLEONDecode a, Std.Data.LEON.GLEONDecode b) => Std.Data.LEON.GLEONDecode (a GHC.Generics.:*: b) instance Std.Data.LEON.GLEONDecode a => Std.Data.LEON.GLEONDecode (GHC.Generics.M1 i c a) instance Std.Data.LEON.GLEONEncode GHC.Generics.V1 instance Std.Data.LEON.GLEONEncode GHC.Generics.U1 instance (Std.Data.LEON.GLEONEncode a, Std.Data.LEON.GLEONEncode b) => Std.Data.LEON.GLEONEncode (a GHC.Generics.:*: b) instance Std.Data.LEON.GLEONEncode a => Std.Data.LEON.GLEONEncode (GHC.Generics.M1 i c a) -- | INTERNAL MODULE, provides all libuv side operations. module Std.IO.UV.FFI uv_version :: IO CUInt uv_version_string :: IO CString type UVSlot = Int -- | UVSlotUnSafe wrap a slot which may not have a MVar in -- blocking table, i.e. the blocking table need to be resized. newtype UVSlotUnSafe UVSlotUnSafe :: UVSlot -> UVSlotUnSafe [unsafeGetSlot] :: UVSlotUnSafe -> UVSlot type UVFD = Int32 pattern ACCEPT_BUFFER_SIZE :: Int pattern SO_REUSEPORT_LOAD_BALANCE :: Int pattern INIT_LOOP_SIZE :: Int data UVLoop data UVLoopData peekUVEventQueue :: Ptr UVLoopData -> IO (Int, Ptr Int) clearUVEventCounter :: Ptr UVLoopData -> IO () peekUVBufferTable :: Ptr UVLoopData -> IO (Ptr (Ptr Word8), Ptr CSsize) newtype UVRunMode UVRunMode :: CInt -> UVRunMode pattern UV_RUN_DEFAULT :: UVRunMode pattern UV_RUN_ONCE :: UVRunMode pattern UV_RUN_NOWAIT :: UVRunMode -- | Peek loop data pointer from uv loop pointer. peekUVLoopData :: Ptr UVLoop -> IO (Ptr UVLoopData) hs_uv_loop_init :: Int -> IO (Ptr UVLoop) hs_uv_loop_close :: Ptr UVLoop -> IO () -- | uv_run with usafe FFI. uv_run :: Ptr UVLoop -> UVRunMode -> IO CInt -- | uv_run with safe FFI. uv_run_safe :: Ptr UVLoop -> UVRunMode -> IO CInt uv_loop_alive :: Ptr UVLoop -> IO CInt hs_uv_wake_up_timer :: Ptr UVLoopData -> IO CInt hs_uv_wake_up_async :: Ptr UVLoopData -> IO CInt data UVHandle peekUVHandleData :: Ptr UVHandle -> IO UVSlotUnSafe hs_uv_fileno :: Ptr UVHandle -> IO UVFD hs_uv_handle_alloc :: Ptr UVLoop -> IO (Ptr UVHandle) hs_uv_handle_free :: Ptr UVHandle -> IO () hs_uv_handle_close :: Ptr UVHandle -> IO () hs_uv_cancel :: Ptr UVLoop -> UVSlot -> IO () hs_uv_listen :: Ptr UVHandle -> CInt -> IO CInt hs_uv_listen_resume :: Ptr UVHandle -> IO () hs_uv_read_start :: Ptr UVHandle -> IO CInt uv_read_stop :: Ptr UVHandle -> IO CInt hs_uv_write :: Ptr UVHandle -> Ptr Word8 -> Int -> IO UVSlotUnSafe hs_uv_accept_check_alloc :: Ptr UVHandle -> IO (Ptr UVHandle) hs_uv_accept_check_init :: Ptr UVHandle -> IO CInt hs_uv_accept_check_close :: Ptr UVHandle -> IO () hs_uv_tcp_open :: Ptr UVHandle -> UVFD -> IO CInt uv_tcp_init :: Ptr UVLoop -> Ptr UVHandle -> IO CInt uv_tcp_init_ex :: Ptr UVLoop -> Ptr UVHandle -> CUInt -> IO CInt uv_tcp_nodelay :: Ptr UVHandle -> CInt -> IO CInt uv_tcp_keepalive :: Ptr UVHandle -> CInt -> CUInt -> IO CInt uV_TCP_IPV6ONLY :: CUInt uv_tcp_bind :: Ptr UVHandle -> Ptr SockAddr -> CUInt -> IO CInt hs_uv_tcp_connect :: Ptr UVHandle -> Ptr SockAddr -> IO UVSlotUnSafe hs_set_socket_reuse :: Ptr UVHandle -> IO CInt uv_udp_init :: Ptr UVLoop -> Ptr UVHandle -> IO CInt uv_udp_init_ex :: Ptr UVLoop -> Ptr UVHandle -> CUInt -> IO CInt uv_udp_open :: Ptr UVHandle -> UVFD -> IO CInt uv_udp_bind :: Ptr UVHandle -> Ptr SockAddr -> UVUDPFlag -> IO CInt newtype UVMembership UVMembership :: CInt -> UVMembership pattern UV_LEAVE_GROUP :: () => () => UVMembership pattern UV_JOIN_GROUP :: () => () => UVMembership newtype UVUDPFlag UVUDPFlag :: CInt -> UVUDPFlag pattern UV_UDP_DEFAULT :: () => () => UVUDPFlag pattern UV_UDP_IPV6ONLY :: () => () => UVUDPFlag pattern UV_UDP_REUSEADDR :: () => () => UVUDPFlag pattern UV_UDP_PARTIAL :: Int32 uv_udp_set_membership :: Ptr UVHandle -> CString -> CString -> UVMembership -> IO CInt uv_udp_set_multicast_loop :: Ptr UVHandle -> CInt -> IO CInt uv_udp_set_multicast_ttl :: Ptr UVHandle -> CInt -> IO CInt uv_udp_set_multicast_interface :: Ptr UVHandle -> CString -> IO CInt uv_udp_set_broadcast :: Ptr UVHandle -> CInt -> IO CInt uv_udp_set_ttl :: Ptr UVHandle -> CInt -> IO CInt hs_uv_udp_recv_start :: Ptr UVHandle -> IO CInt uv_udp_recv_stop :: Ptr UVHandle -> IO CInt hs_uv_udp_send :: Ptr UVHandle -> Ptr SockAddr -> Ptr Word8 -> Int -> IO UVSlotUnSafe uv_udp_getsockname :: Ptr UVHandle -> Ptr SockAddr -> Ptr CInt -> IO CInt uv_pipe_init :: Ptr UVLoop -> Ptr UVHandle -> CInt -> IO CInt -- | Terminal mode. -- -- When in UV_TTY_MODE_RAW mode, input is always available -- character-by-character, not including modifiers. Additionally, all -- special processing of characters by the terminal is disabled, -- including echoing input characters. Note that CTRL+C will no longer -- cause a SIGINT when in this mode. newtype UVTTYMode UVTTYMode :: CInt -> UVTTYMode pattern UV_TTY_MODE_NORMAL :: UVTTYMode pattern UV_TTY_MODE_RAW :: UVTTYMode pattern UV_TTY_MODE_IO :: UVTTYMode uv_tty_init :: Ptr UVLoop -> Ptr UVHandle -> CInt -> IO CInt uv_tty_set_mode :: Ptr UVHandle -> UVTTYMode -> IO CInt newtype UVFileMode UVFileMode :: CInt -> UVFileMode -- | 00700 user (file owner) has read, write and execute permission pattern S_IRWXU :: UVFileMode -- | 00400 user has read permission pattern S_IRUSR :: UVFileMode -- | 00200 user has write permission pattern S_IWUSR :: UVFileMode -- | 00100 user has execute permission pattern S_IXUSR :: UVFileMode -- | 00070 group has read, write and execute permission pattern S_IRWXG :: UVFileMode -- | 00040 group has read permission pattern S_IRGRP :: UVFileMode -- | 00020 group has write permission pattern S_IWGRP :: UVFileMode -- | 00010 group has execute permission pattern S_IXGRP :: UVFileMode -- | 00007 others have read, write and execute permission pattern S_IRWXO :: UVFileMode -- | 00004 others have read permission pattern S_IROTH :: UVFileMode -- | 00002 others have write permission pattern S_IWOTH :: UVFileMode -- | 00001 others have execute permission pattern S_IXOTH :: UVFileMode -- | Default mode for open, 0o666(readable and writable). pattern DEFAULT_MODE :: UVFileMode hs_uv_fs_open :: CString -> UVFileFlag -> UVFileMode -> IO UVFD hs_uv_fs_close :: UVFD -> IO Int hs_uv_fs_read :: UVFD -> Ptr Word8 -> Int -> Int64 -> IO Int hs_uv_fs_write :: UVFD -> Ptr Word8 -> Int -> Int64 -> IO Int hs_uv_fs_unlink :: CString -> IO Int hs_uv_fs_mkdir :: CString -> UVFileMode -> IO Int hs_uv_fs_rmdir :: CString -> IO Int hs_uv_fs_mkdtemp :: CString -> Int -> CString -> IO Int hs_uv_fs_open_threaded :: CString -> UVFileFlag -> UVFileMode -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_close_threaded :: UVFD -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_read_threaded :: UVFD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_write_threaded :: UVFD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_unlink_threaded :: CString -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_mkdir_threaded :: CString -> UVFileMode -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_rmdir_threaded :: CString -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_mkdtemp_threaded :: CString -> Int -> CString -> Ptr UVLoop -> IO UVSlotUnSafe newtype UVFileFlag UVFileFlag :: CInt -> UVFileFlag -- | The file is opened in append mode. Before each write, the file offset -- is positioned at the end of the file. pattern O_APPEND :: UVFileFlag -- | The file is created if it does not already exist. pattern O_CREAT :: UVFileFlag -- | File IO is done directly to and from user-space buffers, which must be -- aligned. Buffer size and address should be a multiple of the physical -- sector size of the block device, (DO NOT USE WITH stdio's -- BufferedIO) pattern O_DIRECT :: UVFileFlag -- | If the path is not a directory, fail the open. (Not useful on regular -- file) -- -- Note o_DIRECTORY is not supported on Windows. pattern O_DIRECTORY :: UVFileFlag -- | The file is opened for synchronous IO. Write operations will complete -- once all data and a minimum of metadata are flushed to disk. -- -- Note o_DSYNC is supported on Windows via -- FILE_FLAG_WRITE_THROUGH. pattern O_DSYNC :: UVFileFlag -- | If the o_CREAT flag is set and the file already exists, fail -- the open. -- -- Note In general, the behavior of o_EXCL is undefined if it is -- used without o_CREAT. There is one exception: on Linux 2.6 -- and later, o_EXCL can be used without o_CREAT if -- pathname refers to a block device. If the block device is in use by -- the system (e.g., mounted), the open will fail with the error -- EBUSY. pattern O_EXCL :: UVFileFlag -- | Atomically obtain an exclusive lock. -- -- Note UV_FS_O_EXLOCK is only supported on macOS and Windows. (libuv: -- Changed in version 1.17.0: support is added for Windows.) pattern O_EXLOCK :: UVFileFlag -- | Do not update the file access time when the file is read. -- -- Note o_NOATIME is not supported on Windows. pattern O_NOATIME :: UVFileFlag -- | If the path identifies a terminal device, opening the path will not -- cause that terminal to become the controlling terminal for the process -- (if the process does not already have one). (Not sure if this flag is -- useful) -- -- Note o_NOCTTY is not supported on Windows. pattern O_NOCTTY :: UVFileFlag -- | If the path is a symbolic link, fail the open. -- -- Note o_NOFOLLOW is not supported on Windows. pattern O_NOFOLLOW :: UVFileFlag -- | Open the file in nonblocking mode if possible. (Definitely not useful -- with stdio) -- -- Note o_NONBLOCK is not supported on Windows. (Not useful on -- regular file anyway) pattern O_NONBLOCK :: UVFileFlag -- | Access is intended to be random. The system can use this as a hint to -- optimize file caching. -- -- Note o_RANDOM is only supported on Windows via -- FILE_FLAG_RANDOM_ACCESS. pattern O_RANDOM :: UVFileFlag -- | Open the file for read-only access. pattern O_RDONLY :: UVFileFlag -- | Open the file for read-write access. pattern O_RDWR :: UVFileFlag -- | Access is intended to be sequential from beginning to end. The system -- can use this as a hint to optimize file caching. -- -- Note o_SEQUENTIAL is only supported on Windows via -- FILE_FLAG_SEQUENTIAL_SCAN. pattern O_SEQUENTIAL :: UVFileFlag -- | The file is temporary and should not be flushed to disk if possible. -- -- Note o_SHORT_LIVED is only supported on Windows via -- FILE_ATTRIBUTE_TEMPORARY. pattern O_SHORT_LIVED :: UVFileFlag -- | Open the symbolic link itself rather than the resource it points to. pattern O_SYMLINK :: UVFileFlag -- | The file is opened for synchronous IO. Write operations will complete -- once all data and all metadata are flushed to disk. -- -- Note o_SYNC is supported on Windows via -- FILE_FLAG_WRITE_THROUGH. pattern O_SYNC :: UVFileFlag -- | The file is temporary and should not be flushed to disk if possible. -- -- Note o_TEMPORARY is only supported on Windows via -- FILE_ATTRIBUTE_TEMPORARY. pattern O_TEMPORARY :: UVFileFlag -- | If the file exists and is a regular file, and the file is opened -- successfully for write access, its length shall be truncated to zero. pattern O_TRUNC :: UVFileFlag -- | Open the file for write-only access. pattern O_WRONLY :: UVFileFlag newtype UVDirEntType UVDirEntType :: CChar -> UVDirEntType data DirEntType DirEntUnknown :: DirEntType DirEntFile :: DirEntType DirEntDir :: DirEntType DirEntLink :: DirEntType DirEntFIFO :: DirEntType DirEntSocket :: DirEntType DirEntChar :: DirEntType DirEntBlock :: DirEntType fromUVDirEntType :: UVDirEntType -> DirEntType uV__DT_FILE :: UVDirEntType uV__DT_DIR :: UVDirEntType uV__DT_LINK :: UVDirEntType uV__DT_FIFO :: UVDirEntType uV__DT_SOCKET :: UVDirEntType data UVDirEnt uV__DT_CHAR :: UVDirEntType peekUVDirEnt :: Ptr UVDirEnt -> IO (CString, UVDirEntType) uV__DT_BLOCK :: UVDirEntType hs_uv_fs_scandir_cleanup :: Ptr (Ptr UVDirEnt) -> Int -> IO () hs_uv_fs_scandir :: CString -> MBA# (Ptr UVDirEnt) -> IO Int hs_uv_fs_scandir_extra_cleanup :: Ptr (Ptr (Ptr UVDirEnt)) -> Int -> IO () hs_uv_fs_scandir_threaded :: CString -> Ptr (Ptr (Ptr UVDirEnt)) -> Ptr UVLoop -> IO UVSlotUnSafe data UVTimeSpec UVTimeSpec :: {-# UNPACK #-} !CLong -> {-# UNPACK #-} !CLong -> UVTimeSpec [uvtSecond] :: UVTimeSpec -> {-# UNPACK #-} !CLong [uvtNanoSecond] :: UVTimeSpec -> {-# UNPACK #-} !CLong data UVStat UVStat :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> UVStat [stDev] :: UVStat -> {-# UNPACK #-} !Word64 [stMode] :: UVStat -> {-# UNPACK #-} !Word64 [stNlink] :: UVStat -> {-# UNPACK #-} !Word64 [stUid] :: UVStat -> {-# UNPACK #-} !Word64 [stGid] :: UVStat -> {-# UNPACK #-} !Word64 [stRdev] :: UVStat -> {-# UNPACK #-} !Word64 [stIno] :: UVStat -> {-# UNPACK #-} !Word64 [stSize] :: UVStat -> {-# UNPACK #-} !Word64 [stBlksize] :: UVStat -> {-# UNPACK #-} !Word64 [stBlocks] :: UVStat -> {-# UNPACK #-} !Word64 [stFlags] :: UVStat -> {-# UNPACK #-} !Word64 [stGen] :: UVStat -> {-# UNPACK #-} !Word64 [stAtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stMtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stCtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stBirthtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec uvStatSize :: Int peekUVStat :: Ptr UVStat -> IO UVStat hs_uv_fs_stat :: CString -> Ptr UVStat -> IO Int hs_uv_fs_fstat :: UVFD -> Ptr UVStat -> IO Int hs_uv_fs_lstat :: CString -> Ptr UVStat -> IO Int hs_uv_fs_rename :: CString -> CString -> IO Int hs_uv_fs_fsync :: UVFD -> IO Int hs_uv_fs_fdatasync :: UVFD -> IO Int hs_uv_fs_ftruncate :: UVFD -> Int64 -> IO Int hs_uv_fs_stat_threaded :: CString -> Ptr UVStat -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_fstat_threaded :: UVFD -> Ptr UVStat -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_lstat_threaded :: CString -> Ptr UVStat -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_rename_threaded :: CString -> CString -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_fsync_threaded :: UVFD -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_fdatasync_threaded :: UVFD -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_ftruncate_threaded :: UVFD -> Int64 -> Ptr UVLoop -> IO UVSlotUnSafe -- | Flags control copying. -- -- newtype UVCopyFileFlag UVCopyFileFlag :: CInt -> UVCopyFileFlag pattern COPYFILE_DEFAULT :: UVCopyFileFlag pattern COPYFILE_EXCL :: UVCopyFileFlag pattern COPYFILE_FICLONE :: UVCopyFileFlag hs_uv_fs_copyfile :: CString -> CString -> UVCopyFileFlag -> IO Int hs_uv_fs_copyfile_threaded :: CString -> CString -> UVCopyFileFlag -> Ptr UVLoop -> IO UVSlotUnSafe newtype UVAccessMode UVAccessMode :: CInt -> UVAccessMode pattern F_OK :: UVAccessMode pattern R_OK :: UVAccessMode pattern W_OK :: UVAccessMode pattern X_OK :: UVAccessMode data AccessResult NoExistence :: AccessResult NoPermission :: AccessResult AccessOK :: AccessResult hs_uv_fs_access :: CString -> UVAccessMode -> IO Int hs_uv_fs_access_threaded :: CString -> UVAccessMode -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_chmod :: CString -> UVFileMode -> IO Int hs_uv_fs_chmod_threaded :: CString -> UVFileMode -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_fchmod :: UVFD -> UVFileMode -> IO Int hs_uv_fs_fchmod_threaded :: UVFD -> UVFileMode -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_utime :: CString -> Double -> Double -> IO Int hs_uv_fs_utime_threaded :: CString -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_futime :: UVFD -> Double -> Double -> IO Int hs_uv_fs_futime_threaded :: UVFD -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnSafe newtype UVSymlinkFlag UVSymlinkFlag :: CInt -> UVSymlinkFlag pattern SYMLINK_DEFAULT :: UVSymlinkFlag pattern SYMLINK_DIR :: UVSymlinkFlag pattern SYMLINK_JUNCTION :: UVSymlinkFlag hs_uv_fs_link :: CString -> CString -> IO Int hs_uv_fs_link_threaded :: CString -> CString -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_symlink :: CString -> CString -> UVSymlinkFlag -> IO Int hs_uv_fs_symlink_threaded :: CString -> CString -> UVSymlinkFlag -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_readlink_cleanup :: CString -> IO () hs_uv_fs_readlink :: CString -> MBA# CString -> IO Int hs_uv_fs_realpath :: CString -> MBA# CString -> IO Int hs_uv_fs_readlink_extra_cleanup :: Ptr CString -> IO () hs_uv_fs_readlink_threaded :: CString -> Ptr CString -> Ptr UVLoop -> IO UVSlotUnSafe hs_uv_fs_realpath_threaded :: CString -> Ptr CString -> Ptr UVLoop -> IO UVSlotUnSafe newtype UVHandleType UVHandleType :: CInt -> UVHandleType pattern UV_UNKNOWN_HANDLE :: UVHandleType pattern UV_ASYNC :: UVHandleType pattern UV_CHECK :: UVHandleType pattern UV_FS_EVENT :: UVHandleType pattern UV_FS_POLL :: UVHandleType pattern UV_HANDLE :: UVHandleType pattern UV_IDLE :: UVHandleType pattern UV_NAMED_PIPE :: UVHandleType pattern UV_POLL :: UVHandleType pattern UV_PREPARE :: UVHandleType pattern UV_PROCESS :: UVHandleType pattern UV_STREAM :: UVHandleType pattern UV_TCP :: UVHandleType pattern UV_TIMER :: UVHandleType pattern UV_TTY :: UVHandleType pattern UV_UDP :: UVHandleType pattern UV_SIGNAL :: UVHandleType pattern UV_FILE :: UVHandleType uv_guess_handle :: UVFD -> IO UVHandleType instance Foreign.Storable.Storable Std.IO.UV.FFI.UVHandleType instance GHC.Show.Show Std.IO.UV.FFI.UVHandleType instance GHC.Read.Read Std.IO.UV.FFI.UVHandleType instance GHC.Classes.Ord Std.IO.UV.FFI.UVHandleType instance GHC.Classes.Eq Std.IO.UV.FFI.UVHandleType instance GHC.Num.Num Std.IO.UV.FFI.UVSymlinkFlag instance Foreign.Storable.Storable Std.IO.UV.FFI.UVSymlinkFlag instance Data.Bits.Bits Std.IO.UV.FFI.UVSymlinkFlag instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVSymlinkFlag instance GHC.Show.Show Std.IO.UV.FFI.UVSymlinkFlag instance GHC.Read.Read Std.IO.UV.FFI.UVSymlinkFlag instance GHC.Classes.Ord Std.IO.UV.FFI.UVSymlinkFlag instance GHC.Classes.Eq Std.IO.UV.FFI.UVSymlinkFlag instance GHC.Classes.Ord Std.IO.UV.FFI.AccessResult instance GHC.Classes.Eq Std.IO.UV.FFI.AccessResult instance GHC.Show.Show Std.IO.UV.FFI.AccessResult instance GHC.Num.Num Std.IO.UV.FFI.UVAccessMode instance Foreign.Storable.Storable Std.IO.UV.FFI.UVAccessMode instance Data.Bits.Bits Std.IO.UV.FFI.UVAccessMode instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVAccessMode instance GHC.Show.Show Std.IO.UV.FFI.UVAccessMode instance GHC.Read.Read Std.IO.UV.FFI.UVAccessMode instance GHC.Classes.Ord Std.IO.UV.FFI.UVAccessMode instance GHC.Classes.Eq Std.IO.UV.FFI.UVAccessMode instance GHC.Num.Num Std.IO.UV.FFI.UVCopyFileFlag instance Foreign.Storable.Storable Std.IO.UV.FFI.UVCopyFileFlag instance Data.Bits.Bits Std.IO.UV.FFI.UVCopyFileFlag instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVCopyFileFlag instance GHC.Show.Show Std.IO.UV.FFI.UVCopyFileFlag instance GHC.Read.Read Std.IO.UV.FFI.UVCopyFileFlag instance GHC.Classes.Ord Std.IO.UV.FFI.UVCopyFileFlag instance GHC.Classes.Eq Std.IO.UV.FFI.UVCopyFileFlag instance GHC.Generics.Generic Std.IO.UV.FFI.UVStat instance GHC.Classes.Ord Std.IO.UV.FFI.UVStat instance GHC.Classes.Eq Std.IO.UV.FFI.UVStat instance GHC.Read.Read Std.IO.UV.FFI.UVStat instance GHC.Show.Show Std.IO.UV.FFI.UVStat instance GHC.Generics.Generic Std.IO.UV.FFI.UVTimeSpec instance GHC.Classes.Ord Std.IO.UV.FFI.UVTimeSpec instance GHC.Classes.Eq Std.IO.UV.FFI.UVTimeSpec instance GHC.Read.Read Std.IO.UV.FFI.UVTimeSpec instance GHC.Show.Show Std.IO.UV.FFI.UVTimeSpec instance GHC.Generics.Generic Std.IO.UV.FFI.DirEntType instance GHC.Classes.Ord Std.IO.UV.FFI.DirEntType instance GHC.Classes.Eq Std.IO.UV.FFI.DirEntType instance GHC.Show.Show Std.IO.UV.FFI.DirEntType instance GHC.Read.Read Std.IO.UV.FFI.DirEntType instance GHC.Num.Num Std.IO.UV.FFI.UVDirEntType instance Foreign.Storable.Storable Std.IO.UV.FFI.UVDirEntType instance Data.Bits.Bits Std.IO.UV.FFI.UVDirEntType instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVDirEntType instance GHC.Show.Show Std.IO.UV.FFI.UVDirEntType instance GHC.Read.Read Std.IO.UV.FFI.UVDirEntType instance GHC.Classes.Ord Std.IO.UV.FFI.UVDirEntType instance GHC.Classes.Eq Std.IO.UV.FFI.UVDirEntType instance GHC.Num.Num Std.IO.UV.FFI.UVFileFlag instance Foreign.Storable.Storable Std.IO.UV.FFI.UVFileFlag instance Data.Bits.Bits Std.IO.UV.FFI.UVFileFlag instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVFileFlag instance GHC.Show.Show Std.IO.UV.FFI.UVFileFlag instance GHC.Read.Read Std.IO.UV.FFI.UVFileFlag instance GHC.Classes.Ord Std.IO.UV.FFI.UVFileFlag instance GHC.Classes.Eq Std.IO.UV.FFI.UVFileFlag instance GHC.Num.Num Std.IO.UV.FFI.UVFileMode instance Foreign.Storable.Storable Std.IO.UV.FFI.UVFileMode instance Data.Bits.Bits Std.IO.UV.FFI.UVFileMode instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVFileMode instance GHC.Show.Show Std.IO.UV.FFI.UVFileMode instance GHC.Read.Read Std.IO.UV.FFI.UVFileMode instance GHC.Classes.Ord Std.IO.UV.FFI.UVFileMode instance GHC.Classes.Eq Std.IO.UV.FFI.UVFileMode instance GHC.Num.Num Std.IO.UV.FFI.UVTTYMode instance Foreign.Storable.Storable Std.IO.UV.FFI.UVTTYMode instance Data.Bits.Bits Std.IO.UV.FFI.UVTTYMode instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVTTYMode instance GHC.Show.Show Std.IO.UV.FFI.UVTTYMode instance GHC.Read.Read Std.IO.UV.FFI.UVTTYMode instance GHC.Classes.Ord Std.IO.UV.FFI.UVTTYMode instance GHC.Classes.Eq Std.IO.UV.FFI.UVTTYMode instance GHC.Num.Num Std.IO.UV.FFI.UVUDPFlag instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVUDPFlag instance Data.Bits.Bits Std.IO.UV.FFI.UVUDPFlag instance Foreign.Storable.Storable Std.IO.UV.FFI.UVUDPFlag instance GHC.Classes.Ord Std.IO.UV.FFI.UVUDPFlag instance GHC.Classes.Eq Std.IO.UV.FFI.UVUDPFlag instance GHC.Show.Show Std.IO.UV.FFI.UVUDPFlag instance GHC.Classes.Ord Std.IO.UV.FFI.UVMembership instance GHC.Classes.Eq Std.IO.UV.FFI.UVMembership instance GHC.Show.Show Std.IO.UV.FFI.UVMembership instance GHC.Num.Num Std.IO.UV.FFI.UVRunMode instance Foreign.Storable.Storable Std.IO.UV.FFI.UVRunMode instance Data.Bits.Bits Std.IO.UV.FFI.UVRunMode instance Data.Bits.FiniteBits Std.IO.UV.FFI.UVRunMode instance GHC.Show.Show Std.IO.UV.FFI.UVRunMode instance GHC.Read.Read Std.IO.UV.FFI.UVRunMode instance GHC.Classes.Ord Std.IO.UV.FFI.UVRunMode instance GHC.Classes.Eq Std.IO.UV.FFI.UVRunMode instance Foreign.Storable.Storable Std.IO.UV.FFI.UVTimeSpec -- | This module provide IO manager which bridge libuv's async interface -- with ghc's light weight thread. -- -- The main procedures for doing event IO is: -- -- -- -- Usually slots are cache in the IO device so that you don't have to -- allocate new one before each IO operation. Check -- System.IO.Socket.TCP as an example. module Std.IO.UV.Manager data UVManager -- | Get UVManager runing on the same capability. getUVManager :: IO UVManager -- | Get MVar from blocking table with given slot. getBlockMVar :: UVManager -> UVSlot -> IO (MVar Int) peekBufferTable :: UVManager -> UVSlot -> IO Int -- | Poke a prepared buffer and size into loop data under given slot. -- -- NOTE, this action is not protected with 'withUVManager_ for effcient -- reason, you should merge this action with other uv action and put them -- together inside a 'withUVManager_ or 'withUVManager\''. for example: -- --
--   ...
--   withUVManager_ uvm $ do
--       pokeBufferTable uvm slot buf len
--       uvReadStart handle
--   ...
--   
pokeBufferTable :: UVManager -> UVSlot -> Ptr Word8 -> Int -> IO () -- | Lock an uv mananger, so that we can safely mutate its uv_loop's state. -- -- libuv is not thread safe, use this function to perform any action -- which will mutate uv_loop's state. withUVManager :: HasCallStack => UVManager -> (Ptr UVLoop -> IO a) -> IO a -- | Lock an uv mananger, so that we can safely mutate its uv_loop's state. -- -- Some action did not request uv_loop pointer explicitly, but will -- mutate uv_loop underhood, for example: uv_read_start. These -- actions have to be protected by locking the uv_loop. -- -- In fact most of the libuv's functions are not thread safe, so watch -- out! withUVManager_ :: HasCallStack => UVManager -> IO a -> IO a -- | Run a libuv FFI to get a UVSlotUnSafe (which may exceed block -- table size), resize the block table in that case, so that the returned -- slot always has an accompanying MVar in block table. -- -- Always use this function to turn an UVSlotUnsafe into -- UVSlot, so that the block table size synchronize with libuv -- side's slot table. getUVSlot :: HasCallStack => UVManager -> IO UVSlotUnSafe -> IO UVSlot -- | Exception safe uv request helper -- -- This helper will run a libuv's async function, which will return a -- libuv side's slot, then we will accommodate a MVar in block -- table and wait on that MVar, until the async function finished -- or an exception is received, in later case we will call -- cancelUVReq to cancel the on-going async function with best -- efforts, withUVRequest :: HasCallStack => UVManager -> (Ptr UVLoop -> IO UVSlotUnSafe) -> IO Int -- | Same with withUVRequest but disgard the result. withUVRequest_ :: HasCallStack => UVManager -> (Ptr UVLoop -> IO UVSlotUnSafe) -> IO () -- | Same with withUVRequest but apply an convert function to -- result. -- -- The convert function have all access to the returned value including -- negative ones, it's convert funtions's responsiblity to throw an -- exception if appropriate. withUVRequest' :: HasCallStack => UVManager -> (Ptr UVLoop -> IO UVSlotUnSafe) -> (Int -> IO b) -> IO b -- | Same with withUVRequest, but will also run an extra cleanup -- function if async exception hit this thread but the async action is -- already successfully performed, e.g. release result memory. withUVRequestEx :: HasCallStack => UVManager -> (Ptr UVLoop -> IO UVSlotUnSafe) -> (Int -> IO ()) -> IO Int -- | Safely lock an uv manager and perform uv_handle initialization. -- -- Initialization an UV stream usually take two step: -- -- -- -- And this is what initUVStream do, all you need to do is to -- provide the manager you want to hook the handle onto(usually the one -- on the same capability, i.e. the one obtained by getUVManager), -- and provide a custom initialization function (which should throw an -- exception if failed). initUVStream :: HasCallStack => (Ptr UVLoop -> Ptr UVHandle -> IO ()) -> UVManager -> Resource UVStream -- | A haskell data type wrap an uv_stream_t inside -- -- UVStream DO NOT provide thread safety! Use UVStream -- concurrently in multiple threads will lead to undefined behavior. data UVStream UVStream :: {-# UNPACK #-} !Ptr UVHandle -> {-# UNPACK #-} !UVSlot -> UVManager -> {-# UNPACK #-} !IORef Bool -> UVStream [uvsHandle] :: UVStream -> {-# UNPACK #-} !Ptr UVHandle [uvsSlot] :: UVStream -> {-# UNPACK #-} !UVSlot [uvsManager] :: UVStream -> UVManager [uvsClosed] :: UVStream -> {-# UNPACK #-} !IORef Bool -- | Fork a new GHC thread with active load-balancing. -- -- Using libuv based IO solution has a disadvantage that file handlers -- are bound to certain uv_loop, thus certain uv mananger/capability. -- Worker threads that migrate to other capability will lead contention -- since various APIs here is protected by manager's lock, this makes -- GHC's work-stealing strategy unsuitable for certain workload, such as -- a webserver. we solve this problem with simple round-robin -- load-balancing: forkBa will automatically distribute new threads to -- all capabilities in round-robin manner. Thus its name forkBa(lance). forkBa :: IO () -> IO ThreadId instance GHC.Show.Show Std.IO.UV.Manager.UVStream instance Std.IO.Buffered.Input Std.IO.UV.Manager.UVStream instance Std.IO.Buffered.Output Std.IO.UV.Manager.UVStream instance GHC.Show.Show Std.IO.UV.Manager.UVManager instance GHC.Classes.Eq Std.IO.UV.Manager.UVManager -- | This module provides an API for creating UDP sender and receiver. module Std.IO.UDP -- | UDP socket. -- -- UDP socket is not thread safe, don't use it among multiple thread! UDP -- is not a sequential protocol, thus not an instance of 'Input/Output'. -- Message are received or sent individually, we do provide batch -- receiving to improve performance under high load. data UDP UDP :: {-# UNPACK #-} !Ptr UVHandle -> {-# UNPACK #-} !UVSlot -> UVManager -> {-# UNPACK #-} !MutablePrimArray RealWorld Word8 -> {-# UNPACK #-} !Int32 -> {-# UNPACK #-} !MutablePrimArray RealWorld (Ptr Word8) -> {-# UNPACK #-} !MutablePrimArray RealWorld Word8 -> {-# UNPACK #-} !IORef Bool -> UDP [udpHandle] :: UDP -> {-# UNPACK #-} !Ptr UVHandle [udpSlot] :: UDP -> {-# UNPACK #-} !UVSlot [udpManager] :: UDP -> UVManager [udpRecvLargeBuffer] :: UDP -> {-# UNPACK #-} !MutablePrimArray RealWorld Word8 [udpRecvBufferSiz] :: UDP -> {-# UNPACK #-} !Int32 [udpRecvBufferArray] :: UDP -> {-# UNPACK #-} !MutablePrimArray RealWorld (Ptr Word8) [udpSendBuffer] :: UDP -> {-# UNPACK #-} !MutablePrimArray RealWorld Word8 [udpClosed] :: UDP -> {-# UNPACK #-} !IORef Bool -- | Initialize a UDP socket. initUDP :: HasCallStack => UDPConfig -> Resource UDP -- | UDP options. -- -- Though technically message length field in the UDP header is a max of -- 65535, but large packets could be more likely dropped by routers, -- usually a packet(IPV4) with a payload <= 508 bytes is considered -- safe. data UDPConfig UDPConfig :: {-# UNPACK #-} !Int32 -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> Maybe (SockAddr, UVUDPFlag) -> UDPConfig -- | maximum size of a received message [recvMsgSize] :: UDPConfig -> {-# UNPACK #-} !Int32 -- | how many messages we want to receive per uv loop, inside each uv_run, -- we do batch receiving, increase this number can improve receiving -- performance, at the cost of memory and potential GHC thread starving. [recvBatchSize] :: UDPConfig -> {-# UNPACK #-} !Int -- | maximum size of sending buffer [sendMsgSize] :: UDPConfig -> {-# UNPACK #-} !Int -- | do we want bind a local address before receiving & sending? set to -- Nothing to let OS pick a random one. [localUDPAddr] :: UDPConfig -> Maybe (SockAddr, UVUDPFlag) -- | default UDPConfig, defaultUDPConfig = UDPConfig 512 6 512 -- Nothing defaultUDPConfig :: UDPConfig data UVUDPFlag pattern UV_UDP_DEFAULT :: () => () => UVUDPFlag pattern UV_UDP_IPV6ONLY :: () => () => UVUDPFlag pattern UV_UDP_REUSEADDR :: () => () => UVUDPFlag -- | Recv messages from UDP socket, return source address if available, and -- a Bool to indicate if the message is partial (larger than -- receive buffer size). recvUDP :: HasCallStack => UDP -> IO [(Maybe SockAddr, Bool, Bytes)] -- | Send a UDP message to target address. -- -- WARNING: A InvalidArgument with errno UV_EMSGSIZE will -- be thrown if message is larger than sendMsgSize. sendUDP :: HasCallStack => UDP -> SockAddr -> Bytes -> IO () getSockName :: HasCallStack => UDP -> IO SockAddr data UVMembership pattern UV_JOIN_GROUP :: () => () => UVMembership pattern UV_LEAVE_GROUP :: () => () => UVMembership setMembership :: HasCallStack => UDP -> CBytes -> CBytes -> UVMembership -> IO () setMulticastLoop :: HasCallStack => UDP -> Bool -> IO () setMulticastTTL :: HasCallStack => UDP -> Int -> IO () setMulticastInterface :: HasCallStack => UDP -> CBytes -> IO () setBroadcast :: HasCallStack => UDP -> Bool -> IO () setTTL :: HasCallStack => UDP -> Int -> IO () instance GHC.Classes.Ord Std.IO.UDP.UDPConfig instance GHC.Classes.Eq Std.IO.UDP.UDPConfig instance GHC.Show.Show Std.IO.UDP.UDPConfig instance GHC.Show.Show Std.IO.UDP.UDP -- | This module provides an API for creating TCP servers and clients. module Std.IO.TCP -- | A TCP client configuration data ClientConfig ClientConfig :: Maybe SockAddr -> SockAddr -> Bool -> ClientConfig -- | assign a local address, or let OS pick one [clientLocalAddr] :: ClientConfig -> Maybe SockAddr -- | target address [clientTargetAddr] :: ClientConfig -> SockAddr -- | if we want to use TCP_NODELAY [clientNoDelay] :: ClientConfig -> Bool defaultClientConfig :: ClientConfig initClient :: HasCallStack => ClientConfig -> Resource TCP -- | A TCP server configuration data ServerConfig ServerConfig :: SockAddr -> Int -> (TCP -> IO ()) -> Bool -> ServerConfig -- | listening address [serverAddr] :: ServerConfig -> SockAddr -- | listening socket's backlog size [serverBackLog] :: ServerConfig -> Int -- | worker which get an accepted TCP stream, the socket will be closed -- upon exception or worker finishes. [serverWorker] :: ServerConfig -> TCP -> IO () -- | if we want to use TCP_NODELAY [serverWorkerNoDelay] :: ServerConfig -> Bool -- | A default hello world server on localhost:8888 -- -- Test it with main = startServer defaultServerConfig, now try -- nc -v 127.0.0.1 8888 defaultServerConfig :: ServerConfig -- | Start a server -- -- Fork new worker thread upon a new connection. startServer :: HasCallStack => ServerConfig -> IO () instance Std.IO.Buffered.Output Std.IO.TCP.TCP instance Std.IO.Buffered.Input Std.IO.TCP.TCP instance GHC.Show.Show Std.IO.TCP.TCP -- | This module provides stdin/stderr/stdout reading and writings. Usually -- you don't have to use stderr or stderrBuf directly, -- Logger provides more logging utilities through stderr. -- While stdinBuf and stdoutBuf is useful when you write -- interactive programs, Buffered module provide many reading and -- writing operations. Example: -- --
--   import Std.IO.LowResTimer
--   import Std.IO.Buffered
--   import Std.IO.StdStream
--   
--   main = do
--       -- read by '\n'
--       b1 <- readLineStd
--       -- read whatever user input in 3s, otherwise get Nothing
--       b2 <- timeoutLowRes 30 $ readBuffered stdinBuf
--       ...
--       putStd "hello world!"
--   
module Std.IO.StdStream -- | Standard input and output streams -- -- We support both regular file and TTY based streams, when initialized -- uv_guess_handle is called to decide which type of devices are -- connected to standard streams. -- -- Note StdStream is not thread safe, you shouldn't use them -- without lock. For the same reason you shouldn't use stderr directly, -- use Logger module instead. data StdStream isStdStreamTTY :: StdStream -> Bool -- | Terminal mode. -- -- When in UV_TTY_MODE_RAW mode, input is always available -- character-by-character, not including modifiers. Additionally, all -- special processing of characters by the terminal is disabled, -- including echoing input characters. Note that CTRL+C will no longer -- cause a SIGINT when in this mode. data UVTTYMode pattern UV_TTY_MODE_NORMAL :: UVTTYMode pattern UV_TTY_MODE_RAW :: UVTTYMode -- | Change terminal's mode if stdin is connected to a terminal. setStdinTTYMode :: UVTTYMode -> IO () stdin :: StdStream stdout :: StdStream -- | Don't use stderr directly, use Logger instead. stderr :: StdStream stdinBuf :: BufferedInput StdStream stdoutBuf :: BufferedOutput StdStream stderrBuf :: BufferedOutput StdStream -- | print a ToText to stdout printStd :: ToText a => a -> IO () -- | read a line from stdin readLineStd :: IO Bytes -- | print a Builder and flush to stdout. putStd :: Builder a -> IO () -- | print a Builder and flush to stdout stdout, with a linefeed. putLineStd :: Builder a -> IO () instance Std.IO.Buffered.Input Std.IO.StdStream.StdStream instance Std.IO.Buffered.Output Std.IO.StdStream.StdStream -- | Simple, high performance logger. The design choice of this logger is -- biased towards simplicity instead of generlization: -- -- -- -- Flushing is automatic and throttled for debug, info, -- warn to boost performance, while a fatal log always -- flush logger's buffer, This also lead to a problem that if main thread -- exits too early logs may missed, to add a flushing when program exits, -- use withLogger like: -- --
--   import Std.IO.Logger
--   
--   main :: IO ()
--   main = withStdLogger $ do
--       ....
--   
module Std.IO.Logger data Logger -- | Logger configuration. data LoggerConfig LoggerConfig :: {-# UNPACK #-} !Int -> IO (Builder ()) -> {-# UNPACK #-} !Int -> Bool -> Bool -> LoggerConfig -- | Minimal flush interval, see Notes on debug [loggerMinFlushInterval] :: LoggerConfig -> {-# UNPACK #-} !Int -- | A IO action return a formatted date/time string [loggerTsCache] :: LoggerConfig -> IO (Builder ()) -- | Buffer size to build each log/line [loggerLineBufSize] :: LoggerConfig -> {-# UNPACK #-} !Int -- | Set to False to filter debug logs [loggerShowDebug] :: LoggerConfig -> Bool -- | Set to False to disable auto data/time string prepending [loggerShowTS] :: LoggerConfig -> Bool -- | Make a new logger newLogger :: Output o => LoggerConfig -> BufferedOutput o -> IO Logger -- | flush logger's buffer to output device loggerFlush :: Logger -> IO () -- | Change stderr logger. setStdLogger :: Logger -> IO () getStdLogger :: IO Logger -- | Flush stderr logger when program exits. withStdLogger :: IO () -> IO () debug :: Builder () -> IO () info :: Builder () -> IO () warn :: Builder () -> IO () fatal :: Builder () -> IO () otherLevel :: Builder () -> Bool -> Builder () -> IO () debugWith :: Logger -> Builder () -> IO () infoWith :: Logger -> Builder () -> IO () warnWith :: Logger -> Builder () -> IO () fatalWith :: Logger -> Builder () -> IO () otherLevelWith :: Logger -> Builder () -> Bool -> Builder () -> IO () -- | This module provide IO operations related to filesystem, operations -- are implemented using libuv's threadpool to achieve non-block behavior -- (non-block here meaning won't block other haskell threads), which -- should be prefered when the operations' estimated time is long -- enough(>1ms) or running with a non-threaded haskell runtime, such -- as accessing network filesystem or scan a very large directory. -- Otherwise you may block RTS's capability thus all the other haskell -- threads live on it. -- -- The threadpool version operations have overheads similar to safe FFI, -- but provide same adventages: -- -- module Std.IO.FileSystemT -- | UVFile wrap a uv_file_t and a referencing counter -- -- Note this is a differet data type from Std.IO.FileSystem 's -- one, the Input and Output instance use thread pool -- version functions. -- -- libuv implements read and write method with both implict and explict -- offset capability. (negative offset result in read/write -- system call otherwise pread/pwrite), we provide implict -- offset interface with UVFile, which is NOT thread safe. -- -- An offset bundled UVFileReader, UVFileWriter is also -- provided, which can be used concurrently. The offset is protected with -- MVar and increasing automatically. data UVFile data UVFileReader -- | Create a reader from an UVFile. -- -- Note this will not increase UVFile's referencing counter. newUVFileReader :: UVFile -> Int64 -> IO UVFileReader -- | Change reader's offset. peekUVFileReader :: UVFileReader -> Int64 -> IO Int64 data UVFileWriter -- | Create a writer from an UVFile. -- -- Note this will not increase UVFile's referencing counter. newUVFileWriter :: UVFile -> Int64 -> IO UVFileWriter -- | Change writer's offset. peekUVFileWriter :: UVFileWriter -> Int64 -> IO Int64 -- | init a file Resource, which open a file when used. -- -- Resource closing will wait for the referencing counter goes down to -- zero (no reading or writing is in process), which can be a problem if -- you are using multiple readers or writers in multiple threads. In that -- case you have to stop all reading or writing thread if you don't want -- to block the resource thread. initUVFile :: HasCallStack => CBytes -> UVFileFlag -> UVFileMode -> Resource UVFile data UVFileMode -- | Default mode for open, 0o666(readable and writable). pattern DEFAULT_MODE :: UVFileMode -- | 00700 user (file owner) has read, write and execute permission pattern S_IRWXU :: UVFileMode -- | 00400 user has read permission pattern S_IRUSR :: UVFileMode -- | 00200 user has write permission pattern S_IWUSR :: UVFileMode -- | 00100 user has execute permission pattern S_IXUSR :: UVFileMode -- | 00070 group has read, write and execute permission pattern S_IRWXG :: UVFileMode -- | 00040 group has read permission pattern S_IRGRP :: UVFileMode -- | 00020 group has write permission pattern S_IWGRP :: UVFileMode -- | 00010 group has execute permission pattern S_IXGRP :: UVFileMode -- | 00007 others have read, write and execute permission pattern S_IRWXO :: UVFileMode -- | 00004 others have read permission pattern S_IROTH :: UVFileMode data UVFileFlag -- | The file is opened in append mode. Before each write, the file offset -- is positioned at the end of the file. pattern O_APPEND :: UVFileFlag -- | The file is created if it does not already exist. pattern O_CREAT :: UVFileFlag -- | File IO is done directly to and from user-space buffers, which must be -- aligned. Buffer size and address should be a multiple of the physical -- sector size of the block device, (DO NOT USE WITH stdio's -- BufferedIO) pattern O_DIRECT :: UVFileFlag -- | The file is opened for synchronous IO. Write operations will complete -- once all data and a minimum of metadata are flushed to disk. -- -- Note o_DSYNC is supported on Windows via -- FILE_FLAG_WRITE_THROUGH. pattern O_DSYNC :: UVFileFlag -- | If the o_CREAT flag is set and the file already exists, fail -- the open. -- -- Note In general, the behavior of o_EXCL is undefined if it is -- used without o_CREAT. There is one exception: on Linux 2.6 -- and later, o_EXCL can be used without o_CREAT if -- pathname refers to a block device. If the block device is in use by -- the system (e.g., mounted), the open will fail with the error -- EBUSY. pattern O_EXCL :: UVFileFlag -- | Atomically obtain an exclusive lock. -- -- Note UV_FS_O_EXLOCK is only supported on macOS and Windows. (libuv: -- Changed in version 1.17.0: support is added for Windows.) pattern O_EXLOCK :: UVFileFlag -- | Do not update the file access time when the file is read. -- -- Note o_NOATIME is not supported on Windows. pattern O_NOATIME :: UVFileFlag -- | If the path is a symbolic link, fail the open. -- -- Note o_NOFOLLOW is not supported on Windows. pattern O_NOFOLLOW :: UVFileFlag -- | Open the file for read-only access. pattern O_RDONLY :: UVFileFlag -- | Open the file for read-write access. pattern O_RDWR :: UVFileFlag -- | Open the symbolic link itself rather than the resource it points to. pattern O_SYMLINK :: UVFileFlag -- | The file is opened for synchronous IO. Write operations will complete -- once all data and all metadata are flushed to disk. -- -- Note o_SYNC is supported on Windows via -- FILE_FLAG_WRITE_THROUGH. pattern O_SYNC :: UVFileFlag -- | If the file exists and is a regular file, and the file is opened -- successfully for write access, its length shall be truncated to zero. pattern O_TRUNC :: UVFileFlag -- | Open the file for write-only access. pattern O_WRONLY :: UVFileFlag -- | Access is intended to be random. The system can use this as a hint to -- optimize file caching. -- -- Note o_RANDOM is only supported on Windows via -- FILE_FLAG_RANDOM_ACCESS. pattern O_RANDOM :: UVFileFlag -- | The file is temporary and should not be flushed to disk if possible. -- -- Note o_SHORT_LIVED is only supported on Windows via -- FILE_ATTRIBUTE_TEMPORARY. pattern O_SHORT_LIVED :: UVFileFlag -- | Access is intended to be sequential from beginning to end. The system -- can use this as a hint to optimize file caching. -- -- Note o_SEQUENTIAL is only supported on Windows via -- FILE_FLAG_SEQUENTIAL_SCAN. pattern O_SEQUENTIAL :: UVFileFlag -- | The file is temporary and should not be flushed to disk if possible. -- -- Note o_TEMPORARY is only supported on Windows via -- FILE_ATTRIBUTE_TEMPORARY. pattern O_TEMPORARY :: UVFileFlag -- | Equivalent to mkdir(2). -- -- Note mode is currently not implemented on Windows. mkdir :: HasCallStack => CBytes -> UVFileMode -> IO () -- | Equivalent to unlink(2). unlink :: HasCallStack => CBytes -> IO () -- | Equivalent to http://linux.die.net/man/3/mkdtemp -- -- Creates a temporary directory in the most secure manner possible. -- There are no race conditions in the directory’s creation. The -- directory is readable, writable, and searchable only by the creating -- user ID. The user of mkdtemp() is responsible for deleting the -- temporary directory and its contents when done with it. -- -- Note: the argument is the prefix of the temporary directory, so no -- need to add XXXXXX ending. mkdtemp :: HasCallStack => CBytes -> IO CBytes -- | Equivalent to rmdir(2). rmdir :: HasCallStack => CBytes -> IO () data DirEntType DirEntUnknown :: DirEntType DirEntFile :: DirEntType DirEntDir :: DirEntType DirEntLink :: DirEntType DirEntFIFO :: DirEntType DirEntSocket :: DirEntType DirEntChar :: DirEntType DirEntBlock :: DirEntType -- | Equivalent to scandir(3). -- -- Note Unlike scandir(3), this function does not return the “.” and “..” -- entries. -- -- Note On Linux, getting the type of an entry is only supported by some -- file systems (btrfs, ext2, ext3 and ext4 at the time of this writing), -- check the getdents(2) man page. scandir :: HasCallStack => CBytes -> IO [(CBytes, DirEntType)] data UVStat UVStat :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> UVStat [stDev] :: UVStat -> {-# UNPACK #-} !Word64 [stMode] :: UVStat -> {-# UNPACK #-} !Word64 [stNlink] :: UVStat -> {-# UNPACK #-} !Word64 [stUid] :: UVStat -> {-# UNPACK #-} !Word64 [stGid] :: UVStat -> {-# UNPACK #-} !Word64 [stRdev] :: UVStat -> {-# UNPACK #-} !Word64 [stIno] :: UVStat -> {-# UNPACK #-} !Word64 [stSize] :: UVStat -> {-# UNPACK #-} !Word64 [stBlksize] :: UVStat -> {-# UNPACK #-} !Word64 [stBlocks] :: UVStat -> {-# UNPACK #-} !Word64 [stFlags] :: UVStat -> {-# UNPACK #-} !Word64 [stGen] :: UVStat -> {-# UNPACK #-} !Word64 [stAtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stMtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stCtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stBirthtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec data UVTimeSpec UVTimeSpec :: {-# UNPACK #-} !CLong -> {-# UNPACK #-} !CLong -> UVTimeSpec [uvtSecond] :: UVTimeSpec -> {-# UNPACK #-} !CLong [uvtNanoSecond] :: UVTimeSpec -> {-# UNPACK #-} !CLong -- | Equivalent to stat(2) stat :: HasCallStack => CBytes -> IO UVStat -- | Equivalent to lstat(2) lstat :: HasCallStack => CBytes -> IO UVStat -- | Equivalent to fstat(2) fstat :: HasCallStack => UVFile -> IO UVStat -- | Equivalent to rename(2). -- -- Note On Windows if this function fails with UV_EBUSY, UV_EPERM or -- UV_EACCES, it will retry to rename the file up to four times with -- 250ms wait between attempts before giving up. If both path and -- new_path are existing directories this function will work only if -- target directory is empty. rename :: HasCallStack => CBytes -> CBytes -> IO () -- | Equivalent to fsync(2). fsync :: HasCallStack => UVFile -> IO () -- | Equivalent to fdatasync(2). fdatasync :: HasCallStack => UVFile -> IO () -- | Equivalent to ftruncate(2). ftruncate :: HasCallStack => UVFile -> Int64 -> IO () -- | Flags control copying. -- -- data UVCopyFileFlag pattern COPYFILE_DEFAULT :: UVCopyFileFlag pattern COPYFILE_EXCL :: UVCopyFileFlag pattern COPYFILE_FICLONE :: UVCopyFileFlag -- | Copies a file from path to new_path. -- -- Warning: If the destination path is created, but an error occurs while -- copying the data, then the destination path is removed. There is a -- brief window of time between closing and removing the file where -- another process could access the file. copyfile :: HasCallStack => CBytes -> CBytes -> UVCopyFileFlag -> IO () data UVAccessMode pattern F_OK :: UVAccessMode pattern R_OK :: UVAccessMode pattern W_OK :: UVAccessMode pattern X_OK :: UVAccessMode data AccessResult NoExistence :: AccessResult NoPermission :: AccessResult AccessOK :: AccessResult -- | Equivalent to access(2) on Unix. Windows uses -- GetFileAttributesW(). access :: HasCallStack => CBytes -> UVAccessMode -> IO AccessResult -- | Equivalent to chmod(2). chmod :: HasCallStack => CBytes -> UVFileMode -> IO () -- | Equivalent to fchmod(2). fchmod :: HasCallStack => UVFile -> UVFileMode -> IO () -- | Equivalent to utime(2). -- -- libuv choose Double type due to cross platform concerns, we -- only provide micro-second precision: -- -- -- -- second and nanosecond are fields in UVTimeSpec respectively. -- -- Note libuv prior to v1.23.1 have issues which may result in nanosecond -- not set, futime doesn't have utime :: HasCallStack => CBytes -> Double -> Double -> IO () -- | Equivalent to futime(2). -- -- Same precision notes with utime. futime :: HasCallStack => UVFile -> Double -> Double -> IO () data UVSymlinkFlag pattern SYMLINK_DEFAULT :: UVSymlinkFlag pattern SYMLINK_DIR :: UVSymlinkFlag pattern SYMLINK_JUNCTION :: UVSymlinkFlag -- | Equivalent to link(2). link :: HasCallStack => CBytes -> CBytes -> IO () -- | Equivalent to symlink(2). -- -- | Note On Windows the flags parameter can be specified to control how -- the symlink will be created. -- -- -- -- On other platforms these flags are ignored. symlink :: HasCallStack => CBytes -> CBytes -> UVSymlinkFlag -> IO () -- | Equivalent to readlink(2). readlink :: HasCallStack => CBytes -> IO CBytes -- | Equivalent to realpath(3) on Unix. Windows uses -- GetFinalPathNameByHandle. -- -- Warning This function has certain platform-specific caveats that were -- discovered when used in Node. -- -- -- -- While this function can still be used, it’s not recommended if -- scenarios such as the above need to be supported. The background story -- and some more details on these issues can be checked here. -- -- Note This function is not implemented on Windows XP and Windows Server -- 2003. On these systems, UV_ENOSYS is returned. realpath :: HasCallStack => CBytes -> IO CBytes instance Std.IO.Buffered.Output Std.IO.FileSystemT.UVFileWriter instance Std.IO.Buffered.Input Std.IO.FileSystemT.UVFileReader instance GHC.Show.Show Std.IO.FileSystemT.UVFile instance Std.IO.Buffered.Input Std.IO.FileSystemT.UVFile instance Std.IO.Buffered.Output Std.IO.FileSystemT.UVFile -- | This module provide IO operations related to filesystem, operations -- are implemented using unsafe FFIs, which should be prefered when the -- operations' estimated time is short(<1ms), which is much common on -- modern SSDs. module Std.IO.FileSystem -- | UVFile wrap a uv_file_t and a referencing counter. -- -- libuv implements read and write method with both implict and explict -- offset capable. (negative offset result in read/write system -- call otherwise pread/pwrite), we provide implict offset -- interface with UVFile, which is NOT thread safe. -- -- An offset bundled UVFileReader, UVFileWriter is also -- provided, which can be used concurrently. The offset is protected with -- MVar and increasing automatically. data UVFile -- | An UVFile bundled with a MVar protected reading offset. data UVFileReader -- | Create a reader from an UVFile. -- -- Note this will not increase UVFile's referencing counter. newUVFileReader :: UVFile -> Int64 -> IO UVFileReader -- | Change reader's offset. peekUVFileReader :: UVFileReader -> Int64 -> IO Int64 -- | An UVFile bundled with a MVar protected writing offset. data UVFileWriter -- | Create a writer from an UVFile. -- -- Note this will not increase UVFile's referencing counter. newUVFileWriter :: UVFile -> Int64 -> IO UVFileWriter -- | Change writer's offset. peekUVFileWriter :: UVFileWriter -> Int64 -> IO Int64 -- | init a file Resource, which open a file when used. -- -- Resource closing will wait for the referencing counter goes down to -- zero (no reading or writing is in process), which can be a problem if -- you are using multiple readers or writers in multiple threads. In that -- case you have to stop all reading or writing thread if you don't want -- to block the resource thread. -- -- Note, on some versions of OSX, repeatly open and close same file -- Resource may result in shared memory object error, use -- O_CREAT to avoid that. initUVFile :: HasCallStack => CBytes -> UVFileFlag -> UVFileMode -> Resource UVFile data UVFileMode -- | Default mode for open, 0o666(readable and writable). pattern DEFAULT_MODE :: UVFileMode -- | 00700 user (file owner) has read, write and execute permission pattern S_IRWXU :: UVFileMode -- | 00400 user has read permission pattern S_IRUSR :: UVFileMode -- | 00200 user has write permission pattern S_IWUSR :: UVFileMode -- | 00100 user has execute permission pattern S_IXUSR :: UVFileMode -- | 00070 group has read, write and execute permission pattern S_IRWXG :: UVFileMode -- | 00040 group has read permission pattern S_IRGRP :: UVFileMode -- | 00020 group has write permission pattern S_IWGRP :: UVFileMode -- | 00010 group has execute permission pattern S_IXGRP :: UVFileMode -- | 00007 others have read, write and execute permission pattern S_IRWXO :: UVFileMode -- | 00004 others have read permission pattern S_IROTH :: UVFileMode data UVFileFlag -- | The file is opened in append mode. Before each write, the file offset -- is positioned at the end of the file. pattern O_APPEND :: UVFileFlag -- | The file is created if it does not already exist. pattern O_CREAT :: UVFileFlag -- | File IO is done directly to and from user-space buffers, which must be -- aligned. Buffer size and address should be a multiple of the physical -- sector size of the block device, (DO NOT USE WITH stdio's -- BufferedIO) pattern O_DIRECT :: UVFileFlag -- | The file is opened for synchronous IO. Write operations will complete -- once all data and a minimum of metadata are flushed to disk. -- -- Note o_DSYNC is supported on Windows via -- FILE_FLAG_WRITE_THROUGH. pattern O_DSYNC :: UVFileFlag -- | If the o_CREAT flag is set and the file already exists, fail -- the open. -- -- Note In general, the behavior of o_EXCL is undefined if it is -- used without o_CREAT. There is one exception: on Linux 2.6 -- and later, o_EXCL can be used without o_CREAT if -- pathname refers to a block device. If the block device is in use by -- the system (e.g., mounted), the open will fail with the error -- EBUSY. pattern O_EXCL :: UVFileFlag -- | Atomically obtain an exclusive lock. -- -- Note UV_FS_O_EXLOCK is only supported on macOS and Windows. (libuv: -- Changed in version 1.17.0: support is added for Windows.) pattern O_EXLOCK :: UVFileFlag -- | Do not update the file access time when the file is read. -- -- Note o_NOATIME is not supported on Windows. pattern O_NOATIME :: UVFileFlag -- | If the path is a symbolic link, fail the open. -- -- Note o_NOFOLLOW is not supported on Windows. pattern O_NOFOLLOW :: UVFileFlag -- | Open the file for read-only access. pattern O_RDONLY :: UVFileFlag -- | Open the file for read-write access. pattern O_RDWR :: UVFileFlag -- | Open the symbolic link itself rather than the resource it points to. pattern O_SYMLINK :: UVFileFlag -- | The file is opened for synchronous IO. Write operations will complete -- once all data and all metadata are flushed to disk. -- -- Note o_SYNC is supported on Windows via -- FILE_FLAG_WRITE_THROUGH. pattern O_SYNC :: UVFileFlag -- | If the file exists and is a regular file, and the file is opened -- successfully for write access, its length shall be truncated to zero. pattern O_TRUNC :: UVFileFlag -- | Open the file for write-only access. pattern O_WRONLY :: UVFileFlag -- | Access is intended to be random. The system can use this as a hint to -- optimize file caching. -- -- Note o_RANDOM is only supported on Windows via -- FILE_FLAG_RANDOM_ACCESS. pattern O_RANDOM :: UVFileFlag -- | The file is temporary and should not be flushed to disk if possible. -- -- Note o_SHORT_LIVED is only supported on Windows via -- FILE_ATTRIBUTE_TEMPORARY. pattern O_SHORT_LIVED :: UVFileFlag -- | Access is intended to be sequential from beginning to end. The system -- can use this as a hint to optimize file caching. -- -- Note o_SEQUENTIAL is only supported on Windows via -- FILE_FLAG_SEQUENTIAL_SCAN. pattern O_SEQUENTIAL :: UVFileFlag -- | The file is temporary and should not be flushed to disk if possible. -- -- Note o_TEMPORARY is only supported on Windows via -- FILE_ATTRIBUTE_TEMPORARY. pattern O_TEMPORARY :: UVFileFlag -- | Equivalent to mkdir(2). -- -- Note mode is currently not implemented on Windows. mkdir :: HasCallStack => CBytes -> UVFileMode -> IO () -- | Equivalent to unlink(2). unlink :: HasCallStack => CBytes -> IO () -- | Equivalent to http://linux.die.net/man/3/mkdtemp -- -- Creates a temporary directory in the most secure manner possible. -- There are no race conditions in the directory’s creation. The -- directory is readable, writable, and searchable only by the creating -- user ID. The user of mkdtemp() is responsible for deleting the -- temporary directory and its contents when done with it. -- -- Note: the argument is the prefix of the temporary directory, so no -- need to add XXXXXX ending. mkdtemp :: HasCallStack => CBytes -> IO CBytes -- | Equivalent to rmdir(2). rmdir :: HasCallStack => CBytes -> IO () data DirEntType DirEntUnknown :: DirEntType DirEntFile :: DirEntType DirEntDir :: DirEntType DirEntLink :: DirEntType DirEntFIFO :: DirEntType DirEntSocket :: DirEntType DirEntChar :: DirEntType DirEntBlock :: DirEntType -- | Equivalent to scandir(3). -- -- Note Unlike scandir(3), this function does not return the “.” and “..” -- entries. -- -- Note On Linux, getting the type of an entry is only supported by some -- file systems (btrfs, ext2, ext3 and ext4 at the time of this writing), -- check the getdents(2) man page. scandir :: HasCallStack => CBytes -> IO [(CBytes, DirEntType)] data UVStat UVStat :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> {-# UNPACK #-} !UVTimeSpec -> UVStat [stDev] :: UVStat -> {-# UNPACK #-} !Word64 [stMode] :: UVStat -> {-# UNPACK #-} !Word64 [stNlink] :: UVStat -> {-# UNPACK #-} !Word64 [stUid] :: UVStat -> {-# UNPACK #-} !Word64 [stGid] :: UVStat -> {-# UNPACK #-} !Word64 [stRdev] :: UVStat -> {-# UNPACK #-} !Word64 [stIno] :: UVStat -> {-# UNPACK #-} !Word64 [stSize] :: UVStat -> {-# UNPACK #-} !Word64 [stBlksize] :: UVStat -> {-# UNPACK #-} !Word64 [stBlocks] :: UVStat -> {-# UNPACK #-} !Word64 [stFlags] :: UVStat -> {-# UNPACK #-} !Word64 [stGen] :: UVStat -> {-# UNPACK #-} !Word64 [stAtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stMtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stCtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec [stBirthtim] :: UVStat -> {-# UNPACK #-} !UVTimeSpec data UVTimeSpec UVTimeSpec :: {-# UNPACK #-} !CLong -> {-# UNPACK #-} !CLong -> UVTimeSpec [uvtSecond] :: UVTimeSpec -> {-# UNPACK #-} !CLong [uvtNanoSecond] :: UVTimeSpec -> {-# UNPACK #-} !CLong -- | Equivalent to stat(2) stat :: HasCallStack => CBytes -> IO UVStat -- | Equivalent to lstat(2) lstat :: HasCallStack => CBytes -> IO UVStat -- | Equivalent to fstat(2) fstat :: HasCallStack => UVFile -> IO UVStat -- | Equivalent to rename(2). -- -- Note On Windows if this function fails with UV_EBUSY, UV_EPERM or -- UV_EACCES, it will retry to rename the file up to four times with -- 250ms wait between attempts before giving up. If both path and -- new_path are existing directories this function will work only if -- target directory is empty. rename :: HasCallStack => CBytes -> CBytes -> IO () -- | Equivalent to fsync(2). fsync :: HasCallStack => UVFile -> IO () -- | Equivalent to fdatasync(2). fdatasync :: HasCallStack => UVFile -> IO () -- | Equivalent to ftruncate(2). ftruncate :: HasCallStack => UVFile -> Int64 -> IO () -- | Flags control copying. -- -- data UVCopyFileFlag pattern COPYFILE_DEFAULT :: UVCopyFileFlag pattern COPYFILE_EXCL :: UVCopyFileFlag pattern COPYFILE_FICLONE :: UVCopyFileFlag -- | Copies a file from path to new_path. -- -- Warning: If the destination path is created, but an error occurs while -- copying the data, then the destination path is removed. There is a -- brief window of time between closing and removing the file where -- another process could access the file. copyfile :: HasCallStack => CBytes -> CBytes -> UVCopyFileFlag -> IO () data UVAccessMode pattern F_OK :: UVAccessMode pattern R_OK :: UVAccessMode pattern W_OK :: UVAccessMode pattern X_OK :: UVAccessMode data AccessResult NoExistence :: AccessResult NoPermission :: AccessResult AccessOK :: AccessResult -- | Equivalent to access(2) on Unix. Windows uses -- GetFileAttributesW(). access :: HasCallStack => CBytes -> UVAccessMode -> IO AccessResult -- | Equivalent to chmod(2). chmod :: HasCallStack => CBytes -> UVFileMode -> IO () -- | Equivalent to fchmod(2). fchmod :: HasCallStack => UVFile -> UVFileMode -> IO () -- | Equivalent to utime(2). -- -- libuv choose Double type due to cross platform concerns, we -- only provide micro-second precision: -- -- -- -- second and nanosecond are fields in UVTimeSpec respectively. -- -- Note libuv prior to v1.23.1 have issues which may result in nanosecond -- not set, futime doesn't have that issue. utime :: HasCallStack => CBytes -> Double -> Double -> IO () -- | Equivalent to futime(2). -- -- Same precision notes with utime. futime :: HasCallStack => UVFile -> Double -> Double -> IO () data UVSymlinkFlag pattern SYMLINK_DEFAULT :: UVSymlinkFlag pattern SYMLINK_DIR :: UVSymlinkFlag pattern SYMLINK_JUNCTION :: UVSymlinkFlag -- | Equivalent to link(2). link :: HasCallStack => CBytes -> CBytes -> IO () -- | Equivalent to symlink(2). -- -- | Note On Windows the flags parameter can be specified to control how -- the symlink will be created. -- -- -- -- On other platforms these flags are ignored. symlink :: HasCallStack => CBytes -> CBytes -> UVSymlinkFlag -> IO () -- | Equivalent to readlink(2). readlink :: HasCallStack => CBytes -> IO CBytes -- | Equivalent to realpath(3) on Unix. Windows uses -- GetFinalPathNameByHandle. -- -- Warning This function has certain platform-specific caveats that were -- discovered when used in Node. -- -- -- -- While this function can still be used, it’s not recommended if -- scenarios such as the above need to be supported. The background story -- and some more details on these issues can be checked here. -- -- Note This function is not implemented on Windows XP and Windows Server -- 2003. On these systems, UV_ENOSYS is returned. realpath :: HasCallStack => CBytes -> IO CBytes instance Std.IO.Buffered.Output Std.IO.FileSystem.UVFileWriter instance Std.IO.Buffered.Input Std.IO.FileSystem.UVFileReader instance GHC.Show.Show Std.IO.FileSystem.UVFile instance Std.IO.Buffered.Input Std.IO.FileSystem.UVFile instance Std.IO.Buffered.Output Std.IO.FileSystem.UVFile