Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Graphics.Text.Font.Choose
Description
Query installed fonts from FontConfig.
Synopsis
- module Graphics.Text.Font.Choose.Config.Accessors
- data Config'
- fini :: IO ()
- version :: Int
- initLoadConfig :: IO Config
- initLoadConfigAndFonts :: IO Config
- initFonts :: IO ()
- reinit :: IO ()
- bringUptoDate :: IO ()
- type CharSet = IntSet
- ord :: Char -> Int
- chr :: Int -> Char
- parseCharSet :: String -> Maybe CharSet
- newtype CharSet' = CharSet' {}
- validCharSet' :: CharSet' -> Bool
- module Graphics.Text.Font.Choose.FontSet
- type LangSet = Set String
- newtype LangSet' = LangSet' {}
- data LangComparison
- validLangSet :: LangSet -> Bool
- validLangSet' :: LangSet' -> Bool
- cmp :: LangSet -> LangSet -> LangComparison
- cmp' :: LangSet' -> LangSet' -> LangComparison
- has :: LangSet' -> String -> LangComparison
- defaultLangs :: StrSet
- langs :: StrSet
- normalize :: String -> String
- langCharSet :: String -> CharSet'
- module Graphics.Text.Font.Choose.ObjectSet
- type Pattern = Map Text [(Binding, Value)]
- data Pattern' = Pattern' {}
- data Binding
- validPattern :: Pattern -> Bool
- validPattern' :: Pattern' -> Bool
- setValue :: ToValue v => Text -> Binding -> v -> Pattern -> Pattern
- setValues :: ToValue v => Text -> Binding -> [v] -> Pattern -> Pattern
- getValue :: ToValue v => Text -> Pattern -> Maybe v
- getValues :: ToValue v => Text -> Pattern -> [v]
- equalSubset :: Pattern -> Pattern -> ObjectSet -> Bool
- defaultSubstitute :: Pattern -> Pattern
- nameParse :: String -> Pattern
- nameUnparse :: Pattern -> String
- nameFormat :: Pattern -> String -> String
- module Graphics.Text.Font.Choose.Range
- data FcException
- newtype StrSet = StrSet {}
- validStrSet :: StrSet -> Bool
- module Graphics.Text.Font.Choose.Value
- module Graphics.Text.Font.Choose.Weight
Documentation
initLoadConfig :: IO Config Source #
Loads the default configuration file and returns the resulting configuration. Does not load any font information.
initLoadConfigAndFonts :: IO Config Source #
Loads the default configuration file and builds information about the available fonts. Returns the resulting configuration.
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 True.
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 () 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 reinit
). Otherwise returns True.
parseCharSet :: String -> Maybe CharSet Source #
Utility for parsing "unicode-range" @font-face property.
Wrapper around CharSet
which can implement typeclasses.
validCharSet' :: CharSet' -> Bool Source #
Can this charset be processed by FontConfig?
type LangSet = Set String Source #
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.
Wrapper around LangSet adding useful typeclasses
data LangComparison Source #
The result of cmp
.
Constructors
DifferentLang | The locales share no languages in common |
SameLang | The locales share any language and territory pair |
DifferentTerritory | The locales share a language but differ in which territory that language is for |
Instances
validLangSet :: LangSet -> Bool Source #
Can the given LangSet be processed by FontConfig?
validLangSet' :: LangSet' -> Bool Source #
Can the given LangSet' be processed by FontConfig?
cmp :: LangSet -> LangSet -> LangComparison Source #
Compares language coverage for the 2 given LangSets.
has :: LangSet' -> String -> LangComparison Source #
returns True if a
contains every language in b
.
a
` will contain a language from b
if a
has exactly the language,
or either the language or a
has no territory.
defaultLangs :: StrSet 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.
langCharSet :: String -> CharSet' Source #
Returns the CharSet for a language.
type Pattern = Map Text [(Binding, Value)] Source #
Holds both patterns to match against the available fonts, as well as the information about each font.
Wrapper around Pattern
supporting useful typeclasses.
Instances
Arbitrary Pattern' Source # | |
Generic Pattern' Source # | |
Read Pattern' Source # | |
Show Pattern' Source # | |
Eq Pattern' Source # | |
Hashable Pattern' Source # | |
Defined in Graphics.Text.Font.Choose.Pattern | |
MessagePack Pattern' Source # | |
Defined in Graphics.Text.Font.Choose.Pattern | |
PropertyParser Pattern' Source # | |
Defined in Graphics.Text.Font.Choose.Pattern Methods inherit :: Pattern' -> Pattern' # priority :: Pattern' -> [Text] # shorthand :: Pattern' -> Text -> [Token] -> [(Text, [Token])] # longhand :: Pattern' -> Pattern' -> Text -> [Token] -> Maybe Pattern' # getVars :: Pattern' -> Props # setVars :: Props -> Pattern' -> Pattern' # pseudoEl :: Pattern' -> Text -> (Pattern' -> Maybe Pattern' -> Pattern') -> Pattern' # | |
type Rep Pattern' Source # | |
Defined in Graphics.Text.Font.Choose.Pattern |
The precedance for a field of a Pattern.
Instances
Arbitrary Binding Source # | |
Enum Binding Source # | |
Generic Binding Source # | |
Read Binding Source # | |
Show Binding Source # | |
Eq Binding Source # | |
Ord Binding Source # | |
Defined in Graphics.Text.Font.Choose.Pattern | |
Hashable Binding Source # | |
Defined in Graphics.Text.Font.Choose.Pattern | |
MessagePack Binding Source # | |
Defined in Graphics.Text.Font.Choose.Pattern | |
type Rep Binding Source # | |
Defined in Graphics.Text.Font.Choose.Pattern type Rep Binding = D1 ('MetaData "Binding" "Graphics.Text.Font.Choose.Pattern" "fontconfig-pure-0.5.1.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))) |
validPattern :: Pattern -> Bool Source #
Does the pattern hold a value we can process?
validPattern' :: Pattern' -> Bool Source #
Variant of validPattern
which applies to the Pattern'
wrapper.
setValue :: ToValue v => Text -> Binding -> v -> Pattern -> Pattern Source #
Replace a field with a singular type-casted value.
setValues :: ToValue v => Text -> Binding -> [v] -> Pattern -> Pattern Source #
Replace a field with multiple type-casted values.
getValue :: ToValue v => Text -> Pattern -> Maybe v Source #
Retrieve a field's primary type-casted value.
equalSubset :: Pattern -> Pattern -> ObjectSet -> Bool Source #
Returns whether the given patterns have exactly the same values for all of the given objects.
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.
nameFormat :: Pattern -> String -> String Source #
Format a pattern into a string according to a format specifier See https://fontconfig.pages.freedesktop.org/fontconfig/fontconfig-devel/fcpatternformat.html for full details.
data FcException Source #
Exceptions which can be thrown by FontConfig.
Instances
A set of strings to match.
validStrSet :: StrSet -> Bool Source #
Whether the StrSet can be processed by FontConfig.