module Opentype.Fileformat.Maxp
where
import Opentype.Fileformat.Types
import Data.Binary.Get
import Data.Binary.Put
import Data.Word
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}
  deriving Show
emptyMaxpTable :: MaxpTable
emptyMaxpTable = MaxpTable 0x00010000 0 0 0 0 0 0 0 0 0 0 0 0 0 0 
putMaxpTable :: MaxpTable -> Put
putMaxpTable maxp = do
  putWord32be $ maxpVersion maxp
  putWord16be $ numGlyphs maxp
  putWord16be $ maxPoints maxp
  putWord16be $ maxContours maxp
  putWord16be $ maxComponentPoints maxp
  putWord16be $ maxComponentContours maxp
  putWord16be $ maxZones maxp
  putWord16be $ maxTwilightPoints maxp
  putWord16be $ maxStorage maxp
  putWord16be $ maxFunctionDefs maxp
  putWord16be $ maxInstructionDefs maxp
  putWord16be $ maxStackElements maxp
  putWord16be $ maxSizeOfInstructions maxp
  putWord16be $ maxComponentElements maxp
  putWord16be $ maxComponentDepth maxp
  
getMaxpTable :: Get MaxpTable
getMaxpTable =
  MaxpTable <$> getWord32be <*>
  getWord16be <*> getWord16be <*> getWord16be <*>
  getWord16be <*> getWord16be <*> getWord16be <*>
  getWord16be <*> getWord16be <*> getWord16be <*>
  getWord16be <*> getWord16be <*> getWord16be <*>
  getWord16be <*> getWord16be