module Data.Char.Properties.BidiBrackets (Type (..), paired) where import Control.Monad (guard) import Data.Bits import Data.Bool import Data.Int import Data.Word foreign import ccall unsafe "bidi_brackets" c_bidi_brackets :: Word32 -> Word32 data Type = O | C deriving (Eq, Read, Show, Enum, Bounded) paired :: Char -> Maybe (Char, Type) paired x = (toEnum $ fromEnum x + d, bool O C $ testBit x' 31) <$ guard (d /= 0) where x' = c_bidi_brackets (fromIntegral (fromEnum x)) d = fromIntegral $ shiftR (fromIntegral (shiftL x' 1) :: Int32) 29 {-# INLINE paired #-}