Dump hmtx

This commit is contained in:
Eugen Wissner 2023-11-18 04:40:17 +01:00
parent 344467b850
commit 9a11ff5dd4
3 changed files with 63 additions and 24 deletions

View File

@ -15,7 +15,7 @@ import qualified Data.Text.Lazy as Text.Lazy
import qualified Data.Text.Lazy.IO as Text.Lazy import qualified Data.Text.Lazy.IO as Text.Lazy
import qualified Data.Text.Encoding as Text import qualified Data.Text.Encoding as Text
import GHC.Records (HasField(..)) import GHC.Records (HasField(..))
import Graphics.Fountainhead.Dumper (dumpTrueType) import Graphics.Fountainhead.Dumper (DumpError(..), dumpTrueType)
-- TODO: kern table since format 1. -- TODO: kern table since format 1.
-- For details on subtable format see examples in TrueType reference. -- For details on subtable format see examples in TrueType reference.
import Graphics.Fountainhead.Parser import Graphics.Fountainhead.Parser
@ -40,8 +40,12 @@ fontMain fontFile = do
ttfContents <- ByteString.readFile fontFile ttfContents <- ByteString.readFile fontFile
case dumpTrueType ttfContents fontFile of case dumpTrueType ttfContents fontFile of
(Right fontDump) -> Text.Lazy.putStrLn $ Text.Builder.toLazyText fontDump Right fontDump -> Text.Lazy.putStrLn $ Text.Builder.toLazyText fontDump
Left e -> putStr (Megaparsec.errorBundlePretty e) Left e
| DumpParseError bundle <- e -> putStr
$ Megaparsec.errorBundlePretty bundle
| DumpRequiredTableMissingError tableName <- e -> putStr
$ "Required table " <> tableName <> " is missing."
main :: IO () main :: IO ()
main = do main = do

View File

