"Insufficient virtual memory" error for allocating small arrays - fortran

I have been using Fortran for a few months now, but I am self-taught and have only been learning it by reading someone else's codes so my knowledge of Fortran is very limited. I wrote this function which is meant to read a text file containing data and save these data in an array. Since I don't know the size of the data, I choose to allocate the array within the function.
FUNCTION RSEBIN(NAMEIN,NZNSEB)
IMPLICIT DOUBLE PRECISION (A-H, O-Z)
INTEGER DSEBTP, IIND, NZNSEB
CHARACTER(LEN=75) :: FILNAM
CHARACTER NAMEIN*(*)
REAL, ALLOCATABLE :: RSEBIN(:,:)
WRITE (FILNAM,1500) 'Extra_InputFiles/SEB_inputs/SEB_', NAMEIN,
2 '.txt' !Define the path and name of the input data text file
1500 FORMAT (A32,A,A4)
OPEN (UNIT=101, FILE=FILNAM, STATUS='OLD')
READ(101,*) !Skip the header
DSEBTP = 0
DO
READ(101,*,IOSTAT=IO) TRASH
IF (IO.NE.0) EXIT !Exit the loop when last line has been reached
DSEBTP = DSEBTP + 1 !Counts how many time periods inputs are set for the input data type
END DO
REWIND(101) !Rewind text file to read the inputs
ALLOCATE(RSEBIN(DSEBTP,NZNSEB+1)) !Allocate the input data array
READ(101,*) !Skip the header
DO 1510 ISEBTP=1,DSEBTP
READ(101,*) (RSEBIN(ISEBTP,IIND), IIND=1, NZNSEB+1) !Save the data in the main array
1510 CONTINUE
CLOSE (UNIT=101)
RETURN
END FUNCTION
I then use this function in another subroutine with this following statement:
ASEBAT = RSEBIN('AirTemperature',NZNSEB) !Allocate the air temperature array (first column is time)
When I try to run the program, I get a "Insufficient virtual memory" error. After a quick search, I discovered that this error usually occurs when one is allocating huge arrays. However, during my tests, I was only using a 3 X 5 array. After a few more tests, I realized that the function works fine if I declare the dimensions of my array RSEBIN rather than making it allocatable and allocating it in the function. However, this solution is not sustainable for me as I want this function to be able to read text files of various dimensions.
Does anyone have an idea why I have such error? Should I avoid allocating arrays in a function? As I said previously, I am fairly new to Fortran and I am pretty sure my code has many issues, so I apologize for my primitive code writing and would be grateful for any tip.
Also, I should note that I'm using the Intel Fortran Compiler from oneAPI for Windows. I recently switched from the fortran compiler in Intel XE, with which, if I can recall, I was using a similar function without any issue.
Thanks!

Related

Gestion of memory in the modular structure of a Fortran 95 program with heavy computations and variables

