Yhc/RTS/hbc: Difference between revisions

From HaskellWiki
< Yhc‎ | RTS
No edit summary
 
mNo edit summary
 
(5 intermediate revisions by 3 users not shown)
Line 1: Line 1:
'''FIXME:''' needs more explanation.
{{Yhc}}
 
'''FIXME:''' needs explanation.


=== .hbc File ===
=== .hbc File ===
Line 13: Line 15:


   struct Header {
   struct Header {
     Char           magic[4];        /* 'H' 'S' 'B' 'C' */
     Char           magic[4];        /* 'H' 'S' 'B' 'C' */
     UShort        majorVersion;
     UInt16          majorVersion;
     UShort        minorVersion;
     UInt16          minorVersion;
     UShort        zero;            /* 0 */
     UInt16          zero;            /* 0 */
     UShort        numObjects;       
     UInt16          numObjects;       
   };
   };


Line 23: Line 25:


   struct StringTable {
   struct StringTable {
     UShort         numStrings;
     UInt16         numStrings;
     String        strings[numStrings];
     String        strings[numStrings];
   };
   };


   struct String {
   struct String {
     UShort         length;
     UInt16         length;
     Char          data[length];
     Char          data[length];
   };
   };
Line 40: Line 42:
   struct Object {
   struct Object {
     QualifId      name;
     QualifId      name;
     UShort       length;
     UInt16       length;
     Char          data[length];
     UByte        data[length];
   };
   };


Line 57: Line 59:
   struct FunObj {
   struct FunObj {
     Char        type;                /* 'F' */
     Char        type;                /* 'F' */
     UByte       arity;
     UInt8       arity;
     UShort     stack;
     UInt16     stack;
    UInt8      flags;
     ConstTable  consts;
     ConstTable  consts;
     UShort     codeLength;
     UInt16     codeLength;
     UByte      code[codeLength];
     UByte      code[codeLength];
   };
   };


   struct ConstTable {
   struct ConstTable {
     UShort     numConsts;
     UInt16     numConsts;
     Constant  consts[numConsts];
     Constant  consts[numConsts];
   };
   };
Line 71: Line 74:
   struct Constant {
   struct Constant {
     Char      type;
     Char      type;
     Char      constData[??];
     UByte    constData[??];
   };
   };


Line 92: Line 95:
   'd'    DOUBLE    Float            Double constant
   'd'    DOUBLE    Float            Double constant
   's'    STRING    String            String 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 ===
=== ConObj ===
Line 97: Line 124:
   struct ConObj {
   struct ConObj {
     Char      type;          /* 'C' */
     Char      type;          /* 'C' */
     UByte     size;  
     UInt8     size;  
     UByte     tag;         
     UInt8     tag;         
   };
   };


Line 113: Line 140:
     Char          type;          /* 'X' */
     Char          type;          /* 'X' */
     String        cName;         
     String        cName;         
     UShort       arity;
     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 ===
=== FullyQualifId ===
Line 126: Line 189:


   struct QualifId {
   struct QualifId {
     UByte       length;
     UInt8       length;
     UShort     stringIndexs[length];
     UInt16     stringIndexs[length];
   };
   };


Line 133: Line 196:


   struct Integer {
   struct Integer {
     SByte     length;
     Int8     length;
     UByte     data[abs(length)];
     UByte     data[abs(length)];
   };
   };


Line 143: Line 206:
   struct Float {
   struct Float {
     Integer  mant;
     Integer  mant;
     Short     exp;
     Int16     exp;
   };
   };

Latest revision as of 17:46, 5 October 2008

Part of Yhc

(Download)

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;
 };