Portability | untested |
---|---|
Stability | experimental |
Maintainer | twanvl@gmail.com |
Internal functions for the CompactString type.
- newtype CompactString a = CS {
- unCS :: ByteString
- data Proxy a
- encoding :: CompactString a -> Proxy a
- class Encoding a where
- pokeCharFun :: Proxy a -> Char -> (Int, Ptr Word8 -> IO ())
- pokeCharLen :: Proxy a -> Char -> Int
- pokeChar :: Proxy a -> Ptr Word8 -> Char -> IO Int
- pokeCharRev :: Proxy a -> Ptr Word8 -> Char -> IO Int
- peekChar :: Proxy a -> Ptr Word8 -> IO (Int, Char)
- peekCharLen :: Proxy a -> Ptr Word8 -> IO Int
- peekCharRev :: Proxy a -> Ptr Word8 -> IO (Int, Char)
- peekCharLenRev :: Proxy a -> Ptr Word8 -> IO Int
- peekCharSafe :: Proxy a -> Int -> Ptr Word8 -> IO (Int, Char)
- validateLength :: Proxy a -> Int -> IO ()
- copyChar :: Proxy a -> Ptr Word8 -> Ptr Word8 -> IO Int
- copyCharRev :: Proxy a -> Ptr Word8 -> Ptr Word8 -> IO Int
- containsASCII :: Proxy a -> Bool
- validEquality :: Proxy a -> Bool
- validOrdering :: Proxy a -> Bool
- validSubstring :: Proxy a -> Bool
- charCount :: Proxy a -> Int -> Int
- byteCount :: Proxy a -> Int -> Int
- newSize :: Proxy a -> Int -> Int
- doUpLoop :: Proxy a -> AccEFL acc -> acc -> ImperativeLoop acc
- doDownLoop :: Proxy a -> AccEFL acc -> acc -> ImperativeLoop acc
- doUpLoopFold :: Proxy a -> FoldEFL acc -> acc -> ImperativeLoop_ acc
- doDownLoopFold :: Proxy a -> FoldEFL acc -> acc -> ImperativeLoop_ acc
- data PairS a b = !a :*: !b
- data MaybeS a
- unSP :: PairS a b -> (a, b)
- type AccEFL acc = acc -> Char -> PairS acc (MaybeS Char)
- type FoldEFL acc = acc -> Char -> acc
- type ImperativeLoop acc = Ptr Word8 -> Ptr Word8 -> Int -> IO (PairS (PairS acc Int) Int)
- type ImperativeLoop_ acc = Ptr Word8 -> Int -> IO acc
- data ByteString = PS !(ForeignPtr Word8) !Int !Int
- memcpy :: Ptr Word8 -> Ptr Word8 -> CSize -> IO ()
- inlinePerformIO :: IO a -> a
- withBuffer :: CompactString a -> (Ptr Word8 -> IO b) -> IO b
- withBufferEnd :: CompactString a -> (Ptr Word8 -> IO b) -> IO b
- unsafeWithBuffer :: CompactString a -> (Ptr Word8 -> IO b) -> b
- unsafeWithBufferEnd :: CompactString a -> (Ptr Word8 -> IO b) -> b
- create :: Int -> (Ptr Word8 -> IO ()) -> IO (CompactString a)
- ord :: Char -> Int
- unsafeChr :: Int -> Char
- returnChr :: Int -> Word32 -> IO (Int, Char)
- plusPtr :: Ptr a -> Int -> Ptr a
- peekByteOff :: Storable a => Ptr a -> Int -> IO a
- pokeByteOff :: Storable a => Ptr a -> Int -> a -> IO ()
- peek :: Storable a => Ptr a -> IO a
- poke :: Storable a => Ptr a -> a -> IO ()
- failMessage :: String -> String -> IO a
- moduleError :: String -> String -> a
- errorEmptyList :: String -> a
- unsafeTry :: MonadPlus m => IO a -> m a
- unsafeTryIO :: MonadPlus m => IO a -> IO (m a)
Documentation
newtype CompactString a Source
A String using a compact, strict representation.
A CompactString a
is encoded using encoding a
, for example CompactString
.
UTF8
CS | |
|
Encoding a => Eq (CompactString a) | |
Encoding a => Ord (CompactString a) | |
Encoding a => Show (CompactString a) | |
Encoding a => IsString (CompactString a) | |
Encoding a => Monoid (CompactString a) |
encoding :: CompactString a -> Proxy aSource
A way to encode characters into bytes
pokeCharFun :: Proxy a -> Char -> (Int, Ptr Word8 -> IO ())Source
Given a character returns the length of that character,
and a function to write it to a memory buffer.
if the encoding can not represent the character, the io function should fail
.
pokeCharLen :: Proxy a -> Char -> IntSource
The size needed to store a character
pokeChar :: Proxy a -> Ptr Word8 -> Char -> IO IntSource
Write a character and return the size used
pokeCharRev :: Proxy a -> Ptr Word8 -> Char -> IO IntSource
Write a character given a pointer to its last byte, and return the size used
peekChar :: Proxy a -> Ptr Word8 -> IO (Int, Char)Source
Read a character from a memory buffer, return it and its length. The buffer is guaranteed to contain a valid character.
peekCharLen :: Proxy a -> Ptr Word8 -> IO IntSource
Return the length of the character in a memory buffer
peekCharRev :: Proxy a -> Ptr Word8 -> IO (Int, Char)Source
Read a character from a memory buffer, return it and its length, given a pointer to the last byte. The buffer is guaranteed to contain a valid character.
peekCharLenRev :: Proxy a -> Ptr Word8 -> IO IntSource
Return the length of the character in a memory buffer, given a pointer to the last byte.
peekCharSafe :: Proxy a -> Int -> Ptr Word8 -> IO (Int, Char)Source
Read a character from a memory buffer, return it and its length. The buffer is not guaranteed to contain a valid character, so that should be verified. There is also no guarantee that the length of the buffer (also given) is sufficient to contain a whole character.
validateLength :: Proxy a -> Int -> IO ()Source
Validate the length, should be used before peekCharSafe is called. Can be used to remove the number of checks used by peekCharSafe.
copyChar :: Proxy a -> Ptr Word8 -> Ptr Word8 -> IO IntSource
Copy a character from one buffer to another, return the length of the character
copyCharRev :: Proxy a -> Ptr Word8 -> Ptr Word8 -> IO IntSource
Copy a character from one buffer to another, where the source pointer points to the last byte of the character. return the length of the character.
containsASCII :: Proxy a -> BoolSource
Is ASCII a valid subset of the encoding?
validEquality :: Proxy a -> BoolSource
Is (a == b) == (toBS a == toBS b)
?
validOrdering :: Proxy a -> BoolSource
validSubstring :: Proxy a -> BoolSource
Is (a
?
isSubstringOf
b) == (toBS a isSubstringOf
toBS b)
charCount :: Proxy a -> Int -> IntSource
What is the maximum number of character a string with the given number of bytes contains?
byteCount :: Proxy a -> Int -> IntSource
What is the maximum number of bytes a string with the given number of characters contains?
newSize :: Proxy a -> Int -> IntSource
What is the maximum size in bytes after transforming (using map) a string?
doUpLoop :: Proxy a -> AccEFL acc -> acc -> ImperativeLoop accSource
doDownLoop :: Proxy a -> AccEFL acc -> acc -> ImperativeLoop accSource
doUpLoopFold :: Proxy a -> FoldEFL acc -> acc -> ImperativeLoop_ accSource
doDownLoopFold :: Proxy a -> FoldEFL acc -> acc -> ImperativeLoop_ accSource
type ImperativeLoop acc = Ptr Word8 -> Ptr Word8 -> Int -> IO (PairS (PairS acc Int) Int)Source
An imperative loop transforming a string, using an accumulating parameter. See Data.ByteString.Fusion
data ByteString
A space-efficient representation of a Word8 vector, supporting many
efficient operations. A ByteString
contains 8-bit characters only.
Instances of Eq, Ord, Read, Show, Data, Typeable
PS !(ForeignPtr Word8) !Int !Int |
inlinePerformIO :: IO a -> a
Just like unsafePerformIO, but we inline it. Big performance gains as
it exposes lots of things to further inlining. Very unsafe. In
particular, you should do no memory allocation inside an
inlinePerformIO
block. On Hugs this is just unsafePerformIO
.
withBuffer :: CompactString a -> (Ptr Word8 -> IO b) -> IO bSource
Perform a function given a pointer to the buffer of a CompactString
withBufferEnd :: CompactString a -> (Ptr Word8 -> IO b) -> IO bSource
Perform a function given a pointer to the last byte in the buffer of a CompactString
unsafeWithBuffer :: CompactString a -> (Ptr Word8 -> IO b) -> bSource
Perform a function given a pointer to the buffer of a CompactString
unsafeWithBufferEnd :: CompactString a -> (Ptr Word8 -> IO b) -> bSource
Perform a function given a pointer to the last byte in the buffer of a CompactString
returnChr :: Int -> Word32 -> IO (Int, Char)Source
Safe variant of chr, combined with return; does more checks. At least GHC does not check for surrogate pairs
peek :: Storable a => Ptr a -> IO a
Read a value from the given memory location.
Note that the peek and poke functions might require properly
aligned addresses to function correctly. This is architecture
dependent; thus, portable code should ensure that when peeking or
poking values of some type a
, the alignment
constraint for a
, as given by the function
alignment
is fulfilled.
poke :: Storable a => Ptr a -> a -> IO ()
Write the given value to the given memory location. Alignment
restrictions might apply; see peek
.
failMessage :: String -> String -> IO aSource
Fail with an error message including the module name and function
moduleError :: String -> String -> aSource
Raise an errorr, with the message including the module name and function
errorEmptyList :: String -> aSource
unsafeTry :: MonadPlus m => IO a -> m aSource
Catch exceptions from fail in the IO monad, and wrap them in another monad
unsafeTryIO :: MonadPlus m => IO a -> IO (m a)Source
Catch exceptions from fail in the IO monad, and wrap them in another monad