Safe Haskell | None |
---|---|
Language | Haskell2010 |
Dynamically-typed datastructure describing a font, whether resolved or a query. Can be parsed from CSS.
Synopsis
- type Pattern = Map Text [(Binding, Value)]
- data Pattern' = Pattern' {}
- module Data.Map
- data Binding
- 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
- validPattern :: Pattern -> Bool
- validPattern' :: Pattern' -> Bool
- parseFontStretch :: Token -> Maybe Int
- parseFontWeight :: Token -> Maybe Int
- parseFontFeatures :: [Token] -> ([(String, Int)], Bool, [Token])
- parseFontVars :: [Token] -> ([(String, Double)], Bool, [Token])
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.
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 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 |
module Data.Map
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.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.
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.