fountainhead/lib/Graphics/Fountainhead/TrueType.hs

1347 lines
46 KiB
Haskell

{- 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 DuplicateRecordFields #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
-- | Types representing a TrueType font.
module Graphics.Fountainhead.TrueType
( BArmStyle(..)
, BContrast(..)
, BFamilyType(..)
, BLetterform(..)
, BMidline(..)
, BProportion(..)
, BSerifStyle(..)
, BStrokeVariation(..)
, BWeight(..)
, BXHeight(..)
, CVTable(..)
, CmapSubtable(..)
, CmapTable(..)
, CmapEncoding(..)
, CmapFormat0Table(..)
, CmapFormat2Subheader(..)
, CmapFormat2Table(..)
, CmapFormat4Table(..)
, CmapFormat6Table(..)
, CmapGroup(..)
, CmapFormat8Table(..)
, CmapFormat10Table(..)
, CmapFormat12Table(..)
, CmapFormat13Table
, CmapFormat14Table(..)
, ComponentGlyphFlags(..)
, ComponentGlyphPartDescription(..)
, CompoundGlyphDefinition(..)
, DeviceRecord(..)
, FpgmTable(..)
, FontDirectionHint(..)
, FontDirectory(..)
, FontStyle(..)
, GASPRange(..)
, GASPTable(..)
, GlyfTable(..)
, GlyphArgument(..)
, GlyphCoordinate(..)
, GlyphDefinition(..)
, GlyphDescription(..)
, GlyphTransformationOption(..)
, HdmxTable(..)
, HeadTable(..)
, HheaTable(..)
, HmtxTable(..)
, IndexToLocFormat(..)
, LocaTable(..)
, LongHorMetric(..)
, MaxpTable(..)
, NameRecord(..)
, NameTable(..)
, OffsetSubtable(..)
, OpenMaxpTable(..)
, Os2BaseFields(..)
, Os2MicrosoftFields(..)
, Os2Table(..)
, Os2Version1Fields(..)
, Os2Version4Fields(..)
, Os2Version5Fields(..)
, OutlineFlag(..)
, Panose(..)
, PostFormat2Table(..)
, PostHeader(..)
, PostSubtable(..)
, PostTable(..)
, PrepTable(..)
, RangeGaspBehavior(..)
, SimpleGlyphDefinition(..)
, TableDirectory(..)
, TrueMaxpTable(..)
, UVSOffset(..)
, UVSMapping(..)
, UnicodeValueRange(..)
, VariationSelectorMap
, findTableByTag
, unLocaTable
, nameStringOffset
, pattern Os2Version4CommonFields
) where
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as Char8
import Data.Int (Int8, Int16)
import Data.IntMap (IntMap)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Time (LocalTime(..))
import Data.Vector (Vector)
import Data.Word (Word8, Word16, Word32)
import Graphics.Fountainhead.Type (F2Dot14(..), Fixed32(..), FWord, UFWord)
import GHC.Records (HasField(..))
import Data.Foldable (find)
-- * Font directory
data FontDirectory = FontDirectory
{ offsetSubtable :: OffsetSubtable
, tableDirectory :: [TableDirectory]
} deriving (Eq, Show)
findTableByTag :: String -> FontDirectory -> Maybe TableDirectory
findTableByTag needle = find ((needle ==) . Char8.unpack . getField @"tag")
. getField @"tableDirectory"
data OffsetSubtable = OffsetSubtable
{ scalerType :: Word32
, numTables :: Int
, searchRange :: Word16
, entrySelector :: Word16
, rangeShift :: Word16
} deriving (Eq, Show)
data TableDirectory = TableDirectory
{ tag :: ByteString
, checkSum :: Word32
, offset :: Int
, length :: Int
} deriving (Eq, Show)
-- * Name table
data NameTable = NameTable
{ format :: Word16 -- ^ Format selector. Set to 0.
, nameRecord :: [NameRecord] -- ^ The name records array.
, variable :: [ByteString] -- ^ The character strings of the names.
} deriving (Eq, Show)
data NameRecord = NameRecord
{ platformID :: Word16 -- ^ Platform identifier code.
, platformSpecificID :: Word16 -- ^ Platform-specific encoding identifier.
, languageID :: Word16 -- ^ Language identifier.
, nameID :: Word16 -- ^ Name identifier.
, length :: Int -- ^ Name string length in bytes.
, offset :: Int -- ^ Offset.
} deriving (Eq, Show)
nameStringOffset :: NameTable -> Word16
nameStringOffset NameTable{..} =
let nameRecordSize = 12
precedingFieldsSize = 2 * 3
in nameRecordSize * fromIntegral (Prelude.length nameRecord) + precedingFieldsSize
-- * 'cvt ' table
newtype CVTable = CVTable [Int16]
deriving (Eq, Show)
-- * Maximum profile table
data TrueMaxpTable = TrueMaxpTable
{ version :: Fixed32 -- ^ 0x00010000 (1.0).
, numGlyphs :: Word16 -- ^ The number of glyphs in the font.
, maxPoints :: Word16 -- ^ Points in non-compound glyph.
, maxContours :: Word16 -- ^ Contours in non-compound glyph.
, maxComponentPoints :: Word16 -- ^ Points in compound glyph.
, maxComponentContours :: Word16 -- ^ Contours in compound glyph.
, maxZones :: Word16 -- ^ Set to 2.
, maxTwilightPoints :: Word16 -- ^ Points used in Twilight Zone (Z0).
, maxStorage :: Word16 -- ^ Number of Storage Area locations.
, maxFunctionDefs :: Word16 -- ^ Number of FDEFs.
, maxInstructionDefs :: Word16 -- ^ Number of IDEFs.
, maxStackElements :: Word16 -- ^ Maximum stack depth.
, maxSizeOfInstructions :: Word16 -- ^ Byte count for glyph instructions.
, maxComponentElements :: Word16 -- ^ Number of glyphs referenced at top level.
, maxComponentDepth :: Word16 -- ^ Levels of recursion, set to 0 if font has only simple glyphs.
} deriving (Eq, Show)
data OpenMaxpTable = OpenMaxpTable
{ version :: Fixed32 -- ^ 0x00005000 (0.5).
, numGlyphs :: Word16 -- ^ The number of glyphs in the font.
} deriving (Eq, Show)
data MaxpTable = OpenMaxp OpenMaxpTable | TrueMaxp TrueMaxpTable
deriving (Eq, Show)
-- * Horizontal header table
data HheaTable = HheaTable
{ version :: Fixed32 -- ^ 0x00010000 (1.0).
, ascent :: FWord -- ^ Distance from baseline of highest ascender.
, descent :: FWord -- ^ Distance from baseline of lowest descender.
, lineGap :: FWord -- ^ Typographic line gap.
, advanceWidthMax :: UFWord -- ^ Must be consistent with horizontal metrics.
, minLeftSideBearing :: FWord -- ^ Must be consistent with horizontal metrics.
, minRightSideBearing :: FWord -- ^ Must be consistent with horizontal metrics.
, xMaxExtent :: FWord -- ^ max(lsb + (xMax-xMin)).
, caretSlopeRise :: Int16 -- ^ used to calculate the slope of the caret (rise/run) set to 1 for vertical caret.
, caretSlopeRun :: Int16 -- ^ 0 for vertical.
, caretOffset :: FWord -- ^ Set value to 0 for non-slanted fonts.
, metricDataFormat :: Int16 -- ^ 0 for current format.
, numOfLongHorMetrics :: Word16 -- ^ Number of advance widths in metrics table.
} deriving (Eq, Show)
-- * Font header table
data IndexToLocFormat
= ShortOffsetIndexToLocFormat
| LongOffsetIndexToLocFormat
deriving (Eq, Show)
data HeadTable = HeadTable
{ version :: Fixed32 -- ^ 0x00010000 if (version 1.0).
, fontRevision :: Fixed32 -- ^ Set by font manufacturer.
, checkSumAdjustment :: Word32 -- ^ To compute: set it to 0, calculate the checksum for the 'head' table and put it in the table directory, sum the entire font as a uint32_t, then store 0xB1B0AFBA - sum. (The checksum for the 'head' table will be wrong as a result. That is OK; do not reset it.)
, magicNumber :: Word32 -- ^ Set to 0x5F0F3CF5.
, flags :: Word16
, unitsPerEm :: Word16 -- ^ Range from 64 to 16384.
, created :: LocalTime -- ^ International date.
, modified :: LocalTime -- ^ International date.
, xMin :: Int16 -- ^ For all glyph bounding boxes.
, yMin :: Int16 -- ^ For all glyph bounding boxes.
, xMax :: Int16 -- ^ For all glyph bounding boxes.
, yMax :: Int16 -- ^ For all glyph bounding boxes.
, macStyle :: FontStyle
, lowestRecPPEM :: Word16 -- ^ Smallest readable size in pixels.
, fontDirectionHint :: FontDirectionHint -- ^ 0 Mixed directional glyphs.
, indexToLocFormat :: IndexToLocFormat -- ^ 0 for short offsets, 1 for long.
, glyphDataFormat :: Word16 -- ^ 0 for current format.
} deriving (Eq, Show)
data FontStyle = FontStyle
{ bold :: Bool
, italic :: Bool
, underline :: Bool
, outline :: Bool
, shadow :: Bool
, condensed :: Bool
, extended :: Bool
} deriving (Eq, Show)
data FontDirectionHint
= MixedDirectionalGlyphs -- ^ 0. Mixed directional glyphs.
| StronglyLeftToRightGlyphs -- ^ 1. Only strongly left to right glyphs.
| LeftToRightGlyphsWithNeutrals -- ^ 2. Like 1 but also contains neutrals.
| StronglyRightToLeftGlyphs -- ^ -1. Only strongly right to left glyphs.
| RightToLeftGlyphsWithNeutrals -- ^ -2. Like -1 but also contains neutrals.
deriving (Eq, Show)
data LocaTable
= ShortLocaTable (Vector Word16)
| LongLocaTable (Vector Word32)
deriving (Eq, Show)
unLocaTable :: LocaTable -> Vector Word32
unLocaTable (LongLocaTable values') = values'
unLocaTable (ShortLocaTable values') = (* 2) . fromIntegral <$> values'
-- * Horizontal metrics table
data LongHorMetric = LongHorMetric
{ advanceWidth :: Word16
, leftSideBearing :: Int16
} deriving (Eq, Show)
data HmtxTable = HmtxTable
{ hMetrics :: NonEmpty LongHorMetric
, leftSideBearing :: [Int16]
} deriving (Eq, Show)
-- * Glyph name and PostScript font table
data PostHeader = PostHeader
{ format :: Fixed32 -- ^ Format of this table
, italicAngle :: Fixed32 -- ^ Italic angle in degrees
, underlinePosition :: Int16 -- ^ Underline position
, underlineThickness :: Int16 -- ^ Underline thickness
, isFixedPitch :: Word32 -- ^ Font is monospaced; set to 1 if the font is monospaced and 0 otherwise (N.B., to maintain compatibility with older versions of the TrueType spec, accept any non-zero value as meaning that the font is monospaced)
, minMemType42 :: Word32 -- ^ Minimum memory usage when a TrueType font is downloaded as a Type 42 font
, maxMemType42 :: Word32 -- ^ Maximum memory usage when a TrueType font is downloaded as a Type 42 font
, minMemType1 :: Word32 -- ^ Minimum memory usage when a TrueType font is downloaded as a Type 1 font
, maxMemType1 :: Word32 -- ^ Maximum memory usage when a TrueType font is downloaded as a Type 1 font
} deriving (Eq, Show)
data PostFormat2Table = PostFormat2Table
{ glyphNameIndex :: Vector Word16 -- ^ Ordinal number of this glyph in 'post' string tables. This is not an offset.
, names :: Vector ByteString
} deriving (Eq, Show)
data PostSubtable
= None
| PostFormat2 PostFormat2Table
| PostFormat25 (Vector Int8)
| PostFormat4 (Vector Word16)
deriving (Eq, Show)
data PostTable = PostTable
{ postHeader :: PostHeader
, postSubtable :: PostSubtable
} deriving (Eq, Show)
-- * Font program table
newtype FpgmTable = FpgmTable (Vector Word8)
deriving (Eq, Show)
-- * Prep table
newtype PrepTable = PrepTable (Vector Word8)
deriving (Eq, Show)
-- * Horizontal device metrics table
data HdmxTable = HdmxTable
{ format :: Int16 -- ^ Format version number.
, records :: [DeviceRecord]
} deriving (Eq, Show)
data DeviceRecord = DeviceRecord
{ pixelSize :: Word8 -- ^ Pixel size for following widths.
, maximumWidth :: Word8 -- ^ Maximum width.
, widths :: Vector Word8 -- ^ Widths.
} deriving (Eq, Show)
-- * Glyph outline table
data GlyphDescription = GlyphDescription
{ numberOfContours :: Int
, xMin :: Int16 -- ^ Minimum x for coordinate data.
, yMin :: Int16 -- ^ Minimum y for coordinate data.
, xMax :: Int16 -- ^ Maximum x for coordinate data.
, yMax :: Int16 -- ^ Maximum y for coordinate data.
, definition :: GlyphDefinition
} deriving (Eq, Show)
data GlyphArgument
= GlyphInt16Argument Int16
| GlyphWord16Argument Word16
| GlyphInt8Argument Int8
| GlyphWord8Argument Word8
deriving (Eq, Show)
data GlyphTransformationOption
= GlyphNoScale
| GlyphScale F2Dot14
| GlyphXyScale F2Dot14 F2Dot14
| Glyph2By2Scale F2Dot14 F2Dot14 F2Dot14 F2Dot14
deriving (Eq, Show)
data SimpleGlyphDefinition = SimpleGlyphDefinition
-- | Array of last points of each contour; n is the number of contours;
-- array entries are point indices.
{ endPtsOfContours :: Vector Word16
-- | Array of instructions for this glyph.
, instructions :: Vector Word8
-- Array of flags.
, flags :: Vector OutlineFlag
-- | Array of coordinates; the first is relative to (0,0), others are
-- relative to previous point.
, coordinates :: Vector GlyphCoordinate
} deriving (Eq, Show)
data CompoundGlyphDefinition = CompoundGlyphDefinition
{ components :: Vector ComponentGlyphPartDescription
, instructions :: Vector Word8
} deriving (Eq, Show)
data GlyphDefinition
= SimpleGlyph SimpleGlyphDefinition
| CompoundGlyph CompoundGlyphDefinition
deriving (Eq, Show)
data ComponentGlyphFlags = ComponentGlyphFlags
{ roundXyToGrid :: Bool
, weHaveInstructions :: Bool
, useMyMetrics :: Bool
, overlapCompound :: Bool
} deriving (Eq, Show)
data GlyphCoordinate = GlyphCoordinate
{ coordinateX :: Int16
, coordinateY :: Int16
} deriving (Eq, Show)
instance Semigroup GlyphCoordinate
where
lhs <> rhs =
let GlyphCoordinate{ coordinateX = lhX, coordinateY = lhY } = lhs
GlyphCoordinate{ coordinateX = rhX, coordinateY = rhY } = rhs
in GlyphCoordinate{ coordinateX = lhX + rhX, coordinateY = lhY + rhY }
instance Monoid GlyphCoordinate
where
mempty = GlyphCoordinate 0 0
data ComponentGlyphPartDescription = ComponentGlyphPartDescription
{ flags :: ComponentGlyphFlags
, glyphIndex :: Word16
, argument1 :: GlyphArgument
, argument2 :: GlyphArgument
, transformationOption :: GlyphTransformationOption
} deriving (Eq, Show)
-- * Glyph outline table
data OutlineFlag = OutlineFlag
{ onCurve :: Bool
, xShortVector :: Bool
, yShortVector :: Bool
, repeat :: Word8
, thisXIsSame :: Bool
, thisYIsSame :: Bool
} deriving (Eq, Show)
newtype GlyfTable = GlyfTable (Vector GlyphDescription)
deriving (Eq, Show)
-- 'cmap' table
-- | Character to glyph mapping table.
data CmapTable = CmapTable
{ version :: Word16 -- ^ Version number is zero.
-- | Encodings with an offset into subtables map.
, encodings :: [CmapEncoding]
-- ^ The key into the map is the offset in the 'CmapEncoding's.
, subtables :: IntMap CmapSubtable
} deriving (Eq, Show)
data CmapEncoding = CmapEncoding
{ platformID :: Word16 -- ^ Platform identifier
, platformSpecificID :: Word16 -- ^ Platform-specific encoding identifier.
, offset :: Word32 -- ^ Offst of the mapping table.
} deriving (Eq, Show)
data CmapFormat0Table = CmapFormat0Table
{ language :: Word16 -- ^ Language code.
, glyphIndexArray :: Vector Word8 -- ^ An array that maps character codes to glyph index values.
} deriving (Eq, Show)
data CmapFormat2Subheader = CmapFormat2Subheader
{ firstCode :: Word16
, entryCount :: Word16
, idDelta :: Int16
, idRangeOffset :: Word16
} deriving (Eq, Show)
data CmapFormat2Table = CmapFormat2Table
{ language :: Word16 -- ^ Language code.
, subHeaderKeys :: Vector Word16 -- ^ Array that maps high bytes to subHeaders: value is index * 8.
, subHeaders :: Vector CmapFormat2Subheader -- ^ Variable length array of subHeader structures.
, glyphIndexArray :: Vector Word16 -- ^ Variable length array containing subarrays.
} deriving (Eq, Show)
data CmapFormat4Table = CmapFormat4Table
{ language :: Word16 -- ^ Language code.
, searchRange :: Word16 -- ^ 2 * (2**FLOOR(log2(segCount))).
, entrySelector :: Word16 -- ^ log2(searchRange/2).
, rangeShift :: Word16 -- ^ (2 * segCount) - searchRange.
, endCode :: Vector Word16 -- ^ Ending character code for each segment, last = 0xFFFF.
, startCode :: Vector Word16 -- ^ Starting character code for each segment.
, idDelta :: Vector Word16 -- ^ Delta for all character codes in segment.
, idRangeOffset :: Vector Word16 -- ^ Offset in bytes to glyph indexArray, or 0.
, glyphIndexArray :: Vector Word16 -- ^ Glyph index array.
} deriving (Eq, Show)
data CmapFormat6Table = CmapFormat6Table
{ language :: Word16 -- ^ Language code.
, firstCode :: Word16 -- ^ First character code of subrange.
, glyphIndexArray :: Vector Word16 -- ^ Array of glyph index values for character codes in the range
} deriving (Eq, Show)
data CmapGroup = CmapGroup
-- | First character code in this group; note that if this group is for one
-- or more 16-bit character codes (which is determined from the is32 array),
-- this 32-bit value will have the high 16-bits set to zero.
{ startCharCode :: Word32
-- | Last character code in this group; same condition as listed above for
-- the startCharCode.
, endCharCode :: Word32
-- | Glyph index corresponding to the starting character code.
, startGlyphCode :: Word32
} deriving (Eq, Show)
data CmapFormat8Table = CmapFormat8Table
{ language :: Word32 -- ^ Language code.
-- | Tightly packed array of bits (8K bytes total) indicating whether the
-- particular 16-bit (index) value is the start of a 32-bit character code.
, is32 :: [Word8]
-- | Word32 Number of groupings which follow.
, groups :: Vector CmapGroup
} deriving (Eq, Show)
data CmapFormat10Table = CmapFormat10Table
{ language :: Word32 -- ^ Language code.
, startCharCode :: Word32 -- ^ First character code covered.
, numChars :: Word32 -- ^ Number of character codes covered.
, glyphs :: Vector Word16 -- ^ Array of glyph indices for the character codes covered.
} deriving (Eq, Show)
data CmapFormat12Table = CmapFormat12Table
{ language :: Word32 -- ^ Language code.
, groups :: Vector CmapGroup
} deriving (Eq, Show)
type CmapFormat13Table = CmapFormat12Table
newtype CmapFormat14Table = CmapFormat14Table
{ varSelectorRecords :: VariationSelectorMap
} deriving (Eq, Show)
data CmapSubtable
= CmapFormat0 CmapFormat0Table
| CmapFormat2 CmapFormat2Table
| CmapFormat4 CmapFormat4Table
| CmapFormat6 CmapFormat6Table
| CmapFormat8 CmapFormat8Table
| CmapFormat10 CmapFormat10Table
| CmapFormat12 CmapFormat12Table
| CmapFormat13 CmapFormat13Table
| CmapFormat14 CmapFormat14Table
deriving (Eq, Show)
data UVSOffset a b = DefaultUVSOffset Word32 a | NonDefaultUVSOffset Word32 b
deriving (Eq, Show)
data UVSMapping = UVSMapping
{ unicodeValue :: Word32 -- ^ Base Unicode value of the UVS.
, glyphID :: Word16 -- ^ Glyph ID of the UVS.
} deriving (Eq, Show)
data UnicodeValueRange = UnicodeValueRange
{ startUnicodeValue :: Word32 -- ^ First value in this range.
, additionalCount :: Word8 -- ^ Number of additional values in this range.
} deriving (Eq, Show)
-- | Mapping from variation selector record offsets to the record data.
type VariationSelectorMap = IntMap
(NonEmpty (UVSOffset (Vector UnicodeValueRange) (Vector UVSMapping)))
-- * OS/2 table
data Os2Table
= Os2Version0 Os2BaseFields (Maybe Os2MicrosoftFields)
| Os2Version1 Os2BaseFields Os2MicrosoftFields Os2Version1Fields
| Os2Version2 Os2BaseFields Os2MicrosoftFields Os2Version4Fields
| Os2Version3 Os2BaseFields Os2MicrosoftFields Os2Version4Fields
| Os2Version4 Os2BaseFields Os2MicrosoftFields Os2Version4Fields
| Os2Version5 Os2BaseFields Os2MicrosoftFields Os2Version5Fields
deriving (Eq, Show)
pattern Os2Version4CommonFields :: Os2BaseFields -> Os2Version4Fields -> Os2Table
pattern Os2Version4CommonFields baseFields versionFields <-
(os2Version4CommonFields -> Just (baseFields, versionFields))
{-# COMPLETE Os2Version4CommonFields, Os2Version0, Os2Version1, Os2Version5 #-}
os2Version4CommonFields :: Os2Table -> Maybe (Os2BaseFields, Os2Version4Fields)
os2Version4CommonFields = \case
Os2Version0{} -> Nothing
Os2Version1{} -> Nothing
Os2Version2 baseFields _ versionFields -> Just (baseFields, versionFields)
Os2Version3 baseFields _ versionFields -> Just (baseFields, versionFields)
Os2Version4 baseFields _ versionFields -> Just (baseFields, versionFields)
Os2Version5{} -> Nothing
data Os2Version1Fields = Os2Version1Fields
{ ulCodePageRange1 :: Word32
, ulCodePageRange2 :: Word32
} deriving (Eq, Show)
data Os2MicrosoftFields = Os2MicrosoftFields
{ sTypoAscender :: Int16
, sTypoDescender :: Int16
, sTypoLineGap :: Int16
, usWinAscent :: Word16
, usWinDescent :: Word16
} deriving (Eq, Show)
data Os2Version4Fields = Os2Version4Fields
{ ulCodePageRange1 :: Word32
, ulCodePageRange2 :: Word32
, sxHeight :: Int16
, sCapHeight :: Int16
, usDefaultChar :: Word16
, usBreakChar :: Word16
, usMaxContext :: Word16
} deriving (Eq, Show)
data Os2Version5Fields = Os2Version5Fields
{ ulCodePageRange1 :: Word32
, ulCodePageRange2 :: Word32
, sxHeight :: Int16
, sCapHeight :: Int16
, usDefaultChar :: Word16
, usBreakChar :: Word16
, usMaxContext :: Word16
, usLowerOpticalPointSize :: Word16
, usUpperOpticalPointSize :: Word16
} deriving (Eq, Show)
data Os2BaseFields = Os2BaseFields
{ version :: Word16 -- ^ Table version number (set to 0).
-- | Average weighted advance width of lower case letters and space.
, xAvgCharWidth :: Int16
-- | Visual weight (degree of blackness or thickness) of stroke in glyphs.
, usWeightClass :: Word16
-- | Relative change from the normal aspect ratio (width to height ratio)
-- as specified by a font designer for the glyphs in the font.
, usWidthClass :: Word16
-- | Characteristics and properties of this font (set undefined bits to
-- zero).
, fsType :: Int16
-- | Recommended horizontal size in pixels for subscripts.
, ySubscriptXSize :: Int16
-- | Recommended vertical size in pixels for subscripts.
, ySubscriptYSize :: Int16
-- | Recommended horizontal offset for subscripts.
, ySubscriptXOffset :: Int16
-- | Recommended vertical offset form the baseline for subscripts.
, ySubscriptYOffset :: Int16
-- | Recommended horizontal size in pixels for superscripts.
, ySuperscriptXSize :: Int16
-- | Recommended vertical size in pixels for superscripts.
, ySuperscriptYSize :: Int16
-- | Recommended horizontal offset for superscripts.
, ySuperscriptXOffset :: Int16
-- | Recommended vertical offset from the baseline for superscripts.
, ySuperscriptYOffset :: Int16
-- | Width of the strikeout stroke.
, yStrikeoutSize :: Int16
-- | Position of the strikeout stroke relative to the baseline.
, yStrikeoutPosition :: Int16
-- ^ Classification of font-family design.
, sFamilyClass :: Int16
-- | 10 byte series of number used to describe the visual characteristics
-- of a given typeface.
, panose :: Panose
-- | Field is split into two bit fields of 96 and 36 bits each. The low 96
-- bits are used to specify the Unicode blocks encompassed by the font file.
-- The high 32 bits are used to specify the character or script sets covered
-- by the font file. Bit assignments are pending. Set to 0.
, ulUnicodeRange :: Vector Word32
-- | Four character identifier for the font vendor.
, achVendID :: Vector Int8
-- | 2-byte bit field containing information concerning the nature of the
-- font patterns.
, fsSelection :: Word16
-- | The minimum Unicode index in this font.
, fsFirstCharIndex :: Word16
-- | The maximum Unicode index in this font.
, fsLastCharIndex :: Word16
} deriving (Eq, Show)
data Panose = Panose
{ bFamilyType :: BFamilyType
, bSerifStyle :: BSerifStyle
, bWeight :: BWeight
, bProportion :: BProportion
, bContrast :: BContrast
, bStrokeVariation :: BStrokeVariation
, bArmStyle :: BArmStyle
, bLetterform :: BLetterform
, bMidline :: BMidline
, bXHeight :: BXHeight
} deriving (Eq, Show)
data BFamilyType
= AnyFamilyType
| NoFitFamilyType
| TextAndDisplayFamilyType
| ScriptFamilyType
| DecorativeFamilyType
| PictorialFamilyType
deriving Eq
instance Show BFamilyType
where
show AnyFamilyType = "Any"
show NoFitFamilyType = "No Fit"
show TextAndDisplayFamilyType = "Text and Display"
show ScriptFamilyType = "Script"
show DecorativeFamilyType = "Decorative"
show PictorialFamilyType = "Pictorial"
instance Enum BFamilyType
where
toEnum 0 = AnyFamilyType
toEnum 1 = NoFitFamilyType
toEnum 2 = TextAndDisplayFamilyType
toEnum 3 = ScriptFamilyType
toEnum 4 = DecorativeFamilyType
toEnum 5 = PictorialFamilyType
toEnum _ = error "Unknown family type"
fromEnum AnyFamilyType = 0
fromEnum NoFitFamilyType = 1
fromEnum TextAndDisplayFamilyType = 2
fromEnum ScriptFamilyType = 3
fromEnum DecorativeFamilyType = 4
fromEnum PictorialFamilyType = 5
data BSerifStyle
= AnySerifStyle
| NoFitSerifStyle
| CoveSerifStyle
| ObtuseCoveSerifStyle
| SquareCoveSerifStyle
| ObtuseSquareCoveSerifStyle
| SquareSerifStyle
| ThinSerifStyle
| BoneSerifStyle
| ExaggeratedSerifStyle
| TriangleSerifStyle
| NormalSansSerifStyle
| ObtuseSansSerifStyle
| PerpSansSerifStyle
| FlaredSerifStyle
| RoundedSerifStyle
deriving Eq
instance Show BSerifStyle
where
show AnySerifStyle = "Any"
show NoFitSerifStyle = "No Fit"
show CoveSerifStyle = "Cove"
show ObtuseCoveSerifStyle = "Obtuse Cove"
show SquareCoveSerifStyle = "Square Cove"
show ObtuseSquareCoveSerifStyle = "Obtuse Square Cove"
show SquareSerifStyle = "Square"
show ThinSerifStyle = "Thin"
show BoneSerifStyle = "Bone"
show ExaggeratedSerifStyle = "Exaggerated"
show TriangleSerifStyle = "Triangle"
show NormalSansSerifStyle = "Normal Sans"
show ObtuseSansSerifStyle = "Obtuse Sans"
show PerpSansSerifStyle = "Perp Sans"
show FlaredSerifStyle = "Flared"
show RoundedSerifStyle = "Rounded"
instance Enum BSerifStyle
where
toEnum 0 = AnySerifStyle
toEnum 1 = NoFitSerifStyle
toEnum 2 = CoveSerifStyle
toEnum 3 = ObtuseCoveSerifStyle
toEnum 4 = SquareCoveSerifStyle
toEnum 5 = ObtuseSquareCoveSerifStyle
toEnum 6 = SquareSerifStyle
toEnum 7 = ThinSerifStyle
toEnum 8 = BoneSerifStyle
toEnum 9 = ExaggeratedSerifStyle
toEnum 10 = TriangleSerifStyle
toEnum 11 = NormalSansSerifStyle
toEnum 12 = ObtuseSansSerifStyle
toEnum 13 = PerpSansSerifStyle
toEnum 14 = FlaredSerifStyle
toEnum 15 = RoundedSerifStyle
toEnum _ = error "Unknown serif type"
fromEnum AnySerifStyle = 0
fromEnum NoFitSerifStyle = 1
fromEnum CoveSerifStyle = 2
fromEnum ObtuseCoveSerifStyle = 3
fromEnum SquareCoveSerifStyle = 4
fromEnum ObtuseSquareCoveSerifStyle = 5
fromEnum SquareSerifStyle = 6
fromEnum ThinSerifStyle = 7
fromEnum BoneSerifStyle = 8
fromEnum ExaggeratedSerifStyle = 9
fromEnum TriangleSerifStyle = 10
fromEnum NormalSansSerifStyle = 11
fromEnum ObtuseSansSerifStyle = 12
fromEnum PerpSansSerifStyle = 13
fromEnum FlaredSerifStyle = 14
fromEnum RoundedSerifStyle = 15
data BWeight
= AnyWeight
| NoFitWeight
| VeryLightWeight
| LightWeight
| ThinWeight
| BookWeight
| MediumWeight
| DemiWeight
| BoldWeight
| HeavyWeight
| BlackWeight
| NordWeight
deriving Eq
instance Show BWeight
where
show AnyWeight = "Any"
show NoFitWeight = "No Fit"
show VeryLightWeight = "Very Light"
show LightWeight = "Light"
show ThinWeight = "Thin"
show BookWeight = "Book"
show MediumWeight = "Medium"
show DemiWeight = "Demi"
show BoldWeight = "Bold"
show HeavyWeight = "Heavy"
show BlackWeight = "Black"
show NordWeight = "Nord"
instance Enum BWeight
where
fromEnum AnyWeight = 0
fromEnum NoFitWeight = 1
fromEnum VeryLightWeight = 2
fromEnum LightWeight = 3
fromEnum ThinWeight = 4
fromEnum BookWeight = 5
fromEnum MediumWeight = 6
fromEnum DemiWeight = 7
fromEnum BoldWeight = 8
fromEnum HeavyWeight = 9
fromEnum BlackWeight = 10
fromEnum NordWeight = 11
toEnum 0 = AnyWeight
toEnum 1 = NoFitWeight
toEnum 2 = VeryLightWeight
toEnum 3 = LightWeight
toEnum 4 = ThinWeight
toEnum 5 = BookWeight
toEnum 6 = MediumWeight
toEnum 7 = DemiWeight
toEnum 8 = BoldWeight
toEnum 9 = HeavyWeight
toEnum 10 = BlackWeight
toEnum 11 = NordWeight
toEnum _ = error "Unknown weight"
data BProportion
= AnyProportion
| NoFitProportion
| OldStyleProportion
| ModernProportion
| EvenWidthProportion
| ExpandedProportion
| CondensedProportion
| VeryExpandedProportion
| VeryCondensedProportion
| MonospacedProportion
deriving Eq
instance Show BProportion
where
show AnyProportion = "Any"
show NoFitProportion = "No Fit"
show OldStyleProportion = "Old Style"
show ModernProportion = "Modern"
show EvenWidthProportion = "Even Width"
show ExpandedProportion = "Expanded"
show CondensedProportion = "Condensed"
show VeryExpandedProportion = "Very Expanded"
show VeryCondensedProportion = "Very Condensed"
show MonospacedProportion = "Monospaced"
instance Enum BProportion
where
fromEnum AnyProportion = 0
fromEnum NoFitProportion = 1
fromEnum OldStyleProportion = 2
fromEnum ModernProportion = 3
fromEnum EvenWidthProportion = 4
fromEnum ExpandedProportion = 5
fromEnum CondensedProportion = 6
fromEnum VeryExpandedProportion = 7
fromEnum VeryCondensedProportion = 8
fromEnum MonospacedProportion = 9
toEnum 0 = AnyProportion
toEnum 1 = NoFitProportion
toEnum 2 = OldStyleProportion
toEnum 3 = ModernProportion
toEnum 4 = EvenWidthProportion
toEnum 5 = ExpandedProportion
toEnum 6 = CondensedProportion
toEnum 7 = VeryExpandedProportion
toEnum 8 = VeryCondensedProportion
toEnum 9 = MonospacedProportion
toEnum _ = error "Unknown proportion"
data BContrast
= AnyContrast
| NoFitContrast
| NoneContrast
| VeryLowContrast
| LowContrast
| MediumLowContrast
| MediumContrast
| MediumHighContrast
| HighContrast
| VeryHighContrast
deriving Eq
instance Show BContrast
where
show AnyContrast = "Any"
show NoFitContrast = "No Fit"
show NoneContrast = "None"
show VeryLowContrast = "Very Low"
show LowContrast = "Low"
show MediumLowContrast = "Medium Low"
show MediumContrast = "Medium"
show MediumHighContrast = "Medium High"
show HighContrast = "High"
show VeryHighContrast = "Very High"
instance Enum BContrast
where
fromEnum AnyContrast = 0
fromEnum NoFitContrast = 1
fromEnum NoneContrast = 2
fromEnum VeryLowContrast = 3
fromEnum LowContrast = 4
fromEnum MediumLowContrast = 5
fromEnum MediumContrast = 6
fromEnum MediumHighContrast = 7
fromEnum HighContrast = 8
fromEnum VeryHighContrast = 9
toEnum 0 = AnyContrast
toEnum 1 = NoFitContrast
toEnum 2 = NoneContrast
toEnum 3 = VeryLowContrast
toEnum 4 = LowContrast
toEnum 5 = MediumLowContrast
toEnum 6 = MediumContrast
toEnum 7 = MediumHighContrast
toEnum 8 = HighContrast
toEnum 9 = VeryHighContrast
toEnum _ = error "Unknown contrast"
data BStrokeVariation
= AnyStrokeVariation
| NoFitStrokeVariation
| GradualDiagonalStrokeVariation
| GradualTransitionalStrokeVariation
| GradualVerticalStrokeVariation
| GradualHorizontalStrokeVariation
| RapidVerticalStrokeVariation
| RapidHorizontalStrokeVariation
| InstantVerticalStrokeVariation
deriving Eq
instance Show BStrokeVariation
where
show AnyStrokeVariation = "Any"
show NoFitStrokeVariation = "No Fit"
show GradualDiagonalStrokeVariation = "Gradual/Diagonal"
show GradualTransitionalStrokeVariation = "Gradual/Transitional"
show GradualVerticalStrokeVariation = "Gradual/Vertical"
show GradualHorizontalStrokeVariation = "Gradual/Horizontal"
show RapidVerticalStrokeVariation = "Rapid/Vertical"
show RapidHorizontalStrokeVariation = "Rapid/Horizontal"
show InstantVerticalStrokeVariation = "Instant/Vertical"
instance Enum BStrokeVariation
where
fromEnum AnyStrokeVariation = 0
fromEnum NoFitStrokeVariation = 1
fromEnum GradualDiagonalStrokeVariation = 2
fromEnum GradualTransitionalStrokeVariation = 3
fromEnum GradualVerticalStrokeVariation = 4
fromEnum GradualHorizontalStrokeVariation = 5
fromEnum RapidVerticalStrokeVariation = 6
fromEnum RapidHorizontalStrokeVariation = 7
fromEnum InstantVerticalStrokeVariation = 8
toEnum 0 = AnyStrokeVariation
toEnum 1 = NoFitStrokeVariation
toEnum 2 = GradualDiagonalStrokeVariation
toEnum 3 = GradualTransitionalStrokeVariation
toEnum 4 = GradualVerticalStrokeVariation
toEnum 5 = GradualHorizontalStrokeVariation
toEnum 6 = RapidVerticalStrokeVariation
toEnum 7 = RapidHorizontalStrokeVariation
toEnum 8 = InstantVerticalStrokeVariation
toEnum _ = error "Unknown stroke variation"
data BArmStyle
= AnyArmStyle
| NoFitArmStyle
| StraightArmsHorizontalArmStyle
| StraightArmsWedgeArmStyle
| StraightArmsVerticalArmStyle
| StraightArmsSingleSerifArmStyle
| StraightArmsDoubleSerifArmStyle
| NonStraightArmsHorizontalArmStyle
| NonStraightArmsWedgeArmStyle
| NonStraightArmsVerticalArmStyle
| NonStraightArmsSingleSerifArmStyle
| NonStraightArmsDoubleSerifArmStyle
deriving Eq
instance Show BArmStyle
where
show AnyArmStyle = "Any"
show NoFitArmStyle = "No Fit"
show StraightArmsHorizontalArmStyle = "Straight Arms/Horizontal"
show StraightArmsWedgeArmStyle = "Straight Arms/Wedge"
show StraightArmsVerticalArmStyle = "Straight Arms/Vertical"
show StraightArmsSingleSerifArmStyle = "Straight Arms/Single Serif"
show StraightArmsDoubleSerifArmStyle = "Straight Arms/Double Serif"
show NonStraightArmsHorizontalArmStyle = "Non-Straight Arms/Horizontal"
show NonStraightArmsWedgeArmStyle = "Non-Straight Arms/Wedge"
show NonStraightArmsVerticalArmStyle = "Non-Straight Arms/Vertical"
show NonStraightArmsSingleSerifArmStyle = "Non-Straight Arms/Single Serif"
show NonStraightArmsDoubleSerifArmStyle = "Non-Straight Arms/Double Serif"
instance Enum BArmStyle
where
fromEnum AnyArmStyle = 0
fromEnum NoFitArmStyle = 1
fromEnum StraightArmsHorizontalArmStyle = 2
fromEnum StraightArmsWedgeArmStyle = 3
fromEnum StraightArmsVerticalArmStyle = 4
fromEnum StraightArmsSingleSerifArmStyle = 5
fromEnum StraightArmsDoubleSerifArmStyle = 6
fromEnum NonStraightArmsHorizontalArmStyle = 7
fromEnum NonStraightArmsWedgeArmStyle = 8
fromEnum NonStraightArmsVerticalArmStyle = 9
fromEnum NonStraightArmsSingleSerifArmStyle = 10
fromEnum NonStraightArmsDoubleSerifArmStyle = 11
toEnum 0 = AnyArmStyle
toEnum 1 = NoFitArmStyle
toEnum 2 = StraightArmsHorizontalArmStyle
toEnum 3 = StraightArmsWedgeArmStyle
toEnum 4 = StraightArmsVerticalArmStyle
toEnum 5 = StraightArmsSingleSerifArmStyle
toEnum 6 = StraightArmsDoubleSerifArmStyle
toEnum 7 = NonStraightArmsHorizontalArmStyle
toEnum 8 = NonStraightArmsWedgeArmStyle
toEnum 9 = NonStraightArmsVerticalArmStyle
toEnum 10 = NonStraightArmsSingleSerifArmStyle
toEnum 11 = NonStraightArmsDoubleSerifArmStyle
toEnum _ = error "Unknown arm style"
data BLetterform
= AnyLetterform
| NoFitLetterform
| NormalContactLetterform
| NormalWeightedLetterform
| NormalBoxedLetterform
| NormalFlattenedLetterform
| NormalRoundedLetterform
| NormalOffCenterLetterform
| NormalSquareLetterform
| ObliqueContactLetterform
| ObliqueWeightedLetterform
| ObliqueBoxedLetterform
| ObliqueFlattenedLetterform
| ObliqueRoundedLetterform
| ObliqueOffCenterLetterform
| ObliqueSquareLetterform
deriving Eq
instance Show BLetterform
where
show AnyLetterform = "Any"
show NoFitLetterform = "No Fit"
show NormalContactLetterform = "Normal/Contact"
show NormalWeightedLetterform = "Normal/Weighted"
show NormalBoxedLetterform = "Normal/Boxed"
show NormalFlattenedLetterform = "Normal/Flattened"
show NormalRoundedLetterform = "Normal/Rounded"
show NormalOffCenterLetterform = "Normal/Off Center"
show NormalSquareLetterform = "Normal/Square"
show ObliqueContactLetterform = "Oblique/Contact"
show ObliqueWeightedLetterform = "Oblique/Weighted"
show ObliqueBoxedLetterform = "Oblique/Boxed"
show ObliqueFlattenedLetterform = "Oblique/Flattened"
show ObliqueRoundedLetterform = "Oblique/Rounded"
show ObliqueOffCenterLetterform = "Oblique/Off Center"
show ObliqueSquareLetterform = "Oblique/Square"
instance Enum BLetterform
where
fromEnum AnyLetterform = 0
fromEnum NoFitLetterform = 1
fromEnum NormalContactLetterform = 2
fromEnum NormalWeightedLetterform = 3
fromEnum NormalBoxedLetterform = 4
fromEnum NormalFlattenedLetterform = 5
fromEnum NormalRoundedLetterform = 6
fromEnum NormalOffCenterLetterform = 7
fromEnum NormalSquareLetterform = 8
fromEnum ObliqueContactLetterform = 9
fromEnum ObliqueWeightedLetterform = 10
fromEnum ObliqueBoxedLetterform = 11
fromEnum ObliqueFlattenedLetterform = 12
fromEnum ObliqueRoundedLetterform = 13
fromEnum ObliqueOffCenterLetterform = 14
fromEnum ObliqueSquareLetterform = 15
toEnum 0 = AnyLetterform
toEnum 1 = NoFitLetterform
toEnum 2 = NormalContactLetterform
toEnum 3 = NormalWeightedLetterform
toEnum 4 = NormalBoxedLetterform
toEnum 5 = NormalFlattenedLetterform
toEnum 6 = NormalRoundedLetterform
toEnum 7 = NormalOffCenterLetterform
toEnum 8 = NormalSquareLetterform
toEnum 9 = ObliqueContactLetterform
toEnum 10 = ObliqueWeightedLetterform
toEnum 11 = ObliqueBoxedLetterform
toEnum 12 = ObliqueFlattenedLetterform
toEnum 13 = ObliqueRoundedLetterform
toEnum 14 = ObliqueOffCenterLetterform
toEnum 15 = ObliqueSquareLetterform
toEnum _ = error "Unknown letterform"
data BMidline
= AnyMidline
| NoFitMidline
| StandardTrimmedMidline
| StandardPointedMidline
| StandardSerifedMidline
| HighTrimmedMidline
| HighPointedMidline
| HighSerifedMidline
| ConstantTrimmedMidline
| ConstantPointedMidline
| ConstantSerifedMidline
| LowTrimmedMidline
| LowPointedMidline
| LowSerifedMidline
deriving Eq
instance Show BMidline
where
show AnyMidline = "Any"
show NoFitMidline = "No Fit"
show StandardTrimmedMidline = "Standard/Trimmed"
show StandardPointedMidline = "Standard/Pointed"
show StandardSerifedMidline = "Standard/Serifed"
show HighTrimmedMidline = "High/Trimmed"
show HighPointedMidline = "High/Pointed"
show HighSerifedMidline = "High/Serifed"
show ConstantTrimmedMidline = "Constant/Trimmed"
show ConstantPointedMidline = "Constant/Pointed"
show ConstantSerifedMidline = "Constant/Serifed"
show LowTrimmedMidline = "Low/Trimmed"
show LowPointedMidline = "Low/Pointed"
show LowSerifedMidline = "Low/Serifed"
instance Enum BMidline
where
fromEnum AnyMidline = 0
fromEnum NoFitMidline = 1
fromEnum StandardTrimmedMidline = 2
fromEnum StandardPointedMidline = 3
fromEnum StandardSerifedMidline = 4
fromEnum HighTrimmedMidline = 5
fromEnum HighPointedMidline = 6
fromEnum HighSerifedMidline = 7
fromEnum ConstantTrimmedMidline = 8
fromEnum ConstantPointedMidline = 9
fromEnum ConstantSerifedMidline = 10
fromEnum LowTrimmedMidline = 11
fromEnum LowPointedMidline = 12
fromEnum LowSerifedMidline = 13
toEnum 0 = AnyMidline
toEnum 1 = NoFitMidline
toEnum 2 = StandardTrimmedMidline
toEnum 3 = StandardPointedMidline
toEnum 4 = StandardSerifedMidline
toEnum 5 = HighTrimmedMidline
toEnum 6 = HighPointedMidline
toEnum 7 = HighSerifedMidline
toEnum 8 = ConstantTrimmedMidline
toEnum 9 = ConstantPointedMidline
toEnum 10 = ConstantSerifedMidline
toEnum 11 = LowTrimmedMidline
toEnum 12 = LowPointedMidline
toEnum 13 = LowSerifedMidline
toEnum _ = error "Unknown midline"
data BXHeight
= AnyXHeight
| NoFitXHeight
| ConstantSmallXHeight
| ConstantStandardXHeight
| ConstantLargeXHeight
| DuckingSmallXHeight
| DuckingStandardXHeight
| DuckingLargeXHeight
deriving Eq
instance Show BXHeight
where
show AnyXHeight = "Any"
show NoFitXHeight = "No Fit"
show ConstantSmallXHeight = "Constant/Small"
show ConstantStandardXHeight = "Constant/Standard"
show ConstantLargeXHeight = "Constant/Large"
show DuckingSmallXHeight = "Ducking/Small"
show DuckingStandardXHeight = "Ducking/Standard"
show DuckingLargeXHeight = "Ducking/Large"
instance Enum BXHeight
where
fromEnum AnyXHeight = 0
fromEnum NoFitXHeight = 1
fromEnum ConstantSmallXHeight = 2
fromEnum ConstantStandardXHeight = 3
fromEnum ConstantLargeXHeight = 4
fromEnum DuckingSmallXHeight = 5
fromEnum DuckingStandardXHeight = 6
fromEnum DuckingLargeXHeight = 7
toEnum 0 = AnyXHeight
toEnum 1 = NoFitXHeight
toEnum 2 = ConstantSmallXHeight
toEnum 3 = ConstantStandardXHeight
toEnum 4 = ConstantLargeXHeight
toEnum 5 = DuckingSmallXHeight
toEnum 6 = DuckingStandardXHeight
toEnum 7 = DuckingLargeXHeight
toEnum _ = error "Unknown X height"
-- * Kern table
newtype KernHeader = KernHeader
{ version :: Fixed32 -- ^ The version number of the kerning table (0x00010000 for the current version).
} deriving (Eq, Show)
data KernSubtableHeader = KernSubtableHeader
-- | The length of this subtable in bytes, including this header.
{ length :: Word32
-- | Circumstances under which this table is used.
, coverage :: [Coverage]
-- | The tuple index (used for variations fonts). This value specifies which
-- tuple this subtable covers.
, tupleIndex :: Word16
} deriving (Eq, Show)
data Coverage
= KernVertical -- ^ Set if table has vertical kerning values.
| KernCrossStream -- ^ Set if table has cross-stream kerning values.
| KernVariation -- ^ Set if table has variation kerning values.
| KernUnusedBits -- ^ Set to 0.
| KernFormatMask -- ^ Set the format of this subtable (0-3 currently defined).
deriving (Eq, Show)
data KernFormat0Pair = KernFormat0Pair
{ left :: Word16 -- ^ The glyph index for the lefthand glyph in the kerning pair.
, right :: Word16 -- ^ The glyph index for the righthand glyph in the kerning pair.
-- | The kerning value in FUnits for the left and right pair in FUnits.
-- If this value is greater than zero, the glyphs are moved apart.
-- If this value is less than zero, the glyphs are moved together.
, value :: Int16
} deriving (Eq, Show)
data KernFormat0Table = KernFormat0Table
-- | The largest power of two less than or equal to the value of nPairs,
-- multiplied by the size in bytes of an entry in the subtable.
{ searchRange :: Word16
-- | This is calculated as log2 of the largest power of two less than or
-- equal to the value of nPairs. This value indicates how many iterations of
-- the search loop have to be made. For example, in a list of eight items,
-- there would be three iterations of the loop.
, entrySelector :: Word16
-- | The value of nPairs minus the largest power of two less than or equal
-- to nPairs. This is multiplied by the size in bytes of an entry in the
-- table.
, rangeShift :: Word16
, pairs :: [KernFormat0Pair]
} deriving (Eq, Show)
-- | Kern subtable format 1 header.
data StateHeader = StateHeader
{ stateSize :: Word16 -- ^ Number of classes defined for this table.
-- | Offset from the beginning of the state table to the beginning of the
-- class subtable.
, classTableOffset :: Word16
-- | Offset from the beginning of the state table to the beginning of the
-- state array.
, stateArrayOffset :: Word16
-- | Offset from the beginning of the state table to the beginning of the
-- entry subtable.
, entryTableOffset :: Word16
-- | Offset from the beginning of the state table to the beginning of the
-- state table values.
, valueOffset :: Word16
} deriving (Eq, Show)
data StateEntry = StateEntry
{ newState :: Word16
, flags :: Word16
} deriving (Eq, Show)
data KernFormat1Table = KernFormat1Table
{ stateHeader :: StateHeader
, firstGlyph :: Word16
, classArray :: ByteString
, stateArray :: ByteString
, entries :: [StateEntry]
} deriving (Eq, Show)
data SimpleArrayHeader = SimpleArrayHeader
{ rowWidth :: Word16 -- ^ The width, in bytes, of a row in the subtable.
-- | Offset from beginning of this subtable to the left-hand offset table.
, leftOffsetTable :: Word16
-- | Offset from beginning of this subtable to right-hand offset table.
, rightOffsetTable :: Word16
-- | Offset from beginning of this subtable to the start of the kerning
-- array.
, array :: Word16
} deriving (Eq, Show)
data ClassTableHeader = ClassTableHeader
{ firstGlyph -- ^ First glyph in class range.
-- | The offsets array for all of the glyphs in the range.
, offsets :: [Word16]
} deriving (Eq, Show)
data KernFormat2Table = KernFormat2Table
{ simpleArrayHeader :: SimpleArrayHeader
, classTableHeader :: ClassTableHeader
, values :: [Int16]
} deriving (Eq, Show)
-- * 'gasp' table
-- | Grid-fitting And Scan-conversion Procedure.
data GASPTable = GASPTable
{ version :: Word16 -- ^ Version number (set to 0).
, gaspRange :: [GASPRange] -- ^ Sorted by ppem.
} deriving (Eq, Show)
data GASPRange = GASPRange
{ rangeMaxPPEM :: Word16 -- ^ Upper limit of range, in PPEM.
, rangeGaspBehavior :: Word16 -- ^ Flags describing desired rasterizer behavior.
} deriving (Eq, Show)
data RangeGaspBehavior
= KGASPGridFit -- ^ Use gridfitting.
| KGASPDoGray -- ^ Use grayscale rendering.
deriving (Eq, Show)
instance Enum RangeGaspBehavior
where
toEnum 1 = KGASPGridFit
toEnum 2 = KGASPDoGray
toEnum _ = error "Unknown range GASP behavior"
fromEnum KGASPGridFit = 1
fromEnum KGASPDoGray = 2