~alcinnz/fontconfig-pure

300e62d11157cf30f84e9eabcba68cdddcf1745f — Adrian Cochrane 2 years ago 614373c
Final memory-safety fixes & expose public API.
M Graphics/Text/Font/Choose/Config.hs => Graphics/Text/Font/Choose/Config.hs +2 -0
@@ 275,6 275,8 @@ configGetFileInfo config =
                return (ent : ents)
            Nothing -> return []}
    go
configGetFileInfo' :: IO [(FilePath, String, Bool)]
configGetFileInfo' = configGetCurrent >>= configGetFileInfo
data ConfigFileInfoIter'
foreign import ccall "size_ConfigFileInfoIter" configFileInfoIter'Size :: Int
type ConfigFileInfoIter_ = Ptr ConfigFileInfoIter'

M Graphics/Text/Font/Choose/FontSet.hs => Graphics/Text/Font/Choose/FontSet.hs +0 -42
@@ 2,8 2,6 @@
module Graphics.Text.Font.Choose.FontSet where

import Graphics.Text.Font.Choose.Pattern
--import Graphics.Text.Font.Choose.Config
import Graphics.Text.Font.Choose.ObjectSet
import Graphics.Text.Font.Choose.Result (throwFalse, throwNull)

import Foreign.Ptr (Ptr, castPtr, nullPtr)


@@ 15,46 13,6 @@ import Control.Exception (bracket)

type FontSet = [Pattern]

{-fontSetList :: Config -> [FontSet] -> Pattern -> ObjectSet
fontSetList config fontss pattern objs = unsafePerformIO $ withConfig config $ \config' ->
    withFontSets fontss $ \fontss' n -> withPattern $ \pattern' ->
        withObjectSet objs $ \objs' ->
            thawFontSet_ $ fcFontSetList config' fontss' n pattern' objs'
fontSetList' :: [FontSet] -> Pattern -> ObjectSet
fontSetList' fontss pattern objs = unsafePerformIO $ withFontSets fontss $ \fontss' n ->
    withPattern $ \pattern' -> withObjectSet objs $ \objs' ->
        thawFontSet_ $ fcFontSetList nullPtr fontss' n pattern' objs'
foreign import ccall "FcFontSetList" fcFontSetList ::
    Config_ -> Ptr FontSet_ -> Int -> Pattern_ -> ObjectSet_ -> IO FontSet_

fontSetMatch :: Config -> [FontSet] -> Pattern -> Maybe Pattern
fontSetMatch config fontss pattern = unsafePerformIO $ withConfig config $ \config' ->
    withFontSets fontss $ \fontss' -> withPattern $ \pattern' ->  alloca $ \res' -> do
        ret <- fcFontSetMatch config' fontss' n pattern' res'
        throwPtr res' $ thawPattern_ $ pure ret
fontSetMatch' :: [FontSet] -> Pattern -> Maybe Pattern
fontSetMatch' fontss pattern = unsafePerformIO $ withFontSets fontss $ \fontss' ->
    withPattern $ \pattern' -> alloca $ \res' -> do
        ret <- fcFontSetMatch nullPtr fontss' n pattern' res'
        throwPtr res' $ thawPattern_ $ pure ret
foreign import ccall "FcFontSetMatch" fcFontSetMatch ::
    Config_ -> Ptr FontSet_ -> Int -> Pattern_ -> IO Pattern_

fontSetSort :: Config -> [FontSet] -> Pattern -> Bool -> CharSet -> Maybe FontSet
fontSetSort config fontss pattern trim csp = unsafePerformIO $
    withConfig config $ \config' -> withFontSets fontss $ \fontss' n ->
        withPattern $ \pattern' -> withCharSet csp $ \csp' -> alloca $ \res' -> do
            ret' <- fcFontSetSort config' fontss' n pattern' trim csp' res'
            throwPtr res' $ thawFontSet_ $ pure ret'
fontSetSort' :: [FontSet] -> Pattern -> Bool -> CharSet -> Maybe FontSet
fontSetSort' fontss pattern trim csp = unsafePerformIO $ withConfig $ \config' ->
    withFontSets fontss $ \fontss' n -> withPattern $ \pattern' withCharSet csp $ \csp' ->
        alloca $ \res' -> do
            ret' <- fcFontSetSort nullPtr fontss' n pattern' trim csp' res'
            throwPtr res' $ thawFontSet_ $ pure ret'
foreign import ccall "FcFontSetSort" fcFontSetSort :: Config_ -> Ptr FontSet_
    -> Int -> Pattern_ -> Bool -> CharSet_ -> Ptr Int -> IO FontSet_ -}

------
--- Low-level
------

M Graphics/Text/Font/Choose/Init.hs => Graphics/Text/Font/Choose/Init.hs +1 -1
@@ 1,4 1,4 @@
module Graphics.Text.Font.Choose.Init ({-Config, initLoadConfig, initLoadConfigAndFonts, -}
module Graphics.Text.Font.Choose.Init (Config, initLoadConfig, initLoadConfigAndFonts,
    init, fini, reinit, bringUptoDate, version) where

import Prelude hiding (init)

M Graphics/Text/Font/Choose/Pattern.hs => Graphics/Text/Font/Choose/Pattern.hs +1 -0
@@ 1,5 1,6 @@
{-# LANGUAGE DeriveGeneric #-}
module Graphics.Text.Font.Choose.Pattern (Pattern(..), Binding(..), equalSubset,
    normalizePattern, filter, substitute, nameParse, nameUnparse, format,
    Pattern_, withPattern, thawPattern, thawPattern_, patternAsPointer) where

import Prelude hiding (filter)

M fontconfig-pure.cabal => fontconfig-pure.cabal +7 -6
@@ 51,18 51,19 @@ cabal-version:       >=1.10

library
  -- Modules exported by the library.
  exposed-modules:      Graphics.Text.Font.Choose.Result, FreeType.FontConfig,
  exposed-modules:    Graphics.Text.Font.Choose, FreeType.FontConfig

  -- Modules included in this library but not exported.
  other-modules:      Graphics.Text.Font.Choose.Result, Graphics.Text.Font.Choose.Pattern,
                Graphics.Text.Font.Choose.ObjectSet, Graphics.Text.Font.Choose.CharSet,
                Graphics.Text.Font.Choose.Strings, Graphics.Text.Font.Choose.Range,
                Graphics.Text.Font.Choose.LangSet, Graphics.Text.Font.Choose.Value,
                Graphics.Text.Font.Choose.Pattern, Graphics.Text.Font.Choose.FontSet,
                Graphics.Text.Font.Choose.Config, Graphics.Text.Font.Choose.Init
                Graphics.Text.Font.Choose.FontSet, Graphics.Text.Font.Choose.FontSet.API,
                Graphics.Text.Font.Choose.Config, Graphics.Text.Font.Choose.Init,
                Graphics.Text.Font.Choose.Weight

  c-sources:    cbits/pattern.c

  -- Modules included in this library but not exported.
  -- other-modules:

  -- LANGUAGE extensions used by modules in this package.
  -- other-extensions: