In this installment, we'll talk about how to deal with different
data types. As I did in the last segment, I will not incorporate
these features directly into the
compiler at this time.
Instead, I'll be using the same approach that has worked so well
for us in the past: using only fragments of the parser and
single-character tokens. As usual, this allows us to get
directly to the heart of the matter without having to wade
through a lot of unnecessary code. Since the major problems in
dealing with multiple types occur in the arithmetic operations,
that's where we'll concentrate our focus.
TINY
A few words of warning: First, there are some types that I will not be covering in this installment. Here we will only be talking about the simple, predefined types. We won't even deal with arrays, pointers or strings in this installment; I'll be covering them in the next few.
Second, we also will not discuss user-defined types. That will
not come until much later, for the simple reason that I still
haven't convinced myself that user-defined types belong in a
language named KISS
. In later installments, I do intend to cover
at least the general concepts of user-defined types, records,
etc., just so that the series will be complete. But whether or
not they will be included as part of KISS
is still an open issue.
I am open to comments or suggestions on this question.
Finally, I should warn you: what we are about to do can add
considerable extra complication to both the parser and the
generated code. Handling variables of different types is
straightforward enough. The complexity comes in when you add
rules about conversion between types. In general, you can make
the compiler as simple or as complex as you choose to make it,
depending upon the way you define the type-conversion rules.
Even if you decide not to allow any type conversions (as in Ada
,
for example) the problem is still there, and is built into the
mathematics. When you multiply two short numbers, for example,
you can get a long result.
I've approached this problem very carefully, in an attempt to Keep It Simple. But we can't avoid the complexity entirely. As has so often has happened, we end up having to trade code quality against complexity, and as usual I will tend to opt for the simplest approach.
TINY
compiler, it's been getting
longer and longer. I realized a couple of installments back that
this was causing trouble, and that's why I've gone back to using
only compiler fragments for the last installment and this one.
The problem is that it just seems dumb to have to reproduce the
code for, say, processing boolean exclusive OR's, when the
subject of the discussion is parameter passing.
The obvious way to have our cake and eat it, too, is to break up
the compiler into separate sources, and of course
a Forth
source file is an ideal vehicle for doing this. This allows
us to hide some fairly complex code (such as the full arithmetic
and boolean expression parsing) into a single file, and just pull
it in whenever it's needed. In that way, the only code I'll have
to reproduce in these installments will be the code that actually
relates to the issue under discussion.
I've also been toying with Object-oriented Forth
lately. I haven't
decided whether to make use of O-O features, for two reasons.
First of all, many of you who have been following this series may
not have such a feature for their Forth
, and I certainly don't want to force anyone to
have to go out and buy a new compiler just to complete the
series. Secondly, I'm not convinced that the O-O extensions have
all that much value for this application. We've been having some
discussions about that in CompuServe's CLM forum, and so far
we've not found any compelling reason to use O-O constructs.
This is another of those areas where I could use some feedback
from you readers. Anyone want to vote for O-O?
In any case, after the next few installments in the series, the
plan is to upload to you a complete set of sources, and complete
functioning compilers as well. The plan, in fact, is to have
three compilers: One for a single-character version of
(to
use for our experiments), one for TINY
and one for TINY
KISS
. I've
pretty much isolated the differences between
and TINY
KISS
, which
are these:
TINY
will support only two data types: The character and the
32-bit integer. I may also try to do something with
strings, since without them a compiler would be pretty
useless. KISS
will support all the usual simple types,
including arrays and even floating point.
TINY
will only have two control constructs, the IF
and the
WHILE
. KISS
will support a very rich set of constructs,
including one we haven't discussed here before ... the CASE
.
KISS
will support separately compilable modules.
One caveat: Since I still don't know much about 68000 assembler language, all these compiler modules will still be written to support 80x86 code. However, for the programs I plan to upload, all the code generation has been carefully encapsulated into a single file, so that any enterprising student should be able to easily retarget to any other processor. This task is "left as an exercise for the student." I'll make an offer right here and now: For the person who provides us the first robust retarget to 68000, I will be happy to discuss shared copyrights and royalties from the book that's upcoming.
But enough talk. Let's get on with the study of types. As I said earlier, we'll do this one as we did in the last installment: by performing experiments using single-character tokens.
The symbol table structure for single-character tokens is particularly simple, and we've used it several times before. To deal with it, we'll steal some procedures that we've used before.
First, we need to declare the symbol table itself:
-- Variable declarations -------------------------------------- 0 VALUE Look -- lookahead character CREATE ST #26 CHARS ALLOT -- symbol table
Next, we need to make sure it's initialized as part of procedure Init:
-- ------------------------------------------------------------ : clearST ( -- ) ST #26 CHARS '? FILL ; -- ------------------------------------------------------------ : init ( -- ) clearST CR getchar skipwhite ; -- ------------------------------------------------------------
We don't really need the next procedure, but it will be helpful for debugging. All it does is to dump the contents of the symbol table:
-- ------------------------------------------------------------ : ST[n] ( n -- addr ) 'A' - ST + ; : typeof ( char -- ) ST[n] C@ ; -- Dump the symbol table : .symbols ( -- ) CR ." -- type --.--- name ---" 'Z' 1+ 'A' ?DO I ST[n] C@ IF CR 5 HTAB I typeof EMIT #16 HTAB I EMIT ENDIF LOOP ; -- ------------------------------------------------------------
It really doesn't matter much where you put this procedure ... I plan to cluster all the symbol table routines together, so I put mine just after the error reporting procedures.
If you're the cautious type (as I am), you might want to begin with a test program that does nothing but initializes, then dumps the table. Just to be sure that we're all on the same wavelength here, I'm reproducing the entire program below, complete with the new procedures. Note that this version includes support for white space:
-- ----------------------------------------------------------------------------------------------------- 0 VALUE Look -- lookahead character CREATE ST #26 CHARS ALLOT -- symbol table : clearST ( -- ) ST #26 CHARS '?' FILL ; -- clear symbol table -- ----------------------------------------------------------------------------------------------------- -- Get type of symbol : ST[n] ( n -- addr ) 'A' - ST + ; -- ----------------------------------------------------------------------------------------------------- : typeof ( char -- ) ST[n] C@ ; -- ----------------------------------------------------------------------------------------------------- -- Dump symbol table : .symbols ( -- ) CR ." -- type --.--- name ---" 'Z' 1+ 'A' ?DO I ST[n] C@ IF CR 5 HTAB I typeof EMIT #16 HTAB I EMIT ENDIF LOOP ; -- ----------------------------------------------------------------------------------------------------- : getchar ( -- ) EKEY TO Look ; -- read new character from input stream : error ( c-addr u -- ) CR ^G EMIT ." Error: " TYPE ." ." ; -- report an error : aborts ( c-addr u -- ) error ABORT ; -- report error and halt : expected ( c-addr u -- ) S" expected" $+ aborts ; -- report what was expected : alpha? ( char -- tf ) >UPC 'A' 'Z' 1+ WITHIN ; -- recognize an alpha character : digit? ( char -- tf ) '0' '9' 1+ WITHIN ; -- recognize a decimal digit : alnum? ( char -- tf ) DUP alpha? SWAP digit? OR ; -- recognize alphanumeric : white? ( char -- tf ) DUP BL = SWAP Tab = OR ; -- Recognize white space : addop? ( char -- tf ) DUP '+' = SWAP '-' = OR ; -- test for AddOp : mulop? ( char -- tf ) DUP '*' = SWAP '/' = OR ; -- test for MulOp : orop? ( char -- tf ) DUP '|' = SWAP '~' = OR ; -- recognize an OR operand -- ----------------------------------------------------------------------------------------------------- -- Recognize a relop : relop? ( char -- tf ) DUP '=' = OVER '#' = OR OVER '<' = OR SWAP '>' = OR ; -- ----------------------------------------------------------------------------------------------------- -- Skip white space : skipwhite ( -- ) BEGIN Look white? WHILE getchar REPEAT ; -- ------------------------------------------------------------ -- Skip over EOL : fin ( -- ) Look ^M = IF getchar Look ^J = IF getchar ENDIF ENDIF ; -- ----------------------------------------------------------------------------------------------------- -- Match a specific input character : match ( char -- ) DUP Look = IF DROP getchar skipwhite ELSE S" `" ROT CHAR-APPEND &' CHAR-APPEND expected ENDIF ; -- ----------------------------------------------------------------------------------------------------- -- Get an identifier : getname ( -- char ) Look alpha? 0= IF S" Identifier" expected ENDIF Look >UPC getchar skipwhite ; -- ----------------------------------------------------------------------------------------------------- -- Get a number : getnum ( -- num ) Look digit? 0= IF S" Integer" expected ENDIF Look getchar skipwhite ; -- ----------------------------------------------------------------------------------------------------- -- Initialize everything : init ( -- ) clearST CR getchar skipwhite ; -- ----------------------------------------------------------------------------------------------------- -- Main program : types1 ( -- ) init .symbols ; -- -----------------------------------------------------------------------------------------------------
OK, run this program (types1.frt). You should get a (very fast) printout of all the letters of the alphabet (potential identifiers), each followed by a question mark. Not very exciting, but it's a start.
Of course, in general we only want to see the types of the
variables that have been defined. We can eliminate the others by
modifying .Symbols
with an IF
test. Change the loop to read:
I typeof '?' <> IF CR 5 HTAB I typeof EMIT #16 HTAB I EMIT ENDIFNow, run the program again (types2.frt). What did you get? Well, that's even more boring than before! There was no output at all, since at this point none of the names have been declared. We can spice things up a bit by inserting some statements declaring some entries in the main program. Try these:
'a' 'A' ST[n] C! 'b' 'P' ST[n] C! 'c' 'X' ST[n] C!
This time, when you run the program (types3.frt), you should get an output showing that the symbol table is working right.
-- -------------------------------------------------------------------- -- Report if a variable is in the table : intable ( char -- ) typeof '?' <> ; -- -------------------------------------------------------------------- -- Check for a duplicate variable name : name.aborts ( c-addr1 u1 char ) >R S" `" $+ R> CHAR-APPEND &' CHAR-APPEND aborts ; -- -------------------------------------------------------------------- : .duplicate ( char -- ) S" Duplicate identifier" ROT name.aborts ; : checkdup ( char -- ) DUP intable 0= IF DROP EXIT ENDIF .duplicate ; -- -------------------------------------------------------------------- -- Add a new entry to symbol table : addentry ( char type -- ) OVER checkdup SWAP ST[n] C! ; -- --------------------------------------------------------------------Now change the three lines in the main program to read:
'a' 'A' addentry 'b' 'P' addentry 'c' 'X' addentry
and run the program (types4.frt) again. Did it work? Then we have the symbol table routines needed to support our work on types. In the next section, we'll actually begin to use them.
TINY
compiler
itself, we have already addressed the issue of declaring global
variables, and the code generated for them. Let's build a
vestigial version of a "compiler" here, whose only function is to
allow us declare variables. Remember, the syntax for a
declaration is:
<data decl> ::= VAR <identifier>
Again, we can lift a lot of the code from previous programs. The
following are stripped-down versions of those words. They
are greatly simplified since I have eliminated niceties like
variable lists and initializers. In procedure Alloc
, note that
the new call to AddEntry
will also take care of checking for
duplicate declarations:
-- ------------------------------------------------------------ -- Allocate storage for a variable : alloc ( char -- ) 'v' OVER addentry S" CREATE " ROT CHAR-APPEND S" 0 ," $+ emitdln ; -- ------------------------------------------------------------ -- Parse and translate a data declaration : decl ( -- ) 'v' match getname alloc ; -- ------------------------------------------------------------ -- Parse and translate global declarations : topdecls ( -- ) BEGIN Look '.' <> WHILE CASE Look 'v' OF decl ENDOF S" Unrecognized keyword " Look CHAR-APPEND aborts ENDCASE fin REPEAT ; -- ------------------------------------------------------------
Now, in the main program, add a call to TopDecls
and run the
program (types5.frt). Try allocating a
few variables, and note the resulting
code generated. This is old stuff for you, so the results should
look familiar. Note from the code for TopDecls
that the program
is ended by a terminating period.
While you're at it, try declaring two variables with the same name, and verify that the parser catches the error.
TopDecls
to recognize more than one keyword. There are
a number of decisions to be made here, in terms of what the
syntax should be, etc., but for now I'm going to duck all the
issues and simply declare by executive fiat that our syntax will
be:
<data decl> ::= <typename> <identifier>where:
<typename> ::= BYTE | WORD | LONG
We can create the code to take care of these declarations with
only slight modifications. In the routines below, note that I've
separated the code generation parts of Alloc
from the logic
parts. This is in keeping with our desire to encapsulate the
machine-dependent part of the compiler.
-- --------------------------------------------------------------------- -- Generate code for allocation of a variable : allocvar ( char -- ) S" CREATE " ROT CHAR-APPEND S" 0 ," $+ emitdln ; -- --------------------------------------------------------------------- -- Allocate storage for a variable : alloc ( N type -- ) OVER addentry allocvar ; -- ------------------------------------------------------------ -- Parse and Translate a Data Declaration : decl ( -- ) getname ( type) getname ( N) SWAP alloc ; -- ------------------------------------------------------------ -- Parse and translate global declarations : topdecls ( -- ) BEGIN Look '.' <> WHILE CASE Look 'b' OF decl ENDOF 'w' OF decl ENDOF 'l' OF decl ENDOF S" Unrecognized keyword " Look CHAR-APPEND aborts ENDCASE fin REPEAT ; -- ------------------------------------------------------------
Make the changes shown to these procedures, and give the thing a try (types6.frt). Use the single characters 'b', 'w', and 'l' for the keywords (they must be lower case, for now). You will see that in each case, we are allocating the proper storage size. Note from the dumped symbol table that the sizes are also recorded for later use. What later use? Well, that's the subject of the rest of this installment.
Now that we can declare variables of different sizes, it stands
to reason that we ought to be able to do something with them.
For our first trick, let's just try loading them into our working
register, EAX. It makes sense to use the same idea we used for
Alloc
; that is, make a load procedure that can load more than one
size. We also want to continue to encapsulate the machine-dependent
stuff. The load word looks like this:
-- -------------------------------------------------------------- -- Load primary register from variable : loadvariable ( char type -- ) >R DUP intable 0= IF .undefined ENDIF CASE R> 'b' OF S" byte-ptr -> al mov," ENDOF 'w' OF S" word-ptr -> ax mov," ENDOF 'l' OF S" dword-ptr -> eax mov," ENDOF ENDCASE ROT CHAR-PREPEND emitln ; -- --------------------------------------------------------------
Note that this one routine is strictly a code generator; it has no error-checking or other logic. To complete the picture, we need one more layer of software that provides these functions.
First of all, we need to make sure that the type we are dealing with is a loadable type. This sounds like a job for another recognizer:
-- ------------------------------------------------------------- -- Recognize a legal variable type : vartype ( char -- tf ) DUP 'B' = OVER 'W' = OR SWAP 'L' = OR ; -- -------------------------------------------------------------
Next, it would be nice to have a routine that will fetch the type of a variable from the symbol table, while checking it to make sure it's valid:
-- ------------------------------------------------------------ -- Get a variable type from the symbol table : vartype ( ch -- char ) DUP typeof LOCALS| Typ name | Typ vartype? 0= IF S" Identifier `" name CHAR-APPEND S" ' is not a variable" $+ aborts ENDIF Typ ; -- ------------------------------------------------------------
Armed with these tools, a word to cause a variable to be loaded becomes trivial:
-- ------------------------------------------------------------ -- Load a variable to the primary register : Load ( name -- ) DUP vartype loadvariable ; -- ------------------------------------------------------------
(Note to the concerned: I know, I know, all this is all very inefficient. In a production program, we probably would take steps to avoid such deep nesting of procedure calls. Don't worry about it. This is an exercise, remember? It's more important to get it right and understand it, than it is to make it get the wrong answer, quickly. If you get your compiler completed and find that you're unhappy with the speed, feel free to come back and hack the code to speed it up!)
It would be a good idea to test the program at this point (types7.frt). Since we don't have a procedure for dealing with assignments yet, I just added the lines:
'A' load 'B' load 'C' load 'X' load
to the main program. Thus, after the declaration section is complete, they will be executed to generate code for the loads. You can play around with this, and try different combinations of declarations to see how the errors are handled.
I'm sure you won't be surprised to learn that storing variables is a lot like loading them. The necessary procedures are shown next:
-- ------------------------------------------------------------- -- Store primary to variable : storevariable ( char type -- ) >R DUP checktable CASE R> 'B' OF S" al -> " ROT CHAR-APPEND S" byte" ENDOF 'W' OF S" ax -> " ROT CHAR-APPEND S" word" ENDOF 'L' OF S" eax -> " ROT CHAR-APPEND S" dword" ENDOF ENDCASE S" -ptr mov," $+ $+ emitln ; -- ------------------------------------------------------------ -- Store a variable from the primary register : store ( name -- ) DUP vartype storevariable ; -- ------------------------------------------------------------
You can test this one the same way as the loads (types8.frt).
Now, of course, it's a rather small step to use these to handle
assignment statements. What we'll do is to create a special
version of word Block
that supports only assignment
statements, and also a special version of Expression
that only
supports single variables as legal expressions. Here they are:
-- ------------------------------------------------------------ -- Parse and translate an expression : expression ( -- ) getname load ; -- ------------------------------------------------------------ -- Parse and translate an assignment statement : assignment ( -- ) getname LOCAL name '=' match expression name store ; -- ------------------------------------------------------------------ -- Parse and translate a block of statements : block ( -- ) BEGIN Look '.' <> WHILE assignment fin REPEAT ; -- ------------------------------------------------------------------
(It's worth noting that, if anything, the new procedures that permit us to manipulate types are, if anything, even simpler and cleaner than what we've seen before. This is mostly thanks to our efforts to encapsulate the code generator procedures.)
There is one small, nagging problem. Before, we used the Pascal
terminating period to get us out of procedure TopDecls
. This is
now the wrong character ... it's used to terminate Block
. In
previous programs, we've used the BEGIN
symbol (abbreviated 'b')
to get us out. But that is now used as a type symbol.
The solution, while somewhat of a kludge, is easy enough. We'll
use an UPPER CASE 'B' to stand for the BEGIN
. So change the
character in the WHILE
loop within TopDecls
, from '.' to 'B', and
everything will be fine.
Now, we can complete the task by changing the main program to read:
-- ------------------------------------------------------------ -- Main program : types9 ( -- ) init topdecls 'B' match fin block .symbols ; -- ------------------------------------------------------------
(Note that I've had to sprinkle a few calls to Fin
around to get
us out of newline troubles.)
OK, run this program (types9.frt). Try the input:
ba { byte a } *** DON'T TYPE THE COMMENTS!!! *** wb { word b } lc { long c } B { begin } a=a a=b a=c b=a b=b b=c c=a c=b c=c .
For each declaration, you should get code generated that allocates storage. For each assignment, you should get code that loads a variable of the correct size, and stores one, also of the correct size.
There's only one small little problem: The generated code is wrong!
Look at the code for a=c above. The code is:
C dword-ptr -> eax mov, al -> A byte-ptr mov,
This code is correct. It will cause the lower eight bits of C
to
be stored into A, which is a reasonable behavior. It's about all
we can expect to happen.
But now, look at the opposite case. For c=a, the code generated is:
A byte-ptr -> al mov, eax -> C dword-ptr mov,
This is not correct. It will cause the byte variable A to be
stored into the lower eight bits of EAX. According to the rules
for the 80x86 processor, the upper 24 bits are unchanged. This
means that when we store the entire 32 bits into C
, whatever
garbage that was in those high bits will also get stored. Not
good.
So what we have run into here, early on, is the issue of type conversion, or coercion.
Before we do anything with variables of different types, even if it's just to copy them, we have to face up to the issue. It is not the most easy part of a compiler. Most of the bugs I have seen in production compilers have had to do with errors in type conversion for some obscure combination of arguments. As usual, there is a tradeoff between compiler complexity and the potential quality of the generated code, and as usual, we will take the path that keeps the compiler simple. I think you'll find that, with this approach, we can keep the potential complexity in check rather nicely.
Here is the modified version:
-- ------------------------------------------------------------- -- Load a variable to primary register : loadvariable ( char type -- ) >R DUP checktable CASE R> 'B' OF S" byte-ptr -> eax movzx," ENDOF 'W' OF S" word-ptr -> eax movzx," ENDOF 'L' OF S" dword-ptr -> eax mov," ENDOF ENDCASE ROT CHAR-PREPEND emitln ; -- -------------------------------------------------------------
(Note that StoreVariable
needs no similar change.)
If you run some tests with this new version, you will find that everything works correctly now.
I should point out that, by setting the high bits to zero, we are
in effect treating the numbers as unsigned integers. If we want
to treat them as signed ones instead (the more likely case) we
should do a sign extension after the load, instead of a clear
before it. Just to tie this part of the discussion up with a
nice, red ribbon, let's change LoadVariable
as shown below:
-- ------------------------------------------------------------- -- Load a Variable to Primary Register } : loadvariable ( char type -- ) >R DUP checktable CASE R> 'B' OF S" byte-ptr -> eax movzx," ENDOF 'W' OF S" word-ptr -> eax movsx," ENDOF 'L' OF S" dword-ptr -> eax mov," ENDOF ENDCASE ROT CHAR-PREPEND emitln ; -- -------------------------------------------------------------
With this version, a byte is treated as unsigned (as in Pascal
and C
), while a word is treated as signed. (types10.frt)
OK, so that solution's no good. Is there still a relatively easy way to get data conversion? Can we still Keep It Simple?
Yes, indeed. All we have to do is to make the conversion at the other end ... that is, we convert on the way out, when the data is stored, rather than on the way in.
But, remember, the storage part of the assignment is pretty much
independent of the data load, which is taken care of by procedure
Expression
. In general the expression may be arbitrarily
complex, so how can procedure Assignment
know what type of data
is left in register EAX?
Again, the answer is simple: We'll just ask procedure
Expression
! The answer can be returned as a function value.
All of this requires several procedures to be modified, but the
mods, like the method, are quite simple. First of all, since we
aren't requiring LoadVariable
to do all the work of conversion, let's
go back to the simple version:
-- ------------------------------------------------------------ -- Load a variable to primary register : loadvariable ( char type -- ) >R DUP checktable CASE R> 'B' OF S" byte-ptr -> al mov," ENDOF 'W' OF S" word-ptr -> ax mov," ENDOF 'L' OF S" dword-ptr -> eax mov," ENDOF ENDCASE ROT CHAR-PREPEND emitln ; -- ------------------------------------------------------------Next, let's add a new word that will convert from one type to another:
-- ------------------------------------------------------------ -- Convert a data item from one type to another : convert ( source dest -- ) 2DUP = IF 2DROP EXIT ENDIF SWAP 'B' = IF S" al -> eax movzx," emitln ENDIF 'L' = IF S" ax -> eax movsx," emitln ENDIF ; -- ------------------------------------------------------------Next, we need to do the logic required to load and store a variable of any type. Here are the routines for that:
-- ------------------------------------------------------------ -- Load a variable to the primary register : load ( name -- typ ) DUP vartype DUP >R loadvariable R> ; -- ------------------------------------------------------------ -- Store a variable with type T1 from the primary register : store ( name T1 -- ) OVER vartype DUP >R convert R> ( name T2 -- ) storevariable ; -- ------------------------------------------------------------
Note that Load
is a function, which not only emits the code for a
load, but also returns the variable type. In this way, we always
know what type of data we are dealing with. When we execute a
Store
, we pass it the current type of the variable in EAX. Since
Store
also knows the type of the destination variable, it can
convert as necessary.
Armed with all these new routines, the implementation of our
rudimentary assignment statement is essentially trivial.
Procedure Expression
now becomes a function, which returns its
type to procedure Assignment
:
-- ------------------------------------------------------------ -- Parse and translate an expression : expression ( -- type ) getname load ; -- ------------------------------------------------------------ -- Parse and translate an assignment statement : assignment ( -- ) getname LOCAL name '=' match name expression store ; -- ------------------------------------------------------------
Again, note how incredibly simple these two routines are. We've
encapsulated all the type logic into Load
and Store
, and the
trick of passing the type around makes the rest of the work
extremely easy. Of course, all of this is for our special,
trivial case of Expression
. Naturally, for the general case it
will have to get more complex. But you're looking now at the
final version of procedure Assignment
!
All this seems like a very simple and clean solution, and it is
indeed. Compile this program and run the same test cases as
before (types11.frt). You will see that all types of data are converted
properly, and there are few if any wasted instructions. Only the
byte-to-long conversion uses two instructions where one would do,
and we could easily modify Convert
to handle this case, too.
Although we haven't considered unsigned variables in this case, I
think you can see that we could easily fix up procedure Convert
to deal with these types as well. This is "left as an exercise
for the student."
To begin with, we'll need a GetNum
function. We've seen several
versions of this, some returning only a single character, some a
string, and some an integer. The one needed here will return a
integer, so that it can handle anything we throw at it. Note
that no type information is returned here: GetNum
doesn't concern
itself with how the number will be used:
-- ------------------------------------------------------------ -- Get a number : getnum ( -- num ) Look digit? 0= IF S" Integer" expected ENDIF 0 >R BEGIN Look digit? WHILE R> #10 * Look '0' - + >R getchar REPEAT R> skipwhite ; -- -------------------------------------------------------------
Now, when dealing with literal data, we have one little small problem. With variables, we know what type things should be because they've been declared to be that type. We have no such type information for literals. When the programmer says, "-1," does that mean a byte, word, or longword version? We have no clue. The obvious thing to do would be to use the largest type possible, i.e. a longword. But that's a bad idea, because when we get to more complex expressions, we'll find that it will cause every expression involving literals to be promoted to long, as well.
A better approach is to select a type based upon the value of the literal, as shown next:
-- ------------------------------------------------------------ -- Load a constant to the primary register : loadnumber ( n -- tf ) 0 LOCALS| typ N | N ABS #127 <= IF 'B' TO typ ELSE N ABS #32767 <= IF 'W' ELSE 'L' ENDIF TO typ ENDIF N typ loadconstant typ ; -- -------------------------------------------------------------
(I know, I know, the number base isn't really symmetric. You can store -128 in a single byte, and -32768 in a word. But that's easily fixed, and not worth the time or the added complexity to fool with it here. It's the thought that counts.)
Note that LoadNumber
calls a new version of the code generator
routine LoadConstant
, which has an added argument to define the
type:
-- ------------------------------------------------------------ -- Load a constant to the primary register : loadconstant ( N Typ -- ) >R (.) CASE R> 'B' OF S" b# -> al mov," ENDOF 'W' OF S" d# -> ax mov," ENDOF 'L' OF S" d# -> eax mov," ENDOF ENDCASE $+ emitln ; -- ------------------------------------------------------------
Now we can modify procedure Expression
to accomodate the two
possible kinds of factors:
-- ------------------------------------------------------------ -- Parse and translate an expression : expression ( -- type ) Look alpha? IF getname load ELSE getnum loadnumber ENDIF ; -- ------------------------------------------------------------
(Wow, that sure didn't hurt too bad! Just a few extra lines do the job.)
OK, compile this code into your program and give it a try (types12.frt). You'll see that it now works for either variables or constants as valid expressions.
The nice part is that we already have a pattern for dealing with
these more complex expressions. All we have to do is to make
sure that all the procedures called by Expression
(Term
, Factor
,
etc.) always return a type identifier. If we do that, the
program structure gets changed hardly at all.
The first step is easy: We can rename our existing function
Expression
to Term
, as we've done so many times before, and
create the new version of Expression
:
-- ------------------------------------------------------------ -- Parse and translate an expression : expression ( -- typ ) Look addop? IF unop ELSE term ENDIF LOCAL typ BEGIN Look addop? WHILE typ _push CASE Look '+' OF typ add TO typ ENDOF '-' OF typ subtract TO typ ENDOF ENDCASE REPEAT typ ; -- ------------------------------------------------------------
Note in this routine how each procedure call has become a
function call, and how the local variable Typ
gets updated at
each pass.
Note also the new call to a function Unop
, which lets us deal
with a leading unary minus. This change is not necessary ... we
could still use a form more like what we've done before. I've
chosen to introduce UnOp
as a separate routine because it will
make it easier, later, to produce somewhat better code than we've
been doing. In other words, I'm looking ahead to optimization
issues.
For this version, though, we'll retain the same dumb old code, which makes the new routine trivial:
-- ------------------------------------------------------------- -- Process a term with leading unary operator : unop ( -- typ ) _clear 'W' ; -- -------------------------------------------------------------The word
_push
is a code-generator routine, and now has a type
argument:
-- ------------------------------------------------------------- -- Push primary onto stack : _push ( size -- ) CASE 'B' OF S" al push," ENDOF 'W' OF S" ax push," ENDOF 'L' OF S" eax push," ENDOF ENDCASE emitln ; -- -------------------------------------------------------------
Now, let's take a look at functions Add
and Subtract
. In the
older versions of these routines, we let them call code generator
routines PopAdd
and PopSub
. We'll continue to do that, which
makes the functions themselves extremely simple:
-- ------------------------------------------------------------- -- Recognize and translate an add : add ( typ1 -- typ2 ) '+' match term _popadd ; -- ------------------------------------------------------------- -- Recognize and translate a subtract : subtract ( typ1 -- typ2 ) '-' match term _popsub ; -- -------------------------------------------------------------
The simplicity is deceptive, though, because what we've done is
to defer all the logic to _PopAdd
and _PopSub
, which are no longer
just code generation routines. They must also now take care of the type conversions required.
And just what conversion is that? Simple: Both arguments must be of the same size, and the result is also of that size. The smaller of the two arguments must be "promoted" to the size of the larger one.
But this presents a bit of a problem. If the argument to be promoted is the second argument (i.e. in the primary register EAX), we are in great shape. If it's not, however, we're in a fix: we can't change the size of the information that's already been pushed onto the stack.
The solution is simple but a little painful: We must abandon that lovely "pop the data and do something with it" instructions thoughtfully provided by Intel.
The alternative is to assign a secondary register, which I've chosen to be EBX. (Why not EDX? Because I have later plans for the other registers.)
The first step in this new structure is to introduce a _Pop
procedure analogous to the _Push
. This procedure will always _Pop
the top element of the stack into EBX:
-- ------------------------------------------------------------- -- Pop stack into secondary register : _pop ( size -- ) CASE 'B' OF S" bl pop," ENDOF 'W' OF S" bx pop," ENDOF 'L' OF S" ebx pop," ENDOF ENDCASE emitln ; -- -------------------------------------------------------------
The general idea is that all the "Pop-Op" routines can call this
one. When this is done, we will then have both operands in
registers, so we can promote whichever one we need to. To deal
with this, procedure Convert
needs another argument, the register
name:
-- ------------------------------------------------------------- -- Convert a data item from one type to another : convert ( source dest reg$ -- ) DLOCAL regname LOCALS| dest src | src dest = ?EXIT regname S" eax" COMPARE 0= IF dest 'L' = src 'B' = AND IF S" al -> eax movzx," emitln EXIT ENDIF src 'B' = IF S" al -> eax movzx," emitln ENDIF dest 'L' = IF S" ax -> eax movsx," emitln ENDIF EXIT ENDIF regname S" edx" COMPARE 0= IF dest 'L' = src 'B' = AND IF S" dl -> edx movzx," emitln EXIT ENDIF src 'B' = IF S" dl -> edx movzx," emitln ENDIF dest 'L' = IF S" dx -> edx movsx," emitln ENDIF EXIT ENDIF ( .. etcetera ) ; -- -------------------------------------------------------------
The next function does a conversion, but only if the current type T1 is smaller in size than the desired type T2. It is a function, returning the final type to let us know what it decided to do:
-- ------------------------------------------------------------- -- Promote the size of a register value : promote ( T1 T2 reg$ -- tf ) 2OVER = IF 3DROP EXIT ENDIF 2SWAP LOCALS| T2 T1 | T1 'B' = T1 'W' = T2 'L' = AND OR IF T1 T2 2SWAP convert T2 ELSE 2DROP T1 ENDIF ; -- -------------------------------------------------------------
Finally, the following function forces the two registers to be of the same type:
-- ------------------------------------------------------------- -- Force both arguments to same type : sametype ( T1 T2 -- typ ) 2DUP S" edx" promote ( T1 T2 typ) SWAP S" eax" promote NIP ; -- -------------------------------------------------------------
These new routines give us the ammunition we need to flesh out
_PopAdd
and _PopSub
:
-- ------------------------------------------------------------- -- Generate code to add primary to the stack : _popadd ( T1 T2 -- typ ) OVER _pop sametype ( typ) DUP _genadd _popadd ; -- ------------------------------------------------------------- -- Generate code to subtract primary from the stack : _popsub ( T1 T2 -- type ) OVER _pop sametype ( typ) DUP _gensub _popsub ; -- -------------------------------------------------------------
After all the buildup, the final results are almost anticlimactic. Once again, you can see that the logic is quite simple. All the two routines do is to pop the top-of-stack into EBX, force the two operands to be the same size, and then generate the code.
Note the new code generator routines _GenAdd
and _GenSub
. These
are vestigial forms of the original _PopAdd
and _PopSub
. That is,
they are pure code generators, producing a register-to-register add or subtract:
-- ------------------------------------------------------------- -- Add top of stack to primary : _genadd ( size -- ) CASE 'B' OF S" dl -> al add," ENDOF 'W' OF S" dx -> ax add," ENDOF 'L' OF S" edx -> eax add," ENDOF ENDCASE emitln ; -- ------------------------------------------------------------- -- Subtract primary from top of stack : _gensub ( size -- ) S" edx -> eax xchg," emitln CASE 'B' OF S" dl -> al sub," ENDOF 'W' OF S" dx -> ax sub," ENDOF 'L' OF S" edx -> eax sub," ENDOF ENDCASE emitln ; -- -------------------------------------------------------------
OK, I grant you: I've thrown a lot of routines at you since we
last tested the code (types13.frt).
But you have to admit that each new
routine is pretty simple and transparent. If you (like me) don't
like to test so many new routines at once, that's OK. You can
stub out routines like Convert
, Promote
, and SameType
, since they
don't read any inputs. You won't get the correct code, of
course, but things should work. Then flesh them out one at a
time.
When testing the program, don't forget that you first have to
declare some variables, and then start the "body" of the program
with an upper-case 'B' (for BEGIN
). You should find that the
parser will handle any additive expressions. Once all the
conversion routines are in, you should see that the correct code
is generated, with type conversions inserted where necessary.
Try mixing up variables of different sizes, and also literals.
Make sure that everything's working properly. As usual, it's a
good idea to try some erroneous expressions and see how the
compiler handles them.
UnOp
, I'm looking ahead to the time when we're going
to want better code generation. The way the code is organized,
we can achieve this without major modifications to the program.
For example, in cases where the value pushed onto the stack does
not have to be converted, it's still better to use the "pop and
add" instruction. If we choose to test for such cases, we can
embed the extra tests into _PopAdd
and _PopSub
without changing
anything else much.
The procedure for dealing with multiplicative operators is much
the same. In fact, at the first level, they are almost
identical, so I'll just show them here without much fanfare. The
first one is our general form for Factor
, which includes
parenthetical subexpressions:
-- ------------------------------------------------------------- -- Parse and translate a factor DEFER expression ( -- typ ) : factor ( -- typ ) Look '(' = IF '(' match expression ')' match EXIT ENDIF Look alpha? IF getname load EXIT ENDIF getnum loadnumber ; -- ------------------------------------------------------------- -- Recognize and translate a multiply : multiply ( typ1 -- typ2 ) '*' match factor _popmul ; -- ------------------------------------------------------------- -- Recognize and translate a divide : divide ( typ1 -- typ2 ) '/' match factor _popdiv ; -- ------------------------------------------------------------- -- Parse and translate a math term : term ( -- typ ) factor LOCAL typ BEGIN Look mulop? WHILE typ _push CASE Look '*' OF typ multiply TO typ ENDOF '/' OF typ divide TO typ ENDOF ENDCASE REPEAT typ ; -- -------------------------------------------------------------
These routines parallel the additive ones almost exactly. As
before, the complexity is encapsulated within _PopMul
and _PopDiv
.
If you'd like to test the program before we get into that, you
can build dummy versions of them, similar to _PopAdd
and
.
Again, the code won't be correct at this point, but the parser
should handle expressions of arbitrary complexity.
_PopSub
Let's take the case of multiplication first. This operation is similar to the "addops" in that both operands should be of the same size. It differs in two important respects:
The actions that we have to take are best shown in the following table:
T1-> T2 v | B | W | L |
B | Convert EAX to WConvert EDX to W MULS Result = W |
Convert EAX to W MULS Result = L |
Convert EAX to L CALL MUL32 Result = L |
W | Convert EDX to W MULS Result = L |
MULS Result = L |
Convert EAX to L CALL MUL32 Result = L |
L | Convert EDX to L CALL MUL32 Result = L |
Convert EDX to L CALL MUL32 Result = L |
CALL MUL32 Result = L |
This table shows the actions to be taken for each combination of operand types. There are three things to note: First, we assume a library routine MUL32 which performs a 32 x 32 multiply, leaving a >> 32-bit << (not 64-bit) product. If there is any overflow in the process, we choose to ignore it and return only the lower 32 bits.
Second, note that the table is symmetric ... the two operands enter in the same way. Finally, note that the product is always a longword, except when both operands are bytes. (It's worth noting, in passing, that this means that many expressions will end up being longwords, whether we like it or not. Perhaps the idea of just promoting them all up front wasn't all that outrageous, after all!)
Now, clearly, we are going to have to generate different code for the 16-bit and 32-bit multiplies. This is best done by having separate code generator routines for the two cases:
-- ----------------------------------------------------------------- -- Multiply secondary by primary (word) : _genmult ( -- ) S" dx mul," emitln ; \ dx * ax -> dx:ax -- ----------------------------------------------------------------- -- Multiply secondary by primary (long) : _genlongmult ( -- ) S" edx mul," emitln ; \ edx * eax -> edx:eax -- -----------------------------------------------------------------
An examination of the code below for _PopMul
should convince you
that the conditions in the table are met:
-- ------------------------------------------------------------- -- Generate code to multiply primary by stack : _popmul ( typ1 typ2 -- typ ) OVER _pop sametype >R R@ 'W' S" edx" convert R@ 'W' S" eax" convert R@ 'L' = IF _genlongmult ELSE _genmult ENDIF R> 'B' = IF 'W' ELSE 'L' ENDIF ; -- -------------------------------------------------------------
As you can see, the routine starts off just like PopAdd. The two
arguments are forced to the same type. The two calls to Convert
take care of the case where both operands are bytes. The data
themselves are promoted to words, but the routine remembers the
type so as to assign the correct type to the result. Finally, we
call one of the two code generator routines, and then assign the
result type. Not too complicated, really.
At this point, I suggest that you go ahead and test the program. Try all combinations of operand sizes. (types14.frt).
All modern 16-bit CPU's support integer divide. The manufacturer's data sheet will describe this operation as a 32 x 16-bit divide, meaning that you can divide a 32-bit dividend by a 16-bit divisor. Here's the bad news:
If you don't believe it, try dividing any large 32-bit number (meaning that it has non-zero bits in the upper 16 bits) by the integer 1. You are guaranteed to get an overflow exception.
The problem is that the instruction really requires that the resulting quotient fit into a 16-bit result. This won't happen unless the divisor is sufficiently large. When any number is divided by unity, the quotient will of course be the same as the dividend, which had better fit into a 16-bit word.
Since the beginning of time (well, computers, anyway), CPU architects have provided this little gotcha in the division circuitry. It provides a certain amount of symmetry in things, since it is sort of the inverse of the way a multiply works. But since unity is a perfectly valid (and rather common) number to use as a divisor, the division as implemented in hardware needs some help from us programmers.
The implications are as follows:
This looks like a job for another table, to summarize the required actions:
T1-> T2 v |
B | W | L |
B | Convert EAX to W Convert EDX to L DIVS Result = B |
Convert EAX to W Convert EDX to L DIVS Result = W |
Convert EAX to L CALL DIV32 Result = L |
W | Convert EDX to L DIVS Result = B |
Convert EDX to L DIVS Result = W |
Convert EAX to L CALL DIV32 Result = L |
L | Convert EDX to L CALL DIV32 Result = B |
Convert EDX to L CALL DIV32 Result = W |
CALL DIV32 Result = L |
(You may wonder why it's necessary to do a 32-bit division, when the dividend is, say, only a byte in the first place. Since the number of bits in the result can only be as many as that in the dividend, why bother? The reason is that, if the divisor is a longword, and there are any high bits set in it, the result of the division must be zero. We might not get that if we only use the lower word of the divisor.)
The following code provides the correct function for _PopDiv
:
-- ---------------------------------------------------------------------------- -- Generate code to divide stack by the primary : _popdiv ( typ1 typ2 -- typ ) LOCALS| T2 T1 | T1 _pop T1 'L' S" edx" convert T1 'L' = T2 'L' = OR IF T2 'L' S" eax" convert _genlongdiv 'L' EXIT ENDIF T2 'W' S" eax" convert _gendiv T1 ; -- ----------------------------------------------------------------------------
The two code generation procedures are:
-- ---------------------------------------------------------------------------- -- Divide secondary by primary (word) : _gendiv ( -- ) S" eax -> edx xchg, dx div," emitln ; -- ---------------------------------------------------------------------------- -- Divide secondary by primary (long) : _genlongdiv ( -- ) S" eax -> ecx mov, edx -> eax mov, cdq, ecx div," emitln ; -- ----------------------------------------------------------------------------
Note that div,
leaves the (longword) result in EAX.
OK, install the new procedures for division. At this point you should be able to generate code for any kind of arithmetic expression. Give it a whirl! (types14.frt).
The main concept that made things easy was that of converting
procedures such as Expression
into functions that return the type
of the result. Once this was done, we were able to retain the
same general structure of the compiler.
I won't pretend that we've covered every single aspect of the issue. I conveniently ignored unsigned arithmetic. From what we've done, I think you can see that to include them adds no new challenges, just extra possibilities to test for.
I've also ignored the logical operators And
, Or
, etc. It turns
out that these are pretty easy to handle. All the logical
operators are bitwise operations, so they are symmetric and
therefore work in the same fashion as _PopAdd
. There is one
difference, however: if it is necessary to extend the word
length for a logical variable, the extension should be done as an
unsigned number. Floating point numbers, again, are
straightforward to handle ... just a few more procedures to be
added to the run-time library, or perhaps instructions for a math
chip.
Perhaps more importantly, I have also skirted the issue of type checking, as opposed to conversion. In other words, we've allowed for operations between variables of all combinations of types. In general this will not be true ... certainly you don't want to add an integer, for example, to a string. Most languages also don't allow you to mix up character and integer variables.
Again, there are really no new issues to be addressed in this
case. We are already checking the types of the two operands ...
much of this checking gets done in procedures like SameType
.
It's pretty straightforward to include a call to an error
handler, if the types of the two operands are incompatible.
In the general case, we can think of every single operator as
being handled by a different procedure, depending upon the type
of the two operands. This is straightforward, though tedious, to
implement simply by implementing a jump table with the operand
types as indices. In Pascal
, the equivalent operation would
involve nested Case
statements. Some of the called procedures
could then be simple error routines, while others could effect
whatever kind of conversion we need. As more types are added,
the number of procedures goes up by a square-law rule, but that's
still not an unreasonably large number of procedures.
What we've done here is to collapse such a jump table into far fewer procedures, simply by making use of symmetry and other simplifying rules.
TINY
and KISS
will probably not be strongly typed languages,
since I've allowed for automatic mixing and conversion of just
about any type. Which brings up the next issue:
The answer depends on what kind of language you want, and the way you'd like it to behave. What we have not addressed is the issue of when to allow and when to deny the use of operations involving different data types. In other words, what should be the semantics of our compiler? Do we want automatic type conversion for all cases, for some cases, or not at all?
Let's pause here to think about this a bit more. To do so, it will help to look at a bit of history.
FORTRAN II
supported only two simple data types: Integer
and
Real
. It allowed implicit type conversion between real and
integer types during assignment, but not within expressions. All
data items (including literal constants) on the right-hand side
of an assignment statement had to be of the same type. That made
things pretty easy ... much simpler than what we've had to do
here.
This was changed in FORTRAN IV
to support "mixed-mode"
arithmetic. If an expression had any real data items in it, they
were all converted to reals and the expression itself was real.
To round out the picture, functions were provided to explicitly
convert from one type to the other, so that you could force an
expression to end up as either type.
This led to two things: code that was easier to write, and code that was less efficient. That's because sloppy programmers would write expressions with simple constants like 0 and 1 in them, which the compiler would dutifully compile to convert at execution time. Still, the system worked pretty well, which would tend to indicate that implicit type conversion is a Good Thing.
C
is also a weakly typed language, though it supports a larger
number of types. C
won't complain if you try to add a character
to an integer, for example. Partly, this is helped by the C
convention of promoting every char to integer when it is loaded,
or passed through a parameter list. This simplifies the
conversions quite a bit. In fact, in subset C
compilers that
don't support long or float types, we end up back where we were
in our earlier, simple-minded first try: every variable has the
same representation, once loaded into a register. Makes life
pretty easy!
The ultimate language in the direction of automatic type
conversion is PL/I
. This language supports a large number of
data types, and you can mix them all freely. If the implicit
conversions of FORTRAN
seemed good, then those of PL/I
should
have been Heaven, but it turned out to be more like Hell! The
problem was that with so many data types, there had to be a large
number of different conversions, and a correspondingly large
number of rules about how mixed operands should be converted.
These rules became so complex that no one could remember what
they were! A lot of the errors in PL/I
programs had to do with
unexpected and unwanted type conversions. Too much of a Good
Thing can be bad for you!
Pascal
, on the other hand, is a language which is "strongly
typed," which means that in general you can't mix types, even if
they differ only in name, and yet have the same base type!
Niklaus Wirth made Pascal
strongly typed to help keep programmers
out of trouble, and the restrictions have indeed saved many a
programmer from himself, because the compiler kept him from doing
something dumb. Better to find the bug in compilation rather
than the debug phase. The same restrictions can also cause
frustration when you really want to mix types, and they tend to
drive an ex-C-programmer up the wall.
Even so, Pascal
does permit some implicit conversions. You can
assign an integer to a real value. You can also mix integer and
real types in expressions of type Real
. The integers will be
automatically coerced to real, just as in FORTRAN
(and with the
same hidden cost in run-time overhead).
You can't, however, convert the other way, from real to integer,
without applying an explicit conversion function, Trunc
. The
theory here is that, since the numerical value of a real number
is necessarily going to be changed by the conversion (the
fractional part will be lost), you really shouldn't do it in
"secret."
In the spirit of strong typing, Pascal
will not allow you to mix
Char
and Integer
variables, without applying the explicit
coercion functions Chr
and Ord
.
Turbo Pascal
also includes the types Byte
, Word
, and LongInt
.
The first two are basically the same as unsigned integers. In
Turbo, these can be freely intermixed with variables of type
Integer, and Turbo will automatically handle the conversion.
There are run-time checks, though, to keep you from overflowing
or otherwise getting the wrong answer. Note that you still can't
mix Byte
and Char
types, even though they are stored internally
in the same representation.
The ultimate in a strongly-typed language is Ada
, which allows
no implicit type conversions at all, and also will not allow
mixed-mode arithmetic. Jean Ichbiah's position is that
conversions cost execution time, and you shouldn't be allowed to
build in such cost in a hidden manner. By forcing the programmer
to explicitly request a type conversion, you make it more
apparent that there could be a cost involved.
I have been using another strongly-typed language, a delightful
little language called Whimsical
, by John Spray. Although
Whimsical
is intended as a systems programming language, it also
requires explicit conversion every time. There are never any
automatic conversions, even the ones supported by Pascal
.
This approach does have certain advantages: The compiler never has to guess what to do: the programmer always tells it precisely what he wants. As a result, there tends to be a more nearly one-to-one correspondence between source code and compiled code, and John's compiler produces very tight code.
On the other hand, I sometimes find the explicit conversions to
be a pain. If I want, for example, to add one to a character, or
AND
it with a mask, there are a lot of conversions to make. If I
get it wrong, the only error message is "Types are not
compatible." As it happens, John's particular implementation of
the language in his compiler doesn't tell you exactly which types
are not compatible ... it only tells you which line the error is
in.
I must admit that most of my errors with this compiler tend to be
errors of this type, and I've spent a lot of time with the
Whimsical
compiler, trying to figure out just where in the line
I've offended it. The only real way to fix the error is to keep
trying things until something works.
So what should we do in TINY
and KISS
? For the first one, I have
the answer: TINY
will support only the types Char
and Integer
,
and we'll use the C
trick of promoting Chars
to Integers
internally. That means that the TINY
compiler will be much
simpler than what we've already done. Type conversion in
expressions is sort of moot, since none will be required! Since
longwords will not be supported, we also won't need the MUL32 and
DIV32 run-time routines, nor the logic to figure out when to call
them. I like it!
KISS
, on the other hand, will support the type Long.
Should it support both signed and unsigned arithmetic? For the sake of simplicity I'd rather not. It does add quite a bit to the complexity of type conversions. Even Niklaus Wirth has eliminated unsigned (Cardinal) numbers from his new language Oberon, with the argument that 32-bit integers should be long enough for anybody, in either case.
But KISS
is supposed to be a systems programming language, which
means that we should be able to do whatever operations that can
be done in assembler. Since the 80x86 supports both flavors of
integers, I guess KISS
should, also. We've seen that logical
operations need to be able to extend integers in an unsigned
fashion, so the unsigned conversion procedures are required in
any case.
That wraps up our session on type conversions. Sorry you had to wait so long for it, but hope you feel that it was worth the wait.
In the next few installments, we'll extend the simple types to
include arrays and pointers, and we'll have a look at what to do
about strings. That should pretty well wrap up the mainstream
part of the series. After that, I'll give you the new versions
of the TINY
and KISS
compilers, and then we'll start to look at
optimization issues.
See you then.
***************************************************************** * * * COPYRIGHT NOTICE * * * * Copyright (C) 1990 Jack W. Crenshaw. All rights reserved. * * * *****************************************************************