I am currently "optimizing" a scientific modelling program developed in Fortran 95. This program is basically making heavy computations in 3D to solve some equations, in addition numerous variable have to be saved and used ~ 50 tables with sizes likes (50; 50; 10000), I even have some 5D tables with sizes like (6;6;15;15;10000) to save in order to reduce the computation time.
I developed a perfectly working version of this code using a python3 interface to control my runs. Basically python is calling a fortran module containing my code to obtain all the results from my modelling. The problem with this method is that I cannot parallelize my code in some time consuming regions. Moreover, I would benefit from the computational time advantage of Fortran for a post treatment of the models that is now partially done in python due to interface.
In the first part of my optimization campaign for this code I want to add a control of the runs with Fortran. A program would call the module containing my code to obtain all the necessary and heavy variables. The Python interface would still be presented, the switch between the Fortran and python control run being done in the compilation in the Makefile directly, this Makefile is already done, everything is compiling well and the python interface is still perfectly working.
My troubles are concerning the Fortran control program and its gestion of the allocated memory I assume. As the size of my tables are not known in advance and requires to open some files I have to declare all my variable as ALLOCATABLE. I then allocate them with the correct sizes before calling my module containing my code. When calling my code errors related to memory problems are appearing, with the error message "Program received signal SIGSEV: Segmentation fault - invalid memory reference". This error appears when I'm setting a table to 0d0, if I'm reducing the size/precision of my modelling the program can proceed a bit further before crashing hence the memory related problem. I think that I'm doing something not correct in the utilisation of the variables between my control and my modelling module. Maybe some variables are stored in the wrong memory space, I precise that I'm using gfortran on ubuntu 22.04.1.
I have different possibilities to try to solve this issue using derived types and pointers or simply by breaking my modelling module. Before going into these heavy structural modifications I wanted to know if someone has experience an equivalent problem and what were the solutions.
Here is a schema of the structure of my code:
Run program:
program run_model
use coordinates
use file
use mathematical
use modelling_module
implicit none
integer :: n_x, n_y, n_z
real(8),dimension(:), ALLOCATABLE:: x,y,z
+ all other output variables in 3D
.
.
.
Some operations and file opening
ALLOCATE(x(n_x),y(n_y),z(n_z))
+ all other variables
CALL modelling(n_x, n_y, n_z, output variables)
end program run_model
Modelling module in a separated file:
module modelling_module
use coordinates
use file
use mathematical
implicit none
private
public :: modelling
contains
subroutine modelling(n_x, n_y, n_z, output variables)
integer, intent(in):: n_x, n_y, n_z,
real(8),dimension(n_x), intent(out):: x
real(8),dimension(n_y), intent(out):: y
real(8),dimension(n_z), intent(out):: z
+ all output variables
Computation of the model
.
.
.
end subroutine modelling
end module modelling_module
Thank you in advance for your answers !

Fortran how to write non-zero elements

I am trying to debug a huge program not written by me by writing out a large selection of the variables into text files. Some are arrays and some are single values.
The arrays were declared with huge initial sizes due to the code being incomplete and people didn't want to use the allocation method as no one knew how many more things would be added to the code. As a result, if I just straight up print out the entire variable, it would also print out the millions of zeros which I don't need and make the file much larger than necessary.
I searched for a way to write out non-zero elements and another post here had answers pointing to the pack() function.
However, pack() seems to have a size limit since visual studio would not even go into the lines that actually calls pack - visual studio would enter chkstk.asm upon entering the subroutine that writes the variables and return a stack overflow error before executing any of the lines inside the subroutine (the first few lines in the subroutine are just opening file and writing non-array variables).
So, what else can I do to write out all the non-zero elements inside these huge arrays?
The beginning of the subroutine is shown below:
subroutine write_everything(fileIDa,fileNamea,fileIDb,fileNameb)
use flags
use const
use mphase_props_v
use sample_props_v
use grain_props_v
use mphase_state_v
use grain_state_v
use mphase_rate_v
use grain_rate_v
use sample_state_v
use sample_rate_v
use twinning_v
use hard_law1_v
use back_stress_v
use phase_transf_v
use bc_v
use diffract_v
use output_v
use YS_v
use epsc_var
integer, intent(in) :: fileIDa,fileIDb
character(len=40), intent(in) :: fileNamea,fileNameb
1 format(1h,78('*'))
open(unit=fileIDa,file=fileNamea,status='unknown')
write(fileIDa,'(''flags'')')
write(fileIDa,1)
write(fileIDa,*) ishape,irot,ipileup,kSM,iPoleFigFlag,i_diff_dir
# ,iDiag,kCL,iSingleCry,iTwinLaw,i_prev_proc,iDetwOpt,iDtwMfp
# ,ilatBS,iBackStress,iPhTr,itwinning,iOutput,itexskip,nCoatedPh
# ,nCoatingPh,ivarBC,inonSch
write(fileIDa,'(''mphase_props_v'')')
write(fileIDa,1)
write(fileIDa,*) pack(nsm,nsm.ne.0),pack(itw,itw.ne.0)
# ,pack(nmodes,nmodes.ne.0),pack(nsys,nsys.ne.0)
# ,pack(nslmod,nslmod.ne.0),pack(nslsys,nslsys.ne.0)
# ,pack(ntwmod,ntwmod.ne.0),pack(ntwsys,ntwsys.ne.0)
# ,pack(nphngr,nphngr.ne.0),pack(icrysym,icrysym.ne.0)
# ,pack(ISECTW,ISECTW.ne.0),pack(ngrnph,ngrnph.ne.0)
Some of the array is of size 10, but some others are size 10000 and even 50 by 10000.
Note before I used pack the program writes the variables just fine, except the file is too large (780 MB) that neither Microsoft word nor notepad++ would open them and I need the compare functions from these programs so I can't just open them with regular notepad. I stopped short of splitting them into two files and decided to try to remove all the zeros.
Following the suggestions from the comments, I set heap array to 0 and although visual studio still goes into chkstk.asm it no longer returns error and pack() writes out non-zero elements just fine.

