opentype-0.1.1: Opentype loading and writing

Safe HaskellNone
LanguageHaskell98

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.

Synopsis

Types

newtype ShortFrac Source #

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.

Constructors

ShortFrac Int16 

type Fixed = Word32 Source #

signed fixed-point number

type FWord = Int16 Source #

FWord describes a quantity in FUnits, the smallest measurable distance in em space.

type UFWord = Word16 Source #

UFWord describes a quantity in FUnits, the smallest measurable distance in em space.

type GlyphID = Word16 Source #

the glyph index in the glyph table

Main datatype

data OpentypeFont Source #

truetype or opentype font

Constructors

OpentypeFont 

Fields

data OutlineTables Source #

tables for quadratic outlines (truetype or opentype)

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

data HeadTable Source #

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

  • headVersion :: Fixed

    0x00010000 for version 1.0. Will be overwritten.

  • fontRevision :: Fixed

    set by font manufacturer.

  • baselineYZero :: Bool

    baseline for font at y=0

  • sidebearingXZero :: Bool

    left sidebearing point at x=0;

  • pointsizeDepend :: Bool

    instructions may depend on point size;

  • integerScaling :: Bool

    Force ppem to integer values for all internal scaler math; may use fractional ppem sizes if this bit is clear;

  • alterAdvanceWidth :: Bool

    Microsoft: Instructions may alter advance width (the advance widths might not scale linearly);

  • verticalFont :: Bool

    Apple: This bit should be set in fonts that are intended to e laid out vertically, and in which the glyphs have been drawn such that an x-coordinate of 0 corresponds to the desired vertical baseline.

  • linguisticRenderingLayout :: Bool

    Apple: This should be set if the font requires layout for correct linguistic rendering (e.g. Arabic fonts).

  • metamorphosisEffects :: Bool

    Apple: This should be set for an AAT font which has one or more metamorphosis effects designated as happening by default.

  • rightToLeftGlyphs :: Bool

    his bit should be set if the font contains any strong right-to-left glyphs.

  • indicRearrangements :: Bool

    This bit should be set if the font contains Indic-style rearrangement effects.

  • losslessFontData :: Bool

    Adobe: Font data is ‘lossless’ as a results of having been subjected to optimizing transformation and/or compression (such as e.g. compression mechanisms defined by ISO/IEC 14496-18, MicroType Express, WOFF 2.0 or similar) where the original font functionality and features are retained but the binary compatibility between input and output font files is not guaranteed. As a result of the applied transform, the ‘DSIG’ Table may also be invalidated.

  • convertedFont :: Bool

    Adobe: Font converted (produce compatible metrics)

  • clearTypeOptimized :: Bool

    Adobe: Font optimized for ClearType™. Note, fonts that rely on embedded bitmaps (EBDT) for rendering should not be considered optimized for ClearType, and therefore should keep this bit cleared.

  • lastResortFont :: Bool

    Last Resort font. If set, indicates that the glyphs encoded in the cmap subtables are simply generic symbolic representations of code point ranges and don’t truly represent support for those code points. If unset, indicates that the glyphs encoded in the cmap subtables represent proper support for those code points.

  • unitsPerEm :: Word16

    Valid range is from 16 to 16384. This value should be a power of 2 for fonts that have TrueType outlines.

  • created :: UTCTime
     
  • modified :: UTCTime
     
  • xMin :: FWord

    Will be overwritten.

  • yMin :: FWord

    Will be overwritten.

  • xMax :: FWord

    Will be overwritten.

  • yMax :: FWord

    Will be overwritten.

  • boldStyle :: Bool
     
  • italicStyle :: Bool
     
  • underlineStyle :: Bool
     
  • outlineStyle :: Bool
     
  • shadowStyle :: Bool
     
  • condensedStyle :: Bool
     
  • extendedStyle :: Bool
     
  • lowerRecPPEM :: Word16

    Smallest readable size in pixels.

  • fontDirectionHint :: Int16

    deprecated, will be set to 2

  • longLocIndices :: Bool

    0 for short offsets, 1 for long. Will be overwritten.

  • glyphDataFormat :: Int16

    0 for current format. Will be overwritten.

Glyf table

newtype GlyfTable Source #

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 

data Glyph a Source #

The glyph type is parametrized over the type of glyph reference for compound glyphs.

Constructors

Glyph 

Fields

Instances

Functor Glyph Source # 

Methods

fmap :: (a -> b) -> Glyph a -> Glyph b #

