module Opentype.Fileformat.Hhea
where
import Opentype.Fileformat.Types
import Data.Binary.Get
import Data.Binary.Put
import Data.Int
import Data.Word
import Control.Monad
data HheaTable = HheaTable {
  
  version :: Fixed,
  
  ascent :: FWord,
  
  descent :: FWord,
  
  lineGap :: FWord,
  
  advanceWidthMax :: UFWord,
  
  minLeftSideBearing :: FWord,
  
  minRightSideBearing :: FWord,
  
  xMaxExtent :: FWord,
  
  caretSlopeRise :: Int16,
  
  caretSlopeRun :: Int16,
  
  caretOffset :: FWord,
  
  numOfLongHorMetrics :: Word16}
  deriving Show
putHheaTable :: HheaTable -> Put
putHheaTable table = do
  putWord32be 0x00010000
  putInt16be $ ascent table
  putInt16be $ descent table
  putInt16be $ lineGap table
  putWord16be $ advanceWidthMax table
  putInt16be $ minLeftSideBearing table
  putInt16be $ minRightSideBearing table
  putInt16be $ xMaxExtent table
  putInt16be $ caretSlopeRise table
  putInt16be $ caretSlopeRun table
  putInt16be $ caretOffset table
  replicateM_ 5 $ putInt16be 0
  putWord16be $ numOfLongHorMetrics table
  
getHheaTable :: Get HheaTable
getHheaTable =
  HheaTable <$> getWord32be <*> getInt16be <*>
  getInt16be <*> getInt16be <*> getWord16be <*>
  getInt16be <*> getInt16be <*> getInt16be <*>
  getInt16be <*> getInt16be <*> getInt16be <*>
  (skip 10 *> getWord16be)