TweetFollow Us on Twitter

Record Definitions
Volume Number:5
Issue Number:2
Column Tag:Forth Forum

Record Definitions

By Jörg Langowski, MacTutor Editorial Staff

“Record definitions in Mach2”

Record structures and arrays are not part of standard Forth implementations. More than two years ago, in V2#7, I had given an example how to implement records. Mach2 has evolved since then, and so have ways of implementing new data structures, as you can see in the Object Forth project by Wayne Joerding that we recently discussed. For those of you who do not want a full object-oriented system, but still ways of defining data structures in an easy way, I have found two examples on the GEnie bulletin boards. Those examples show two fundamentally different approaches to deal with record definitions.

‘Local’ field names - method 1

The problem in setting up the Forth compiler to deal with record definition in a proper way is somewhat similar to implementing an object-oriented programming system. That is, just like a message is local to an object, and the same message may cause different effects on different objects, a field name should be local to a record. In the Pascal record definitions

\1

rec1 = record
 x: real;
 i: integer;
 y: real;
 end;

rec2 = record
 y: real;
 j: integer;
 x: real;
 end;

the field x would create a different offset into a record of type rec2 than for a rec1 type; and rec1.i, rec2.j would be valid while rec1.j, rec2.i would not. So if we define a field name as some kind of Forth word, this word should be in some ‘local vocabulary’ that belongs to the record definition and is only visible while the field reference is resolved.

The other requirement is that we should be able to pass a record as a parameter to a routine, so that given the pointer to a record on the stack, a Forth definition would know how to resolve the field reference. In a strongly typed language like Pascal this is easy; field references into record formal parameters can be resolved at compile time because the procedure arguments are of defined type. In Forth, typically the address of a data structure would be passed on the stack. However, at compile time there is no way we can restrict the type of argument that this address might later point to at run time! This problem could only be solved by type checking built into the record definition and deferring the resolution of the field reference to run time, some sort of ‘late binding’.

The first method of record definition (Listing 1), written by Waymen Askey of Palo Alto Shipping (I added some minor modifications, like floating point and array support), creates a local dictionary for each record template in the Forth dictionary space. When a record template is defined, using the syntax

\2

template rec1
 :real x
 :word i
 :byte c
tend  

its field names x, i and c are compiled into the dictionary together with relevant information for resolving the references. At the end of the template declaration, the dictionary links are changed in such a way that the ‘local’ names are skipped when the dictionary is searched. Let’s declare a record:

\3

rec1 structure myRec

A field of this record is later accessed by using the structure fetch/store words, s@ and s!.

myRec x s@ will put the value in field x of myrec on the floating point stack, and myRec i s@ will put the word value of field i on the stack. The trick Waymen used was to build some intelligence into the fetch/store words. When the record and field words, myRec and x for example, are executed or compiled into a definition, field type and offset are determined and kept in global variables. The s@ word will check these variables and know how to access the field, whether - in immediate execution - to do a byte, word or long word fetch, addressing into an array, or a ten-byte fetch onto the floating point stack for a real number; or at compile time create code that will do these things later.

The drawback of this approach is that field references can only be resolved at compile or immediate execution time. If we wanted to write a word that operates on a record whose address is passed on the stack, we couldn’t use the field names that were defined in the record template - they are only valid right after a record name was executed or compiled. Therefore, a definition like

\4

: getX { myRec -- } myRec x s@ ;  

must fail because myRec is a local variable, not a record name.

An example how to use this method of record declaration with various field types is given at the end of the listing. You see the drawback: Even though the record fields wavelength, temperature, and angle are all themselves structures of the same type parameter, there is no way to factor out the common code in

5

 cr curve1 wavelength name s^ count type .” = “
 curve1 wavelength value s@ f.
 curve1 wavelength unit s^ count type
 cr curve1 temperature name s^ count type .” = “
 curve1 temperature value s@ f.
 curve1 temperature unit s^ count type
 cr curve1 angle name s^ count type .” = “
 curve1 angle value s@ f.
 curve1 angle unit s^ count type

by using a word that would just print name, value and unit of any given parameter. If this problem was resolved, the record compiler would almost be perfect.

‘Global’ field names - method 2

Listing 2 shows a much simpler approach to structure definitions that does not do type checking. I downloaded this code from the Forth Roundtable on GEnie, and unfortunately have not the slightest idea who the author is. All I could find out was that the original code was probably posted on the East Coast Forth Board.

However, since this code solves one of our problems, record passing as formal parameters, I’d like to print it here. Its strategy is much more like that of the structure words built into MacForth Plus. Here, a record template is defined like

\6

