CAF vs 0-arity function question

The HBC bytecode format has different constant tags for the folloing: 1) CAF, tag 'A' 2) 0-arity function, tag '0' http://haskell.org/haskellwiki/Yhc/RTS/hbc Why the distinction? Maybe I don't fully understand, but I thought that a 0-arity function _was_ a CAF? The runtime seems to treat them very much the same (although I can't be quite sure -- reading C gives me a headache ;) Rob Dockins

Robert Dockins wrote:
The HBC bytecode format has different constant tags for the folloing:
1) CAF, tag 'A' 2) 0-arity function, tag '0'
http://haskell.org/haskellwiki/Yhc/RTS/hbc
Why the distinction? Maybe I don't fully understand, but I thought that a 0-arity function _was_ a CAF?
The runtime seems to treat them very much the same (although I can't be quite sure -- reading C gives me a headache ;)
Maybe a 0-arity function is a non-updatable CAF? Cheers, Simon

Hi Rob, The constant table item constants are somewhat of a legacy. The original constants were chosen to correspond to nhc's constants, however as far as the Yhc runtime is concerned: - A and Z are simply references to heap nodes and are treated in exactly the same way. - F, 0, C, P, X are all references to Info structures and are also treated in exactly the same way. However, you are quite right, looking at the C code 0 is mistakenly included with the A&Z code. This has likely not proved a problem because '0' is infact entirely redundant. The only thing you could do with a 0-arity FInfo is make an application to it, but why would you want to when you can just push the CAF instead? Ultimately we should tidy up the constants to a more simple - Some constant value (i, l, f, d, s) - References to heap nodes (N) - References to FInfo or CInfo (I) For the moment I shall change the C code to make using '0' an error :-) Thanks Tom Robert Dockins wrote:
The HBC bytecode format has different constant tags for the folloing:
1) CAF, tag 'A' 2) 0-arity function, tag '0'
http://haskell.org/haskellwiki/Yhc/RTS/hbc
Why the distinction? Maybe I don't fully understand, but I thought that a 0-arity function _was_ a CAF?
The runtime seems to treat them very much the same (although I can't be quite sure -- reading C gives me a headache ;)
Rob Dockins _______________________________________________ Yhc mailing list Yhc@haskell.org http://www.haskell.org//mailman/listinfo/yhc

Upon further inspection of the code it seems I really don't remember what the constant were for :-) The difference is probably best illustrated by an example: f :: Int f = 2 + 2 g :: Int -> Int g x = f Here g would be compiled to: function g(x): PUSH_CONST 0 RETURN_EVAL constants 0. CAF(A) f Here f is a CAF constant because f is a CAF. However in the next example ... f :: Int -> Int f x = 2 + 2 g :: Int -> Int g = f In this case g would be compiled to: function g(): PUSH_CONST 0 RETURN constants 0. FUN0(0) f Here f is a FUN0 because although f is not a CAF (it takes more than one argument) we want the object that represents the currying of the function f that does take no arguments. So in some sense Simon is right, FUN0 is sort of like a non-updatable CAF, although if my memory serves me correctly the no-argument currying of a function that does take arguments is not defined as a CAF. However, the distinction is still academic, the runtime treats A, Z, and 0 as being exactly the same . I shall update the wiki to make it clearer ... thanks :-) Tom Tom Shackell wrote:
Hi Rob,
The constant table item constants are somewhat of a legacy. The original constants were chosen to correspond to nhc's constants, however as far as the Yhc runtime is concerned:
- A and Z are simply references to heap nodes and are treated in exactly the same way. - F, 0, C, P, X are all references to Info structures and are also treated in exactly the same way.
However, you are quite right, looking at the C code 0 is mistakenly included with the A&Z code. This has likely not proved a problem because '0' is infact entirely redundant. The only thing you could do with a 0-arity FInfo is make an application to it, but why would you want to when you can just push the CAF instead?
Ultimately we should tidy up the constants to a more simple
- Some constant value (i, l, f, d, s) - References to heap nodes (N) - References to FInfo or CInfo (I)
For the moment I shall change the C code to make using '0' an error :-)
Thanks
Tom
Robert Dockins wrote:
The HBC bytecode format has different constant tags for the folloing: 1) CAF, tag 'A' 2) 0-arity function, tag '0'
http://haskell.org/haskellwiki/Yhc/RTS/hbc
Why the distinction? Maybe I don't fully understand, but I thought that a 0-arity function _was_ a CAF?
The runtime seems to treat them very much the same (although I can't be quite sure -- reading C gives me a headache ;)
Rob Dockins _______________________________________________ Yhc mailing list Yhc@haskell.org http://www.haskell.org//mailman/listinfo/yhc
_______________________________________________ Yhc mailing list Yhc@haskell.org http://www.haskell.org//mailman/listinfo/yhc

On May 12, 2006, at 5:52 AM, Tom Shackell wrote:
Upon further inspection of the code it seems I really don't remember what the constant were for :-)
The difference is probably best illustrated by an example:
f :: Int f = 2 + 2
g :: Int -> Int g x = f
Here g would be compiled to:
function g(x): PUSH_CONST 0 RETURN_EVAL
constants 0. CAF(A) f Here f is a CAF constant because f is a CAF. However in the next example ...
f :: Int -> Int f x = 2 + 2
g :: Int -> Int g = f
In this case g would be compiled to:
function g(): PUSH_CONST 0 RETURN
constants 0. FUN0(0) f
Here f is a FUN0 because although f is not a CAF (it takes more than one argument) we want the object that represents the currying of the function f that does take no arguments.
Having looked at some bytecode myself, it looks like the FUN0 is just a shorthand for creating a partial application; you can use the PUSH_CONST instruction instead of the MK_PAP instruction (which takes two arguments). That is perhaps a slight advantage. It doesn't mean "0 arity function" it seems to mean "a partial application with no arguments applied". Con0 is similar: the generated bytecode uses a PUSH_CONST instruction rather than a MK_CON. Here, however, it seems to actually only do this for 0 arity constructors. I'm not sure why one would prefer that in this case, however....
So in some sense Simon is right, FUN0 is sort of like a non- updatable CAF, although if my memory serves me correctly the no- argument currying of a function that does take arguments is not defined as a CAF.
However, the distinction is still academic, the runtime treats A, Z, and 0 as being exactly the same .
I shall update the wiki to make it clearer ...
thanks :-)
Tom
Tom Shackell wrote:
Hi Rob,
The constant table item constants are somewhat of a legacy. The original constants were chosen to correspond to nhc's constants, however as far as the Yhc runtime is concerned:
- A and Z are simply references to heap nodes and are treated in exactly the same way. - F, 0, C, P, X are all references to Info structures and are also treated in exactly the same way.
However, you are quite right, looking at the C code 0 is mistakenly included with the A&Z code. This has likely not proved a problem because '0' is infact entirely redundant. The only thing you could do with a 0-arity FInfo is make an application to it, but why would you want to when you can just push the CAF instead?
Ultimately we should tidy up the constants to a more simple
- Some constant value (i, l, f, d, s) - References to heap nodes (N) - References to FInfo or CInfo (I)
For the moment I shall change the C code to make using '0' an error :-)
Thanks
Tom
Robert Dockins wrote:
The HBC bytecode format has different constant tags for the folloing: 1) CAF, tag 'A' 2) 0-arity function, tag '0'
http://haskell.org/haskellwiki/Yhc/RTS/hbc
Why the distinction? Maybe I don't fully understand, but I thought that a 0-arity function _was_ a CAF?
The runtime seems to treat them very much the same (although I can't be quite sure -- reading C gives me a headache ;)
Rob Dockins _______________________________________________ Yhc mailing list Yhc@haskell.org http://www.haskell.org//mailman/listinfo/yhc
_______________________________________________ Yhc mailing list Yhc@haskell.org http://www.haskell.org//mailman/listinfo/yhc
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG
participants (3)
-
Robert Dockins
-
Simon Marlow
-
Tom Shackell