-- |
-- Module      : Basement.UTF8.Table
-- License     : BSD-style
-- Maintainer  : Vincent Hanquez <vincent@snarc.org>
-- Stability   : experimental
-- Portability : portable
--
-- UTF8 lookup tables for fast continuation & nb bytes per header queries
{-# LANGUAGE MagicHash #-}
module Basement.UTF8.Table
    ( isContinuation
    , isContinuation2
    , isContinuation3
    , getNbBytes
    , isContinuation#
    , isContinuationW#
    , getNbBytes#
    ) where

import           GHC.Prim (Word#, Int#, Addr#, indexWord8OffAddr#, word2Int#)
import           GHC.Types
import           GHC.Word
import           Basement.Compat.Base
import           Basement.Compat.Primitive
import           Basement.Bits
import           Basement.UTF8.Types (StepASCII(..))

-- | Check if the byte is a continuation byte
isContinuation :: Word8 -> Bool
isContinuation :: Word8 -> Bool
isContinuation (W8# Word8#
w) = Word8# -> Bool
isContinuation# Word8#
w
{-# INLINE isContinuation #-}

isContinuation2 :: Word8 -> Word8 -> Bool
isContinuation2 :: Word8 -> Word8 -> Bool
isContinuation2 !Word8
w1 !Word8
w2 = Word8 -> Bool
forall {a}. (Eq a, BitOps a, Integral a) => a -> Bool
mask Word8
w1 Bool -> Bool -> Bool
&& Word8 -> Bool
forall {a}. (Eq a, BitOps a, Integral a) => a -> Bool
mask Word8
w2
  where
    mask :: a -> Bool
mask a
v = (a
v a -> a -> a
forall bits. BitOps bits => bits -> bits -> bits
.&. a
0xC0) a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0x80
{-# INLINE isContinuation2 #-}

isContinuation3 :: Word8 -> Word8 -> Word8 -> Bool
isContinuation3 :: Word8 -> Word8 -> Word8 -> Bool
isContinuation3 !Word8
w1 !Word8
w2 !Word8
w3 =
    Word8 -> Bool
forall {a}. (Eq a, BitOps a, Integral a) => a -> Bool
mask Word8
w1 Bool -> Bool -> Bool
&& Word8 -> Bool
forall {a}. (Eq a, BitOps a, Integral a) => a -> Bool
mask Word8
w2 Bool -> Bool -> Bool
&& Word8 -> Bool
forall {a}. (Eq a, BitOps a, Integral a) => a -> Bool
mask Word8
w3
  where
    mask :: a -> Bool
mask a
v = (a
v a -> a -> a
forall bits. BitOps bits => bits -> bits -> bits
.&. a
0xC0) a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0x80
{-# INLINE isContinuation3 #-}

-- | Number of bytes associated with a specific header byte
--
-- If the header byte is invalid then NbBytesInvalid is returned,
data NbBytesCont = NbBytesInvalid | NbBytesCont0 | NbBytesCont1 | NbBytesCont2 | NbBytesCont3

-- | Identical to 'NbBytesCont' but doesn't allow to represent any failure.
--
-- Only use in validated place
data NbBytesCont_ = NbBytesCont0_ | NbBytesCont1_ | NbBytesCont2_ | NbBytesCont3_

-- | Get the number of following bytes given the first byte of a UTF8 sequence.
getNbBytes :: StepASCII -> Int
getNbBytes :: StepASCII -> Int
getNbBytes (StepASCII (W8# Word8#
w)) = Int# -> Int
I# (Word8# -> Int#
getNbBytes# Word8#
w)
{-# INLINE getNbBytes #-}

-- | Check if the byte is a continuation byte
isContinuation# :: Word8# -> Bool
isContinuation# :: Word8# -> Bool
isContinuation# Word8#
w = Word8# -> Word8
W8# (Addr# -> Int# -> Word8#
indexWord8OffAddr# (Table -> Addr#
unTable Table
contTable) (Word# -> Int#
word2Int# (Word8# -> Word#
word8ToWord# Word8#
w))) Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0
{-# INLINE isContinuation# #-}

-- | Check if the byte is a continuation byte
isContinuationW# :: Word# -> Bool
isContinuationW# :: Word# -> Bool
isContinuationW# Word#
w = Word8# -> Word8
W8# (Addr# -> Int# -> Word8#
indexWord8OffAddr# (Table -> Addr#
unTable Table
contTable) (Word# -> Int#
word2Int# Word#
w)) Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0
{-# INLINE isContinuationW# #-}

-- | Get the number of following bytes given the first byte of a UTF8 sequence.
getNbBytes# :: Word8# -> Int#
getNbBytes# :: Word8# -> Int#
getNbBytes# Word8#
w = Word8# -> Int#
word8ToInt# (Addr# -> Int# -> Word8#
indexWord8OffAddr# (Table -> Addr#
unTable Table
headTable) (Word# -> Int#
word2Int# (Word8# -> Word#
word8ToWord# Word8#
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 #-}