@ -3,6 +3,7 @@
obtain one at https://mozilla.org/MPL/2.0/. -} obtain one at https://mozilla.org/MPL/2.0/. -}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
@ -10,14 +11,16 @@
-- | Outputs information about a font as text. -- | Outputs information about a font as text.
module Graphics.Fountainhead.Dumper module Graphics.Fountainhead.Dumper
( ParseErrorOrDump ( DumpError(..)
, dumpCmap , dumpCmap
, dumpHead , dumpHead
, dumpHmtx
, dumpTrueType , dumpTrueType
, dumpOffsetTable , dumpOffsetTable
) where ) where
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as Char8
import Data.Int (Int64) import Data.Int (Int64)
import Data.Word (Word16) import Data.Word (Word16)
import qualified Data.IntMap as IntMap import qualified Data.IntMap as IntMap
@ -35,12 +38,14 @@ import Graphics.Fountainhead.TrueType
, FontDirectionHint(..) , FontDirectionHint(..)
, HeadTable(..) , HeadTable(..)
, HheaTable(..) , HheaTable(..)
, HmtxTable(..)
, OffsetSubtable(..) , OffsetSubtable(..)
, TableDirectory(..) , TableDirectory(..)
, CmapEncoding(..) , CmapEncoding(..)
, CmapSubtable(..) , CmapSubtable(..)
, CmapFormat4Table(..) , CmapFormat4Table(..)
, FontStyle(..) , FontStyle(..)
, LongHorMetric(..)
) )
import qualified Text.Megaparsec as Megaparsec import qualified Text.Megaparsec as Megaparsec
import Graphics.Fountainhead.Parser import Graphics.Fountainhead.Parser
@ -49,15 +54,18 @@ import Graphics.Fountainhead.Parser
, cmapTableP , cmapTableP
, headTableP , headTableP
, hheaTableP , hheaTableP
, hmtxTableP
) )
import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch) import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch)
import Data.Foldable (Foldable(..)) import Data.Foldable (Foldable(..), find)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Time (LocalTime(..), NominalDiffTime, diffLocalTime, midnight) import Data.Time (LocalTime(..), NominalDiffTime, diffLocalTime, midnight)
import Data.Bits (Bits(..)) import Data.Bits (Bits(..))
import Data.Bifunctor (Bifunctor(first))
type ParseErrorOrDump data DumpError
= Either (Megaparsec.ParseErrorBundle ByteString Void) Text.Builder.Builder = DumpParseError (Megaparsec.ParseErrorBundle ByteString Void)
| DumpRequiredTableMissingError String
paddedHexadecimal :: Integral a => a -> Text.Builder.Builder paddedHexadecimal :: Integral a => a -> Text.Builder.Builder
paddedHexadecimal = ("0x" <>) paddedHexadecimal = ("0x" <>)
@ -115,9 +123,27 @@ dumpFixed32 (Fixed32 word)
<> Text.Builder.singleton '.' <> Text.Builder.singleton '.'
<> Text.Builder.decimal (word .&. 0xff00) <> Text.Builder.decimal (word .&. 0xff00)
dumpHmtx :: HmtxTable -> Text.Builder.Builder
dumpHmtx HmtxTable{..} =
let caption = dumpCaption "'hmtx' Table - Horizontal Metrics"
lastAccumulator = foldl' dumpHMetric (0 :: Int, caption) hMetrics
in snd $ foldl' dumpLeftSideBear lastAccumulator leftSideBearing
where
dumpLeftSideBear (index, accumulator) leftSideBearing' =
let withNewLine = dumpIndex index <> ". LSbear: "
<> justifyNumber 4 leftSideBearing' <> newlineBuilder
in (succ index, accumulator <> withNewLine)
dumpHMetric (index, accumulator) metric =
let LongHorMetric{ leftSideBearing = leftSideBearing', ..} = metric
withNewLine = dumpIndex index <> ". advWid: "
<> justifyNumber 4 advanceWidth <> ", LSBear: "
<> justifyNumber 4 leftSideBearing' <> newlineBuilder
in (succ index, accumulator <> withNewLine)
dumpIndex = justifyNumber 12
dumpHhea :: HheaTable -> Text.Builder.Builder dumpHhea :: HheaTable -> Text.Builder.Builder
dumpHhea HheaTable{..} dumpHhea HheaTable{..}
= dumpCaption "'hhea' Table - Font Header" = dumpCaption "'hhea' Table - Horizontal Header"
<> " 'hhea' version: " <> dumpFixed32 version <> newlineBuilder <> " 'hhea' version: " <> dumpFixed32 version <> newlineBuilder
<> " yAscender: " <> Text.Builder.decimal ascent <> newlineBuilder <> " yAscender: " <> Text.Builder.decimal ascent <> newlineBuilder
<> " yDescender: " <> Text.Builder.decimal descent <> newlineBuilder <> " yDescender: " <> Text.Builder.decimal descent <> newlineBuilder
@ -280,25 +306,34 @@ dumpCmap CmapTable{..}
dumpTables dumpTables
:: Megaparsec.State ByteString Void :: Megaparsec.State ByteString Void
-> FontDirectory -> FontDirectory
-> ParseErrorOrDump -> Either DumpError Text.Builder.Builder
dumpTables processedState directory@FontDirectory{..} dumpTables processedState directory@FontDirectory{..} =
= foldl' go (Right $ dumpOffsetTable directory) tableDirectory findRequired "hhea" hheaTableP >>= traverseDirectory
where where
go :: ParseErrorOrDump -> TableDirectory -> ParseErrorOrDump traverseDirectory parsedHhea =
go (Left accumulator) _ = Left accumulator let initial = Right $ dumpOffsetTable directory
go (Right accumulator) tableEntry in foldl' (go parsedHhea) initial tableDirectory
= maybe (Right accumulator) (concatDump accumulator) findRequired tableName parser =
$ dumpSubTable tableEntry let missingError = Left $ DumpRequiredTableMissingError tableName
parseRequired tableEntry = parseTable tableEntry parser processedState
in maybe missingError (first DumpParseError . parseRequired)
$ find ((== Char8.pack tableName) . getField @"tag") tableDirectory
go _ (Left accumulator) _ = Left accumulator
go hheaTable (Right accumulator) tableEntry
= maybe (Right accumulator) (concatDump accumulator . first DumpParseError)
$ dumpSubTable hheaTable tableEntry
concatDump accumulator builderDump = ((accumulator <> newlineBuilder) <>) concatDump accumulator builderDump = ((accumulator <> newlineBuilder) <>)
<$> builderDump <$> builderDump
dumpSubTable tableEntry = dumpSubTable hheaTable@HheaTable{ numOfLongHorMetrics } tableEntry =
case getField @"tag" tableEntry of case getField @"tag" tableEntry of
"cmap" -> Just $ dumpCmap <$> parseTable tableEntry cmapTableP processedState "cmap" -> Just $ dumpCmap <$> parseTable tableEntry cmapTableP processedState
"head" -> Just $ dumpHead <$> parseTable tableEntry headTableP processedState "head" -> Just $ dumpHead <$> parseTable tableEntry headTableP processedState
"hhea" -> Just $ dumpHhea <$> parseTable tableEntry hheaTableP processedState "hhea" -> Just $ Right $ dumpHhea hheaTable
"hmtx" -> Just $ dumpHmtx
<$> parseTable tableEntry (hmtxTableP numOfLongHorMetrics) processedState
_ -> Nothing _ -> Nothing
dumpTrueType :: ByteString -> FilePath -> ParseErrorOrDump dumpTrueType :: ByteString -> FilePath -> Either DumpError Text.Builder.Builder
dumpTrueType ttfContents fontFile = dumpTrueType ttfContents fontFile =
let initialState = Megaparsec.State let initialState = Megaparsec.State
{ stateInput = ttfContents { stateInput = ttfContents
@ -314,4 +349,4 @@ dumpTrueType ttfContents fontFile =
} }
(processedState, initialResult) = Megaparsec.runParser' fontDirectoryP initialState (processedState, initialResult) = Megaparsec.runParser' fontDirectoryP initialState
in initialResult >>= dumpTables processedState in first DumpParseError initialResult >>= dumpTables processedState

View File

@ -337,9 +337,9 @@ longHorMetricP = LongHorMetric
<$> Megaparsec.Binary.word16be <$> Megaparsec.Binary.word16be
<*> Megaparsec.Binary.int16be <*> Megaparsec.Binary.int16be
hmtxTableP :: Int -> Parser HmtxTable hmtxTableP :: Word16 -> Parser HmtxTable
hmtxTableP numOfLongHorMetrics = HmtxTable hmtxTableP numOfLongHorMetrics = HmtxTable
<$> countP numOfLongHorMetrics longHorMetricP <$> countP (fromIntegral numOfLongHorMetrics) longHorMetricP
<*> Megaparsec.many Megaparsec.Binary.int16be <*> Megaparsec.many Megaparsec.Binary.int16be
-- * Glyph name and PostScript font table -- * Glyph name and PostScript font table
@ -928,7 +928,7 @@ parseTable
-> Parser a -> Parser a
-> Megaparsec.State ByteString Void -> Megaparsec.State ByteString Void
-> Either (Megaparsec.ParseErrorBundle ByteString Void) a -> Either (Megaparsec.ParseErrorBundle ByteString Void) a
parseTable TableDirectory{ offset, length } parser state = snd parseTable TableDirectory{ offset, length = length' } parser state = snd
$ Megaparsec.runParser' parser $ Megaparsec.runParser' parser
$ state $ state
{ Megaparsec.stateInput = stateInput { Megaparsec.stateInput = stateInput
@ -940,7 +940,7 @@ parseTable TableDirectory{ offset, length } parser state = snd
} }
where where
posState = Megaparsec.statePosState state posState = Megaparsec.statePosState state
stateInput = ByteString.take length stateInput = ByteString.take length'
$ ByteString.drop (offset - Megaparsec.stateOffset state) $ ByteString.drop (offset - Megaparsec.stateOffset state)
$ Megaparsec.stateInput state $ Megaparsec.stateInput state
stateOffset = offset stateOffset = offset