M FreeType/FontConfig.hs => FreeType/FontConfig.hs +11 -3
@@ 2,7 2,7 @@
 module FreeType.FontConfig (ftCharIndex, ftCharSet, ftCharSetAndSpacing,
     ftQuery, ftQueryAll, ftQueryFace,
     FTFC_Instance(..), FTFC_Metrics(..), FTFC_Subpixel(..), instantiatePattern,
-    FTFC_Glyph(..), glyphForIndex) where
+    FTFC_Glyph(..), glyphForIndex, bmpAndMetricsForIndex) where
 
 import Graphics.Text.Font.Choose.CharSet (CharSet, CharSet_, thawCharSet, thawCharSet_)
 import Graphics.Text.Font.Choose.Pattern (Pattern, Pattern_, thawPattern, thawPattern_)
@@ 249,7 249,8 @@ data FTFC_Glyph a = Glyph {
     glyphFontName :: Maybe String,
     glyphImage :: a,
     glyphAdvance :: (Double, Double),
-    glyphSubpixel :: FTFC_Subpixel
+    glyphSubpixel :: FTFC_Subpixel,
+    glyphMetrics :: FT_Glyph_Metrics
 }
 
 -- | Looks up a given glyph in a `FTFC_Instance` & its underlying `FT_Face`
@@ 318,9 319,16 @@ glyphForIndex font index subpixel cb = do
             if fontPixelFixupEstimated font then fontPixelSizeFixup font else 1,
             fromIntegral (vY $ gsrAdvance glyph2') / 64 *
             if fontPixelFixupEstimated font then fontPixelSizeFixup font else 1),
-        glyphSubpixel = subpixel
+        glyphSubpixel = subpixel,
+        glyphMetrics = gsrMetrics glyph2'
     }
 
+bmpAndMetricsForIndex ::
+    FTFC_Instance -> FTFC_Subpixel -> Word32 -> IO (FT_Bitmap, FT_Glyph_Metrics)
+bmpAndMetricsForIndex inst subpixel index = do
+    glyph <- glyphForIndex inst index subpixel pure
+    return (glyphImage glyph, glyphMetrics glyph)
+
 withPtr :: Storable a => a -> (Ptr a -> IO b) -> IO a
 withPtr a cb = alloca $ \a' -> do
     poke a' a
 
M fontconfig-harfbuzz/Data/Text/Glyphize/Choose.hs => fontconfig-harfbuzz/Data/Text/Glyphize/Choose.hs +11 -6
@@ 2,22 2,27 @@ module Data.Text.Glyphize.Choose where
 
 import Data.Text.Glyphize (Font, createFace, createFontWithOptions,
                           Variation, FontOptions (..), defaultFontOptions)
