Dump the loca table

This commit is contained in:
Eugen Wissner 2023-11-19 09:42:29 +01:00
parent 9a11ff5dd4
commit cda2a2a446
3 changed files with 76 additions and 18 deletions

View File

@ -3,7 +3,6 @@
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 #-}
@ -15,6 +14,8 @@ module Graphics.Fountainhead.Dumper
, dumpCmap , dumpCmap
, dumpHead , dumpHead
, dumpHmtx , dumpHmtx
, dumpHhea
, dumpLoca
, dumpTrueType , dumpTrueType
, dumpOffsetTable , dumpOffsetTable
) where ) where
@ -22,7 +23,7 @@ module Graphics.Fountainhead.Dumper
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as Char8 import qualified Data.ByteString.Char8 as Char8
import Data.Int (Int64) import Data.Int (Int64)
import Data.Word (Word16) import Data.Word (Word16, Word32)
import qualified Data.IntMap as IntMap import qualified Data.IntMap as IntMap
import qualified Data.Text.Encoding as Text import qualified Data.Text.Encoding as Text
import qualified Data.Text.Lazy as Text.Lazy import qualified Data.Text.Lazy as Text.Lazy
@ -46,6 +47,8 @@ import Graphics.Fountainhead.TrueType
, CmapFormat4Table(..) , CmapFormat4Table(..)
, FontStyle(..) , FontStyle(..)
, LongHorMetric(..) , LongHorMetric(..)
, LocaTable(..)
, IndexToLocFormat(..)
) )
import qualified Text.Megaparsec as Megaparsec import qualified Text.Megaparsec as Megaparsec
import Graphics.Fountainhead.Parser import Graphics.Fountainhead.Parser
@ -55,6 +58,7 @@ import Graphics.Fountainhead.Parser
, headTableP , headTableP
, hheaTableP , hheaTableP
, hmtxTableP , hmtxTableP
, locaTableP
) )
import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch) import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch)
import Data.Foldable (Foldable(..), find) import Data.Foldable (Foldable(..), find)
@ -67,6 +71,11 @@ data DumpError
= DumpParseError (Megaparsec.ParseErrorBundle ByteString Void) = DumpParseError (Megaparsec.ParseErrorBundle ByteString Void)
| DumpRequiredTableMissingError String | DumpRequiredTableMissingError String
data RequiredTables = RequiredTables
{ hheaTable :: HheaTable
, headTable :: HeadTable
} deriving (Eq, Show)
paddedHexadecimal :: Integral a => a -> Text.Builder.Builder paddedHexadecimal :: Integral a => a -> Text.Builder.Builder
paddedHexadecimal = ("0x" <>) paddedHexadecimal = ("0x" <>)
. Text.Builder.fromLazyText . Text.Builder.fromLazyText
@ -180,9 +189,13 @@ dumpHead HeadTable{..}
<> " macStyle bits: " <> "0x" <> dumpFontStyle macStyle <> newlineBuilder <> " macStyle bits: " <> "0x" <> dumpFontStyle macStyle <> newlineBuilder
<> " lowestRecPPEM " <> Text.Builder.decimal lowestRecPPEM <> newlineBuilder <> " lowestRecPPEM " <> Text.Builder.decimal lowestRecPPEM <> newlineBuilder
<> " fontDirectionHint " <> dumpFontDirectionHint fontDirectionHint <> newlineBuilder <> " fontDirectionHint " <> dumpFontDirectionHint fontDirectionHint <> newlineBuilder
<> " indexToLocFormat " <> Text.Builder.decimal indexToLocFormat <> newlineBuilder <> " indexToLocFormat " <> dumpIndexToLocFormat indexToLocFormat <> newlineBuilder
<> " glyphDataFormat " <> Text.Builder.decimal glyphDataFormat <> newlineBuilder <> " glyphDataFormat " <> Text.Builder.decimal glyphDataFormat <> newlineBuilder
dumpIndexToLocFormat :: IndexToLocFormat -> Text.Builder.Builder
dumpIndexToLocFormat ShortOffsetIndexToLocFormat = "0"
dumpIndexToLocFormat LongOffsetIndexToLocFormat = "1"
dumpFontDirectionHint :: FontDirectionHint -> Text.Builder.Builder dumpFontDirectionHint :: FontDirectionHint -> Text.Builder.Builder
dumpFontDirectionHint = \case dumpFontDirectionHint = \case
MixedDirectionalGlyphs -> "0" MixedDirectionalGlyphs -> "0"
@ -303,34 +316,60 @@ dumpCmap CmapTable{..}
dumpGlyphAtIndex index element = " glyphIdArray[" <> Text.Builder.decimal index <> "] = " dumpGlyphAtIndex index element = " glyphIdArray[" <> Text.Builder.decimal index <> "] = "
<> Text.Builder.decimal element <> newlineBuilder <> Text.Builder.decimal element <> newlineBuilder
dumpLoca :: LocaTable -> Text.Builder.Builder
dumpLoca table =
dumpCaption "'loca' Table - Index to Location"
<> go table
where
go (LongLocaTable elements) = dumpElements elements
go (ShortLocaTable elements) = dumpElements
$ (* 2)
. (fromIntegral :: Word16 -> Word32)
<$> elements
dumpElements elements =
case Vector.unsnoc elements of
Just (init', last')
-> foldMap dumpLocaLine (Vector.indexed init')
<> " Ended at " <> paddedHexadecimal last'
Nothing -> mempty
dumpLocaLine :: Integral a => (Int, a) -> Text.Builder.Builder
dumpLocaLine (index, element)
= " Idx " <> justifyNumber 6 index
<> " -> GlyphOffset " <> paddedHexadecimal element <> newlineBuilder
dumpTables dumpTables
:: Megaparsec.State ByteString Void :: Megaparsec.State ByteString Void
-> FontDirectory -> FontDirectory
-> Either DumpError Text.Builder.Builder -> Either DumpError Text.Builder.Builder
dumpTables processedState directory@FontDirectory{..} = dumpTables processedState directory@FontDirectory{..}
findRequired "hhea" hheaTableP >>= traverseDirectory = parseRequired >>= traverseDirectory
where where
traverseDirectory parsedHhea = traverseDirectory parsedRequired =
let initial = Right $ dumpOffsetTable directory let initial = Right $ dumpOffsetTable directory
in foldl' (go parsedHhea) initial tableDirectory in foldl' (go parsedRequired) initial tableDirectory
parseRequired = RequiredTables
<$> findRequired "hhea" hheaTableP
<*> findRequired "head" headTableP
findRequired tableName parser = findRequired tableName parser =
let missingError = Left $ DumpRequiredTableMissingError tableName let missingError = Left $ DumpRequiredTableMissingError tableName
parseRequired tableEntry = parseTable tableEntry parser processedState parseFound tableEntry = parseTable tableEntry parser processedState
in maybe missingError (first DumpParseError . parseRequired) in maybe missingError (first DumpParseError . parseFound)
$ find ((== Char8.pack tableName) . getField @"tag") tableDirectory $ find ((== Char8.pack tableName) . getField @"tag") tableDirectory
go _ (Left accumulator) _ = Left accumulator go _ (Left accumulator) _ = Left accumulator
go hheaTable (Right accumulator) tableEntry go parsedRequired (Right accumulator) tableEntry
= maybe (Right accumulator) (concatDump accumulator . first DumpParseError) = maybe (Right accumulator) (concatDump accumulator . first DumpParseError)
$ dumpSubTable hheaTable tableEntry $ dumpSubTable parsedRequired tableEntry
concatDump accumulator builderDump = ((accumulator <> newlineBuilder) <>) concatDump accumulator builderDump = ((accumulator <> newlineBuilder) <>)
<$> builderDump <$> builderDump
dumpSubTable hheaTable@HheaTable{ numOfLongHorMetrics } tableEntry = dumpSubTable RequiredTables{..} 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 $ Right $ dumpHead headTable
"hhea" -> Just $ Right $ dumpHhea hheaTable "hhea" -> Just $ Right $ dumpHhea hheaTable
"hmtx" -> Just $ dumpHmtx "hmtx" -> Just $ dumpHmtx
<$> parseTable tableEntry (hmtxTableP numOfLongHorMetrics) processedState <$> parseTable tableEntry (hmtxTableP $ getField @"numOfLongHorMetrics" hheaTable) processedState
"loca" -> Just $ dumpLoca
<$> parseTable tableEntry (locaTableP $ getField @"indexToLocFormat" headTable) processedState
_ -> Nothing _ -> Nothing
dumpTrueType :: ByteString -> FilePath -> Either DumpError Text.Builder.Builder dumpTrueType :: ByteString -> FilePath -> Either DumpError Text.Builder.Builder

View File

@ -23,6 +23,7 @@ module Graphics.Fountainhead.Parser
, headTableP , headTableP
, hheaTableP , hheaTableP
, hmtxTableP , hmtxTableP
, locaTableP
, longDateTimeP , longDateTimeP
, longLocaTableP , longLocaTableP
, maxpTableP , maxpTableP
@ -107,6 +108,7 @@ import Graphics.Fountainhead.TrueType
, HeadTable(..) , HeadTable(..)
, HheaTable(..) , HheaTable(..)
, HmtxTable(..) , HmtxTable(..)
, IndexToLocFormat(..)
, LocaTable(..) , LocaTable(..)
, LongHorMetric(..) , LongHorMetric(..)
, MaxpTable(..) , MaxpTable(..)
@ -293,9 +295,17 @@ headTableP = HeadTable
<*> fontStyleP <*> fontStyleP
<*> Megaparsec.Binary.word16be <*> Megaparsec.Binary.word16be
<*> fontDirectionHintP <*> fontDirectionHintP
<*> Megaparsec.Binary.word16be <*> indexToLocFormatP
<*> Megaparsec.Binary.word16be <*> Megaparsec.Binary.word16be
<* Megaparsec.eof <* Megaparsec.eof
where
indexToLocFormatP = do
indexToLocFormat' <- Megaparsec.Binary.int16be
case indexToLocFormat' of
0 -> pure ShortOffsetIndexToLocFormat
1 -> pure LongOffsetIndexToLocFormat
_ -> fail $ "Unknown loca table format indexToLocFormat: "
<> show indexToLocFormat'
fontStyleP :: Parser FontStyle fontStyleP :: Parser FontStyle
fontStyleP = go <$> Megaparsec.Binary.word16be fontStyleP = go <$> Megaparsec.Binary.word16be
@ -330,6 +340,10 @@ shortLocaTableP = ShortLocaTable
<$> vectorP Megaparsec.Binary.word16be <$> vectorP Megaparsec.Binary.word16be
<?> "loca table, short version" <?> "loca table, short version"
locaTableP :: IndexToLocFormat -> Parser LocaTable
locaTableP ShortOffsetIndexToLocFormat = shortLocaTableP
locaTableP LongOffsetIndexToLocFormat = longLocaTableP
-- * Horizontal metrics table -- * Horizontal metrics table
longHorMetricP :: Parser LongHorMetric longHorMetricP :: Parser LongHorMetric
@ -587,9 +601,8 @@ simpleGlyphDefinitionP numberOfContours' = do
, thisXIsSame = testBit flag 4 , thisXIsSame = testBit flag 4
, thisYIsSame = testBit flag 5 , thisYIsSame = testBit flag 5
} }
repeat = testBit flag 3
repeatN <- repeatN <-
if repeat if testBit flag 3
then (1 +) then (1 +)
. fromIntegral . fromIntegral
<$> Megaparsec.Binary.word8 <$> Megaparsec.Binary.word8

