-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Pure-functional language bindings to FontConfig -- -- Resolves font descriptions to font libraries, including ones installed -- on your freedesktop (Linux or BSD system). @package fontconfig-pure @version 0.4.0.0 module FreeType.FontConfig -- | Maps a Unicode char to a glyph index. This function uses information -- from several possible underlying encoding tables to work around broken -- fonts. As a result, this function isn't designed to be used in -- performance sensitive areas; results from this function are intended -- to be cached by higher level functions. ftCharIndex :: FT_Face -> Char -> Word -- | Scans a FreeType face and returns the set of encoded Unicode chars. ftCharSet :: FT_Face -> CharSet ftCharSetAndSpacing :: FT_Face -> (CharSet, Spacing) -- | Constructs a pattern representing the idth face in fst. -- The number of faces in file is returned in snd. ftQuery :: FilePath -> Int -> IO (Pattern, Int) -- | Constructs patterns found in filename. If id is -1, then all -- patterns found in filename are added to fst. -- Otherwise, this function works exactly like ftQuery. The number -- of faces in filename is returned in snd. ftQueryAll :: FilePath -> Int -> IO (FontSet, Int) -- | Constructs a pattern representing face. filename and -- id are used solely as data for pattern elements. ftQueryFace :: FT_Face -> FilePath -> Int -> IO Pattern -- | A FT_Face queried from FontConfig with glyph-loading -- parameters. data FTFC_Instance Instance :: Maybe String -> Maybe String -> FT_Face -> Int -> Bool -> Bool -> Bool -> Int -> Int -> Double -> Bool -> Bool -> FT_LcdFilter -> [String] -> FTFC_Metrics -> FTFC_Instance [fontName] :: FTFC_Instance -> Maybe String [fontPath] :: FTFC_Instance -> Maybe String [fontFace] :: FTFC_Instance -> FT_Face [fontLoadFlags] :: FTFC_Instance -> Int [fontAntialias] :: FTFC_Instance -> Bool [fontEmbolden] :: FTFC_Instance -> Bool [fontIsColor] :: FTFC_Instance -> Bool [fontRenderFlags] :: FTFC_Instance -> Int [fontRenderFlagsSubpixel] :: FTFC_Instance -> Int [fontPixelSizeFixup] :: FTFC_Instance -> Double [fontPixelFixupEstimated] :: FTFC_Instance -> Bool [fontBGR] :: FTFC_Instance -> Bool [fontLCDFilter] :: FTFC_Instance -> FT_LcdFilter [fontFeats] :: FTFC_Instance -> [String] [fontMetrics] :: FTFC_Instance -> FTFC_Metrics -- | Results queried from FontConfig with caller-relevant properties, -- notably relating to layout. data FTFC_Metrics Metrics :: Int -> Int -> Int -> (Int, Int) -> Bool -> FTFC_Subpixel -> Maybe String -> FTFC_Metrics [height] :: FTFC_Metrics -> Int [descent] :: FTFC_Metrics -> Int [ascent] :: FTFC_Metrics -> Int [maxAdvance] :: FTFC_Metrics -> (Int, Int) [metricsAntialias] :: FTFC_Metrics -> Bool [metricsSubpixel] :: FTFC_Metrics -> FTFC_Subpixel [metricsName] :: FTFC_Metrics -> Maybe String -- | Defines subpixel order to use. Note that this is *ignored* if -- antialiasing has been disabled. data FTFC_Subpixel -- | From FontConfig. SubpixelNone :: FTFC_Subpixel SubpixelHorizontalRGB :: FTFC_Subpixel SubpixelHorizontalBGR :: FTFC_Subpixel SubpixelVerticalRGB :: FTFC_Subpixel SubpixelVerticalBGR :: FTFC_Subpixel -- | Disable subpixel antialiasing. SubpixelDefault :: FTFC_Subpixel -- | Converts the results of a FontConfig query requesting a specific size -- into a FT_Face & related properties. Throw exceptions. instantiatePattern :: FT_Library -> Pattern -> (Double, Double) -> IO FTFC_Instance -- | Results from glyphForIndex. data FTFC_Glyph a Glyph :: Maybe String -> a -> (Double, Double) -> FTFC_Subpixel -> FT_Glyph_Metrics -> FTFC_Glyph a [glyphFontName] :: FTFC_Glyph a -> Maybe String [glyphImage] :: FTFC_Glyph a -> a [glyphAdvance] :: FTFC_Glyph a -> (Double, Double) [glyphSubpixel] :: FTFC_Glyph a -> FTFC_Subpixel [glyphMetrics] :: FTFC_Glyph a -> FT_Glyph_Metrics -- | Looks up a given glyph in a FTFC_Instance & its underlying -- FT_Face Taking into account additional properties from -- FontConfig. Runs a provided callback to render the glyph into a -- reusable datastructure. The FT_Bitmap given to this callback -- must not be used outside it. Throws exceptions. glyphForIndex :: FTFC_Instance -> Word32 -> FTFC_Subpixel -> (FT_Bitmap -> IO a) -> IO (FTFC_Glyph a) bmpAndMetricsForIndex :: FTFC_Instance -> FTFC_Subpixel -> Word32 -> IO (FT_Bitmap, FT_Glyph_Metrics) module Graphics.Text.Font.Choose -- | An FcCharSet is a set of Unicode chars. type CharSet = IntSet -- | The toEnum method restricted to the type Char. chr :: Int -> Char -- | The fromEnum method restricted to the type Char. ord :: Char -> Int -- | An FontSet contains a list of Patterns. Internally -- fontconfig uses this data structure to hold sets of fonts. Externally, -- fontconfig returns the results of listing fonts in this format. type FontSet = [Pattern] -- | An ObjectSet holds a list of pattern property names; it is used -- to indicate which properties are to be returned in the patterns from -- FontList. type ObjectSet = [String] -- | An Pattern` holds a set of names with associated value lists; -- each name refers to a property of a font. Patterns are used as -- inputs to the matching code as well as holding information about -- specific fonts. Each property can hold one or more values; -- conventionally all of the same type, although the interface doesn't -- demand that. type Pattern = [(String, [(Binding, Value)])] -- | How important is it to match this property of the Pattern. data Binding Strong :: Binding Weak :: Binding Same :: Binding -- | Matches a numeric range. data Range Range :: Double -> Double -> Range -- | Matches an integral range. iRange :: Int -> Int -> Range -- | Set of strings, as exposed by other FreeType APIs. type StrSet = Set String -- | Output string lists from FontConfig. type StrList = [String] -- | A dynamic type system for Patterns. data Value ValueVoid :: Value ValueInt :: Int -> Value ValueDouble :: Double -> Value ValueString :: String -> Value ValueBool :: Bool -> Value ValueMatrix :: M22 Double -> Value ValueCharSet :: CharSet -> Value ValueFTFace :: FT_Face -> Value ValueLangSet :: LangSet -> Value ValueRange :: Range -> Value -- | StyleSheet wrapper to parse @font-face rules. data FontFaceParser a FontFaceParser :: FontSet -> a -> FontFaceParser a [cssFonts] :: FontFaceParser a -> FontSet [cssInner] :: FontFaceParser a -> a -- | System configuration regarding available fonts. type Config = ForeignPtr Config' -- | Creates an empty configuration. configCreate :: IO Config -- | Sets the current default configuration to config. Implicitly calls -- configBuildFonts if necessary. configSetCurrent :: Config -> IO () -- | Returns the current default configuration. configGetCurrent :: IO Config -- | Checks all of the files related to config and returns whether any of -- them has been modified since the configuration was created. configUptoDate :: Config -> IO Bool -- | Return the current user's home directory, if it is available, and if -- using it is enabled, and NULL otherwise. (See also -- configEnableHome). configHome :: IO (Maybe String) -- | If enable is True, then Fontconfig will use various files which -- are specified relative to the user's home directory (using the ~ -- notation in the configuration). When enable is False, then all -- use of the home directory in these contexts will be disabled. The -- previous setting of the value is returned. configEnableHome :: Bool -> IO Bool -- | Returns the list of font directories specified in the configuration -- files for config. Does not include any subdirectories. configBuildFonts :: Config -> IO () -- | Variant of configBuildFonts operating on the current -- configuration. configBuildFonts' :: IO () -- | Returns the list of font directories specified in the configuration -- files for config. Does not include any subdirectories. configGetConfigDirs :: Config -> IO StrList -- | Variant of configGetConfigDirs which operates on the current -- configuration. configGetConfigDirs' :: IO StrList -- | Returns the list of font directories in config. This includes the -- configured font directories along with any directories below those in -- the filesystem. configGetFontDirs :: Config -> IO StrList -- | Variant of configGetFontDirs which operates on the current -- config. configGetFontDirs' :: IO StrList -- | Returns the list of known configuration files used to generate config. configGetConfigFiles :: Config -> IO StrList -- | Variant of configGetConfigFiles which operates upon current -- configuration. configGetConfigFiles' :: IO StrList -- | Returns a string list containing all of the directories that -- fontconfig will search when attempting to load a cache file for a font -- directory. configGetCacheDirs :: Config -> IO StrList -- | Variant of configGetCacheDirs which operates upon current -- configuration. configGetCacheDirs' :: IO StrList -- | Whether to operate upon system or application fontlists. data SetName SetSystem :: SetName SetApplication :: SetName -- | Returns one of the two sets of fonts from the configuration as -- specified by set. This font set is owned by the library and must not -- be modified or freed. If config is NULL, the current configuration is -- used. This function isn't MT-safe. configGetFonts :: Config -> SetName -> IO FontSet -- | Variant of configGetFonts which operates upon current -- configuration. configGetFonts' :: SetName -> IO FontSet -- | Returns the interval between automatic checks of the configuration (in -- seconds) specified in config. The configuration is checked during a -- call to FcFontList when this interval has passed since the last check. -- An interval setting of zero disables automatic checks. configGetRescanInterval :: Config -> IO Int -- | Variant of configGetRescanInterval which operates upon current -- configuration. configGetRescanInterval' :: IO Int -- | Clears the set of application-specific fonts. configAppFontClear :: Config -> IO () -- | Variant of configAppFontClear which operates upon current -- configuration. configAppFontClear' :: IO () -- | Adds an application-specific font to the configuration. configAppFontAddFile :: Config -> String -> IO () -- | Variant of configAppFontAddFile which operates upon current -- configuration. configAppFontAddFile' :: String -> IO () -- | Scans the specified directory for fonts, adding each one found to the -- application-specific set of fonts. configAppFontAddDir :: Config -> String -> IO () -- | Variant of configAppFontAddDir which operates upon current -- configuration. configAppFontAddDir' :: String -> IO () -- | What purpose does the given pattern serve? data MatchKind MatchPattern :: MatchKind MatchFont :: MatchKind MatchScan :: MatchKind -- | Performs the sequence of pattern modification operations, if kind is -- MatchPattern, then those tagged as pattern operations are -- applied, else if kind is MatchFont, those tagged as font -- operations are applied and p_pat is used for test elements with -- target=pattern. configSubstituteWithPat :: Config -> Pattern -> Pattern -> MatchKind -> Pattern -- | Variant of configSubstituteWithPat which operates upon current -- configuration. configSubstituteWithPat' :: Pattern -> Pattern -> MatchKind -> Pattern -- | Selects fonts matching p, creates patterns from those fonts containing -- only the objects in os and returns the set of unique such patterns. fontList :: Config -> Pattern -> ObjectSet -> FontSet -- | Variant of fontList which operates upon current configuration. fontList' :: Pattern -> ObjectSet -> FontSet -- | Calls FcConfigSubstituteWithPat without setting p_pat. configSubstitute :: Config -> Pattern -> MatchKind -> Pattern -- | Variant configSubstitute which operates upon current -- configuration. configSubstitute' :: Pattern -> MatchKind -> Pattern -- | Finds the font in sets most closely matching pattern and returns the -- result of fontRenderPrepare for that font and the provided -- pattern. This function should be called only after -- configSubstitute and defaultSubstitute have been called -- for p; otherwise the results will not be correct. fontMatch :: Config -> Pattern -> Maybe Pattern -- | Variant of fontMatch which operates upon current configuration. fontMatch' :: Pattern -> Maybe Pattern -- | Returns the list of fonts sorted by closeness to p. If trim is -- True, elements in the list which don't include Unicode coverage -- not provided by earlier elements in the list are elided. The union of -- Unicode coverage of all of the fonts is returned in snd. This -- function should be called only after configSubstitute and -- defaultSubstitute have been called for p; otherwise the results -- will not be correct. fontSort :: Config -> Pattern -> Bool -> Maybe (FontSet, CharSet) -- | Variant of fontSort which operates upon current configuration. fontSort' :: Pattern -> Bool -> Maybe (FontSet, CharSet) -- | Creates a new pattern consisting of elements of font not appearing in -- pat, elements of pat not appearing in font and the best matching value -- from pat for elements appearing in both. The result is passed to -- configSubstituteWithPat with kind matchFont and then -- returned. fontRenderPrepare :: Config -> Pattern -> Pattern -> Pattern -- | Variant of fontRenderPrepare which operates upon current -- configuration. fontRenderPrepare' :: Pattern -> Pattern -> Pattern -- | Walks the configuration in file and constructs the internal -- representation in config. Any include files referenced from -- within file will be loaded and parsed. If complain -- is False, no warning will be displayed if file does -- not exist. Error and warning messages will be output to stderr. configParseAndLoad :: Config -> String -> Bool -> IO Bool configParseAndLoad' :: String -> Bool -> IO Bool -- | Obtains the system root directory in config if available. All -- files (including file properties in patterns) obtained from this -- config are relative to this system root directory. This -- function isn't MT-safe. configGetSysRoot :: Config -> IO String -- | Variant of configGetSysRoot which operates upon current -- configuration. configGetSysRoot' :: IO String -- | Walks the configuration in memory and constructs the internal -- representation in config. Any includes files referenced from -- within memory will be loaded and dparsed. If -- complain is False, no warning will be displayed if -- file does not exist. Error and warning messages will be -- output to stderr. configParseAndLoadFromMemory :: Config -> String -> Bool -> IO Bool -- | Variant of configParseAndLoadFromMemory which operates upon -- current configuration. configParseAndLoadFromMemory' :: String -> Bool -> IO Bool -- | Set sysroot as the system root directory. All file paths used -- or created with this config (including file properties in -- patterns) will be considered or made relative to this -- sysroot. This allows a host to generate caches for targets at -- build time. This also allows a cache to be re-targeted to a different -- base directory if configGetSysRoot is used to resolve file -- paths. When setting this on the current config this causes changing -- current config. configSetSysRoot :: Config -> String -> IO () -- | Variant of configSetSysRoot which operates upon current -- configuration. configSetSysRoot' :: String -> IO () -- | Retrieves a list of all filepaths & descriptions for all fonts in -- this configuration alongside whether each is enabled. Not thread-safe. configGetFileInfo :: Config -> IO [(FilePath, String, Bool)] -- | Variant configGetFileInfo which operates upon current -- configuration. configGetFileInfo' :: IO [(FilePath, String, Bool)] -- | Selects fonts matching pattern from sets, creates patterns from those -- fonts containing only the objects in object_set and returns the set of -- unique such patterns. fontSetList :: Config -> [FontSet] -> Pattern -> ObjectSet -> FontSet -- | Variant of fontSetList operating upon register default -- Config. fontSetList' :: [FontSet] -> Pattern -> ObjectSet -> FontSet -- | Finds the font in sets most closely matching pattern and returns the -- result of fontRenderPrepare for that font and the provided -- pattern. This function should be called only after -- configSubstitute and defaultSubstitute have been called -- for pattern; otherwise the results will not be correct. fontSetMatch :: Config -> [FontSet] -> Pattern -> Maybe Pattern -- | Variant of fontSetMatch operating upon registered default -- Config. fontSetMatch' :: [FontSet] -> Pattern -> Maybe Pattern -- | Returns the list of fonts from sets sorted by closeness to pattern. If -- trim is True, elements in the list which don't include Unicode -- coverage not provided by earlier elements in the list are elided. The -- union of Unicode coverage of all of the fonts is returned in csp. This -- function should be called only after configSubstitute and -- defaultSubstitute have been called for p; otherwise the results -- will not be correct. The returned FcFontSet references Pattern -- structures which may be shared by the return value from multiple -- fontSort calls, applications cannot modify these patterns. -- Instead, they should be passed, along with pattern to -- fontRenderPrepare which combines them into a complete pattern. fontSetSort :: Config -> [FontSet] -> Pattern -> Bool -> Maybe (FontSet, CharSet) -- | Variant of fontSetSort operating upon registered default -- Config. fontSetSort' :: [FontSet] -> Pattern -> Bool -> Maybe (FontSet, CharSet) -- | Loads the default configuration file and returns the resulting -- configuration. Does not load any font information. initLoadConfig :: IO (ForeignPtr Config') -- | Loads the default configuration file and builds information about the -- available fonts. Returns the resulting configuration. initLoadConfigAndFonts :: IO (ForeignPtr Config') -- | Initialize fontconfig library Loads the default configuration file and -- the fonts referenced therein and sets the default configuration to -- that result. Returns whether this process succeeded or not. If the -- default configuration has already been loaded, this routine does -- nothing and returns FcTrue. init :: IO Bool -- | Frees all data structures allocated by previous calls to fontconfig -- functions. Fontconfig returns to an uninitialized state, requiring a -- new call to one of the FcInit functions before any other fontconfig -- function may be called. fini :: IO () -- | Forces the default configuration file to be reloaded and resets the -- default configuration. Returns False if the configuration -- cannot be reloaded (due to configuration file errors, allocation -- failures or other issues) and leaves the existing configuration -- unchanged. Otherwise returns True. reinit :: IO Bool -- | Checks the rescan interval in the default configuration, checking the -- configuration if the interval has passed and reloading the -- configuration if when any changes are detected. Returns False if the -- configuration cannot be reloaded (see FcInitReinitialize). Otherwise -- returns True. bringUptoDate :: IO Bool -- | Library version number Returns the version number of the library. version :: Int -- | An LangSet is a set of language names (each of which include -- language and an optional territory). They are used when selecting -- fonts to indicate which languages the fonts need to support. Each font -- is marked, using language orthography information built into -- fontconfig, with the set of supported languages. type LangSet = Set String -- | Returns a string set of the default languages according to the -- environment variables on the system. This function looks for them in -- order of FC_LANG, LC_ALL, LC_CTYPE and LANG then. If there are no -- valid values in those environment variables, "en" will be set as -- fallback. defaultLangs :: IO LangSet -- | Returns a string set of all known languages. langs :: LangSet -- | langSetCompare compares language coverage for ls_a and ls_b. If -- they share any language and territory pair, returns SameLang. -- If they share a language but differ in which territory that language -- is for, this function returns DifferentTerritory. If they share -- no languages in common, this function returns DifferentLang. langSetCompare :: LangSet -> LangSet -> LangResult -- | Returns a string to make lang suitable on FontConfig. langNormalize :: String -> String -- | Returns the FcCharMap for a language. langCharSet :: String -> CharSet -- | Returns whether pa and pb have exactly the same values for all of the -- objects in os. equalSubset :: Pattern -> Pattern -> ObjectSet -> Bool -- | Restructures a Pattern so each key repeats at most once. normalizePattern :: Pattern -> Pattern -- | Returns a new pattern that only has those objects from p that are in -- os. If os is NULL, a duplicate of p is returned. filter :: Pattern -> ObjectSet -> Pattern -- | Supplies default values for underspecified font patterns: * Patterns -- without a specified style or weight are set to Medium * Patterns -- without a specified style or slant are set to Roman * Patterns without -- a specified pixel size are given one computed from any specified point -- size (default 12), dpi (default 75) and scale (default 1). defaultSubstitute :: Pattern -> Pattern -- | Converts name from the standard text format described above into a -- pattern. nameParse :: String -> Pattern -- | Converts the given pattern into the standard text format described -- above. nameUnparse :: Pattern -> String -- | Converts given pattern into text described fy given format specifier. -- See for details: -- https://www.freedesktop.org/software/fontconfig/fontconfig-devel/fcpatternformat.html format :: Pattern -> String -> String -- | Replaces the values under the given "key" in given "pattern" with -- given "binding" & "value". setValue :: ToValue x => String -> Binding -> x -> Pattern -> Pattern -- | Replaces the values under the given "key" in given "pattern" with -- given "binding" & "value"s. setValues :: ToValue x => String -> Binding -> [x] -> Pattern -> Pattern -- | Deletes all entries in the given pattern under a given key. unset :: Eq a => a -> [(a, b)] -> [(a, b)] -- | Retrieves all values in the given pattern under a given key. getValues :: String -> Pattern -> [Value] -- | Retrieves all values under a given key & coerces to desired -- Maybe type. getValues' :: ToValue b => String -> Pattern -> [b] -- | Retrieves first value in the given pattern under a given key. getValue :: String -> Pattern -> Value getValue' :: ToValue x => String -> Pattern -> Maybe x getValue0 :: ToValue x => String -> Pattern -> x