Win32Forth Version 6.06

List of all CODE and COLON definitions.


A B C D E F G H I J K L M N O P Q R S T U V W X Y Z #

- # -


NAME Stack Comment File
' ( -- cfa ) Fkernel.f
' Meta.f
- ( n1 n2 -- n3 ) subtract n2 from n1, return difference n3 Fkernel.f
-- Primutil.f
! ( n1 a1 -- ) store cell n1 into address a1 Fkernel.f
!-C ( n taddr -- ) Meta.f
!-H ( n taddr -- ) Meta.f
!-T ( n taddr -- ) Meta.f
!CSP ( -- ) save current stack pointer for later stack depth check Fkernel.f
!DEFAULT-SIZE ( not the default size, eg. change 16bit to 32bit ) 486ASM.F
!DIR->FILE-NAME { \ string$ -- } RELEASE.F
!IN-MACRO ( flag the fact that we've left a macro ) 486ASM.F
!LABEL ( bind a label to code-here ) 486ASM.F
!LREF ( targ-adr ref-type -- ) store targ-adr & ref-type Newlab.f
!VAR ( n -- ) directly set value from a variable optv1.F
"!. ( pfa - ) TOOLSET.F
"#HASH ( a1 n1 #threads -- n2 ) Fkernel.f
"#PROC ( a1 n1 n2 -- ) define a procedure from string a1,n1 Fkernel.f
"&PUTTEXTOUT ( adr len -- ) Wined.f
".EXT-ONLY" ( a1 n1 -- a1 n1 ) returns dotted file extension Primutil.f
"/TTO ( a1 n1 n2 -- a2 n3) show part n2 of string a1,n1, return remainder Wined.f
"/TTO+ ( a1 n1 n2 -- a2 n3) Wined.f
">MESSAGEFILEB ( a1 n1 -- ) MESSAGES.F
">MESSAGEFILEH ( a1 n1 -- ) MESSAGES.F
"-BLANKS" ( a1 n1 -- a2 n2 ) remove leading and trailing blanks Wined.f
"ADD-FONT { hadr hlen lplf \ message$ -- } Wined.f
"ADDDEBUG { adr len \ ztemp -- } Wined.f
"ADDFILE ( a1 n1 a2 n2 line -- ) add file a2,n2 to file list Wined.f
"ADDLINE { adr len \ list$ -- } Wined.f
"ADDRETURN { adr len \ ztemp -- } Wined.f
"ADDSTACK { adr len \ ztemp -- } Wined.f
"ALREADY-OPEN# { adr len \ open$ -- n1 } return number of times it's open Wined.f
"ALREADY-OPEN? { adr len \ open$ -- f1 } if already open, return ENTRY# Wined.f
"ALREADY-OPEN-SWITCH? { adr len \ open$ -- f1 } if already open, switch, TRUE Wined.f
"ANYFIND { adr len \ find$ -- a2 f1 } Order.f
"ARG-NEXT" ( a1 n1 -- a2 n2 ) Primutil.f
"BROWSE ( a1 n1 -- ) Wined.f
"BUILD-URL" { relURL relLen -- adr2 len2 } Wined.f
"CLIP" ( a1 n1 -- a1 n1 ) clip a string to between 0 and MAXCOUNTED Fkernel.f
"COMMENT ( a1 n1 -- ) everything is a comment up to the string a1,n1 Primutil.f
"CONSOLE ( a1 n1 -- ) Wined.f
"DEBUG-WORD ( a1 n1 -- ) Wined.f
"DEL-BUF ( a1 n1 -- ) Wined.f
"DEMO-MESSAGE ( a1 n1 -- ) WINDEMO.F
"FILE-CLIP" { adr len limit \ temp$ pre -- 'adr 'len } Utils.f
"FIND-LABEL ( a1 n1 -- ) Wined.f
"FIND-PROC ( addr len -- proccfa -1 | 0 ) find windows proc by name **WINED** Fkernel.f
"FIND-WORD+ ( a1 n1 -- a1 n1 f1) Wined.f
"FIRST-SUB-DIR" { adr len -- sub-adr sub-len } Wined.f
"FIRSTPARM ( addr cnt -- ) store string in first slot of parmlist Fkernel.f
"FLOAD ( a1 n1 -- f1 ) a1,n1 = file string Primutil.f
"FORTH ( a1 n1 -- ) Wined.f
"FPATH+ ( a1 n1 -- ) append a directory to forth path Utils.f
"FSAVE { adr len \ from$ to$ -- } save a Forth executable Utils.f
"FTYPE { \ locHdl typ$ -- } type file "name" to the console Utils.f
"GETDEFAULT ( a1 n1 -- a2 n2 ) Wined.f
"HELP-LINK ( a1 n1 -- ) Wined.f
"HOLD ( adr len -- ) Primutil.f
"HTML { htmlAdr HtmlLen \ open$ html$ name$ fhndl -- } Wined.f
"HYPER-FIND ( a1 n1 -- n2 ) look for filename a1,n1 in the file list, Wined.f
"HYPER-LINK ( a1 n1 -- ) Wined.f
"IGNORETO ( a1 n1 -- ) ignore text till a1,n1 string found Wined.f
"IMAGE-SAVE { adr len \ image$ imagehndl -- } save a Forth executable image Utils.f
"INDEX ( a1 n1 -- ) HYPER.F
"LATER ( a1 n1 -- ) Later.f
"LCLIP" ( a1 n1 -- a1 n1 ) clip a string to between 0 and LINE-MAX Primutil.f
"LOADED? { adr len \ temp$ -- f1 } f1 = true if file has been loaded Utils.f
"LOG ( a1 n1 -- ) Keysave.f
"MINUS-EXT" ( a1 n1 -- a2 n2 ) remove the file extension Primutil.f
"NEW-LOG ( a1 n1 -- ) Keysave.f
"NEWMESSAGE ( a1 n1 -- ) MESSAGES.F
"OF-COMPARE ( n1 n2 n3 -- n1 ) extension to CASE for a string Fcases.f
"OF-CONTAIN ( n1 n2 n3 -- n1 ) extension to CASE for a string Fcases.f
"OF-INCLUDE ( n1 n2 n3 -- n1 ) extension to CASE for a string Fcases.f
"OPEN-BITMAP { openAdr len \ editHndl bitDC hbm hdcMem -- } Wined.f
"OPEN-FILE ( a1 n1 -- ) FILEDUMP.F
"OPEN-TEXT { nadr nlen \ textlen open$ create$ -- } Wined.f
"OPEN-TEXT ( a1 n1 -- ) WINBROWS.F
"OPENMENUFILE ( a1 n1 -- ) Wined.f
"PARSE-TEXT" { \ strbuf strlen -- addr len } DIALOGRC.F
"PATH-FILE ( a1 n1 -- a2 n2 f1 ) find file a1,n1 return full path Utils.f
"PATH-ONLY" ( a1 n1 -- a2 n2 ) return path, minus final '\' Primutil.f
"PLAYKEYS ( a1 n1 -- ) Keysave.f
"PROCESS&" { adr len \ &$ -- a2 n2 } process one HTML statement Wined.f
"PROCESS-DIRECTORY { adr len \ buf1 buf2 -- } Wined.f
"PROCESS-MASK-DIRECTORY { adr1 len1 adr2 len2 \ buf -- } Wined.f
"PROCESSHTML" { adr len \ html$ -- a2 n2 } process one HTML statement Wined.f
"PUSHKEYS ( a1 n1 -- ) push the characters of string a1,n1 Primutil.f
"PUTTEXTOUT ( a1 n1 -- ) Wined.f
"RESOURCE-IMAGE-SAVE { adr len \ image$ exehndl -- } save a Forth executable resource Utils.f
"SAVE-COUNTS { adr len \ fileid -- } Wined.f
"SAVE-WORD ( a1 n1 -- ) Wined.f
"SETDEFAULT ( a1 n1 a2 n2 -- ) Wined.f
"SKIP-URLBASE" ( a1 n1 --- a2 n2 ) return a2 and count=n2 of URL after base Wined.f
"TO-PATHEND" ( a1 n1 --- a2 n2 ) return a2 and count=n1 of filename Fkernel.f
"TOPVIEWMESSAGE ( a1 n1 ) Wined.f
"UPPER/LOWER ( a1 n1 -- ) Wined.f
"URL-BASE" ( a1 n1 -- a2 n2 ) return URL base Wined.f
"VIEWMESSAGE ( a1 n1 ) force all message window on top of application Wined.f
"VIEWWEB-LINK ( a1 n1 -- ) Wined.f
"WEB-LINK { adr len hWnd \ web$ -- } open the Web link supplied, using the web browser Utils.f
"WINLIBRARY ( adr len -- ) Fkernel.f
# ( d1 -- d2 ) Fkernel.f
#"NEWMESSAGE { adr len val typ \ temp$ temp2$ comment$ -- } MESSAGES.F
##D ( #zeros d - ) TOOLSET.F
#(;CODE) ( a1 -- ) Fkernel.f
#^FLOAT-ARRAY ( n1 -- ) compile time 64-bits FLOAT.F
#> ( d1 -- addr len ) Fkernel.f
#ACTIVE-BITS ( n - #active-bits ) TOOLSET.F
#BLOCKS ( -- n1 ) return the number of block in the current file BLOCK.F
#BYTE-ARRAY ( n1 -- ) compile time 8-bits Primutil.f
#DBG-RSTACK ( a1 a2 -- ) Debug.f
#DEFINE ( -- ) Primutil.f
#DOES> ( -- ) "compile time" Fkernel.f
#DOUBLE-ARRAY ( n1 -- ) compile time 2 x 32-bits Primutil.f
#ELSE ( the alternative selection ) INTERPIF.F
#ENDIF ( mark the end of the interpretive control structure ) INTERPIF.F
#ENTRY ( n1 -- ) initialized CELL entry Wined.f
#FLOAD ( n1 -- ) load file "name" from line n1, 1 based Utils.f
#FLOAT? ( a1 -- a1 f1 ) is a1 the CFA of a #float? or #^float? FLOAT.F
#FLOAT-ARRAY ( n1 -- ) compile time 64-bits FLOAT.F
#FLOATS+ ( adr kmax k - adr.float) Opengl.f
#HELP ( n1 -- ) help on a help context index number Utils.f
#IF ( begin the interpretive control structure ) INTERPIF.F
#IFDEF ( 'definedword' -- ) INTERPIF.F
#IFNDEF ( 'notdefinedword' -- ) INTERPIF.F
#LATER ( n1 -- ) push a number onto the later stack Later.f
#LINE! { caddr clen cline \ cbuf$ cdiff -- } Wined.f
#LINE" ( n1 -- a1 n2 ) get line # n1, return address and length Wined.f
#LINE" ( n1 -- a1 n2 ) get the address and length a1,n2 of line n1 WINBROWS.F
#LINE.ADDR ( n1 -- a1 ) Wined.f
#LINE.BYTES ( n1 -- n2 ) the real line length, including CRLF Wined.f
#LINE.LEN ( n1 -- n2 ) the line length without CRLF Wined.f
#LINE+" ( n1 offset -- a1 n2 ) get line # n1, return address and length Wined.f
#LINE2" ( n -- adr1 len1 len2 ) Wined.f
#LL-ERRS? ( n1 -- ) DUMMY to check for unresolved labels Newlab.f
#LONG-ARRAY ( n1 -- ) compile time 32-bits Primutil.f
#NEWMESSAGE ( n1 -- ) define a newmessage "name" with value n1 MESSAGES.F
#PATCHINTO ( a1 n1 -- ) patch a1 into name1 at name2 Debug.f
#PRINT-SCREEN ( start_line lines -- ) print a range of lines from saved Dc.f
#S ( d1 -- d2 ) Fkernel.f
#TAB ( n1 -- ) Fkernel.f
#THEN ( mark the end of the interpretive control structure ) INTERPIF.F
#VOCABULARY ( #threads -- ) Order.f
#WORD-ARRAY ( n1 -- ) compile time 16-bits Primutil.f
#WORDLIST ( #threads -- wid ) Order.f
$ ( n1 -- a1 ) reference local label n1 and Newlab.f
$.VIEWINFO ( a1 -- line filename ) Utils.f
$: ( n1 -- ) Newlab.f
$BROWSE ( line filename | dummy -1 -- ) Utils.f
$COPY ( stringadr-source stringadr-dest - ) and makes it 0 terminated TOOLSET.F
$CURRENT-DIR! ( a1 -- f1 ) a1 is a null terminated directory string REGISTRY.F
$EDIT ( line filename | dummy -1 -- ) Utils.f
$ENTRY ( -- ) string entry, MAXSTRING bytes long Wined.f
$EXEC ( a1 -- f1 ) preprocess for file and line parameters Utils.f
$EXTRACT ( adr-counted-string from #chars - adr-string-from #chars ) TOOLSET.F
$FLOAD ( a1 -- f1 ) a1 = counted file string Primutil.f
$FPRINT { the-name \ message$ fpr$ locHdl -- } Dc.f
$FTYPE TOOLSET.F
$HELP ( a1 -- ) help on a string Utils.f
$HELP-FILE ( a1 -- ) set the name of the current help file Utils.f
$LOCATE ( line# filename | dummy -1 -- ) Utils.f
$MAX-COUNT ( string$-adr - str$ max-allocated ) TOOLSET.F
$OPEN ( addr -- fileid f1 ) open counted filename specified by addr Fkernel.f
$SHELL ( a1 -- ) Utils.f
%. ( n -- ) Debug.f
%.S ( ... -- ... ) Debug.f
%D TESTANSI.F
%SIZEOF! ( bytes cfa -- ) set the size of pointer "cfa" POINTER.F
%SIZEOF@ ( cfa -- bytes ) get the size of pointer "cfa" POINTER.F
%UNPOINTER ( cfa -- ) deallocate pointer given the cfa POINTER.F
& ( n1 -- char n2 ) Debug.f
&: ( "&string" -- ) compile time Wined.f
&> Debug.f
&CMDLINE Primutil.f
&LATER ( -- a1 ) address of the next later stack character Later.f
&LOCAL ( -- a1 ) ARGS.F
&LOCAL ( -- a1 ) return the address of local "name" Fkernel.f
&OF ( -- addr ) Fkernel.f
&S ( n1 -- c1 c2 ... 0 ) Debug.f
&THE-SCREEN ( -- a1 ) get the forth relative address of the users Primutil.f
&TYPE ( 0 c1 c2 ... -- ) Debug.f
( Primutil.f
("OF-COMPARE) ( counted-source a1 c1 -- counted-source f ) Fcases.f
("OF-CONTAIN) ( counted-source a1 c1 -- counted-source f ) Fcases.f
("OF-INCLUDE) ( counted-source a1 c1 -- counted-source f ) Fcases.f
(( ( -- ) Primutil.f
(("W)) ( -- w-string ) DIALOGRC.F
((.ROM)) { n x y -- } ROMCALC.F
((FINDM)) ( SelID addr -- 0cfa t | f ) PRIMHASH.F
((SEE)) ( Cfa -- ) SEE.F
(* Primutil.f
(.") ( -- ) Fkernel.f
(.) ( n1 -- a1 n1 ) convert number n1 to an ascii string Primutil.f
(.FPS ( - ) Opengl.f
(.LIBS) ( lib-addr -- ) Winlib.f
(.MALLOCS) ( link-addr -- ) display one line Primutil.f
(.ONEPATH) ( link -- ) paths.f
(.PATH) ( link -- ) for a link, print the directories paths.f
(.PROCS) ( addr len proc-addr -- addr len ) Winlib.f
(.ROM) ( n x y t -- n%1000^tiefe x+? y | ) Paints a number ( 1 and 999 ) ROMCALC.F
(;CODE) ( -- ) Fkernel.f
(?DO) ( n1 n2 -- ) "runtime" setup loop using n1,n2, if n1=n2 donew.f
(|BUILD) ( #elems ^class OR ^class -- ) Build an instance of a class Class.f
(+FTO ( n 'cell-array - ) TOOLSET.F
(+LOOP) ( n1 -- ) "runtime" bump count by n1 and branch to donew.f
(ABORT") ( f -- ) Fkernel.f
(ABORT") ( f -- ) TOOLSET.F
(BUILD) ( #elems ^class OR ^class -- ) Build an instance of a class Class.f
(C") ( -- counted-string ) Fkernel.f
(C"W) ( -- w-string ) DIALOGRC.F
(CLS ( - ) TOOLSET.F
(CR ( - ) TOOLSET.F
(CREATE-TASK) ( addr state -- flag ) create a task task.f
(D.#) ( d1 n1 -- a1 n1 ) display d1 with n1 places behind DP Primutil.f
(D.) ( d -- addr len ) Fkernel.f
(DEFER) ( ^obj -- ) look up SelID at IP and run the method Class.f
(DIALOGPROC) ( hwnd msg wparam lparam -- res ) Dialog.f
(DO) ( n1 n2 -- ) "runtime" setup loop using n1,n2 donew.f
(EQU) ( n -- ) Meta.f
(EXCEPT-IO) EXCEPTIO.F
(FIND) ( str -- str FALSE | cfa flag ) Fkernel.f
(FINDM) ( SelID ^class -- m0cfa ) find method in a class Class.f
(FOLDER-ZSTR) ( link -- link' ) point at absoluted zstring paths.f
(FORGET) ( cfa -- ) assumes count follows name Nforget.f
(FORWARD) ( taddr -- ) Meta.f
(FSINH) ( f: r1 -- r2 ) FLOAT.F
(HEAPOBJ) { theClass \ dLen obAddr idWid #els -- } Class.f
(HELLO-WNDPROC) { hWnd msg wParam lParam -- result } HELLO.F
(IS) ( xt -- ) Fkernel.f
(LOCAL) ( addr cnt -- ) ARGS.F
(LOCAL) ( addr cnt -- ) Fkernel.f
(LOOP) ( -- ) "runtime" bump count and branch to after donew.f
(OBJ-BUILD) ( #elems ^class OR ^class -- ) Build an instance of a class Class.f
(PAUSE multithr.f
(PFIND) ( addr -- cfa t | addr f ) ARGS.F
(ROM.STREICH) { x y l t -- l } Paints t lines of length l above x y ROMCALC.F
(S") ( -- addr len ) Fkernel.f
(S"W) ( -- addr len ) DIALOGRC.F
(S.) ( n addr len w -- addr w ) FLOAT.F
(SYSLOAD) ( |FileName1 FileName2... ) sysload.f
(TAG) ( n1 addr -- n2 ) Returns the 2 bit tag for ST(n1) FLOAT.F
(TASK) ( parm cfa -- ) helper routine task.f
(TASK-BLOCK) ( parm cfa-task addr -- len ) build a task block at addr task.f
(TOT-MALLOC) ( n link-addr -- n' ) add in a single entry's byte count Primutil.f
(TRIM) ( addr1 addr2 -- addr1 addr3 ) Primutil.f
(TYPE ( adr len - ) TOOLSET.F
(TYPETEXT) ( addr len -- ) rda made a new version Wined.f
(U. ( - ) TOOLSET.F
(UD,.) ( ud -- a1 n1 ) Primutil.f
(WNDPROC) ( hwnd msg wparam lparam -- res ) Window.f
(WORDS) { voc \ words-pad$ w#threads -- } WORDS.F
(XUD,.) ( ud commas -- a1 n1 ) Primutil.f
(Z") ( -- ) Primutil.f
) ( -- ) ASSERT.F
* ( n1 n2 -- n3 ) multiply n1 by n2, return single result n3 Fkernel.f
*/ ( n1*n2/n3 -- quotient ) Fkernel.f
*/MOD ( n1*n2/n3 -- remainder quotient) Fkernel.f
*-OPEN-FILE { sadr slen \ spath$ smask$ -- } Wined.f
, Meta.f
," ( -- ) Fkernel.f
," Meta.f
,"TEXT" ( -<"text">- ) parse out quote delimited text and compile Primutil.f
,"W ( -- ) compile string with 2-byte wide chars (UNICODE) DIALOGRC.F
,$ ( -< #text#>- ) Utils.f
,| ( -- ) RELEASE.F
,-C ( n -- ) Meta.f
,-H ( n -- ) Meta.f
,-T ( n -- ) Meta.f
,WORD ( -- ) lay a word into the dictionary, aligned BUILD.F
-DUP ( n1 n2 - n1 n1 n2 ) TOOLSET.F
-OVER ( n1 n2 n3 - n1 n2 n1 n3 ) TOOLSET.F
-SWAP ( n1 n2 n3 - n2 n1 n3 ) TOOLSET.F
-TIME ( dfact-start seconds-start dfact-end seconds-end - days seconds ) TOOLSET.F
. ( n -- ) Fkernel.f
." ( -- ) Fkernel.f
.# DIS486.F
.#" ( n1 n2 -- a1 n3 ) Utils.f
.$ ( -< #text#>- ) Utils.f
.$MOVE ( adr$ mv -- ) fcp3d.f
.$SQ ( sq $ -- ) fcp3d.f
.( ( -- ) Fkernel.f
.() ( n -- ) XDEBUG.F
.(;CODE) ( ip -- ip' ) SEE.F
.(DAY ( day - ) TOOLSET.F
., ( -- ) DIS486.F
.: ( cfa -- ) SEE.F
.;CODE ( cfa -- ) SEE.F
.[BASE16](XX-XXX-1NN) ( r/m -- ) DIS486.F
.[IND16](XX-XXX-0NN) ( r/m -- ) DIS486.F
.[INDEX]=SS-III-BBB ( sib -- ) DIS486.F
.[REG*2](XX-XXX-NNN) ( i -- ) DIS486.F
.[REG*4](XX-XXX-NNN) ( i -- ) DIS486.F
.[REG*8](XX-XXX-NNN) ( i -- ) DIS486.F
.[REG16](XX-XXX-NNN) ( r/m -- ) DIS486.F
.[REG32](XX-XXX-NNN) ( n -- ) DIS486.F
.1THREAD { voc-thread \ thread-depth -- } DTHREAD.F
.ALU ( n -- ) DIS486.F
.AM/PM ( -- ) Utils.f
.ASQ ( sq -- sq ) fcp101.f
.ASQ_OGL ( -- ) fcp3d.f
.BEGINPATH ( a1 n1 -- A1 n1 ) ISPY.F
.BEZIERTO ( a1 n1 -- A1 n1 ) ISPY.F
.BITMAPFILEHEADER ( BitmapFileHeader -) BMPDOT.F
.BITMAPINFOHEADER ( BitmapFileHeader - ) BMPDOT.F
.BOARD_ASCII fcp101.f
.BOARD_OGL ( - ) fcp3d.f
.BRANCH ( IP -- IP' ) SEE.F
.BTX(XXXN-NXXX) ( n -- ) DIS486.F
.CALL ( ip -- ip' ) SEE.F
.CHAIN ( chain -- ) Primutil.f
.CHAINS ( -- ) display the contents of all chains Primutil.f
.CHANGE-SCENE ( adr-flookat - ) Opengl.f
.CHANGED-FPS>TITLE ( - ) Opengl.f
.CLASS ( cfa -- ) SEE.F
.CLASSES ( -- ) display all classes in the system Class.f
.CLOCK ( second minute hour - ) TOOLSET.F
.CND-CODE(OP) ( code -- ) was tttn DIS486.F
.CODE ( cfa -- ) SEE.F
.COLORS { \ clink -- } Displays the current set of defined COLORS.F
.CONSTANT ( cfa -- ) SEE.F
.COUNTS { \ #thread-over -- } DTHREAD.F
.CR ( n - ) TOOLSET.F
.CREG(XX-NNN-XXX) ( eee -- ) DIS486.F
.CUR-FILE ( -- ) Utils.f
.CURMOVE ( ^move -- ) fcp101.f
.CVERSION ( -- ) Utils.f
.DAG ( day - ) TOOLSET.F
.DATE ( -- ) Utils.f
.DEFER ( cfa -- ) SEE.F
.DEFERRED ( -- ) Utils.f
.DEFINITION-CLASS ( cfa cfa -- ) SEE.F
.DIR->FILE-NAME ( -- ;print file name in the dir ) ANSFILE.F
.DIR->FILE-SIZE ( -- ;print file size ) ANSFILE.F
.DISP16/32[PC++] ( adr -- adr' ) DIS486.F
.DISP16[PC++] ( adr -- adr' ) DIS486.F
.DISP32[PC++] ( adr -- adr' ) DIS486.F
.DISP8[PC++] ( adr -- adr' ) DIS486.F
.DOES> ( pfa -- ) SEE.F
.DOT ( - ) TOOLSET.F
.DRAWLIST ( -- ) ISPY.F
.DREG(XX-NNN-XXX) ( eee -- ) DIS486.F
.EDITOR ( -- ) display the editor, browser, shell & dos strings Utils.f
.ELAPSED ( -- ) Utils.f
.ENDPATH ( a1 n1 -- A1 n1 ) ISPY.F
.EPD fcp101.f
.EPDSQ ( sq -- sq ) fcp101.f
.EXCEPTION ( -- ) print exception info EXCEPTIO.F
.EXCEPTION-CODE ( -- ) get the last exception EXCEPTIO.F
.EXECUTION-CLASS ( ip cfa -- ip' ) SEE.F
.EXECUTION-CLASS-CLASS ( ip cfa flag -- ip' cfa flag ) Class.f
.EXNAME ( addr -- ) EXCEPTIO.F
.EXREGS ( n -- ) EXCEPTIO.F
.FDEPTH ( -- ) FLOAT.F
.FILLAREA ( a1 n1 -- a1 n1 ) ISPY.F
.FILLPATH ( a1 n1 -- A1 n1 ) ISPY.F
.FONT ( -- ) SCRNCTRL.F
.FONTS ( -- ) CALLBACK.f
.FORTH ( - ) TOOLSET.F
.FPATH ( -- ) display the forth directory search path list Utils.f
.FREE ( -- ) Utils.f
.GLUERROR ( *nobj - ) Opengl.f
.HELLO { hdc counter -- } HELLO.F
.HELP ( -- ) display the current help file string Utils.f
.HMS ( -- ) WINCLOCK.F
.HOUR ( -- ) draw hour display WINCLOCK.F
.HR ( n1 -- ) WINCLOCK.F
.ID ( nfa -- ) Fkernel.f
.ID>S ( nfa -- ) DIS486.F
.ID-USER TOOLSET.F
.IMM16/32[PC++] ( adr -- adr' ) DIS486.F
.IMM8[PC++] ( adr -- adr' ) DIS486.F
.IMMEDIATE ( cfa -- ) SEE.F
.INDEXING { \ index$ -- } HYPER.F
.INDEXING-START { \ index$ -- } HYPER.F
.ISPY ( -- ) ISPY.F
.ISPYN ( n -- ) ISPY.F
.JXX ( addr op -- addr' ) DIS486.F
.LAB ( n1 -- ) display a local label record Newlab.f
.LABELS_BOT ( - ) fcp3d.f
.LABELS_LEFT ( - ) fcp3d.f
.LAST-MOVE ( - ) fcp3d.f
.LAST-MOVE_OGL fcp3d.f
.LAST-WTM$ ( wtm $adr - ) fcp3d.f
.LDATE ( day month year - ) TOOLSET.F
.LECURSOR ( --- ) show the cursor LINEEDIT.F
.LELINE ( --- ) redisplay edit line LINEEDIT.F
.LIBS ( -- ) Winlib.f
.LINECOLOR ( a1 n1 -- a1 n1 ) ISPY.F
.LINETO ( a1 n1 -- a1 n1 ) ISPY.F
.LOADED ( -- ) Utils.f
.LOCALS ( IP -- IP' ) SEE.F
.LTIME ( - ) TOOLSET.F
.M0NAME ( a1 -- ) PRIMHASH.F
.M1NAME ( a1 a2 -- a3 ) PRIMHASH.F
.MALLOCS ( -- ) display all dynamically allocated buffers Primutil.f
.MEM-FREE ( -- ) Extend.f
.MIN ( n1 -- ) WINCLOCK.F
.MINUTE ( -- ) draw minute display WINCLOCK.F
.MONTH ( month - ) TOOLSET.F
.MONTH,DAY,YEAR ( -- ) Utils.f
.MOVE ( mv -- ) fcp101.f
.MOVELIST fcp101.f
.MOVETO ( a1 n1 -- a1 n1 ) ISPY.F
.MPAGE ( a1 n1 -- a1 n1 ) ISPY.F
.MREG(XX-XXX-NNN) ( n -- ) DIS486.F
.MS ( ms -- ) fcp101.f
.NAME ( xt -- ) show name, if can't find name, show address Fkernel.f
.NAME>S ( xt -- ) DIS486.F
.NAMECACHE ( -- ) OPTIMIZE.F
.OBJ ( nfa -- ) CLASSDBG.F
.OBJECT ( cfa -- ) SEE.F
.OGL_BALL ( - ) Bounce3d.f
.OGL_BISHOP ( - ) fcp3d.f
.OGL_BOARD ( - ) fcp3d.f
.OGL_KING ( - ) fcp3d.f
.OGL_KNIGHT ( - ) fcp3d.f
.OGL_PAWN ( - ) fcp3d.f
.OGL_PLATE1 ( - ) Bounce3d.f
.OGL_QUEEN ( - ) fcp3d.f
.OGL_ROOK ( - ) fcp3d.f
.OGL_SQUASHROOM ( - ) Bounce3d.f
.OK ( - ) TOOLSET.F
.OPT-ONOFF ( f -- ) print on/off optcomp.f
.OPTLISTS ( -- ) display the lists of optimizable words OPTIMIZE.F
.OPTS ( opt -- ) print options optcomp.f
.OTHER ( cfa -- ) SEE.F
.PAGE ( a1 n1 -- a1 n1 ) ISPY.F
.PATHS ( -- ) Print out the paths and the searched directories paths.f
.PFA ( cfa -- ) SEE.F
.PFD ( - ) PIXELFRM.F
.PIECE ( piece[+color] -- ) fcp101.f
.PLATFORM ( -- ) Utils.f
.POINTERS ( -- ) POINTER.F
.PRIMES ( -- ) PRIMES.F
.PROC-NAME ( cfa -- ) SEE.F
.PROCS ( -- ) Winlib.f
.PROGRAM ( -- ) Utils.f
.PSX(XXNN-XXXX) ( op -- ) DIS486.F
.PV fcp101.f
.R ( n w -- ) Fkernel.f
.R.1 ( n1 n2 -- ) print n1 right justified in field of n2 Primutil.f
.R>S ( n w -- ) DIS486.F
.REG(XX-XXX-NNN) ( a n -- a ) DIS486.F
.REG16(XX-XXX-NNN) ( n -- ) DIS486.F
.REG16/32(XX-XXX-NNN) ( n -- ) DIS486.F
.REG32(XX-XXX-NNN) ( n -- ) DIS486.F
.REG8(XX-XXX-NNN) ( n -- ) DIS486.F
.REGISTRY ( -- ) REGISTRY.F
.REL16/32 ( addr -- addr' ) DIS486.F
.REL8 ( addr -- addr' ) DIS486.F
.RESULT? ( -- tf ) fcp101.f
.ROM ( n x y hdc -- ) Print the positive number n at x y in device context ROMCALC.F
.S ( -- ) Fkernel.f
.S" DIS486.F
.S-BASE ( -- ) Debug.f
.SCORE ( value -- ) fcp101.f
.SEARCHHEADER fcp101.f
.SEARCHSTATUS ( value codeChar -- ) fcp101.f
.SEC ( n1 -- ) WINCLOCK.F
.SECOND ( -- ) draw second display WINCLOCK.F
.SETPIXEL ( a1 n1 -- a1 n1 ) ISPY.F
.SHARE ( -- ) MAPFILE.F
.SHIFT ( n -- ) DIS486.F
.SIB=NN ( adr mod -- adr ) DIS486.F
.SQ ( sq -- ) fcp101.f
.SQUARE ( f: x y - ) fcp3d.f
.SQUARES fcp3d.f
.SREG(XX-NNN-XXX) ( sreg -- ) DIS486.F
.STRING ( IP -- IP' ) SEE.F
.STRING ( adr - ) TOOLSET.F
.STROKEANDFILL ( a1 n1 -- A1 n1 ) ISPY.F
.STROKEPATH ( a1 n1 -- A1 n1 ) ISPY.F
.STRUCT ( struct sizeof - ) STRUCT.F
.SYMBOLS ( -- ) Meta.f
.SYNONYM ( cfa -- ) SEE.F
.SYSLOAD sysload.f
.TEST BMPDOT.F
.TEXT-LINE ( str$ count - ) Opengl.f
.TEXTOT ( a1 n1 -- a1 n1 ) ISPY.F
.TEXTOTF ( a1 n1 -- a1 n1 ) ISPY.F
.TEXTOTL ( a1 n1 -- a1 n1 ) ISPY.F
.TEXTOTR ( a1 n1 -- a1 n1 ) ISPY.F
.THINKRESULT fcp101.f
.THREAD ( n1 -- ) display a thread of context vocabulary DTHREAD.F
.THREADS ( -- ) DTHREAD.F
.TIME ( -- ) Utils.f
.TIME-STAMP ( - ) TOOLSET.F
.TODAY ( - ) TOOLSET.F
.TREG(XX-NNN-XXX) ( eee -- ) DIS486.F
.UNRESOLVED ( -- ) Meta.f
.USAGE-DATABASE ( -- ) MARKUSED.F
.USER ( cfa -- ) SEE.F
.USERSIZE ( - ) Shows what is left in the user-area Fkernel.f
.VALUE ( cfa -- ) SEE.F
.VARIABLE ( cfa -- ) SEE.F
.VIEWINFO ( -- line filename ) Utils.f
.VOC-ONCE ( -- ) WORDS.F
.VOCABULARY ( cfa -- ) SEE.F
.WHOSETURN ( - ) fcp101.f
.WORD ( IP -- IP' ) SEE.F
.WORD-TYPE-CLASS ( cfa flag -- cfa false | true ) Class.f
.WORDS ( -- ) WORDS.F
.WORDTYPE ( -- ) XDEBUG.F
.WORDTYPE ( -- ) Debug.f
/ ( n1 n2 -- n3 ) Fkernel.f
/* Primutil.f
// Primutil.f
//{{NO_DEPENDENCIES}} Primutil.f
/BOLD ( -- ) Wined.f
/GET { str len char \ str1 len1 -- str len str1 len1 } Wined.f
/IMAGE ( 'imagename' -- ) dummy, really loaded by wrapper Fkernel.f
/ITALICS ( -- ) Wined.f
/MOD ( n1 n2 -- rem quot ) Fkernel.f
/PARSE ( -- addr u ) Fkernel.f
/PARSE-S$ ( -- a1 ) parse possibly quoted string Fkernel.f
/PARSE-WORD ( -- a1 ) Fkernel.f
/POSTFIX 486ASM.F
/POSTFIX? ( are we in postfix mode? ) rls March 3rd, 2002 - 11:13 486ASM.F
/PREFIX 486ASM.F
/PREFIX? ( are we in prefix mode? ) 486ASM.F
/R&FREG>MOD-R/M ( turn /r and fp reg into the rqd mod-r/m ) 486ASM.F
/SET-POSTFIX ( set the assembler to postfix mode, leave a mode flag ) 486ASM.F
/SET-PREFIX ( set the assembler to prefix mode, leave a mode flag ) 486ASM.F
/SPLIT { str len part -- remainder len1 prefix len2 } Wined.f
/STRIKEOUT ( -- ) Wined.f
/STRING ( addr1 len1 n1 -- addr2 len2 ) Fkernel.f
/UNDERLINE ( -- ) Wined.f
: Meta.f
:CLASS ( -- ) Class.f
:DLLFUNC { \ temp$ -- } define a colon definition in the DLL function chain MESSAGES.F
:INLINE ( ccc; -- ) TOOLSET.F
:M ( -- ) Class.f
:MESSAGE { \ temp$ -- } define a colon definition in the message function chain MESSAGES.F
:NONAME ( -- xt ) start a headerless colon definition Fkernel.f
:OBJECT ( -- ) Class.f
; ( -- ) ARGS.F
; ( -- ) Fkernel.f
;CLASS ( -- ) Class.f
;M ( -- ) Class.f
;MACRO ( end a macro definition ) 486ASM.F
;OBJECT ( -- ) Class.f
;RECORD ( -- ) end a group of data fields that need to contiguous Class.f
;RECORDSIZE: ( -- ) create a name with the size of the record Class.f
? ( addr -- ) Fkernel.f
?! ( - ) compile-time: 1 variable TOOLSET.F
?#FLOAT ( cfa -- cfa ) abort if not a #FLOAT-ARRAY FLOAT.F
?&-EXIT ( a1 n1 a2 n2 -- a3 n3 ) Wined.f
?-\ ( a1 -- ) delete trailing '\' if present Primutil.f
?.EPDBL fcp101.f
?.NAME ( cfa -- ) try to display the name at CFA Primutil.f
?.NAME>S { op-addr \ cfa -- } DIS486.F
?.REFILL ( -- ) Fkernel.f
??? ( n1 -- ) DIS486.F
?+; ( a1 -- ) append a ';' if not already present Primutil.f
?+\ ( a1 -- ) append a '\' if not already present Primutil.f
? ( -- f addr ) Meta.f
? ( f addr -- ) Meta.f
?>MARK ( -- f addr ) Meta.f
?>RESOLVE ( f addr -- ) Meta.f
?ASSERT ( flag nfa -- ) ASSERT.F
?BEEP ( f1 -- ) if f1=FALSE, then BEEP Wined.f
?CHECKTIME ( nodes -- ) fcp101.f
?CLASS ( -- ) Class.f
?CLR-OPSTACK ( clear the operand stack when the flag is non-zero ) 486ASM.F
?COLORCHECK ( a1 -- a1 ) verify that a1 is a color object address COLORS.F
?COMP Fkernel.f
?CONDITION Meta.f
?CONTROL ( --- ) handle control characters LINEEDIT.F
?CONTROL ( -- f1 ) return true if control is down Primutil.f
?CSP ( -- ) check current stack pointer against saved stack pointer Fkernel.f
?DEFEXT ( addr -- ) conditionally add a default extension Fkernel.f
?DLGERR ( ior -- ) Dialog.f
?DO donew.f
?DO Fkernel.f
?DUP ( n -- n [n] ) duplicate top of data stack if non-zero Fkernel.f
?END-OPTIMIZATION ( -- ) finish up optimization if we are OPTIMIZE.F
?EPDCB ( "KQkq" testChar bit -- "Qkq" ) fcp101.f
?ERROR ( f1 n1 -- ) abort with error code n1 if f1=true Utils.f
?ERRORBOX { flag adr len \ message$ -- } Utils.f
?EXEC Fkernel.f
?EXIT ( f1 -- ) ARGS.F
?EXIT ( F1 -- ) Fkernel.f
?F1-HELP ( char flag -- char flag ) Menu.f
?FLOAT ( cfa -- cfa ) abort if not a FLOAT FLOAT.F
?FUNC ( --- ) handle function keys LINEEDIT.F
?GENCAPTURE ( sq dest piece -- sq ) fcp101.f
?GENEMPTY fcp101.f
?GET-HIGHLIGHT ( -- ) Wined.f
?GOTREC ( n1 --- f1 ) Do we have block n1 in memory? BLOCK.F
?HTML-EXIT ( a1 n1 a2 n2 -- a3 n3 ) Wined.f
?IS ( xt -- xt ) error if not a deferred word Fkernel.f
?ISCLASS ( cfa -- f ) Class.f
?ISOBJ ( cfa -- f ) Class.f
?ISPAREN ( cfa -- f ) Class.f
?ISPY ( n1 n2 ... nn n flag -- ) ISPY.F
?ISSEL ( str -- str f1 ) f1 = true if it's a selector Class.f
?ISVALUE ( cfa -- f ) Class.f
?ISVECT ( cfa -- f ) Class.f
?JUMP ( ip f -- ip' ) XDEBUG.F
?JUMP ( ip f -- ip' ) Debug.f
?LATER-FULL ( n1 -- ) check to see if there is room for n1 bytes on later stack Later.f
?LEAVE-MACRO ( conditionally unnest a macro ) 486ASM.F
?LECHAR ( --- ) handle normal keys, insert them LINEEDIT.F
?LINE ( n1 -- ) Primutil.f
?LINE-TBL-OK ( -- ) Wined.f
?MABORT ( -- ) give mouse a chance to recognize button press Primutil.f
?MACRO-KEYS ( chad flag -- char flag ) Menu.f
?MEM,REG ( is the instruction coded as memory,register? ) 486ASM.F
?MEMCHK ( n1 -- ) test to see if we have enough memory Fkernel.f
?MESSAGEBOX { flag adr len \ message$ -- } Utils.f
?MISSING ( f -- ) Fkernel.f
?MOUSE_ABORT ( -- ) abort if both mouse buttons are down Primutil.f
?NAME { ?name-val \ ?name-max -- cfa } Primutil.f
?NOSHORT ( do we have an illegal short? ) 486ASM.F
?OPEN-MESSAGEFILE ( -- ) make sure the message file is open MESSAGES.F
?PAGE-STARTED ( -- ) Dc.f
?PAIRS ( n1 n2 -- ) Fkernel.f
?PRIME ( n1 -- f1 ) PRIMES.F
?PUSHEP ( dir piece -- ) fcp101.f
?REG,MEM ( is the instruction coded as register,memory? ) 486ASM.F
?REGEXCLUS ( is the addressing mode exclusive? ) 486ASM.F
?RESEARCH ( alpha -beta value -- value ) fcp101.f
?RESUME ( seconds -- true/false ) fcp_inputwin.f
?ROTATE ( sq -- sq' ) fcp101.f
?SAVE-NEW ( -- f1 ) Wined.f
?SECOND ( -- f ) f = true if second has changed. WINCLOCK.F
?SHIFT ( -- f1 ) return true if shift is down Primutil.f
?STACK ( -- ) check the data stack for stack underflow Fkernel.f
?SYS-ADDRESS ( a1 -- ) check that a1 is not in system dictionary, Fkernel.f
?SYS-CHAIN ( chain_address cfa -- chain_address cfa ) Primutil.f
?TERMINATEBOX { flag adr len \ message$ -- } Utils.f
?THINKABORT ( err -- ) fcp101.f
?U,. ( adr - ) TOOLSET.F
?U,.CR ( adr - ) TOOLSET.F
?UNHASH ( hash-val -- f1 ) PRIMHASH.F
?UPDATEKINGPOSITION ( sq -- ) fcp101.f
?VALID_POINTER ( plink -- plink ) check for valid pointer sturcture POINTER.F
?WIN-ERROR ( f1 -- ) f1=0=failed Utils.f
?WORD.AFTER ( -- ) find occurances of index-word-buf string and put word HYPER.F
?WORD.BEFORE ( -- ) find occurances of index-word-buf string and put the HYPER.F
?WORD.BEGIN ( -- ) find occurances of index-word-buf string and put word HYPER.F
?WORD.ENDING ( -- ) find a word ending with char in index-word-buf HYPER.F
?WORD.STLINE ( -- ) find occurance of index-word-buf string at line start HYPER.F
?WORD.TERMINATE ( -- ) stop scanning file if this string is found HYPER.F
@ ( a1 -- n1 ) get the cell n1 from address a1 Fkernel.f
@+ ( adr -- adr n ) TOOLSET.F
@-C ( taddr -- n ) Meta.f
@-H ( taddr -- n ) Meta.f
@-T ( taddr -- n ) Meta.f
@IVARCPTR ( ivar -- flag ) Class.f
@IVARELEMS ( ivar -- #elems ) Class.f
@IVAROFFS ( ivar -- offset ) Class.f
@LABEL ( fetch the binding of a label, or return a pseudo address if not ) 486ASM.F
@VAR ( -- n ) directly fetch value from a variable optv1.F
@WORD ( -- addr ) Class.f
[$EDIT] { line_number file_name edit_cfa -- } Utils.f
[(E)BP]? ( does the address mode have either [bp] or [ebp] alone? ) 486ASM.F
[[ Class.f
['] ( -- ) Fkernel.f
[]CELL ( no addr - addr+offset ) TOOLSET.F
[CHAR] ( -- char ) Fkernel.f
[COMPILE] ( -- ) Fkernel.f
[DEFINED] ( -- f1 ) Primutil.f
[DEFINED] ( "word" -- tf ) fcp101.f
[ELSE] ( interpretive control structure -- alternate selection ) INTERPIF.F
[ENDIF] ( interpretive control structure -- end the structure ) INTERPIF.F
[ESP]? ( does it have only a base of esp? ) 486ASM.F
[ESP][REG]? ( does it have esp as an index register? ) 486ASM.F
[FORWARD] ( -- ) Meta.f
[IF] ( interpretive control structure -- select on true ) INTERPIF.F
[LABEL] ( -- ) Meta.f
[OBJECT ( fill - ) Opengl.f
[QUAD Opengl.f
[QUAD_OBJECT ( - ) Opengl.f
[REG*N]? ( does it have only an index register? ) 486ASM.F
[ROT-OBJECT ( fill - ) Opengl.f
[ROT-SCALED-OBJECT ( fill - ) Opengl.f
[ROT-SCALED-OBJECT-INLINE ( fill - ) Opengl.f
[SCALED-OBJECT ( fill - ) Opengl.f
[TARGET] ( -- ) Meta.f
[THEN] ( interpretive control structure -- end the structure ) INTERPIF.F
[TRANSITION] Meta.f
[UNDEFINED] ( -- f1 ) Primutil.f
[UNDEFINED] ( "word" -- tf ) fcp101.f
[UP] ( offset -- ) Meta.f
\ ( -- ) BLOCK.F
\ ( -- ) Fkernel.f
\- ( -- ) load line if word IS NOT defined Primutil.f
\+ ( -- ) load line if word IS defined Primutil.f
\IN-SYSTEM-OK ( -- ) Primutil.f
\LOADED ( -- ) if the following file IS LOADED interpret line Utils.f
\LOADED- ( -- ) if the following file IS NOT LOADED interpret line Utils.f
\S comment to end of file Primutil.f
] ( -- ) Meta.f
]MACRO ( end a macro definition ) ASMWIN32.F
]OPT ( -- ) disable optimization for remainder of definition OPTIMIZE.F
]OPT ( -- ) disable optimization for remainder of definition optv1.F
^#BYTE-ARRAY ( a1 -- ) compile time 8-bits Primutil.f
^#DOUBLE-ARRAY ( a1 -- ) compile time 2 x 32-bits Primutil.f
^#LONG-ARRAY ( a1 -- ) compile time 32-bits Primutil.f
^#WORD-ARRAY ( n1 -- ) compile time 16-bits Primutil.f
^BASE ( -- addr ) PRIMHASH.F
^FLOAT ( a1 -- ) compile time 64-bits FLOAT.F
-BLSCAN1 ( a1 n1 -- a2 n2 ) rls - page Dc.f
_"+OPEN-TEXT { adr len -- } Wined.f
_"ERR ( a1 n1 -- ) default to a simple error handler Newlab.f
_"HYPER-LINK { adr len adr2 len2 -- } Wined.f
_"MESSAGE ( a1 n1 -- ) a floating non-modal message box WINMSG.F
_"OPEN ( a1 n1 -- fileid f1 ) open filename a1,n1 Fkernel.f
_"TOP-MESSAGE ( a1 n1 -- ) a floating ON-TOP message box WINMSG.F
_$WATCH ( line filename -- ) Utils.f
_.ANY-KEY ( - ) TOOLSET.F
_.BOARD_OGL fcp3d.f
_.OPENGL_ERROR ( error - ) Opengl.f
_.RSTACK ( -- ) Debug.f
_: ( -- ) Forth's primary function defining word Fkernel.f
_;CODE ( create the [;code] part of a low level defining word ) 486ASM.F
_;CODEP ( -- ) ARGS.F
_?ADSIZE1 ( is the address size mismatched? ) 486ASM.F
_?ADSIZE2 ( just store the address size ) 486ASM.F
_?BADCOMBINE ( can the operand types be combined? ) 486ASM.F
_?BADMODE ( is the address mode illegal? ) 486ASM.F
_?BADTYPE ( is the operand type allowed? ) 486ASM.F
_?CR ( n -- ) Fkernel.f
_?FINISHED ( are there operands left? ) 486ASM.F
_?INST-PRE ( is there any instruction prefix? ) 486ASM.F
_?LOCK ( is there a LOCK prefix? ) 486ASM.F
_?MATCH ( error if the parameters match ) 486ASM.F
_?MEM ( is one of the operands in memory? ) 486ASM.F
_?NOADSIZE ( no or unknown address size ) 486ASM.F
_?NOFAR ( is there an unallowed far reference? ) 486ASM.F
_?NOIMMED ( is there an illegal immediate operand? ) 486ASM.F
_?NOMATCH ( error if the parameters don't match ) 486ASM.F
_?NOTENOUGH ( are there not enough operands? ) 486ASM.F
_?OPERANDS ( are there any operands? ) 486ASM.F
_?OPSIZE1 ( is the operand size mismatched? ) 486ASM.F
_?OPSIZE2 ( just store the operand size ) 486ASM.F
_?PARAMS ( are there parameters on the stack? ) 486ASM.F
_?R/M,REG ( is the source a register? ) 486ASM.F
_?REG ( are all of the operands register? ) 486ASM.F
_?REG,R/M ( is the destination a register? ) 486ASM.F
_?REP ( is there a repeat prefix? ) 486ASM.F
_?SAVE-TEXT ( -- f1 ) return f1=true if we canceled Wined.f
_?SEG ( is there a segment override? ) 486ASM.F
_?SHORT ( is the address short? ) 486ASM.F
_?TOOFAR ( is the branch offset to far? ) 486ASM.F
_?TOOMANYOPS ( are there too many operands? ) 486ASM.F
_?UNRES ( are there any unresolved forward reference labels? ) 486ASM.F
_?UNSAVE-SRC ( -- ) DBGSRC1.F
_?WRAP-WORD { \ original-col wrap-col -- } Wined.f
_@COL Meta.f
_[ ( -- ) turn off compiling Fkernel.f
_\N->CRLF ( a1 n1 -- ) parse "\n" occurances, change to CRLF's Primutil.f
_] ( -- ) Fkernel.f
__CDECL CALLBACK.f
__LACCEPT ( a1 n1 -- ) LINEEDIT.F
__LE-LDEL ( -- ) Line delete LINEEDIT.F
__STDCALL CALLBACK.f
_>BOLD ( -- ) SCRNCTRL.F
_>NAME ( CFA -- NFA ) search vocabs for cfa, return nfa Fkernel.f
_>NORM ( -- ) SCRNCTRL.F
_>ROW-COL ( row col -- ) Wined.f
_3DTRIANGLE ( size - ) Opengl.f
_ACCEPT ( addr len -- n ) Fkernel.f
_ADD-STRUCT ( sizeof.struct - ) STRUCT.F
_ADDFILEMENU ( -- ) Wined.f
_APP-COMPILE, ( xt -- ) Fkernel.f
_BACK-DELETE-CHARACTER ( -- ) Wined.f
_BASIC-FORTH-IO ( -- ) reset to Forth IO words Primutil.f
_BEEP ( -- ) Primutil.f
_BOX ( - ) init c1 c2 and c3 first Opengl.f
_BYE ( -- ) Exit Forth Fkernel.f
_BYE" ( flag nfa- ) TOOLSET.F
_CALC_FONT_HEIGHT ( --- points_high ) Dc.f
_CLASSINIT ( -- ) Class.f
_CLOSE-TEXT ( -- ) Wined.f
_CLS ( -- ) Fkernel.f
_CODE ( start a native code definition ) 486ASM.F
_COL ( n -- ) Fkernel.f
_COMMENT char -- Primutil.f
_CONHNDL Primutil.f
_CR ( -- ) Fkernel.f
_CRTAB ( -- ) Primutil.f
_DBG-NEST ( cfa -- ) Debug.f
_DEFAULT-HELLO ( -- ) startup stuff Utils.f
_DEFAULTWINDOWPROC ( hwnd msg wparam lparam -- res ) Winlib.f
_DELETE-CHARACTER ( -- ) Wined.f
_DISCARD-NUMBER ( d1 -- ) discard a converted number Primutil.f
_DO-;CHAIN ( -- ) Primutil.f
_DO-MABORT ( -- ) Primutil.f
_DO-OPCODE ( create the actual opcode, or at least call the functions ) 486ASM.F
_DO_MESSAGE ( val string -- ) normal stack format Class.f
_DOLOADINFO { \ temp$ -- } load the debugger information from disk DBGSRC2.F
_DOSCONSOLE ( fl -- ) true = open, false = close Fkernel.f
_EDIT-ERROR ( -- ) Utils.f
_EMIT ( char -- ) SP@ REL>ABS 1 _TYPE DROP Fkernel.f
_EMIT_OGL ( char - ) fcp3d.f
_END-CODE ( end a code definition ) 486ASM.F
_ENTER-ASSEMBLER ( -- ) ASMWIN32.F
_EXECUTE-MENUFUNC ( cfa -- ) Menu.f
_EXIT-ASSEMBLER ( -- ) ASMWIN32.F
_FACCEPT ( a1 n1 -- n2 ) Primutil.f
_FIND-TEXT-AGAIN ( -- f1 ) Wined.f
_FOREGROUND-CONSOLE ( -- ) Utils.f
_GETCOLROW ( -- cols rows ) Fkernel.f
_GETXY ( -- x y ) Fkernel.f
_GOTOXY ( x y -- ) Fkernel.f
_HEADER ( -- ) build a header, but check available memory Fkernel.f
_HELP-RELEASE ( -- ) release our marker to help system Utils.f
_INIT-CONSOLE ( -- f1 ) initialize the Forth console window Fkernel.f
_INIT-SCREEN ( -- ) init the screen Fkernel.f
_INSERT-CHARACTER ( char -- ) insert a char into text line Wined.f
_INTERPRET ( -- ) Fkernel.f
_IS-DEFAULT ( cfa -- ) Primutil.f
_LACCEPT ( a1 n1 -- n2 ) line editor version of accept LINEEDIT.F
_LE-ANY ( --- ) handle any character entry LINEEDIT.F
_LE-BDEL ( --- ) back delete LINEEDIT.F
_LE-END ( --- ) End of line LINEEDIT.F
_LE-FDEL ( --- ) Forward delete LINEEDIT.F
_LE-HOME ( --- ) beginning of line LINEEDIT.F
_LE-INS ( --- ) toggle insert mode LINEEDIT.F
_LE-KEY ( c1 --- ) process a key LINEEDIT.F
_LE-LEFT ( --- ) left a character LINEEDIT.F
_LE-LWORD ( --- ) back a word LINEEDIT.F
_LE-RIGHT ( --- ) right a character LINEEDIT.F
_LE-RWORD ( --- ) Forward to next word LINEEDIT.F
_LE-WDEL ( --- ) word delete LINEEDIT.F
_LEDONE ( --- ) flag edit is finished, save changes LINEEDIT.F
_LEGETXY ( --- x ~y ) Negative y indicates buffer coordinates LINEEDIT.F
_LEGOTOXY ( x y --- ) Goto screen or buffer coordinates LINEEDIT.F
_LEQUIT ( false --- true ) flag edit is finished, discard chngs LINEEDIT.F
_LICHAR ( c1 -- ) LINEEDIT.F
_LOAD-BITMAP ( - flag ) save$ should be set BMPIO.F
_M?CR ( n1 -- ) Primutil.f
_MARKCONSOLE ( startline startcol endline endcol -- ) Fkernel.f
_MCLS ( -- ) Primutil.f
_MCOL ( n1 -- ) Primutil.f
_MCRTAB ( -- ) Primutil.f
_MEMIT ( c1 -- ) allow mouse to abort EMIT Primutil.f
_MESSAGE ( n -- ) Fkernel.f
_MESSAGE-OFF ( -- ) WINMSG.F
_METHODS ( class_body -- ) CLASSDBG.F
_MKEY ( -- c1 ) get a key from the keyboard, and handle mouse clicks Primutil.f
_MKEY? ( -- c1 ) check for key from keyboard, and handle mouse clicks Primutil.f
_MOUSE-CLICK ( -- ) Primutil.f
_MS ( n1 -- ) delay n1 milli-seconds Utils.f
_MSGFIND { addr \ temp$ -- addr false | cfa true } Class.f
_MTYPE ( a1 n1 -- ) allow mouse to abort TYPE Primutil.f
_MUST-SAVE ( -- ) Wined.f
_NULLIFY-PRINTER ( -- ) mark printer as not used yet Dc.f
_NUMBER, ( d -- ) Fkernel.f
_OF-RANGE ( n1 n2 n3 -- n1 f1 ) Utils.f
_OPEN-PREVIOUS ( -- ) load last active files and restore cursor positions Wined.f
_OPT-CODE ( -- ) redefine to resolve code length in bytes ASMWIN32.F
_OUTLINED init c1 c2 and c3 first Opengl.f
_P?CR ( n1 -- ) Dc.f
_PARMS: ( -- ) ARGS.F
_PASS ( -- ) TASKER.F
_PCOL ( n1 -- ) Dc.f
_PCR ( -- ) Dc.f
_PEMIT ( c1 -- ) Dc.f
_PGETCOLROW ( -- cols rows ) Dc.f
_PGETXY ( -- x y ) Dc.f
_PGOTOXY ( x y -- ) Dc.f
_PPAGE ( -- ) Dc.f
_PRINT-DIR-FILES ( adr slen -- ) ANSFILE.F
_PRINTER-RELEASE ( -- ) release the printer DC if allocated Dc.f
_PROC-ERROR ( addr -- ) Fkernel.f
_PROFILE: ( -- ) PROFILE.F
_PTYPE ( a1 n1 -- ) Dc.f
_QUIT ( -- ) Fkernel.f
_R?CR ( n1 -- ) MAPFILE.F
_RACCEPT ( a1 n1 -- ) MAPFILE.F
_RCLS ( -- ) MAPFILE.F
_RCOL ( n1 -- ) MAPFILE.F
_RCRTAB ( -- ) MAPFILE.F
_REFRESH-CMD-WINDOW ( - ) fcp_inputwin.f
_REMIT ( c1 -- ) allow mouse to abort EMIT MAPFILE.F
_RESET-STACKS ( ?? -- ) Fkernel.f
_RESETSRCINFO { ip@ -- } DBGSRC1.F
_RESTORE_DEFAULT ( -- ) Utils.f
_RGETCOLROW ( -- cols rows ) MAPFILE.F
_RGETXY ( -- col row ) MAPFILE.F
_RGOTOXY ( x y -- ) MAPFILE.F
_RTYPE ( a1 n1 -- ) allow mouse to abort TYPE MAPFILE.F
_SAVE-BITMAP-AS { \ nBits pbmi lpBits hbm hdcMem hfile nrgbquad BitmapFileHeader save$ -- } Wined.f
_SAVE-INST ( save the current instruction, and fetch the previous one ) 486ASM.F
_SAVE-SOURCE ( -- ) DBGSRC1.F
_SAVE-SRC ( -- ) DBGSRC1.F
_SAVE-TEXT { \ save$ fhndl -- } save the file in memory to a disk file Wined.f
_SAVE-USAGE ( -- ) MARKUSED.F
_SEARCH ( -b a -- -b value ) recursive fcp101.f
_SEARCH-WORDLIST ( addr len voc -- 0 | cfa flag ) Fkernel.f
_SIZESTATE ( -- state ) state of the display Fkernel.f
_STACK-CHECK ( -- ) Utils.f
_STACK-WATCH { \ stack-cnt -- } DBGSRC2.F
_START/END-FULLSCREEN Oglwin.f
_START/STOP ( -- ) Fkernel.f
_SUBCLASS-WNDPROC ( hwnd msg wparam lparam window -- res ) CONTROL.F
_TYPE ( addr len -- ) SWAP REL>ABS TYPE_X XCALL DROP Fkernel.f
_WAKE ( -- ) TASKER.F
_WARN-TO-SAVE ( -- ) Wined.f
_WHOSETURN-OGL ( turn - turn ) fcp_inputwin.f
_WIN32FORTH-MESSAGE ( lParam wParam -- ) Window.f
_WORD-WATCH { ip@ -- } ip@ is address we want shown in source DBGSRC2.F
_WRITE-DIR-FILES ( adr slen -- ) RELEASE.F
_XIT ( rda ) Wined.f
_XMESSAGE ( n -- ) TOOLSET.F
_Y/N? ( - true | false ) y | n TOOLSET.F
{ ( -- ) ARGS.F
{ ( -- ) begin local variable usage in the form; Fkernel.f
| Meta.f
|: Meta.f
|CLASS ( -- ) Class.f
}; compiletime: ( >GLfloat fdepth - ) ( f: ffdepth_x..ffdepth_0 -- ) Opengl.f
}STRUCT STRUCT.F
+ ( n1 n2 -- n3 ) add n1 to n2, return sum n3 Fkernel.f
+! ( n1 a1 -- ) add cell n1 to the contents of address a1 Fkernel.f
+ACCEPT# ( n1 -- ) LINEEDIT.F
+BMP ( str$ - ) BMPIO.F
+BMP ( str$ - ) Opengl.f
+CELLS ( n1 a1 -- n1*cell+a1 ) multiply n1 by the cell size and add Fkernel.f
+COL-CURSOR ( n1 -- ) Wined.f
+DIRECT-BIT ( adjust an opcode for the direction of the operands ) 486ASM.F
+FIELD ( n1 n2 -- n3 ) define a reference record field Newlab.f
+FP-DIRECT-BIT ( add 4, depending on the direction of the operands ) 486ASM.F
+FP-SIZE ( add 4 if the operation size is 64bit: ie., default float ) 486ASM.F
+FTO TOOLSET.F
+FTO-CELL TOOLSET.F
+HCED ( n -- ) increments highlight column end Wined.f
+HCST ( n -- ) increments highlight column start Wined.f
+HLED ( n -- ) increments highlight line end Wined.f
+HLST ( n -- ) increments highlight line start Wined.f
+HYPER ( n1 -- ) next hyper Wined.f
+INIFILE ( inifile section key - inifile adres ) TOOLSET.F
+K fcp101.f
+K_ALT ( c1 -- c2 ) KEYBOARD.F
+K_CONTROL ( c1 -- c2 ) KEYBOARD.F
+K_SHIFT ( c1 -- c2 ) KEYBOARD.F
+KP fcp101.f
+LNULL ( a1 -- ) append a NULL just beyond the counted chars Primutil.f
+LOOP donew.f
+LOOP Fkernel.f
+LPLACE ( addr len dest -- ) append string addr,len to LONG counted Primutil.f
+MACRO ( get an index into the label table from an offset ) 486ASM.F
+MACRO-BIND ( bind a label offset from the macro level ) 486ASM.F
+MACRO-REF ( reference a label offset from the macro level ) 486ASM.F
+NO-WRAP ( a1 n1 -- a2 ) add n1 to a1, limit to address 0xFFFFFFFF Fkernel.f
+ORDER ( wid - ) add wid to search order Order.f
+OV? ( n1 n2 -- f ) Fkernel.f
+OV? ( n1 n2 -- f ) primcode.f
+PAGE-CURSOR ( 1 -- ) Wined.f
+PLACE ( addr len dest -- ) append string addr,len to counted Fkernel.f
+ROW-CURSOR ( n1 -- ) Wined.f
+ROW-SCROLL ( n1 -- ) Wined.f
+SCR ( -- ) down 1 screen ending with 2 or more empty lines Wined.f
+SIZE-BIT ( adjust an opcode for the size of the operation ) 486ASM.F
+TAB ( --- ) Primutil.f
+TITLE ( adr count - ) Opengl.f
+TO ( n -- ) Fkernel.f
+TO-CELL TOOLSET.F
+UNICODE ( adr-dest c - ) TOOLSET.F
+VALUE$>FPARAMS$ f: ( n - ) Opengl.f
+WORD ( a1 n1 -- a2 n2 a3 n3 ) HYPER.F
+Z", ( a1 n1 -- ) Primutil.f
+Z," ( -- ) Primutil.f
< ( n1 n2 -- f1 ) return true if n1 is less than n2 Fkernel.f
<# ( -- ) Fkernel.f
<& ( n -- 0 n ) Debug.f
<_?MATCH> ( the error action for ?match and ?nomatch ) 486ASM.F
<= ( n1 n2 -- f1 ) return true if n1 is less than n2 Fkernel.f
<> ( n1 n2 -- f1 ) return true if n1 is not equal to n2 Fkernel.f
Primutil.f
( decode the single cell operand representation to its ) 486ASM.F
( encode the single cell operand representation from the values ) 486ASM.F
( ip -- ip' ) XDEBUG.F
( ip -- ip' ) Debug.f
( ip -- ip' ) Debug.f
( ip -- ip' ) XDEBUG.F
( ip -- ip' ) Debug.f
( width -- ) Class.f
( x y a1 n1 --- ) Edit line currently in EDITBUF. LINEEDIT.F
( -- addr ) Fkernel.f
( -- ) Class.f
( addr -- ) Fkernel.f
( ip -- ip' ) XDEBUG.F
( ip -- ip' ) Debug.f
( -- ) allow inheriting from a class or an object Class.f
BL ( --- ) Back to non blank LINEEDIT.F
( --- ) back to char following BL LINEEDIT.F
( #elems ^class OR ^class -- ) Class.f
= ( n1 n2 -- f1 ) return true if n1 is equal to n2 Fkernel.f
> ( n1 n2 -- f1 ) return true if n1 is greater than n2 Fkernel.f
>= ( n1 n2 -- f1 ) return true if n1 is greater than n2 Fkernel.f
>3D.BOARD ( - ) fcp3d.f
>AM/PM" ( time_structure -- ) Utils.f
>APPLICATION ( -- ) select system dictionary, save prev dict Fkernel.f
>BMP ( x y >BitmapInfoHeader - adr>bmp ) BMPDOT.F
>BODY ( cfa -- pfa ) Fkernel.f
>BODY Meta.f
>BODY-T Meta.f
>CLASS ( objCfa -- ^Class ) Class.f
>COL-CURSOR ( n1 -- ) Wined.f
>COLOR ( n1 -- color_object ) WINCLOCK.F
>DATE" ( time_structure -- ) Utils.f
>DEFAULT-SIZE ( change a zero size to the default size ) 486ASM.F
>E ( -- ) Wined.f
>E-UNMINIMIZE ( -- ) Wined.f
>F ( -- ) select the console window as active Wined.f
>F! ( adr which - ) Opengl.f
>F@ ( adr which - ) Opengl.f
>FFA ( cfa -- ffa ) get the File Field Address Fkernel.f
>FLOAT ( addr len -- f ) FLOAT.F
>FLOAT-INT ( f: -- r ) FLOAT.F
>FLOAT-INT.FRAC ( f: -- r ) FLOAT.F
>HCED ( n -- ) set highlight column end Wined.f
>HCST ( n -- ) set highlight column start Wined.f
>HLED ( n -- ) set highlight line end Wined.f
>HLST ( n -- ) set highlight line start Wined.f
>IN[] ( n -- char ) sysload.f
>IS ( xt -- addr ) Fkernel.f
>LINE ( n1 -- ) move to line n1, 1 based Fkernel.f
>LOC ( n -- cfa ) ARGS.F
>LOC ( n -- cfa ) Fkernel.f
>MARK ( -- addr ) Fkernel.f
>MASK ( n1 -- mask ) Class.f
>MONTH,DAY,YEAR" ( time_structure -- ) Utils.f
>NAME-ADD ( nfa cfa -- ) add cfa and nfa to the cache OPTIMIZE.F
>NAME-CACHE-INIT ( -- ) OPTIMIZE.F
>NEWFILE ( addr cnt -- ) dfc.F
>NNAME { cfa -- nfa } optimized >NAME OPTIMIZE.F
>NUMBER ( ud addr len -- ud addr len ) Fkernel.f
>OBJ ( objCfa -- ^obj ) Class.f
>OFA ( cfa -- ofa ) get the Optimization Field Address Fkernel.f
>OLDFILE ( addr cnt -- ) dfc.F
>R ( n1 -- ) push n1 onto the return stack Fkernel.f
>REC#FIL ( n1 --- a1 ) return the buffer n1's file addr BLOCK.F
>REC#S ( n1 --- a1 ) return the buffer n1's record addr BLOCK.F
>REC#UPDT ( n1 --- a1 ) return the buffer n1's update addr BLOCK.F
>RESOLVE ( addr -- ) Fkernel.f
>ROW-COL ( row col -- ) move display to row and column Wined.f
->RVA ( n -- n' ) convert to RVA imageman.f
>S ( a1 n1 -- ) DIS486.F
>SCREENX ( n1 -- n2 ) WINCLOCK.F
>SCREENY ( n1 -- n2 ) WINCLOCK.F
>SELECTOR ( str -- SelID ) get a selector from the input stream Class.f
>SIFENTRY ( n1 -- a1 f1 ) locate address a1 of search in sfiles entry n1 Wined.f
>SIFFILE" ( a1 -- a2 n1 ) Wined.f
>SIFLINE# ( a1 -- n1 ) Wined.f
>SIFTEXT" ( a1 -- a2 n1 ) Wined.f
>STRUCT ( -- -- - adress+offset_in_structure ) STRUCT.F
>SYSTEM ( -- ) select system dictionary, save prev dict Fkernel.f
>TAB ( -- ) Dc.f
>TIME" ( time_structure -- ) Utils.f
>TO<>BL ( --- ) forward to a non blank LINEEDIT.F
>TO=BL ( --- ) forward to a blank LINEEDIT.F
>VIEW ( cfa -- vfa ) Fkernel.f
>WORDLIST ( voc-cfa -- wordlist ) Meta.f
-ALIGNED ( addr1 -- addr2 ) Fkernel.f
-BG ( -- ) Wined.f
-CELLS ( n1 a1 -- a1-n1*cell ) multiply n1 by the cell size and Fkernel.f
-LATER ( n1 -- ) backup later-off by n1 Later.f
-NULL, ( -- ) Primutil.f
-NULLS ( addr n1 -- addr n2 ) remove trailing nulls from addr,n1 Fkernel.f
-ROT ( n1 n2 n3 -- n3 n1 n2 ) rotate top of data stack to third item Fkernel.f
-SCAN ( addr len char -- addr' len' ) Fkernel.f
-SCAN ( addr len char -- addr' len' ) primcode.f
-SCR ( -- ) up 1 screen ending with 2 or more empty lines Wined.f
-SKIP ( addr len char -- addr' len' ) Fkernel.f
-SKIP ( addr len char -- addr' len' ) primcode.f
-TAB ( --- ) Primutil.f
-TRAILCHARS ( addr n1 c1 -- addr n2 ) remove trailing c1's from addr,n1 Fkernel.f
-TRAILING ( addr n1 -- addr n2 ) remove trailing blanks from addr,n1 Fkernel.f
-TRAILING-BLANKS ( -- ) Wined.f
-WORD ( a1 n1 -- a2 n2 a3 n3 ) HYPER.F
-XSEARCH { sadr slen fadr flen \ ffnd srch_lenz -- a3 n3 n4 } Wined.f
-ZR ( - adr-flookat flag ) Opengl.f
-ZX ( - adr-flookat ) Opengl.f
-ZY ( - adr-flookat ) Opengl.f
-ZZ ( - adr-flookat ) Opengl.f
.FMASK ( n -- ) FLOAT.F
.FSTATUS ( n -- ) FLOAT.F
.FTAG1 ( n -- ) FLOAT.F
.FTAG2 ( i -- ) FLOAT.F
.FTEMPX ( -- ) FLOAT.F
.ONEFLOAT ( -- r1 ) FLOAT.F
.SEARCHING ( n1 -- ) Wined.f
.TENBYTE ( addr -- ) Needs lots of work yet. FLOAT.F
.VERSION ( -- ) Forthdlg.f
_+BG ( -- ) Wined.f
_BACK-FIND-TEXT-AGAIN ( -- f1 ) f1=TRUE if found Wined.f
_FLOAT-NUMBER, ( d1 -- d1 ) interpreting a double FLOAT.F
_NEW$ ( -- a1 ) allocate the next MAXSTRING buffer POINTER.F
_RELATIVE-DIRECTION ( adr n - ) Opengl.f
0%.R ( n -- ) display signed right justified except in HEX, Debug.f
0.$SQ ( adr$ sq -- ) fcp3d.f
0< ( n1 -- f1 ) return true if n1 is less than zero Fkernel.f
0<= ( - flag ) TOOLSET.F
0<> ( n1 -- f1 ) return true if n1 is not equal to zero Fkernel.f
0= ( n1 -- f1 ) return true if n1 equals zero Fkernel.f
0> ( n1 -- f1 ) return true if n1 is greater than zero Fkernel.f
0>= ( - flag ) TOOLSET.F
0>S ( -- ) reset s-buf DIS486.F
0F. ( adr code -- ) DIS486.F
0FLOATS! ( adr k - ) Opengl.f
0LOOK-ASIDE ( -- ) LAFIND.F
0MAX ( n1 -- n2 ) return n2 the greater of n1 and zero Fkernel.f
0MODE-BIT! ( clear a mode bit ) 486ASM.F
0TAB ( -- ) left margin goes to left edge of screen Primutil.f
0TERMINATED ( adr-counted-string - ) TOOLSET.F
0XNUMBER? { adr len flg \ adr2 len2 -- d1 TRUE | a1 n1 FALSE } Primutil.f
1- ( n1 -- n2 ) subtract one from n1 Fkernel.f
1-! ( adr - ) TOOLSET.F
1/F FLOAT.F
1+ ( n1 -- n2 ) add one to n1 Fkernel.f
1+! ( adr - ) TOOLSET.F
10**N-0.5 ( f: -- r ) FLOAT.F
1000^N ( n -- 1000^n ) ROMCALC.F
10DIGIT FLOAT.F
16*+ 486ASM.F
16/MOD 486ASM.F
16BIT+ ( a1 -- a1+2 ) same as 2 chars + Wined.f
1BYTE ( compile a single byte, no operand, no override opcode ) 486ASM.F
1MODE-BIT! ( set a mode bit ) 486ASM.F
1TCOUNT { voc-thread \ thread-depth -- n1 } get thread depth of voc thread DTHREAD.F
1WORD ( a1 n1 -- a2 n2 a3 n3 ) parse out a word HYPER.F
2- 486ASM.F
2! ( d1 a1 -- ) store the double number d1 into address a1 Fkernel.f
2* ( n1 -- n2 ) multiply n1 by two Fkernel.f
2/ ( n1 -- n2 ) signed divide n1 by two Fkernel.f
2@ ( a1 -- d1 ) fetch the double number n1 from address a1 Fkernel.f
2^X ( x - 2^x ) TOOLSET.F
2+ 486ASM.F
2+ ( n - n+2 ) TOOLSET.F
2+! ( d1 a1 -- ) double accumulate Primutil.f
2>R ( n1 n2 -- ) push two items onto the returnstack Fkernel.f
2BYTE ( compile a two byte, no operand, no override opcode ) 486ASM.F
2CONSTANT ( n1 n2 -- ) Fkernel.f
2D' ( f: f1 f0 - ) Opengl.f
2DROP ( n1 n2 -- ) discard two single items from the data stack Fkernel.f
2DUP ( n1 n2 -- n1 n2 n1 n2 ) duplicate the top two single items Fkernel.f
2FDUPS ( f: f - f f ) Opengl.f
2LIT ( -- n n ) push the 2 literals following optv1.F
2LITERAL ( d1 -- ) Utils.f
2OVER ( n1 n2 n3 n4 -- n1 n2 n3 n4 n1 n2 ) Fkernel.f
2PRINT ( -- ) Dc.f
2R@ ( -- n1 n2 ) get a copy of the top two items on the return stack Fkernel.f
2R> ( -- n1 n2 ) pop two items off the return stack Fkernel.f
2ROT ( n1 n2 n3 n4 n5 n6 -- n3 n4 n5 n6 n1 n2) slow! Fkernel.f
2SWAP ( n1 n2 n3 n4 -- n3 n4 n1 n2 ) Fkernel.f
2VALUE ( d1 -- ) Primutil.f
2VARIABLE ( -- ) Fkernel.f
332PALETTE ( adr-color-table flag - ) PALETTE.F
3BYTE ( compile a three byte, no operand, no override opcode ) 486ASM.F
3D' ( f: f2 f1 f0 - ) Opengl.f
3D-BD@ ( sq -- piece ) fcp3d.f
3DDOT ( f: 2*size - ) Opengl.f
3DROP ( n1 n2 n3 -- ) discard three items from the data stack Fkernel.f
3DTRIANGLE ( f: size - ) Opengl.f
3DUP ( n1 n2 n3 -- n1 n2 n3 n1 n2 n3 ) Fkernel.f
3FDUPS ( f: f - f f f ) Opengl.f
3FLITERAL ( f: f f f - ) Opengl.f
3LIT ( -- n n n ) push the 3 literals following optv1.F
4* ( n - 4*n ) TOOLSET.F
4+ 486ASM.F
4>R ( n1 n2 n3 n4 -- ) push a 4 items onto the returnstack TOOLSET.F
4D' ( f: f3 f2 f1 f0 - ) Opengl.f
4DROP ( n1 n2 n3 n4 -- ) discard four items from the data stack Fkernel.f
4DUP ( a b c d -- a b c d a b c d ) Fkernel.f
4F' ( f: f3 f2 f1 f0 - ) Opengl.f
4LIT ( -- n n n n ) push the 4 literals following optv1.F
4PRINT ( -- ) Dc.f
4R@ ( -- n1 n2 n3 n4 ) get a copy of the top 4 items on the return stack TOOLSET.F
4R> ( -- n1 n2 n3 n4 ) pop a 4 items off the return stack TOOLSET.F
4TH>TITLE ( - ) Opengl.f
8- 486ASM.F
8* 486ASM.F
8*+ 486ASM.F
8/ 486ASM.F
8+ 486ASM.F
8BIT? ( is the operation 8 bits wide? ) 486ASM.F
8F. ( addr op -- addr' ) DIS486.F

A B C D E F G H I J K L M N O P Q R S T U V W X Y Z #
Created on June 22nd, 2003 by Dirk Busch.