Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- shortInteger :: Int# -> Integer
- isDigit :: Char -> Bool
- isLatinLetter :: Char -> Bool
- isGreekLetter :: Char -> Bool
- mul10 :: Int# -> Int#
- readInt' :: Int# -> Addr# -> Addr# -> (# Int#, Addr# #)
- readInt :: Addr# -> Addr# -> (# (# #) | (# Int#, Addr# #) #)
- readInteger :: ForeignPtrContents -> Addr# -> Addr# -> (# (# #) | (# Integer, Addr# #) #)
- newtype Pos = Pos Int
- data Span = Span !Pos !Pos
- addrToPos# :: Addr# -> Addr# -> Pos
- posToAddr# :: Addr# -> Pos -> Addr#
- unsafeSlice :: ByteString -> Span -> ByteString
- packUTF8 :: String -> ByteString
- charToBytes :: Char -> [Word]
- strToBytes :: String -> [Word]
- packBytes :: [Word] -> Word
- splitBytes :: [Word] -> ([Word], [Word])
- derefChar8# :: Addr# -> Char#
- data Trie a = Branch !a !(Map Word (Trie a))
- type Rule = Maybe Int
- nilTrie :: Trie Rule
- updRule :: Int -> Maybe Int -> Maybe Int
- insert :: Int -> [Word] -> Trie Rule -> Trie Rule
- listToTrie :: [(Int, String)] -> Trie Rule
- mindepths :: Trie Rule -> Trie (Rule, Int)
- data Trie' a
- pathify :: Trie (Rule, Int) -> Trie' (Rule, Int)
- fallbacks :: Trie' (Rule, Int) -> Trie' (Rule, Int, Int)
- ensureBytes :: Trie' (Rule, Int, Int) -> Trie' (Rule, Int, Maybe Int)
- compileTrie :: [(Int, String)] -> Trie' (Rule, Int, Maybe Int)
Documentation
shortInteger :: Int# -> Integer Source #
isLatinLetter :: Char -> Bool Source #
isLatinLetter c = ('A' <= c && c <= 'Z') || ('a' <= c && c <= 'z')
isGreekLetter :: Char -> Bool Source #
isGreekLetter c = ('Α' <= c && c <= 'Ω') || ('α' <= c && c <= 'ω')
readInteger :: ForeignPtrContents -> Addr# -> Addr# -> (# (# #) | (# Integer, Addr# #) #) Source #
Read an Integer
from the input, as a non-empty digit sequence.
Byte offset counted backwards from the end of the buffer.
A pair of positions.
unsafeSlice :: ByteString -> Span -> ByteString Source #
Slice into a ByteString
using a Span
. The result is invalid if the Span
is not a valid slice of the first argument.
packUTF8 :: String -> ByteString Source #
Convert a String
to an UTF-8-coded ByteString
.
charToBytes :: Char -> [Word] Source #
strToBytes :: String -> [Word] Source #
derefChar8# :: Addr# -> Char# Source #
mindepths :: Trie Rule -> Trie (Rule, Int) Source #
Decorate a trie with the minimum lengths of non-empty paths. This
is used later to place ensureBytes#
.
fallbacks :: Trie' (Rule, Int) -> Trie' (Rule, Int, Int) Source #
Compute where to fall back after we exhausted a branch. If the branch is empty, that means we've succeded at reading and we jump to the rhs rule.