Create a Metrics module
This commit is contained in:
@ -114,6 +114,7 @@ import Graphics.Fountainhead.Type
|
||||
( Fixed32(..)
|
||||
, succIntegral
|
||||
, ttfEpoch
|
||||
, newlineBuilder
|
||||
, fixed2Double
|
||||
)
|
||||
import Data.Foldable (Foldable(..), find)
|
||||
@ -160,9 +161,6 @@ justifyNumber count = Text.Builder.fromLazyText
|
||||
. 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
|
||||
@ -288,7 +286,7 @@ longDateTime localTime = Text.Builder.fromLazyText
|
||||
dumpCVTable :: CVTable -> Text.Builder.Builder
|
||||
dumpCVTable (CVTable cvTable) = dumpCaption "'cvt ' Table - Control Value Table"
|
||||
<> "Size = " <> Text.Builder.decimal (tableSize * 2)
|
||||
<> " bytes, " <> Text.Builder.decimal tableSize <> " entries\n"
|
||||
<> " bytes, " <> Text.Builder.decimal tableSize <> " entries" <> newlineBuilder
|
||||
<> foldMap (uncurry go) (zip [0..] cvTable)
|
||||
where
|
||||
tableSize = Prelude.length cvTable
|
||||
|
29
lib/Graphics/Fountainhead/Metrics.hs
Normal file
29
lib/Graphics/Fountainhead/Metrics.hs
Normal file
@ -0,0 +1,29 @@
|
||||
{- 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 OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
|
||||
module Graphics.Fountainhead.Metrics
|
||||
( FontMetrics(..)
|
||||
, afmFontMetrics
|
||||
) where
|
||||
|
||||
import qualified Data.Text.Lazy.Builder as Text.Builder
|
||||
import Data.Version (Version(..), showVersion)
|
||||
import Graphics.Fountainhead.Type (newlineBuilder)
|
||||
|
||||
newtype FontMetrics = FontMetrics
|
||||
{ version :: Version
|
||||
} deriving (Eq, Show)
|
||||
|
||||
afmKeyString :: Text.Builder.Builder -> String -> Text.Builder.Builder
|
||||
afmKeyString key value = key <> Text.Builder.singleton '\t'
|
||||
<> Text.Builder.fromString value <> newlineBuilder
|
||||
|
||||
afmFontMetrics :: FontMetrics -> Text.Builder.Builder
|
||||
afmFontMetrics FontMetrics{..}
|
||||
= afmKeyString "StartFontMetrics" (showVersion version)
|
||||
<> afmKeyString "Comment" "Generated by Fountainhead"
|
||||
<> "EndFontMetrics" <> newlineBuilder
|
@ -9,10 +9,12 @@ module Graphics.Fountainhead.Type
|
||||
, FWord
|
||||
, UFWord
|
||||
, fixed2Double
|
||||
, newlineBuilder
|
||||
, succIntegral
|
||||
, ttfEpoch
|
||||
) where
|
||||
|
||||
import qualified Data.Text.Lazy.Builder as Text.Builder
|
||||
import Data.Bits ((.>>.), (.&.))
|
||||
import Data.Int (Int16)
|
||||
import Data.Word (Word16, Word32)
|
||||
@ -39,3 +41,6 @@ fixed2Double (F2Dot14 fixed) =
|
||||
let mantissa = realToFrac (fixed .>>. 14)
|
||||
fraction = realToFrac (fixed .&. 0x3fff) / 16384.0
|
||||
in mantissa + fraction
|
||||
|
||||
newlineBuilder :: Text.Builder.Builder
|
||||
newlineBuilder = Text.Builder.singleton '\n'
|
||||
|
Reference in New Issue
Block a user