(<$) :: a -> Glyph b -> Glyph a #

Foldable Glyph Source # 

Methods

fold :: Monoid m => Glyph m -> m #

foldMap :: Monoid m => (a -> m) -> Glyph a -> m #

foldr :: (a -> b -> b) -> b -> Glyph a -> b #

foldr' :: (a -> b -> b) -> b -> Glyph a -> b #

foldl :: (b -> a -> b) -> b -> Glyph a -> b #

foldl' :: (b -> a -> b) -> b -> Glyph a -> b #

foldr1 :: (a -> a -> a) -> Glyph a -> a #

foldl1 :: (a -> a -> a) -> Glyph a -> a #

toList :: Glyph a -> [a] #

null :: Glyph a -> Bool #

length :: Glyph a -> Int #

elem :: Eq a => a -> Glyph a -> Bool #

maximum :: Ord a => Glyph a -> a #

minimum :: Ord a => Glyph a -> a #

sum :: Num a => Glyph a -> a #

product :: Num a => Glyph a -> a #

Traversable Glyph Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Glyph a -> f (Glyph b) #

sequenceA :: Applicative f => Glyph (f a) -> f (Glyph a) #

mapM :: Monad m => (a -> m b) -> Glyph a -> m (Glyph b) #

sequence :: Monad m => Glyph (m a) -> m (Glyph a) #

Show a => Show (Glyph a) Source # 

Methods

showsPrec :: Int -> Glyph a -> ShowS #

show :: Glyph a -> String #

showList :: [Glyph a] -> ShowS #

data GlyphOutlines a Source #

Instances

Functor GlyphOutlines Source # 

Methods

fmap :: (a -> b) -> GlyphOutlines a -> GlyphOutlines b #

(<$) :: a -> GlyphOutlines b -> GlyphOutlines a #

Foldable GlyphOutlines Source # 

Methods

fold :: Monoid m => GlyphOutlines m -> m #

foldMap :: Monoid m => (a -> m) -> GlyphOutlines a -> m #

foldr :: (a -> b -> b) -> b -> GlyphOutlines a -> b #

foldr' :: (a -> b -> b) -> b -> GlyphOutlines a -> b #

foldl :: (b -> a -> b) -> b -> GlyphOutlines a -> b #

foldl' :: (b -> a -> b) -> b -> GlyphOutlines a -> b #

foldr1 :: (a -> a -> a) -> GlyphOutlines a -> a #

foldl1 :: (a -> a -> a) -> GlyphOutlines a -> a #

toList :: GlyphOutlines a -> [a] #

null :: GlyphOutlines a -> Bool #

length :: GlyphOutlines a -> Int #

elem :: Eq a => a -> GlyphOutlines a -> Bool #

maximum :: Ord a => GlyphOutlines a -> a #

minimum :: Ord a => GlyphOutlines a -> a #

sum :: Num a => GlyphOutlines a -> a #

product :: Num a => GlyphOutlines a -> a #

Traversable GlyphOutlines Source # 

Methods

traverse :: Applicative f => (a -> f b) -> GlyphOutlines a -> f (GlyphOutlines b) #

sequenceA :: Applicative f => GlyphOutlines (f a) -> f (GlyphOutlines a) #

mapM :: Monad m => (a -> m b) -> GlyphOutlines a -> m (GlyphOutlines b) #

sequence :: Monad m => GlyphOutlines (m a) -> m (GlyphOutlines a) #

Show a => Show (GlyphOutlines a) Source # 

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 

type Instructions = Vector Word8 Source #

TODO: make a proper datatype for instructions.

data GlyphComponent a Source #

Constructors

GlyphComponent 

Fields

Instances

Functor GlyphComponent Source # 

Methods

fmap :: (a -> b) -> GlyphComponent a -> GlyphComponent b #

(<$) :: a -> GlyphComponent b -> GlyphComponent a #

Foldable GlyphComponent Source # 

Methods

fold :: Monoid m => GlyphComponent m -> m #

foldMap :: Monoid m => (a -> m) -> GlyphComponent a -> m #

foldr :: (a -> b -> b) -> b -> GlyphComponent a -> b #

foldr' :: (a -> b -> b) -> b -> GlyphComponent a -> b #

foldl :: (b -> a -> b) -> b -> GlyphComponent a -> b #

foldl' :: (b -> a -> b) -> b -> GlyphComponent a -> b #

foldr1 :: (a -> a -> a) -> GlyphComponent a -> a #

