fontconfig-pure-0.5.0.0: Resolves font descriptions to font libraries, including ones installed on your freedesktop (Linux or BSD system).
Safe HaskellNone
LanguageHaskell2010

Graphics.Text.Font.Choose.Pattern

Description

Dynamically-typed datastructure describing a font, whether resolved or a query. Can be parsed from CSS.

Synopsis

Documentation

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.0.0-inplace" 'False) (C1 ('MetaCons "Pattern'" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPattern") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pattern)))

module Data.Map

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

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.

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.

parseFontStretch :: Token -> Maybe Int Source #

Parse the CSS font-stretch property.

parseFontWeight :: Token -> Maybe Int Source #

Parse the CSS font-weight property.

parseFontVars :: [Token] -> ([(String, Double)], Bool, [Token]) Source #

Parse OpenType variables from CSS syntax.