{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.Collate.CombiningClass
( genCombiningClassMap
)
where
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Read as TR
import Language.Haskell.TH
import Language.Haskell.TH.Syntax (qAddDependentFile)
genCombiningClassMap :: FilePath -> Q Exp
genCombiningClassMap :: FilePath -> Q Exp
genCombiningClassMap FilePath
fp = do
FilePath -> Q ()
forall (m :: * -> *). Quasi m => FilePath -> m ()
qAddDependentFile FilePath
fp
[(Int, Int)]
cccmap <- Text -> [(Int, Int)]
parseDerivedCombiningClass (Text -> [(Int, Int)]) -> Q Text -> Q [(Int, Int)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Text -> Q Text
forall a. IO a -> Q a
runIO (FilePath -> IO Text
T.readFile FilePath
fp)
[| cccmap |]
parseDerivedCombiningClass :: Text -> [(Int, Int)]
parseDerivedCombiningClass :: Text -> [(Int, Int)]
parseDerivedCombiningClass =
[[(Int, Int)]] -> [(Int, Int)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(Int, Int)]] -> [(Int, Int)])
-> (Text -> [[(Int, Int)]]) -> Text -> [(Int, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Maybe [(Int, Int)]) -> [Text] -> [[(Int, Int)]]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Text -> Maybe [(Int, Int)]
parseLine ([Text] -> [[(Int, Int)]])
-> (Text -> [Text]) -> Text -> [[(Int, Int)]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines
parseLine :: Text -> Maybe [(Int, Int)]
parseLine :: Text -> Maybe [(Int, Int)]
parseLine Text
t =
case Reader Int
forall a. Integral a => Reader a
TR.hexadecimal Text
t of
Left FilePath
_ -> Maybe [(Int, Int)]
forall a. Maybe a
Nothing
Right (Int
lower, Text
rest) ->
let (Int
upper, Text
rest') =
if Text
".." Text -> Text -> Bool
`T.isPrefixOf` Text
rest
then case Reader Int
forall a. Integral a => Reader a
TR.hexadecimal (Int -> Text -> Text
T.drop Int
2 Text
rest) of
Left FilePath
_ -> (Int
lower, Text
rest)
Right (Int
upper', Text
rest'') -> (Int
upper', Text
rest'')
else (Int
lower, Text
rest)
in case Reader Int
forall a. Integral a => Reader a
TR.decimal Reader Int -> Reader Int
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
2 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
';') Text
rest' of
Left FilePath
_ -> Maybe [(Int, Int)]
forall a. Maybe a
Nothing
Right (Int
0, Text
_) -> Maybe [(Int, Int)]
forall a. Maybe a
Nothing
Right (Int
category :: Int, Text
_)
-> [(Int, Int)] -> Maybe [(Int, Int)]
forall a. a -> Maybe a
Just ([(Int, Int)] -> Maybe [(Int, Int)])
-> [(Int, Int)] -> Maybe [(Int, Int)]
forall a b. (a -> b) -> a -> b
$ (Int -> (Int, Int)) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (,Int
category) (Int -> Int -> [Int]
forall a. Enum a => a -> a -> [a]
enumFromTo Int
lower Int
upper)