module Unicode.Char.Identifiers.Security
(
unicodeVersion
, isAllowedInIdentifier
, T.IdentifierType(..)
, identifierTypes
, isIdentifierTypeAllowed
, confusablePrototype
, intentionalConfusables
, isIntentionallyConfusable
)
where
import Data.List.NonEmpty (NonEmpty)
import GHC.Exts (eqChar#, indexCharOffAddr#, isTrue#)
import Unicode.Internal.Bits.Security (unpackCStringUtf8#)
import qualified Unicode.Internal.Char.Security.Confusables as C
import qualified Unicode.Internal.Char.Security.IdentifierStatus as S
import qualified Unicode.Internal.Char.Security.IdentifierType as T
import qualified Unicode.Internal.Char.Security.IntentionalConfusables as IC
import Unicode.Internal.Char.Security.Version (unicodeVersion)
{-# INLINE isAllowedInIdentifier #-}
isAllowedInIdentifier :: Char -> Bool
isAllowedInIdentifier :: Char -> Bool
isAllowedInIdentifier = Char -> Bool
S.isAllowedInIdentifier
{-# INLINE isIdentifierTypeAllowed #-}
isIdentifierTypeAllowed :: T.IdentifierType -> Bool
isIdentifierTypeAllowed :: IdentifierType -> Bool
isIdentifierTypeAllowed = \case
IdentifierType
T.Inclusion -> Bool
True
IdentifierType
T.Recommended -> Bool
True
IdentifierType
_ -> Bool
False
{-# INLINE identifierTypes #-}
identifierTypes :: Char -> NonEmpty T.IdentifierType
identifierTypes :: Char -> NonEmpty IdentifierType
identifierTypes = Int -> NonEmpty IdentifierType
T.decodeIdentifierTypes (Int -> NonEmpty IdentifierType)
-> (Char -> Int) -> Char -> NonEmpty IdentifierType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
T.identifierTypes
{-# INLINE confusablePrototype #-}
confusablePrototype :: Char -> String
confusablePrototype :: Char -> String
confusablePrototype Char
c = Addr# -> String
unpackCStringUtf8# (Char -> Addr#
C.confusablePrototype Char
c)
{-# INLINE intentionalConfusables #-}
intentionalConfusables :: Char -> String
intentionalConfusables :: Char -> String
intentionalConfusables Char
c = Addr# -> String
unpackCStringUtf8# (Char -> Addr#
IC.intentionalConfusables Char
c)
{-# INLINE isIntentionallyConfusable #-}
isIntentionallyConfusable :: Char -> Bool
isIntentionallyConfusable :: Char -> Bool
isIntentionallyConfusable Char
c = Int# -> Bool
isTrue# (Char#
c# Char# -> Char# -> Int#
`eqChar#` Char#
'\0'#)
where
!addr :: Addr#
addr = Char -> Addr#
IC.intentionalConfusables Char
c
!c# :: Char#
c# = Addr# -> Int# -> Char#
indexCharOffAddr# Addr#
addr Int#
0#