call ALSO and add ASSEMBLER wordlist if available. Add PROC ENTER
assembler snippet as needed for the architecture into the PFA. The
CFA is setup (a) with the PFA adress in traditional ITC or (b)
with an infoblock as for sbr-coded colon words.
Remember that not all architectures are support and that the
ASSEMBLER wordset is not compiled into pfe by default. Use always
the corresponding END-CODE for each CODE start. The new
word name is not smudged.
call PREVIOUS and add PROC LEAVE assembler snippet as needed
for the architecture - usually includes bits to "return from
subroutine". Remember that not all architectures are support and
PFE usually does only do variants of call-threading with a separate
loop for the inner interpreter that does "call into subroutine".
Some forth implementations do "jump into routine" and the PROC
LEAVE part would do "jump to next routine" also known as
next-threading. The sbr-call-threading is usually similar to the
native subroutine-coding of the host operating system. See CODE
close-blockfile
parse-word r/w create-file abort" failed to create block-file"
set-blockfile
dup b/buf m* blockhandle resize-file
abort" unable to create a file of that size"
empty-buffers
0 do i wipe loop
flush
win32forth uses a system-filedescriptor where -1 means unused
in the BLOCKHANDLE, but we use a "FILE*"-like structure, so NULL
means NOT-IN-USE. Here we set it.
p4_file_access(const p4_char_t *fn, int len)
: _export int
...
pfe/block-sub.c
p4_open_file(const p4_char_t *name, int len, int mode)
: _export p4_File *
...
pfe/block-sub.c
p4_create_file(const p4_char_t *name, int len, int mode)
: _export p4_File *
prepares for a following #IS_TRUE or #IS_FALSE,
does basically switch off compile-mode for the enclosed
code.
better use the ANSI style [IF][ELSE][THEN] construct.
pass the word to ENVIRONMENT?
If the word does *not* exist, the rest of the line is parsed
away with // - therefore, if the executed word does not
consume the line itself, the rest of the line is still executed.
examples:
#pragma warnings on // if warnings is a variable, ON can set it
#pragma stack-cells 50 < [if] .( not enough stackcells ) [then]
#pragma simply anything else you like to have in environment or not
implementation:
: #pragma ?exec
bl word count environment? if exit then ( interpret the rest of the line )
[compile] \ ( parse away the rest of the line as a comment )
;
EXECUTE each entry in the wordlist in the reverse order defined
but only as long as after EXECUTE of "word" a TRUE flag is left
on the stack. The wordlist execution is cut when a FALSE flag is seen.
(the current wordlist entry is _not_ on the stack!)
: DO-ALL-WORDS-WHILE-LOOP >R
0 FIRST-NAME
BEGIN ?DUP WHILE
R@ EXECUTE 0= IF R>DROP DROP EXIT THEN
DUP NAME> EXECUTE
NAME-NEXT
REPEAT R>DROP
;
EXECUTE each entry in the wordlist in the reverse order defined
but only as long as after EXECUTE of "word" a TRUE flag is left
on the stack. The wordlist execution is cut when a FALSE flag is seen.
(the current wordlist entry is _not_ on the stack!)
: DO-ALL-WORDS-WHILE '
STATE @ IF LITERAL, COMPILE DO-ALL-WORDS-WHILE-LOOP EXIT THEN
>R 0 FIRST-NAME
BEGIN ?DUP WHILE
R@ EXECUTE 0= IF R>DROP DROP EXIT THEN
DUP NAME> EXECUTE
NAME-NEXT
REPEAT R>DROP
;
to run the NEW-WORDLIST in original order, use REDO-ALL-WORDS
Compute the real part of the complex product without
computing the imaginary part. Recommended by Kahan to avoid
gratuitous overflow or underflow signals from the unnecessary
part.
Defined *only* for zero and infinite arguments. This difffers
from Kahan's CBOX [p. 198] by conserving signs when only
one of x or y is infinite, consistent with the other cases, and
with its use in his ARG [p. 199].
Compute the principal branch of the complex natural
logarithm. The angle theta is the principal argument. This
code uses Kahan's algorithm for the scaled logarithm
CLOGS(z,J) = ln(z*2^J), with J=0 and blind choices of the
threshholds T0, T1, and T2. Namely, T0 = 1/sqrt(2), T1 =
5/4, and T2 = 3;
Kahan, p. 204, including his divide by zero signal
suppression for infinite values of tan(). To quote the very
informative "=>'man math'" on our Darwin system about IEEE 754:
"Divide-by-Zero is signaled only when a function takes
exactly infinite values at finite operands."
see also HOLD for old-style forth-formatting words
and PRINTF of the C-style formatting - this word
divides the argument by BASE and add it to the
picture space - it should be used inside of <#
and #>
see also HOLD for old-style forth-formatting words
and PRINTF of the C-style formatting - this word
drops the argument and returns the picture space
buffer
see also HOLD for old-style forth-formatting words
and PRINTF of the C-style formatting - this word
does repeat the word # for a number of times, until
the argument becomes zero. Hence the result is always
null - it should be used inside of <# and #>
return the execution token of the following name. This word
is _not_ immediate and may not do what you expect in
compile-mode. See ['] and '> - note that in FIG-forth
the word of the same name had returned the PFA (not the CFA)
and was immediate/smart, so beware when porting forth-code
from FIG-forth to ANSI-forth.
create a header for a nesting word and go to compiling
mode then. This word is usually ended with ; but
the execution of the resulting colon-word can also
return with EXIT
adjust the execution-token (ie. the CFA) to point
to the parameter field (ie. the PFA) of a word.
this is not a constant operation - most words have their
parameters at "1 CELLS +" but CREATE/DOES-words have the
parameters at "2 CELLS +" and ROM/USER words go indirect
with a rom'ed offset i.e. "CELL + @ UP +"
save the value onto the return stack. The return
stack must be returned back to clean state before
an exit and you should note that the return-stack
is also touched by the DO ... WHILE loop.
Use R> to clean the stack and R@ to get the
last value put by >R
one of the rare words whose stack-change is
condition-dependet. This word will duplicate
the value only if it is not zero. The usual
place to use it is directly before a control-word
that can go to different places where we can
spare an extra DROP on the is-null-part.
This makes the code faster and often a little
easier to read.
example:
: XX BEGIN ?DUP WHILE DUP . 2/ REPEAT ; instead of
: XX BEGIN DUP WHILE DUP . 2/ REPEAT DROP ;
uses the value (being usually a dictionary-address)
and increment it to the required alignment for the
dictionary which is usually in CELLS - see also
ALIGN
make room in the dictionary - usually called after
a CREATE word like VARIABLE or VALUE
to make for an array of variables. Does not
initialize the space allocated from the dictionary-heap.
The count is in bytes - use CELLS ALLOT to allocate
a field of cells.
scale the value by the sizeof a char
- the value is then often applied to an address or
fed into ALLOT (did you expect that sizeof(p4char)
may actually yield 2 bytes?)
CONSTANT ( value 'name' -- ) [ANS] [DOES: -- value ]
pfe/core-ext.c
CREATE a new word with runtime ((CONSTANT))
so that the value placed here is returned everytime
the constant's name is used in code. See VALUE
for constant-like names that are expected to change
during execution of the program. In a ROM-able
forth the CONSTANT-value may get into a shared
ROM-area and is never copied to a RAM-address.
pushes $end and $start onto the return-stack ( >R )
and starts a control-loop that ends with LOOP or
+LOOP and may get a break-out with LEAVE . The
loop-variable can be accessed with I
does twist the last CREATE word to carry
the (DOES>) runtime. That way, using the
word will execute the code-piece following DOES>
where the pfa of the word is already on stack.
(note: FIG option will leave pfa+cell since does-rt is stored in pfa)
make a HEADER whose runtime will be changed later
using DOES>
note that ans'forth does not define and
it suggests to use CREATE directly.
... if you want to write FIG-programs in pure pfe then you have
to use CREATE: to get the FIG-like meaning of CREATE whereas
the ans-forth CREATE is the same as
check the environment for a property, usually
a condition like questioning the existance of
specified wordset, but it can also return some
implementation properties like "WORDLISTS"
(the length of the search-order) or "#LOCALS"
(the maximum number of locals)
Here it implements the environment queries as a SEARCH-WORDLIST
in a user-visible vocabulary called ENVIRONMENT
: ENVIRONMENT?
['] ENVIRONMENT >WORDLIST SEARCH-WORDLIST
IF EXECUTE TRUE ELSE FALSE THEN ;
looks into the current search-order and tries to find
the name string as the name of a word. Returns its
execution-token or the original-bstring if not found,
along with a flag-like value that is zero if nothing
could be found. Otherwise it will be 1 (a positive value)
if the word had been immediate, -1 otherwise (a negative
value).
checks the value on the stack (at run-time, not compile-time)
and if true executes the code-piece between IF and the next
ELSE or THEN . Otherwise it has compiled a branch over
to be executed if the value on stack had been null at run-time.
if compiling this will take the value from the compiling-stack
and puts in dictionary so that it will pop up again at the
run-time of the word currently in creation. This word is used
in compiling words but may also be useful in making a hard-constant
value in some code-piece like this:
: DCELLS [ 2 CELLS ] LITERAL * ; ( will save a multiplication at runtime)
(in most configurations this word is statesmart and it will do nothing
in interpret-mode. See LITERAL, for a non-immediate variant)
resolves a previous DO thereby compiling ((LOOP)) which
does increment/decrement the index-value and branch back if
the end-value of the loop has not been reached.
will compile the following word at the run-time of the
current-word which is a compiling-word. The point is that
POSTPONE takes care of the fact that word may be
an IMMEDIATE-word that flags for a compiling word, so it
must be executed (and not pushed directly) to compile
sth. later. Choose this word in favour of COMPILE
(for non-immediate words) and [COMPILE] (for immediate
words)
this will throw and lead back to the outer-interpreter.
traditionally, the outer-interpreter is called QUIT
in forth itself where the first part of the QUIT-word
had been to clean the stacks (and some other variables)
and then turn to an endless loop containing QUERY
and EVALUATE (otherwise known as INTERPRET )
- in pfe it is defined as a THROW ,
get back a value from the return-stack that had been saved
there using >R . This is the traditional form of a local
var space that could be accessed with R@ later. If you
need more local variables you should have a look at LOCALS|
which does grab some space from the return-stack too, but names
them the way you like.
fetch the (upper-most) value from the return-stack that had
been saved there using >R - This is the traditional form of a local
var space. If you need more local variables you should have a
look at LOCALS| , see also >R and R> . Without LOCALS-EXT
there are useful words like 2R@R'@R"@R!
when creating a colon word the name of the currently-created
word is smudged, so that you can redefine a previous word
of the same name simply by using its name. Sometimes however
one wants to recurse into the current definition instead of
calling the older defintion. The RECURSE word does it
exactly this.
traditionally the following code had been in use:
: GREAT-WORD [ UNSMUDGE ] DUP . 1- ?DUP IF GREAT-WORD THEN ;
now use
: GREAT-WORD DUP . 1- ?DUP IF RECURSE THEN ;
rotates the three uppermost values on the stack,
the other direction would be with -ROT - please
have a look at LOCALS| and VAR that can avoid
its use.
if compiling then place the string into the currently
compiled word and on execution the string pops up
again as a double-cell value yielding the string's address
and length. To be most portable this is the word to be
best being used. Compare with C" and non-portable "
the current point of interpret can be gotten through SOURCE.
The buffer may flag out TIB or BLK or a FILE and IN gives
you the offset therein. Traditionally, if the current SOURCE
buffer is used up, REFILL is called that asks for another
input-line or input-block. This scheme would have made it
impossible to stretch an [IF] ... [THEN] over different blocks,
unless [IF] does call REFILL
print n space to stdout, actually a loop over n calling SPACE ,
but the implemenation may take advantage of printing chunks of
spaces to speed up the operation.
drop the DO .. LOOP runtime variables from the return-stack,
usually used just in before an EXIT call. Using this multiple
times can unnest multiple nested loops.
CREATE a new variable, so that everytime the variable is
name, the address is returned for using with @ and => !
- be aware that in FIG-forth VARIABLE did take an argument
being the initial value. ANSI-forth does different here.
middle part of a BEGIN .. WHILE .. REPEAT
control-loop - if cond is true the code-piece up to REPEAT
is executed which will then jump back to BEGIN - and if
the cond is null then WHILE will branch to right after
the REPEAT
(compare with UNTIL that forms a BEGIN .. UNTIL loop)
read the next SOURCE section (thereby moving >IN ) up
to the point reaching $delimiter-char - the text is placed
at HERE - where you will find a counted string. You may
want to use PARSE instead.
leave compiling mode - often used inside of a colon-definition
to make fetch some very constant value and place it into the
currently compiled colon-defintion with => , or LITERAL
- the corresponding unleave word is ]
in compile-mode, get the (ascii-)value of the first charachter
in the following word and compile it as a literal so that it
will pop up on execution again. See CHAR and forth-83 ASCII
print the message to the screen while reading a file. This works
too while compiling, so you can whatch the interpretation/compilation
to go on. Some Forth-implementations won't even accept a => ." message"
outside compile-mode while the (current) pfe does.
returns a logical-value saying if the value was not-zero.
This is most useful in turning a numerical value into a
boolean value that can be fed into bitwise words like
AND and XOR - a simple IF or WHILE doesn't
need it actually.
fetch a double-cell value from the return-stack, that had been
previously been put there with 2>R - see R@ for single value.
This can partly be a two-cell LOCALS| value, without LOCALS-EXT
there are alos other useful words like 2R!R'@R"@
start a colon nested-word but do not use CREATE - so no name
is given to the colon-definition that follows. When the definition
is finished at the corresponding ; the start-address (ie.
the execution token) can be found on the outer cs.stack that may
be stored used elsewhere then.
start a control-loop just like DO - but don't execute
atleast once. Instead jump over the code-piece if the loop's
variables are not in a range to allow any loop.
in compiling mode place the following string in the current
word and return the address of the counted string on execution.
(in exec-mode use a POCKET and leave the bstring-address of it),
see S" string" and the non-portable " string"
place the execution-token on stack into the dictionary - in
traditional forth this is not even the least different than
a simple => , but in call-threaded code there's a big
difference - so COMPILE, is the portable one. Unlike
COMPILE , [COMPILE] and POSTPONE this word does
not need the xt to have actually a name, see :NONAME
ends a CASE construct that may surround multiple sections of
OF ... ENDOF code-portions. The ENDCASE has to resolve the
branches that are necessary at each ENDOF to point to right after
ENDCASE
create a named marker that you can use to FORGET ,
running the created word will reset the dict/order variables
to the state at the creation of this name.
: MARKER PARSE-WORD (MARKER) ;
see also ANEW which is not defined in ans-forth but which uses
the MARKER functionality in the way it should have been defined.
compare the case-value placed lately with the comp-value
being available since CASE - if they are equal run the
following code-portion up to ENDOF after which the
case-construct ends at the next ENDCASE
parse a piece of input (not much unlike WORD) and place
it into the given buffer. The difference with word is
also that WORD would first skip any delim-char while
PARSE does not and thus may yield that one. In a newer
version, PARSE will not copy but just return the word-span
being seen in the input-buffer - therefore a transient space.
the ANS'94 standard describes this word in a comment
under PARSE, section A.6.2.2008 - quote:
Skip leading spaces and parse name delimited by a space. c-addr
is the address within the input buffer and u is the length of the
selected string. If the parse area is empty, the resulting string
has a zero length.
If both PARSE and PARSE-WORD are present, the need for WORD
is largely eliminated. Note that Forth200x calls it PARSE-NAME
and clarifies that non-empty whitespace-only input is returned as
a zero length string as well.
try to get a new input line from the SOURCE and set
>IN accordingly. Return a flag if sucessful, which is
always true if the current input comes from a
terminal and which is always false if the current input
comes from EVALUATE - and may be either if the
input comes from a file
VALUE ( value 'name' -- ) [HIDDEN] [DOES: -- value ]
pfe/core-ext.c
CREATE a word and initialize it with value. Using it
later will push the value back onto the stack. Compare with
VARIABLE and CONSTANT - look also for LOCALS| and
VAR
while compiling the next word will be place in the currently
defined word no matter if that word is immediate (like IF )
- compare with COMPILE and POSTPONE
or perhaps ( [string<">] -- string-ptr string-len )
This is the non-portable word which is why the ANSI-committee
on forth has created the two other words, namely S" and C" ,
since each implementation (and in pfe configurable) uses another
runtime behaviour. FIG-forth did return bstring which is the configure
default for pfe.
show a lisence info - the basic PFE system is licensed under the terms
of the LGPL (Lesser GNU Public License) - binary modules loaded into
the system and hooking into the system may carry another LICENSE
show a warranty info - the basic PFE system is licensed under the terms
of the LGPL (Lesser GNU Public License) - which exludes almost any
liabilities whatsoever - however loadable binary modules may hook into
the system and their functionality may have different WARRANTY infos.
create a named marker that you can use to FORGET ,
running the created word will reset the dict/order variables
to the state at the creation of this name.
: (MARKER) (CREATE) HERE ,
GET-ORDER DUP , 0 DO ?DUP IF , THEN LOOP 0 ,
...
DOES> DUP @ (FORGET)
...
;
creates a MARKER if it doesn't exist,
or forgets everything after it if it does. (it just gets executed).
Note: in PFE the ANEW will always work on the ENVIRONMENT-WORDLIST
which has a reason: it is never quite sure whether the same
DEFINITIONS wordlist is in the search ORDER that the original
ANEWMARKER was defined in. Therefore, ANEW would be only safe
on systems that do always stick to FORTHDEFINITIONS. Instead
we will CREATE the ANEWMARKER in the ENVIRONMENT and use a
simple SEARCH-WORDLIST on the ENVIRONMENT-WORDLIST upon re-run.
\ old
: ANEW BL WORD DUP FIND NIP IF EXECUTE THEN (MARKER) ;
\ new
: ANEW
PARSE-WORD 2DUP ENVIRONMENT-WORDLIST SEARCH-WORDLIST IF EXECUTE THEN
GET-CURRENT >R ENVIRONMENT-WORDLIST SET-CURRENT (MARKER) R> SET-CURRENT ;
copy stringbuffer into a field as a zero-terminated filename-string,
a shell-homedir like "~username" will be expanded, and the
platform-specific dir-delimiter is converted in on the fly ('/' vs. '\\')
p4_pocket_filename(const p4_char_t* src, int n)
: _export P4_GCC_MALLOC char*
Divides *ud by denom, leaves result in *ud, returns remainder.
For number output conversion: dividing by BASE.
p4_u_d_mul(p4udcell *ud, p4ucell w, p4ucell c)
: _export void
_ud*_
pfe/core-sub.c
Computes *ud * w + c, where w is actually only half of a cell in size.
Leaves result in *ud.
For number input conversion: multiply by BASE and add digit.
p4_dig2num(p4_char_t c, p4ucell *n, p4ucell base)
: _export int
_dig>num_ ( c n* base -- ?ok )
pfe/core-sub.c
Get value of digit c into *n, return flag: valid digit.
type counted string to terminal, if it does not fit in full on
the current line, emit a CR before
(output adjusting the OUT variable, see _type_ and _outs_ )
: _typeline_ out @ over + cols @ > if cr then _type_ ;
type a string of chars by repeating a single character which
is usually a space, see SPACES
(output adjusting the OUT variable, see _type_ and _outs_ )
: _emits_ swap 0 do dup _putc_ loop drop _flush_ _?xy_ drop out ! ;
complement _word:parse_ to arrive at the normal WORD implementation
will also ensure the string is zero-terminated - this makes a lot of
operations easier since most forth function can receive a string-span
directly but some need a string-copy and that is usually because it has
to be passed down into a C-defined function with zerotermined string. Just
use p4_HERE+1 (which is also the returnvalue of the p4_word_to_here function!) to have
the start of the zero-terminated string. Note that the p4_word_to_here function may throw
with P4_ON_PARSE_OVER if the string is too long (it has set *DP=0 to
ensure again that THROW will report PFE.word. as the offending string)
this word will place an debug-runtime into
the CFA of the following word. If the
word gets executed later, the user will
be prompted and can decide to single-step
the given word. The debug-stepper is
interactive and should be self-explanatory.
(use NO-DEBUG to turn it off again)
the only-vocabulary is special. Calling it will erase
the search ORDER of vocabularies and only allows
to name some very basic vocabularies. Even ALSO
is not available.
example:
ONLY FORTH ALSO EXTENSIONS ALSO DEFINITIONS
request a slot index. The index is written to the variable arg-address.
if the arg-address contains a value != 0, we check if that specific
slot index is free for assignment - or already assigned to this variable.
a slot_use can be done for the same slot-variable multiple times,
which will increase a use-counter. Call slot_unuse correspondingly.
dlmap the shared object (or share an already mapped object)
and run the per-thread initialization code. This is the
user-convenient function, otherwise use (LOADM)
simulate:
: LOADM BL WORD
((IS_MODULE_LOADED)) IF EXIT THEN
HERE (LOADM) 0= IF ." -- load failed: " HERE COUNT TYPE CR THEN ;
result is the numeric equivalent of d. If the double number was
greater than what could fit into a single cell number, the
modulo cellsize will be left since the higher-significant bits
are just DROPed
take the value from stack (or cs-stack) and compile a runtime-code and
the value as for LITERAL ... this word is never state-smart, it
is not immediate, and has therefore no complications with POSTPONE
(compare also with COMPILE, to make a call-stub with an exectoken)
take the double-value from stack (or cs-stack) and compile a runtime-code
and the value as for 2LITERAL ... this word is never state-smart, it
is not immediate, and has therefore no complications with POSTPONE
(compare also with COMPILE, to make a call-stub with an exectoken)
(M!) is the same as Wil Baden's PLACE, except it assumes
the buffer address msa to be aligned, and stores the ANS
Forth string a.s as a measured string, zero-filled to
trailing alignment. As with PLACE, it is assumed that the
mstring copy does not clobber the old string, and there is no
check for room starting at msa. "parens-m-store"
Parse the input stream up to the first occurrence of char,
which is parsed away. If executing in compilation mode,
append run-time semantics to the current definition that
leaves the ANS Forth string representation on the stack. In
interpretation mode, leave the ANS Forth string
representation for a stored copy, which may be transient in
the style of S". In either mode, the format of the
stored string is implementation dependent.
"parse-to-s"
NOTE: The interpreted copy is a nontransient in this
implementation, and both copies are mstrings.
ALLOT room and store the ANS Forth string into aligned data
space as an mstring, leaving data space zero-filled to
alignment; and leave the length and new body address. It is
assumed that len is unsigned. An error is thrown if len is
larger than the system parameter MAX_DATA_STR.
"m-comma-s"
NOTE: MAX_DATA_STR is returned by
S" /SCOPY" ENVIRONMENT?
NOTE: M,S differs from STRING, in Wil Baden's Tool
Belt in that it stores an aligned, measured string with
zero-filled alignment instead of a counted string, and it
leaves the ANS Forth string representation of the stored
string.
Set all string variables holding bound string values in string
space to the empty string, and clear string space, including
the string buffer, string stack, and string stack frames.
"zero-strings"
NOTE: If used for under the hood development, this word must
be executed only when string space is in a valid state.
Fetch the dstring garbage collection "off" state. Intended
for saving the off state for later restoration after a usage
of $GC-ON or $GC-OFF.
"string-g-c-lock-fetch"
Set the dstring garbage collection "off" state according to
flag. Intended for restoring the off state previously
fetched by $GC-LOCK@.
"string-g-c-lock-fetch"
If string space is not marked as containing garbage, return
false. If there is garbage, throw an error when garbage
collection is disabled. Otherwise remove the garbage and
return true. Garbage collection is "transparent", so the
user would not normally use this word.
"collect-string-garbage"
Allocate and initialize a string space with size bytes
available for the string buffer including the string stack,
and with a string frame stack for frame description entries
holding up to #frames. The size is rounded up to cell
alignment, and the buffer begins and ends with cell alignment.
Return addr, the address of the string space. The standard
word FREE with addr as input can be used to release the space.
"make-string-space"
Store the string MSA on the string stack in the variable
whose DFA is on the parameter stack.
"string-store"
NOTES: The only situation in which $! copies the string
value is when it is a bound string already stored in another
variable. In that case, the new copy is the one that is
stored in the variable. In particular, external strings are
not copied.
If the string value held by the string variable on entry is a
bound string that is also referenced deeper on the string
stack, its back link is reset to point to the deepest string
stack reference. If it is a bound string not deeper on the
string stack and not identical to the input string, its back
link is set to zero, making it garbage. If it is an external
string, its MSA in the variable is simply written over by
that popped from the string stack.
Parse ccc delimited by " (double quote) and store it in data
space as an mstring. If interpreting, leave the MSA on the
string stack. If compiling, append run-time semantics to the
current definition that leaves the MSA on the string stack.
A program should not alter the stored string. An error is
thrown if the quoted string length is larger than the system
parameter MAX_DATA_STR (see SM,).
"string-quote"
NOTE: In contrast to S", the string stored by $" when
interpreting is not transient.
Create an ordinary Forth variable and initialize it to the
address of a fixed, external, measured representation of the
empty string, such as that pushed onto the string stack by
EMPTY$. "string-variable""
Parse the input stream up to the first occurrence of char,
which is parsed away, and store the string as an external
measured string. If executing in compilation mode, append
run-time semantics to the current definition that leaves the
MSA on the string stack. In interpretation mode, leave the
MSA on the string stack, where the stored copy, unlike
PARSE>S, is required to be nontransient.
Copy the u-th string stack entry to the top of the string
stack. The string value is not copied. Throw an error if
the input string stack does not have at least u+1 items.
"string-pick"
Exchange the two most accessible strings on the string stack.
Throw an error if there are less than two strings on the
stack. Neither string value is copied.
"string-swap"
($: maxth$ ... minth$ ... -- minth$ ... maxth$ ... )
Exchange the ith and jth strings on the string stack, where
the top is the 0th. Throw an error if there are not at least
max[i,j] + 1 strings on the stack. Neither string value is
copied.
"string-exchange"
Drop a$ from the string stack and leave it as a ANS Forth
string a.s, without copying.
"string-s-from"
WARNING: If a$ is a bound string, it may move or disappear
at the next garbage collection, making a.s invalid. This can
be avoided by sandwiching sections of code where this could
occur between $GC-OFF and $GC-ON.
Drop a$ from the string stack, copy it into data space as a
measured string, and leave it as an ANS Forth string a.s.
An error is thrown if the string length is larger than the
system parameter MAX_DATA_STR (see M,S).
"string-comma-s"
Leave the string stack unchanged, and leave the string body
address and length on the data stack.
"string-s-fetch"
WARNING: If a$ is a bound string, it may move at the next
garbage collection, making a.s invalid. This can be avoided
by sandwiching sections of code where this could occur
between $GC-OFF and $GC-ON.
Push the external ANS Forth string a.s onto the string
stack, without copying the string value into the string
buffer. It is an unchecked error if the Forth string a.s
is not stored as an external measured string.
"to-string-s"
WARNING: If the string value of a.s is actually in the
string buffer and not external, the push operation may
generate a garbage collection that invalidates its MSA.
Copy the external string value whose body address and count
are on the parameter stack into the string buffer and push it
onto the string stack. Errors are thrown if the count is
larger than MAX_MCOUNT, if there is not enough room in string
space, even after garbage collection, or if there is an
unterminated string concatenation. The input external string
need not exist as a measured string.
"to-string-s-copy"
NOTE: MAX_MCOUNT is the largest size the count field of a
measured string can hold, e.g., 255, 64K-1, or 4,096M-1. It
is returned by:
S" /DYNAMIC-STRING" ENVIRONMENT?
WARNING: This word should not be used when the input string
is a bound string because the copy operation may generate a
garbage collection which invalidates its MSA.
If a$ is the empty string, drop it and do nothing else.
In particular, do not start a new concatenation, which would
lock string space against new nonconcatenating copies.
Otherwise append the string body to the end of the string
currently being concatenated as the last string in the string
buffer, and update its count field. If there is no
concatenating string, start one. An error is thrown if the
size of the combined string would be larger than
MAX_MCOUNT or if there is not enough room in string space
even after a garbage collection.
If garbage collection occurs, a$ remains valid even when
it is in the string buffer.
When there is a concatenating string, concatenation is the
only basic string operation that can copy a string into the
string buffer. "string-plus"
Parse the input stream up to the first occurrence of char,
which is parsed away. If executing in compilation mode,
append run-time semantics to the current definition that
concatenates the characters parsed from the string.
Otherwise concatenate the characters.
"parse-s-plus"
If there is no concatenating string, do nothing but leave the
empty string. If there is, leave it as a string bound to the
top of the string stack, and terminate concatenation,
permitting normal copies into the string buffer.
"end-cat"
This word is immediate. In compilation mode it appends
run-time semantics to the current definition that
concatenates the quoted string according to the specification
for $+. In interpretation mode it concatenates the
string. An error is thrown if the length of the quoted
string is longer than the system parameter MAX_DATA_STR
(see M,S). "string-plus-quote"
Copy the argument strings across lines to the string buffer,
push them onto the string stack with "argN" the most
accessible, and make them into the top compile-time string
stack frame. Compile the run-time code to make an argument
frame out of the N most accessible run-time string stack
entries. Inform the system text interpreter that it should
compile run-time code for any white-space delimited argument
encountered in the text of the definition, that concatenates
the corresponding string in the run-time frame. At the
semicolon terminating the definition, drop the compile-time
argument frame and compile code to drop the run-time argument
frame.
The code between $ARGS{ ... } and the terminating
semicolon is not allowed to make a net change in the string
stack depth, because that would interfere with the automatic
dropping of the string argument frame at the semicolon.
"string-args-brace"
Syntax for defining a string macro GEORGE:
: george ($: a$ b$ c$ -- cat$ )
$ARGS{ arg1 arg2 arg3 }
cat" This is arg1: " arg1 cat" ." ENDCAT $. ;
The blank following the last argument is required. For a
macro with no arguments, $ARGS{ } does nothing but add
useless overhead and should be omitted. Two of the
arguments in this example are ignored and could have been
left out. Note that ENDCAT would not be legal in this
word without something like $. to remove the concatenated
string from the string stack before the terminating
semicolon. It is normal to use an $ARGS{ } word as a step
in a concatenation that is terminated elsewhere.
Sample syntax using the string macro george:
$" bill" $" sue" $" marie" george $.
The resulting display is:
This is arg1: bill.
NOTE: Macro argument labels must be distinct from each other
and from any local labels that appear in the same definition,
and there is no check for that.
NOTE: At the moment the semantics of $ARGS{ is undefined
before DOES>.
Push the description of a string stack frame starting at the
top of the string stack and containing u entries onto the
string frame stack. Errors are thrown if the frame stack
would overflow or if the depth of the string stack above the
top frame, if there is one, is less than u. The value u = 0
is allowed. "string-frame"
NOTE: This implementation pushes u and the string stack
pointer onto the frame stack.
Drop the topmost string frame from the string frame stack,
and the corresponding strings, frame*$, from the string
stack. An error is thrown if either stack would underflow.
The cases where the frame has zero entries on the string
stack and/or there are zero or more items on the string stack
above the top frame item are handled properly.
"drop-string-frame"
Leave true and its index u in the top string frame if the
ANS Forth string matches an element of the frame, else leave
false. The index of the top frame element is zero.
"find-string-arg"
Leave the u-th string in the topmost string frame, where the
index u of the top element is zero. Throw an error if the
frame stack is empty or if the top frame contains less than
u+1 strings. "th-string-arg"
Cleanup code for the end of a definition that uses
$ARGS{. ;-semicolon should be overloaded to compile
it automatically if dynamic string arguments were in use.
"paren-drop-string-frame-paren"
Abort if the string stack would underflow when popped.
Otherwise pop the top of the string stack and push it onto
the data stack.
If the string is in the current string space and initially
bound to the top of the string stack, mark it as garbage by
setting its back link to NULL and set the garbage flag.
This word violates the rule that only ANS Forth strings
should appear on the data stack, and so is under the hood.
"string-pop"
Pop an external mstring address from the data stack and push
it onto the string stack after checking for room, invoking
garbage collection if necessary. Not to be used with a
dynamic string because a garbage collection can invalidate
its address.
This word violates the normal rule that only ANS Forth
strings should appear on the data stack, and so is under the
hood.
"string-push-ext"
Clear the string buffer, string stack, and string frame stack
in the string space starting at space.addr. Any string
variables holding strings in the string buffer are left
pointing into limbo. This may be executed with the string
space in an invalid state, as long as the /$BUF and
MAX-#$FRAMES fields of its string space structure are
intact. "zero-string-space"
NOTE: This word does not zero fill the string buffer.
init and execute the previously allocated forth-maschine,
e.g. pthread_create(&thread_id,0,p4_Exec,threadP);
The following words have been extracted from a big boot init
procedure previously existing in PFE. In the boot_system we
do initialize all inputs/outputs and load the wordset extensions
and the boot-preinit-block or boot-preinit-script. After that,
we run script_files to init the application code, and finally
the application is started - and if no APPLICATION was set then
we do the fallback to the forth interactive INTERPRET loop. The
latter is the usual case, use BYE to exit that inifinite loop.
When the mainloop returns, we run the cleanup-routines. They are
registered seperatly so they can be run asynchronously - if the
application has broken down or it blocks hard on some hardware
then we can still run cleanup code in a new forthish context.
the filename argument is loaded via INCLUDED as
an extension package to the current system. The filename
is registered in the current ENVIRONMENT so that it is
only INCLUDED once (!!) if called multiple times via
REQUIRED or REQUIRES
check the environment for a property, usually
a condition like questioning the existance of
specified wordset, but it can also return some
implementation properties like "WORDLISTS"
(the length of the search-order) or "#LOCALS"
(the maximum number of locals)
Here it implements the environment queries as a SEARCH-WORDLIST
in a user-visible vocabulary called ENVIRONMENT
: ENVIRONMENT?
['] ENVIRONMENT >WORDLIST SEARCH-WORDLIST
IF EXECUTE TRUE ELSE FALSE THEN ;
special extension: a search for CORE will also find a definition
of CORE-EXT or CORE-EXT-EXT or CORE-EXT-EXT-EXT - it just has to
be below the ansi-standard maximum length of 31 chars.
if a name like "dstrings-ext" is given, and no such entry
can be found, then envQ will try to trigger a (LOADM) of
that module, in the hope that this implicit-load does in fact
define the answer. Use with care, it's a very new feature.
A self-parsing variant of an environment-query check. It is similar
to a simulation like
: NEEDS PARSE-WORD 2DUP ENVIRONMENT?
IF DROP ( extra value ) 2DROP ( success - be silent )
ELSE TYPE ." not available " CR THEN ;
however that would only match those worset-envqueries which return a
single extra item under the uppermost TRUE flag in the success case.
Instead it works more like
: NEEDS PARSE-WORD 2DUP ENVIRONMENT-WORDLIST SEARCH-WORDLIST
IF 2DROP ( success - be silent and just drop the parsed word )
ELSE TYPE ." not available " CR THEN ;
however we add the same extension as in ENVIRONMENT? as that
it can automatically load a wordset module to fullfil a query
that looks like "[wordsetname]-ext". Therefore, the following
two lines are pretty much identical:
LOADM floating
NEEDS floating-ext
the difference between the two: if somebody did provide a forth
level implementation of floating-ext then that implementation might
have registered a hint "floating-ext" in the environment-wordlist.
This extra-hint will inhibit loading of the binary module even if
it exists and not been loaded so far. The LOADM however will
not check the ENVIRONMENT-WORDLIST and only check its loadlist
of binary wordset modules in the system.
It is therefore recommended to use NEEDS instead of LOADM
unless you know you want the binary module, quickly and uncondtionally.
execute the given execution-token and catch
any exception that can be caught therein.
software can arbitrarily raise an exception
using THROW - the value 0 means there
was no exception, other denote implementation
dependent exception-codes.
raise an exception - it will adjust the depth
of all stacks and start interpreting at the point
of the latest CATCH
if n is null nothing happens, the -1 (ie. FALSE )
is the raise-code of ABORT - the other codes
are implementation dependent and will result in
something quite like ABORT
move the cursor position to the given row and column
of the screen. If the output device is not a terminal
this will have no effect but can still send an
escape sequence.
return clock(2) - the number of clocks of this proces.
To get the number of seconds, divide by CLOCKS_PER_SEC a.k.a. CLK_TCK
as represented in the ENVIROMENT for a hosted forth system.
Remember that the process clock will wrap around at some point,
therefore only use difference values between two clock reads.
check the named file - if it exists
the status errno code is zero. The status subcode
is implementation-specific and usually matches the
file access permission bits of the filesystem.
The word F>S was sometimes defined with a different behavior
than FTRUNC>S which is the type-cast behaviour of C according
to C99 section 6.3.1.4 - truncation would also match the ANS-Forth
specification for F>D.
Some systems used F>S defined to FROUND>S instead. The pfe
provides explicit words for both conversions, the word FROUND>S
and FTRUNC>S which return single-cell parameters for a floating
point number with the conversion method of FTRUNC or FROUND.
In PFE, F>S is a synonym pointing to FTRUNC>S in analogy
of the behavior of F>D where no explicit word exists. The
inverse of F>S is the cast conversion of S>F.
compile the next word. The next word should not be immediate,
in which case you would have to use [COMPILE]. For this
reason, you should use the word POSTPONE, which takes care
it.
create a vocabulary of that name. If the named vocabulary
is called later, it will run ((VOCABULARY)) , thereby
putting it into the current search order.
Special pfe-extensions are accessible via
CASE-SENSITIVE-VOC and SEARCH-ALSO-VOC
does increase BLK and refills the input-buffer
from there. Does hence break interpretation of the
current BLK and starts with the next. Old-style
forth mechanism. You should use INCLUDE
depracated: use NTOHS which does the same as this word when
the local byte-order seems to have no match, and be otherwise
a no-op. Note that only the two lower bytes of the top-of-cell
are swapped.
depracated: this word has not been very useful lately. It does
still stem from times of 16bit forth systems that wanted to
interchange data blocks. It is better to use functionality
based on NTOHS or NTOHL. Note that this word >MOVE<
does swap each 2byte. It is not useful for byte-swapping
WCHAR strings as the count is given in bytes, not wchar items.
converts a pointer to the code-field (CFA) to point
then to the corresponding link-field (LFA) - in some configurations
this can be a very slow operation since the system might need to walk
through all header-words in the system, looking for a >NAME that
has the cfa and *then* returning the "N>LINK" result here - which might
be none at all if the word is a :NONAME. Use always >NAME and
treat this word as non-portable just like any assumption about the
contents of the >LINK-field.
Only in fig-mode and for traditional fig-mode programs, this word may
possibly have enough extra assertions to be somewhat reliable.
(and fig-mode did not know about SYNONYMs - see note at LINK>).
trying to convert a pointer to the parameter-field (PFA) to point
then to the corresponding code-field (CFA) - note that this is not
necessarily the inverse of >BODY instead it is a fast implementation
assuming a VARIABLE thing had been used. Every use of "BODY>" is
warned in the logfile.
converts a pointer to the link-field (LFA) to point
then to the corresponding code-field (CFA)
BEWARE: this one does not care about SYNONYMs and it is the
only way to get at the data of a SYNONYM. Therefore, if you have
a synonym called A for an old word B then there is a different
result using "NAME>" on an A-nfa or using "N>LINK LINK>" since the
first "NAME>" will return the xt of B while the latter will return
the xt of A - but executing an xt of A is an error and it will THROW
this difference is intentional to allow knowledgable persons to
do weird things looking around in the dictionary. The forth standard
words will not give you much of a chance to get hold of the nfa of
a SYNONYM word anyway - asking FIND for a word A will return
the execution token of B immediatly and "NAME>" on that one lead to
the nfa of B and not that of A.
converts a pointer to the link-field (LFA) to point
then to the corresponding name-field (CFA) - this one is one of
the slowest operation available. One should always use the inverse
operation N>LINK and cache an older value if that is needed.
Some words might be linked but they do not have a name-field (just
the other fields) but this word can not detect that and will try to look
into the bits of the dictionary anway in the assumption that there is
something - and if done in the wrong place it might even segfault.
Only in fig-mode and for traditional fig-mode programs, this word may
possibly have enough extra assertions to be somewhat reliable.
(and fig-mode did not know about SYNONYMs - see note at LINK>).
implementation-specific configure-dependent fig-only simulation:
: L>NAME BEGIN DUP C@ 128 AND 0= WHILE 1- REPEAT ;
converts a pointer to the name-field (NFA) to point
then to the corresponding link-field (LFA) - this operation
is quicker than the inverse L>NAME. This word is a specific
implementation detail and should not be used by normal users - instead
use always NAME> which is much more portable. Many systems may
possibly not even have a >LINK-field in the sense that a @ on
this adress will lead to another >NAME. Any operation on the
resulting >LINK-adress is even dependent on the current configuration
of PFE - only in fig-mode you are asserted to have the classic detail.
(and fig-mode did not know about SYNONYMs - see note at LINK>).
converts a pointer to the name-field (NFA) to point
then to the corresponding flag-field (FFA) - in traditinal
Forth this is the same address. pfe _can_ do different.
converts a pointer to the flag-field (FFA) to point
then to the corresponding name-field (NFA) - in traditinal
Forth this is the same address. pfe _can_ do different.
convert a name-token into a string-span, used to detect the
name for a word and print it. The word ID. can be defined as
: ID. NAME>STRING TYPE ;
the implementation of NAME>STRING depends on the header layout
that is defined during the configuration of the forth system.
: NAME>STRING COUNT 31 AND ; ( for fig-like names )
: NAME>STRING COUNT ; ( default, name is a simple counted string )
: NAME>STRING @ ZCOUNT ; ( name-token is a pointer to a C-level string )
: NAME>STRING COUNT 31 AND ( hybrid of fig-like and zero-terminated )
DUP 31 = IF DROP 1+ ZCOUNT THEN
;
: NAME>STRING HEAD:: COUNT CODE:: PAD PLACE PAD ; ( different i86 segments )
the FIG definition toggles the SMUDGE bit, and not all systems have
a smudge bit - instead one should use REVEAL or HIDE
: SMUDGE LAST @ >FFA SMUDGE-MASK TOGGLE ;
: SMUDGE LAST @ NAME-FLAGS@ SMUDGE-MASK XOR LAST @ NAME-FLAGS! ;
: HIDE LAST @ NAME-FLAGS@ SMUDGE-MASK OR LAST @ NAME-FLAGS! ;
set the nfa-flags of nfa given. Note that in the fig-style the nfa-flags
would include the nfa-count in the lower bits - therefore this should only
set bits that had been previously retrieved with NAME-FLAGS@
: IMMEDIATE LAST @ NAME-FLAGS@ IMMEDIATE-MASK OR LAST @ NAME-FLAGS! ;
set a DEFER word
(in pfe: set the DOES-field - which is the BODY-field in ans-mode
and therefore the same as TO / in fig-mode the DOES-field is
one cell higher up than for a CREATE:VARIABLE
Use IS freely on each DOES-words in both modes).
: IS '
STATE @ IF LITERAL, POSTPONE >DOES-BODY POSTPONE !
ELSE >DOES-BODY ! THEN
; IMMEDIATE
get the BEHAVIOR of a DEFER word when executed. If being
compiled then the ACTION-OF will be the value of [word] at the
time of execution and not that of compilation time (non-constant).
In PFE it does actually pick whatever is stored in the DOES-field
of a word and therefore ACTION-OF may applied to all DOES-words.
get the execution token xt2 that would be executed by the DEFER
identified by xt1.
This command is used to obtain the execution contents of a deferred
word. A typical use would be to retrieve and save the execution
behavior of the deferred word, set the deferred word to a new behavior,
and then later restore the old behavior.
If the deferred word identified by _xt1_ is associated with some
other deferred word, _xt2_ is the execution token of that other
deferred word. To retrieve the execution token of the word currently
associated with that other deferred word, use the phrase DEFER@ DEFER@ .
Experience:
BEHAVIOR was used many years in OpenBoot and OpenFirmware systems.
In PFE it is the inverse of an IS operation and it will never fail
if applied to a word with atleast a body. That's just like IS can
be applied to almost every DOES> word where DEFER@ will get
the value back.
make an name-alias for a word - this is very different from a DEFER
since a DEFER will resolve at runtime. Changing the target of a
DEFER via IS will result in changing the BEHAVIOR of all
words defined earlier and containing the name of the DEFER.
A SYNONYM however does not have any data field (theoretically not
even an execution token), instead it gets resolved at compile time.
In theory, you can try to FIND the name of the SYNONYM but as
soon as you apply NAME> the execution token of the end-point is
returned. This has also the effect that using the inverse >NAME
operation will result in the name-token of the other name.
SYNONYM CREATE <BUILDS ( like it is in ANS Forth )
: FOO CREATE DOES> @ ;
SEE FOO
: foo <builds
does> @ ;
SYNONYM CREATE CREATE:
: BAR CREATE 10 ALLOT ;
SEE BAR
: bar create: 10 allot ;
an internal function that will check a word name
to have any deprecation attribution - some words have
a (one time) message to be shown to the user, while
OBSOLETED-SYNONYM will show a message and rebuild
itself as a normal SYNONYM. - Note that most deprecations
are only shown once and that they are not emitted when
having REDEFINED-MSG OFF.
compile a pointer to an extern (loader) z-string
to the dictionary and on execution show a deprecation
message once. Note: the new name is smudged+immediate,
so it you can not FIND it right after compilation.
see also (DEPRECATED: name message) for the real thing
compile a pointer to an extern (loader) z-string
to the dictionary and on execution show a logging
message once. Note: this name is NOT smudged+immediate.
see also (DEPRECATED: name message) for
deprecation messages
open terminal logfile named by the string-buffer
all further output to the terminal window is also logged into
this file. This is especially useful in embedded environments
where the terminal connection is often not used or it is
directed to a different location that does not easily allow to
redirect the forth output to a file for further examination.
send terminal-output as a data-message to the specified link sap.
Unlike TERMINAL-OUTPUT-LINK the data-messages are in line-mode.
The flushed characters are buffered until a non-printable character
is seen. This is somewhat more useful when treating pfe as a print
service and testing machine, but can not provide for interactivity.
60 TERMINAL-ANSWER-LINK !
...
TERMINAL-ANSWER-LINK OFF
send terminal-output as a data-message to the specified link sap.
This can be used in an embedded systems for a terminal session simulation.
setting zero-sap will disable sending message-frames (the zero sap is
therefore not usable for output-to-link). The startup default is zero.
60 TERMINAL-OUTPUT-LINK !
...
TERMINAL-OUTPUT-LINK OFF
let the forth stdin-handling look for data-messages on this link too.
These will be interpreted like messages that come from the interactive
forth terminal. This can be used in an embedded systems for a terminal
session simulation. setting zero-sap will disable interpreting these
incoming data-frames as keyboard-strings (so that the zero sap is
therefore not usable for an input-link!). The startup default is zero.
60 TERMINAL-INPUT-LINK !
...
TERMINAL-INPUT-LINK OFF
returns the address of the emulations state variable so it can be
read and explicitly changed to another value from forth text. This is
a very questionable thing to do as the emulation-state is actually
an enumerated value, the ESE will just show question-marks setting
this variable to something not understood.
this word is used to create compiling words that can
declare LOCALS| - it shall not be used directly
to declare a local, the pfe provides LVALUE for
that a purpose beyond LOCALS|
create local identifiers to be used in the current definition.
At runtime, each identifier will be assigned a value from
the parameter stack.
The identifiers may be treated as if being a VALUE , it does
also implement the ansi TO extensions for locals. Note that
the identifiers are only valid inside the currently compiled
word, the SEE decompiled word will show them as
... a.s.o.
see also LVALUE
declares a single local VALUE using (LOCAL) - a
sequence of LVALUE declarations can replace a
LOCALS| argument, ie. LOCALS| a b c |
is the same as LVALUE a LVALUE b LVALUE c .
This should also clarify the runtime stack behaviour of
LOCALS| where the stack parameters seem to be
assigned in reverse order as opposed to their textual
identifier declarations.
compare with VALUE and the pfe's convenience word
VAR.
: LVALUE
STATE @ IF
VALUE
ELSE
BL WORD COUNT DUP (LOCAL) (TO)
THEN
; IMMEDIATE
declares a single local VALUE using (LOCAL) - which
will hold the address of an area like BUFFER: but carved
from the return-stack (as in C with alloca). This local buffer
will be automatically given up at the end of the word. The
return-stack-pointer will be increased only at the time of
the p4_local_buffer_var function (and the address assigned to the LVALUE)
so that the provided size gets determined at runtime. Note
that in some configurations the forth-return-stack area is
quite small - for large string operations you should consider
to use a POCKET-PAD in pfe.
: LBUFFER:
STATE @ IF
BUFFER:
ELSE
:NONAME ( size -- rp* ) R> RP@ - DUP RP! SWAP >R ;NONAME
COMPILE, POSTPONE LVALUE
THEN
; IMMEDIATE
BEWARE: helper function, make sure to save LEM context and setup the
pfe/main-k12.c
forth's REGTH (if it uses a cpu register for that).
the p4_emu_sendme_command function will create an eventbuffer that will land
in the term-k12 getevent loop - it will work as if the
the string has been magically typed on the terminal. It
can be used to send a string from LEM-context (during a
config-request) to the PFE-context (in its getevent loop).
The string will be implicitly terminated with a CR to start
execution in the engine's interpret_loop.
Note: the old pfe version of UNDER+ is obsolete as it is in conflict
with a comus word of the same name. The behavior of this word will
continue to exist under the name of (UNDER+). Users are encouraged
to use the comus behavior of UNDER+ which does already exist under
the name of +UNDER. In the future pfe will be changed to pick up
the comus behavior making UNDER+ and +UNDER to be synonyms. In the
current version there will be load-time warning on usages of "UNDER+".
The p4_pocket_pad function Returns the next pocket.
A pocket has usually the size of a maxstring, see ENVIRONMENT /STRING
(but can be configured to be different, mostly when MAXPATH > /STRING )
Note that a pocket is a temporary and forth internal functions do
sometimes call POCKET-PAD too, especially when building filenames
and getting a literal (but temporary) string from the keyboard.
Functions are not expected to hold references to this transient
area any longer than building a name and calling another word with it.
Usage of a pocket pad is a good way to make local temporary buffers
superfluous that are only used to construct a temporary string that
usually gets swallowed by another function.
depracated code:
create temp-buffer 255 allot
: make-temp ( str buf )
temp-buffer place " .tmp" count temp-buffer append
temp-buffer count make-file ;
replace with this:
: make-temp ( str buf )
pocket-pad >r
r place " .tmp" count r append
r> count make-file
;
will load the help module in the background and hand over the
parsed name to (HELP) to be resolved. If no (HELP) word
can be loaded, nothing will happen.
will load the edit module in the background and look for a word
called EDIT-BLOCK that could be used to edit the blockfile.
If no EDIT-BLOCKFILE word can be loaded, nothing will happen.
Otherwise, OPEN-BLOCKFILE is called followed by 0EDIT-BLOCK
to start editing the file at the first block.
this creates a name with the VARIABLE runtime.
Note that this is the FIG-implemenation of CREATE whereas in
ANS-Forth mode we have a CREATE identical to FIG-style
store the value into the next-under value in the returnstack.
used to interpret the returnstack to hold two LOCALS| values.
see R'@ for inverse operation
fetch the second-under value from the returnstack.
used to interpret the returnstack to hold three LOCALS| values.
see R"! for inverse operation ( R'@R@ / 2R@ / R>DROP )
store the value into the second-under value in the returnstack.
used to interpret the returnstack to hold three LOCALS| values.
see R"@ for inverse operation
shortcut (e.g. in CSI-Forth)
note that the access to R is configuration dependent - only in
a traditional fig-forth each NEST will be one cell wide - in case that
there are no LOCALS| of course. And remember, the word above reads
like the sequence R> and DROP but that is not quite true.
: R>DROP R> DROP ; ( is bad - correct might be ) : R>DROP R> R> DROP >R ;
create a new WORDLIST with the given name. It
will also have an implicit hidden vocabulary just as
well and all DEFINITIONS will go into that
hidden wordlist. Therefore the old CURRENT is
memorized on the cs-stack.
effectivly, CONTEXT[1] will have the wordlist-id
of the public wordlist "name" and CONTEXT[0] will
have the hidden wordlist contained in "name" - the
hidden wordlist will always be known as HIDDEN' so
that it can be re-referenced without need to use
ALSO just to access a single definition from
just another vocabulary. Note that HIDDEN' is
defined immediate (a VOCABULARY' ) to modify
the ORDER inside a colon definition.
: MODULE
CURRENT @ ( -- old-current )
VOCABULARY
ALSO LATEST NAME> EXECUTE ALSO DEFINITIONS
C" HIDDEN'" $CREATE WORDLIST CONTEXT !
;
the named word in the hidden dictionary (i.e.
the wordlist referenced in CURRENT) is exported
into the public wordlist of it (i.e. which is in
this implementation CONTEXT[1]). The actual
implemenation will create a DEFER-word in the
public wordlist withits parameter area pointing
to the cfa of the hidden implementation.
: EXPORT
CURRENT @ CONTEXT CELL+ @ CURRENT !
DEFER CURRENT !
LATEST COUNT CURRENT @ SEARCH-WORDLIST
IF LATEST NAME> >BODY ! ELSE ABORT" can't find word to export" THEN
;
affects the search order, ALSO module-wid CONTEXT ! hidden'
: EXPOSE-MODULE
ALSO S" HIDDEN'"
' DUP VOC? ABORT?" is no vocabulary" >VOC
SEARCH-WORDLIST 0= IF " no hidden vocabulary found" THEN
DUP VOC? ABORT?" hidden is no vocabulary" EXECUTE
;
Print a list of WORDS in the NVRAM buffer. Try to show also the
current value, atleast for NVRAM numbers and strings. Words can be
added or changed with the help of NVRAM,SET or NVRAM,USE
Values in the NVRAM buffer will survive a COLD reboot, in many
hosted environments however the NVRAM will be lost on program exit.
if current host-encoding is bigendian, this is a NOOP
otherwise byteswap the lower 16-bit bits of the topofstack.
see W@ and W!
(on some platforms, the upper bits are erased, on others not)
if current host-encoding is bigendian, this is a NOOP
otherwise byteswap the lower 32-bit bits of the topofstack.
see L@ and L! (being usually just @ and ! )
(on some platforms, the upper bits are erased, on others not)
a DUP on the search ORDER - each named vocabulary
replaces the topmost ORDER vocabulary. Using ALSO
will make it fixed to the search-order. (but it is
not nailed in trap-conditions as if using DEFAULT-ORDER )
suppose that the left side is a tracked stack line during compiling
and the right side is a candidate changer input stack. Test whethr
the candidate does match and the complete changer would be allowed
to run a rewrite in the track stack buffer.
Possible conditions include:
the left side has not enough arguments or...
any argument on the right side has a type specialization
that does not match as a valid suffix to their counterpart
on the left side.
suppose that the left side is a tracked stack line during compiling
and the right side is a candidate changer input stack. Assume the
righthand candidate does match - look at the given argument on the
left side and show the prefix being copied to the output trackstack
when the rewrite-rule is gettin applied later.
check whether this stackhelp does match on current rewrite-buffer
and in the given input match show us the argument but only the
good prefix i.e. the type constraint being cut off already.
match a stackdef (single variant of stacks).
assume: single variant in rewrite-buffer and
single variant in stackdef-arg and
only one changer in arg-stackhelp
and find a matching stackhelp entry in the stackhelp-wordlist.
We do check for a matching XT to allow for multiple words with
the same name. If this find-routine is too specific then try
again with a direct search.
add a checkstack notation for the LAST word or just try to
match the given notation with the stacklayout traced so
far - possibly casting a few types as needed.
call it after p4_stackhelp_rewrite : it does consume any
pfe/stackhelp-ext.c
stackhelp infos that ought to be executed to be a check.
This applies also to exitpoints! - no argument as it does
work on the CHK.line internal buffer
this word does almost the same as LITERAL - it takes
an S" string as specified in the CS-STACK at compile
time and compiles into the current definition where it is
returned as if there were a direct string-literal. This
can be used to compute a string-literal at compile-time
and hardwire it.
create a field - the workhorse for both STRUCT and STRUCTURE
implementations. The created fieldname is an OFFSET:-word
that memorizes the current offset in its PFA and will add
that offset on runtime. This forth-word does *not* align.
VARIANT ( outer-offset "name" -- outer-offset here zero-offset )
pfe/struct-ext.c
Variant records describe an alternative view of the
current record or subrecord from the start to the current point.
The variant need not be of the same length, but the larger is taken
makes room for a pointer in the dictionary to
be resolved through RESOLVE> and does therefore
memorize that cell's address on the CS-STACK
Mostly used after BRANCH or => ?BRANCH in compiling
words like IF or ELSE
create a catch-domain around the token to be executed. This works
the same as CATCH. Additionally all terminal output of that word
is being captured to the buffer being provided as an argument. The
maximum length input argument is modified flagging the actual length
of captured output stream as the output argument. Note that in most
cases a POCKET-PAD is just not big enough, atleast many error
condition notifications tend to be quite lengthy for byte counted
forth strings.
returns the cursor position on screen, on a real unix system
this includes a special call to the screen driver, in remote
systems this can be the expected position as seen on the
client side's terminal driver.
If the input ekey value was not an extended key
then flag is set to FALSE and the value is left
unchanged. Compare to EKEY>CHAR for the inverse.
If the input eky was an extended key then the value
will be modified such that shifted values are transposed
to their base EKEY plus K-SHIFT-MASK - therefore the
K-SHIFT-MASK is only apropriate for the result fkey-code
values of the p4_ekey_to_fkey function.
Search the dictionary for _name_. If _name_ is found,
return TRUE; otherwise return FALSE. Immediate for use in
definitions.
[DEFINED] word ( -- nfa|0 ) immediate
does check for the word using find (so it does not throw like ' )
and puts it on stack. As it is immediate it does work in compile-mode
too, so it places its argument in the cs-stack then. This is most
useful with a directly following [IF] clause, so that sth. like
an [IFDEF] word can be simulated through [DEFINED] word [IF]
Get the next word in the input stream as a hex
single-number literal. (Adopted from Open Firmware.)
: H# ( "hexnumber" -- n ) \ Simplified for easy porting.
0 0 BL WORD COUNT
BASE @ >R HEX >NUMBER R> BASE !
ABORT" Not Hex " 2DROP ( n)
STATE @ IF POSTPONE LITERAL THEN
; IMMEDIATE
print the stack content in vertical nice format.
tries to show cell-stack and float-stack side-by-side,
Depending on configuration,
there are two parameter stacks: for integers and for
floating point operations. If both stacks are empty, .S
will display the message <stacks empty>.
If only the floating point stack is empty, .S displays
the integer stack items in one column, one item per line,
both in hex and in decimal like this (the first item is topmost):
12345 HEX 67890 .S
424080 [00067890]
12345 [00003039] ok
If both stacks ar not empty, => .S displays both stacks, in two
columns, one item per line
HEX 123456.78E90 ok
DECIMAL 123456.78E90 .S
291 [00000123] 1.234568E+95
1164414608 [45678E90] ok
Confusing example? Remember that floating point input only works
when the BASE number is DECIMAL. The first number looks like
a floating point but it is a goodhex double integer too - the number
base is HEX. Thus it is accepted as a hex number. Second try
with a decimal base will input the floating point number.
If only the integer stack is empty, => .S shows two columns, but
he first columns is called <stack empty>, and the
second column is the floating point stack, topmost item first.
decompile word - tries to show it in re-compilable form.
(SEE) tries to display the word as a reasonable indented
source text. If you defined your own control structures or
use extended control-flow patterns, the indentation may be
suboptimal.
pick a value in the compilation-stack - note that the compilation
stack _can_ be seperate in some forth-implemenations. In PFE
the parameter-stack is used in a double-cell fashion, so CS-PICK
would 2PICK a DP-mark and a COMP-magic, see PICK
roll a value in the compilation-stack - note that the compilation
stack _can_ be seperate in some forth-implemenations. In PFE
the parameter-stack is used in a double-cell fashion, so CS-ROLL
would 2ROLL a DP-mark and a COMP-magic, see ROLL
check the condition in the CS-STACK. If true let the following
text flow into INTERPRET , otherwise eat up everything upto
and including the next [ELSE] or [THEN] . In case of
skipping, count nested [IF] ... [THEN] constructs.
this word provides a simple pre-compiler mechanism
CREATE a new name and put PFA adress into the CFA place.
NOTE: this description (PFA into CFA) is only correct for traditional
indirect threaded code (ITC). The other variants use a block info
in the CFA - there we will start a normal colon word which is cut
off immediately by a ;CODE directive to enter the machine-level.
BE AWARE:
The TOOLS-EXT will not provide an END-CODE or any other word in the
ASSEMBLER wordlist which is required to start any useful assembler
programming. After requiring ASSEMBLER-EXT you will see a second "CODE"
in the EXTENSIONS wordlist that will also provide an optimized execution
than the result of this standard-forth implemenation.
Does end the latest word (being usually some DOES> part) and enters
machine-level (in EXEC-mode).
BE AWARE:
The TOOLS-EXT will not provide an END-CODE or any other word in the
ASSEMBLER wordlist which is required to start any useful assembler
programming. After requiring ASSEMBLER-EXT you will see a second ";CODE"
in the EXTENSIONS wordlist that will also provide an optimized execution
than the result of this standard-forth implemenation.
The Standard-Forth implementation will actually compile a derivate of
BRANCH into the dictionary followed by ;. The compiled word
will not jump to the target adress (following the execution token)
but it will call the target adress via the host C stack. The target
machine level word (C domain) will just return here for being
returned (Forth domain). Hence END-CODE may be a simple RET, comma!
call PREVIOUS and add PROC LEAVE assembler snippet as needed
for the architecture - usually includes bits to "return from
subroutine". Remember that not all architectures are support and
PFE usually does only do variants of call-threading with a separate
loop for the inner interpreter that does "call into subroutine".
Some forth implementations do "jump into routine" and the PROC
LEAVE part would do "jump to next routine" also known as
next-threading. The sbr-call-threading is usually similar to the
native subroutine-coding of the host operating system. See CODE
The VLIST command had been present in FIG and other forth
implementations. It has to list all accessible words. In PFE
it list all words in the search order. Well, the point is,
that we do really just look into the search order and are
then calling WORDS on that Wordl. That way you can see
all accessible words in the order they might be found.
Uses => ?CR
the upper limit of the forth writeable memory space,
the variable DICTLIMIT must be below this line.
stack-space and other space-areas are often allocated
above DICTLIMIT upto this constant.
DICTFENCE is the lower end of the writeable dictionary
the lower limit of the forth writeable memory space,
the variable DICTFENCE must be above this line.
Some code-areas are often moved in between DICTFENCE and
this constant. To guard normal Forth code from deletion
the usual practice goes with the FENCE variable
DICTLIMIT is the upper end of the writeable dictionary
takes the execution token of the following word and
saves it on the compile-stack. The correspondig closing
) will then feed it into >COMPILE - so this pair
of word provides you with a prefix-operation syntax
that you may have been seen in lisp-like languages.
just like the standard sprintf() function in C, but
the format is a counted string and accepts %#s to
be the format-symbol for a forth-counted string.
The result is a zeroterminated string at dest$ having
a length being returned. To create a forth-counted
string, you could use:
variable A 256 ALLOT
15 " example" " the %#s value is %i" A 1+ SPRINTF A C!
A COUNT TYPE
loads a file just like INCLUDE but does also put
a MARKER in the LOADED dictionary that you can
do a FORGET on to kill everything being loaded
from that file.
look for the filename created by LOADF that had been
defining the given name. LOADF has created a marker
that is above the INCLUDED file and that
marker has a body-value just below the
INCLUDED file. Hence the symbol was defined during
LOADF execution of that file.
For the code piece between MAKE and ;AND , this word
will do just an EXIT . For the code outside of
the MAKE construct a branch-around must be resolved then.
make a seperated piece of code between MAKE and ;AND
and on execution of the MAKE the named word is twisted
to point to this piece of code. The word is usually
a DOER but the current implementation works
on DEFER just as well, just as it does on other words who
expect to find an execution-token in its PFA. You could even
create a colon-word that starts with NOOP and can then make
that colon-word be prefixed with the execution of the code piece.
This MAKE
does even work on LOCALS| and VAR but it is uncertain
what that is good for.
create a new offsetword. The word is created and upon execution
it adds the offset, ie. compiling the OFFSET-RT runtime:
( address -- address+offset )
This word is just a convenience word, just use the word +FIELD
directly and choose a DROP to flag the end of a current
offset-field declaration series. See also /FIELD series to
declare simple structures which end with a final CONSTANT to
memorize the complete size. The /FIELD style is more traditional.
created a new name with an OFFSET-RT runtime using the given offset.
Leave the offset-value untouched, so it can be modified with words
like CHAR+ and CELL+ and SFLOAT+ ; This word is the simplest way
to declared structure access words in forth - the two STRUCT modules
contain a more elaborate series of words. Use this one like:
0 ( a fresh definition is started )
+FIELD: zapp.a+ CHAR+ ( zero offset from the base of the struct )
+FIELD: zapp.b+ CELL+ ( no alignment, starts off at 1 from base )
+FIELD: zapp+ DROP ( store size of complete zap structure )
0 zapp+ ( extend the zap structure )
+FIELD: zappx.c+ CELL+ ( a new field )
+FIELD: zappx+ DROP ( and save it again )
CREATE zapp1 0 zapp+ ALLOT ( a way to allocate a strucutre )
zapp2 zapp.b+ @ ( read a value from the field )
16 zapp2 zapp.b+ ! ( store a value in there )
this form is not the traditional form used in forth, it is however
quite simple. Use the simplefield declaration with /FIELD to
be compatible with traditional styles that build on top of sizeof
constants in forth (which are not part of the ANS Forth standard).
created a new +FIELD name with an OFFSET-RT
of offset. Then add the size value to the offset so that
the next /FIELD declaration will start at the end of the
field currently declared. This word is the simplest way to
declared structure access words in forth - the two STRUCT modules
contain a more elaborate series of words. This one is used like:
0 ( a fresh definition is started )
/CHAR /FIELD ->zapp.a ( zero offset from the base of the struct )
/CELL /FIELD ->zapp.b ( no alignment, starts off at 1 from base )
CONSTANT /zapp ( store size of complete zap structure )
/zapp ( extend the zap structure )
/CELL /FIELD ->zappx.c ( a new field )
CONSTANT /zappx ( and save it again )
CREATE zapp1 /zapp ALLOT ( a way to allocate a strucutre )
/zapp BUFFER: zapp2 ( another way to do it, semi-standard )
zapp2 ->zapp.b @ ( read a value from the field )
16 zapp2 ->zapp.b ! ( store a value in there )
compare also with /CHAR/WCHAR/CELL/DCELL
and use +FIELD as the lowlevel word, can simulate as
executes 0= but this word is immediate so that it does
affect the cs-stack while compiling rather than compiling
anything. This is useful just before words like [IF] to
provide semantics of an [IFNOT]. It is most useful in
conjunction with "=> [DEFINED] word" as it the sequence
"[DEFINED] word [NOT] [IF]" can simulate "[IFNOTDEF] word"
will handle the body of the named word as a sequence of cells (or tokens)
and replaces the n'th occurences of from-xt into to-xt. A negative value
will change all occurences. A zero value will not change any.
EVALUATE-WITH ( i*x addr len xt[i*x--j*x] -- j*x )
pfe/useful-ext.c
added to be visible on the forth command line on request by MLG,
he has explained the usage before a lot, you can get an idea from:
: EVALUATE ['] INTERPRET EVALUATE-WITH ;
The word is used internally in PFE for the loadlist evaluation of
the binary modules: where previously each loadercode had its own
CREATE-execution we do now call the original forthish CREATE-word
like, so bootstrapping a VARIABLE will now call VARIABLE itself
and of course we need to set up the TIB-area to point to the name
of the variable that shall be created in the forth dictionary:
: LOAD-WORD ( arg-value str-ptr str-len loader-code -- )
CASE
#LOAD-VARIABLE OF ['] VARIABLE EVALUATE-WITH ENDOF
....
ENDCASE
CLEARSTACK
;
where the first wordlist to be searched via the search order are
[ANS] and [FIG] and FORTH (in this order) and which may or may not
yield different flavours of the FIND routine (i.e. different XTs)
GET-CONTEXT and count how many times it is in the order but
the CONTEXT variable itself. The returned number is therefore
minus one the occurences in the complete search-order.
usage:
ALSO EXTENSIONS CONTEXT? [IF] PREVIOUS [THEN]
ALSO DEF' DEFAULT-ORDER
: CONTEXT?
0 LVALUE _count
GET-ORDER 1- SWAP LVALUE _context
0 ?DO _context = IF 1 +TO _count THEN LOOP
_count
;
accesses CURRENT which is generally the last wordlist that the
DEFINITIONS shall go in. sets there a flag in the vocabulary-definition
so that words are matched case-sensitive.
binds CONTEXT with CURRENT. If the CURRENTVOCABULARY is in
the search-order (later), then the CONTEXT vocabulary will
be searched also. If the result of this word could lead into
a recursive lookup with FIND it will throw CURRENT_DELETED
and leave the CURRENTVOCABULARY unaltered.
change the runtime-code of (NEST)
to call a special word that prints info
to the screen whenever a colon word is
entered. It will print the name and
the current stack, and results in a kind
of execution trace over SPY' :-colon nested
words.
create a header for a nesting word and go to compiling
mode then. This word is usually ended with ; but
the execution of the resulting colon-word can also
return with EXIT
this is the spy-version SPY_ON
does fetch the value from the PFA of the named item, which
may be about everything, including a VARIABLE , VALUELVALUE , LOCALS| , VAR , DEFER , DOER , DOES>
and more.
will return the parameter-field address of the following word.
Unlike others, this word will also return the address of
LOCALS| and local LVALUE - so in fact a TO A and
INTO A ! are the same. This word is most useful when calling
C-exported function with a temporary local-VAR as a return-place
argument - so the address of a local has to be given as an arg.
Beware that you should not try to save the address anywhere else,
since a local's address does always depend of the RP-depth -
EXIT from a colon-word and the value may soon get overwritten.
(see also TO )
a FIG-compatible WORD. Where ANSI says "skip leading delimiters"
this one acts as "skip leading whitespace". And it will not return
anything and have the string parsed to HERE
scan the input to the next doublequote and create a buffer
that holds the chars - return the address of that zero-terminated
string-buffer, either POCKET-PAD or ALLOTed into the dictionary.
Add the string defined by CADDR LEN to the zero terminated string
at ZDEST - (for older scripts the SYNONYM named APPENDZ exists)
(see libc strncat(3)) / compare with ZPLACE / +PLACE
scan the following text to create a literal just
like C" does, but backslashes can be used to
escape special chars. The rules for the backslashes
follow C literals, implemented techniques are
\n \r \b \a \f \v \e \777
and all non-alnum chars represent themselves, esp.
\" \' \ \? \! \% \( \) \[ \] \{ \} etcetera.
most importantly the doublequote itself can be escaped.
but be also informed that the usage of \' and \" is not
portable as some systems preferred to map [\'] into ["].
Here I use the experimental addition to map [\q] to ["] and [\i] to [']
scan the following text to create a literal just
like S" does, but backslashes can be used to
escape special chars. The rules for the backslashes
follow C literals, implemented techniques are
\n \r \b \a \f \v \e \777
and all non-alnum chars represent themselves, esp.
\" \' \ \? \! \% \( \) \[ \] \{ \} etcetera.
most importantly the doublequote itself can be escaped.
but be also informed that the usage of \' and \" is not
portable as some systems preferred to map [\'] into ["].
Here I use the experimental addition to map [\q] to ["] and [\i] to [']
scan the following text to create a literal just
like Z" does, but backslashes can be used to
escape special chars. The rules for the backslashes
follow C literals, implemented techniques are
\n \r \b \a \f \v \e \777
and all non-alnum chars represent themselves, esp.
\" \' \ \? \! \% \( \) \[ \] \{ \} etcetera.
most importantly the doublequote itself can be escaped
but be also informed that the usage of \' and \" is not
portable as some systems preferred to map [\'] into ["].
Here I use the experimental addition to map [\q] to ["] and [\i] to [']