M lib/Graphics/Text/Font/Choose.hs => lib/Graphics/Text/Font/Choose.hs +1 -0
@@ 1,3 1,4 @@
+-- | Query installed fonts from FontConfig.
module Graphics.Text.Font.Choose(
module Graphics.Text.Font.Choose.Config.Accessors, Config', fini, version,
initLoadConfig, initLoadConfigAndFonts, initFonts, reinit, bringUptoDate,
M lib/Graphics/Text/Font/Choose/CharSet.hs => lib/Graphics/Text/Font/Choose/CharSet.hs +1 -1
@@ 1,8 1,8 @@
+-- | Process sets of unicode characters, possibly parsed from CSS.
module Graphics.Text.Font.Choose.CharSet(
CharSet, ord, chr, module IntSet, parseCharSet, CharSet'(..), validCharSet'
) where
-import Data.IntSet (IntSet, union)
import Data.IntSet as IntSet
import Data.Char (isHexDigit, ord, chr)
M lib/Graphics/Text/Font/Choose/Config.hs => lib/Graphics/Text/Font/Choose/Config.hs +1 -0
@@ 1,4 1,5 @@
{-# LANGUAGE CApiFFI #-}
+-- | Load system fonts configuration.
module Graphics.Text.Font.Choose.Config(Config', fini, version,
initLoadConfig, initLoadConfigAndFonts, initFonts, reinit, bringUptoDate,
-- For the sake of Graphics.Font.Choose.Config.Accessors
M lib/Graphics/Text/Font/Choose/Config/Accessors.hs => lib/Graphics/Text/Font/Choose/Config/Accessors.hs +2 -0
@@ 1,4 1,6 @@
{-# LANGUAGE CApiFFI #-}
+-- | APIs for retrieving configuration
+-- This is seperate from Graphics.Text.Font.Choose.Config to avoid cyclic dependencies.
module Graphics.Text.Font.Choose.Config.Accessors(
configCreate, setCurrent, current, uptodate, home, enableHome, buildFonts,
configDirs, fontDirs, configFiles, cacheDirs, fonts, rescanInterval,
M lib/Graphics/Text/Font/Choose/FontSet.hs => lib/Graphics/Text/Font/Choose/FontSet.hs +1 -0
@@ 1,4 1,5 @@
{-# LANGUAGE CApiFFI, OverloadedStrings #-}
+-- | A set of fonts to query, or resulting from a query.
module Graphics.Text.Font.Choose.FontSet(
FontSet, validFontSet, fontSetList, fontSetMatch, fontSetSort, FontFaceParser(..)
) where
M lib/Graphics/Text/Font/Choose/Internal/FFI.hs => lib/Graphics/Text/Font/Choose/Internal/FFI.hs +2 -0
@@ 1,3 1,5 @@
+-- | Utilities for writing language bindings transferring complex parameters.
+-- Encoding & decoding parameters via MessagePack.
module Graphics.Text.Font.Choose.Internal.FFI(
unpackWithErr, withMessageIO, withMessage, fromMessage, fromMessage0,
fromMessageIO0, withCString', peekCString', withForeignPtr'
M lib/Graphics/Text/Font/Choose/LangSet.hs => lib/Graphics/Text/Font/Choose/LangSet.hs +1 -0
@@ 1,4 1,5 @@
{-# LANGUAGE CApiFFI #-}
+-- | Languages supported by different fonts.
module Graphics.Text.Font.Choose.LangSet(
LangSet, LangSet'(..), module S, LangComparison(..), validLangSet, validLangSet',
cmp, has, defaultLangs, langs, normalize, langCharSet) where
M lib/Graphics/Text/Font/Choose/ObjectSet.hs => lib/Graphics/Text/Font/Choose/ObjectSet.hs +1 -0
@@ 1,3 1,4 @@
+-- | Which properties of a font do we want to read?
module Graphics.Text.Font.Choose.ObjectSet(ObjectSet) where
type ObjectSet = [String]
M lib/Graphics/Text/Font/Choose/Pattern.hs => lib/Graphics/Text/Font/Choose/Pattern.hs +2 -0
@@ 1,5 1,7 @@
{-# LANGUAGE DeriveGeneric, CApiFFI #-}
{-# LANGUAGE OverloadedStrings #-}
+-- | Dynamically-typed datastructure describing a font, whether resolved or a query.
+-- Can be parsed from CSS.
module Graphics.Text.Font.Choose.Pattern(Pattern, Pattern'(..), module M, Binding(..),
setValue, setValues, getValue, getValues, equalSubset, defaultSubstitute,
nameParse, nameUnparse, nameFormat, validPattern, validPattern',
M lib/Graphics/Text/Font/Choose/Range.hs => lib/Graphics/Text/Font/Choose/Range.hs +1 -0
@@ 1,4 1,5 @@
{-# LANGUAGE DeriveGeneric #-}
+-- | A range between 2 values.
module Graphics.Text.Font.Choose.Range(Range(..), iRange, validRange) where
import Data.MessagePack (MessagePack(..), Object(..))
M lib/Graphics/Text/Font/Choose/Result.hs => lib/Graphics/Text/Font/Choose/Result.hs +1 -0
@@ 1,3 1,4 @@
+-- | Exceptions which can be thrown by FontConfig.
module Graphics.Text.Font.Choose.Result (FcException(..), throwBool, throwNull, throwString) where
import Foreign.Ptr (Ptr, nullPtr)
M lib/Graphics/Text/Font/Choose/StrSet.hs => lib/Graphics/Text/Font/Choose/StrSet.hs +1 -0
@@ 1,3 1,4 @@
+-- | A set of strings to match.
module Graphics.Text.Font.Choose.StrSet(StrSet(..), module S, validStrSet) where
import Data.Set (Set)
M lib/Graphics/Text/Font/Choose/Value.hs => lib/Graphics/Text/Font/Choose/Value.hs +1 -0
@@ 1,5 1,6 @@
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
+-- | A dynamic type system for patterns.
module Graphics.Text.Font.Choose.Value(Value(..), validValue, ToValue(..)) where
import Linear.Matrix (M22)
M lib/Graphics/Text/Font/Choose/Weight.hs => lib/Graphics/Text/Font/Choose/Weight.hs +1 -0
@@ 1,4 1,5 @@
{-# LANGUAGE CApiFFI #-}
+-- | Convert between OpenType & FontConfig weight scales.
module Graphics.Text.Font.Choose.Weight(weightFromOpenTypeDouble,
weightToOpenTypeDouble, weightFromOpenType, weightToOpenType) where