foldl1 :: (a -> a -> a) -> GlyphComponent a -> a #

toList :: GlyphComponent a -> [a] #

null :: GlyphComponent a -> Bool #

length :: GlyphComponent a -> Int #

elem :: Eq a => a -> GlyphComponent a -> Bool #

maximum :: Ord a => GlyphComponent a -> a #

minimum :: Ord a => GlyphComponent a -> a #

sum :: Num a => GlyphComponent a -> a #

product :: Num a => GlyphComponent a -> a #

Traversable GlyphComponent Source # 

Methods

traverse :: Applicative f => (a -> f b) -> GlyphComponent a -> f (GlyphComponent b) #

sequenceA :: Applicative f => GlyphComponent (f a) -> f (GlyphComponent a) #

mapM :: Monad m => (a -> m b) -> GlyphComponent a -> m (GlyphComponent b) #

sequence :: Monad m => GlyphComponent (m a) -> m (GlyphComponent a) #

Show a => Show (GlyphComponent a) Source # 

Glyf table lenses

_glyphContours :: Traversal' StandardGlyph [[CurvePoint]] Source #

traversal over simple glyph contours

_glyphComponents :: Traversal' StandardGlyph [GlyphComponent Int] Source #

traversal over compound glyph components

CMap table

newtype CmapTable Source #

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

CmapTable 

Fields

data CMap Source #

Constructors

CMap 

Fields

Instances

Eq CMap Source # 

Methods

(==) :: CMap -> CMap -> Bool #

(/=) :: CMap -> CMap -> Bool #

Ord CMap Source # 

Methods

compare :: CMap -> CMap -> Ordering #

(<) :: CMap -> CMap -> Bool #

(<=) :: CMap -> CMap -> Bool #

(>) :: CMap -> CMap -> Bool #

(>=) :: CMap -> CMap -> Bool #

max :: CMap -> CMap -> CMap #

min :: CMap -> CMap -> CMap #

Show CMap Source # 

Methods

showsPrec :: Int -> CMap -> ShowS #

show :: CMap -> String #

showList :: [CMap] -> ShowS #

data MapFormat Source #

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

data HheaTable Source #

This table contains information for horizontal layout.

Constructors

HheaTable 

Fields

Maxp table

data MaxpTable Source #

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

data NameTable Source #

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

Post table

data PostTable Source #

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

  • postVersion :: PostVersion
     
  • italicAngle :: Fixed

    Italic angle in counter-clockwise degrees from the vertical. Zero for upright text, negative for text that leans to the right (forward).

  • underlinePosition :: FWord

    This is the suggested distance of the top of the underline from the baseline (negative values indicate below baseline).

    The PostScript definition of this FontInfo dictionary key (the y coordinate of the center of the stroke) is not used for historical reasons. The value of the PostScript key may be calculated by subtracting half the underlineThickness from the value of this field.

  • underlineThickness :: FWord

    suggested values for the underline thickness.

  • isFixedPitch :: Word32

    Set to 0 if the font is proportionally spaced, non-zero if the font is not proportionally spaced (i.e. monospaced).

  • minMemType42 :: Word32

    Minimum memory usage when an OpenType font is downloaded. Set to 0 if unsure.

  • maxMemType42 :: Word32

    Maximum memory usage when an OpenType font is downloaded. Set to 0 if unsure.

  • minMemType1 :: Word32

    Minimum memory usage when an OpenType font is downloaded as a Type 1 font. Set to 0 if unsure.

  • maxMemType1 :: Word32

    Maximum memory usage when an OpenType font is downloaded as a Type 1 font. Set to 0 if unsure.

  • glyphNameIndex :: [Int]

    Ordinal number of the glyph in post string tables. For format 2.0 only.

    If the name index is between 0 and 257, treat the name index as a glyph index in the Macintosh standard order. If the name index is between 258 and 65535, then subtract 258 and use that to index into the list of Pascal strings at the end of the table. Thus a given font may map some of its glyphs to the standard glyph names, and some to its own names.

    If you do not want to associate a PostScript name with a particular glyph, use index number 0 which points to the name .notdef.

  • postStrings :: [String]

    strings for indices 258 and upwards.

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

OS/2 table

data OS2Table Source #

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

Kern table

data KernTable Source #

Constructors

KernTable 

Fields

data KernPair Source #

KernPair left right adjustment: Pair of kerning values. left and right are indices in the glyph table.

Constructors

KernPair Word16 Word16 FWord