Initial commit
This commit is contained in:
1198
src/Graphics/Fountainhead/Parser.hs
Normal file
1198
src/Graphics/Fountainhead/Parser.hs
Normal file
File diff suppressed because it is too large
Load Diff
794
src/Graphics/Fountainhead/TrueType.hs
Normal file
794
src/Graphics/Fountainhead/TrueType.hs
Normal file
@ -0,0 +1,794 @@
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
|
||||
-- | 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(..)
|
||||
, GlyfTable(..)
|
||||
, GlyphArgument(..)
|
||||
, GlyphCoordinate(..)
|
||||
, GlyphDefinition(..)
|
||||
, GlyphDescription(..)
|
||||
, GlyphTransformationOption(..)
|
||||
, HdmxTable(..)
|
||||
, HeadTable(..)
|
||||
, HheaTable(..)
|
||||
, HmtxTable(..)
|
||||
, LocaTable(..)
|
||||
, LongHorMetric(..)
|
||||
, MaxpTable(..)
|
||||
, NameRecord(..)
|
||||
, NameTable(..)
|
||||
, OffsetSubtable(..)
|
||||
, OpenMaxpTable(..)
|
||||
, Os2BaseFields(..)
|
||||
, Os2MicrosoftFields(..)
|
||||
, Os2Table(..)
|
||||
, Os2Version1Fields(..)
|
||||
, Os2Version4Fields(..)
|
||||
, Os2Version5Fields(..)
|
||||
, OutlineFlag(..)
|
||||
, Panose(..)
|
||||
, PostFormat2Table(..)
|
||||
, PostHeader(..)
|
||||
, PostSubtable(..)
|
||||
, PostTable(..)
|
||||
, PrepTable(..)
|
||||
, SimpleGlyphDefinition(..)
|
||||
, TableDirectory(..)
|
||||
, TrueMaxpTable(..)
|
||||
, UVSOffset(..)
|
||||
, UVSMapping(..)
|
||||
, UnicodeValueRange(..)
|
||||
, VariationSelectorMap
|
||||
, unLocaTable
|
||||
) where
|
||||
|
||||
import Data.ByteString (ByteString)
|
||||
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(..))
|
||||
|
||||
-- * Font directory
|
||||
|
||||
data FontDirectory = FontDirectory
|
||||
{ offsetSubtable :: OffsetSubtable
|
||||
, tableDirectory :: [TableDirectory]
|
||||
} deriving (Eq, Show)
|
||||
|
||||
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)
|
||||
|
||||
-- * '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 :: Int16 -- ^ Distance from baseline of highest ascender.
|
||||
, descent :: Int16 -- ^ Distance from baseline of lowest descender.
|
||||
, lineGap :: Int16 -- ^ Typographic line gap.
|
||||
, advanceWidthMax :: Word16 -- ^ Must be consistent with horizontal metrics.
|
||||
, minLeftSideBearing :: Word16 -- ^ Must be consistent with horizontal metrics.
|
||||
, minRightSideBearing :: Word16 -- ^ Must be consistent with horizontal metrics.
|
||||
, xMaxExtent :: Word16 -- ^ 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 :: Int16 -- ^ 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 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 :: Word16 -- ^ 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 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
|
||||
, onCurve :: Bool
|
||||
} deriving (Eq, Show)
|
||||
|
||||
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
|
||||
, thisXIsSame :: Bool
|
||||
, thisYIsSame :: Bool
|
||||
} deriving (Eq, Show)
|
||||
|
||||
newtype GlyfTable = GlyfTable (Vector GlyphDescription)
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- * 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)
|
||||
|
||||
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, Show)
|
||||
|
||||
data BSerifStyle
|
||||
= AnySerifStyle
|
||||
| NoFitSerifStyle
|
||||
| CoveSerifStyle
|
||||
| ObtuseCoveSerifStyle
|
||||
| SquareCoveSerifStyle
|
||||
| ObtuseSquareCoveSerifStyle
|
||||
| SquareSerifStyle
|
||||
| ThinSerifStyle
|
||||
| BoneSerifStyle
|
||||
| ExaggeratedSerifStyle
|
||||
| TriangleSerifStyle
|
||||
| NormalSansSerifStyle
|
||||
| ObtuseSansSerifStyle
|
||||
| PerpSansSerifStyle
|
||||
| FlaredSerifStyle
|
||||
| RoundedSerifStyle
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BWeight
|
||||
= AnyWeight
|
||||
| NoFitWeight
|
||||
| VeryLightWeight
|
||||
| LightWeight
|
||||
| ThinWeight
|
||||
| BookWeight
|
||||
| MediumWeight
|
||||
| DemiWeight
|
||||
| BoldWeight
|
||||
| HeavyWeight
|
||||
| BlackWeight
|
||||
| NordWeight
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BProportion
|
||||
= AnyProportion
|
||||
| NoFitProportion
|
||||
| OldStyleProportion
|
||||
| ModernProportion
|
||||
| EvenWidthProportion
|
||||
| ExpandedProportion
|
||||
| CondensedProportion
|
||||
| VeryExpandedProportion
|
||||
| VeryCondensedProportion
|
||||
| MonospacedProportion
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BContrast
|
||||
= AnyContrast
|
||||
| NoFitContrast
|
||||
| NoneContrast
|
||||
| VeryLowContrast
|
||||
| LowContrast
|
||||
| MediumLowContrast
|
||||
| MediumContrast
|
||||
| MediumHighContrast
|
||||
| HighContrast
|
||||
| VeryHighContrast
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BStrokeVariation
|
||||
= AnyStrokeVariatoon
|
||||
| NoFitStrokeVariatoon
|
||||
| GradualDiagonalStrokeVariatoon
|
||||
| GradualTransitionalStrokeVariatoon
|
||||
| GradualVerticalStrokeVariatoon
|
||||
| GradualHorizontalStrokeVariatoon
|
||||
| RapidVerticalStrokeVariatoon
|
||||
| RapidHorizontalStrokeVariatoon
|
||||
| InstantVerticalStrokeVariatoon
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BArmStyle
|
||||
= AnyArmStyle
|
||||
| NoFitArmStyle
|
||||
| StraightArmsHorizontalArmStyle
|
||||
| StraightArmsWedgeArmStyle
|
||||
| StraightArmsVerticalArmStyle
|
||||
| StraightArmsSingleSerifArmStyle
|
||||
| StraightArmsDoubleSerifArmStyle
|
||||
| NonStraightArmsHorizontalArmStyle
|
||||
| NonStraightArmsWedgeArmStyle
|
||||
| NonStraightArmsVerticalArmStyle
|
||||
| NonStraightArmsSingleSerifArmStyle
|
||||
| NonStraightArmsDoubleSerifArmStyle
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BLetterform
|
||||
= AnyLetterform
|
||||
| NoFitLetterform
|
||||
| NormalContactLetterform
|
||||
| NormalWeightedLetterform
|
||||
| NormalBoxedLetterform
|
||||
| NormalFlattenedLetterform
|
||||
| NormalRoundedLetterform
|
||||
| NormalOffCenterLetterform
|
||||
| NormalSquareLetterform
|
||||
| ObliqueContactLetterform
|
||||
| ObliqueWeightedLetterform
|
||||
| ObliqueBoxedLetterform
|
||||
| ObliqueFlattenedLetterform
|
||||
| ObliqueRoundedLetterform
|
||||
| ObliqueOffCenterLetterform
|
||||
| ObliqueSquareLetterform
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BMidline
|
||||
= AnyMidline
|
||||
| NoFitMidline
|
||||
| StandardTrimmedMidline
|
||||
| StandardPointedMidline
|
||||
| StandardSerifedMidline
|
||||
| HighTrimmedMidline
|
||||
| HighPointedMidline
|
||||
| HighSerifedMidline
|
||||
| ConstantTrimmedMidline
|
||||
| ConstantPointedMidline
|
||||
| ConstantSerifedMidline
|
||||
| LowTrimmedMidline
|
||||
| LowPointedMidline
|
||||
| LowSerifedMidline
|
||||
deriving (Eq, Show)
|
||||
|
||||
data BXHeight
|
||||
= AnyXHeight
|
||||
| NoFitXHeight
|
||||
| ConstantSmallXHeight
|
||||
| ConstantStandardXHeight
|
||||
| ConstantLargeXHeight
|
||||
| DuckingSmallXHeight
|
||||
| DuckingStandardXHeight
|
||||
| DuckingLargeXHeight
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- * Kern table
|
||||
|
||||
data 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
|
||||
{ nPairs :: Word16 -- ^ The number of kerning pairs in this subtable.
|
||||
, searchRange :: Word16 -- ^ 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.
|
||||
-- | 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)
|
14
src/Graphics/Fountainhead/Type.hs
Normal file
14
src/Graphics/Fountainhead/Type.hs
Normal file
@ -0,0 +1,14 @@
|
||||
-- | Generic font types.
|
||||
module Graphics.Fountainhead.Type
|
||||
( F2Dot14(..)
|
||||
, Fixed32(..)
|
||||
) where
|
||||
|
||||
import Data.Int (Int16)
|
||||
import Data.Word (Word32)
|
||||
|
||||
newtype Fixed32 = Fixed32 Word32
|
||||
deriving (Eq, Show)
|
||||
|
||||
newtype F2Dot14 = F2Dot14 Int16
|
||||
deriving (Eq, Show)
|
Reference in New Issue
Block a user