{-# LANGUAGE MagicHash #-}
module Basement.UTF8.Table
( isContinuation
, isContinuation2
, isContinuation3
, getNbBytes
, isContinuation#
, getNbBytes#
) where
import GHC.Prim
import GHC.Types
import GHC.Word
import Basement.Compat.Base
import Basement.Compat.Primitive
import Basement.UTF8.Types (StepASCII(..))
isContinuation :: Word8 -> Bool
isContinuation :: Word8 -> Bool
isContinuation (W8# Word#
w) = Word# -> Bool
isContinuation# Word#
w
{-# INLINE isContinuation #-}
isContinuation2 :: Word8 -> Word8 -> Bool
isContinuation2 :: Word8 -> Word8 -> Bool
isContinuation2 (W8# Word#
w1) (W8# Word#
w2) =
Int# -> Bool
bool# (Word# -> Int#
mask Word#
w1 Int# -> Int# -> Int#
`andI#` Word# -> Int#
mask Word#
w2)
where
mask :: Word# -> Int#
mask Word#
v = (Word# -> Word# -> Word#
and# Word#
0xC0## Word#
v) Word# -> Word# -> Int#
`eqWord#` Word#
0x80##
{-# INLINE isContinuation2 #-}
isContinuation3 :: Word8 -> Word8 -> Word8 -> Bool
isContinuation3 :: Word8 -> Word8 -> Word8 -> Bool
isContinuation3 (W8# Word#
w1) (W8# Word#
w2) (W8# Word#
w3) =
Int# -> Bool
bool# (Word# -> Int#
mask Word#
w1) Bool -> Bool -> Bool
&& Int# -> Bool
bool# (Word# -> Int#
mask Word#
w2) Bool -> Bool -> Bool
&& Int# -> Bool
bool# (Word# -> Int#
mask Word#
w3)
where
mask :: Word# -> Int#
mask Word#
v = (Word# -> Word# -> Word#
and# Word#
0xC0## Word#
v) Word# -> Word# -> Int#
`eqWord#` Word#
0x80##
{-# INLINE isContinuation3 #-}
data NbBytesCont = NbBytesInvalid | NbBytesCont0 | NbBytesCont1 | NbBytesCont2 | NbBytesCont3
data NbBytesCont_ = NbBytesCont0_ | NbBytesCont1_ | NbBytesCont2_ | NbBytesCont3_
getNbBytes :: StepASCII -> Int
getNbBytes :: StepASCII -> Int
getNbBytes (StepASCII (W8# Word#
w)) = Int# -> Int
I# (Word# -> Int#
getNbBytes# Word#
w)
{-# INLINE getNbBytes #-}
isContinuation# :: Word# -> Bool
isContinuation# :: Word# -> Bool
isContinuation# Word#
w = Word# -> Word
W# (Addr# -> Int# -> Word#
indexWord8OffAddr# (Table -> Addr#
unTable Table
contTable) (Word# -> Int#
word2Int# Word#
w)) Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word# -> Word
W# Word#
0##
{-# INLINE isContinuation# #-}
getNbBytes# :: Word# -> Int#
getNbBytes# :: Word# -> Int#
getNbBytes# Word#
w = Word# -> Int#
word2Int# (Addr# -> Int# -> Word#
indexWord8OffAddr# (Table -> Addr#
unTable Table
headTable) (Word# -> Int#
word2Int# Word#
w))
{-# INLINE getNbBytes# #-}
data Table = Table { Table -> Addr#
unTable :: !Addr# }
contTable :: Table
contTable :: Table
contTable = Addr# -> Table
Table
Addr#
"\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01"#
{-# NOINLINE contTable #-}
headTable :: Table
headTable :: Table
headTable = Addr# -> Table
Table
Addr#
"\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\
\\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
\\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
\\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
\\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\xff\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\x01\
\\x02\x02\x02\x02\x02\x02\x02\x02\x02\x02\x02\x02\x02\x02\x02\x02\
\\x03\x03\x03\x03\x03\x03\x03\x03\xff\xff\xff\xff\xff\xff\xff\xff"#
{-# NOINLINE headTable #-}