{-# LANGUAGE CApiFFI #-}
module FreeType.FontConfig where
import FreeType.Core.Base (FT_Face)
import Foreign.Ptr (Ptr)
import Foreign.C.String (CString)
import Graphics.Text.Font.Choose.CharSet (CharSet')
import Graphics.Text.Font.Choose.Pattern (Pattern)
import Graphics.Text.Font.Choose.FontSet (FontSet)
import Graphics.Text.Font.Choose.Internal.FFI (fromMessage0, withCString')
foreign import capi "fontconfig-wrap.h fcFreeTypeCharIndex" charIndex :: FT_Face -> Char -> Word
fontCharSet :: FT_Face -> CharSet'
fontCharSet arg = fromMessage0 $ fcFreeTypeCharSet arg
foreign import capi "fontconfig-wrap.h" fcFreeTypeCharSet :: FT_Face -> Ptr Int -> CString
fontCharSetAndSpacing :: FT_Face -> (Int, CharSet')
fontCharSetAndSpacing arg = fromMessage0 $ fcFreeTypeCharSetAndSpacing arg
foreign import capi "fontconfig-wrap.h" fcFreeTypeCharSetAndSpacing ::
FT_Face -> Ptr Int -> CString
fontQuery :: FilePath -> Int -> (Int, Pattern)
fontQuery a b = fromMessage0 $ flip withCString' a $ \a' -> fcFreeTypeQuery a' b
foreign import capi "fontconfig-wrap.h" fcFreeTypeQuery ::
CString -> Int -> Ptr Int -> CString
fontQueryAll :: FilePath -> (Int, Int, FontSet)
fontQueryAll a = fromMessage0 $ withCString' fcFreeTypeQueryAll a
foreign import capi "fontconfig-wrap.h" fcFreeTypeQueryAll ::
CString -> Ptr Int -> CString
fontQueryFace :: FT_Face -> FilePath -> Int -> Pattern
fontQueryFace a b c = fromMessage0 $ flip withCString' b $ \b' -> fcFreeTypeQueryFace a b' c
foreign import capi "fontconfig-wrap.h" fcFreeTypeQueryFace ::
FT_Face -> CString -> Int -> Ptr Int -> CString