2023-11-11 10:57:43 +01:00
|
|
|
{- This Source Code Form is subject to the terms of the Mozilla Public License,
|
|
|
|
v. 2.0. If a copy of the MPL was not distributed with this file, You can
|
|
|
|
obtain one at https://mozilla.org/MPL/2.0/. -}
|
|
|
|
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2023-11-28 20:02:57 +01:00
|
|
|
{-# LANGUAGE PatternGuards #-}
|
2023-11-11 10:57:43 +01:00
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2023-11-13 19:18:33 +01:00
|
|
|
{-# LANGUAGE LambdaCase #-}
|
2023-11-28 20:02:57 +01:00
|
|
|
{-# LANGUAGE TypeApplications #-}
|
2023-11-11 10:57:43 +01:00
|
|
|
|
|
|
|
-- | Outputs information about a font as text.
|
|
|
|
module Graphics.Fountainhead.Dumper
|
2023-11-18 04:40:17 +01:00
|
|
|
( DumpError(..)
|
2023-11-11 10:57:43 +01:00
|
|
|
, dumpCmap
|
2023-11-16 09:09:59 +01:00
|
|
|
, dumpHead
|
2023-11-18 04:40:17 +01:00
|
|
|
, dumpHmtx
|
2023-11-19 09:42:29 +01:00
|
|
|
, dumpHhea
|
|
|
|
, dumpLoca
|
2023-11-28 20:02:57 +01:00
|
|
|
, dumpName
|
2023-11-20 09:33:04 +01:00
|
|
|
, dumpMaxp
|
2023-11-11 10:57:43 +01:00
|
|
|
, dumpTrueType
|
|
|
|
, dumpOffsetTable
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Data.ByteString (ByteString)
|
2023-11-28 20:02:57 +01:00
|
|
|
import qualified Data.ByteString as ByteString
|
2023-11-18 04:40:17 +01:00
|
|
|
import qualified Data.ByteString.Char8 as Char8
|
2023-11-11 10:57:43 +01:00
|
|
|
import Data.Int (Int64)
|
2023-11-28 20:02:57 +01:00
|
|
|
import Data.Word (Word8, Word16, Word32)
|
2023-11-12 10:13:38 +01:00
|
|
|
import qualified Data.IntMap as IntMap
|
2023-11-28 20:02:57 +01:00
|
|
|
import qualified Data.Text as Text
|
2023-11-11 10:57:43 +01:00
|
|
|
import qualified Data.Text.Encoding as Text
|
|
|
|
import qualified Data.Text.Lazy as Text.Lazy
|
|
|
|
import qualified Data.Text.Lazy.Builder as Text.Builder
|
|
|
|
import qualified Data.Text.Lazy.Builder.Int as Text.Builder
|
2023-11-15 21:25:18 +01:00
|
|
|
import Data.Vector (Vector)
|
2023-11-13 19:18:33 +01:00
|
|
|
import qualified Data.Vector as Vector
|
2023-11-11 10:57:43 +01:00
|
|
|
import Data.Void
|
|
|
|
import GHC.Records (HasField(..))
|
|
|
|
import Graphics.Fountainhead.TrueType
|
|
|
|
( CmapTable(..)
|
|
|
|
, FontDirectory(..)
|
2023-11-17 09:54:26 +01:00
|
|
|
, FontDirectionHint(..)
|
2023-11-16 09:09:59 +01:00
|
|
|
, HeadTable(..)
|
2023-11-17 09:54:26 +01:00
|
|
|
, HheaTable(..)
|
2023-11-18 04:40:17 +01:00
|
|
|
, HmtxTable(..)
|
2023-11-11 10:57:43 +01:00
|
|
|
, OffsetSubtable(..)
|
2023-11-13 19:18:33 +01:00
|
|
|
, TableDirectory(..)
|
|
|
|
, CmapEncoding(..)
|
|
|
|
, CmapSubtable(..)
|
|
|
|
, CmapFormat4Table(..)
|
2023-11-16 09:09:59 +01:00
|
|
|
, FontStyle(..)
|
2023-11-18 04:40:17 +01:00
|
|
|
, LongHorMetric(..)
|
2023-11-19 09:42:29 +01:00
|
|
|
, LocaTable(..)
|
2023-11-28 20:02:57 +01:00
|
|
|
, NameRecord (..)
|
|
|
|
, NameTable(..)
|
2023-11-19 09:42:29 +01:00
|
|
|
, IndexToLocFormat(..)
|
2023-11-20 09:33:04 +01:00
|
|
|
, OpenMaxpTable(..)
|
|
|
|
, MaxpTable(..)
|
|
|
|
, TrueMaxpTable(..)
|
2023-11-28 20:02:57 +01:00
|
|
|
, nameStringOffset
|
2023-11-11 10:57:43 +01:00
|
|
|
)
|
|
|
|
import qualified Text.Megaparsec as Megaparsec
|
|
|
|
import Graphics.Fountainhead.Parser
|
2023-11-12 10:13:38 +01:00
|
|
|
( fontDirectoryP
|
|
|
|
, parseTable
|
2023-11-11 10:57:43 +01:00
|
|
|
, cmapTableP
|
2023-11-16 09:09:59 +01:00
|
|
|
, headTableP
|
2023-11-17 09:54:26 +01:00
|
|
|
, hheaTableP
|
2023-11-18 04:40:17 +01:00
|
|
|
, hmtxTableP
|
2023-11-19 09:42:29 +01:00
|
|
|
, locaTableP
|
2023-11-28 20:02:57 +01:00
|
|
|
, maxpTableP, nameTableP
|
2023-11-11 10:57:43 +01:00
|
|
|
)
|
2023-11-17 09:54:26 +01:00
|
|
|
import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch)
|
2023-11-18 04:40:17 +01:00
|
|
|
import Data.Foldable (Foldable(..), find)
|
2023-11-15 21:25:18 +01:00
|
|
|
import Data.Maybe (fromMaybe)
|
2023-11-16 09:09:59 +01:00
|
|
|
import Data.Time (LocalTime(..), NominalDiffTime, diffLocalTime, midnight)
|
2023-11-17 09:54:26 +01:00
|
|
|
import Data.Bits (Bits(..))
|
2023-11-18 04:40:17 +01:00
|
|
|
import Data.Bifunctor (Bifunctor(first))
|
2023-11-28 20:02:57 +01:00
|
|
|
import Data.List (intersperse)
|
2023-11-11 10:57:43 +01:00
|
|
|
|
2023-11-18 04:40:17 +01:00
|
|
|
data DumpError
|
|
|
|
= DumpParseError (Megaparsec.ParseErrorBundle ByteString Void)
|
|
|
|
| DumpRequiredTableMissingError String
|
2023-11-11 10:57:43 +01:00
|
|
|
|
2023-11-19 09:42:29 +01:00
|
|
|
data RequiredTables = RequiredTables
|
|
|
|
{ hheaTable :: HheaTable
|
|
|
|
, headTable :: HeadTable
|
|
|
|
} deriving (Eq, Show)
|
|
|
|
|
2023-11-11 10:57:43 +01:00
|
|
|
paddedHexadecimal :: Integral a => a -> Text.Builder.Builder
|
|
|
|
paddedHexadecimal = ("0x" <>)
|
|
|
|
. Text.Builder.fromLazyText
|
|
|
|
. Text.Lazy.justifyRight 8 '0'
|
|
|
|
. Text.Builder.toLazyText
|
|
|
|
. Text.Builder.hexadecimal
|
|
|
|
|
2023-11-14 11:49:11 +01:00
|
|
|
halfPaddedHexadecimal :: Integral a => a -> Text.Builder.Builder
|
|
|
|
halfPaddedHexadecimal = Text.Builder.fromLazyText
|
|
|
|
. Text.Lazy.justifyRight 4 '0'
|
|
|
|
. Text.Builder.toLazyText
|
|
|
|
. Text.Builder.hexadecimal
|
|
|
|
|
2023-11-11 10:57:43 +01:00
|
|
|
justifyNumber :: Integral a => Int64 -> a -> Text.Builder.Builder
|
|
|
|
justifyNumber count = Text.Builder.fromLazyText
|
|
|
|
. Text.Lazy.justifyRight count ' '
|
|
|
|
. Text.Builder.toLazyText
|
|
|
|
. Text.Builder.decimal
|
|
|
|
|
|
|
|
newlineBuilder :: Text.Builder.Builder
|
|
|
|
newlineBuilder = Text.Builder.singleton '\n'
|
|
|
|
|
2023-11-16 09:09:59 +01:00
|
|
|
dumpCaption :: String -> Text.Builder.Builder
|
|
|
|
dumpCaption headline = Text.Builder.fromString headline
|
2023-11-11 10:57:43 +01:00
|
|
|
<> newlineBuilder
|
|
|
|
<> Text.Builder.fromLazyText (Text.Lazy.replicate headlineLength "-")
|
|
|
|
<> newlineBuilder
|
|
|
|
where
|
|
|
|
headlineLength = fromIntegral $ Prelude.length headline
|
|
|
|
|
|
|
|
dumpOffsetTable :: FontDirectory -> Text.Builder.Builder
|
|
|
|
dumpOffsetTable directory
|
2023-11-16 09:09:59 +01:00
|
|
|
= dumpCaption "Offset Table"
|
2023-11-11 10:57:43 +01:00
|
|
|
<> " sfnt version: 1.0\n number of tables: "
|
|
|
|
<> Text.Builder.decimal (numTables $ offsetSubtable directory)
|
|
|
|
<> newlineBuilder
|
|
|
|
<> dumpOffsetSummary (tableDirectory directory)
|
|
|
|
where
|
2023-11-13 19:18:33 +01:00
|
|
|
dumpOffsetSummary = mconcat . fmap dumpOffsetRow . zip [0 :: Int ..]
|
2023-11-11 10:57:43 +01:00
|
|
|
dumpOffsetRow (index, table) = justifyNumber 4 index
|
|
|
|
<> ". '"
|
|
|
|
<> Text.Builder.fromText (Text.decodeASCII $ tag table)
|
|
|
|
<> "' - checksum = "
|
|
|
|
<> paddedHexadecimal (getField @"checkSum" table)
|
|
|
|
<> ", offset = "
|
|
|
|
<> paddedHexadecimal (getField @"offset" table)
|
|
|
|
<> ", len = "
|
|
|
|
<> justifyNumber 9 (getField @"length" table)
|
|
|
|
<> newlineBuilder
|
|
|
|
|
2023-11-17 09:54:26 +01:00
|
|
|
dumpFixed32 :: Fixed32 -> Text.Builder.Builder
|
|
|
|
dumpFixed32 (Fixed32 word)
|
|
|
|
= Text.Builder.decimal (shiftR word 16)
|
|
|
|
<> Text.Builder.singleton '.'
|
|
|
|
<> Text.Builder.decimal (word .&. 0xff00)
|
|
|
|
|
2023-11-18 04:40:17 +01:00
|
|
|
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
|
|
|
|
|
2023-11-17 09:54:26 +01:00
|
|
|
dumpHhea :: HheaTable -> Text.Builder.Builder
|
|
|
|
dumpHhea HheaTable{..}
|
2023-11-18 04:40:17 +01:00
|
|
|
= dumpCaption "'hhea' Table - Horizontal Header"
|
2023-11-17 09:54:26 +01:00
|
|
|
<> " 'hhea' version: " <> dumpFixed32 version <> newlineBuilder
|
|
|
|
<> " yAscender: " <> Text.Builder.decimal ascent <> newlineBuilder
|
|
|
|
<> " yDescender: " <> Text.Builder.decimal descent <> newlineBuilder
|
|
|
|
<> " yLineGap: " <> Text.Builder.decimal lineGap <> newlineBuilder
|
|
|
|
<> " advanceWidthMax: " <> Text.Builder.decimal advanceWidthMax <> newlineBuilder
|
|
|
|
<> " minLeftSideBearing: " <> Text.Builder.decimal minLeftSideBearing <> newlineBuilder
|
|
|
|
<> " minRightSideBearing: " <> Text.Builder.decimal minRightSideBearing <> newlineBuilder
|
|
|
|
<> " xMaxExtent: " <> Text.Builder.decimal xMaxExtent <> newlineBuilder
|
|
|
|
<> " caretSlopeRise: " <> Text.Builder.decimal caretSlopeRise <> newlineBuilder
|
|
|
|
<> " caretSlopeRun: " <> Text.Builder.decimal caretSlopeRun <> newlineBuilder
|
|
|
|
<> " reserved0: 0" <> newlineBuilder
|
|
|
|
<> " reserved1: 0" <> newlineBuilder
|
|
|
|
<> " reserved2: 0" <> newlineBuilder
|
|
|
|
<> " reserved3: 0" <> newlineBuilder
|
|
|
|
<> " reserved4: 0" <> newlineBuilder
|
|
|
|
<> " metricDataFormat: " <> Text.Builder.decimal metricDataFormat <> newlineBuilder
|
|
|
|
<> " numberOfHMetrics: " <> Text.Builder.decimal numOfLongHorMetrics <> newlineBuilder
|
|
|
|
|
2023-11-16 09:09:59 +01:00
|
|
|
dumpHead :: HeadTable -> Text.Builder.Builder
|
|
|
|
dumpHead HeadTable{..}
|
|
|
|
= dumpCaption "'head' Table - Font Header"
|
2023-11-17 09:54:26 +01:00
|
|
|
<> " head version: " <> dumpFixed32 version <> newlineBuilder
|
|
|
|
<> " fontRevision: " <> dumpFixed32 fontRevision <> newlineBuilder
|
2023-11-16 09:09:59 +01:00
|
|
|
<> " checkSumAdjustment: " <> paddedHexadecimal checkSumAdjustment <> newlineBuilder
|
|
|
|
<> " magicNumber: " <> paddedHexadecimal magicNumber <> newlineBuilder
|
|
|
|
<> " flags: 0x" <> halfPaddedHexadecimal flags <> newlineBuilder
|
|
|
|
<> " unitsPerEm: " <> Text.Builder.decimal unitsPerEm <> newlineBuilder
|
|
|
|
<> " created: " <> "0x" <> longDateTime created <> newlineBuilder
|
|
|
|
<> " modified: " <> "0x" <> longDateTime modified <> newlineBuilder
|
|
|
|
<> " xMin: " <> Text.Builder.decimal xMin <> newlineBuilder
|
|
|
|
<> " yMin: " <> Text.Builder.decimal yMin <> newlineBuilder
|
|
|
|
<> " xMax: " <> Text.Builder.decimal xMax <> newlineBuilder
|
|
|
|
<> " yMax: " <> Text.Builder.decimal yMax <> newlineBuilder
|
|
|
|
<> " macStyle bits: " <> "0x" <> dumpFontStyle macStyle <> newlineBuilder
|
2023-11-17 09:54:26 +01:00
|
|
|
<> " lowestRecPPEM " <> Text.Builder.decimal lowestRecPPEM <> newlineBuilder
|
|
|
|
<> " fontDirectionHint " <> dumpFontDirectionHint fontDirectionHint <> newlineBuilder
|
2023-11-19 09:42:29 +01:00
|
|
|
<> " indexToLocFormat " <> dumpIndexToLocFormat indexToLocFormat <> newlineBuilder
|
2023-11-17 09:54:26 +01:00
|
|
|
<> " glyphDataFormat " <> Text.Builder.decimal glyphDataFormat <> newlineBuilder
|
|
|
|
|
2023-11-19 09:42:29 +01:00
|
|
|
dumpIndexToLocFormat :: IndexToLocFormat -> Text.Builder.Builder
|
|
|
|
dumpIndexToLocFormat ShortOffsetIndexToLocFormat = "0"
|
|
|
|
dumpIndexToLocFormat LongOffsetIndexToLocFormat = "1"
|
|
|
|
|
2023-11-17 09:54:26 +01:00
|
|
|
dumpFontDirectionHint :: FontDirectionHint -> Text.Builder.Builder
|
|
|
|
dumpFontDirectionHint = \case
|
|
|
|
MixedDirectionalGlyphs -> "0"
|
|
|
|
StronglyLeftToRightGlyphs -> "1"
|
|
|
|
LeftToRightGlyphsWithNeutrals -> "2"
|
|
|
|
StronglyRightToLeftGlyphs -> "-1"
|
|
|
|
RightToLeftGlyphsWithNeutrals -> "-2"
|
2023-11-16 09:09:59 +01:00
|
|
|
|
|
|
|
dumpFontStyle :: FontStyle -> Text.Builder.Builder
|
|
|
|
dumpFontStyle FontStyle{..} = halfPaddedHexadecimal
|
2023-11-17 09:54:26 +01:00
|
|
|
$ foldr (go . fst) (zeroBits :: Int)
|
2023-11-16 09:09:59 +01:00
|
|
|
$ filter snd
|
|
|
|
$ zip [0..] [bold, italic, underline, outline, shadow, condensed, extended]
|
|
|
|
where
|
|
|
|
go bitNumber accumulator = setBit accumulator bitNumber
|
|
|
|
|
|
|
|
longDateTime :: LocalTime -> Text.Builder.Builder
|
|
|
|
longDateTime localTime = Text.Builder.fromLazyText
|
|
|
|
$ Text.Lazy.justifyRight 16 '0'
|
|
|
|
$ Text.Builder.toLazyText
|
|
|
|
$ Text.Builder.hexadecimal
|
|
|
|
$ (truncate :: NominalDiffTime -> Int)
|
|
|
|
$ diffLocalTime localTime (LocalTime ttfEpoch midnight)
|
|
|
|
|
2023-11-11 10:57:43 +01:00
|
|
|
dumpCmap :: CmapTable -> Text.Builder.Builder
|
2023-11-12 10:13:38 +01:00
|
|
|
dumpCmap CmapTable{..}
|
2023-11-16 09:09:59 +01:00
|
|
|
= dumpCaption "'cmap' Table - Character to Glyph Index Mapping Table"
|
2023-11-12 10:13:38 +01:00
|
|
|
<> " 'cmap' version: " <> Text.Builder.decimal version <> newlineBuilder
|
|
|
|
<> " number of encodings: " <> Text.Builder.decimal encodingsLength <> newlineBuilder
|
|
|
|
<> " number of subtables: " <> Text.Builder.decimal (Prelude.length subtables) <> newlineBuilder
|
|
|
|
<> newlineBuilder
|
|
|
|
<> snd (foldr dumpCmapEncoding (pred encodingsLength, "") encodings) <> newlineBuilder
|
2023-11-13 19:18:33 +01:00
|
|
|
<> snd (foldr dumpCmapSubTable (pred subTablesLength, "") subtables) <> newlineBuilder
|
2023-11-12 10:13:38 +01:00
|
|
|
where
|
|
|
|
encodingsLength = Prelude.length encodings
|
2023-11-13 19:18:33 +01:00
|
|
|
subTablesLength = IntMap.size subtables
|
2023-11-12 10:13:38 +01:00
|
|
|
dumpCmapEncoding CmapEncoding{..} (index, accumulator) =
|
|
|
|
let findSubTableIndex = Text.Builder.decimal
|
|
|
|
. Prelude.length
|
|
|
|
. filter ((< offset) . fromIntegral)
|
|
|
|
. IntMap.keys
|
|
|
|
summary = "Encoding " <> Text.Builder.decimal index
|
|
|
|
<> ". PlatformID: " <> Text.Builder.decimal platformID <> newlineBuilder
|
|
|
|
<> " EcodingID: " <> Text.Builder.decimal platformSpecificID <> newlineBuilder
|
|
|
|
<> " SubTable: " <> findSubTableIndex subtables
|
|
|
|
<> ", Offset: " <> paddedHexadecimal offset <> newlineBuilder
|
|
|
|
in (pred index, summary <> newlineBuilder <> accumulator)
|
2023-11-13 19:18:33 +01:00
|
|
|
dumpCmapSubTable currentSubTable (index, accumulator) =
|
|
|
|
let contents = "SubTable " <> Text.Builder.decimal index
|
|
|
|
<> ". " <> dumpCmapSubTableFormat currentSubTable
|
|
|
|
in (pred index, contents <> accumulator)
|
|
|
|
dumpCmapSubTableFormat = \case
|
|
|
|
(CmapFormat0 _) -> "Format 0"
|
|
|
|
(CmapFormat2 _) -> "Format 2"
|
|
|
|
(CmapFormat4 CmapFormat4Table{..}) ->
|
2023-11-14 11:49:11 +01:00
|
|
|
let segCount = Vector.length startCode
|
2023-11-15 21:25:18 +01:00
|
|
|
dumpSegment' = dumpSegment segCount glyphIndexArray
|
2023-11-14 11:49:11 +01:00
|
|
|
in "Format 4 - Segment mapping to delta values\n\
|
|
|
|
\ Length: 994\n\
|
|
|
|
\ Version: 0\n\
|
|
|
|
\ segCount: "
|
|
|
|
<> Text.Builder.decimal segCount
|
|
|
|
<> newlineBuilder <> " searchRange: "
|
|
|
|
<> Text.Builder.decimal searchRange
|
|
|
|
<> newlineBuilder <> " entrySelector: "
|
|
|
|
<> Text.Builder.decimal entrySelector
|
|
|
|
<> newlineBuilder <> " rangeShift: "
|
|
|
|
<> Text.Builder.decimal (segCount * 2 - fromIntegral searchRange)
|
|
|
|
<> newlineBuilder
|
2023-11-15 21:25:18 +01:00
|
|
|
<> fold (Vector.izipWith4 (dumpSegmentSummary segCount) startCode endCode idDelta idRangeOffset)
|
|
|
|
<> " Number of glyphIndex "
|
|
|
|
<> Text.Builder.decimal (Vector.length glyphIndexArray) <> newlineBuilder
|
|
|
|
<> fold (Vector.imap dumpGlyphAtIndex glyphIndexArray)
|
|
|
|
<> fold (Vector.izipWith4 dumpSegment' startCode endCode idDelta idRangeOffset)
|
2023-11-13 19:18:33 +01:00
|
|
|
(CmapFormat6 _) -> "Format 6"
|
|
|
|
(CmapFormat8 _) -> "Format 8"
|
|
|
|
(CmapFormat10 _) -> "Format 10"
|
|
|
|
(CmapFormat12 _) -> "Format 12"
|
|
|
|
(CmapFormat13 _) -> "Format 13"
|
|
|
|
(CmapFormat14 _) -> "Format 14"
|
2023-11-15 21:25:18 +01:00
|
|
|
dumpSegment :: Int -> Vector Word16 -> Int -> Word16 -> Word16 -> Word16 -> Word16 -> Text.Builder.Builder
|
|
|
|
dumpSegment segCount glyphIndexArray' segmentIndex startCode' endCode' idDelta' idRangeOffset' =
|
|
|
|
let charRange = [startCode'..endCode']
|
|
|
|
dumpSegmentCharIndex' =
|
|
|
|
dumpSegmentCharIndex segCount glyphIndexArray' segmentIndex idDelta' idRangeOffset' startCode'
|
|
|
|
in "Segment " <> Text.Builder.decimal segmentIndex <> ":\n"
|
|
|
|
<> foldMap dumpSegmentCharIndex' charRange
|
|
|
|
dumpSegmentCharIndex segCount glyphIndexArray' segmentIndex idDelta' idRangeOffset' startCode' charCode =
|
|
|
|
let calculateGlyphIndex' =
|
|
|
|
calculateGlyphIndex charCode segmentIndex segCount glyphIndexArray' idRangeOffset' idDelta' startCode'
|
|
|
|
in " Char 0x"
|
|
|
|
<> halfPaddedHexadecimal charCode <> " -> Index "
|
|
|
|
<> Text.Builder.decimal calculateGlyphIndex'
|
|
|
|
<> newlineBuilder
|
|
|
|
dumpSegmentSummary segCount index startCode' endCode' idDelta' idRangeOffset'
|
2023-11-14 11:49:11 +01:00
|
|
|
= " Seg " <> justifyNumber 5 index
|
|
|
|
<> " : St = " <> halfPaddedHexadecimal startCode'
|
|
|
|
<> ", En = " <> halfPaddedHexadecimal endCode'
|
|
|
|
<> ", D = " <> justifyNumber 6 idDelta'
|
|
|
|
<> ", RO = " <> justifyNumber 6 idRangeOffset'
|
|
|
|
<> ", gId# = " <> dumpGlyphId index segCount idRangeOffset'
|
|
|
|
<> newlineBuilder
|
2023-11-15 21:25:18 +01:00
|
|
|
dumpGlyphId segmentIndex segCount idRangeOffset'
|
|
|
|
= maybe "N/A" Text.Builder.decimal
|
|
|
|
$ calculateGlyphId segmentIndex segCount idRangeOffset'
|
|
|
|
calculateGlyphIndex :: Word16 -> Int -> Int -> Vector Word16 -> Word16 -> Word16 -> Word16 -> Int
|
|
|
|
calculateGlyphIndex c segmentIndex segCount glyphIndexArray' idRangeOffset' idDelta' startCode' =
|
|
|
|
let defaultIndex = fromIntegral $ c + idDelta'
|
|
|
|
addOffset = fromIntegral
|
|
|
|
. fromMaybe 0
|
|
|
|
. (glyphIndexArray' Vector.!?)
|
|
|
|
. (+ fromIntegral (c - startCode'))
|
|
|
|
in maybe defaultIndex addOffset
|
|
|
|
$ calculateGlyphId segmentIndex segCount idRangeOffset'
|
|
|
|
calculateGlyphId segmentIndex segCount idRangeOffset'
|
|
|
|
| idRangeOffset' == 0 = Nothing
|
|
|
|
| otherwise = Just $ segmentIndex - segCount + (fromIntegral idRangeOffset' `div` 2)
|
|
|
|
dumpGlyphAtIndex index element = " glyphIdArray[" <> Text.Builder.decimal index <> "] = "
|
|
|
|
<> Text.Builder.decimal element <> newlineBuilder
|
2023-11-11 10:57:43 +01:00
|
|
|
|
2023-11-19 09:42:29 +01:00
|
|
|
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')
|
2023-11-20 09:33:04 +01:00
|
|
|
<> " Ended at " <> paddedHexadecimal last' <> newlineBuilder
|
2023-11-19 09:42:29 +01:00
|
|
|
Nothing -> mempty
|
|
|
|
dumpLocaLine :: Integral a => (Int, a) -> Text.Builder.Builder
|
|
|
|
dumpLocaLine (index, element)
|
|
|
|
= " Idx " <> justifyNumber 6 index
|
|
|
|
<> " -> GlyphOffset " <> paddedHexadecimal element <> newlineBuilder
|
|
|
|
|
2023-11-28 20:02:57 +01:00
|
|
|
dumpName :: NameTable -> Text.Builder.Builder
|
|
|
|
dumpName table'@NameTable{..} = dumpCaption "'name' Table - Naming Table"
|
|
|
|
<> " Format: " <> Text.Builder.decimal format <> newlineBuilder
|
|
|
|
<> " Number of Record: " <> Text.Builder.decimal (Prelude.length nameRecord) <> newlineBuilder
|
|
|
|
<> " Storage offset: " <> Text.Builder.decimal (nameStringOffset table') <> newlineBuilder
|
|
|
|
<> foldMap go (zip3 [0 :: Int ..] nameRecord variable)
|
|
|
|
where
|
|
|
|
go (index, NameRecord{ length = length', ..}, variable')
|
|
|
|
= "Name table " <> justifyNumber 3 index <> "."
|
|
|
|
<> " PlatformID: " <> Text.Builder.decimal platformID <> newlineBuilder
|
|
|
|
<> " EncodingID: " <> Text.Builder.decimal platformSpecificID <> newlineBuilder
|
|
|
|
<> " LanguageID: " <> Text.Builder.decimal languageID <> newlineBuilder
|
|
|
|
<> " NameID: " <> Text.Builder.decimal nameID <> newlineBuilder
|
|
|
|
<> " Length: " <> Text.Builder.decimal length' <> newlineBuilder
|
|
|
|
<> " Offset: " <> Text.Builder.decimal offset <> newlineBuilder
|
|
|
|
<> foldMap (" " <>) (dumpHexString $ ByteString.unpack variable')
|
|
|
|
|
|
|
|
dumpHexString :: [Word8] -> [Text.Builder.Builder]
|
|
|
|
dumpHexString byteCodes
|
|
|
|
| null byteCodes = [dumpHexLine " > " byteCodes]
|
|
|
|
| Prelude.length byteCodes < 10 = [dumpHexLine " > " byteCodes]
|
|
|
|
| otherwise = dumpHexLine " > " byteCodes
|
|
|
|
: dumpHexString (drop 10 byteCodes)
|
|
|
|
where
|
|
|
|
dumpHexLine separator variable' =
|
|
|
|
let firstTen = take 10 variable'
|
|
|
|
digits = fold $ intersperse (Text.Builder.singleton ' ') $ hexByte <$> firstTen
|
|
|
|
printables = foldMap printableByte firstTen
|
|
|
|
in digits
|
|
|
|
<> Text.Builder.fromText (Text.replicate (10 - Prelude.length firstTen) " ")
|
|
|
|
<> separator
|
|
|
|
<> printables
|
|
|
|
<> newlineBuilder
|
|
|
|
hexByte = Text.Builder.fromLazyText
|
|
|
|
. Text.Lazy.justifyRight 2 '0'
|
|
|
|
. Text.Builder.toLazyText . Text.Builder.hexadecimal
|
|
|
|
printableByte :: Word8 -> Text.Builder.Builder
|
|
|
|
printableByte code
|
|
|
|
| code >= 0x20
|
|
|
|
, code < 0x7f = Text.Builder.singleton $ toEnum $ fromIntegral code
|
|
|
|
| otherwise = Text.Builder.singleton '.'
|
|
|
|
|
2023-11-20 09:33:04 +01:00
|
|
|
dumpMaxp :: MaxpTable -> Text.Builder.Builder
|
|
|
|
dumpMaxp (TrueMaxp TrueMaxpTable{..})
|
|
|
|
= dumpCaption "'maxp' Table - Maximum Profile"
|
|
|
|
<> " 'maxp' version: " <> dumpFixed32 version <> newlineBuilder
|
|
|
|
<> " numGlyphs: " <> Text.Builder.decimal numGlyphs <> newlineBuilder
|
|
|
|
<> " maxPoints: " <> Text.Builder.decimal maxPoints <> newlineBuilder
|
|
|
|
<> " maxContours: " <> Text.Builder.decimal maxContours <> newlineBuilder
|
|
|
|
<> " maxCompositePoints: " <> Text.Builder.decimal maxComponentPoints <> newlineBuilder
|
|
|
|
<> " maxCompositeContours: " <> Text.Builder.decimal maxComponentContours <> newlineBuilder
|
|
|
|
<> " maxZones: " <> Text.Builder.decimal maxZones <> newlineBuilder
|
|
|
|
<> " maxTwilightPoints: " <> Text.Builder.decimal maxTwilightPoints <> newlineBuilder
|
|
|
|
<> " maxStorage: " <> Text.Builder.decimal maxStorage <> newlineBuilder
|
|
|
|
<> " maxFunctionDefs: " <> Text.Builder.decimal maxFunctionDefs <> newlineBuilder
|
|
|
|
<> " maxInstructionDefs: " <> Text.Builder.decimal maxInstructionDefs <> newlineBuilder
|
|
|
|
<> " maxStackElements: " <> Text.Builder.decimal maxStackElements <> newlineBuilder
|
|
|
|
<> " maxSizeOfInstructions: " <> Text.Builder.decimal maxSizeOfInstructions <> newlineBuilder
|
|
|
|
<> " maxComponentElements: " <> Text.Builder.decimal maxComponentElements <> newlineBuilder
|
|
|
|
<> " maxCompoenetDepth: " <> Text.Builder.decimal maxComponentDepth <> newlineBuilder
|
|
|
|
dumpMaxp (OpenMaxp OpenMaxpTable{..})
|
|
|
|
= dumpCaption "'maxp' Table - Maximum Profile"
|
|
|
|
<> " 'maxp' version: " <> dumpFixed32 version <> newlineBuilder <> newlineBuilder
|
|
|
|
<> " numGlyphs: " <> Text.Builder.decimal numGlyphs <> newlineBuilder
|
|
|
|
|
2023-11-12 10:13:38 +01:00
|
|
|
dumpTables
|
2023-11-11 10:57:43 +01:00
|
|
|
:: Megaparsec.State ByteString Void
|
|
|
|
-> FontDirectory
|
2023-11-18 04:40:17 +01:00
|
|
|
-> Either DumpError Text.Builder.Builder
|
2023-11-19 09:42:29 +01:00
|
|
|
dumpTables processedState directory@FontDirectory{..}
|
|
|
|
= parseRequired >>= traverseDirectory
|
2023-11-11 10:57:43 +01:00
|
|
|
where
|
2023-11-19 09:42:29 +01:00
|
|
|
traverseDirectory parsedRequired =
|
2023-11-18 04:40:17 +01:00
|
|
|
let initial = Right $ dumpOffsetTable directory
|
2023-11-19 09:42:29 +01:00
|
|
|
in foldl' (go parsedRequired) initial tableDirectory
|
|
|
|
parseRequired = RequiredTables
|
|
|
|
<$> findRequired "hhea" hheaTableP
|
|
|
|
<*> findRequired "head" headTableP
|
2023-11-18 04:40:17 +01:00
|
|
|
findRequired tableName parser =
|
|
|
|
let missingError = Left $ DumpRequiredTableMissingError tableName
|
2023-11-19 09:42:29 +01:00
|
|
|
parseFound tableEntry = parseTable tableEntry parser processedState
|
|
|
|
in maybe missingError (first DumpParseError . parseFound)
|
2023-11-18 04:40:17 +01:00
|
|
|
$ find ((== Char8.pack tableName) . getField @"tag") tableDirectory
|
|
|
|
go _ (Left accumulator) _ = Left accumulator
|
2023-11-19 09:42:29 +01:00
|
|
|
go parsedRequired (Right accumulator) tableEntry
|
2023-11-18 04:40:17 +01:00
|
|
|
= maybe (Right accumulator) (concatDump accumulator . first DumpParseError)
|
2023-11-19 09:42:29 +01:00
|
|
|
$ dumpSubTable parsedRequired tableEntry
|
2023-11-11 10:57:43 +01:00
|
|
|
concatDump accumulator builderDump = ((accumulator <> newlineBuilder) <>)
|
|
|
|
<$> builderDump
|
2023-11-19 09:42:29 +01:00
|
|
|
dumpSubTable RequiredTables{..} tableEntry =
|
2023-11-11 10:57:43 +01:00
|
|
|
case getField @"tag" tableEntry of
|
|
|
|
"cmap" -> Just $ dumpCmap <$> parseTable tableEntry cmapTableP processedState
|
2023-11-19 09:42:29 +01:00
|
|
|
"head" -> Just $ Right $ dumpHead headTable
|
2023-11-18 04:40:17 +01:00
|
|
|
"hhea" -> Just $ Right $ dumpHhea hheaTable
|
|
|
|
"hmtx" -> Just $ dumpHmtx
|
2023-11-19 09:42:29 +01:00
|
|
|
<$> parseTable tableEntry (hmtxTableP $ getField @"numOfLongHorMetrics" hheaTable) processedState
|
|
|
|
"loca" -> Just $ dumpLoca
|
|
|
|
<$> parseTable tableEntry (locaTableP $ getField @"indexToLocFormat" headTable) processedState
|
2023-11-20 09:33:04 +01:00
|
|
|
"maxp" -> Just $ dumpMaxp <$> parseTable tableEntry maxpTableP processedState
|
2023-11-28 20:02:57 +01:00
|
|
|
"name" -> Just $ dumpName <$> parseTable tableEntry nameTableP processedState
|
2023-11-11 10:57:43 +01:00
|
|
|
_ -> Nothing
|
2023-11-12 10:13:38 +01:00
|
|
|
|
2023-11-18 04:40:17 +01:00
|
|
|
dumpTrueType :: ByteString -> FilePath -> Either DumpError Text.Builder.Builder
|
2023-11-12 10:13:38 +01:00
|
|
|
dumpTrueType ttfContents fontFile =
|
|
|
|
let initialState = Megaparsec.State
|
|
|
|
{ stateInput = ttfContents
|
|
|
|
, stateOffset = 0
|
|
|
|
, statePosState = Megaparsec.PosState
|
|
|
|
{ pstateInput = ttfContents
|
|
|
|
, pstateOffset = 0
|
|
|
|
, pstateSourcePos = Megaparsec.initialPos fontFile
|
|
|
|
, pstateTabWidth = Megaparsec.defaultTabWidth
|
|
|
|
, pstateLinePrefix = ""
|
|
|
|
}
|
|
|
|
, stateParseErrors = []
|
|
|
|
}
|
|
|
|
(processedState, initialResult) = Megaparsec.runParser' fontDirectoryP initialState
|
|
|
|
|
2023-11-18 04:40:17 +01:00
|
|
|
in first DumpParseError initialResult >>= dumpTables processedState
|