{-# LANGUAGE BangPatterns #-}
module Data.Unicode.Properties.DecomposeHangul
(decomposeCharHangul
, hangulFirst
, hangulLast
, isHangul
, isHangulLV
, isJamo
, jamoLFirst
, jamoLIndex
, jamoLLast
, jamoVFirst
, jamoVIndex
, jamoVLast
, jamoTFirst
, jamoTCount
, jamoTIndex
, jamoLast
, jamoNCount
)
where
import Control.Exception (assert)
import Data.Char (ord)
import GHC.Base (unsafeChr)
import Data.Unicode.Internal.Division (quotRem21, quotRem28)
jamoLFirst, jamoLCount, jamoLLast :: Int
jamoLFirst = 0x1100
jamoLCount = 19
jamoLLast = jamoLFirst + jamoLCount - 1
jamoVFirst, jamoVCount, jamoVLast :: Int
jamoVFirst = 0x1161
jamoVCount = 21
jamoVLast = jamoVFirst + jamoVCount - 1
jamoTFirst, jamoTCount :: Int
jamoTFirst = 0x11a7
jamoTCount = 28
jamoLast :: Int
jamoLast = jamoTFirst + jamoTCount - 1
jamoNCount :: Int
jamoNCount = 588
hangulFirst, hangulLast :: Int
hangulFirst = 0xac00
hangulLast = hangulFirst + jamoLCount * jamoVCount * jamoTCount - 1
isHangul :: Char -> Bool
isHangul c = n >= hangulFirst && n <= hangulLast
where n = ord c
isHangulLV :: Char -> Bool
isHangulLV c = assert (jamoTCount == 28)
snd (quotRem28 (ord c - hangulFirst)) == 0
isJamo :: Char -> Bool
isJamo c = n >= jamoLFirst && n <= jamoLast
where n = ord c
jamoLIndex :: Char -> Maybe Int
jamoLIndex c
| index >= 0 && index < jamoLCount = Just index
| otherwise = Nothing
where index = ord c - jamoLFirst
jamoVIndex :: Char -> Maybe Int
jamoVIndex c
| index >= 0 && index < jamoVCount = Just index
| otherwise = Nothing
where index = ord c - jamoVFirst
jamoTIndex :: Char -> Maybe Int
jamoTIndex c
| index > 0 && index < jamoTCount = Just index
| otherwise = Nothing
where index = ord c - jamoTFirst
{-# INLINE decomposeCharHangul #-}
decomposeCharHangul :: Char -> (Char, Char, Char)
decomposeCharHangul c = (l, v, t)
where
i = (ord c) - hangulFirst
!(tn, ti) = assert (jamoTCount == 28) quotRem28 i
!(li, vi) = assert (jamoVCount == 21) quotRem21 tn
l = unsafeChr (jamoLFirst + li)
v = unsafeChr (jamoVFirst + vi)
t = unsafeChr (jamoTFirst + ti)