Intel Fortran error "allocatable array or pointer is not allocated"

When I tried to run a huge Fortran code (the code is compiled using Intel compiler version 13.1.3.192), it gave me error message like this:
...
Info[FDFI_Setup]: HPDF code version number is 1.00246
forrtl: severe (153): allocatable array or pointer is not allocated
Image PC Routine Line Source
arts 0000000002AD96BE Unknown Unknown Unknown
arts 0000000002AD8156 Unknown Unknown Unknown
arts 0000000002A87532 Unknown Unknown Unknown
...
Nonetheless, if I insert a small write statement (which is just to check the code, not to disturb the original purpose of the code) in one of the subroutines as the following (I couldn't put all the codes since they are too huge):
...
endif
call GetInputLine(Unit,line,eof,err)
enddo
if(err) return
! - [elfsummer] 20140815 Checkpoint 23
open(unit = 1, file = '/bin/monitor/log_checkpoint',status='old',position='append')
write(1,*) "BEFORE checking required keys: so far so good!"
close(1)
! check required keys
! for modes = 2,3, P and T are the required keys
if(StrmDat%ModeCI==2.or.StrmDat%ModeCI==3) then
...
then suddenly, the error message shown above disappears and the code can run correctly! I also tried to insert such write statements in other locations in the source code but the above error message still exists.
According to Intel's documentation:
severe (153): Allocatable array or pointer is not allocated
FOR$IOS_INVDEALLOC. A Fortran 90 allocatable array or pointer must already be allocated when you attempt to deallocate it. You must allocate the array or pointer before it can again be deallocated.
Note: This error can be returned by STAT in a DEALLOCATE statement.
However, I couldn't see any relations between the error and the "write statements" I added to the code. There is no such "allocate" command in the location I add the write statements.
So I am quite confused. Does anybody know the reasons? Any help is greatly appreciated!!
With traceback option, I could locate the error source directly:
subroutine StringRead(Str,delimiter,StrArray,ns) ! [private] read strings separated by delimiter
implicit none
character*(*),intent(in) :: Str
character*(*),intent(in) :: delimiter
character*(*),pointer :: StrArray(:)
integer,intent(out) :: ns
! - local variables
character(len=len(Str)) :: tline
integer :: nvalue,nvalue_max
character(len=len(StrArray)),pointer:: sarray(:),sarray_bak(:)
integer :: len_a,len_d,i
! deallocate StrArray
if(associated(StrArray)) deallocate(StrArray)
The error, according to the information the traceback gave me, lies in the last statement shown above. If I comment out this statement, then the "forrtl: severe (153)" error would disappear while new errors being generated... But still, I don't think this statement itself could go wrong...It acts as if it just ignores the if... condition and directly reads the deallocate commend, which seems weird to me.
You could have a bug in which you are illegally writing to memory and damaging the structure that stores the allocation information. Changing the code might cause the memory damage to occur elsewhere and that specific error to disappear. Generally, illegal memory accesses typically occur two ways in Fortran. 1) illegal subscripts, 2) mismatch between actual and dummy arguments, i.e., between variables in call and variables as declared in procedures. You can search for the first type of error by using your compiler's option for run-time subscript checking. You can guard against the second by placing all of your procedures in modules and useing those modules so that the compiler can check for argument consistency.
Sounds like some of the earlier comments give the general explanation. However,
1) Is StrArray(:) an Intent(out)? That is, are you reading the file's lines into StrArray() in the s/r, with the hope of returning that as the file's content? If so, declare it as an (Out), or whatever it should be.
2) Why is StrArray() a Pointer? Does it need to be a Pointer? If all you want is file content, you may be better off using a non-Pointer.
You may still need an Allocatable, or Automatic or something, but non-Pointers are easier in many cases.
3) If you must have StrArray(:) as a Pointer, then its size/shape etc must be created prior to use. If the calling sequence ACTUAL Arg is correctly defined (and if StrArray() is Intent(In) or Intent(InOUT), then that might do it.
By contrast, if it is an (Out), then, as with all Pointer arrays, it must be FIRST Allcoated() in the s/r.
If it is not Allocated somewhere early on, then it is undefined, and so the DeAllocate() fails, since it has nothing to DeAlloc, hence Stat = 153.
4) It is possible that you may wish to use this to read files without first knowing the number of lines to read. In that case, you cannot (at least not easily), Allocate StrArray() in advance, since you don't know the Size. In this case, alternate strategies are required.
One possible solution is a loop that simple reads the first char, or advances somehow, for each line in the file. Have the loop track the "sum" of each line read, until EOF. Then, you will know the size of the file (in terms of num lines), and you then allocate StrArray(SumLines) or something. Something like
SumLines = 0
Do i=1, ?? (or use a While)
... test to see if "line i" exists, or EOF, if so, Exit
SumLines = SumLines + 1
End Do
It may be best to do this in a separate s/r, so that the Size etc are known prior to calling the FileRead bits (i.e. that the file size is set prior to the FileRead s/r call).
However, that still leaves you with the problem of what Character(Len) to use. There are many possible solutions to this. Three of which are:
a) Use max length, like Character(Len = 2048), Intent(Out), or better yet, some compile time constant Parameter, call it MaxLineWidth
This has the obvious limitation to lines that <= MaxLineWidth, and that the memory usage may be excessively large when there many "short lines", etc.
b) Use a single char array, like Character(Len = 1), Intent(Out) :: StrArrayChar(:,:)
This is 2-D, since you need 1 D for the chars in each line, and the 2nd D for the lines.
This is a bit better compared to a) since it gives control over line width.
c) A more general approach might rely on a User Defined Type such as:
Type MyFileType
Character(Len=1), Allocatable :: FileLine(:) ! this give variable length lines, but each "line" must be allocated to the length of the line
End Type MyFileType
Then, create an array of this Type, such as:
Type(MyFileType), Allocatable :: MyFile(:) ! or, instead of Allocatable, can use Automatic etc etc
Then, Allocate MyFile to Size = num lines
... anyway, there are various choices, each with its own suitability for varying circumstances (and I have omitted much "housekeeping" re DeAllocs etc, which you will need to implement).
Incidentally, c) is also one possible prototype for "variable length strings" for many Fortran compilers that don't support such explicitly.

