{- 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 #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE LambdaCase #-} -- | Outputs information about a font as text. module Graphics.Fountainhead.Dumper ( ParseErrorOrDump , dumpCmap , dumpHead , dumpTrueType , dumpOffsetTable ) where import Data.ByteString (ByteString) import Data.Int (Int64) import Data.Word (Word16) import qualified Data.IntMap as IntMap 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 import Data.Vector (Vector) import qualified Data.Vector as Vector import Data.Void import GHC.Records (HasField(..)) import Graphics.Fountainhead.TrueType ( CmapTable(..) , FontDirectory(..) , FontDirectionHint(..) , HeadTable(..) , HheaTable(..) , OffsetSubtable(..) , TableDirectory(..) , CmapEncoding(..) , CmapSubtable(..) , CmapFormat4Table(..) , FontStyle(..) ) import qualified Text.Megaparsec as Megaparsec import Graphics.Fountainhead.Parser ( fontDirectoryP , parseTable , cmapTableP , headTableP , hheaTableP ) import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch) import Data.Foldable (Foldable(..)) import Data.Maybe (fromMaybe) import Data.Time (LocalTime(..), NominalDiffTime, diffLocalTime, midnight) import Data.Bits (Bits(..)) type ParseErrorOrDump = Either (Megaparsec.ParseErrorBundle ByteString Void) Text.Builder.Builder paddedHexadecimal :: Integral a => a -> Text.Builder.Builder paddedHexadecimal = ("0x" <>) . Text.Builder.fromLazyText . Text.Lazy.justifyRight 8 '0' . Text.Builder.toLazyText . Text.Builder.hexadecimal halfPaddedHexadecimal :: Integral a => a -> Text.Builder.Builder halfPaddedHexadecimal = Text.Builder.fromLazyText . Text.Lazy.justifyRight 4 '0' . Text.Builder.toLazyText . Text.Builder.hexadecimal 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' dumpCaption :: String -> Text.Builder.Builder dumpCaption headline = Text.Builder.fromString headline <> newlineBuilder <> Text.Builder.fromLazyText (Text.Lazy.replicate headlineLength "-") <> newlineBuilder where headlineLength = fromIntegral $ Prelude.length headline dumpOffsetTable :: FontDirectory -> Text.Builder.Builder dumpOffsetTable directory = dumpCaption "Offset Table" <> " sfnt version: 1.0\n number of tables: " <> Text.Builder.decimal (numTables $ offsetSubtable directory) <> newlineBuilder <> dumpOffsetSummary (tableDirectory directory) where dumpOffsetSummary = mconcat . fmap dumpOffsetRow . zip [0 :: Int ..] 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 dumpFixed32 :: Fixed32 -> Text.Builder.Builder dumpFixed32 (Fixed32 word) = Text.Builder.decimal (shiftR word 16) <> Text.Builder.singleton '.' <> Text.Builder.decimal (word .&. 0xff00) dumpHhea :: HheaTable -> Text.Builder.Builder dumpHhea HheaTable{..} = dumpCaption "'hhea' Table - Font Header" <> " '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 dumpHead :: HeadTable -> Text.Builder.Builder dumpHead HeadTable{..} = dumpCaption "'head' Table - Font Header" <> " head version: " <> dumpFixed32 version <> newlineBuilder <> " fontRevision: " <> dumpFixed32 fontRevision <> newlineBuilder <> " 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 <> " lowestRecPPEM " <> Text.Builder.decimal lowestRecPPEM <> newlineBuilder <> " fontDirectionHint " <> dumpFontDirectionHint fontDirectionHint <> newlineBuilder <> " indexToLocFormat " <> Text.Builder.decimal indexToLocFormat <> newlineBuilder <> " glyphDataFormat " <> Text.Builder.decimal glyphDataFormat <> newlineBuilder dumpFontDirectionHint :: FontDirectionHint -> Text.Builder.Builder dumpFontDirectionHint = \case MixedDirectionalGlyphs -> "0" StronglyLeftToRightGlyphs -> "1" LeftToRightGlyphsWithNeutrals -> "2" StronglyRightToLeftGlyphs -> "-1" RightToLeftGlyphsWithNeutrals -> "-2" dumpFontStyle :: FontStyle -> Text.Builder.Builder dumpFontStyle FontStyle{..} = halfPaddedHexadecimal $ foldr (go . fst) (zeroBits :: Int) $ 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) dumpCmap :: CmapTable -> Text.Builder.Builder dumpCmap CmapTable{..} = dumpCaption "'cmap' Table - Character to Glyph Index Mapping Table" <> " '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 <> snd (foldr dumpCmapSubTable (pred subTablesLength, "") subtables) <> newlineBuilder where encodingsLength = Prelude.length encodings subTablesLength = IntMap.size subtables 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) 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{..}) -> let segCount = Vector.length startCode dumpSegment' = dumpSegment segCount glyphIndexArray 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 <> 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) (CmapFormat6 _) -> "Format 6" (CmapFormat8 _) -> "Format 8" (CmapFormat10 _) -> "Format 10" (CmapFormat12 _) -> "Format 12" (CmapFormat13 _) -> "Format 13" (CmapFormat14 _) -> "Format 14" 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' = " Seg " <> justifyNumber 5 index <> " : St = " <> halfPaddedHexadecimal startCode' <> ", En = " <> halfPaddedHexadecimal endCode' <> ", D = " <> justifyNumber 6 idDelta' <> ", RO = " <> justifyNumber 6 idRangeOffset' <> ", gId# = " <> dumpGlyphId index segCount idRangeOffset' <> newlineBuilder 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 dumpTables :: Megaparsec.State ByteString Void -> FontDirectory -> ParseErrorOrDump dumpTables processedState directory@FontDirectory{..} = foldl' go (Right $ dumpOffsetTable directory) tableDirectory where go :: ParseErrorOrDump -> TableDirectory -> ParseErrorOrDump go (Left accumulator) _ = Left accumulator go (Right accumulator) tableEntry = maybe (Right accumulator) (concatDump accumulator) $ dumpSubTable tableEntry concatDump accumulator builderDump = ((accumulator <> newlineBuilder) <>) <$> builderDump dumpSubTable tableEntry = case getField @"tag" tableEntry of "cmap" -> Just $ dumpCmap <$> parseTable tableEntry cmapTableP processedState "head" -> Just $ dumpHead <$> parseTable tableEntry headTableP processedState "hhea" -> Just $ dumpHhea <$> parseTable tableEntry hheaTableP processedState _ -> Nothing dumpTrueType :: ByteString -> FilePath -> ParseErrorOrDump 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 in initialResult >>= dumpTables processedState