~alcinnz/fontconfig-pure

9e1e5029f66325c1391a658c39c4573e74aafe03 — Adrian Cochrane 2 years ago c10cdcf
Commit FontSet API (seperated out to break import loop).
1 files changed, 55 insertions(+), 0 deletions(-)

A Graphics/Text/Font/Choose/FontSet/API.hs
A Graphics/Text/Font/Choose/FontSet/API.hs => Graphics/Text/Font/Choose/FontSet/API.hs +55 -0
@@ 0,0 1,55 @@
-- Here to break recursive imports...
module Graphics.Text.Font.Choose.FontSet.API where

import Graphics.Text.Font.Choose.FontSet
import Graphics.Text.Font.Choose.Pattern
import Graphics.Text.Font.Choose.Config
import Graphics.Text.Font.Choose.ObjectSet
import Graphics.Text.Font.Choose.CharSet
import Graphics.Text.Font.Choose.Result (throwPtr)

import Foreign.Ptr (Ptr, castPtr, nullPtr)
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Marshal.Alloc (alloca)
import System.IO.Unsafe (unsafePerformIO)

fontSetList :: Config -> [FontSet] -> Pattern -> ObjectSet -> FontSet
fontSetList config fontss pattern objs = unsafePerformIO $ withForeignPtr config $ \config' ->
    withFontSets fontss $ \fontss' n -> withPattern pattern $ \pattern' ->
        withObjectSet objs $ \objs' ->
            thawFontSet_ $ fcFontSetList config' fontss' n pattern' objs'
fontSetList' :: [FontSet] -> Pattern -> ObjectSet -> FontSet
fontSetList' fontss pattern objs = unsafePerformIO $ withFontSets fontss $ \fontss' n ->
    withPattern pattern $ \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 $ withForeignPtr config $ \config' ->
    withFontSets fontss $ \fontss' n -> withPattern pattern $ \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' n ->
    withPattern pattern $ \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_ -> Ptr Int -> IO Pattern_

fontSetSort :: Config -> [FontSet] -> Pattern -> Bool -> CharSet -> Maybe FontSet
fontSetSort config fontss pattern trim csp = unsafePerformIO $
    withForeignPtr config $ \config' -> withFontSets fontss $ \fontss' n ->
        withPattern pattern $ \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 $
    withFontSets fontss $ \fontss' n -> withPattern pattern $ \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_