How do I compile to arbitrary memory and execute it in Forth? - forth

I'm interesting in testing some of the limits of Gforth and would like to have it execute arbitrary code that I "hand compile" into allocated memory. Here is my attempt.
100 cells allocate throw constant &mem
\ store at &mem: docol: . EXIT
docol: &mem !
comp' . &mem 1 cells + ! drop \ drop "execution token"
comp' EXIT &mem 2 cells + ! drop
42 \ something to print
&mem execute
Unfortunately this fails with:
in file included from *OS command line*:-1
notes/execute.fs:8: Invalid memory address
&mem >>>execute<<<
Backtrace:
$7EFC61175B28 execute
I have to use comp' instead of ', because it doesn't work for getting the xt of EXIT.
I would have thought this should work, unless Gforth doesn't operate in any way like JonesForth did where docol: starts executing the xt's next to it.
Is this possible in either Gforth or ANS forth in general?

You can execute an arbitrary list of xt, but you have to use your own word to execute this list, by applying execute to each xt from the list.
By the current standard, a standard program cannot compile arbitrary code into allocated memory. The program may only compile into the code space of the dictionary, and in the frame of the current definition (i.e., that is not yet completed). Compilation can be performed via compile, ( xt -- ) or postpone ( i*x "name" -- j*x ) words. Also the words literal, 2literal, sliteral, fliteral (or their counterparts lit,, 2lit,, slit,, flit,) can be used to compile literals.
In Gforth you can also compile into another dictionary ("section"), that can be allocated using word extra-section ( size "name" -- ).
10000 extra-section execute-in-my-section
\ execute-in-my-section ( i*x xt -- j*x )
unused cr . \ free space in the default dictionary
[:
unused cr . \ free space in the current section
:noname
postpone .
postpone ;
( xt-new )
unused cr . \ free space after compile the new definition
;] execute-in-my-section ( xt-new )
\ test
123 swap execute
See also section.fs source, and Sections paper by Anton Ertl, 2016.

Related

Skip over input stream in ATLAST forth

