TweetFollow Us on Twitter

Segments
Volume Number:4
Issue Number:11
Column Tag:Forth Forum

Code Segments & Linker

By Jörg Langowski, MacTutor Editorial Board

Code segments and a Mach 2 linker

This month I’d like to report on some recent Mach2 improvements: the new 2.14 version and a linker for kernel-independent applications that has recently appeared on the GEnie Mach2 roundtable. Since many of you don’t have access to that BBS, I’ll document the linker here, with some review of code segment structure, and put the code on the source code disk.

Single-segment linker

We have seen several examples - DAs, XCMDs, MDEFs - of Mach2 code that runs independent of the Forth multitasking kernel. Writing such code requires that the programmer write the setup code that is usually provided by the Mach2 system. For the examples that I gave in my column, the standard glue code for making a routine callable from outside Mach2 looked similar to:

CODE prelude
 LINK A6,#-Nstack  
 \ Nstack bytes of local Forth stack
 MOVEM.L A0-A5/D0-D7,-(A7)\ save registers 
 MOVE.L A6,A3  \ setup local loop return stack
 SUBA.L #Nlocal,A3 \ in the low Nlocal stack bytes
 MOVE.L 8(A6),D0 \ pointer to parameter block 
 MOVE.L D0,-(A6)
 RTS  \ just to indicate the MACHro stops here 
END-CODE MACH

CODE epilogue
 MOVEM.L (A7)+,A0-A5/D0-D7\ restore registers 
 UNLK A6
 MOVE.L (A7)+,A0 \ return address
 ADD.W  #4,A7  \ pop off 4 bytes of parameters
 JMP    (A0)
 RTS
END-CODE MACH

: my-forth-code
 ( code to be called externally )
;

: ext.routine
 prelude my-forth-code epilogue
;

After these definitions, the routine ext.routine may be called from the outside as if defined in Pascal as:

procedure ext.routine (parameter:longint);
begin
 ( code to be called externally )
end;

All we need in this case before calling our Forth code is to set up a local Forth stack maintained by the A6 register, save all the registers for safety, and create a loop return stack maintained by A3.

In principle, a complete application can be created this way; however, some more setup is required. A simple one-segment application consists of two CODE resources: the jump table in CODE 0 and the actual code in CODE 1. The structure of the jump table (JT) as given in IM II-60 looks like the following (in the case that the first entry in the JT corresponds to a routine in segment 1):

