{-# LANGUAGE MagicHash, BangPatterns #-}

-- |
-- Module      : Data.Text.Internal.Encoding.Utf16
-- Copyright   : (c) 2008, 2009 Tom Harper,
--               (c) 2009 Bryan O'Sullivan,
--               (c) 2009 Duncan Coutts
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : GHC
--
-- /Warning/: this is an internal module, and does not have a stable
-- API or name. Functions in this module may not check or enforce
-- preconditions expected by public modules. Use at your own risk!
--
-- Basic UTF-16 validation and character manipulation.
module Data.Text.Internal.Encoding.Utf16
    (
      chr2
    , validate1
    , validate2
    ) where

import GHC.Exts
import GHC.Word (Word16(..))

chr2 :: Word16 -> Word16 -> Char
chr2 :: Word16 -> Word16 -> Char
chr2 (W16# Word#
a#) (W16# Word#
b#) = Char# -> Char
C# (Int# -> Char#
chr# (Int#
upper# Int# -> Int# -> Int#
+# Int#
lower# Int# -> Int# -> Int#
+# Int#
0x10000#))
    where
      !x# :: Int#
x# = Word# -> Int#
word2Int# Word#
a#
      !y# :: Int#
y# = Word# -> Int#
word2Int# Word#
b#
      !upper# :: Int#
upper# = Int# -> Int# -> Int#
uncheckedIShiftL# (Int#
x# Int# -> Int# -> Int#
-# Int#
0xD800#) Int#
10#
      !lower# :: Int#
lower# = Int#
y# Int# -> Int# -> Int#
-# Int#
0xDC00#
{-# INLINE chr2 #-}

validate1    :: Word16 -> Bool
validate1 :: Word16 -> Bool
validate1 Word16
x1 = Word16
x1 Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
< Word16
0xD800 Bool -> Bool -> Bool
|| Word16
x1 Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
> Word16
0xDFFF
{-# INLINE validate1 #-}

validate2       ::  Word16 -> Word16 -> Bool
validate2 :: Word16 -> Word16 -> Bool
validate2 Word16
x1 Word16
x2 = Word16
x1 Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word16
0xD800 Bool -> Bool -> Bool
&& Word16
x1 Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word16
0xDBFF Bool -> Bool -> Bool
&&
                  Word16
x2 Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word16
0xDC00 Bool -> Bool -> Bool
&& Word16
x2 Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word16
0xDFFF
{-# INLINE validate2 #-}