RECORD Rectangle
        Global  SHORT: Top
        Global  Short: Left
        Global  Short: Bottom
        Global  SHORT: RIght
ENd.RECORD
 
Variable myRect Rectangle 4 - VALLOT ;

so the record name, when executed, simply leaves the record length on the stack for later ALLOT or VALLOT. The field names are words which add the field offset to an existing address on the stack, so they can be used in any context. We have to check ourselves whether the address is a valid record address and whether the field referenced actually exists in that record (if we care at all). All field names are global, and therefore must be unique; no two different record declarations can have fields of the same name at different offsets.

This approach is not so different from the very basic one that I used in most of my examples, where I simply defined field names as constants and added the offset to the record address.

What the Macintosh Forth world needs is really a combination of the two approaches, with type checking at compile time and local field names for convenience, and a possibility to resolve field references on record addresses at compile time without too much overhead. If one knew the type of the record passed on the stack ahead of time (which is usually the case), one could probably define some ‘field reference resolution word’ which computes an offset given a template and a field name. I hope I can show you an example in one of my next columns.

Upcoming: an update to Wayne Joerding’s Object Forth, and a review of PocketForth, a public domain 16-bit Forth that comes as an application and a desk accessory. Stay tuned.

Listing 1: Structure definitions with local field names
\ STRUCTUREs 2.5   for the Macintosh  MACH2
\ Jan 3, 1987 by Waymen Askey 
\ edited, floating point & array addition by 
\ J. Langowski @ MacTutor
\ This MACH2 extension is released for the public good; 
\ however, for those planning commercial use of this code, 
\ please notify  me so that I might know of its intended use.
\              Waymen Askey @ PASC
\  also GEnie MACH2 RoundTable.

only mac also sane also forth definitions
( VARIABLES used in STRUCTURE 2.5 )
decimal
variable current.template
variable op.type
variable A5offset ( holds the A5 offset to a structure )

( CODE word utilities used in STRUCTURE 2.5 )
code var.link  ( -- a | variable link pointer )
 lea $F7F8(A5),A0
 move.l A0,-(A6)
 rts
end-code

code a5@  ( -- a )
 move.l A5,-(A6)
 rts
end-code mach
  
code get.field  ( a1 a2 -- a3 -1 or 0 | searches templates )
  ( a1=template, a2= pad, a3=field pointer, 0 if not found )
 move.l (A6)+,D2
 move.l (A6)+,D3
 moveq.l #0,D1
 moveq.l #0,D0
@start  movea.l D3,A1
        movea.l D2,A0
        move.b (A1)+,D1  ( link to next field )
        beq.s @end       ( if link=0, field not found )
        move.b (A1),D0
@loop   cmpm.b (A1)+,(A0)+
        dbne D0,@loop
        beq.s @found
        add.l D1,D3   ( increment field pointer )
        bra.s @start
@found  movea.l D3,A1
        move.b 1(A1),D1  ( get string count )
        addq.w #2,D1
        btst #0,D1  ( test for odd count )
        beq.s @even
        addq.w #1,D1
@even   add.l D1,D3
        moveq.l #-1,D1
        move.l D3,-(A6)
@end    move.l D1,-(A6)
        rts
end-code

code >sr  ( n -- | push value onto subroutine stack )
 move.l (A6)+,-(A7)
 rts
end-code mach

code sr>  ( -- n | pop value from subroutine stack )
 move.l (A7)+,-(A6)
 rts
end-code mach

code sr@  ( -- n | copy value from subroutine stack )
 move.l (A7),-(A6)
 rts
end-code mach

( Miscellaneous utility words used in STRUCTURE 2.5 )
: >even  ( a -- a’ | 
 word aligns address, i.e. rounds up to even)
 dup  1 and  + ;

: >odd  ( a -- a’ | odd aligns address, rounds up to odd )
 1 or ;

: needed  ( n -- | checks for at least n items on stack )
 depth 1- > abort” Missing needed stack item(s)! “ ;

( Brute-force machine code words )
: ncode,  
( n1...n -- | machine code defining word, stuffs n words )
 create   dup needed   dup 2* w,   
 0 do   w,   loop
 does>   ( -- | compiles machine code )
 dup   2+ swap   dup w@   +   
 do   i  w@  w,   -2 +loop ;  