View File

@ -49,6 +49,7 @@ module Graphics.Fountainhead.TrueType
, HeadTable(..) , HeadTable(..)
, HheaTable(..) , HheaTable(..)
, HmtxTable(..) , HmtxTable(..)
, IndexToLocFormat(..)
, LocaTable(..) , LocaTable(..)
, LongHorMetric(..) , LongHorMetric(..)
, MaxpTable(..) , MaxpTable(..)
@ -180,6 +181,11 @@ data HheaTable = HheaTable
-- * Font header table -- * Font header table
data IndexToLocFormat
= ShortOffsetIndexToLocFormat
| LongOffsetIndexToLocFormat
deriving (Eq, Show)
data HeadTable = HeadTable data HeadTable = HeadTable
{ version :: Fixed32 -- ^ 0x00010000 if (version 1.0). { version :: Fixed32 -- ^ 0x00010000 if (version 1.0).
, fontRevision :: Fixed32 -- ^ Set by font manufacturer. , fontRevision :: Fixed32 -- ^ Set by font manufacturer.
@ -196,7 +202,7 @@ data HeadTable = HeadTable
, macStyle :: FontStyle , macStyle :: FontStyle
, lowestRecPPEM :: Word16 -- ^ Smallest readable size in pixels. , lowestRecPPEM :: Word16 -- ^ Smallest readable size in pixels.
, fontDirectionHint :: FontDirectionHint -- ^ 0 Mixed directional glyphs. , fontDirectionHint :: FontDirectionHint -- ^ 0 Mixed directional glyphs.
, indexToLocFormat :: Word16 -- ^ 0 for short offsets, 1 for long. , indexToLocFormat :: IndexToLocFormat -- ^ 0 for short offsets, 1 for long.
, glyphDataFormat :: Word16 -- ^ 0 for current format. , glyphDataFormat :: Word16 -- ^ 0 for current format.
} deriving (Eq, Show) } deriving (Eq, Show)