M fontconfig-pure.cabal => fontconfig-pure.cabal +2 -1
@@ 69,7 69,8 @@ library
Graphics.Text.Font.Choose.Pattern, Graphics.Text.Font.Choose.FontSet,
Graphics.Text.Font.Choose.Config, Graphics.Text.Font.Choose.Result,
Graphics.Text.Font.Choose.Internal.FFI, FreeType.FontConfig,
- Graphics.Text.Font.Choose.Config.Accessors, Graphics.Text.Font.Choose.Weight
+ Graphics.Text.Font.Choose.Config.Accessors, Graphics.Text.Font.Choose.Weight,
+ Graphics.Text.Font.Choose
c-sources: cbits/cmp.c, cbits/transcode.c, cbits/fontconfig-wrap.c
include-dirs: cbits
M lib/FreeType/FontConfig.hs => lib/FreeType/FontConfig.hs +26 -23
@@ 1,5 1,8 @@
{-# LANGUAGE CApiFFI, OverloadedStrings #-}
-module FreeType.FontConfig where
+module FreeType.FontConfig(charIndex,
+ fontCharSet, fontCharSetAndSpacing, fontQuery, fontQueryAll, fontQueryFace,
+ FTFC_Instance(..), FTFC_Metrics(..), FTFC_Subpixel(..), FTFC_Glyph(..),
+ instantiatePattern, glyphForIndex, bmpAndMetricsForIndex) where
--import FreeType.Core.Base (FT_Face)
@@ 60,8 63,8 @@ fontQueryFace a b c = fromMessage0 $ flip withCString' b $ \b' -> fcFreeTypeQuer
foreign import capi "fontconfig-wrap.h" fcFreeTypeQueryFace ::
FT_Face -> CString -> Int -> Ptr Int -> CString
-
- ------
+
+------
--- Transliterated from FcFt
--- https://codeberg.org/dnkl/fcft/
--- Untested
@@ 309,30 312,30 @@ m22toFt (V2 (V2 xx xy) (V2 yx yy)) = FT_Matrix {
-- Taken from FreeType language bindings,
-- but converted to constants rather than pattern synonyms.
-ft_LOAD_DEFAULT, ft_LOAD_NO_SCALE, ft_LOAD_NO_HINTING, ft_LOAD_RENDER,
+ft_LOAD_DEFAULT, {-ft_LOAD_NO_SCALE,-} ft_LOAD_NO_HINTING, {-ft_LOAD_RENDER,
ft_LOAD_NO_BITMAP, ft_LOAD_VERTICAL_LAYOUT, ft_LOAD_FORCE_AUTOHINT,
ft_LOAD_CROP_BITMAP, ft_LOAD_PEDANTIC, ft_LOAD_IGNORE_GLOBAL_ADVANCE_WIDTH,
- ft_LOAD_NO_RECURSE, ft_LOAD_IGNORE_TRANSFORM, ft_LOAD_MONOCHROME,
- ft_LOAD_LINEAR_DESIGN, ft_LOAD_NO_AUTOHINT, ft_LOAD_COLOR,
- ft_LOAD_COMPUTE_METRICS, ft_LOAD_BITMAP_METRICS_ONLY :: Int
+ ft_LOAD_NO_RECURSE, ft_LOAD_IGNORE_TRANSFORM,-} ft_LOAD_MONOCHROME,
+ {-ft_LOAD_LINEAR_DESIGN, ft_LOAD_NO_AUTOHINT,-} ft_LOAD_COLOR{-,
+ ft_LOAD_COMPUTE_METRICS, ft_LOAD_BITMAP_METRICS_ONLY-} :: Int
ft_LOAD_DEFAULT = 0
-ft_LOAD_NO_SCALE = 1
+--ft_LOAD_NO_SCALE = 1
ft_LOAD_NO_HINTING = 2
-ft_LOAD_RENDER = 4
-ft_LOAD_NO_BITMAP = 8
-ft_LOAD_VERTICAL_LAYOUT = 16
-ft_LOAD_FORCE_AUTOHINT = 32
-ft_LOAD_CROP_BITMAP = 64
-ft_LOAD_PEDANTIC = 128
-ft_LOAD_IGNORE_GLOBAL_ADVANCE_WIDTH = 512
-ft_LOAD_NO_RECURSE = 1024
-ft_LOAD_IGNORE_TRANSFORM = 2048
+--ft_LOAD_RENDER = 4
+--ft_LOAD_NO_BITMAP = 8
+--ft_LOAD_VERTICAL_LAYOUT = 16
+--ft_LOAD_FORCE_AUTOHINT = 32
+--ft_LOAD_CROP_BITMAP = 64
+--ft_LOAD_PEDANTIC = 128
+--ft_LOAD_IGNORE_GLOBAL_ADVANCE_WIDTH = 512
+--ft_LOAD_NO_RECURSE = 1024
+--ft_LOAD_IGNORE_TRANSFORM = 2048
ft_LOAD_MONOCHROME = 4096
-ft_LOAD_LINEAR_DESIGN = 8192
-ft_LOAD_NO_AUTOHINT = 32768
+--ft_LOAD_LINEAR_DESIGN = 8192
+--ft_LOAD_NO_AUTOHINT = 32768
ft_LOAD_COLOR = 1048576
-ft_LOAD_COMPUTE_METRICS = 2097152
-ft_LOAD_BITMAP_METRICS_ONLY = 4194304
+--ft_LOAD_COMPUTE_METRICS = 2097152
+--ft_LOAD_BITMAP_METRICS_ONLY = 4194304
ft_LOAD_TARGET_NORMAL, ft_LOAD_TARGET_LIGHT, ft_LOAD_TARGET_MONO,
ft_LOAD_TARGET_LCD, ft_LOAD_TARGET_LCD_V :: Int
@@ 342,10 345,10 @@ ft_LOAD_TARGET_MONO = 131072
ft_LOAD_TARGET_LCD = 196608
ft_LOAD_TARGET_LCD_V = 262144
-ft_RENDER_MODE_NORMAL, ft_RENDER_MODE_LIGHT, ft_RENDER_MODE_MONO,
+ft_RENDER_MODE_NORMAL, {-ft_RENDER_MODE_LIGHT,-} ft_RENDER_MODE_MONO,
ft_RENDER_MODE_LCD, ft_RENDER_MODE_LCD_V :: Int
ft_RENDER_MODE_NORMAL = 0
-ft_RENDER_MODE_LIGHT = 1
+--ft_RENDER_MODE_LIGHT = 1
ft_RENDER_MODE_MONO = 2
ft_RENDER_MODE_LCD = 3
ft_RENDER_MODE_LCD_V = 4
A lib/Graphics/Text/Font/Choose.hs => lib/Graphics/Text/Font/Choose.hs +28 -0
@@ 0,0 1,28 @@
+module Graphics.Text.Font.Choose(
+ module Graphics.Text.Font.Choose.Config.Accessors, Config', fini, version,
+ initLoadConfig, initLoadConfigAndFonts, initFonts, reinit, bringUptoDate,
+ CharSet, ord, chr, parseCharSet, CharSet'(..),
+ module Graphics.Text.Font.Choose.FontSet,
+ module Graphics.Text.Font.Choose.LangSet,
+ module Graphics.Text.Font.Choose.ObjectSet,
+ Pattern, Pattern'(..), Binding(..),
+ setValue, setValues, getValue, getValues, equalSubset, defaultSubstitute,
+ nameParse, nameUnparse, nameFormat,
+ module Graphics.Text.Font.Choose.Range,
+ FcException(..), StrSet(..),
+ module Graphics.Text.Font.Choose.Value,
+ module Graphics.Text.Font.Choose.Weight
+ ) where
+
+import Graphics.Text.Font.Choose.Config.Accessors
+import Graphics.Text.Font.Choose.Config
+import Graphics.Text.Font.Choose.CharSet
+import Graphics.Text.Font.Choose.FontSet
+import Graphics.Text.Font.Choose.LangSet
+import Graphics.Text.Font.Choose.ObjectSet
+import Graphics.Text.Font.Choose.Pattern
+import Graphics.Text.Font.Choose.Range
+import Graphics.Text.Font.Choose.Result
+import Graphics.Text.Font.Choose.StrSet
+import Graphics.Text.Font.Choose.Value
+import Graphics.Text.Font.Choose.Weight
M lib/Graphics/Text/Font/Choose/CharSet.hs => lib/Graphics/Text/Font/Choose/CharSet.hs +3 -2
@@ 1,9 1,10 @@
-module Graphics.Text.Font.Choose.CharSet where
+module Graphics.Text.Font.Choose.CharSet(
+ CharSet, ord, chr, module IntSet, parseCharSet, CharSet'(..)) where
import Data.IntSet (IntSet, union)
import qualified Data.IntSet as IntSet
-import Data.Char (isHexDigit)
+import Data.Char (isHexDigit, ord, chr)
import Numeric (readHex)
import Data.MessagePack (MessagePack(..))
M lib/Graphics/Text/Font/Choose/Config.hs => lib/Graphics/Text/Font/Choose/Config.hs +6 -3
@@ 1,5 1,8 @@
{-# LANGUAGE CApiFFI #-}
-module Graphics.Text.Font.Choose.Config where
+module Graphics.Text.Font.Choose.Config(Config', fini, version,
+ initLoadConfig, initLoadConfigAndFonts, initFonts, reinit, bringUptoDate,
+ -- For the sake of Graphics.Font.Choose.Config.Accessors
+ Config, fcConfigDestroy) where
import Foreign.Ptr (Ptr, FunPtr)
import Foreign.ForeignPtr (ForeignPtr, newForeignPtr)
@@ 17,8 20,8 @@ initLoadConfig = newForeignPtr fcConfigDestroy =<< throwNull =<< fcInitLoadConfi
initLoadConfigAndFonts :: IO Config
initLoadConfigAndFonts = newForeignPtr fcConfigDestroy =<< throwNull =<< fcInitLoadConfigAndFonts -- FIXME: What's proper memory-management here?
-init :: IO ()
-init = throwBool =<< fcInit
+initFonts :: IO ()
+initFonts = throwBool =<< fcInit
foreign import capi "fontconfig/fontconfig.h FcFini" fini :: IO ()
foreign import capi "fontconfig/fontconfig.h FcGetVersion" version :: Int
reinit :: IO ()
M lib/Graphics/Text/Font/Choose/Config/Accessors.hs => lib/Graphics/Text/Font/Choose/Config/Accessors.hs +7 -1
@@ 1,5 1,11 @@
{-# LANGUAGE CApiFFI #-}
-module Graphics.Text.Font.Choose.Config.Accessors where
+module Graphics.Text.Font.Choose.Config.Accessors(
+ configCreate, setCurrent, current, uptodate, home, enableHome, buildFonts,
+ configDirs, fontDirs, configFiles, cacheDirs, fonts, rescanInterval,
+ setRescanInterval, appFontAddFile, appFontAddDir, appFontClear, substituteWithPat,
+ fontMatch, fontSort, fontRenderPrepare, fontList, filename, parseAndLoad,
+ parseAndLoadFromMemory, sysroot, setSysroot, SetName(..), MatchKind(..)
+ ) where
import Graphics.Text.Font.Choose.Config
import Graphics.Text.Font.Choose.FontSet
M lib/Graphics/Text/Font/Choose/FontSet.hs => lib/Graphics/Text/Font/Choose/FontSet.hs +3 -2
@@ 1,7 1,8 @@
{-# LANGUAGE CApiFFI, OverloadedStrings #-}
-module Graphics.Text.Font.Choose.FontSet where
+module Graphics.Text.Font.Choose.FontSet(
+ FontSet, fontSetList, fontSetMatch, fontSetSort, FontFaceParser(..)) where
-import Graphics.Text.Font.Choose.Pattern
+import Graphics.Text.Font.Choose.Pattern hiding (map)
import Graphics.Text.Font.Choose.Config
import Graphics.Text.Font.Choose.ObjectSet
import Graphics.Text.Font.Choose.CharSet
M lib/Graphics/Text/Font/Choose/Internal/FFI.hs => lib/Graphics/Text/Font/Choose/Internal/FFI.hs +4 -1
@@ 1,4 1,7 @@
-module Graphics.Text.Font.Choose.Internal.FFI where
+module Graphics.Text.Font.Choose.Internal.FFI(
+ unpackWithErr, withMessageIO, withMessage, fromMessage, fromMessage0,
+ fromMessageIO0, withCString', peekCString', withForeignPtr'
+ ) where
import Data.MessagePack (MessagePack(fromObject), pack, unpack, Object(ObjectStr))
import Foreign.C.String (CString, withCString, peekCString)
M lib/Graphics/Text/Font/Choose/LangSet.hs => lib/Graphics/Text/Font/Choose/LangSet.hs +3 -1
@@ 1,5 1,7 @@
{-# LANGUAGE CApiFFI #-}
-module Graphics.Text.Font.Choose.LangSet where
+module Graphics.Text.Font.Choose.LangSet(
+ LangSet, LangSet'(..), module S, LangComparison(..),
+ cmp, has, defaultLangs, langs, normalize, langCharSet) where
import Data.Set (Set)
import qualified Data.Set as S
M lib/Graphics/Text/Font/Choose/ObjectSet.hs => lib/Graphics/Text/Font/Choose/ObjectSet.hs +1 -1
@@ 1,4 1,4 @@
-module Graphics.Text.Font.Choose.ObjectSet where
+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 +5 -1
@@ 1,6 1,10 @@
{-# LANGUAGE DeriveGeneric, CApiFFI #-}
{-# LANGUAGE OverloadedStrings #-}
-module Graphics.Text.Font.Choose.Pattern where
+module Graphics.Text.Font.Choose.Pattern(Pattern, Pattern'(..), module M, Binding(..),
+ setValue, setValues, getValue, getValues, equalSubset, defaultSubstitute,
+ nameParse, nameUnparse, nameFormat,
+ -- For Graphics.Text.Font.Choose.FontSet
+ parseFontStretch, parseFontWeight, parseFontFeatures, parseFontVars) where
import Data.Map as M
import Data.MessagePack (MessagePack(..), Object(..))
M lib/Graphics/Text/Font/Choose/Range.hs => lib/Graphics/Text/Font/Choose/Range.hs +1 -1
@@ 1,4 1,4 @@
-module Graphics.Text.Font.Choose.Range where
+module Graphics.Text.Font.Choose.Range(Range(..), iRange) where
import Data.MessagePack (MessagePack(..), Object(..))
import qualified Data.Vector as V
M lib/Graphics/Text/Font/Choose/StrSet.hs => lib/Graphics/Text/Font/Choose/StrSet.hs +1 -1
@@ 1,4 1,4 @@
-module Graphics.Text.Font.Choose.StrSet where
+module Graphics.Text.Font.Choose.StrSet(StrSet(..), module S) where
import Data.Set (Set)
import qualified Data.Set as S
M lib/Graphics/Text/Font/Choose/Value.hs => lib/Graphics/Text/Font/Choose/Value.hs +1 -1
@@ 1,5 1,5 @@
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
-module Graphics.Text.Font.Choose.Value where
+module Graphics.Text.Font.Choose.Value(Value(..), ToValue(..)) where
import Linear.Matrix (M22)
import Linear.V2 (V2(..))
M lib/Graphics/Text/Font/Choose/Weight.hs => lib/Graphics/Text/Font/Choose/Weight.hs +2 -1
@@ 1,5 1,6 @@
{-# LANGUAGE CApiFFI #-}
-module Graphics.Text.Font.Choose.Weight where
+module Graphics.Text.Font.Choose.Weight(weightFromOpenTypeDouble,
+ weightToOpenTypeDouble, weightFromOpenType, weightToOpenType) where
foreign import capi "fontconfig/fontconfig.h FcWeightFromOpenTypeDouble"
weightFromOpenTypeDouble :: Double -> Double