-import Graphics.Text.Font.Choose (Pattern, getValue0, getValue')
+import Graphics.Text.Font.Choose (Pattern, getValue0, getValue', Value(..),
+                                normalizePattern, )
 import qualified Data.ByteString as B
 
 import System.IO.Unsafe (unsafePerformIO)
+import Data.Maybe (fromMaybe)
 
 -- Warning: file-read sideeffect.
-instantiatePattern :: Pattern -> [Variation] -> IO Font
-instantiatePattern pat variations = createFontWithOptions options face
+pattern2hbfont :: Pattern -> [Variation] -> Font
+pattern2hbfont pat variations = createFontWithOptions options face
   where
     bytes = unsafePerformIO $ B.readFile $ getValue0 "file" pat
-    face = createFace bytes $ fromMaybe 0 $ getValue' "index" pat
+    face = createFace bytes $ toEnum $ fromMaybe 0 $ getValue' "index" pat
     options = foldl value2opt defaultFontOptions $ normalizePattern pat
 
-    value2opt opts ("slant", (_, ValueInt x):_) = opts {optionSynthSlant = Just x}
+    value2opt opts ("slant", (_, ValueInt x):_) = opts {
+        optionSynthSlant = Just $ realToFrac x
+      }
     value2opt opts ("fontvariations", _:_) = opts {optionVariations = variations}
-    value2opt opts ("size", (_, ValueDouble x):_) = opts {optionPtEm = Just x}
+    value2opt opts ("size", (_, ValueDouble x):_) = opts {optionPtEm = Just $ realToFrac x}
     value2opt opts ("pixelsize", (_, ValueDouble x):_) = opts {
         optionPPEm = Just (toEnum $ fromEnum x, toEnum $ fromEnum x)
       }
+    value2opt opts _ = opts
 
M fontconfig-harfbuzz/app/Main.hs => fontconfig-harfbuzz/app/Main.hs +13 -4
@@ 5,14 5,17 @@ import Graphics.UI.GLUT
 import Graphics.GL.Core32
 
 import FreeType.Core.Base
-import FreeType.FontConfig
+import FreeType.FontConfig (instantiatePattern)
 
 import Graphics.Text.Font.Choose as Font
+import Typograffiti (makeDrawGlyphs)
+
+import Data.Text.Glyphize
+import Data.Text.Glyphize.Choose
 
 import System.Environment (getArgs)
 import System.Exit (exitFailure)
-import Data.Function (fix)
-import Control.Monad (unless)
+import Control.Monad.Except (runExceptT)
 import Data.Maybe (fromMaybe)
 
 main :: IO ()
@@ 32,9 35,15 @@ main = do
             putStrLn ("Failed to locate font " ++ show query)
             exitFailure
 
+    let buf = defaultBuffer { text = "sphinx of black quartz judge my vow" }
+    let glyphs = shape (pattern2hbfont font []) buf []
+
     ft_With_FreeType $ \ft -> do
         inst <- instantiatePattern ft font (fromMaybe 12 $ getValue' "size" font, 20)
-        let text = shape 
+        res <- runExceptT $ do
+--            render <- makeDrawGlyphs
+            allocAtlas ?? $ map (fst . codepoint) glyphs
+            return atlas
 
         displayCallback $= do
             clear [ ColorBuffer ]
 
M fontconfig-harfbuzz/fontconfig-harfbuzz.cabal => fontconfig-harfbuzz/fontconfig-harfbuzz.cabal +5 -4
@@ 48,7 48,7 @@ cabal-version:       >=1.10
 
 library
   -- Modules exported by the library.
-  -- exposed-modules:
+  exposed-modules:      Data.Text.Glyphize.Choose
 
   -- Modules included in this library but not exported.
   -- other-modules:
@@ 57,7 57,7 @@ library
   -- other-extensions:
 
   -- Other library packages from which modules are imported.
-  build-depends:       base >=4.12 && <4.13, fontconfig-pure, harfbuzz-pure
+  build-depends:       base >=4.12 && <4.13, fontconfig-pure, harfbuzz-pure, bytestring
 
   -- Directories containing source files.
   hs-source-dirs:      .
@@ 77,8 77,9 @@ executable fontconfig-harfbuzz
   -- other-extensions:
 
   -- Other library packages from which modules are imported.
-  build-depends:       base >=4.12 && <4.13, typograffiti>=0.2, text, harfbuzz,
-                        GLUT >= 2.7, gl, mtl, fontconfig-pure, freetype2
+  build-depends:       base >=4.12 && <4.13, typograffiti>=0.2, text,
+                        harfbuzz-pure, GLUT >= 2.7, gl, mtl, fontconfig-pure,
+                        freetype2, fontconfig-harfbuzz
 
   -- Directories containing source files.
   hs-source-dirs:      app
 
M fontconfig-pure.cabal => fontconfig-pure.cabal +2 -2
@@ 10,13 10,13 @@ name:                fontconfig-pure
 -- PVP summary:      +-+------- breaking API changes
 --                   | | +----- non-breaking API additions
 --                   | | | +--- code changes with no API change
-version:             0.1.0.0
+version:             0.1.1.1
 
 -- A short (one-line) description of the package.
 synopsis:            Pure-functional language bindings to FontConfig
 
 -- A longer description of the package.
--- description:
+description:         Resolves font descriptions to font libraries, including ones installed on your freedesktop (Linux or BSD system).
 
 -- URL for the project homepage or repository.
 homepage:            https://www.freedesktop.org/wiki/Software/fontconfig/