hex
( define some machine code “stuff” words )
41ED 1 ncode,  lea_d(a5),a0      
4EBA 1 ncode, jsr_d(PC)
4EAD 1 ncode, jsr_d(A5)
( LEA and JSR also need a word of extension for displacement )
2D3C 1 ncode, move.l_#,-(A6)  
 ( plus a long extension for # )
2D08 1 ncode,  move.l_a0,-(a6)     
4E75 1 ncode,  rts,
( The following expect an address to be in A0 )
7000 1010 2D00 3 ncode, byte@
7000 3010 2D00 3 ncode, word@
2D10 1 ncode, long@
201E 1080 2 ncode, byte!
201E 3080 2 ncode, word!
209E 1 ncode, long!
\ disassemble the following to check how they work.
\ Exercise for the reader... - JL
5187 5587 2247 22d8 22d8 32d8 6 ncode, real@
2247 20d9 20d9 30d9 5087 5487 6 ncode, real!
201e e580 2d30 0000 4 ncode, array@
201e e580 219e 0000 4 ncode, array!
201e e380 4281 3230 0000 2d01 6 ncode, warray@
201e e380 221e 3181 0000 5 ncode, warray!
decimal

( Dictionary header, name, and struct link words )
: link>name   ( lfa -- ‘nf | ‘nf points to header length byte)
 4 + ;
 
: name.count   
 ( ‘nf -- ‘nf+1  n | dictionary header name count)
 count 31 and ;

: link>segment  
 ( lfa -- ‘sf | ‘sf is the dictionary segment field address)
 link>name name.count  +  >even ;
 
: link>parameter  
 ( lfa -- ‘pf | ‘pf is the parameter field pointer)
 link>segment 2+ ;

: link>struct  ( lfa -- struct.fields )
 link>segment 4 + ;
 
: jsr_d(PC),  ( lfa -- | compiles PC relative JSR)
 jsr_d(PC)
 link>body here -  w, ;
 
: jsr_d(A5),  
 ( lfa -- | compiles A5 relative JSR, i.e. jump table )
 jsr_d(A5)  
 link>parameter w@  w, ;
 
: struct.zero  ( -- lfa | returns lfa of struct.zero )
 “ struct.zero” find  drop ;

: nallot  ( n -- | allots n bytes in name space )
 np +! ; 
  
: name,   ( -- parses and compiles text into name space.)
 32 word  np @  over c@ 1+  dup >odd nallot  cmove ;
 
: nc,  ( n -- | compiles byte into name space )
 np @ c!   1 nallot ;
 
: nw,  ( n -- | compiles word into name space )
 np @ w!   2 nallot ;
 
: n,  ( n -- | compiles long into name space )
 np @ !   4 nallot ;
 
( TEMPLATE, STRUCTURE and field words )
: struct.error  ( -- )
  cr pad count type 
  .”  ?  Error, unknown field or incomplete structure path! “
  abort ;
  
global 
: template  ( -- here 0 | begins TEMPLATE definition )   
  create here 0   2 allot 
  does>  ( -- template.size ) 
    dup w@ swap 4 - body>link   current.template ! ;
 
: tend  
 ( here n -- | (T)emplate(END) ends template definition  )
  swap w!   0 nw, ;
  
global 
: afield  ( size op.type --  )
  create  w,  >even w,
  does>  ( here Toffset -- here new.Toffset )
         ( Toffset means (T)emplate(OFFSET) )  
    2dup 2+   w@  + >sr  
    w@  np @ >sr  1 nallot  name,  
    0 nc, ( field type=0 )   nc, ( op.type )   
    nw, ( Toffset )   np @ sr@ - sr> c! ( field link )
    sr> ;
  
( The following op.types are reserved and defined below )
( 06 byte, 12 word, 18 long, 24 string, 
 30 real, 36 struct, 42 array, 48 warray )

( size.in.bytes op.type  AFIELD  named.afield.type )
1  06 afield  :byte   
2  12 afield  :word
4  18 afield  :long
10 30 afield  :real

: :string  ( here Toffset size -- here Toffset+size+1  )
 3 needed  1+   over +   >even swap   
 np @ >sr  1 nallot  name,   
 0 nc, ( field type=0 )   24 nc, ( op.type=24) 
   nw, ( Toffset )   np @ sr@ - sr> c! ( field link ) ;     

: :array  ( here Toffset size -- here Toffset+size+1  )
 3 needed  4* over +   swap   np @ >sr  1 nallot  name,   
 0 nc, ( field type=0 )   42 nc, ( op.type=42) 
  nw, ( Toffset )   np @ sr@ - sr> c! ( field link ) ;     

: :warray  ( here Toffset size -- here Toffset+size+1  )
 3 needed  2* over +   swap   np @ >sr  1 nallot  name,   
 0 nc, ( field type=0 )   48 nc, ( op.type=48) 
  nw, ( Toffset )   np @ sr@ - sr> c! ( field link ) ;     

: :struct  ( here Toffset size -- here Toffset+size  )
 3 needed  over +   >even swap   
 np @ >sr  1 nallot  name,  
 06 nc, ( field type=06 )  36 nc, ( op.type=36 )
 nw, ( Toffset )
 current.template @  struct.zero - n, ( template link )  
  np @ sr@ - sr> c! ( field link ) ;  

: >pad  ( a -- | moves string to pad )
  pad over c@ 1+  cmove ;

: make.var.link  { | name.pointer var.pointer vlink --  }
 np @ -> name.pointer  var.link @ -> var.pointer   
 name.pointer var.link ! 
 name.pointer var.pointer -    -> vlink
 name.pointer dup 1 and + -> name.pointer
 vlink name.pointer !
 name.pointer 4 + np ! ;

( Decision table for field type decode )
: do.afield ( ^field.type --  true )
 1+ dup c@ op.type !   1+ w@ A5offset +!   -1 ;

: do.bfield  ( ^field.type -- new.template false )
 dup 1+ dup c@ op.type !   1+ w@ A5offset +!
 4 + @   struct.zero +   link>struct   0 ; 

: rts rts, ; immediate
 
( DO.FIELD table entries decode field data )
( afield’s are simple :BYTE, :WORD, 
 :LONG, :STRING types )
( bfield’s are :STRUCT fields )

create do.field  ( field_type  table_offset/type )
]do.afield rts  (   afield         0            )
 do.bfield rts  (   bfield         6            )
