Yhc/RTS/hbc
Part of Yhc |
FIXME: needs explanation.
.hbc File
struct HbcFile { Header header; StringTable strings; QualifId moduleName; ObjectTable objects; };
Header
struct Header { Char magic[4]; /* 'H' 'S' 'B' 'C' */ UInt16 majorVersion; UInt16 minorVersion; UInt16 zero; /* 0 */ UInt16 numObjects; };
StringTable
struct StringTable { UInt16 numStrings; String strings[numStrings]; };
struct String { UInt16 length; Char data[length]; };
ObjectTable
struct ObjectTable { Object objects[numObjects]; };
struct Object { QualifId name; UInt16 length; UByte data[length]; };
The first byte of the 'data' section identifies the object type. Depending on the object type the rest of the data for and object has different structures.
Object types
'F' function object (FunObj) 'C' constructor object (ConObj) 'P' primitive object (PrimObj) 'X' external object (ExtObj)
FunObj
struct FunObj { Char type; /* 'F' */ UInt8 arity; UInt16 stack; UInt8 flags; ConstTable consts; UInt16 codeLength; UByte code[codeLength]; };
struct ConstTable { UInt16 numConsts; Constant consts[numConsts]; };
struct Constant { Char type; UByte constData[??]; };
The type of the constant identifies the size and type of the rest of the constant data.
Constant Types
Type Name ConstData Desc
'A' CAF FullyQualifId Reference to a CAF node 'F' FUN FullyQualifId Reference to a FInfo '0' FUN0 FullyQualifId Reference to a zero arity FInfo 'C' CON FullyQualifId Reference to a CInfo 'Z' ZCON FullyQualifId Reference to a zero arity constructor node 'P' PRIM FullyQualifId Reference to a primitive function (XInfo) 'X' EXT FullyQualifId Reference to an external function (XInfo) 'i' INT Int Int constant 'l' INTEGER Integer Integer constant 'f' FLOAT Float Float constant 'd' DOUBLE Float Double constant 's' STRING String String constant
A, Z and 0 are all references to heap nodes and are treated in exactly the same way by the runtime system.
Similarly F, C, P and X are all references to Info structures and are treated in exactly the same way.
The difference between a CAF and a FUN0 is that a CAF is a reference to a function node that takes no arguments and FUN0 is a reference to a function node that has no arguments (so far). For example:
f :: Int f = 2 + 2
g :: Int -> Int g x = f
here the reference to f from g would be a CAF, because f takes no arguments.
f :: Int -> Int f x = 2 + 2
g :: Int -> Int g = f
here the reference to f from g would be a FUN0, because f takes arguments and we want the heap node for the partial application of f to no arguments.
ConObj
struct ConObj { Char type; /* 'C' */ UInt8 size; UInt8 tag; };
PrimObj
struct PrimObj { Char type; /* 'P' */ FullyQualifId name; };
ExtObj
struct ExtObj { Char type; /* 'X' */ String cName; UInt16 arity; Char callConv; Char resultType; Char argTypes[arity]; };
Valid calling conventions are:
'a' direct address (i.e. not function call) 'x' cast (just convert the first argument to the result) 'c' ccall (which might block) 'C' fastccall (which we promise won't block) 'p' primitive (don't try and convert arguments) 's' stdcall (pascal/WIN32 calling convention) 'S' faststdcall (see ccall versus fastccall) 'b' hand written bytecode function, load specially.
Valid result and argument types are:
'i' Int8 'j' Int16 'k Int32 'l' Int64 'w' Word8 'x' Word16 'y' Word32 'z' Word64 'I' Int 'F' Float 'D' Double 'C' Char 'B' Bool 'P' Ptr/FunPtr 'p' StablePtr 'f' ForeignPtr 'u' PackedString 'N' Integer 'H' HaskellFun 'U' () 'u' unknown / not converted.
FullyQualifId
struct FullyQualifId { QualifId module; QualifId item; };
QualifId
struct QualifId { UInt8 length; UInt16 stringIndexs[length]; };
Integer
struct Integer { Int8 length; UByte data[abs(length)]; };
If length < 0 then the whole Integer is negative.
Float
struct Float { Integer mant; Int16 exp; };