fortran77 to fortran90 differences in output

I have downloaded the following fortran program dragon.f at http://www.iamg.org/documents/oldftp/VOL32/v32-10-11.zip
I need to do a minor modification to the program which requires the program to be translated to fortran90 (see below to confirm if this is truly needed).
I have managed to do this (translation only) by three different methods:
replacing comment line indicators (c for !) and line continuation
indicators (* in column 6 for & at the end of last line)
using convert.f90 (see https ://wwwasdoc.web.cern.ch/wwwasdoc/WWW/f90/convert.f90)
using f2f.pl (see https :// bitbucket.org/lemonlab/f2f/downloads)
Both 1) and 3) worked (i.e. managed to compile program) while 2) didn't work straight away.
However, after testing the program I found that the results are different.
With the fortran77 program, I get the "expected" results for the example provided with the program (the program comes with an example data "grdata.txt", and its example output "flm.txt" and "check.txt"). However, after running the translated (fortran90) program the results I get are different.
I suspect there are some issues with the way some variables are declared.
Can you give me recommendations in how to properly translate this program so I get the exact same results?
The reason I need to do it in fortran90 is because I need to input the parameters via a text file instead of modifying the program. This shouldnt be an issue for most of the parameters involved, except for the declaration of the last one, in which the size is determined from parameters that the program does not know a priori (see below):
implicit double precision(a-h,o-z)
parameter(lmax=90,imax=45,jmax=30)
parameter(dcta=4.0d0,dfai=4.0d0)
parameter(thetaa=0.d0,thetab=180.d0,phaia=0.d0,phaib=120.d0)
dimension f(0:imax,0:jmax),coe(imax,jmax,4),coew(4),fw(4)
So for example, I will read lmax, imax, jmax, dcta, dfai, thetaa, thetab, phaia, and phaib and the program needs to declare f and coe but as far as I read after googling this issue, they cannot be declared with an unknown size in fortran77.
Edit: This was my attempt to do this modification:
character fname1*100
call getarg(1,fname1)
open(10,file=fname1)
read(10,*)lmax,imax,jmax,dcta,dfai,thetaa,thetab,phaia,phaib
close(10)
So the program will read these constants from a file (e.g. params.txt), where the name of the file is supplied as an argument when invoking the program. The problem when I do this is that I do not know how to modify the line
dimension f(0:imax,0:jmax)...
in order to declare this array when the values imax and jmax are not known when compiling the program (they depend on the size of the data that the user will use).
As has been pointed out in the comments above, parameters cannot be read from file since they are set at compile time. Read them in as integer, declare the arrays as allocatable, and then allocate.
integer imax,jmax
real(8), allocatable :: f(:,:),coe(:,:,:)
read(10,*) imax,jmax
allocate(f(0:imax,0:jmax),coe(imax,jmax,4))
I found out that the differences in the results were attributed to using different compilers.
PS I ended up adding a lot more code than I intended at the beginning to allow reading data from netcdf files. This program in particular is really helpful for spherical harmonic expansion. [tag:spherical harmonics]

