~alcinnz/harfbuzz-pure

2546e12708a4def41cfbb36f35666ca2d702b8c7 — Adrian Cochrane 1 year, 2 months ago af0c75f
Implement more typeclasses & ensure empty input don't throw errors.
4 files changed, 10 insertions(+), 7 deletions(-)

M Data/Text/Glyphize.hs
M Data/Text/Glyphize/Buffer.hs
M Data/Text/Glyphize/Font.hs
M harfbuzz-pure.cabal
M Data/Text/Glyphize.hs => Data/Text/Glyphize.hs +2 -0
@@ 1,3 1,4 @@
{-# LANGUAGE OverloadedStrings #-}
-- | HarfBuzz is a text shaping library.
-- Using the HarfBuzz library allows programs to convert a sequence of
-- Unicode input into properly formatted and positioned glyph output —


@@ 46,6 47,7 @@ import Foreign.Marshal.Array (withArrayLen)
-- If two `Feature`s have the same tag but overlapping ranges
-- the value of the `Feature` with the higher index takes precedance.
shape :: Font -> Buffer -> [Feature] -> [(GlyphInfo, GlyphPos)]
shape _ Buffer {text = ""} _ = []
shape font buffer features = unsafePerformIO $ withForeignPtr font $ \font' ->
    withBuffer buffer $ \buffer' -> withArrayLen features $ \len features' -> do
        hb_shape font' buffer' features' $ toEnum len

M Data/Text/Glyphize/Buffer.hs => Data/Text/Glyphize/Buffer.hs +1 -0
@@ 323,6 323,7 @@ withBuffer buf cb = withNewBuffer $ \buf' -> bufferWithText buf' (text buf) $ do
        (Just ContentTypeUnicode, Nothing, _, _) -> hb_buffer_guess_segment_properties buf'
        (Just ContentTypeUnicode, _, Nothing, _) -> hb_buffer_guess_segment_properties buf'
        (Just ContentTypeUnicode, _, _, Nothing) -> hb_buffer_guess_segment_properties buf'
        _ -> return ()

    throwFalse $ hb_buffer_allocation_successful buf'
    cb buf'

M Data/Text/Glyphize/Font.hs => Data/Text/Glyphize/Font.hs +6 -6
@@ 44,7 44,7 @@ data Feature = Feature {
    -- ^ The cluster to start applying this feature setting (inclusive).
    featEnd :: Word
    -- ^ The cluster to end applying this feature setting (exclusive).
} deriving (Read, Show, Generic)
} deriving (Read, Show, Generic, Ord, Eq)
instance GStorable Feature
-- | Parses a string into a hb_feature_t.
-- The format for specifying feature strings follows. All valid CSS


@@ 80,7 80,7 @@ data Variation = Variation {
    -- ^ Tag of the variation-axis name. Use `varTag` to decode as an ASCII string.
    varValue :: Float
    -- ^ Value of the variation axis.
} deriving (Read, Show, Generic)
} deriving (Read, Show, Generic, Ord, Eq)
instance GStorable Variation
-- | Parses a string into a hb_variation_t.
-- The format for specifying variation settings follows.


@@ 238,7 238,7 @@ data FaceOptions = FaceOptions {
    faceOptUPEm :: Maybe Word
    -- ^ Sets the units-per-em (upem) for a newly-created `Face` object
    -- to the specified value.
}
} deriving (Read, Show, Ord, Eq)
-- | `FaceOptions` which has no effect on the newly-created `Face` object.
defaultFaceOptions = FaceOptions Nothing Nothing Nothing
-- | Internal utility to apply the given `FaceOptions` to a `Face`.


@@ 451,7 451,7 @@ data GlyphExtents = GlyphExtents {
    -- ^ Distance from the left extremum of the glyph to the right extremum.
    height :: Word32
    -- ^ Distance from the top extremum of the glyph to the right extremum.
} deriving (Generic)
} deriving (Generic, Read, Show, Ord, Eq)
instance GStorable GlyphExtents
-- | Fetches the `GlyphExtents` data for a glyph ID in the specified `Font`.
fontGlyphExtents :: Font -> Word32 -> Maybe GlyphExtents


@@ 754,7 754,7 @@ data FontExtents = FontExtents {
    -- ^ The depth of typographic descenders.
    lineGap :: Int32
    -- ^ The suggested line-spacing gap.
} deriving (Generic)
} deriving (Generic, Read, Show, Ord, Eq)
instance GStorable FontExtents
-- | Fetches the extents for a font in a text segment of the specified direction.
-- Calls the appropriate direction-specific variant (horizontal or vertical)


@@ 831,7 831,7 @@ data FontOptions = FontOptions {
    -- Axes not included in coords will be effectively set to their default values.
    optionVarNamedInstance :: Maybe Word
    -- ^ Sets design coords of a font from a named instance index.
}
} deriving (Show, Ord, Eq)
-- | `FontOptions` which has no effect on the newly-created `Font`.
defaultFontOptions = FontOptions {
    optionPPEm = Nothing, optionPtEm = Nothing, optionScale = Nothing,

M harfbuzz-pure.cabal => harfbuzz-pure.cabal +1 -1
@@ 10,7 10,7 @@ name:                harfbuzz-pure
-- PVP summary:      +-+------- breaking API changes
--                   | | +----- non-breaking API additions
--                   | | | +--- code changes with no API change
version:             1.0.1.0
version:             1.0.2.0

-- A short (one-line) description of the package.
synopsis:            Pure-functional Harfbuzz language bindings