| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Opentype.Fileformat
Contents
Description
This module provides opentype file loading and writing. An attempt was made to have a higher level interface without sacrificing features of the file format.
- newtype ShortFrac = ShortFrac Int16
 - type Fixed = Word32
 - type FWord = Int16
 - type UFWord = Word16
 - type GlyphID = Word16
 - type WordMap a = Map Word32 a
 - data OpentypeFont = OpentypeFont {}
 - data OutlineTables
 - type GenericTables = Map String ByteString
 - _headTable :: Lens' OpentypeFont HeadTable
 - _hheaTable :: Lens' OpentypeFont HheaTable
 - _cmapTable :: Lens' OpentypeFont CmapTable
 - _nameTable :: Lens' OpentypeFont NameTable
 - _postTable :: Lens' OpentypeFont PostTable
 - _os2Table :: Traversal' OpentypeFont OS2Table
 - _kernTable :: Traversal' OpentypeFont KernTable
 - _outlineTables :: Lens' OpentypeFont OutlineTables
 - _otherTables :: Lens' OpentypeFont GenericTables
 - _maxpTable :: Traversal' OpentypeFont MaxpTable
 - _glyfTable :: Traversal' OpentypeFont GlyfTable
 - readOTFile :: FilePath -> IO OpentypeFont
 - writeOTFile :: OpentypeFont -> FilePath -> IO ()
 - data HeadTable = HeadTable {
- headVersion :: Fixed
 - fontRevision :: Fixed
 - baselineYZero :: Bool
 - sidebearingXZero :: Bool
 - pointsizeDepend :: Bool
 - integerScaling :: Bool
 - alterAdvanceWidth :: Bool
 - verticalFont :: Bool
 - linguisticRenderingLayout :: Bool
 - metamorphosisEffects :: Bool
 - rightToLeftGlyphs :: Bool
 - indicRearrangements :: Bool
 - losslessFontData :: Bool
 - convertedFont :: Bool
 - clearTypeOptimized :: Bool
 - lastResortFont :: Bool
 - unitsPerEm :: Word16
 - created :: UTCTime
 - modified :: UTCTime
 - xMin :: FWord
 - yMin :: FWord
 - xMax :: FWord
 - yMax :: FWord
 - boldStyle :: Bool
 - italicStyle :: Bool
 - underlineStyle :: Bool
 - outlineStyle :: Bool
 - shadowStyle :: Bool
 - condensedStyle :: Bool
 - extendedStyle :: Bool
 - lowerRecPPEM :: Word16
 - fontDirectionHint :: Int16
 - longLocIndices :: Bool
 - glyphDataFormat :: Int16
 
 - newtype GlyfTable = GlyfTable {
- glyphVector :: Vector (Glyph Int)
 
 - data Glyph a = Glyph {
- glyphName :: String
 - advanceWidth :: Word16
 - leftSideBearing :: Int16
 - glyphXmin :: FWord
 - glyphYmin :: FWord
 - glyphXmax :: FWord
 - glyphYmax :: FWord
 - glyphOutlines :: GlyphOutlines a
 
 - type StandardGlyph = Glyph Int
 - data GlyphOutlines a
 - getScaledContours :: OpentypeFont -> StandardGlyph -> [[CurvePoint]]
 - emptyGlyfTable :: GlyfTable
 - data CurvePoint = CurvePoint FWord FWord Bool
 - type Instructions = Vector Word8
 - data GlyphComponent a = GlyphComponent {
- componentID :: a
 - componentInstructions :: Maybe Instructions
 - componentXX :: ShortFrac
 - componentXY :: ShortFrac
 - componentYX :: ShortFrac
 - componentYY :: ShortFrac
 - componentX :: Int
 - componentY :: Int
 - matchPoints :: Bool
 - roundXYtoGrid :: Bool
 - useMyMetrics :: Bool
 - overlapCompound :: Bool
 - scaledComponentOffset :: Maybe Bool
 
 - _glyphContours :: Traversal' StandardGlyph [[CurvePoint]]
 - _glyphInstructions :: Traversal' StandardGlyph Instructions
 - _glyphComponents :: Traversal' StandardGlyph [GlyphComponent Int]
 - newtype CmapTable = CmapTable {}
 - data CMap = CMap {}
 - data PlatformID
 - data MapFormat
 - emptyCmapTable :: CmapTable
 - data HheaTable = HheaTable {}
 - data MaxpTable = MaxpTable {
- maxpVersion :: Fixed
 - numGlyphs :: Word16
 - maxPoints :: Word16
 - maxContours :: Word16
 - maxComponentPoints :: Word16
 - maxComponentContours :: Word16
 - maxZones :: Word16
 - maxTwilightPoints :: Word16
 - maxStorage :: Word16
 - maxFunctionDefs :: Word16
 - maxInstructionDefs :: Word16
 - maxStackElements :: Word16
 - maxSizeOfInstructions :: Word16
 - maxComponentElements :: Word16
 - maxComponentDepth :: Word16
 
 - emptyMaxpTable :: MaxpTable
 - data NameTable = NameTable {
- nameRecords :: [NameRecord]
 
 - data NameRecord = NameRecord {}
 - data PostTable = PostTable {}
 - data PostVersion
 - data OS2Table = OS2Table {
- os2version :: Word16
 - xAvgCharWidth :: Int16
 - usWeightClass :: Word16
 - usWidthClass :: Word16
 - fsType :: Word16
 - ySubscriptXSize :: Int16
 - ySubscriptYSize :: Int16
 - ySubscriptXOffset :: Int16
 - ySubscriptYOffset :: Int16
 - ySuperscriptXSize :: Int16
 - ySuperscriptYSize :: Int16
 - ySuperscriptXOffset :: Int16
 - ySuperscriptYOffset :: Int16
 - yStrikeoutSize :: Int16
 - yStrikeoutPosition :: Int16
 - bFamilyClass :: Int16
 - bFamilyType :: Int8
 - bSerifStyle :: Int8
 - bWeight :: Int8
 - bProportion :: Int8
 - bContrast :: Int8
 - bStrokeVariation :: Int8
 - bArmStyle :: Int8
 - bLetterform :: Int8
 - bMidline :: Int8
 - bXHeight :: Int8
 - ulUnicodeRange1 :: Word32
 - ulUnicodeRange2 :: Word32
 - ulUnicodeRange3 :: Word32
 - ulUnicodeRange4 :: Word32
 - achVendID :: Word32
 - fsSelection :: Word16
 - usFirstCharIndex :: Word16
 - usLastCharIndex :: Word16
 - sTypoAscender :: Int16
 - sTypoDescender :: Int16
 - sTypoLineGap :: Int16
 - usWinAscent :: Word16
 - usWinDescent :: Word16
 - ulCodePageRange1 :: Word32
 - ulCodePageRange2 :: Word32
 - sxHeight :: Int16
 - sCapHeight :: Int16
 - usDefaultChar :: Word16
 - usBreakChar :: Word16
 - usMaxContext :: Word16
 - usLowerOpticalPointSize :: Word16
 - usUpperOpticalPointSize :: Word16
 
 - data KernTable = KernTable {}
 - data KernPair = KernPair Word16 Word16 FWord
 - _kernPairs :: Lens' KernTable [KernPair]
 
Types
A ShortFrac is an 16 bit signed fixed number with a bias of 14. This means it can represent numbers between 1.999 (0x7fff) and -2.0 (0x8000). 1.0 is stored as 16384 (0x4000) and -1.0 is stored as -16384 (0xc000). Efficient numeric instances are provided.
FWord describes a quantity in FUnits, the smallest measurable distance in em space.
UFWord describes a quantity in FUnits, the smallest measurable distance in em space.
Main datatype
data OpentypeFont Source #
truetype or opentype font
Constructors
| OpentypeFont | |
Fields 
  | |
Instances
data OutlineTables Source #
tables for quadratic outlines (truetype or opentype)
Constructors
| QuadTables MaxpTable GlyfTable | |
| CubicTables | 
Instances
type GenericTables = Map String ByteString Source #
OpentypeFont lenses
IO
readOTFile :: FilePath -> IO OpentypeFont Source #
read an opentype font from a file.
writeOTFile :: OpentypeFont -> FilePath -> IO () Source #
write an opentype font to a file
Head table
This table contains global information about the font. it records such facts as the font version number, the creation and modification dates, revision number and basic typographic data that applies to the font as a whole. this includes a specification of the font bounding box, the direction in which the font's glyphs are most likely to be written and other information about the placement of glyphs in the em square.
Constructors
| HeadTable | |
Fields 
  | |
Glyf table
This table contains the data that defines the appearance of the glyphs in the font. This includes specification of the points that describe the contours that make up a glyph outline and the instructions that grid-fit that glyph. The glyf table supports the definition of simple glyphs and compound glyphs, that is, glyphs that are made up of other glyphs.
Constructors
| GlyfTable | |
Fields 
  | |
The glyph type is parametrized over the type of glyph reference for compound glyphs.
Constructors
| Glyph | |
Fields 
  | |
type StandardGlyph = Glyph Int Source #
data GlyphOutlines a Source #
Constructors
| GlyphContours [[CurvePoint]] Instructions | |
| CompositeGlyph [GlyphComponent a] | 
Instances
getScaledContours :: OpentypeFont -> StandardGlyph -> [[CurvePoint]] Source #
getScaledContours scaleOffset glyfTable glyph: Get the scaled
 contours for a simple or composite glyph.
data CurvePoint Source #
CurvePoint x y onCurve: Points used to describe the outline
 using lines and quadratic beziers.  Coordinates are absolute (not
 relative).  If two off-curve points follow each other, an on-curve
 point is added halfway between.
Constructors
| CurvePoint FWord FWord Bool | 
Instances
type Instructions = Vector Word8 Source #
TODO: make a proper datatype for instructions.
data GlyphComponent a Source #
Constructors
| GlyphComponent | |
Fields 
  | |
Instances
Glyf table lenses
_glyphContours :: Traversal' StandardGlyph [[CurvePoint]] Source #
traversal over simple glyph contours
_glyphInstructions :: Traversal' StandardGlyph Instructions Source #
instructions for simple glyphs
_glyphComponents :: Traversal' StandardGlyph [GlyphComponent Int] Source #
traversal over compound glyph components
CMap table
This table defines the mapping of character codes to the glyph index values used in the font. It may contain more than one subtable, in order to support more than one character encoding scheme. Character codes that do not correspond to any glyph in the font should be mapped to glyph index 0. The glyph at this location must be a special glyph representing a missing character, commonly known as .notdef.
The table header indicates the character encodings for which subtables are present. Each subtable is in one of seven possible formats and begins with a format code indicating the format used.
The platformID and platform-specific encodingID in the header
 entry (and, in the case of the Macintosh platform, the macLanguage
 field in the subtable itself) are used to specify a particular
 cmap encoding. Each platform ID, platform-specific encoding ID,
 and subtable macLanguage combination may appear only once in the
 CmapTable.
When platformID is UnicodePlatform, encodingID is interpreted as follows:
- 0: Default semantics
 - 1: Version 1.1 semantics
 - 2: ISO 10646 1993 semantics (deprecated)
 - 3: Unicode 2.0 or later semantics (BMP only)
 - 4: Unicode 2.0 or later semantics (non-BMP characters allowed)
 - 5: Unicode Variation Sequences
 - 6: Full Unicode coverage (used with type 13.0 cmaps by OpenType)
 
When platformID MacintoshPlatform, the encodingID is a QuickDraw script code.
Note that the use of the Macintosh platformID is currently discouraged. Subtables with a Macintosh platformID are only required for backwards compatibility with QuickDraw and will be synthesized from Unicode-based subtables if ever needed.
When platformID is MicrosoftPlatform, the encodingID is a is interpreted as follows:
- 0: Symbol
 - 1: Unicode BMP-only (UCS-2)
 - 2: Shift-JIS
 - 3: PRC
 - 4: BigFive
 - 5: Johab
 - 10: Unicode UCS-4
 
Constructors
| CMap | |
Fields 
  | |
data PlatformID Source #
Constructors
| UnicodePlatform | |
| MacintoshPlatform | DEPRECATED  | 
| MicrosoftPlatform | 
Instances
Constructors
| MapFormat0 | 8 bit encoding, contiguous block of bytes. LEGACY ONLY.  | 
| MapFormat2 | mixed 8/16 bit encoding with gaps. LEGACY ONLY.  | 
| MapFormat4 | 16 bit encoding with holes. This should contain the BMP for a unicode font.  | 
| MapFormat6 | 16 bit single contiguous block (trimmed).  | 
| MapFormat8 | mixed 16/32 bit, for compatibility only, DO NOT USE  | 
| MapFormat10 | 32 bit single contiguous block (trimmed), for compatibility only, DO NOT USE  | 
| MapFormat12 | 32 bit segmented coverage. This should contain Unicode encodings with glyphs above 0xFFFF. It's recommended to save a subset to format 4, for backwards compatibility.  | 
Hhea table
This table contains information for horizontal layout.
Constructors
| HheaTable | |
Fields 
  | |
Maxp table
The maxp table establishes the memory requirements for a font.
 Only instruction data needs to be filled in, since instructions
 aren't yet supported.  Note: The cff version of this table will
 be handled automatically.
Constructors
| MaxpTable | |
Fields 
  | |
Name table
This table allows multilingual strings to be associated with the OpenType™ font file. These strings can represent copyright notices, font names, family names, style names, and so on. To keep this table short, the font manufacturer may wish to make a limited set of entries in some small set of languages; later, the font can be “localized” and the strings translated or added. Other parts of the OpenType font file that require these strings can then refer to them simply by their index number. Clients that need a particular string can look it up by its platform ID, character encoding ID, language ID and name ID. Note that some platforms may require single byte character strings, while others may require double byte strings.
For historical reasons, some applications which install fonts
 perform version control using Macintosh platform (platform ID 1)
 strings from the name table. Because of this, it is strongly
 recommended that the name table of all fonts include Macintosh
 platform strings and that the syntax of the version number (name id
 5) follows the guidelines given in the opentype specification.
The encoding for each bytestring depends on the PlatformID and encodingID. This library doesn't do any conversion. For more information see the opentype specification: https://www.microsoft.com/typography/otspec/name.htm
Constructors
| NameTable | |
Fields 
  | |
data NameRecord Source #
Constructors
| NameRecord | |
Fields 
  | |
Instances
Post table
This table contains additional information needed to use TrueType or OpenType™ fonts on PostScript printers. This includes data for the FontInfo dictionary entry and the PostScript names of all the glyphs. For more information about PostScript names, see the Adobe document Unicode and Glyph Names.
Versions 1.0, 2.0, and 2.5 refer to TrueType fonts and OpenType fonts with TrueType data. OpenType fonts with TrueType data may also use Version 3.0. OpenType fonts with CFF data use Version 3.0 only.
Constructors
| PostTable | |
Fields 
  | |
data PostVersion Source #
Constructors
| PostTable1 | The first 258 Glyphs have standard names  | 
| PostTable2 | Order of glyph names can be changed, and glyphs can have non-standard names.  | 
| PostTable3 | No glyph names  | 
Instances
OS/2 table
The OS/2 table consists of a set of metrics that are required in OpenType fonts. For a description of these fields see: https://www.microsoft.com/typography/otspec/os2.htm
Constructors
Kern table
Constructors
| KernTable | |
KernPair left right adjustment: Pair of kerning values.  left
 and right are indices in the glyph table.