module Graphics.Text.Font.Choose.CharSet where import Data.Set (Set, union) import qualified Data.Set as Set import Graphics.Text.Font.Choose.Result (throwNull, throwFalse) import Data.Word (Word32) import Foreign.Ptr import Control.Exception (bracket) import Control.Monad (forM) import Foreign.Marshal.Alloc (alloca) import Foreign.Marshal.Array (allocaArray) import GHC.Base (unsafeChr) import Data.Char (ord, isHexDigit) import Numeric (readHex) -- | An FcCharSet is a set of Unicode chars. type CharSet = Set Char parseChar :: String -> Char parseChar str | ((x, _):_) <- readHex str = toEnum x replaceWild ch ('?':rest) = ch:replaceWild ch rest replaceWild ch (c:cs) = c:replaceWild ch cs replaceWild _ "" = "" parseWild ch str = parseChar $ replaceWild ch str -- | Utility for parsing "unicode-range" @font-face property. parseCharSet ('U':rest) = parseCharSet ('u':rest) -- lowercase initial "u" parseCharSet ('u':'+':cs) | (start@(_:_), '-':ends) <- span isHexDigit cs, (end@(_:_), rest) <- span isHexDigit ends, Just set <- parseCharSet' rest = Just $ Set.union set $ Set.fromList [parseChar start..parseChar end] | (codepoint@(_:_), rest) <- span isHexDigit cs, Just set <- parseCharSet' rest = Just $ flip Set.insert set $ parseChar codepoint | (codepoint@(_:_), rest) <- span (\c -> isHexDigit c || c == '?') cs, Just set <- parseCharSet' rest = Just $ Set.union set $ Set.fromList [ parseWild '0' codepoint..parseWild 'f' codepoint] parseCharSet _ = Nothing parseCharSet' (',':rest) = parseCharSet rest parseCharSet' "" = Just Set.empty parseCharSet' _ = Nothing ------ --- Low-level ------ data CharSet' type CharSet_ = Ptr CharSet' withNewCharSet :: (CharSet_ -> IO a) -> IO a withNewCharSet cb = bracket (throwNull <$> fcCharSetCreate) fcCharSetDestroy cb foreign import ccall "FcCharSetCreate" fcCharSetCreate :: IO CharSet_ foreign import ccall "FcCharSetDestroy" fcCharSetDestroy :: CharSet_ -> IO () withCharSet :: CharSet -> (CharSet_ -> IO a) -> IO a withCharSet chars cb = withNewCharSet $ \chars' -> do forM (Set.elems chars) $ \ch' -> throwFalse <$> (fcCharSetAddChar chars' $ fromIntegral $ ord ch') cb chars' foreign import ccall "FcCharSetAddChar" fcCharSetAddChar :: CharSet_ -> Word32 -> IO Bool thawCharSet :: CharSet_ -> IO CharSet thawCharSet chars' | chars' == nullPtr = return Set.empty | otherwise = allocaArray fcCHARSET_MAP_SIZE $ \iter' -> alloca $ \next' -> do first <- fcCharSetFirstPage chars' iter' next' let go = do ch <- fcCharSetNextPage chars' iter' next' if ch == maxBound then return [] else do chs <- go return (ch:chs) if first == maxBound then return Set.empty else do rest <- go return $ Set.fromList $ map (unsafeChr . fromIntegral) (first:rest) foreign import ccall "my_FcCharSetFirstPage" fcCharSetFirstPage :: CharSet_ -> Ptr Word32 -> Ptr Word32 -> IO Word32 foreign import ccall "my_FcCharSetNextPage" fcCharSetNextPage :: CharSet_ -> Ptr Word32 -> Ptr Word32 -> IO Word32 foreign import ccall "my_FcCHARSET_MAP_SIZE" fcCHARSET_MAP_SIZE :: Int thawCharSet_ :: IO CharSet_ -> IO CharSet thawCharSet_ cb = bracket (throwNull <$> cb) fcCharSetDestroy thawCharSet