{-# LANGUAGE CApiFFI #-}
module Graphics.Text.Font.Choose.Config.Accessors(
configCreate, setCurrent, current, current', uptodate, home, enableHome, buildFonts,
configDirs, fontDirs, configFiles, cacheDirs, fonts, rescanInterval,
setRescanInterval, appFontAddFile, appFontAddDir, appFontClear, substitute,
fontMatch, fontSort, fontRenderPrepare, fontList, filename, parseAndLoad,
parseAndLoadFromMemory, sysroot, setSysroot, SetName(..), MatchKind(..)
) where
import Graphics.Text.Font.Choose.Config
import Graphics.Text.Font.Choose.FontSet
import Graphics.Text.Font.Choose.Pattern
import Graphics.Text.Font.Choose.CharSet
import Graphics.Text.Font.Choose.ObjectSet
import Foreign.Ptr (Ptr, nullPtr)
import Foreign.ForeignPtr (newForeignPtr, withForeignPtr)
import Foreign.C.String (CString, withCString, peekCString)
import Graphics.Text.Font.Choose.Result (throwBool, throwNull)
import Graphics.Text.Font.Choose.Internal.FFI (peekCString', fromMessageIO0,
withMessage, withForeignPtr', fromMessage0, fromMessage)
import System.IO.Unsafe (unsafePerformIO)
configCreate :: IO Config
configCreate :: IO Config
configCreate = FinalizerPtr Config' -> Ptr Config' -> IO Config
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Config'
fcConfigDestroy (Ptr Config' -> IO Config) -> IO (Ptr Config') -> IO Config
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr Config' -> IO (Ptr Config')
forall a. Ptr a -> IO (Ptr a)
throwNull (Ptr Config' -> IO (Ptr Config'))
-> IO (Ptr Config') -> IO (Ptr Config')
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Ptr Config')
fcConfigCreate
foreign import capi "fontconfig/fontconfig.h FcConfigCreate" fcConfigCreate :: IO (Ptr Config')
setCurrent :: Config -> IO ()
setCurrent :: Config -> IO ()
setCurrent Config
conf = Bool -> IO ()
throwBool (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf Ptr Config' -> IO Bool
fcConfigSetCurrent
foreign import capi "fontconfig/fontconfig.h FcConfigSetCurrent" fcConfigSetCurrent :: Ptr Config' -> IO Bool
current :: IO Config
current :: IO Config
current = FinalizerPtr Config' -> Ptr Config' -> IO Config
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Config'
fcConfigDestroy (Ptr Config' -> IO Config) -> IO (Ptr Config') -> IO Config
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr Config' -> IO (Ptr Config')
forall a. Ptr a -> IO (Ptr a)
throwNull (Ptr Config' -> IO (Ptr Config'))
-> IO (Ptr Config') -> IO (Ptr Config')
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr Config' -> IO (Ptr Config')
fcConfigReference Ptr Config'
forall a. Ptr a
nullPtr
foreign import capi "fontconfig/fontconfig.h FcConfigReference" fcConfigReference :: Ptr Config' -> IO (Ptr Config')
{-# NOINLINE current' #-}
current' :: Config
current' :: Config
current' = IO Config -> Config
forall a. IO a -> a
unsafePerformIO IO Config
current
uptodate :: Config -> IO Bool
uptodate :: Config -> IO Bool
uptodate Config
conf = Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf Ptr Config' -> IO Bool
fcConfigUptoDate
foreign import capi "fontconfig/fontconfig.h FcConfigUptoDate" fcConfigUptoDate :: Ptr Config' -> IO Bool
home :: String
home :: [Char]
home = CString -> [Char]
peekCString' CString
fcConfigHome
foreign import capi "fontconfig/fontconfig.h FcConfigHome" fcConfigHome :: CString
foreign import capi "fontconfig/fontconfig.h FcConfigEnableHome" enableHome :: Bool -> IO Bool
buildFonts :: Config -> IO ()
buildFonts :: Config -> IO ()
buildFonts Config
conf = Bool -> IO ()
throwBool (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf Ptr Config' -> IO Bool
fcConfigBuildFonts
foreign import capi "fontconfig/fontconfig.h FcConfigBuildFonts" fcConfigBuildFonts :: Ptr Config' -> IO Bool
configDirs :: Config -> IO [String]
configDirs :: Config -> IO ObjectSet
configDirs Config
conf =
(Ptr Int -> IO CString) -> IO ObjectSet
forall a. MessagePack a => (Ptr Int -> IO CString) -> IO a
fromMessageIO0 ((Ptr Int -> IO CString) -> IO ObjectSet)
-> (Ptr Int -> IO CString) -> IO ObjectSet
forall a b. (a -> b) -> a -> b
$ \Ptr Int
len -> Config -> (Ptr Config' -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf ((Ptr Config' -> IO CString) -> IO CString)
-> (Ptr Config' -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> Ptr Config' -> Ptr Int -> IO CString
fcConfigGetConfigDirs Ptr Config'
conf' Ptr Int
len
foreign import capi "fontconfig-wrap.h" fcConfigGetConfigDirs :: Ptr Config' -> Ptr Int -> IO CString
fontDirs :: Config -> IO [String]
fontDirs :: Config -> IO ObjectSet
fontDirs Config
conf =
(Ptr Int -> IO CString) -> IO ObjectSet
forall a. MessagePack a => (Ptr Int -> IO CString) -> IO a
fromMessageIO0 ((Ptr Int -> IO CString) -> IO ObjectSet)
-> (Ptr Int -> IO CString) -> IO ObjectSet
forall a b. (a -> b) -> a -> b
$ \Ptr Int
len -> Config -> (Ptr Config' -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf ((Ptr Config' -> IO CString) -> IO CString)
-> (Ptr Config' -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> Ptr Config' -> Ptr Int -> IO CString
fcConfigGetFontDirs Ptr Config'
conf' Ptr Int
len
foreign import capi "fontconfig-wrap.h" fcConfigGetFontDirs :: Ptr Config' -> Ptr Int -> IO CString
configFiles :: Config -> IO [String]
configFiles :: Config -> IO ObjectSet
configFiles Config
conf =
(Ptr Int -> IO CString) -> IO ObjectSet
forall a. MessagePack a => (Ptr Int -> IO CString) -> IO a
fromMessageIO0 ((Ptr Int -> IO CString) -> IO ObjectSet)
-> (Ptr Int -> IO CString) -> IO ObjectSet
forall a b. (a -> b) -> a -> b
$ \Ptr Int
len -> Config -> (Ptr Config' -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf ((Ptr Config' -> IO CString) -> IO CString)
-> (Ptr Config' -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> Ptr Config' -> Ptr Int -> IO CString
fcConfigGetConfigFiles Ptr Config'
conf' Ptr Int
len
foreign import capi "fontconfig-wrap.h" fcConfigGetConfigFiles :: Ptr Config' -> Ptr Int -> IO CString
cacheDirs :: Config -> IO [String]
cacheDirs :: Config -> IO ObjectSet
cacheDirs Config
conf =
(Ptr Int -> IO CString) -> IO ObjectSet
forall a. MessagePack a => (Ptr Int -> IO CString) -> IO a
fromMessageIO0 ((Ptr Int -> IO CString) -> IO ObjectSet)
-> (Ptr Int -> IO CString) -> IO ObjectSet
forall a b. (a -> b) -> a -> b
$ \Ptr Int
len -> Config -> (Ptr Config' -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf ((Ptr Config' -> IO CString) -> IO CString)
-> (Ptr Config' -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> Ptr Config' -> Ptr Int -> IO CString
fcConfigGetCacheDirs Ptr Config'
conf' Ptr Int
len
foreign import capi "fontconfig-wrap.h" fcConfigGetCacheDirs :: Ptr Config' -> Ptr Int -> IO CString
data SetName = System
| App
deriving (ReadPrec [SetName]
ReadPrec SetName
Int -> ReadS SetName
ReadS [SetName]
(Int -> ReadS SetName)
-> ReadS [SetName]
-> ReadPrec SetName
-> ReadPrec [SetName]
-> Read SetName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SetName
readsPrec :: Int -> ReadS SetName
$creadList :: ReadS [SetName]
readList :: ReadS [SetName]
$creadPrec :: ReadPrec SetName
readPrec :: ReadPrec SetName
$creadListPrec :: ReadPrec [SetName]
readListPrec :: ReadPrec [SetName]
Read, Int -> SetName -> ShowS
[SetName] -> ShowS
SetName -> [Char]
(Int -> SetName -> ShowS)
-> (SetName -> [Char]) -> ([SetName] -> ShowS) -> Show SetName
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SetName -> ShowS
showsPrec :: Int -> SetName -> ShowS
$cshow :: SetName -> [Char]
show :: SetName -> [Char]
$cshowList :: [SetName] -> ShowS
showList :: [SetName] -> ShowS
Show, SetName -> SetName -> Bool
(SetName -> SetName -> Bool)
-> (SetName -> SetName -> Bool) -> Eq SetName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SetName -> SetName -> Bool
== :: SetName -> SetName -> Bool
$c/= :: SetName -> SetName -> Bool
/= :: SetName -> SetName -> Bool
Eq, Int -> SetName
SetName -> Int
SetName -> [SetName]
SetName -> SetName
SetName -> SetName -> [SetName]
SetName -> SetName -> SetName -> [SetName]
(SetName -> SetName)
-> (SetName -> SetName)
-> (Int -> SetName)
-> (SetName -> Int)
-> (SetName -> [SetName])
-> (SetName -> SetName -> [SetName])
-> (SetName -> SetName -> [SetName])
-> (SetName -> SetName -> SetName -> [SetName])
-> Enum SetName
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SetName -> SetName
succ :: SetName -> SetName
$cpred :: SetName -> SetName
pred :: SetName -> SetName
$ctoEnum :: Int -> SetName
toEnum :: Int -> SetName
$cfromEnum :: SetName -> Int
fromEnum :: SetName -> Int
$cenumFrom :: SetName -> [SetName]
enumFrom :: SetName -> [SetName]
$cenumFromThen :: SetName -> SetName -> [SetName]
enumFromThen :: SetName -> SetName -> [SetName]
$cenumFromTo :: SetName -> SetName -> [SetName]
enumFromTo :: SetName -> SetName -> [SetName]
$cenumFromThenTo :: SetName -> SetName -> SetName -> [SetName]
enumFromThenTo :: SetName -> SetName -> SetName -> [SetName]
Enum)
fonts :: Config -> SetName -> IO FontSet
fonts :: Config -> SetName -> IO FontSet
fonts Config
conf SetName
setname =
(Ptr Int -> IO CString) -> IO FontSet
forall a. MessagePack a => (Ptr Int -> IO CString) -> IO a
fromMessageIO0 ((Ptr Int -> IO CString) -> IO FontSet)
-> (Ptr Int -> IO CString) -> IO FontSet
forall a b. (a -> b) -> a -> b
$ \Ptr Int
len -> Config -> (Ptr Config' -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf ((Ptr Config' -> IO CString) -> IO CString)
-> (Ptr Config' -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> Ptr Config' -> Bool -> Ptr Int -> IO CString
fcConfigGetFonts Ptr Config'
conf' (SetName
setname SetName -> SetName -> Bool
forall a. Eq a => a -> a -> Bool
== SetName
System) Ptr Int
len
foreign import capi "fontconfig-wrap.h" fcConfigGetFonts :: Ptr Config' -> Bool -> Ptr Int -> IO CString
rescanInterval :: Config -> IO Int
rescanInterval :: Config -> IO Int
rescanInterval = (Config -> (Ptr Config' -> IO Int) -> IO Int)
-> (Ptr Config' -> IO Int) -> Config -> IO Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Config -> (Ptr Config' -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Ptr Config' -> IO Int
fcConfigGetRescanInterval
foreign import capi "fontconfig/fontconfig.h FcConfigGetRescanInterval" fcConfigGetRescanInterval ::
Ptr Config' -> IO Int
setRescanInterval :: Config -> Int -> IO ()
setRescanInterval :: Config -> Int -> IO ()
setRescanInterval Config
conf Int
period =
Bool -> IO ()
throwBool (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf ((Ptr Config' -> Int -> IO Bool) -> Int -> Ptr Config' -> IO Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip Ptr Config' -> Int -> IO Bool
fcConfigSetRescanInterval Int
period)
foreign import capi "fontconfig/fontconfig.h FcConfigSetRescanInterval" fcConfigSetRescanInterval ::
Ptr Config' -> Int -> IO Bool
appFontAddFile :: Config -> FilePath -> IO ()
appFontAddFile :: Config -> [Char] -> IO ()
appFontAddFile Config
conf [Char]
file = Bool -> IO ()
throwBool (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf (\Ptr Config'
conf' ->
[Char] -> (CString -> IO Bool) -> IO Bool
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
file ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
file' -> Ptr Config' -> CString -> IO Bool
fcConfigAppFontAddFile Ptr Config'
conf' CString
file')
foreign import capi "fontconfig/fontconfig.h FcConfigAppFontAddFile" fcConfigAppFontAddFile ::
Ptr Config' -> CString -> IO Bool
appFontAddDir :: Config -> FilePath -> IO ()
appFontAddDir :: Config -> [Char] -> IO ()
appFontAddDir Config
conf [Char]
file = Bool -> IO ()
throwBool (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf (\Ptr Config'
conf' ->
[Char] -> (CString -> IO Bool) -> IO Bool
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
file ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
file' -> Ptr Config' -> CString -> IO Bool
fcConfigAppFontAddDir Ptr Config'
conf' CString
file')
foreign import capi "fontconfig/fontconfig.h FcConfigAppFontAddDir" fcConfigAppFontAddDir ::
Ptr Config' -> CString -> IO Bool
appFontClear :: Config -> IO ()
appFontClear :: Config -> IO ()
appFontClear = (Config -> (Ptr Config' -> IO ()) -> IO ())
-> (Ptr Config' -> IO ()) -> Config -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Config -> (Ptr Config' -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Ptr Config' -> IO ()
fcConfigAppFontClear
foreign import capi "fontconfig/fontconfig.h FcConfigAppFontClear" fcConfigAppFontClear ::
Ptr Config' -> IO ()
data MatchKind = MatchPattern
| MatchFont
deriving (ReadPrec [MatchKind]
ReadPrec MatchKind
Int -> ReadS MatchKind
ReadS [MatchKind]
(Int -> ReadS MatchKind)
-> ReadS [MatchKind]
-> ReadPrec MatchKind
-> ReadPrec [MatchKind]
-> Read MatchKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MatchKind
readsPrec :: Int -> ReadS MatchKind
$creadList :: ReadS [MatchKind]
readList :: ReadS [MatchKind]
$creadPrec :: ReadPrec MatchKind
readPrec :: ReadPrec MatchKind
$creadListPrec :: ReadPrec [MatchKind]
readListPrec :: ReadPrec [MatchKind]
Read, Int -> MatchKind -> ShowS
[MatchKind] -> ShowS
MatchKind -> [Char]
(Int -> MatchKind -> ShowS)
-> (MatchKind -> [Char])
-> ([MatchKind] -> ShowS)
-> Show MatchKind
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MatchKind -> ShowS
showsPrec :: Int -> MatchKind -> ShowS
$cshow :: MatchKind -> [Char]
show :: MatchKind -> [Char]
$cshowList :: [MatchKind] -> ShowS
showList :: [MatchKind] -> ShowS
Show, MatchKind -> MatchKind -> Bool
(MatchKind -> MatchKind -> Bool)
-> (MatchKind -> MatchKind -> Bool) -> Eq MatchKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MatchKind -> MatchKind -> Bool
== :: MatchKind -> MatchKind -> Bool
$c/= :: MatchKind -> MatchKind -> Bool
/= :: MatchKind -> MatchKind -> Bool
Eq, Int -> MatchKind
MatchKind -> Int
MatchKind -> [MatchKind]
MatchKind -> MatchKind
MatchKind -> MatchKind -> [MatchKind]
MatchKind -> MatchKind -> MatchKind -> [MatchKind]
(MatchKind -> MatchKind)
-> (MatchKind -> MatchKind)
-> (Int -> MatchKind)
-> (MatchKind -> Int)
-> (MatchKind -> [MatchKind])
-> (MatchKind -> MatchKind -> [MatchKind])
-> (MatchKind -> MatchKind -> [MatchKind])
-> (MatchKind -> MatchKind -> MatchKind -> [MatchKind])
-> Enum MatchKind
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: MatchKind -> MatchKind
succ :: MatchKind -> MatchKind
$cpred :: MatchKind -> MatchKind
pred :: MatchKind -> MatchKind
$ctoEnum :: Int -> MatchKind
toEnum :: Int -> MatchKind
$cfromEnum :: MatchKind -> Int
fromEnum :: MatchKind -> Int
$cenumFrom :: MatchKind -> [MatchKind]
enumFrom :: MatchKind -> [MatchKind]
$cenumFromThen :: MatchKind -> MatchKind -> [MatchKind]
enumFromThen :: MatchKind -> MatchKind -> [MatchKind]
$cenumFromTo :: MatchKind -> MatchKind -> [MatchKind]
enumFromTo :: MatchKind -> MatchKind -> [MatchKind]
$cenumFromThenTo :: MatchKind -> MatchKind -> MatchKind -> [MatchKind]
enumFromThenTo :: MatchKind -> MatchKind -> MatchKind -> [MatchKind]
Enum)
substitute :: Config -> Pattern -> Maybe Pattern -> MatchKind -> Pattern
substitute :: Config -> Pattern -> Maybe Pattern -> MatchKind -> Pattern
substitute Config
conf Pattern
p (Just Pattern
p_pat) MatchKind
kind =
(Ptr Int -> CString) -> Pattern
forall a. MessagePack a => (Ptr Int -> CString) -> a
fromMessage0 ((Ptr Int -> CString) -> Pattern)
-> (Ptr Int -> CString) -> Pattern
forall a b. (a -> b) -> a -> b
$ ((Ptr Config' -> Ptr Int -> CString)
-> Config -> Ptr Int -> CString)
-> Config
-> (Ptr Config' -> Ptr Int -> CString)
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Ptr Config' -> Ptr Int -> CString) -> Config -> Ptr Int -> CString
forall a b. (Ptr a -> b) -> ForeignPtr a -> b
withForeignPtr' Config
conf ((Ptr Config' -> Ptr Int -> CString) -> Ptr Int -> CString)
-> (Ptr Config' -> Ptr Int -> CString) -> Ptr Int -> CString
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> ((CString -> Int -> Ptr Int -> CString)
-> FontSet -> Ptr Int -> CString)
-> FontSet
-> (CString -> Int -> Ptr Int -> CString)
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (CString -> Int -> Ptr Int -> CString)
-> FontSet -> Ptr Int -> CString
forall a b. MessagePack a => (CString -> Int -> b) -> a -> b
withMessage [Pattern
p, Pattern
p_pat] ((CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString)
-> (CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString
forall a b. (a -> b) -> a -> b
$ \CString
msg Int
len ->
Ptr Config' -> CString -> Int -> Bool -> Ptr Int -> CString
fcConfigSubstituteWithPat Ptr Config'
conf' CString
msg Int
len (MatchKind
kind MatchKind -> MatchKind -> Bool
forall a. Eq a => a -> a -> Bool
== MatchKind
MatchFont)
substitute Config
conf Pattern
p Maybe Pattern
Nothing MatchKind
kind =
(Ptr Int -> CString) -> Pattern
forall a. MessagePack a => (Ptr Int -> CString) -> a
fromMessage0 ((Ptr Int -> CString) -> Pattern)
-> (Ptr Int -> CString) -> Pattern
forall a b. (a -> b) -> a -> b
$ ((Ptr Config' -> Ptr Int -> CString)
-> Config -> Ptr Int -> CString)
-> Config
-> (Ptr Config' -> Ptr Int -> CString)
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Ptr Config' -> Ptr Int -> CString) -> Config -> Ptr Int -> CString
forall a b. (Ptr a -> b) -> ForeignPtr a -> b
withForeignPtr' Config
conf ((Ptr Config' -> Ptr Int -> CString) -> Ptr Int -> CString)
-> (Ptr Config' -> Ptr Int -> CString) -> Ptr Int -> CString
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> ((CString -> Int -> Ptr Int -> CString)
-> FontSet -> Ptr Int -> CString)
-> FontSet
-> (CString -> Int -> Ptr Int -> CString)
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (CString -> Int -> Ptr Int -> CString)
-> FontSet -> Ptr Int -> CString
forall a b. MessagePack a => (CString -> Int -> b) -> a -> b
withMessage [Pattern
p] ((CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString)
-> (CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString
forall a b. (a -> b) -> a -> b
$ \CString
msg Int
len ->
Ptr Config' -> CString -> Int -> Bool -> Ptr Int -> CString
fcConfigSubstituteWithPat Ptr Config'
conf' CString
msg Int
len (MatchKind
kind MatchKind -> MatchKind -> Bool
forall a. Eq a => a -> a -> Bool
== MatchKind
MatchFont)
foreign import capi "fontconfig-wrap.h" fcConfigSubstituteWithPat ::
Ptr Config' -> CString -> Int -> Bool -> Ptr Int -> CString
fontMatch :: Config -> Pattern -> Maybe Pattern
fontMatch :: Config -> Pattern -> Maybe Pattern
fontMatch Config
conf Pattern
pat = (Ptr Int -> CString) -> Maybe Pattern
forall a. MessagePack a => (Ptr Int -> CString) -> Maybe a
fromMessage ((Ptr Int -> CString) -> Maybe Pattern)
-> (Ptr Int -> CString) -> Maybe Pattern
forall a b. (a -> b) -> a -> b
$ ((CString -> Int -> Ptr Int -> CString)
-> Pattern -> Ptr Int -> CString)
-> Pattern
-> (CString -> Int -> Ptr Int -> CString)
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (CString -> Int -> Ptr Int -> CString)
-> Pattern -> Ptr Int -> CString
forall a b. MessagePack a => (CString -> Int -> b) -> a -> b
withMessage Pattern
pat ((CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString)
-> (CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString
forall a b. (a -> b) -> a -> b
$ (Ptr Config' -> CString -> Int -> Ptr Int -> CString)
-> Config -> CString -> Int -> Ptr Int -> CString
forall a b. (Ptr a -> b) -> ForeignPtr a -> b
withForeignPtr' Ptr Config' -> CString -> Int -> Ptr Int -> CString
fcFontMatch Config
conf
foreign import capi "fontconfig-wrap.h" fcFontMatch :: Ptr Config' -> CString -> Int -> Ptr Int -> CString
fontSort :: Config -> Pattern -> Bool -> Maybe (FontSet, CharSet')
fontSort :: Config -> Pattern -> Bool -> Maybe (FontSet, CharSet')
fontSort Config
conf Pattern
pat Bool
trim = (Ptr Int -> CString) -> Maybe (FontSet, CharSet')
forall a. MessagePack a => (Ptr Int -> CString) -> Maybe a
fromMessage ((Ptr Int -> CString) -> Maybe (FontSet, CharSet'))
-> (Ptr Int -> CString) -> Maybe (FontSet, CharSet')
forall a b. (a -> b) -> a -> b
$ (((CString -> Int -> Bool -> Ptr Int -> CString)
-> Pattern -> Bool -> Ptr Int -> CString)
-> Pattern
-> (CString -> Int -> Bool -> Ptr Int -> CString)
-> Bool
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (CString -> Int -> Bool -> Ptr Int -> CString)
-> Pattern -> Bool -> Ptr Int -> CString
forall a b. MessagePack a => (CString -> Int -> b) -> a -> b
withMessage Pattern
pat ((CString -> Int -> Bool -> Ptr Int -> CString)
-> Bool -> Ptr Int -> CString)
-> (CString -> Int -> Bool -> Ptr Int -> CString)
-> Bool
-> Ptr Int
-> CString
forall a b. (a -> b) -> a -> b
$ (Ptr Config' -> CString -> Int -> Bool -> Ptr Int -> CString)
-> Config -> CString -> Int -> Bool -> Ptr Int -> CString
forall a b. (Ptr a -> b) -> ForeignPtr a -> b
withForeignPtr' Ptr Config' -> CString -> Int -> Bool -> Ptr Int -> CString
fcFontSort Config
conf) Bool
trim
foreign import capi "fontconfig-wrap.h" fcFontSort ::
Ptr Config' -> CString -> Int -> Bool -> Ptr Int -> CString
fontRenderPrepare :: Config -> Pattern -> Pattern -> Pattern
fontRenderPrepare :: Config -> Pattern -> Pattern -> Pattern
fontRenderPrepare Config
conf Pattern
pat Pattern
font = (Ptr Int -> CString) -> Pattern
forall a. MessagePack a => (Ptr Int -> CString) -> a
fromMessage0 ((Ptr Int -> CString) -> Pattern)
-> (Ptr Int -> CString) -> Pattern
forall a b. (a -> b) -> a -> b
$ ((CString -> Int -> Ptr Int -> CString)
-> FontSet -> Ptr Int -> CString)
-> FontSet
-> (CString -> Int -> Ptr Int -> CString)
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (CString -> Int -> Ptr Int -> CString)
-> FontSet -> Ptr Int -> CString
forall a b. MessagePack a => (CString -> Int -> b) -> a -> b
withMessage [Pattern
pat, Pattern
font] ((CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString)
-> (CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString
forall a b. (a -> b) -> a -> b
$
(Ptr Config' -> CString -> Int -> Ptr Int -> CString)
-> Config -> CString -> Int -> Ptr Int -> CString
forall a b. (Ptr a -> b) -> ForeignPtr a -> b
withForeignPtr' Ptr Config' -> CString -> Int -> Ptr Int -> CString
fcFontRenderPrepare Config
conf
foreign import capi "fontconfig-wrap.h" fcFontRenderPrepare ::
Ptr Config' -> CString -> Int -> Ptr Int -> CString
fontList :: Config -> Pattern -> ObjectSet -> FontSet
fontList :: Config -> Pattern -> ObjectSet -> FontSet
fontList Config
conf Pattern
pat ObjectSet
os = (Ptr Int -> CString) -> FontSet
forall a. MessagePack a => (Ptr Int -> CString) -> a
fromMessage0 ((Ptr Int -> CString) -> FontSet)
-> (Ptr Int -> CString) -> FontSet
forall a b. (a -> b) -> a -> b
$ ((CString -> Int -> Ptr Int -> CString)
-> (Pattern, ObjectSet) -> Ptr Int -> CString)
-> (Pattern, ObjectSet)
-> (CString -> Int -> Ptr Int -> CString)
-> Ptr Int
-> CString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (CString -> Int -> Ptr Int -> CString)
-> (Pattern, ObjectSet) -> Ptr Int -> CString
forall a b. MessagePack a => (CString -> Int -> b) -> a -> b
withMessage (Pattern
pat, ObjectSet
os) ((CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString)
-> (CString -> Int -> Ptr Int -> CString) -> Ptr Int -> CString
forall a b. (a -> b) -> a -> b
$ (Ptr Config' -> CString -> Int -> Ptr Int -> CString)
-> Config -> CString -> Int -> Ptr Int -> CString
forall a b. (Ptr a -> b) -> ForeignPtr a -> b
withForeignPtr' Ptr Config' -> CString -> Int -> Ptr Int -> CString
fcFontList Config
conf
foreign import capi "fontconfig-wrap.h" fcFontList :: Ptr Config' -> CString -> Int -> Ptr Int -> CString
filename :: Config -> FilePath -> IO FilePath
filename :: Config -> [Char] -> IO [Char]
filename Config
conf [Char]
path =
CString -> IO [Char]
peekCString (CString -> IO [Char]) -> IO CString -> IO [Char]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf (\Ptr Config'
_ -> [Char] -> (CString -> IO CString) -> IO CString
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
path ((CString -> IO CString) -> IO CString)
-> (CString -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ CString -> IO CString
fcConfigGetFilename)
foreign import capi "fontconfig/fontconfig.h FcConfigFilename" fcConfigGetFilename ::
CString -> IO CString
parseAndLoad :: Config -> FilePath -> Bool -> IO ()
parseAndLoad :: Config -> [Char] -> Bool -> IO ()
parseAndLoad Config
conf [Char]
path Bool
complain =
Bool -> IO ()
throwBool (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf (\Ptr Config'
conf' -> [Char] -> (CString -> IO Bool) -> IO Bool
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
path ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
path' ->
Ptr Config' -> CString -> Bool -> IO Bool
fcConfigParseAndLoad Ptr Config'
conf' CString
path' Bool
complain)
foreign import capi "fontconfig/fontconfig.h FcConfigParseAndLoad" fcConfigParseAndLoad ::
Ptr Config' -> CString -> Bool -> IO Bool
parseAndLoadFromMemory :: Config -> FilePath -> Bool -> IO ()
parseAndLoadFromMemory :: Config -> [Char] -> Bool -> IO ()
parseAndLoadFromMemory Config
conf [Char]
buf Bool
complain =
Bool -> IO ()
throwBool (Bool -> IO ()) -> IO Bool -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf (\Ptr Config'
conf' -> [Char] -> (CString -> IO Bool) -> IO Bool
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
buf ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
buf' ->
Ptr Config' -> CString -> Bool -> IO Bool
fcConfigParseAndLoadFromMemory Ptr Config'
conf' CString
buf' Bool
complain)
foreign import capi "fontconfig/fontconfig.h FcConfigParseAndLoadFromMemory"
fcConfigParseAndLoadFromMemory :: Ptr Config' -> CString -> Bool -> IO Bool
sysroot :: Config -> IO String
sysroot :: Config -> IO [Char]
sysroot Config
conf = CString -> IO [Char]
peekCString (CString -> IO [Char]) -> IO CString -> IO [Char]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Config -> (Ptr Config' -> IO CString) -> IO CString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf Ptr Config' -> IO CString
fcConfigGetSysRoot
foreign import ccall "fontconfig/fontconfig.h FcConfigGetSysRoot" fcConfigGetSysRoot ::
Ptr Config' -> IO CString
setSysroot :: Config -> String -> IO ()
setSysroot :: Config -> [Char] -> IO ()
setSysroot Config
conf [Char]
root =
Config -> (Ptr Config' -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr Config
conf ((Ptr Config' -> IO ()) -> IO ())
-> (Ptr Config' -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Config'
conf' -> [Char] -> (CString -> IO ()) -> IO ()
forall a. [Char] -> (CString -> IO a) -> IO a
withCString [Char]
root ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Config' -> CString -> IO ()
fcConfigSetSysRoot Ptr Config'
conf'
foreign import capi "fontconfig/fontconfig.h FcConfigSetSysRoot" fcConfigSetSysRoot ::
Ptr Config' -> CString -> IO ()