[                ( end of current table          )

global
: make.struct  (  template.link A5offset  -- )   
( This is the word which must resolve a structure reference. )
  A5offset !  ( A5 displacement for the struct )
  36 op.type !  ( set default op.type to struct )
  struct.zero +  link>struct  ( template.address -- )
  begin    
    32 word   >pad
    pad get.field        
    if  ( field found )
      dup  c@ do.field +  execute
    else ( field not found )
      pad find 1 = 
      if 
        link>body   execute  -1
      else 
        struct.error
      then 
    then  
  until ;

hex
: structure  
( n -- | creates structure alloting n bytes in variable space )
  1 needed create   immediate make.var.link   
  -4 allot lea_d(a5),a0  vp @ w,  ( variable-like beginning )
  move.l_#,-(A6)  current.template @ struct.zero - ,    
  move.l_#,-(A6)   vp @ ,  
  “ make.struct” find drop dup link>segment  w@ 0=
  if  jsr_d(PC),  else  jsr_d(A5), then
  rts,   
  vallot ; 
decimal

( STRUCTURE operators )
: compileA5  ( -- | compiles A5 reference )
  lea_d(a5),a0  a5offset @ w, ;

: pushA5  ( -- | executes A5 var reference )
  a5offset @ a5@ + ;

: do.bit  ( -- )  ( I’m lazy, define your own.  W. Askey )
  cr .” BIT operations are yet undefined!” abort ;
 
: do.struct  ( -- )  ( Fetch/store doesn’t make sense here. )   
  cr .” STRUCTURE fetch/store operations are undefined! “ abort ;
  
: do.string  ( -- )  ( If you wish, define your own. )
  cr .” STRING fetch/store operations are undefined! “ abort ;
  
: do.byte@  ( f -- )
  if compileA5  byte@ else  pushA5 c@ then ;
 
: do.word@  ( f -- )
  if compileA5  word@ else pushA5 w@ then ;
  
: do.long@  ( f -- )
  if compileA5 long@ else pushA5 @ then ;
 
: do.array@  ( idx f -- )
  if compileA5 array@ else 4* pushA5 + @ then ;

: do.warray@  ( idx f -- )
  if compileA5 warray@ else 2* pushA5 + w@ then ;

: do.real@  ( f -- )
  if compileA5 real@ else pushA5 f@ then ;

 ( Decision table for fetch )
 create op.table@   ( op.types are offsets into this table ) 
 ]  do.bit rts      ( op.type = 0  )
    do.byte@ rts    (  “  “   = 6  )
    do.word@ rts    (  “  “   = 12 )
    do.long@ rts    (  “   “  = 18  etc, etc. )
    do.string rts
    do.real@ rts
    do.struct rts
 do.array@ rts
 do.warray@ rts
[

: do.byte!  ( f -- )
  if compileA5  byte! else pushA5 c! then ;
 
: do.word!  ( f -- )
  if compileA5  word! else pushA5 w! then ;
  
: do.long!  ( f -- )
  if compileA5 long! else pushA5 ! then ;

: do.array!  ( idx f -- )
  if compileA5 array! else 4* pushA5 + ! then ;

: do.warray!  ( idx f -- )
  if compileA5 warray! else 2* pushA5 + w! then ;

: do.real!  ( f -- )
  if compileA5 real! else pushA5 f! then ;

create op.table!  ( decision table for store )
]do.bit rts
 do.byte! rts
 do.word! rts
 do.long! rts
 do.string rts
 do.real! rts
 do.struct rts
 do.array! rts
 do.warray! rts
