M Graphics/Text/Font/Choose/CharSet.hs => Graphics/Text/Font/Choose/CharSet.hs +6 -4
@@ 2,7 2,7 @@ module Graphics.Text.Font.Choose.CharSet where
import Data.Set (Set)
import qualified Data.Set as Set
-import Graphics.Text.Font.Choose.Result (throwNull)
+import Graphics.Text.Font.Choose.Result (throwNull, throwFalse)
import Data.Word (Word32)
import Foreign.Ptr
@@ 28,7 28,8 @@ foreign import ccall "FcCharSetDestroy" fcCharSetDestroy :: CharSet_ -> IO ()
withCharSet :: CharSet -> (CharSet_ -> IO a) -> IO a
withCharSet chars cb = withNewCharSet $ \chars' -> do
- forM (Set.elems chars) $ fcCharSetAddChar chars' . fromIntegral . ord
+ forM (Set.elems chars) $ \ch' ->
+ throwFalse <$> (fcCharSetAddChar chars' $ fromIntegral $ ord ch')
cb chars'
foreign import ccall "FcCharSetAddChar" fcCharSetAddChar :: CharSet_ -> Word32 -> IO Bool
@@ 42,8 43,9 @@ thawCharSet chars' = allocaBytes fcCHARSET_MAP_SIZE $ \iter' -> alloca $ \next'
chs <- go
return (ch:chs)
}
- rest <- go
- return $ Set.fromList $ map (unsafeChr . fromIntegral) (first:rest)
+ if first == maxBound then return Set.empty else do
+ rest <- go
+ return $ Set.fromList $ map (unsafeChr . fromIntegral) (first:rest)
foreign import ccall "FcCharSetFirstPage" fcCharSetFirstPage ::
CharSet_ -> Ptr Word32 -> Ptr Word32 -> IO Word32
foreign import ccall "FcCharSetNextPage" fcCharSetNextPage ::
M Graphics/Text/Font/Choose/Value.hs => Graphics/Text/Font/Choose/Value.hs +2 -1
@@ 1,5 1,6 @@
{-# LANGUAGE DeriveGeneric #-}
-module Graphics.Text.Font.Choose.Value where
+module Graphics.Text.Font.Choose.Value (Value(..), Value_, withValue, thawValue,
+ value'Size) where
import Linear.Matrix (M22)
import Linear.V2 (V2(..))