I'm trying to implement a kind of "conditional :" in ATLAST, the reasoning being I have a file that gets FLOADed multiple times to handle multiple steps of my program flow (I'm essentially abusing Forth as an assembler, step 1 does a first parsing for references, etc. and in step 2 the instruction words actually emit bytes).
So when declaring words for "macros" in that file, it errors out in step 2, because they were already declared in step 1, but I also can't just FORGET them, because that would forget everything that came afterwards, such as the references I just collected in step 1.
So essentially I need a ": that only runs in step 1", my idea being something like this:
VARIABLE STAGE
: ::
STAGE # 0 = IF
[COMPILE] : ( be a word declaration )
EXIT
THEN
BEGIN ( eat the disabled declaration )
' ( get the address of the next word )
['] ; ( get the address of semicolon )
= ( loop until they are equal )
UNTIL
; IMMEDIATE
:: FIVE 5 ; ( declares as expected )
FIVE . ( prints 5 )
1 STAGE ! ( up to here everything's fine )
:: FIVE 6 ; ( is supposed to do nothing, but errors out )
FIVE . ( is supposed to print 5 again )
The traced error message (starting from 1 STAGE !):
Trace: !
Trace: ::
Trace: STAGE
Trace: #
Trace: (LIT) 0
Trace: =
Trace: ?BRANCH
Trace: '
Trace: (LIT) 94721509587192
Trace: =
Trace: ?BRANCH
Trace: '
Word not specified when expected.
Trace: ;
Compiler word outside definition.
Walkback:
;
KEY ( -- ch ) as common in some other Forths for reading a single character from the input stream ( outside the :: declaration, since it's IMMEDIATE ) doesn't exist in ATLAST, the only related words I could find are:
': is supposed to read a word from the input stream, then pushes its compile address
[']: like ' but reads a word from the current line (the inside of the :: declaration)
(LIT)/(STRLIT): are supposed to read literals from the input stream according to the documentation, I could only ever make them segmentation fault, I think they're for compiler-internal use only (e.g., if the compiler encounters a number literal it will compile the (LIT) word to make it push that number onto the stack)
There aren't any WORD or PARSE either, as in some other Forths.
As you can see, ' is struggling actually getting something from the input stream for some weird reason, and it looks like ['] is failing to capture the ; which then errors out because it's suddenly encountering a ; where it doesn't belong.
I suspect it actually ran ' ['], even though it's supposed to work on the input stream, not the immediate line, and I'm clearly in compile mode there.
I did a similar thing with conditionally declaring variables, there it was rather easy to just [COMPILE] ' DROP to skip a single word (turning RES x into ' x DROP), but here I'm pretty sure I can't actually compile those instructions, because I can't emit a loop outside of a declaration. Unless there is a way to somehow compile similar code that recursively gets rid of everything until the ;.
A problem is that ' cannot find a number. A possible solution is to use a special dummy name for the definition, instead of skip it over:
: ::
STAGE # 0 = IF : EXIT THEN
' DROP \ this xt isn't needed
" : _dummy" EVALUATE ( -- n ) DROP
;
Or maybe use a new name every time:
: ::
STAGE # 0 = IF : EXIT THEN
' >NAME # \ ( s1 ) \ should be checked
": _dummy_" DUP >R S+
R> EVALUATE ( -- n ) DROP
;
But due to non standard words it might not work. Another problem is that non colon-definitions are out of the scope.
Perhaps, a better solution is a preprocessing by external means.
It appears that ATLAST is a primitive Forth, that doesn't allow you to go to a more sophisticated handling of sources. But all is not lost!
For example, a Forth implementation according to the ISO standard will handle the matter with ease with one or more of: REQUIRE [IF] [THEN] [DEFINED] SRC >IN NAME WORD FIND.
As you have a Forth, you can steal these words from another Forth and compile the code.
Another solution that may help directly is executing EXIT in interpret mode while loading a file.
You have to find out whether you can create a flag whether to abandon the input source. Then this definition might help:
: ?abandon IF S" EXIT" EVALUATE THEN ;
S" FIVE" FOUND ?abandon
Note that ?abandon must be executed in interpret mode.

fortran deallocate array but not released in OS

I have the following question:how do I deallocate array memory in type? Like a%b%c,
how do I deallocate c? the specific problem is(The compiler environment I tried are gfortran version gcc4.4.7 and ifort version 18.0.1.OS:linux):
module grist_domain_types
implicit none
public :: aaa
type bbb
real (8), allocatable :: c(:)
end type bbb
type aaa
type(bbb), allocatable :: b(:)
end type aaa
end module grist_domain_types
program main
use grist_domain_types
type(aaa) :: a
integer(4) :: time,i
time=20
allocate(a%b(1:100000000))
call sleep(time)!--------------1
do i=1,100000000
allocate(a%b(i)%c(1:1))
enddo
call sleep(time)!--------------2
do i=1,100000000
deallocate(a%b(i)%c)
enddo
call sleep(time)!--------------3
deallocate(a%b)
call sleep(time)!--------------4
end program
First,"gfortran main.F90 -o main" to compile the program, and run this program. Then I use top -p processID to see memory. When the program is executed to 1, the memory is 4.5G. When the program is executed to 2, the memory is 7.5G. When the program is executed to 3, the memory is also 7.5G(but I think is 4.5G). When the program is executed to 4, the memory is 3G(I think is 0G or close to 0G). So deallocate(a%b(i)%c) does not seem to work. However, I use valgrind to see memory. the memory of this program is all deallocate...I used ifort and gfortran. This problem happens no matter which compiler I use. How to explain this question? I allocate many c array in this way,the program will finally crash due to insufficient memory. And how to solve it?
Take a look at this post from the Intel forum. There are 2 important information in there:
(From Doctor Forran):
When you do a DEALLOCATE, the memory that was allocated returns to the pool used by the memory allocator (on Linux and OS X this is the same as C's malloc/free). The memory is not released back to the OS - it is very rare that this would even be possible. What often happens is that the pattern of allocations and deallocations causes virtual memory to be fragmented, so that while the total available space may be high, there may not be sufficient contiguous space to allocate a large item. Unlike with disks, there is no way to "defrag" memory.
(From Jim Dempsey)
See if you can deallocate the memory in the reverse order in which it was allocated. This can reduce memory fragmentation.
You may also refer to this other Intel post:
During the program run, the Fortran runtime library will manage your heap. Yes, if data is DEALLOCATED, the runtime may choose to wait to release that memory. It's an optimization - if you do another ALLOCATE with the same size it will just reuse those pages. If the heap starts to run low, it will do some collection but not until it's absolutely necessary.
Also, let me add something: Check if there aren't other objects dynamically created in scope, like automatic arrays or temporal array copies. That could be demanding memory that may be freed only when they get out of scope.
Summing up, even if 'top' says the memory is still in use, you should start to worry only if your program starts to crash or if Valgrind shows something wreid.
I modified your program ( to see where it was up to ) and ran on Windows 7 / gFortran 7.2.0. It does not demonstrate the memory retention as you report, as memory reverts to 13 mb. Contrary to my comment, memory demand did not change during initialisation of c.
module grist_domain_types
implicit none
public :: aaa
type bbb
real (8), allocatable :: c(:)
end type bbb
type aaa
type(bbb), allocatable :: b(:)
end type aaa
end module grist_domain_types
program main
use grist_domain_types
type(aaa) :: a
integer(4),parameter :: million = 1000000
integer(4) :: n = 100*million
integer(4) :: time = 5, i, pass
do pass = 1,5
write (*,*) ' go #', pass
allocate(a%b(1:n))
write (*,*) 'allocate b'
call sleep(time)!--------------1
write (*,*) ' go'
do i=1,n
allocate(a%b(i)%c(1:1))
enddo
write (*,*) 'allocate c'
call sleep(time)!--------------2
write (*,*) ' go'
do i=1,n
a%b(i)%c = real(i)
enddo
write (*,*) 'use c'
call sleep(time)!--------------2a
write (*,*) ' go'
do i=1,n
deallocate(a%b(i)%c)
enddo
write (*,*) 'deallocate c'
call sleep(time)!--------------3
write (*,*) ' go'
deallocate(a%b)
write (*,*) 'deallocate b'
call sleep(time)!--------------4
end do
write (*,*) ' done : exit ?'
read (*,*) i
end program
edit: I have given the test a repeat with do pass... to repeat the memory demands. This shows no memory leakage for this Fortran program. I use Task manager to identify memory usage, both for this program and the O/S. Your particular O/S and Fortran compiler may be different.

Is it possible to consume tick in a Forth definition?

When reading about the tick (') operator I wondered if it can be useful inside a word definition. I know that there is ['] to be used inside a definition, but I thought about using it to read the word name following invocation.
An example:
4 variable cnt
: cycle: ( arg fn -- )
'
4 cnt !
begin
cr
dup execute
-1 cnt +!
cnt # 0 = until
drop
;
I can use cycle: to repeat some word invocation, as follows.
: hello ." hello" ;
cycle: hello
Which prints hello four times, as expected.
But the following code won't define a word that prints hello four times:
: 4hello cycle: hello ;
The tick operator still expects a word from the input stream following invocation of 4hello.
Is it possible to inject it somehow when using cycle: in a word definition, so it won't "leak" outside?
Yes, it's possible. You would have to make cycle: immediate. And then also change it to postpone its actions, rather than perform them at runtime.
Postponing means to delay the actions of words. Immediate words are compiled into the current definition, and normal words are arranged to be compiled when the current definition is executing.
In this case it might look something like this.
: (cycle) 4 0 do dup execute loop drop ;
: cycle: ' postpone literal postpone (cycle) ; immediate
Note that this version no longer works outside definitions.

gforth base-execute syntax

Some online gforth docs provide a seemingly complete description of base-execute's effects:
base-execute i*x xt u – j*x gforth “base-execute”
execute xt with the content of BASE being u, and restoring the
original BASE afterwards.
But the syntax for the effects seems like a lock without a key -- the page links to nothing that describes what i*x xt u – j*x signifies. Some hunting turned up a partial description of the syntax notation, (which tells us that u is an unsigned number and xt is an execution token), but that's still not enough to understand i*x xt u – j*x.
How is base-execute used, and what does it do?
To understand what base-execute does you need to understand execute and BASE. I'll also explain how to read i*x and j*x in the stack effect.
execute works by taking an execution token xt and executing it. ' 1+ execute is the same as 1+ on its own. The reason to use execute, though, is because you can pass xt on the stack, instead of having to choose it ahead of time. For instance:
: exec-twice dup >r execute r> execute ;
2 ' 1+ exec-twice . ( this outputs 4 )
BASE is a variable that controls what numeric base to use for input and output.
BASE is initially 10. So 5 2 BASE ! . outputs 101 (which is 5 in base 2).
base-execute puts them together: it changes BASE to u, executes xt, then restores BASE to its previous value. Its implementation might look like this:
: base-execute BASE # >r BASE ! execute r> BASE ! ;
Here's an example usage:
: squared ( n1 -- n2 ) dup * ;
: squares ( n -- ) 0 do i squared . loop ;
10 squares ( 0 1 4 9 16 25 36 49 64 81 )
: hex-execute ( i*x xt -- j*x ) 16 base-execute ;
10 ' squares hex-execute ( 0 1 4 9 10 19 24 31 40 51 )
10 squares ( 0 1 ... 81 we're back to decimal )
Now for i*x xt u -- j*x:
The stack notation documentation you linked to has most of the information you need to read the effect. i*x -- j*x means that something might happen to the stack, but it doesn't specify what. In this case, the exact stack effect depends on what xt is.
To know the stack effect with a given xt, replace i*x and j*x with the two sides of xt's stack effect.
For example, if xt is ' . you would look at .'s stack effect, which is n --. In that case you could think of base-execute's stack effect as n xt-of-. u --.

New lines in word definition using interpreter directives of Gforth

I am using the interpreter directives (non ANS standard) control structures of Gforth as described in the manual section 5.13.4 Interpreter Directives. I basically want to use the loop words to create a dynamically sized word containing literals. I came up with this definition for example:
: foo
[ 10 ] [FOR]
1
[NEXT]
;
Yet this produces an Address alignment exception after the [FOR] (yes, I know you should not use a for loop in Forth at all. This is just for an easy example).
In the end it turned out that you have to write loops as one-liners in order to ensure their correct execution. So doing
: foo [ 10 [FOR] ] 1 [ [NEXT] ] ;
instead works as intended. Running see foo yields:
: foo
1 1 1 1 1 1 1 1 1 1 1 ; ok
which is exactly what I want.
Is there a way to get new lines in the word definition? The words I would like to write are way more complex, and for a presentation I would need them better formatted.
It would really be best to use an immediate word instead. For example,
: ones ( n -- ) 0 ?do 1 postpone literal loop ; immediate
: foo ( -- ten ones ) [ 10 ] ones ;
With SEE FOO resulting in the same as your example. With POSTPONE, especially with Gforth's ]] .. [[ syntax, the repeated code can be as elaborate as you like.
A multiline [FOR] would need to do four things:
Use REFILL to read in subsequent lines.
Save the read-in lines, because you'll need to evaluate them one by one to preserve line-expecting parsing behavior (such as from comments: \ ).
Stop reading in lines, and loop, when you match the terminating [NEXT].
Take care to leave >IN right after the [NEXT] so that interpretation can continue normally.
You might still run into issues with some code, like code checking SOURCE-ID.
For an example of using REFILL to parse across multiple lines, here's code from a recent posting from CLF, by Gerry:
: line, ( u1 caddr2 u2 -- u3 )
tuck here swap chars dup allot move +
;
: <text>  ( "text" -- caddr u )
here 0
begin
refill
while
bl word count s" </text>" compare
while
0 >in ! source line, bl c, 1+
repeat then
;
This collects everything between <text> and a </text> that's on its own line, as with a HERE document, while also adding spaces. To save the individual lines for [FOR] in an easy way, I'd recommend leaving 0 as a sentinel on the data stack and then drop SAVE-MEM 'd lines on top of it.

Resources