performance of allocatable vs. statically sized arrays

I have a fortran code I had to modify to include a new library. Initially in the code the size of an array was passed in the Makefile, which meant every time I wanted to change the size of array I had to recompile the code. I changed this to read the size of the input array from an "input parameters file" so that it avoids the need to recompile every time. However, due to various reasons, my code is much slower than before.
Talking to my boss, he was of the opinion it might be possible that because we are not passing the size of the array during compile time, the code is not well optimized. Is it possibly true?
Thanks
---------------Edit---------------------
Initially there were these line in the makefile
NL = 8
#echo Making $(SIZE_FILE) .....
echo " integer, parameter( nl = " $(NL) " )" > $(SIZE_FILE)
This created a "sizefile" with value of "NL". This file was "include"d in the main program at as the header and then arrays were declared like this in the fortran file:
include "sizefile"
real*8, dimension ur(nl)
Now I have declared a subroutine called "read_input_parameters" which is called by the program which reads a text file with the value of "Nl". And then I allocate the array like this:
program test
integer n
allocatable :: ur(:)
call read_input_parameters(n)
allocate(ur(n))
*operations*
deallocate(ur)
stop
end
You should use a profiler and find the operations that are slow and post their code. The code you showed is useless. Are the results correct, at least?
The slowness can be caused by many factors. One of them is bad argument passing, which makes copy-in / copy-out necessary. Also, the fact that the subroutine does not know if the array is contiguous can do some harm, but not much.