[
  
: s^  ( -- a | returns pointer to structure field )
( ALL field types are allowed. i.e. strings, struct, etc. )
 state @ 
 if  compileA5 move.l_a0,-(a6) else pushA5 then 
; immediate

: s@  ( -- data | Fetch field contents, data type smart)
  state @
  op.type @ op.table@ + execute ; immediate

: s!  ( data -- | Store into field, data type smart)
  state @
  op.type @ op.table! + execute ; immediate
 
: stype  ( -- op.type | returns the op.type of a field )
 op.type @  state @ 
  if [compile] literal then 
; immediate
( Examples of structure usage.  Data Storage is limited to the approximately 
32K global area referenced off of register A5 -- just as for regular 
MACH2 variables. Structure references have a REQUIRED syntax, it is best 
NOT to use any non-STRUCTURE Forth words when between field names in 
a structure calling sequence.  That is, please end each structure reference 
prior to any DUP’s, SWAP’s, etc. The structure pointer operator -- S^ 
-- may be used at any place in the structure calling sequence.  S^ will 
return the address of the field or structure itself.  Structures MUST 
be terminated with a defined structure operator!  The defined operators 
in this upload are S^, S@, S!, and STYPE.  WARNING, if you forget to 
terminate a structure, no structure reference will be compiled and an 
error message MAY NOT be given.  Remember also that field names ARE CASE 
SENSITIVE and LOCAL to the structure template.  Last comment, structures 
MAY be nested to any level. ) 

fp

template Point
 :word x
 :word y
tend

template Rect
  :word top
  :word left
  :word bottom
  :word right
tend  ( TEND ends template definition )
  
\ example for FP parameters 
template parameter
30 :string name
 :real value
30 :string unit
tend

template measurement
 :long date \ in internal Mac format
80 :string title
255 :string descriptor
parameter :struct wavelength
parameter :struct temperature
parameter :struct angle
256:array time
256:array counts
tend

measurement structure curve1

: testarray
 100 0 do i 4* i curve1 time s! loop
 100 0 do i curve1 time s@ . cr loop;

: .date ( DateTime DateForm ) { | [ 40 lallot ] mydate -- }
 8 shift ^ mydate call IUDateString ^ mydate count type;

: read.int
 begin
 pad 1+ 80 expect span @ pad c! pad number? not while
 drop cr .” Illegal number [integer], reenter - “
 repeat;

: read.float
 begin
 pad 1+ 80 expect span @ pad c! pad fnumber? not while
 fdrop cr .” Illegal number [float], reenter - “
 repeat;

: setup.curve1 { | dattim -- }
 ^ dattim call readdatetime drop @
 cr .” Today is “ 1 .date
 cr .” Setting up parameters for curve 1.”
 dattim curve1 date s!
 “ lambda” dup c@ 1+ curve1 wavelength name s^ swap cmove 
 “      T” dup c@ 1+ curve1 temperature name s^ swap cmove 
 “  delta” dup c@ 1+ curve1 angle name s^ swap cmove 
 “ [nm]” dup c@ 1+ curve1 wavelength unit s^ swap cmove 
 “  [K]” dup c@ 1+ curve1 temperature unit s^ swap cmove 
 “  [°]” dup c@ 1+ curve1 angle unit s^ swap cmove 
 cr .” Title (one line) - “ cr pad 80 expect
 span @ curve1 title s^ c!
 pad curve1 title s^ 1+ span @ cmove 
 cr .” Description (one line) - “ cr pad 80 expect
 span @ curve1 descriptor s^ c!
 pad curve1 descriptor s^ 1+ span @ cmove
 cr .” lambda [nm] - “ read.float curve1 wavelength value s!
 cr .”      T  [K] - “ read.float curve1 temperature value s!
 cr .”  delta  [°] - “ read.float curve1 angle value s!
\ example setup of ‘measurement data’
 20 0 do
 i i curve1 time s!
 i 100 * i curve1 counts s!
 loop

 cr .” End setup -- “ cr;
 
: dump.curve1 { | [ 80 lallot ] mydate -- }
 cr .” Data taken on “ curve1 date s@ 1 .date
 cr curve1 title s^ count type
 cr curve1 descriptor s^ count type
 cr curve1 wavelength name s^ count type .” = “
 curve1 wavelength value s@ f.
 curve1 wavelength unit s^ count type
 cr curve1 temperature name s^ count type .” = “
 curve1 temperature value s@ f.
 curve1 temperature unit s^ count type
 cr curve1 angle name s^ count type .” = “
 curve1 angle value s@ f.
 curve1 angle unit s^ count type
 cr .” data follows:”
 20 0 do cr
 i curve1 time s@ . space
 i curve1 counts s@ .
 loop
 cr
;
Listing 2: Structure definitions from ECFB
\ downloaded from GEnie  J. L. Nov 1988
\ Originally from East Coast Forth Board, 
\ author A. Nonymous
( This is a set of machforth routines for building records. They allow 
you to build a named record with items of various sizes. Executing the 
record name leaves the record size on the stack, executing an item name 
leaves the offset of the item into the record on the stack. It creates 
a template for the record but not the actual record. Create the record 
with “ create <name> <record name> allot” or “variable <name> <record 
name> 4 - vallot” depending if you want the entry in the dictionary or 
variable space )
 
VOCABULARY RECORDS ( NEW VOCABULARY )
ALSO RECORDS
DEFINITIONS
 
Global
: Align ( n1 -- [n1] or [n1 + 1] makes n word aligned )
        dup 2 mod + ; ( USED TO WORD ALIGN 2 & 4 BYTE ITEMS )
 
Global
: RECORD ( -- a 0)
         HERE 4 +  CREATE  0 dup W,  DOES>  W@ ;
         ( USED TO OPEN A RECORD )
 
Global
: BYTE: ( a n -- a n1+1)
        CREATE DUP W, 1+ DOES> W@ + ;
 
Global
: BYTES: ( a n1 n2 -- a n1+n2 | AN ARRAY OF n2 bytes ) 
        CREATE OVER Align W, swap Align + DOES> W@ + ;
 
Global
: SHORT: ( a n1  -- a n1+2 | 2 byte integer item )
        CREATE Align DUP W, 2+ DOES> W@ + ;

Global
: WORD: ( a n1  -- a n1+2 | 2 byte integer item )
        CREATE Align DUP W, 2+ DOES> W@ + ;
 
Global
: BOOLEAN: ( a n1  -- a n1+2 | 2 byte boolean item )
        CREATE Align DUP W, 2+ DOES> W@ + ;
Global
: SHORTS: ( a n1 n2 -- a n1+n2*2 | an array of n2 shorts )
   CREATE OVER Align  W,  2* Swap Align  + DOES> W@ + ;
 
Global
: LONG:  ( a n1  -- a n1+4 | a 4 byte integer )
        CREATE Align DUP W, 4 + DOES> W@ + ;
Global
: POINTER:  ( a n1  -- a n1+4 | a 4 byte integer )
        CREATE Align DUP W, 4 + DOES> W@ + ;
Global
: LONGS: 
 ( a n1 n2 -- a n1+n2*4 | an array of n2 4 byte integers )
  CREATE OVER Align  W, 4 * swap Align + DOES> W@ + ;
Global
: HANDLE: ( a n1  -- a n1+4 | a handle, 4 byte, item )
        CREATE Align DUP W, 4 + DOES> W@ + ;
Global
: HANDLES: ( a n1 n2 -- a n1+n2*4| array of n2 handles )
  CREATE OVER Align  W, 4 * swap Align  + DOES> W@ + ;
 
Global
: ADDR: ( a n1  -- a n1+4 | 4 byte address item, ie pointer )
        CREATE Align DUP W, 4 + DOES> W@ + ;
Global
: ADDRS: ( a n1 n2 -- a n1+n2*4 | array of n2 addresses )
  CREATE OVER Align  W, 4 * swap Align + DOES> W@ + ;
Global
: RECT: ( a n1 n2 -- a n1+8 | a rect item )
  CREATE Align DUP W, 8 + DOES> W@ + ;
Global
: RECTS: ( a n1 n2 -- a n1+n2*8 | an array of n2 rects )
  CREATE  OVER Align  W, 8 * swap Align + DOES> W@ + ;
Global
: STRING: ( a n1 n2 -- a n1+n2+1 | a string item n2+1 long ) 
  CREATE OVER W, + 1+ DOES> W@ + ;
Global
: RECORD: ( a n1 n2 -- a n1+n2 | a record item of size n2) 
  CREATE OVER Align  W, swap Align + DOES> W@ + ;
Global
: END.RECORD 
 { Mainaddr size --|sets size of struct at a to n }
                Mainaddr W@ Size <
                IF Size MainAddr W! THen ;
          ( CLOSES RECORD, STORES RECORD SIZE IN RECORD NAME)
Global
: SUB.REC ( -- )
        CReate  0 W, 2DUP Here 2- Rot Rot DOES> W@ ;
        ( USE TO CREATE VARIANT RECORD ON THE END OF A RECORD)
Global
: END.SUB { SubAddrs MainAddrs Size -- }
        Size SubAddrs W!
        MainAddrs W@ Size <
        IF Size Align MainAddrs W! THen ;
        ( USE TO CLOSE VARIANT RECORD ) 
 
ONLY MAC
ALSO FORTH
DEFINITIONS
ALSO RECORDS
 
Global
RECORD Rectangle
        Global  SHORT: Top
        Global  Short: Left
        Global  Short: Bottom
        Global  SHORT: RIght
ENd.RECORD
 
Global
: rect Variable Rectangle 4 - VALLOT ;
( CREATES A RECTANGLE RECORD IN THE VARIABLE SPACE )

 

Community Search:
MacTech Search:

Software Updates via MacUpdate

Ableton Live 11.3.11 - Record music usin...
Ableton Live lets you create and record music on your Mac. Use digital instruments, pre-recorded sounds, and sampled loops to arrange, produce, and perform your music like never before. Ableton Live... Read more
Affinity Photo 2.2.0 - Digital editing f...
Affinity Photo - redefines the boundaries for professional photo editing software for the Mac. With a meticulous focus on workflow it offers sophisticated tools for enhancing, editing and retouching... Read more
SpamSieve 3.0 - Robust spam filter for m...
SpamSieve is a robust spam filter for major email clients that uses powerful Bayesian spam filtering. SpamSieve understands what your spam looks like in order to block it all, but also learns what... Read more
WhatsApp 2.2338.12 - Desktop client for...
WhatsApp is the desktop client for WhatsApp Messenger, a cross-platform mobile messaging app which allows you to exchange messages without having to pay for SMS. WhatsApp Messenger is available for... Read more
Fantastical 3.8.2 - Create calendar even...
Fantastical is the Mac calendar you'll actually enjoy using. Creating an event with Fantastical is quick, easy, and fun: Open Fantastical with a single click or keystroke Type in your event details... Read more
iShowU Instant 1.4.14 - Full-featured sc...
iShowU Instant gives you real-time screen recording like you've never seen before! It is the fastest, most feature-filled real-time screen capture tool from shinywhitebox yet. All of the features you... Read more
Geekbench 6.2.0 - Measure processor and...
Geekbench provides a comprehensive set of benchmarks engineered to quickly and accurately measure processor and memory performance. Designed to make benchmarks easy to run and easy to understand,... Read more
Quicken 7.2.3 - Complete personal financ...
Quicken makes managing your money easier than ever. Whether paying bills, upgrading from Windows, enjoying more reliable downloads, or getting expert product help, Quicken's new and improved features... Read more
EtreCheckPro 6.8.2 - For troubleshooting...
EtreCheck is an app that displays the important details of your system configuration and allow you to copy that information to the Clipboard. It is meant to be used with Apple Support Communities to... Read more
iMazing 2.17.7 - Complete iOS device man...
iMazing is the world’s favourite iOS device manager for Mac and PC. Millions of users every year leverage its powerful capabilities to make the most of their personal or business iPhone and iPad.... Read more

Latest Forum Discussions

See All

‘Junkworld’ Is Out Now As This Week’s Ne...
Epic post-apocalyptic tower-defense experience Junkworld () from Ironhide Games is out now on Apple Arcade worldwide. We’ve been covering it for a while now, and even through its soft launches before, but it has returned as an Apple Arcade... | Read more »
Motorsport legends NASCAR announce an up...
NASCAR often gets a bad reputation outside of America, but there is a certain charm to it with its close side-by-side action and its focus on pure speed, but it never managed to really massively break out internationally. Now, there's a chance... | Read more »
Skullgirls Mobile Version 6.0 Update Rel...
I’ve been covering Marie’s upcoming release from Hidden Variable in Skullgirls Mobile (Free) for a while now across the announcement, gameplay | Read more »
Amanita Design Is Hosting a 20th Anniver...
Amanita Design is celebrating its 20th anniversary (wow I’m old!) with a massive discount across its catalogue on iOS, Android, and Steam for two weeks. The announcement mentions up to 85% off on the games, and it looks like the mobile games that... | Read more »
SwitchArcade Round-Up: ‘Operation Wolf R...
Hello gentle readers, and welcome to the SwitchArcade Round-Up for September 21st, 2023. I got back from the Tokyo Game Show at 8 PM, got to the office here at 9:30 PM, and it is presently 11:30 PM. I’ve done what I can today, and I hope you enjoy... | Read more »
Massive “Dark Rebirth” Update Launches f...
It’s been a couple of months since we last checked in on Diablo Immortal and in that time the game has been doing what it’s been doing since its release in June of last year: Bringing out new seasons with new content and features. | Read more »
‘Samba De Amigo Party-To-Go’ Apple Arcad...
SEGA recently released Samba de Amigo: Party-To-Go () on Apple Arcade and Samba de Amigo: Party Central on Nintendo Switch worldwide as the first new entries in the series in ages. | Read more »
The “Clan of the Eagle” DLC Now Availabl...
Following the last paid DLC and free updates for the game, Playdigious just released a new DLC pack for Northgard ($5.99) on mobile. Today’s new DLC is the “Clan of the Eagle" pack that is available on both iOS and Android for $2.99. | Read more »
Let fly the birds of war as a new Clan d...
Name the most Norse bird you can think of, then give it a twist because Playdigious is introducing not the Raven clan, mostly because they already exist, but the Clan of the Eagle in Northgard’s latest DLC. If you find gathering resources a... | Read more »
Out Now: ‘Ghost Detective’, ‘Thunder Ray...
Each and every day new mobile games are hitting the App Store, and so each week we put together a big old list of all the best new releases of the past seven days. Back in the day the App Store would showcase the same games for a week, and then... | Read more »

Price Scanner via MacPrices.net

Apple AirPods 2 with USB-C now in stock and o...
Amazon has Apple’s 2023 AirPods Pro with USB-C now in stock and on sale for $199.99 including free shipping. Their price is $50 off MSRP, and it’s currently the lowest price available for new AirPods... Read more
New low prices: Apple’s 15″ M2 MacBook Airs w...
Amazon has 15″ MacBook Airs with M2 CPUs and 512GB of storage in stock and on sale for $1249 shipped. That’s $250 off Apple’s MSRP, and it’s the lowest price available for these M2-powered MacBook... Read more
New low price: Clearance 16″ Apple MacBook Pr...
B&H Photo has clearance 16″ M1 Max MacBook Pros, 10-core CPU/32-core GPU/1TB SSD/Space Gray or Silver, in stock today for $2399 including free 1-2 day delivery to most US addresses. Their price... Read more
Switch to Red Pocket Mobile and get a new iPh...
Red Pocket Mobile has new Apple iPhone 15 and 15 Pro models on sale for $300 off MSRP when you switch and open up a new line of service. Red Pocket Mobile is a nationwide service using all the major... Read more
Apple continues to offer a $350 discount on 2...
Apple has Studio Display models available in their Certified Refurbished store for up to $350 off MSRP. Each display comes with Apple’s one-year warranty, with new glass and a case, and ships free.... Read more
Apple’s 16-inch MacBook Pros with M2 Pro CPUs...
Amazon is offering a $250 discount on new Apple 16-inch M2 Pro MacBook Pros for a limited time. Their prices are currently the lowest available for these models from any Apple retailer: – 16″ MacBook... Read more
Closeout Sale: Apple Watch Ultra with Green A...
Adorama haș the Apple Watch Ultra with a Green Alpine Loop on clearance sale for $699 including free shipping. Their price is $100 off original MSRP, and it’s the lowest price we’ve seen for an Apple... Read more
Use this promo code at Verizon to take $150 o...
Verizon is offering a $150 discount on cellular-capable Apple Watch Series 9 and Ultra 2 models for a limited time. Use code WATCH150 at checkout to take advantage of this offer. The fine print: “Up... Read more
New low price: Apple’s 10th generation iPads...
B&H Photo has the 10th generation 64GB WiFi iPad (Blue and Silver colors) in stock and on sale for $379 for a limited time. B&H’s price is $70 off Apple’s MSRP, and it’s the lowest price... Read more
14″ M1 Pro MacBook Pros still available at Ap...
Apple continues to stock Certified Refurbished standard-configuration 14″ MacBook Pros with M1 Pro CPUs for as much as $570 off original MSRP, with models available starting at $1539. Each model... Read more

Jobs Board

Omnichannel Associate - *Apple* Blossom Mal...
Omnichannel Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
Cashier - *Apple* Blossom Mall - JCPenney (...
Cashier - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Blossom Mall Read more
Operations Associate - *Apple* Blossom Mall...
Operations Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
Retail Key Holder- *Apple* Blossom Mall - Ba...
Retail Key Holder- APPLE BLOSSOM MALL Brand: Bath & Body Works Location: Winchester, VA, US Location Type: On-site Job ID: 03YM1 Job Area: Store: Sales and Support Read more
Omnichannel Associate - *Apple* Blossom Mal...
Omnichannel Associate - Apple Blossom Mall Location:Winchester, VA, United States (https://jobs.jcp.com/jobs/location/191170/winchester-va-united-states) - Apple Read more
All contents are Copyright 1984-2011 by Xplain Corporation. All rights reserved. Theme designed by Icreon.