fontconfig-pure-0.5.1.0: Queries your system (Linux/BSD/etc) font database.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.Text.Font.Choose

Description

Query installed fonts from FontConfig.

Synopsis

Documentation

data Config' Source #

Internal placeholder underlying Config.

fini :: IO () Source #

Closes FontConfig's database connection.

version :: Int Source #

Returns the version number of the library.

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.

initFonts :: IO () Source #

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.

reinit :: IO () 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 () 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.

type CharSet = IntSet Source #

An FcCharSet is a set of Unicode characters.

ord :: Char -> Int #

The fromEnum method restricted to the type Char.

chr :: Int -> Char #

The toEnum method restricted to the type Char.

parseCharSet :: String -> Maybe CharSet Source #

Utility for parsing "unicode-range" @font-face property.

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.

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

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.

cmp' :: LangSet' -> LangSet' -> LangComparison Source #

Variation of cmp which operates on LangSet'.

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.

langs :: StrSet Source #

Returns a string set of all languages.

normalize :: String -> String Source #

Returns a string to make lang suitable on fontconfig.

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.

data Pattern' Source #

Wrapper around Pattern supporting useful typeclasses.

Constructors

Pattern' 

Fields

Instances

Instances details
Arbitrary Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Generic Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Associated Types

type Rep Pattern' :: Type -> Type #

Methods

from :: Pattern' -> Rep Pattern' x #

to :: Rep Pattern' x -> Pattern' #

Read Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Show Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Eq Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Hashable Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Methods

hashWithSalt :: Int -> Pattern' -> Int #

hash :: Pattern' -> Int #

MessagePack Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

PropertyParser Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

type Rep Pattern' Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

type Rep Pattern' = D1 ('MetaData "Pattern'" "Graphics.Text.Font.Choose.Pattern" "fontconfig-pure-0.5.1.0-inplace" 'False) (C1 ('MetaCons "Pattern'" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPattern") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pattern)))

data Binding Source #

The precedance for a field of a Pattern.

Constructors

Strong 
Weak 
Same 

Instances

Instances details
Arbitrary Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

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 #

Methods

from :: Binding -> Rep Binding x #

to :: Rep Binding x -> Binding #

Read Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Show Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Eq Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Methods

(==) :: Binding -> Binding -> Bool #

(/=) :: Binding -> Binding -> Bool #

Ord Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Hashable Binding Source # 
Instance details

Defined in Graphics.Text.Font.Choose.Pattern

Methods

hashWithSalt :: Int -> Binding -> Int #

hash :: Binding -> Int #

MessagePack Binding 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.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.

getValues :: ToValue v => Text -> Pattern -> [v] Source #

Retrieve a field's type-casted values.

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.

newtype StrSet Source #

A set of strings to match.

Constructors

StrSet 

Fields

validStrSet :: StrSet -> Bool Source #

Whether the StrSet can be processed by FontConfig.