--- gforth/prim 1998/10/18 23:16:51 1.12 +++ gforth/prim 2000/05/31 14:37:40 1.46 @@ -1,6 +1,6 @@ \ Gforth primitives -\ Copyright (C) 1995,1996 Free Software Foundation, Inc. +\ Copyright (C) 1995,1996,1997,1998 Free Software Foundation, Inc. \ This file is part of Gforth. @@ -115,12 +115,13 @@ INC_IP(1); r> dup @ swap cell+ >r ; execute xt -- core +""Perform the semantics represented by the execution token, @i{xt}."" ip=IP; IF_TOS(TOS = sp[0]); EXEC(xt); perform a_addr -- gforth -""equivalent to @code{@ execute}"" +""Equivalent to @code{@ execute}."" /* and pfe */ ip=IP; IF_TOS(TOS = sp[0]); @@ -128,7 +129,8 @@ EXEC(*(Xt *)a_addr); : @ execute ; -\+has? glocals [IF] +\fhas? skipbranchprims 0= [IF] +\+glocals branch-lp+!# -- gforth branch_lp_plus_store_number /* this will probably not be used */ @@ -136,12 +138,11 @@ branch_adjust_lp: lp += (Cell)(IP[1]); goto branch; -\+[THEN] +\+ branch -- gforth branch: -ip = (Xt *)(((Cell)IP)+(Cell)NEXT_INST); -NEXT_P0; +SET_IP((Xt *)(((Cell)IP)+(Cell)NEXT_INST)); : r> dup @ + >r ; @@ -149,15 +150,14 @@ NEXT_P0; \ this is non-syntactical: code must open a brace that is closed by the macro define(condbranch, $1 $2 -$3 ip = (Xt *)(((Cell)IP)+(Cell)NEXT_INST); - NEXT_P0; +$3 SET_IP((Xt *)(((Cell)IP)+(Cell)NEXT_INST)); NEXT; } else INC_IP(1); $4 -\+has? glocals [IF] +\+glocals $1-lp+!# $2_lp_plus_store_number $3 goto branch_adjust_lp; @@ -165,7 +165,7 @@ $3 goto branch_adjust_lp; else INC_IP(2); -\+[THEN] +\+ ) condbranch(?branch,f -- f83 question_branch, @@ -181,15 +181,14 @@ if (f==0) { \ we don't need an lp_plus_store version of the ?dup-stuff, because it \ is only used in if's (yet) -\+has? xconds [IF] +\+xconds ?dup-?branch f -- f new question_dupe_question_branch ""The run-time procedure compiled by @code{?DUP-IF}."" if (f==0) { sp++; IF_TOS(TOS = sp[0]); - ip = (Xt *)(((Cell)IP)+(Cell)NEXT_INST); - NEXT_P0; + SET_IP((Xt *)(((Cell)IP)+(Cell)NEXT_INST)); NEXT; } else @@ -203,14 +202,15 @@ few cycles in that case, but is easy to invocation */ if (f!=0) { sp--; - ip = (Xt *)(((Cell)IP)+(Cell)NEXT_INST); - NEXT_P0; + SET_IP((Xt *)(((Cell)IP)+(Cell)NEXT_INST)); NEXT; } else INC_IP(1); -\+[THEN] +\+ +\f[THEN] +\fhas? skiploopprims 0= [IF] condbranch((next),-- cmFORTH paren_next, if ((*rp)--) { @@ -250,7 +250,7 @@ if ((olddiff^(olddiff+n))>=0 /* the li IF >r + >r dup @ + >r ELSE >r >r drop cell+ >r THEN ;) -\+has? xconds [IF] +\+xconds condbranch((-loop),u -- gforth paren_minus_loop, /* !! check this thoroughly */ @@ -286,7 +286,7 @@ if (diff>=0 || newdiff<0) { IF_TOS(TOS = sp[0]); ,) -\+[THEN] +\+ unloop -- core rp += 2; @@ -325,7 +325,7 @@ else { cell+ >r THEN ; \ --> CORE-EXT -\+has? xconds [IF] +\+xconds (+do) nlimit nstart -- gforth paren_plus_do *--rp = nlimit; @@ -407,7 +407,7 @@ else { cell+ THEN >r ; -\+[THEN] +\+ \ don't make any assumptions where the return stack is!! \ implement this in machine code if it should run quickly! @@ -440,21 +440,33 @@ n = rp[4]; r> r> r> r> r> r> dup itmp ! >r >r >r >r >r >r itmp @ ; [IFUNDEF] itmp variable itmp [THEN] +\f[THEN] + \ digit is high-level: 0/0% move c_from c_to ucount -- core +""Copy the contents of @i{ucount} address units at @i{c-from} to +@i{c-to}. @code{move} works correctly even if the two areas overlap."" memmove(c_to,c_from,ucount); /* make an Ifdef for bsd and others? */ : >r 2dup u< IF r> cmove> ELSE r> cmove THEN ; -cmove c_from c_to u -- string +cmove c_from c_to u -- string c_move +""Copy the contents of @i{ucount} characters from data space at +@i{c-from} to @i{c-to}. The copy proceeds @code{char}-by-@code{char} +from low address to high address; i.e., for overlapping areas it is +safe if @i{c-to}=<@i{c-from}."" while (u-- > 0) *c_to++ = *c_from++; : bounds ?DO dup c@ I c! 1+ LOOP drop ; cmove> c_from c_to u -- string c_move_up +""Copy the contents of @i{ucount} characters from data space at +@i{c-from} to @i{c-to}. The copy proceeds @code{char}-by-@code{char} +from high address to low address; i.e., for overlapping areas it is +safe if @i{c-to}>=@i{c-from}."" while (u-- > 0) c_to[u] = c_from[u]; : @@ -463,17 +475,20 @@ while (u-- > 0) DO 1- dup c@ I c! -1 +LOOP drop ; fill c_addr u c -- core +"" If @i{u}>0, store character @i{c} in each of @i{u} consecutive +@code{char} addresses in memory, starting at address @i{c-addr}."" memset(c_addr,c,u); : -rot bounds ?DO dup I c! LOOP drop ; compare c_addr1 u1 c_addr2 u2 -- n string -""Compare the strings lexicographically. If they are equal, n is 0; if -the first string is smaller, n is -1; if the first string is larger, n +""Compare two strings lexicographically. If they are equal, @i{n} is 0; if +the first string is smaller, @i{n} is -1; if the first string is larger, @i{n} is 1. Currently this is based on the machine's character -comparison. In the future, this may change to considering the current +comparison. In the future, this may change to consider the current locale and its collation order."" +/* close ' to keep fontify happy */ n = memcmp(c_addr1, c_addr2, u10) n = 1; : - rot 2dup - >r min swap -text dup - IF rdrop - ELSE drop r@ 0> - IF rdrop -1 - ELSE r> 1 and - THEN - THEN ; + rot 2dup swap - >r min swap -text dup + IF rdrop ELSE drop r> sgn THEN ; +: sgn ( n -- -1/0/1 ) + dup 0= IF EXIT THEN 0< 2* 1+ ; -text c_addr1 u c_addr2 -- n new dash_text n = memcmp(c_addr1, c_addr2, u); @@ -500,10 +512,12 @@ else if (n>0) swap bounds ?DO dup c@ I c@ = WHILE 1+ LOOP drop 0 ELSE c@ I c@ - unloop THEN -text-flag ; -: -text-flag ( n -- -1/0/1 ) - dup 0< IF drop -1 ELSE 0> 1 and THEN ; +: sgn ( n -- -1/0/1 ) + dup 0= IF EXIT THEN 0< 2* 1+ ; toupper c1 -- c2 gforth +""If @i{c1} is a lower-case character (in the current locale), @i{c2} +is the equivalent upper-case character. All other characters are unchanged."" c2 = toupper(c1); : dup [char] a - [ char z char a - 1 + ] Literal u< bl and - ; @@ -522,6 +536,8 @@ else if (n>0) ELSE c@ toupper I c@ toupper - unloop THEN -text-flag ; -trailing c_addr u1 -- c_addr u2 string dash_trailing +""Adjust the string specified by @i{c-addr, u1} to remove all trailing +spaces. @i{u2} is the length of the modified string."" u2 = u1; while (u2>0 && c_addr[u2-1] == ' ') u2--; @@ -530,6 +546,8 @@ while (u2>0 && c_addr[u2-1] == ' ') dup 0= UNTIL ELSE 1+ THEN ; /string c_addr1 u1 n -- c_addr2 u2 string slash_string +""Adjust the string specified by @i{c-addr1, u1} to remove @i{n} +characters from the start of the string."" c_addr2 = c_addr1+n; u2 = u1-n; : @@ -540,7 +558,7 @@ n = n1+n2; \ PFE-0.9.14 has it differently, but the next release will have it as follows under+ n1 n2 n3 -- n n2 gforth under_plus -""add @var{n3} to @var{n1} (giving @var{n})"" +""add @i{n3} to @i{n1} (giving @i{n})"" n = n1+n3; : rot + swap ; @@ -627,7 +645,7 @@ n2 = n1>>1; LOOP nip ; fm/mod d1 n1 -- n2 n3 core f_m_slash_mod -""floored division: d1 = n3*n1+n2, n1>n2>=0 or 0>=n2>n1"" +""Floored division: @i{d1} = @i{n3}*@i{n1}+@i{n2}, @i{n1}>@i{n2}>=0 or 0>=@i{n2}>@i{n1}."" #ifdef BUGGY_LONG_LONG DCell r = fmdiv(d1,n1); n2=r.hi; @@ -649,7 +667,7 @@ if (1%-3>0 && (d1<0) != (n1<0) && n2!=0) r> 0< IF swap negate swap THEN ; sm/rem d1 n1 -- n2 n3 core s_m_slash_rem -""symmetric division: d1 = n3*n1+n2, sign(n2)=sign(d1) or 0"" +""Symmetric division: @i{d1} = @i{n3}*@i{n1}+@i{n2}, sign(@i{n2})=sign(@i{d1}) or 0."" #ifdef BUGGY_LONG_LONG DCell r = smdiv(d1,n1); n2=r.hi; @@ -699,6 +717,7 @@ ud = (UDCell)u1 * (UDCell)u2; and >r >r 2dup d+ swap r> + swap r> ; um/mod ud u1 -- u2 u3 core u_m_slash_mod +""ud=u3*u1+u2, u1>u2>=0"" #ifdef BUGGY_LONG_LONG UDCell r = umdiv(ud,u1); u2=r.hi; @@ -747,7 +766,7 @@ d = d1-d2; : dnegate d+ ; -dnegate d1 -- d2 double +dnegate d1 -- d2 double d_negate /* use dminus as alias */ #ifdef BUGGY_LONG_LONG d2 = dnegate(d1); @@ -786,7 +805,7 @@ w = w1|w2; : invert swap invert and invert ; -xor w1 w2 -- w core +xor w1 w2 -- w core x_or w = w1^w2; invert w1 -- w2 core @@ -794,12 +813,12 @@ w2 = ~w1; : MAXU xor ; -rshift u1 n -- u2 core +rshift u1 n -- u2 core r_shift u2 = u1>>n; : 0 ?DO 2/ MAXI and LOOP ; -lshift u1 n -- u2 core +lshift u1 n -- u2 core l_shift u2 = u1< $2 -- f $7 $3different +$1<> $2 -- f $7 $3not_equals f = FLAG($4!=$5); : [ char $1x char 0 = [IF] @@ -824,7 +843,7 @@ f = FLAG($4!=$5); ] xor 0<> [ [THEN] ] ; -$1< $2 -- f $8 $3less +$1< $2 -- f $8 $3less_than f = FLAG($4<$5); : [ char $1x char 0 = [IF] @@ -836,7 +855,7 @@ f = FLAG($4<$5); [THEN] [THEN] ] ; -$1> $2 -- f $9 $3greater +$1> $2 -- f $9 $3greater_than f = FLAG($4>$5); : [ char $1x char 0 = [IF] ] negate [ [ELSE] ] swap [ [THEN] ] @@ -868,21 +887,21 @@ f = FLAG($4.lo==$5.lo && $4.hi==$5.hi); f = FLAG($4==$5); #endif -$1<> $2 -- f $7 $3different +$1<> $2 -- f $7 $3not_equals #ifdef BUGGY_LONG_LONG f = FLAG($4.lo!=$5.lo || $4.hi!=$5.hi); #else f = FLAG($4!=$5); #endif -$1< $2 -- f $8 $3less +$1< $2 -- f $8 $3less_than #ifdef BUGGY_LONG_LONG f = FLAG($4.hi==$5.hi ? $4.lo<$5.lo : $4.hi<$5.hi); #else f = FLAG($4<$5); #endif -$1> $2 -- f $9 $3greater +$1> $2 -- f $9 $3greater_than #ifdef BUGGY_LONG_LONG f = FLAG($4.hi==$5.hi ? $4.lo>$5.lo : $4.hi>$5.hi); #else @@ -905,33 +924,40 @@ f = FLAG($4>=$5); ) -\+has? dcomps [IF] +\+dcomps dcomparisons(d, d1 d2, d_, d1, d2, double, gforth, double, gforth) dcomparisons(d0, d, d_zero_, d, DZERO, double, gforth, double, gforth) dcomparisons(du, ud1 ud2, d_u_, ud1, ud2, gforth, gforth, double-ext, gforth) -\+[THEN] +\+ within u1 u2 u3 -- f core-ext +""u2=r - r> u< ; -sp@ -- a_addr gforth spat +sp@ -- a_addr gforth sp_fetch a_addr = sp+1; -sp! a_addr -- gforth spstore +sp! a_addr -- gforth sp_store sp = a_addr; /* works with and without TOS caching */ -rp@ -- a_addr gforth rpat +rp@ -- a_addr gforth rp_fetch a_addr = rp; -rp! a_addr -- gforth rpstore +rp! a_addr -- gforth rp_store rp = a_addr; -\+has? floating [IF] +\+floating fp@ -- f_addr gforth fp_fetch f_addr = fp; @@ -939,11 +965,11 @@ f_addr = fp; fp! f_addr -- gforth fp_store fp = f_addr; -\+[THEN] +\+ ;s -- gforth semis -ip = (Xt *)(*rp++); -NEXT_P0; +""The primitive compiled by @code{EXIT}."" +SET_IP((Xt *)(*rp++)); >r w -- core to_r *--rp = w; @@ -998,7 +1024,7 @@ swap w1 w2 -- w2 w1 core >r (swap) ! r> (swap) @ ; Variable (swap) -dup w -- w w core +dup w -- w w core dupe : sp@ @ ; @@ -1069,17 +1095,21 @@ w = sp[u+1]; \ toggle is high-level: 0.11/0.42% @ a_addr -- w core fetch +"" Read from the cell at address @i{a-addr}, and return its contents, @i{w}."" w = *a_addr; ! w a_addr -- core store +"" Write the value @i{w} to the cell at address @i{a-addr}."" *a_addr = w; +! n a_addr -- core plus_store +"" Add @i{n} to the value stored in the cell at address @i{a-addr}."" *a_addr += n; : tuck @ + swap ! ; -c@ c_addr -- c core cfetch +c@ c_addr -- c core c_fetch +"" Read from the char at address @i{c-addr}, and return its contents, @i{c}."" c = *c_addr; : [ bigendian [IF] ] @@ -1104,7 +1134,8 @@ c = *c_addr; ; : 8>> 2/ 2/ 2/ 2/ 2/ 2/ 2/ 2/ ; -c! c c_addr -- core cstore +c! c c_addr -- core c_store +"" Write the value @i{c} to the char at address @i{c-addr}."" *c_addr = c; : [ bigendian [IF] ] @@ -1134,23 +1165,28 @@ c! c c_addr -- core cstore : 8<< 2* 2* 2* 2* 2* 2* 2* 2* ; 2! w1 w2 a_addr -- core two_store +"" Write the value @i{w1, w2} to the double at address @i{a-addr}."" a_addr[0] = w2; a_addr[1] = w1; : tuck ! cell+ ! ; 2@ a_addr -- w1 w2 core two_fetch +"" Read from the double at address @i{a-addr}, and return its contents, @i{w1, w2}."" w2 = a_addr[0]; w1 = a_addr[1]; : dup cell+ @ swap @ ; cell+ a_addr1 -- a_addr2 core cell_plus +"" Increment @i{a-addr1} by the number of address units corresponding to the size of +one cell, to give @i{a-addr2}."" a_addr2 = a_addr1+1; : cell + ; cells n1 -- n2 core +"" @i{n2} is the number of address units corresponding to @i{n1} cells."" n2 = n1 * sizeof(Cell); : [ cell @@ -1160,24 +1196,28 @@ n2 = n1 * sizeof(Cell); 2/ dup [IF] ] 2* [ [THEN] drop ] ; -char+ c_addr1 -- c_addr2 core care_plus +char+ c_addr1 -- c_addr2 core char_plus +"" Increment @i{c-addr1} by the number of address units corresponding to the size of +one char, to give @i{c-addr2}."" c_addr2 = c_addr1 + 1; : 1+ ; -(chars) n1 -- n2 gforth paren_cares +(chars) n1 -- n2 gforth paren_chars n2 = n1 * sizeof(Char); : ; count c_addr1 -- c_addr2 u core +"" If @i{c-add1} is the address of a counted string return the length of +the string, @i{u}, and the address of its first character, @i{c-addr2}."" u = *c_addr1; c_addr2 = c_addr1+1; : dup 1+ swap c@ ; (f83find) c_addr u f83name1 -- f83name2 new paren_f83find -for (; f83name1 != NULL; f83name1 = f83name1->next) +for (; f83name1 != NULL; f83name1 = (struct F83Name *)(f83name1->next)) if ((UCell)F83NAME_COUNT(f83name1)==u && memcasecmp(c_addr, f83name1->name, u)== 0 /* or inline? */) break; @@ -1191,14 +1231,14 @@ f83name2=f83name1; : (find-samelen) ( u f83name1 -- u f83name2/0 ) BEGIN 2dup cell+ c@ $1F and <> WHILE @ dup 0= UNTIL THEN ; -\+has? hash [IF] +\+hash (hashfind) c_addr u a_addr -- f83name2 new paren_hashfind -F83Name *f83name1; +struct F83Name *f83name1; f83name2=NULL; while(a_addr != NULL) { - f83name1=(F83Name *)(a_addr[1]); + f83name1=(struct F83Name *)(a_addr[1]); a_addr=(Cell *)(a_addr[0]); if ((UCell)F83NAME_COUNT(f83name1)==u && memcasecmp(c_addr, f83name1->name, u)== 0 /* or inline? */) @@ -1217,11 +1257,11 @@ while(a_addr != NULL) (tablefind) c_addr u a_addr -- f83name2 new paren_tablefind ""A case-sensitive variant of @code{(hashfind)}"" -F83Name *f83name1; +struct F83Name *f83name1; f83name2=NULL; while(a_addr != NULL) { - f83name1=(F83Name *)(a_addr[1]); + f83name1=(struct F83Name *)(a_addr[1]); a_addr=(Cell *)(a_addr[0]); if ((UCell)F83NAME_COUNT(f83name1)==u && memcmp(c_addr, f83name1->name, u)== 0 /* or inline? */) @@ -1272,7 +1312,7 @@ Create rot-values 7 c, 5 c, 5 c, 5 c, 5 c, 6 c, 5 c, 5 c, 5 c, 5 c, 7 c, 5 c, 5 c, -\+[THEN] +\+ (parse-white) c_addr1 u1 -- c_addr2 u2 gforth paren_parse_white /* use !isgraph instead of isspace? */ @@ -1295,60 +1335,67 @@ else { REPEAT THEN nip - ; aligned c_addr -- a_addr core +"" @i{a-addr} is the first aligned address greater than or equal to @i{c-addr}."" a_addr = (Cell *)((((Cell)c_addr)+(sizeof(Cell)-1))&(-sizeof(Cell))); : [ cell 1- ] Literal + [ -1 cells ] Literal and ; faligned c_addr -- f_addr float f_aligned +"" @i{f-addr} is the first float-aligned address greater than or equal to @i{c-addr}."" f_addr = (Float *)((((Cell)c_addr)+(sizeof(Float)-1))&(-sizeof(Float))); : [ 1 floats 1- ] Literal + [ -1 floats ] Literal and ; >body xt -- a_addr core to_body +"" Get the address of the body of the word represented by @i{xt} (the address +of the word's data field)."" a_addr = PFA(xt); : 2 cells + ; +\ threading stuff is currently only interesting if we have a compiler +\fhas? standardthreading has? compiler and [IF] + >code-address xt -- c_addr gforth to_code_address -""c_addr is the code address of the word xt"" +""@i{c-addr} is the code address of the word @i{xt}."" /* !! This behaves installation-dependently for DOES-words */ c_addr = (Address)CODE_ADDRESS(xt); : @ ; >does-code xt -- a_addr gforth to_does_code -""If xt ist the execution token of a defining-word-defined word, -a_addr is the start of the Forth code after the DOES>; -Otherwise a_addr is 0."" +""If @i{xt} is the execution token of a defining-word-defined word, +@i{a-addr} is the start of the Forth code after the @code{DOES>}; +Otherwise @i{a-addr} is 0."" a_addr = (Cell *)DOES_CODE(xt); : cell+ @ ; code-address! c_addr xt -- gforth code_address_store -""Creates a code field with code address c_addr at xt"" +""Create a code field with code address @i{c-addr} at @i{xt}."" MAKE_CF(xt, c_addr); CACHE_FLUSH(xt,(size_t)PFA(0)); : ! ; does-code! a_addr xt -- gforth does_code_store -""creates a code field at xt for a defining-word-defined word; a_addr -is the start of the Forth code after DOES>"" +""Create a code field at @i{xt} for a defining-word-defined word; @i{a-addr} +is the start of the Forth code after @code{DOES>}."" MAKE_DOES_CF(xt, a_addr); CACHE_FLUSH(xt,(size_t)PFA(0)); : dodoes: over ! cell+ ! ; does-handler! a_addr -- gforth does_handler_store -""creates a DOES>-handler at address a_addr. a_addr usually points -just behind a DOES>."" +""Create a @code{DOES>}-handler at address @i{a-addr}. Usually, @i{a-addr} points +just behind a @code{DOES>}."" MAKE_DOES_HANDLER(a_addr); CACHE_FLUSH((caddr_t)a_addr,DOES_HANDLER_SIZE); : drop ; /does-handler -- n gforth slash_does_handler -""the size of a does-handler (includes possible padding)"" +""The size of a @code{DOES>}-handler (includes possible padding)."" /* !! a constant or environmental query might be better */ n = DOES_HANDLER_SIZE; : @@ -1369,15 +1416,25 @@ n=1; : 1 ; -\+has? os [IF] +\f[THEN] key-file wfileid -- n gforth paren_key_file +#ifdef HAS_FILE fflush(stdout); n = key((FILE*)wfileid); +#else +n = key(stdin); +#endif key?-file wfileid -- n facility key_q_file +#ifdef HAS_FILE fflush(stdout); n = key_query((FILE*)wfileid); +#else +n = key_query(stdin); +#endif + +\+os stdin -- wfileid gforth wfileid = (Cell)stdin; @@ -1398,7 +1455,7 @@ ucols=cols; flush-icache c_addr u -- gforth flush_icache ""Make sure that the instruction cache of the processor (if there is -one) does not contain stale data at @var{c_addr} and @var{u} bytes +one) does not contain stale data at @i{c-addr} and @i{u} bytes afterwards. @code{END-CODE} performs a @code{flush-icache} automatically. Caveat: @code{flush-icache} might not work on your installation; this is usually the case if direct threading is not @@ -1412,14 +1469,23 @@ FLUSH_ICACHE(c_addr,u); return (Label *)n; (system) c_addr u -- wretval wior gforth peren_system +#ifndef MSDOS int old_tp=terminal_prepped; deprep_terminal(); +#endif wretval=system(cstr(c_addr,u,1)); /* ~ expansion on first part of string? */ wior = IOR(wretval==-1 || (wretval==127 && errno != 0)); +#ifndef MSDOS if (old_tp) prep_terminal(); +#endif getenv c_addr1 u1 -- c_addr2 u2 gforth +""The string @i{c-addr1 u1} specifies an environment variable. The string @i{c-addr2 u2} +is the host operating system's expansion of that environment variable. If the +environment variable does not exist, @i{c-addr2 u2} specifies a string 0 characters +in length."" +/* close ' to keep fontify happy */ c_addr2 = getenv(cstr(c_addr1,u1,1)); u2 = (c_addr2 == NULL ? 0 : strlen(c_addr2)); @@ -1432,6 +1498,8 @@ wretval = pclose((FILE *)wfileid); wior = IOR(wretval==-1); time&date -- nsec nmin nhour nday nmonth nyear facility-ext time_and_date +""Report the current time of day. Seconds, minutes and hours are numbered from 0. +Months are numbered from 1."" struct timeval time1; struct timezone zone1; struct tm *ltime; @@ -1445,27 +1513,41 @@ nmin =ltime->tm_min; nsec =ltime->tm_sec; ms n -- facility-ext +""Wait at least @i{n} milli-second."" struct timeval timeout; timeout.tv_sec=n/1000; timeout.tv_usec=1000*(n%1000); (void)select(0,0,0,0,&timeout); allocate u -- a_addr wior memory +""Allocate @i{u} address units of contiguous data space. The initial +contents of the data space is undefined. If the allocation is successful, +@i{a-addr} is the start address of the allocated region and @i{wior} +is 0. If the allocation fails, @i{a-addr} is undefined and @i{wior} +is an implementation-defined I/O result code."" a_addr = (Cell *)malloc(u?u:1); wior = IOR(a_addr==NULL); free a_addr -- wior memory +""Return the region of data space starting at @i{a-addr} to the system. +The regon must originally have been obtained using @code{allocate} or +@code{resize}. If the operational is successful, @i{wior} is 0. +If the operation fails, @i{wior} is an implementation-defined +I/O result code."" free(a_addr); wior = 0; resize a_addr1 u -- a_addr2 wior memory -""Change the size of the allocated area at @i{a_addr1} to @i{u} +""Change the size of the allocated area at @i{a-addr1} to @i{u} address units, possibly moving the contents to a different -area. @i{a_addr2} is the address of the resulting area. If -@code{a_addr1} is 0, Gforth's (but not the standard) @code{resize} -@code{allocate}s @i{u} address units."" +area. @i{a-addr2} is the address of the resulting area. +If the operational is successful, @i{wior} is 0. +If the operation fails, @i{wior} is an implementation-defined +I/O result code. If @i{a-addr1} is 0, Gforth's (but not the Standard) +@code{resize} @code{allocate}s @i{u} address units."" /* the following check is not necessary on most OSs, but it is needed on SunOS 4.1.2. */ +/* close ' to keep fontify happy */ if (a_addr1==NULL) a_addr2 = (Cell *)malloc(u); else @@ -1495,23 +1577,32 @@ fp=FP; IF_TOS(TOS=sp[0]); IF_FTOS(FTOS=fp[0]); -\+[THEN] ( has? os ) has? file [IF] +\+ +\+file close-file wfileid -- wior file close_file wior = IOR(fclose((FILE *)wfileid)==EOF); -open-file c_addr u ntype -- w2 wior file open_file -w2 = (Cell)fopen(tilde_cstr(c_addr, u, 1), fileattr[ntype]); -wior = IOR(w2 == 0); +open-file c_addr u ntype -- wfileid wior file open_file +wfileid = (Cell)fopen(tilde_cstr(c_addr, u, 1), fileattr[ntype]); +#if defined(GO32) && defined(MSDOS) +if(wfileid && !(ntype & 1)) + setbuf((FILE*)wfileid, NULL); +#endif +wior = IOR(wfileid == 0); -create-file c_addr u ntype -- w2 wior file create_file +create-file c_addr u ntype -- wfileid wior file create_file Cell fd; fd = open(tilde_cstr(c_addr, u, 1), O_CREAT|O_TRUNC|ufileattr[ntype], 0666); if (fd != -1) { - w2 = (Cell)fdopen(fd, fileattr[ntype]); - wior = IOR(w2 == 0); + wfileid = (Cell)fdopen(fd, fileattr[ntype]); +#if defined(GO32) && defined(MSDOS) + if(wfileid && !(ntype & 1)) + setbuf((FILE*)wfileid, NULL); +#endif + wior = IOR(wfileid == 0); } else { - w2 = 0; + wfileid = 0; wior = IOR(1); } @@ -1519,6 +1610,7 @@ delete-file c_addr u -- wior file delet wior = IOR(unlink(tilde_cstr(c_addr, u, 1))==-1); rename-file c_addr1 u1 c_addr2 u2 -- wior file-ext rename_file +""Rename file @i{c_addr1 u1} to new name @i{c_addr2 u2}"" char *s1=tilde_cstr(c_addr2, u2, 1); wior = IOR(rename(tilde_cstr(c_addr1, u1, 0), s1)==-1); @@ -1531,7 +1623,6 @@ reposition-file ud wfileid -- wior file wior = IOR(fseek((FILE *)wfileid, UD2LONG(ud), SEEK_SET)==-1); file-size wfileid -- ud wior file file_size -#include struct stat buf; wior = IOR(fstat(fileno((FILE *)wfileid), &buf)==-1); ud = LONG2UD(buf.st_size); @@ -1548,24 +1639,29 @@ if (wior) clearerr((FILE *)wfileid); read-line c_addr u1 wfileid -- u2 flag wior file read_line -/* +#if 1 Cell c; flag=-1; for(u2=0; u2d r -- d float f_to_d #ifdef BUGGY_LONG_LONG -d.hi = ldexp(r,-CELL_BITS) - (r<0); +d.hi = ldexp(r,-(int)(CELL_BITS)) - (r<0); d.lo = r-ldexp((Float)d.hi,CELL_BITS); #else d = r; #endif f! r f_addr -- float f_store +"" Store the floating-point value @i{r} to address @i{f-addr}."" *f_addr = r; f@ f_addr -- r float f_fetch +"" Fetch floating-point value @i{r} from address @i{f-addr}."" r = *f_addr; df@ df_addr -- r float-ext d_f_fetch +"" Fetch the double-precision IEEE floating-point value @i{r} from the address @i{df-addr}."" #ifdef IEEE_FP r = *df_addr; #else @@ -1656,6 +1765,7 @@ r = *df_addr; #endif df! r df_addr -- float-ext d_f_store +"" Store the double-precision IEEE floating-point value @i{r} to the address @i{df-addr}."" #ifdef IEEE_FP *df_addr = r; #else @@ -1663,6 +1773,7 @@ df! r df_addr -- float-ext d_f_store #endif sf@ sf_addr -- r float-ext s_f_fetch +"" Fetch the single-precision IEEE floating-point value @i{r} from the address @i{sf-addr}."" #ifdef IEEE_FP r = *sf_addr; #else @@ -1670,6 +1781,7 @@ r = *sf_addr; #endif sf! r sf_addr -- float-ext s_f_store +"" Store the single-precision IEEE floating-point value @i{r} to the address @i{sf-addr}."" #ifdef IEEE_FP *sf_addr = r; #else @@ -1689,39 +1801,42 @@ f/ r1 r2 -- r3 float f_slash r3 = r1/r2; f** r1 r2 -- r3 float-ext f_star_star -""@i{r3} is @i{r1} raised to the @i{r2}th power"" +""@i{r3} is @i{r1} raised to the @i{r2}th power."" r3 = pow(r1,r2); -fnegate r1 -- r2 float +fnegate r1 -- r2 float f_negate r2 = - r1; -fdrop r -- float +fdrop r -- float f_drop -fdup r -- r r float +fdup r -- r r float f_dupe -fswap r1 r2 -- r2 r1 float +fswap r1 r2 -- r2 r1 float f_swap -fover r1 r2 -- r1 r2 r1 float +fover r1 r2 -- r1 r2 r1 float f_over -frot r1 r2 r3 -- r2 r3 r1 float +frot r1 r2 r3 -- r2 r3 r1 float f_rote -fnip r1 r2 -- r2 gforth +fnip r1 r2 -- r2 gforth f_nip -ftuck r1 r2 -- r2 r1 r2 gforth +ftuck r1 r2 -- r2 r1 r2 gforth f_tuck float+ f_addr1 -- f_addr2 float float_plus +"" Increment @i{f-addr1} by the number of address units corresponding to the size of +one floating-point number, to give @i{f-addr2}."" f_addr2 = f_addr1+1; floats n1 -- n2 float +""@i{n2} is the number of address units corresponding to @i{n1} floating-point numbers."" n2 = n1*sizeof(Float); floor r1 -- r2 float -""round towards the next smaller integral value, i.e., round toward negative infinity"" +""Round towards the next smaller integral value, i.e., round toward negative infinity."" /* !! unclear wording */ r2 = floor(r1); -fround r1 -- r2 float -""round to the nearest integral value"" +fround r1 -- r2 float f_round +""Round to the nearest integral value."" /* !! unclear wording */ #ifdef HAVE_RINT r2 = rint(r1); @@ -1730,13 +1845,13 @@ r2 = floor(r1+0.5); /* !! This is not quite true to the rounding rules given in the standard */ #endif -fmax r1 r2 -- r3 float +fmax r1 r2 -- r3 float f_max if (r1float c_addr u -- flag float to_float +""Attempt to convert the character string @i{c-addr u} to +internal floating-point representation. If the string +represents a valid floating-point number @i{r} is placed +on the floating-point stack and @i{flag} is true. Otherwise, +@i{flag} is false. A string of blanks is a special case +and represents the floating-point number 0."" /* real signature: c_addr u -- r t / f */ Float r; char *number=cstr(c_addr, u, 1); char *endconv; -while(isspace(number[--u]) && u>0); +int sign = 0; +if(number[0]=='-') { + sign = 1; + number++; + u--; +} +while(isspace((unsigned)(number[--u])) && u>0); switch(number[u]) { case 'd': @@ -1772,7 +1899,7 @@ if((flag=FLAG(!(Cell)*endconv))) { IF_FTOS(fp[0] = FTOS); fp += -1; - FTOS = r; + FTOS = sign ? -r : r; } else if(*endconv=='d' || *endconv=='D') { @@ -1782,34 +1909,34 @@ else if(*endconv=='d' || *endconv=='D') { IF_FTOS(fp[0] = FTOS); fp += -1; - FTOS = r; + FTOS = sign ? -r : r; } } -fabs r1 -- r2 float-ext +fabs r1 -- r2 float-ext f_abs r2 = fabs(r1); -facos r1 -- r2 float-ext +facos r1 -- r2 float-ext f_a_cos r2 = acos(r1); -fasin r1 -- r2 float-ext +fasin r1 -- r2 float-ext f_a_sine r2 = asin(r1); -fatan r1 -- r2 float-ext +fatan r1 -- r2 float-ext f_a_tan r2 = atan(r1); -fatan2 r1 r2 -- r3 float-ext -""@i{r1/r2}=tan@i{r3}. The standard does not require, but probably +fatan2 r1 r2 -- r3 float-ext f_a_tan_two +""@i{r1/r2}=tan(@i{r3}). ANS Forth does not require, but probably intends this to be the inverse of @code{fsincos}. In gforth it is."" r3 = atan2(r1,r2); -fcos r1 -- r2 float-ext +fcos r1 -- r2 float-ext f_cos r2 = cos(r1); -fexp r1 -- r2 float-ext +fexp r1 -- r2 float-ext f_e_x_p r2 = exp(r1); -fexpm1 r1 -- r2 float-ext +fexpm1 r1 -- r2 float-ext f_e_x_p_m_one ""@i{r2}=@i{e}**@i{r1}@minus{}1"" #ifdef HAVE_EXPM1 extern double @@ -1822,10 +1949,10 @@ r2 = expm1(r1); r2 = exp(r1)-1.; #endif -fln r1 -- r2 float-ext +fln r1 -- r2 float-ext f_l_n r2 = log(r1); -flnp1 r1 -- r2 float-ext +flnp1 r1 -- r2 float-ext f_l_n_p_one ""@i{r2}=ln(@i{r1}+1)"" #ifdef HAVE_LOG1P extern double @@ -1838,74 +1965,82 @@ r2 = log1p(r1); r2 = log(r1+1.); #endif -flog r1 -- r2 float-ext -""the decimal logarithm"" +flog r1 -- r2 float-ext f_log +""The decimal logarithm."" r2 = log10(r1); -falog r1 -- r2 float-ext +falog r1 -- r2 float-ext f_a_log ""@i{r2}=10**@i{r1}"" extern double pow10(double); r2 = pow10(r1); -fsin r1 -- r2 float-ext +fsin r1 -- r2 float-ext f_sine r2 = sin(r1); -fsincos r1 -- r2 r3 float-ext +fsincos r1 -- r2 r3 float-ext f_sine_cos ""@i{r2}=sin(@i{r1}), @i{r3}=cos(@i{r1})"" r2 = sin(r1); r3 = cos(r1); -fsqrt r1 -- r2 float-ext +fsqrt r1 -- r2 float-ext f_square_root r2 = sqrt(r1); -ftan r1 -- r2 float-ext +ftan r1 -- r2 float-ext f_tan r2 = tan(r1); : fsincos f/ ; -fsinh r1 -- r2 float-ext +fsinh r1 -- r2 float-ext f_cinch r2 = sinh(r1); : fexpm1 fdup fdup 1. d>f f+ f/ f+ f2/ ; -fcosh r1 -- r2 float-ext +fcosh r1 -- r2 float-ext f_cosh r2 = cosh(r1); : fexp fdup 1/f f+ f2/ ; -ftanh r1 -- r2 float-ext +ftanh r1 -- r2 float-ext f_tan_h r2 = tanh(r1); : f2* fexpm1 fdup 2. d>f f+ f/ ; -fasinh r1 -- r2 float-ext +fasinh r1 -- r2 float-ext f_a_cinch r2 = asinh(r1); : fdup fdup f* 1. d>f f+ fsqrt f/ fatanh ; -facosh r1 -- r2 float-ext +facosh r1 -- r2 float-ext f_a_cosh r2 = acosh(r1); : fdup fdup f* 1. d>f f- fsqrt f+ fln ; -fatanh r1 -- r2 float-ext +fatanh r1 -- r2 float-ext f_a_tan_h r2 = atanh(r1); : fdup f0< >r fabs 1. d>f fover f- f/ f2* flnp1 f2/ r> IF fnegate THEN ; sfloats n1 -- n2 float-ext s_floats +""@i{n2} is the number of address units corresponding to @i{n1} +single-precision IEEE floating-point numbers."" n2 = n1*sizeof(SFloat); dfloats n1 -- n2 float-ext d_floats +""@i{n2} is the number of address units corresponding to @i{n1} +double-precision IEEE floating-point numbers."" n2 = n1*sizeof(DFloat); sfaligned c_addr -- sf_addr float-ext s_f_aligned +"" @i{sf-addr} is the first single-float-aligned address greater +than or equal to @i{c-addr}."" sf_addr = (SFloat *)((((Cell)c_addr)+(sizeof(SFloat)-1))&(-sizeof(SFloat))); : [ 1 sfloats 1- ] Literal + [ -1 sfloats ] Literal and ; dfaligned c_addr -- df_addr float-ext d_f_aligned +"" @i{df-addr} is the first double-float-aligned address greater +than or equal to @i{c-addr}."" df_addr = (DFloat *)((((Cell)c_addr)+(sizeof(DFloat)-1))&(-sizeof(DFloat))); : [ 1 dfloats 1- ] Literal + [ -1 dfloats ] Literal and ; @@ -1916,7 +2051,8 @@ df_addr = (DFloat *)((((Cell)c_addr)+(si \ INDIRECT-THREADED, TOS-CACHED, FTOS-CACHED, CODEFIELD-DOES */ \ local variable implementation primitives -\+[THEN] ( has? floats ) has? glocals [IF] +\+ +\+glocals @local# -- w gforth fetch_local_number w = *(Cell *)(lp+(Cell)NEXT_INST); @@ -1934,7 +2070,7 @@ w = *(Cell *)(lp+2*sizeof(Cell)); @local3 -- w new fetch_local_twelve w = *(Cell *)(lp+3*sizeof(Cell)); -\+has? floating [IF] +\+floating f@local# -- r gforth f_fetch_local_number r = *(Float *)(lp+(Cell)NEXT_INST); @@ -1946,7 +2082,7 @@ r = *(Float *)(lp+0*sizeof(Float)); f@local1 -- r new f_fetch_local_eight r = *(Float *)(lp+1*sizeof(Float)); -\+[THEN] +\+ laddr# -- c_addr gforth laddr_number /* this can also be used to implement lp@ */ @@ -1976,7 +2112,7 @@ lp = (Address)c_addr; lp -= sizeof(Cell); *(Cell *)lp = w; -\+has? floating [IF] +\+floating f>l r -- gforth f_to_l lp -= sizeof(Float); @@ -1987,9 +2123,10 @@ r = fp[u+1]; /* +1, because update of fp : floats fp@ + f@ ; -\+[THEN] [THEN] \ has? glocals +\+ +\+ -\+has? OS [IF] +\+OS define(`uploop', `pushdef(`$1', `$2')_uploop(`$1', `$2', `$3', `$4', `$5')`'popdef(`$1')') @@ -2020,6 +2157,7 @@ rret = (SYSCALL(Float(*)(argdlist($1)))u ') +\ close ' to keep fontify happy open-lib c_addr1 u1 -- u2 gforth open_lib #if defined(HAVE_LIBDL) || defined(HAVE_DLOPEN) @@ -2028,7 +2166,7 @@ open-lib c_addr1 u1 -- u2 gforth open_li #endif u2=(UCell) dlopen(cstr(c_addr1, u1, 1), RTLD_GLOBAL | RTLD_LAZY); #else -# ifdef HAVE_LIBKERNEL32 +# ifdef _WIN32 u2 = (Cell) GetModuleHandle(cstr(c_addr1, u1, 1)); # else #warning Define open-lib! @@ -2040,7 +2178,7 @@ lib-sym c_addr1 u1 u2 -- u3 gforth lib_s #if defined(HAVE_LIBDL) || defined(HAVE_DLOPEN) u3 = (UCell) dlsym((void*)u2,cstr(c_addr1, u1, 1)); #else -# ifdef HAVE_LIBKERNEL32 +# ifdef _WIN32 u3 = (Cell) GetProcAddress((HMODULE)u2, cstr(c_addr1, u1, 1)); # else #warning Define lib-sym! @@ -2053,7 +2191,7 @@ icall(20) uploop(i, 0, 7, `fcall(i)') fcall(20) -\+[THEN] \ has? OS +\+ up! a_addr -- gforth up_store UP=up=(char *)a_addr; @@ -2061,3 +2199,53 @@ UP=up=(char *)a_addr; up ! ; Variable UP +wcall u -- gforth +IF_FTOS(fp[0]=FTOS); +FP=fp; +sp=(SYSCALL(Cell(*)(Cell *, void *))u)(sp, &FP); +fp=FP; +IF_TOS(TOS=sp[0];) +IF_FTOS(FTOS=fp[0]); + +\+file + +open-dir c_addr u -- wdirid wior gforth open_dir +wdirid = (Cell)opendir(tilde_cstr(c_addr, u, 1)); +wior = IOR(wdirid == 0); + +read-dir c_addr u1 wdirid -- u2 flag wior gforth read_dir +struct dirent * dent; +dent = readdir((DIR *)wdirid); +wior = 0; +flag = -1; +if(dent == NULL) { + u2 = 0; + flag = 0; +} else { + u2 = strlen(dent->d_name); + if(u2 > u1) + u2 = u1; + memmove(c_addr, dent->d_name, u2); +} + +close-dir wdirid -- wior gforth close_dir +wior = IOR(closedir((DIR *)wdirid)); + +filename-match c_addr1 u1 c_addr2 u2 -- flag gforth match_file +char * string = cstr(c_addr1, u1, 1); +char * pattern = cstr(c_addr2, u2, 0); +flag = FLAG(!fnmatch(pattern, string, 0)); + +\+ + +newline -- c_addr u gforth +""String containing the newline sequence of the host OS"" +char newline[] = { +#ifdef unix +'\n' +#else +'\r','\n' +#endif +}; +c_addr=newline; +u=sizeof(newline);