0: longintAbove A5 size ( 32 + length of JT )
4: longintBelow A5 size (appl. and QD globals)
8: longintLength of jump table in bytes
12:longint  Offset from A5 to jump table (32 )
16:Jump table:
 ------ Jump table entry #1 ------
 word   offset of routine #1 from beginning of
 segment
 longintMOVE.W #1,-(A7)
 ( push segment # of routine on stack)
 word   _LoadSeg
 ------ following jump table entries ----
 ------ for routine #2...n, if necessary ------

When an application is launched, the CODE 0 resource will be loaded and the first JT entry executed. This will load the appropriate segment into memory and jump to the routine to which the first entry is pointing. Thus, a simple one-segment application would consist of a CODE 0 resource like above, with one single JT entry:

 $nnnn  ( entry address in CODE 1 segment )
 ( attention: segment starts at )
 ( beginning of resource + 4)
 $3F3C0001( MOVE.W #1,-(A7) )
 $A9F0  ( _LoadSeg )

CODE 1 would contain the actual code, written in Mach2.

What are the advantages of creating single-segment Mach2 programs? First of all, we can create very small applications. The smallest conceivable application, which does absolutely nothing but return, would comprise only 30 bytes:

CODE 0:
 $00000028( always $20 + length(JT) )
 $00000200( arbitrary )
 $00000008( length of JT; one entry )
 $00000020( always )
 $0000  ( entry address in CODE 1 segment )
 $3F3C0001( MOVE.W #1,-(A7) )
 $A9F0  ( _LoadSeg )
CODE 1:
 $0000  ( first routine is at beginning of JT )
 $0001  ( one entry in this segment )
 $4E75  ( RTS )

This program is enclosed on the source code disk as a curiosity. The file actually is 364 bytes long (Resource map etc.), which is still pretty small.

A second advantage is that we have complete control over the way the application sets itself up. In particular, we could pass a routine pointer to _InitDialogs to activate the Resume button of the system bomb box, or we might want to control the amount of calls to _MoreMasters.

The disadvantage of compiling applications under Mach2: Obviously we have to care about all the things that the kernel normally does for us, like basic event handling, menu and menu bar setup, screen input/output, etc. Particularly, there are quite a few Forth words that may not be used anymore; regular readers of this column should be familiar with the rules for creating ‘kernel-independent code’ that I’ve laid out a few times already.

The Forth words that can be used include:

!  “  +  +!  ^  +>  -  ->  0<  0=  0>  1+  1-  2*  2+  2-  2/  2DROP 
 2DUP  2OVER  <  <>  =  >  >BODY  >R  ?DUP  @  ABS  AND  ASCII  C!  C@ 
 DROP  DUP  EXIT  I  I’  J  LEAVE  L_EXT  NEGATE  NOT  OR   OVER  PAD 
 PICK  R>  R@  SWAP U<  W!  W@  XOR  {   (it’s OK to use local variables)

The following control and branching structures may also be used:

IF  ELSE  THEN  BEGIN  WHILE  REPEAT  UNTIL  AGAIN CASE  ENDCASE  OF 
 ENDOF  DO  LOOP  +LOOP

Assembler, of course, may be used freely.

Waymen Askey, of Palo Alto Shipping, has created a ‘linker’ utility that compiles single-segment application using the strategy given above. We reprint his program in listing 1 with his permission. This linker operates on a program which has the following structure:

PROGRAM  programname;
( definitions not to be included in the final application
such as constants, compiling words, etc. )

VAR
( global variable declarations which will be offset from A5 )

PROCEDURES
( Forth words called by the top level word )

MAIN
( top level word which is called on startup. )
( This word should call the setup procedures )
( MachSetUp and MacintoshSetUp )
( which are provided with the Linker utility. )
END 

The linker computes the ‘below A5’ size from the variables defined after the VAR statement, adding space for the Forth stacks, Quickdraw globals and various other things. The offset of the MAIN entry point into the code segment is calculated and the jump table set up. MakeJumpTable and MakeMain are the words that create the jump table and code segment 1.

MachSetUp initializes the registers for Mach2 usage. Floating point (D7), parameter (A6) and return (A3) stacks are created above the current stack base in the application globals area. The A7 stack, starting at CurStackBase, remains unaffected. The application globals area is then cleared.

MacintoshSetUp does the standard initialization calls to _MoreMasters, _InitGraf, _InitFonts, _InitWindows, _InitMenus, _TEInit, _InitDialogs, _FlushEvents and _InitCursor.

After these initialization calls, the main program may be entered. An example of a short program which creates a window and beeps is given in the listing. This program, too, is only 858 bytes long (!!!).

Mach 2.14 upgrade

For those of you who haven’t yet upgraded to Mach2.14, I’ll briefly review the latest changes.

1. CASE optimization: redundant instruction sequences of the type

 MOVE.L  D0,-(A6)
 MOVE.L (A6)+,D0

are no longer generated.

2. Local variable handling: the new release offers access to the local variable compiler with the words LALLOT and LP@. For example, a word might define a local 16-byte buffer in the following way:

 : EXAMPLE  {  |  [ 12 LALLOT ] myBuffer --  }
 CR  .” Please enter your name “
 ^ myBuffer  16 EXPECT
 CR .” Hello “  ^ myBuffer  SPAN @  TYPE ;

The local variable compiler can be further enhanced through ‘local variable compiling words’; examples on how to do this are given on the 2.14 release disk.

3. Disassembler: References to USER and global variables are now given with their Forth names. Disassembly speed has been greatly improved, which is particularly evident when executing IL on a Mac Plus or SE. 68881 opcodes are now supported, however, 68020-specific instructions not yet.

4. New words: ASCII now takes up to four characters, for easy definition of resource types. 4+, 4-, 4*, 4/ have been added. a n SHIFT will shift a 32-bit word a by n bits.

5. The trap list has been updated.

Feedback dept.

“Dear Jörg,

I saw a discussion of accented character problems in the July MacTutor and thought I would throw in a few digressions on that matter.

First, you and your readers might be interested to know that Apple has removed the scaron and zcaron characters from the new NTX PROMs against the recommendation of Adobe. These characters were not accessible from the keyboard, because they are uncoded, meaning that no ASCII value is assigned. The only way to access them is via Postscript character names. The good news is that several new characters were added making the NTX almost compliant with the ISO 8859 character set that Adobe routinely supplies with all new fonts. (Apple removed the ´y and ´Y, too).

For those of you who want to see the unencoded characters, you can get at them with the following Postscript code and a download utility, if you have one of the new unprotected Adobe fonts or a late model Laserwriter Plus with v.3 PROMs:

/Garamond-Light findfont dup length dict
 /newdict exch def
{1 index /FID 
 ne{ newdict 3 1 roll put }{ pop pop }ifelse
 } forall
/Encoding 256 array def
Encoding 0 /Garamond-Light findfont
/Encoding get 0 256 getinterval putinterval
Encoding 127 /DEL put
Encoding 129 /lslash put
Encoding 130 /Lslash put
Encoding 131 /eth put
Encoding 132 /Eth put
Encoding 133 /thorn put
Encoding 134 /Thorn put
Encoding 135 /onehalf put
Encoding 136 /onequarter put
Encoding 137 /threequarters put
Encoding 138 /brokenbar put
Encoding 139 /onesuperior put
Encoding 140 /twosuperior put
Encoding 141 /threesuperior put
Encoding 142 /scaron put
Encoding 143 /Scaron put
Encoding 144 /zcaron put
Encoding 145 /Zcaron put
Encoding 146 /yacute put
Encoding 147 /Yacute put
newdict /Encoding Encoding put
/IsoGaramond newdict definefont pop
/IsoGaramond findfont 18 scalefont setfont
75 250 moveto 
(ÄÅÇÉÑÖÜáàâäãåçéèêëíì Garamond) show
showpage

Unfortunately there is no way, at present, to get at these with templates in Fontographer, so you have to make your own composites, if you want to add these characters to PostScript fonts.

Best regards, Tim Ryan

SourceNet

P.O.Box 6767

Santa Barbara, CA 93160

PS: The standalone caron () is frequently found as ASCII character 255, one of the last four untypeable characters. It can be accessed using QUED, ... and MS Word if you enter the character using its ASCII value.

By the way, I did get a Greek + Hebrew System from Apple-France via persistent phone calls.

I’ve enclosed the first draft of an article that will appear in my forthcoming book “The Macintosh Book of Fonts”. If you’re interested in reprinting the final draft when it’s available, let me know.

Tim “

Thanks, Tim, for that interesting letter (I’ve enclosed your Postscript code on the source code disk). Now if all these characters were defined somewhere in the standard fonts, wouldn’t that be nice? I always wondered why there were so many empty places in the font definition tables, seems like a waste of space to me

In the next issue we’ll introduce - with other contributions from this side of the Atlantic - a very nice and powerful utility for changing keyboard definitions, so at least that problem can be overcome. Till then.

Listing 1: Mach 2.14 single-segment linker
\ © Waymen Askey c/o Palo Alto Shipping
\ Reprinted with permission. -- JL

\ Guidelines for use of the single-segment “linker.”
\ This utility is NOT meant to replace the
\ standard Mach TURNKEY process.  Its use (at present)
\ is limited to creating small (one-segment, less than
\ 32K) programs which do NOT require the multi-tasking,
\ I/O, and  auto event-handling support which the normal
\ turnkey process supplies.  
\ Also, since this utility is being supplied free to
\ Mach users, Palo Alto Shipping will NOT assume
\ responsibility for support of the utility, nor
\ will we be held responsible for any errors (bugs)
\ which it may produce.
\ It should, however, point the way for other
\ compiler enhancements by users.  The “bottom line” is
\ that Mach can be used to create any type (and size) of 
\ Macintosh application, DA, driver, INIT, etc.  
\ Waymen @ PASC

(
\ The following words MAY be used freely within the 
\ stand-alone, “linked” application.
\

!  “  +  +!  ^  +>  -  ->  0<  0=  0>  1+  1-  2*  2+  2-  
2/  2DROP  2DUP  2OVER  <  <>  =  >  >BODY  >R  ?DUP  @  
ABS  AND  ASCII  C!  C@  DROP  DUP  EXIT  I  I’  J  LEAVE  
L_EXT  NEGATE  NOT  OR   OVER  PAD  PICK  R>  R@  SWAP
U<  W!  W@  XOR  {   (it’s OK to use local variables)
    
\ The following control and branching structures MAY
\ also be used.
\
IF  ELSE  THEN  BEGIN  WHILE  REPEAT  UNTIL  AGAIN  
CASE  ENDCASE  OF  ENDOF  DO  LOOP  +LOOP

\ All assembler words may be used.

\  The following compilation words MAY be used to
\ create your application  (but don’t attempt to
\ compile them, they can’t be executed during the 
\ run-time of your finished application).
\ 
:  ;  VARIABLE  CONSTANT  USER  CREATE  DOES>  
;CODE  CODE  END-CODE  ALLOT  VALLOT  ,  W,  C,  
HERE  COMPILE  [COMPILE]  IMMEDIATE  SMUDGE  LITERAL
LAST  MACH  RECURSIVE  [  ]  
\ Note, global variables may ONLY be used if you
\ declare a VAR block.

\ [‘] should be used with caution.
\ Don’t use it on words defined outside of your
\ program block.
\ If you wish to use EXECUTE, it may be redefined as
\
CODE EXECUTE  ( a -- )
  MOVE.L (A6)+,A0
  JSR (A0)
  RTS
END-CODE MACH

\ ONLY the following MAC vocabulary words MAY be used.
\ Remember to use  (CALL)  instead of  CALL.
\
(CALL)  All CONSTANTS used for the creation of user
interface structures (CLOSEBOX, VISIBLE, etc.)
If you define a VAR block, EVENT-RECORD (and all
other system global variables) may be
used as a storage area only -- events (and other 
information) will NOT automatically be posted
there).
\ These utilities may also be used.
TRAP#  TRAPLIST  TRAPNAME


\ ====================================
\ ========== Can’t Use These ============
\ Words which may NOT be used!!!  This is NOT a
\ complete list, just some of the more common words.
\ You must NOT compile any word which is referenced
\ through Mach’s own jump table (words which compile
\ a JSR d(A5) instruction.
\ 
CALL  GLOBAL  TERMINAL  TURNKEY  NEW.WINDOW  ADD (etc.)
BUILD  TASK  TASK->  BYE  EVENT-TABLE  PAUSE
All I/O such as  KEY  EXPECT  EMIT  .”  TYPE  (etc.)
<#  #  #S  #>  DEPTH  2SWAP  CMOVE  *  /  /MOD  */MOD  */
(if you are using a Mac II exclusively, you may substitute the new 32-bit 
math routines which came with the last Mach upgrades.)  NO SANE words, 
 NO TALKing words,
NO I/O words.  None of the “high-level” FILE words in
the MAC vocabulary.  NO words which reference the 
multi-tasking kernel, NO I/O task words (i.e. events
MUST be handled explicitly, you must create your own
event-loop).
A space for USER variables is reserved for your
program, but all of them (except for the TIB value,
S0, and RETURN_STK) are initialized to zero.
Consider USER variables as just another global storage
area.  Words like BASE and (ABORT) may be used; however, they will have 
NO effect on your program unless you specifically design the words to 
use them. 
)

\ ----------------------------------------------------------------------
\ A simple, one-segment linker which may
\ be used (with restrictions) to create
\ small applications in high-level Forth.
\ Also allows you to create very small assembly
\ language programs (mininum size about 40 bytes)
\ With slight modifications to the “linker” and the
\ proper SetUp word, could also be used 
\ to create DA’s, FKEY’s, XCMD’s, and INIT’s.
\ -- Waymen 
\ @ Palo Alto Shipping Company

ONLY MAC ALSO FORTH DEFINITIONS
DECIMAL

$908    CONSTANT CurStackBase
$434F4445 CONSTANT ‘CODE’
$4150504C CONSTANT ‘APPL’
$3F3F3F3F CONSTANT ‘????’
%1 CONSTANT MainErr
%10CONSTANT EndErr
%100    CONSTANT ProcErr
$12344320 CONSTANT GoodStart
$1234432F CONSTANT StartFlag
$12344328 CONSTANT GoodEnd

\ The default stack and USER variable sizes
\ to be used in building the jump table.
\ I’ve made the USER size larger to allow
\ for a 256 byte PAD
572CONSTANT USERSize ( USER variables)
74 CONSTANT TIBSize( plus STATUS)
600CONSTANT ParameterSize ( A6 & A3 stacks)
200CONSTANT FPSize ( FP stack)
206CONSTANT GrafSize ( QD globals)

$20CONSTANT BL
-1 CONSTANT TRUE
0CONSTANT FALSE

VARIABLE VarEntry
VARIABLE SegmentEntry
VARIABLE MainEntry
VARIABLE SegmentEnd
VARIABLE ProgramFlag
VARIABLE ProgramName 28 VALLOT
VARIABLE JumpTable 20 VALLOT


: -Leading  {  addr cnt | whiteSpace -- addr’ cnt’  }
\ Adjusts addr and cnt to “strip” leading spaces from a string.
\ Addr is the starting character address,
\ cnt is the original length.
 0  -> whiteSpace
 BEGIN
 addr whiteSpace +  C@  BL =
 whiteSpace cnt <  AND
 WHILE
 1  +> whiteSpace
 REPEAT
 addr whiteSpace +
 cnt whiteSpace - ;

: RemoveSpaces  {  addr | cnt  --  }
\ Given counted string at addr, remove trailing and leading 
\ spaces and repack string.
 addr COUNT  -TRAILING  addr C!  DROP
 addr COUNT  -Leading  -> cnt  
 ( addr’) addr 1+  cnt  CMOVE  cnt addr C! ;

: Scan  {  addr num delimiter | cnt char -- flag  }
\ Scans input stream, placing characters into string at addr until 
\ num characters are received or delimiter is found.
\ If delimiter is NOT found prior to num, return FALSE
\ else return TRUE.
 num 0>
 IF
 0  -> cnt
 BEGIN
 0 WORD  1+  C@  -> char
 char  delimiter = NOT
 num cnt  >  AND
 WHILE
 1  +> cnt  char  addr cnt +  C!
 REPEAT
 cnt addr C!  char delimiter =
 ELSE
 0 addr !  FALSE
 THEN ;

: PROGRAM  {  | cnt scanFlag --  }
\ Gets program name and init’s linker variables.
 ProgramName  31  ASCII ;   Scan  -> ScanFlag
 ProgramName RemoveSpaces

 ProgramName C@ 0=  scanFlag 0=  OR  
 ABORT” Must use  ; to delimit program name!”

 0 MainEntry !  0 SegmentEnd !  0 VarEntry !  
 StartFlag ProgramFlag ! ;

: ClearErr  ( errNum -- )
 ProgramFlag @  XOR  ProgramFlag  ! ;

: VAR  ( -- )
\ Ensure that current VP offset from A5 is
\ even, then save it.
 VP @   1 AND 
 IF
 1 VALLOT
 THEN  VP @  ABS VarEntry ! ;

: Globals?  ( -- )
\ Checks to see if a VAR statement was made.
 VarEntry @  0=
 IF
 10 CALL SysBeep
 CR .” WARNING: No global variables were declared!”
 THEN ;

: ?HERE  ( -- a )
\ Ensures that HERE pointer is even, then
\ returns HERE.
 HERE  1 AND 
 IF
 1 ALLOT
 THEN  HERE ;

: PROCEDURES  ( -- )
 ProcErr  ClearErr
 ?HERE SegmentEntry !  4 ALLOT ; 

: MAIN  ( -- )
 MainErr ClearErr
 ?HERE  MainEntry ! ;

: END  ( -- )
 EndErr  ClearErr
 ?HERE  SegmentEnd ! ;

: ZeroFlags  ( -- )
 0 ProgramFlag !  0 VarEntry !  
 0 MainEntry !  0 SegmentEnd ! ;

: BelowA5  ( -- n )
\ Calculates the Below A5 space for
\ the jump table.
 VarEntry @  DUP  0=
 IF
 DROP  GrafSize
 THEN
 USERSize +  TIBSize +
 ParameterSize +  FPSize + ;   

: MakeJumpTable  ( -- handle f )
\  handle is to a generic, one-entry jump table.
 $00000028JumpTable! \ Above A5 size
 BelowA5JumpTable 4 +!  
 \ Global variable space
 $00000008JumpTable 8 + !
 \ Jump table length
 $00000020JumpTable 12 +  ! 
 \ Jump table A5 offset 

 \ Calculate segment entry point
 MainEntry @  SegmentEntry @  4 +  -
 ( entry) JumpTable 16 +  W! 
 $3F3C0001JumpTable 18 +  ! 
 \ MOVE.W #1,-(A7)
 $0001A9F0JumpTable 22 +  W!
 \ _LoadSeg
 JumpTable  24  CALL PtrToHand ;

: MakeMain  ( -- handle f )
 \ Offset to first jump-table entry
 0  SegmentEntry @  W!
 \ Only one jump-table entry
 1  SegmentEntry @  2+  W!
 SegmentEntry @  ( start of segment )
 SegmentEnd @  SegmentEntry @  -   ( length of segment )
 CALL PtrToHand ;
 
: Link  {  refNum |  JumpHandle  MainHandle --  }
\ Creates, then adds CODE segments 0 and 1 
\ to file refNum
 refNum
 IF
 MakeJumpTable  
 IF
 ZeroFlags
 refNum  CALL CloseResFile
 CR .” MakeJumpTable error!”  ABORT
 THEN 
 -> JumpHandle
 JumpHandle  ‘CODE’  0  “ Jump Table”  
 CALL AddResource
 CALL ResError  
 IF
 ZeroFlags
 refNum  CALL CloseResFile
 JumpHandle  CALL DisposHandle  DROP
 CR  .” Link (0): AddResource error!”  ABORT
 THEN

 MakeMain
 IF
 ZeroFlags
 refNum  CALL CloseResFile
 JumpHandle  CALL DisposHandle  DROP
 CR .” MakeMain error!”  ABORT
 THEN
 -> MainHandle
 MainHandle  ‘CODE’  1  “ Main”  
 CALL AddResource
 CALL ResError
 IF
 ZeroFlags
 refNum  CALL CloseResFile
 JumpHandle  CALL DisposHandle  DROP
 MainHandle  CALL DisposHandle  DROP
 CR .” Link (1): AddResource error!” ABORT
 THEN
 THEN ;

: CreateApplFile  {  | refNum --  refNum or zero }
\ Remember to delete previously made files!
 0  -> refNum  
 ‘????’ ‘APPL’ ProgramName  0  CreateFile
 DISK 4 +  W@  0=
 IF
 ProgramName  CALL CreateResFile
 ProgramName  CALL OpenResFile
 \ This logic returns either a valid refNum or zero,
 \ as OpenResFile returns a -1 if it can’t open the file.
 DUP  -1 =  NOT AND  -> refNum  
 THEN  refNum ;

: ?Error  {  errFlag --  }
\ Checks for proper program headings
 errFlag  GoodEnd  XOR
 IF
 CR  .” Missing: “
 errFlag $FFFFFFF0 AND  GoodStart  = 
 IF
 errFlag %111 AND
 CASE
 MainErr  OF.” MAIN “ ENDOF
 EndErr  OF .” END “  ENDOF
 ProcErr  OF.” PROCEDURES “
 ENDOF
 ( else)
 .” MAIN, END and/or PROCEDURES “
 ENDCASE
 ELSE
 .” PROGRAM “
 THEN
 .” Statement(s)!”  ZeroFlags  ABORT
 THEN ;
 
: MakeApplication  {   | refNum --  }
 ProgramFlag @  ?Error
 CreateApplFile  -> refNum
 refNum
 IF
 refNum Link  Globals?
 refNum  CALL CLoseResFile
 ZeroFlags
 ELSE
 CR .” CreateFile error #”  DISK 4 + W@  L_EXT  .
 ZeroFlags  ABORT
 THEN ;

\ ============================================
\ All of the code previous to here will NOT be included
\ in the linked program.  Thus, the above utilities may be
\ workspaced, used and/or enhanced at will.
\ MachSetUp and MacintoshSetUp should appear as the 
\ first statements in your MAIN or LAUNCH word.

CODE MachSetUp  ( -- )
\ Sets up stacks for high-level Forth.
\ Not needed if you work only in assembly language.
 MOVE.L CurStackBase,D0
 MOVE.L D0,D1
 ADD.L #FPSize,D0
 MOVE.L D0,D7  \ FP stack
 MOVEA.L D0,A3 \ “loop” stack
 ADD.L #ParameterSize,D0
 MOVEA.L D0,A6 \ parameter stack
 ADD.L #TIBSize,D0
 MOVEA.L D0,A4 \ USER variables
 MOVEA.L D1,A0
 MOVE.L A5,D0
 SUB.L D1,D0\ below A5 bytes to clear
 DIVU.W #16,D0
 MOVE.W D0,D2  \ “blocks” to clear
 SWAP.W D0\ bytes to clear
 \ Init all globals, USER
 \ vars and stack area to zeros
 BRA.S @20
@10CLR.L (A0)+
 CLR.L (A0)+
 CLR.L (A0)+
 CLR.L (A0)+
@20DBF D2,@10
 BRA.S @40
@30CLR.B (A0)+
@40DBF D0,@30
 \ Although it can’t really be used,
 \ here I set-up the (TIB) USER var
 MOVE.L A6,24(A4)
 MOVE.L A6,4(A4) \ S0 USER var
 MOVE.L A3,12(A4)\ RETURN_STK USER var
 RTS
END-CODE MACH

CODE MacintoshSetUp  ( -- )
 _MoreMasters
 _MoreMasters
 PEA -4(A5)
 _InitGraf
 _InitFonts
 _InitWindows
 _InitMenus
 _TEInit
 CLR.L -(A7)
 _InitDialogs
 MOVE.L #$0000FFFF,D0
 _FlushEvents
 _InitCursor
 RTS
END-CODE MACH
 
\ =============================================
\ ============= An Example =====================

\ From this point on (between the PROCEDURES and END 
\ statement) is where you place your application code.         
PROGRAM My Example;
\ The required and beginning statement in your program.
\ The application will be titled as whatever appears 
\ between the PROGRAM statement and the delimiting 
\ colon (up to 31 characters).
 \ Words defined here 
 \ will NOT be included in your application
 \ The redefintion of CALL is just a reminder.
: CALL  
 CR .” Don’t use CALL here, use (CALL) instead.”  
 ABORT ;  

 0 CONSTANT NIL
 -1 CONSTANT InFront
 10 CONSTANT TenTicks
 30 CONSTANT HalfSecond

VAR
\ All global variables used within the program MUST follow
\ the VAR statement.  If you don’t include the VAR 
\ statement, a warning will be given during program link.  
\ If you don’t use global variables (or Mach system 
\ globals), you may ignore the warning. 
 VARIABLE DelayTicks
 VARIABLE BoundsRect 4 VALLOT
PROCEDURES
\ All subroutines must appear between PROCEDURES and 
\ MAIN. Only that code appearing between the 
\ PROCEDURES and END statements will appear in your 
\ finished application.

 : SetDelay ( n -- ) DelayTicks ! ;
 : Beeper  {  beepTime --  }
 HalfSecond  TenTicks
 DO  
 beepTime  (CALL) SysBeep
 I SetDelay  
 DelayTicks @  (CALL) Delay  DROP  
 TenTicks +LOOP ;
 : MakeWindow  ( -- a | returns a window pointer)
 BoundsRect 20 72 492 322  (CALL) SetRect
 NIL  BoundsRect  “ Beeper Window” VISIBLE
 NOGROW  InFront  NOCLOSEBOX  NIL  
 (CALL) NewWindow ;      
 
 : ProgramLoop  {  | windowPointer --  }
 NIL  -> windowPointer
 MakeWindow  -> windowPointer

 10 Beeper
 
 windowPointer 0= NOT
 IF
 10  (CALL) SysBeep
 windowPointer “ BYE”  (CALL) SetWTitle
 60  (CALL) Delay  DROP
 windowPointer  (CALL) DisposWindow
 THEN ;
MAIN
\ The program’s entry point must appear immediately
\ after  MAIN
 : LAUNCH  ( -- )
 \ Don’t attempt to use local variables in the 
 \ LAUNCH word. The stacks aren’t created until 
 \ after MachSetUp.
 MachSetUp
 MacintoshSetUp
 ProgramLoop ;
END ( of program “My Example”)
\ This statement does error checking 
\ and creates the application.
MakeApplication

CR .( An application called “My Example” has been created.)

 

Community Search:
MacTech Search:

Software Updates via MacUpdate

Latest Forum Discussions

See All

Make the passage of time your plaything...
While some of us are still waiting for a chance to get our hands on Ash Prime - yes, don’t remind me I could currently buy him this month I’m barely hanging on - Digital Extremes has announced its next anticipated Prime Form for Warframe. Starting... | Read more »
If you can find it and fit through the d...
The holy trinity of amazing company names have come together, to release their equally amazing and adorable mobile game, Hamster Inn. Published by HyperBeard Games, and co-developed by Mum Not Proud and Little Sasquatch Studios, it's time to... | Read more »
Amikin Survival opens for pre-orders on...
Join me on the wonderful trip down the inspiration rabbit hole; much as Palworld seemingly “borrowed” many aspects from the hit Pokemon franchise, it is time for the heavily armed animal survival to also spawn some illegitimate children as Helio... | Read more »
PUBG Mobile teams up with global phenome...
Since launching in 2019, SpyxFamily has exploded to damn near catastrophic popularity, so it was only a matter of time before a mobile game snapped up a collaboration. Enter PUBG Mobile. Until May 12th, players will be able to collect a host of... | Read more »
Embark into the frozen tundra of certain...
Chucklefish, developers of hit action-adventure sandbox game Starbound and owner of one of the cutest logos in gaming, has released their roguelike deck-builder Wildfrost. Created alongside developers Gaziter and Deadpan Games, Wildfrost will... | Read more »
MoreFun Studios has announced Season 4,...
Tension has escalated in the ever-volatile world of Arena Breakout, as your old pal Randall Fisher and bosses Fred and Perrero continue to lob insults and explosives at each other, bringing us to a new phase of warfare. Season 4, Into The Fog of... | Read more »
Top Mobile Game Discounts
Every day, we pick out a curated list of the best mobile discounts on the App Store and post them here. This list won't be comprehensive, but it every game on it is recommended. Feel free to check out the coverage we did on them in the links below... | Read more »
Marvel Future Fight celebrates nine year...
Announced alongside an advertising image I can only assume was aimed squarely at myself with the prominent Deadpool and Odin featured on it, Netmarble has revealed their celebrations for the 9th anniversary of Marvel Future Fight. The Countdown... | Read more »
HoYoFair 2024 prepares to showcase over...
To say Genshin Impact took the world by storm when it was released would be an understatement. However, I think the most surprising part of the launch was just how much further it went than gaming. There have been concerts, art shows, massive... | Read more »
Explore some of BBCs' most iconic s...
Despite your personal opinion on the BBC at a managerial level, it is undeniable that it has overseen some fantastic British shows in the past, and now thanks to a partnership with Roblox, players will be able to interact with some of these... | Read more »

Price Scanner via MacPrices.net

You can save $300-$480 on a 14-inch M3 Pro/Ma...
Apple has 14″ M3 Pro and M3 Max MacBook Pros in stock today and available, Certified Refurbished, starting at $1699 and ranging up to $480 off MSRP. Each model features a new outer case, shipping is... Read more
24-inch M1 iMacs available at Apple starting...
Apple has clearance M1 iMacs available in their Certified Refurbished store starting at $1049 and ranging up to $300 off original MSRP. Each iMac is in like-new condition and comes with Apple’s... Read more
Walmart continues to offer $699 13-inch M1 Ma...
Walmart continues to offer new Apple 13″ M1 MacBook Airs (8GB RAM, 256GB SSD) online for $699, $300 off original MSRP, in Space Gray, Silver, and Gold colors. These are new MacBook for sale by... Read more
B&H has 13-inch M2 MacBook Airs with 16GB...
B&H Photo has 13″ MacBook Airs with M2 CPUs, 16GB of memory, and 256GB of storage in stock and on sale for $1099, $100 off Apple’s MSRP for this configuration. Free 1-2 day delivery is available... Read more
14-inch M3 MacBook Pro with 16GB of RAM avail...
Apple has the 14″ M3 MacBook Pro with 16GB of RAM and 1TB of storage, Certified Refurbished, available for $300 off MSRP. Each MacBook Pro features a new outer case, shipping is free, and an Apple 1-... Read more
Apple M2 Mac minis on sale for up to $150 off...
Amazon has Apple’s M2-powered Mac minis in stock and on sale for $100-$150 off MSRP, each including free delivery: – Mac mini M2/256GB SSD: $499, save $100 – Mac mini M2/512GB SSD: $699, save $100 –... Read more
Amazon is offering a $200 discount on 14-inch...
Amazon has 14-inch M3 MacBook Pros in stock and on sale for $200 off MSRP. Shipping is free. Note that Amazon’s stock tends to come and go: – 14″ M3 MacBook Pro (8GB RAM/512GB SSD): $1399.99, $200... Read more
Sunday Sale: 13-inch M3 MacBook Air for $999,...
Several Apple retailers have the new 13″ MacBook Air with an M3 CPU in stock and on sale today for only $999 in Midnight. These are the lowest prices currently available for new 13″ M3 MacBook Airs... Read more
Multiple Apple retailers are offering 13-inch...
Several Apple retailers have 13″ MacBook Airs with M2 CPUs in stock and on sale this weekend starting at only $849 in Space Gray, Silver, Starlight, and Midnight colors. These are the lowest prices... Read more
Roundup of Verizon’s April Apple iPhone Promo...
Verizon is offering a number of iPhone deals for the month of April. Switch, and open a new of service, and you can qualify for a free iPhone 15 or heavy monthly discounts on other models: – 128GB... Read more

Jobs Board

Relationship Banker - *Apple* Valley Financ...
Relationship Banker - Apple Valley Financial Center APPLE VALLEY, Minnesota **Job Description:** At Bank of America, we are guided by a common purpose to help Read more
IN6728 Optometrist- *Apple* Valley, CA- Tar...
Date: Apr 9, 2024 Brand: Target Optical Location: Apple Valley, CA, US, 92308 **Requisition ID:** 824398 At Target Optical, we help people see and look great - and Read more
Medical Assistant - Orthopedics *Apple* Hil...
Medical Assistant - Orthopedics Apple Hill York Location: WellSpan Medical Group, York, PA Schedule: Full Time Sign-On Bonus Eligible Remote/Hybrid Regular Apply Now Read more
*Apple* Systems Administrator - JAMF - Activ...
…**Public Trust/Other Required:** None **Job Family:** Systems Administration **Skills:** Apple Platforms,Computer Servers,Jamf Pro **Experience:** 3 + years of Read more
Liquor Stock Clerk - S. *Apple* St. - Idaho...
Liquor Stock Clerk - S. Apple St. Boise Posting Begin Date: 2023/10/10 Posting End Date: 2024/10/14 Category: Retail Sub Category: Customer Service Work Type: Part Read more
All contents are Copyright 1984-2011 by Xplain Corporation. All rights reserved. Theme designed by Icreon.