fontconfig-pure-0.4.0.0: Pure-functional language bindings to FontConfig
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.Text.Font.Choose

Synopsis

Documentation

type CharSet = IntSet Source #

An FcCharSet is a set of Unicode chars.

chr :: Int -> Char Source #

The toEnum method restricted to the type Char.

ord :: Char -> Int Source #

The fromEnum method restricted to the type Char.

type FontSet = [Pattern] Source #

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 ObjectSet = [String] Source #

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 Pattern = [(String, [(Binding, Value)])] Source #

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.

data Binding Source #

How important is it to match this property of the Pattern.

Constructors

Strong 
Weak 
Same 

Instances

Instances details
Enum Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Generic Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Associated Types

type Rep Binding :: Type -> Type Source #

Show Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Eq Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Ord Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Hashable Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

PropertyParser Pattern Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

type Rep Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

type Rep Binding = D1 ('MetaData "Binding" "Graphics.Text.Font.Choose.Pattern" "fontconfig-pure-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Strong" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Weak" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Same" 'PrefixI 'False) (U1 :: Type -> Type)))

data Range Source #

Matches a numeric range.

Constructors

Range Double Double 

Instances

Instances details
Generic Range Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Range

Associated Types

type Rep Range :: Type -> Type Source #

Methods

from :: Range -> Rep Range x Source #

to :: Rep Range x -> Range Source #

Show Range Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Range

Eq Range Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Range

Methods

(==) :: Range -> Range -> Bool Source #

(/=) :: Range -> Range -> Bool Source #

Ord Range Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Range

Hashable Range Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Range

type Rep Range Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Range

type Rep Range = D1 ('MetaData "Range" "Graphics.Text.Font.Choose.Range" "fontconfig-pure-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Range" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

iRange :: Int -> Int -> Range Source #

Matches an integral range.

type StrSet = Set String Source #

Set of strings, as exposed by other FreeType APIs.

type StrList = [String] Source #

Output string lists from FontConfig.

data Value Source #

A dynamic type system for Patterns.

Instances

Instances details
Generic Value Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Value

Associated Types

type Rep Value :: Type -> Type Source #

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Show Value Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Value

Eq Value Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Value

Methods

(==) :: Value -> Value -> Bool Source #

(/=) :: Value -> Value -> Bool Source #

Ord Value Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Value

Hashable Value Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Value

PropertyParser Pattern Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

type Rep Value Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Value

type Rep Value = D1 ('MetaData "Value" "Graphics.Text.Font.Choose.Value" "fontconfig-pure-0.4.0.0-inplace" 'False) (((C1 ('MetaCons "ValueVoid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValueInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "ValueDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: (C1 ('MetaCons "ValueString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ValueBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :+: ((C1 ('MetaCons "ValueMatrix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (M22 Double))) :+: C1 ('MetaCons "ValueCharSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CharSet))) :+: (C1 ('MetaCons "ValueFTFace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FT_Face)) :+: (C1 ('MetaCons "ValueLangSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LangSet)) :+: C1 ('MetaCons "ValueRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range))))))

data FontFaceParser a Source #

StyleSheet wrapper to parse @font-face rules.

Constructors

FontFaceParser 

Fields

type Config = ForeignPtr Config' Source #

System configuration regarding available fonts.

configCreate :: IO Config Source #

Creates an empty configuration.

configSetCurrent :: Config -> IO () Source #

Sets the current default configuration to config. Implicitly calls configBuildFonts if necessary.

configGetCurrent :: IO Config Source #

Returns the current default configuration.

configUptoDate :: Config -> IO Bool Source #

Checks all of the files related to config and returns whether any of them has been modified since the configuration was created.

configHome :: IO (Maybe String) Source #

Return the current user's home directory, if it is available, and if using it is enabled, and NULL otherwise. (See also configEnableHome).

configEnableHome :: Bool -> IO Bool Source #

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.

configBuildFonts :: Config -> IO () Source #

Returns the list of font directories specified in the configuration files for config. Does not include any subdirectories.

configBuildFonts' :: IO () Source #

Variant of configBuildFonts operating on the current configuration.

configGetConfigDirs :: Config -> IO StrList Source #

Returns the list of font directories specified in the configuration files for config. Does not include any subdirectories.

configGetConfigDirs' :: IO StrList Source #

Variant of configGetConfigDirs which operates on the current configuration.

configGetFontDirs :: Config -> IO StrList Source #

Returns the list of font directories in config. This includes the configured font directories along with any directories below those in the filesystem.

configGetFontDirs' :: IO StrList Source #

Variant of configGetFontDirs which operates on the current config.

configGetConfigFiles :: Config -> IO StrList Source #

Returns the list of known configuration files used to generate config.

configGetConfigFiles' :: IO StrList Source #

Variant of configGetConfigFiles which operates upon current configuration.

configGetCacheDirs :: Config -> IO StrList Source #

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' :: IO StrList Source #

Variant of configGetCacheDirs which operates upon current configuration.

configGetFonts :: Config -> SetName -> IO FontSet Source #

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' :: SetName -> IO FontSet Source #

Variant of configGetFonts which operates upon current configuration.

configGetRescanInterval :: Config -> IO Int Source #

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' :: IO Int Source #

Variant of configGetRescanInterval which operates upon current configuration.

configAppFontClear :: Config -> IO () Source #

Clears the set of application-specific fonts.

configAppFontClear' :: IO () Source #

Variant of configAppFontClear which operates upon current configuration.

configAppFontAddFile :: Config -> String -> IO () Source #

Adds an application-specific font to the configuration.

configAppFontAddFile' :: String -> IO () Source #

Variant of configAppFontAddFile which operates upon current configuration.

configAppFontAddDir :: Config -> String -> IO () Source #

Scans the specified directory for fonts, adding each one found to the application-specific set of fonts.

configAppFontAddDir' :: String -> IO () Source #

Variant of configAppFontAddDir which operates upon current configuration.

configSubstituteWithPat :: Config -> Pattern -> Pattern -> MatchKind -> Pattern Source #

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' :: Pattern -> Pattern -> MatchKind -> Pattern Source #

Variant of configSubstituteWithPat which operates upon current configuration.

fontList :: Config -> Pattern -> ObjectSet -> FontSet Source #

Selects fonts matching p, creates patterns from those fonts containing only the objects in os and returns the set of unique such patterns.

fontList' :: Pattern -> ObjectSet -> FontSet Source #

Variant of fontList which operates upon current configuration.

configSubstitute :: Config -> Pattern -> MatchKind -> Pattern Source #

Calls FcConfigSubstituteWithPat without setting p_pat.

configSubstitute' :: Pattern -> MatchKind -> Pattern Source #

Variant configSubstitute which operates upon current configuration.

fontMatch :: Config -> Pattern -> Maybe Pattern Source #

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' :: Pattern -> Maybe Pattern Source #

Variant of fontMatch which operates upon current configuration.

fontSort :: Config -> Pattern -> Bool -> Maybe (FontSet, CharSet) Source #

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' :: Pattern -> Bool -> Maybe (FontSet, CharSet) Source #

Variant of fontSort which operates upon current configuration.

fontRenderPrepare :: Config -> Pattern -> Pattern -> Pattern Source #

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' :: Pattern -> Pattern -> Pattern Source #

Variant of fontRenderPrepare which operates upon current configuration.

configParseAndLoad :: Config -> String -> Bool -> IO Bool Source #

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.

configGetSysRoot :: Config -> IO String Source #

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' :: IO String Source #

Variant of configGetSysRoot which operates upon current configuration.

configParseAndLoadFromMemory :: Config -> String -> Bool -> IO Bool Source #

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' :: String -> Bool -> IO Bool Source #

Variant of configParseAndLoadFromMemory which operates upon current configuration.

configSetSysRoot :: Config -> String -> IO () Source #

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' :: String -> IO () Source #

Variant of configSetSysRoot which operates upon current configuration.

configGetFileInfo :: Config -> IO [(FilePath, String, Bool)] Source #

Retrieves a list of all filepaths & descriptions for all fonts in this configuration alongside whether each is enabled. Not thread-safe.

configGetFileInfo' :: IO [(FilePath, String, Bool)] Source #

Variant configGetFileInfo which operates upon current configuration.

fontSetList :: Config -> [FontSet] -> Pattern -> ObjectSet -> FontSet Source #

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' :: [FontSet] -> Pattern -> ObjectSet -> FontSet Source #

Variant of fontSetList operating upon register default Config.

fontSetMatch :: Config -> [FontSet] -> Pattern -> Maybe Pattern Source #

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' :: [FontSet] -> Pattern -> Maybe Pattern Source #

Variant of fontSetMatch operating upon registered default Config.

fontSetSort :: Config -> [FontSet] -> Pattern -> Bool -> Maybe (FontSet, CharSet) Source #

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' :: [FontSet] -> Pattern -> Bool -> Maybe (FontSet, CharSet) Source #

Variant of fontSetSort operating upon registered default Config.

initLoadConfig :: IO (ForeignPtr Config') Source #

Loads the default configuration file and returns the resulting configuration. Does not load any font information.

initLoadConfigAndFonts :: IO (ForeignPtr Config') Source #

Loads the default configuration file and builds information about the available fonts. Returns the resulting configuration.

init :: IO Bool Source #

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.

fini :: IO () Source #

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.

reinit :: IO Bool Source #

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.

bringUptoDate :: IO Bool Source #

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.

version :: Int Source #

Library version number Returns the version number of the library.

type LangSet = Set String Source #

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.

defaultLangs :: IO LangSet Source #

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.

langs :: LangSet Source #

Returns a string set of all known languages.

langSetCompare :: LangSet -> LangSet -> LangResult Source #

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.

langNormalize :: String -> String Source #

Returns a string to make lang suitable on FontConfig.

langCharSet :: String -> CharSet Source #

Returns the FcCharMap for a language.

equalSubset :: Pattern -> Pattern -> ObjectSet -> Bool Source #

Returns whether pa and pb have exactly the same values for all of the objects in os.

normalizePattern :: Pattern -> Pattern Source #

Restructures a Pattern so each key repeats at most once.

filter :: Pattern -> ObjectSet -> Pattern Source #

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.

defaultSubstitute :: Pattern -> Pattern Source #

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).

nameParse :: String -> Pattern Source #

Converts name from the standard text format described above into a pattern.

nameUnparse :: Pattern -> String Source #

Converts the given pattern into the standard text format described above.

format :: Pattern -> String -> String Source #

Converts given pattern into text described fy given format specifier. See for details: https://www.freedesktop.org/software/fontconfig/fontconfig-devel/fcpatternformat.html

setValue :: ToValue x => String -> Binding -> x -> Pattern -> Pattern Source #

Replaces the values under the given "key" in given "pattern" with given "binding" & "value".

setValues :: ToValue x => String -> Binding -> [x] -> Pattern -> Pattern Source #

Replaces the values under the given "key" in given "pattern" with given "binding" & "value"s.

unset :: Eq a => a -> [(a, b)] -> [(a, b)] Source #

Deletes all entries in the given pattern under a given key.

getValues :: String -> Pattern -> [Value] Source #

Retrieves all values in the given pattern under a given key.

getValues' :: ToValue b => String -> Pattern -> [b] Source #

Retrieves all values under a given key & coerces to desired Maybe type.

getValue :: String -> Pattern -> Value Source #

Retrieves first value in the given pattern under a given key.

getValue' :: ToValue x => String -> Pattern -> Maybe x Source #

getValue0 :: ToValue x => String -> Pattern -> x Source #