Error: Two main PROGRAMs at (1) and (2) - fortran

I'm using the Simply Fortran compiler and when I try to compile I get the error:
prog.f95:35.13:
1 Implicit None
prog.f95:53.65:
2 open (unit=1,file='in',status='OLD') ! opens file with parameters
Error: Two main PROGRAMs at (1) and (2)
I have included only the parts of the code in which the errors occur since the whole thing is quite long. This begins at the very beginning of the program. Let me know if I should include more.
Implicit None
Integer :: i,j,iter
real(8) :: Elow,Ehigh,chi,B_NS,Vbrprof,Neprof,taues
real(8) :: Xcyclave,a
character(8) systemdate
character(10) systemtime
character(5) timezone
integer dateandtime(8)
character(8) systemdate2
character(10) systemtime2
character(5) timezone2
integer dateandtime2(8)
character(len=40) :: infname,outfname,comm
include 'common.f95'
open (unit=1,file='in',status='OLD') ! opens file with parameters
read (1,1) ! comment line
read (1,1) outfname
read (1,*) Elow,Ehigh ! lower and higher energy
read (1,*) Eminf,Emind,Emaxf ! min and max energy for fedd
read (1,*) Rin, Rout ! inner and outer radii
read (1,*) profpar(1) ! for Ne
read (1,*) profpar(2) ! Te in keV
read (1,*) profpar(3) ! for absorption+emission
read (1,*) profpar(4) ! T_bb for neutron star in keV
read (1,*) profpar(5) ! for bulk velocity
read (1,*) profpar(6) ! other parameter for model
read (1,*) profpar(10) ! magnetic moment in 10^27 CGS
1 format (A10)
close (1)

The compiler is probably seeing an END xxx statement in the file common.f95. The file common.f95 is possibly not meant to be used as an INCLUDE file - it may be a program unit in its own right.

Related

Fortran ftell returning to wrong position

Here is a snippet of simple code that reads line from file, then returns to previous position and re-reads same line:
program main
implicit none
integer :: unit, pos, stat
character(128) :: buffer
! Open file as formatted stream
open( NEWUNIT=unit, FILE="data.txt", ACCESS="stream", FORM="formatted", STATUS="old", ACTION="read", IOSTAT=stat )
if ( stat /= 0 ) error stop
! Skip 2 lines
read (unit,*) buffer
read (unit,*) buffer
! Store position
pos = ftell(unit)
! Read & write next line
read (unit,*) buffer
write (*,*) "buffer=", trim(buffer)
! Return to previous position
call fseek(unit,pos,0)
! pos = ftell(unit) ! <-- ?!
! Read & write next line (should be same output)
read (unit,*) buffer
write (*,*) "buffer=", trim(buffer)
! Close file stream
close (UNIT=unit)
end program main
The "data.txt" is just a dummy file with 4 lines:
1
2
3
4
Now when I compile the snippet (gfortran 9.3.0) and run it, I get an answer:
buffer=3
buffer=4
which is wrong, as they should be same. More interestingly when I add an additional ftell (commented line in the snippet) after 'fseek' I get correct answer:
buffer=3
buffer=3
Any idea why it does that? or am I using ftell and fseek incorrectly?
gfortran's documentation for FTELL and FSEEK clearly states that these routines are provided for backwards compatibility with g77. As your code is using NEWUNIT, ERROR STOP, and STREAM access, you are not compiling old moldy code. You ought to use standard conforming methods as pointed out by #Vladimir.
A quick debugging session shows that FTELL and FSEEK are using a 0-based reference for the file position while the inquire method of modern Fortran is 1 based. There could be an off-by-one type bug in gfortran, but as FTELL and FSEEK are for backwards compatibility with g77 (an unmaintained 15+ year old compiler), someone would need to do some code spelunking to determine the intended behavior. I suspect none of the current, active, gfortran developers care enough to explore the problem. So, to fix your problem
program main
implicit none
integer pos, stat, unit
character(128) buffer
! Open file as formatted stream
open(NEWUNIT=unit, FILE="data.txt", ACCESS="stream", FORM="formatted", &
& STATUS="old", ACTION="read", IOSTAT=stat)
if (stat /= 0) stop
! Skip 2 lines
read (unit,*) buffer
read (unit,*) buffer
! Store position
inquire(unit, pos=pos)
! Read & write next line
read (unit,*) buffer
write (*,*) "buffer=", trim(buffer)
! Reread & write line (should be same output)
read (unit,*,pos=pos) buffer
write (*,*) "buffer=", trim(buffer)
! Close file stream
close (UNIT=unit)
end program main

Fortran code produces runtime error 'operation not supported' when attempting to open a text file

I am trying to run a piece of fortran code written in f95. I have compiled it using gfortran in Ubuntu.
In the code there is a command to read in a text file. When I run it, it gives me the following error:
Fortran runtime error: Cannot open file 'input_parameters.txt': Operation not supported
This is the code up until the point that we attempt to read the text file:
program LSmodel
implicit none !this is a fortran thing that means that all variables that start with i,j,k,l,m,n are integers.
real :: sec,ran,gasdev ! random generator variables
real :: x,y,z,u,v,w,ut,vt,wt,t,dt ! simulation variables
real :: wg ! seed parametes
real :: Um,sigma_u,sigma_v,sigma_w,uw ! wind statistics variables
real :: dvaru_dz,dvarv_dz,dvarw_dz,duw_dz ! wind statistics variables
real :: dissip_m,TL ! vector over the range of ustars
real :: zs,zg,zmax ! release height & boundaries
real :: Ainv,C0inv ! inverse parameters
real :: C0,A,b,au,av,aw,dt_on_TL ! LS model parameters
real :: dz_max,dt_max ! time step limit
real :: CT,beta ! Crossing Trajectories correction
real :: C_chi,chi,TKE,T_chi,omega ! DI parameters
real :: a_ln,b_ln,sigma_chi,dissip_s ! DI parameters
real :: rhop,rho,r,g,gt,Re,AIP,Cd,nu ! IP parameters
real :: up,vp,wp,upt,vpt,wpt,vr,dt_ip,alpha ! IP parameters
real :: keepseed, maxheight
integer :: seed ! random generator variables, keepseed decides whether to keep the same seed or not for comparison of simulation
integer :: pnum, traj_exit ! simulation parameters. traj_exit counts the number of particles that have exited from the topo f the wind flow.
integer :: i,j,jj,n,ii ! counting parameters
integer :: n_ip,IP=1 ! IP parameters
character(len=80) :: filename, wgchar, foldername
real, allocatable,dimension(:) :: z_vec,Um_vec,sigma_u_vec,sigma_v_vec,sigma_w_vec,uw_vec
real, allocatable,dimension(:) :: dvaru_dz_vec,dvarv_dz_vec,dvarw_dz_vec,duw_dz_vec,dissip_m_vec
! input
open (23,file='input_parameters.txt') !opening a file for the input parameters....
read (23, *) x,C0,wg,zs,zg,beta,dt_on_TL,y,sigma_chi,C_chi,r,rhop,alpha,rho,nu, keepseed, foldername
close(23)
I am running Ubuntu 18.04.2 LTS.
An update - I have found (I believe) the reason this code was not working, although I don't know why.
The folder was in a network drive, not on my local computer. Once I moved the folder onto my local computer, I stopped getting this error.

Change variable value when signal is trapped in Fortran

While developing the program on Fortran, that employs some iteration procedure, I faced the necessity to stop iterations manually (to exit from the iteration loop without program termination).
I decided to do it sending a signal to the process. I have chosen SIGALRM. I have checked that it can be trapped without any unexpected consequences.
When received signal, the flag value is changed. This flag is checked inside the iteration loop and exit if flag is true. The sample of such code is given below.
!file mymod.f90
module mymod
use ifport
integer*4 :: err
integer*4 :: SIGNSET
integer*4, parameter :: mySignal=14
logical*1 :: toStopIteration
contains
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ !
integer*4 function setTrap() result(ret)
implicit none
call PXFSTRUCTCREATE('sigset',SIGNSET,err)
call PXFSIGADDSET(SIGNSET,mySignal,err) !add my signal to the set.
ret=0; return
end function setTrap
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ !
integer*4 function onTrap(sig_num) result(rcode)
implicit none
integer*4 :: sig_num,err
rcode=0
select case (sig_num)
case(mySignal)
write (*,*) 'Signal occurred. Stop iteration called'
write (*,*) 'flag: ',toStopIteration
toStopIteration=.true.
write (*,*) 'flag: ',toStopIteration
rcode=1
return
case (SIGINT) ; stop
case (SIGTERM); stop
case (SIGABRT); stop
end select
end function onTrap
! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ !
end module mymod
!file main.f90
program main
use mymod
implicit none
integer*4 :: i,j,N,Niters,sum1
err=setTrap()
err=signal(mySignal, onTrap, -1)
toStopIteration=.false.
open (1,file='output')
write (*,*) 'PID=',getpid()
write (1,*) 'Outside',toStopIteration
N=5000000; Niters=100000
do i = 1,Niters
if (toStopIteration) then
toStopIteration=.false.
exit
endif
sum1=0
do j = 1,N
sum1=sum1+j
enddo
write (1,*) i,toStopIteration,sum1
enddo
write (*,*) 'Procedure was terminated due to signal received. The last iteration was', i
write (*,*) 'Now I will do other job for you.'
stop
end program main
Application was compiled with ifort: ifort -c -O2 -traceback.
When I send signal to the process kill -14 pid,
I get output to the terminal:
Signal occurred. Stop iteration called
flag: F
flag: T
But iteration loop is still running and as written in the file, variable "toStopIteration" is equal false.
Accidentally, I have found out that when compiled with -O0 -traceback parameter, it works fine.
Why does it happen? Does variable "toStopIteration" become local with such optimization level? And what can I do to make it work correctly?
Thanks in advance.
MuKeP.
As Lorri answered (unfortunately that succinct, but correct, answer has been deleted by misdirected reviews) - try the volatile attribute on toStopIteration. This tells the compiler that the variable might be redefined by something else, otherwise from the source visible to the compiler it looks like the value of that variable cannot change in an iteration, and therefore there is no point testing it each iteration.

How can I read data from a text file and save/write parts/variables to different text files?

I'm fairly new to Fortran so this might be a naive question. I would like to read a huge .txt file with a # of rows=540001. The data are from a sonic anemometer with measurements of velocity and temperature as u,v,w,T at five heights. Here are the first few lines of the file:
"2011-07-10 09:30:00",9838,1.132,2.30225,-0.5635,29.18585,0.30275,0.689,-0.01125,29.67004,0.2165,-0.25475,0.12725,29.8923,0.51425,3.0405,-0.58375,29.5242,-0.0085,3.6235,-0.65175,29.61972,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
"2011-07-10 09:30:00.05",9839,-0.21325,3.22775,-0.17,29.10953,0.33925,0.6867501,-0.0015,29.67874,0.1715,-0.196,0.1235,29.8923,0.035,2.6915,-0.3845,29.82806,-0.102,3.5505,-0.15825,29.61795,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
"2011-07-10 09:30:00.1",9840,0.403,3.1195,-0.37175,29.22574,0.06550001,0.6655,0.1275,29.76208,0.196,-0.2,0.1,29.901,0.16225,2.31525,-0.5975,29.69263,0.24175,3.11925,-0.3725,29.57977,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
etc...
I would like to save/write the matrices u(5,540001),v(5,540001),w(5,540001), and T(5,540001) so that I can do some calculations and plots. Here is what I am using:
PROGRAM READ_MAIZE
IMPLICIT NONE
REAL,DIMENSION(:,:),Allocatable :: u_r, v_r, w_r, T_r
CHARACTER(len=*) :: fname
fname='FINALDATA.txt'
open(unit=1,file=fname,status='old',action='read')
do i=1,540001
READ(1,*)timestamp(i),count(i),u_r(5,i),v_r(5,i),w_r(5,i), &
T_r(5,i),u_r(2,i),v_r(2,i),w_r(2,i),T_r(2,i), &
u_r(1,i),v_r(1,i),w_r(1,i),T_r(1,i), &
u_r(3,i),v_r(3,i),w_r(3,i),T_r(3,i), &
u_r(4,i),v_r(4,i),w_r(4,i),T_r(4,i),flags(1:20)
end do
close(1)
WRITE(U_maize,'(A,I7.7,A,I7.7,A)'), &
'.txt'
open(11,file=U_maize,status='unknown',action='write')
write(11,'(F20.14)')(u_r)
end
Never mind the order in u_r(5,i) followed by u_r(2,i)... (they just correspond to different heights that are out of order). This is not working.
There's quite a lot going on in your code which makes it hard to understand what you're trying to do in the first place. I have annotated your code below and turned it into something that compiles and produces output. Maybe it'll help.
PROGRAM READ_MAIZE
IMPLICIT NONE ! This means that every variable has to be declared
! explicitly. You don't do that. So I did it for you
REAL,DIMENSION(:,:),Allocatable :: u_r, v_r, w_r, T_r
integer, dimension(:), allocatable :: data_count ! using fortran keywords
! (such as "count") as variables is dangerous and should be avoided
character(len=len("2011-07-10 09:30:00.05")), allocatable :: timestamp(:)
CHARACTER(len=*), parameter :: fname='FINALDATA.txt'
character(len=len("U_XXXXXXX_XXXXXXX.txt")) :: U_maize
integer :: in_unit, out_unit ! Use integer variables for the unit.
! together with newunit keyword, this is
! safer
integer, parameter :: num_records = 3 ! you need to up this number to
! 540001 again
integer :: i
! If you have allocatable arrays, you need to allocate them before you
! can use them
allocate(u_r(5, num_records))
allocate(v_r(5, num_records))
allocate(w_r(5, num_records))
allocate(T_r(5, num_records))
allocate(data_count(num_records))
allocate(timestamp(num_records))
! the "newunit" keyword is a safe way to create a unique unit
! identifier. You should really use this.
open(newunit=in_unit,file=fname,status='old',action='read')
do i=1,num_records
READ(in_unit,*) timestamp(i), data_count(i), &
u_r(5,i),v_r(5,i),w_r(5,i),T_r(5,i), &
u_r(2,i),v_r(2,i),w_r(2,i),T_r(2,i), &
u_r(1,i),v_r(1,i),w_r(1,i),T_r(1,i), &
u_r(3,i),v_r(3,i),w_r(3,i),T_r(3,i), &
u_r(4,i),v_r(4,i),w_r(4,i),T_r(4,i) ! I left out the flags
! since I didn't know what
! that was.
end do
close(in_unit)
! I don't know how the file name should be constructed, except
! that it should end in a .txt, and the format. So I made something up.
write(U_maize, '(A, I7.7, A, I7.7, A)') 'U_', 35, '_', 6, '.txt'
open(newunit=out_unit,file=U_maize,status='unknown',action='write')
! To make it more readable, I tell write to write 5 numbers per row,
! Not sure whether this is what you want.
write(out_unit,'(5(X, F20.14))') u_r
close(out_unit) ! I know it isn't technically needed, but please always
! close files when finished, even if the program terminates anyway.
end program READ_MAIZE ! tell the compiler what you want to end here.

MPI write to file sequentially

I am writing a parallel VTK file (pvti) from my fortran CFD solver. The file is really just a list of all the individual files for each piece of the data. Running MPI, if I have each process write the name of its individual file to standard output
print *, name
then I get a nice list of each file, ie
block0.vti
block1.vti
block2.vti
This is exactly the sort of list I want. But if I write to a file
write(9,*) name
then I only get one output in the file. Is there a simple way to replicate the standard output version of this without transferring data?
You could try adapting the following which uses MPI-IO, which is really the only way to ensure ordered files from multiple processes. It does assume an end of line character and that all the lines are the same length (padded with blanks if required) but I think that's about it.
Program ascii_mpiio
! simple example to show MPI-IO "emulating" Fortran
! formatted direct access files. Note can not use the latter
! in parallel with multiple processes writing to one file
! is behaviour is not defined (and DOES go wrong on certain
! machines)
Use mpi
Implicit None
! All the "lines" in the file will be this length
Integer, Parameter :: max_line_length = 30
! We also need to explicitly write a carriage return.
! here I am assuming ASCII
Character, Parameter :: lf = Achar( 10 )
! Buffer to hold a line
Character( Len = max_line_length + 1 ) :: line
Integer :: me, nproc
Integer :: fh
Integer :: record
Integer :: error
Integer :: i
! Initialise MPI
Call mpi_init( error )
Call mpi_comm_rank( mpi_comm_world, me , error )
Call mpi_comm_size( mpi_comm_world, nproc, error )
! Create a MPI derived type that will contain a line of the final
! output just before we write it using MPI-IO. Note this also
! includes the carriage return at the end of the line.
Call mpi_type_contiguous( max_line_length + 1, mpi_character, record, error )
Call mpi_type_commit( record, error )
! Open the file. prob want to change the path and name
Call mpi_file_open( mpi_comm_world, '/home/ian/test/mpiio/stuff.dat', &
mpi_mode_wronly + mpi_mode_create, &
mpi_info_null, fh, error )
! Set the view for the file. Note the etype and ftype are both RECORD,
! the derived type used to represent a whole line, and the displacement
! is zero. Thus
! a) Each process can "see" all of the file
! b) The unit of displacement in subsequent calls is a line.
! Thus if we have a displacement of zero we write to the first line,
! 1 means we write to the second line, and in general i means
! we write to the (i+1)th line
Call mpi_file_set_view( fh, 0_mpi_offset_kind, record, record, &
'native', mpi_info_null, error )
! Make each process write to a different part of the file
Do i = me, 50, nproc
! Use an internal write to transfer the data into the
! character buffer
Write( line, '( "This is line ", i0, " from ", i0 )' ) i, me
!Remember the line feed at the end of the line
line( Len( line ):Len( line ) ) = lf
! Write with a displacement of i, and thus to line i+1
! in the file
Call mpi_file_write_at( fh, Int( i, mpi_offset_kind ), &
line, 1, record, mpi_status_ignore, error )
End Do
! Close the file
Call mpi_file_close( fh, error )
! Tidy up
Call mpi_type_free( record, error )
Call mpi_finalize( error )
End Program ascii_mpii
Also please note you're just getting lucky with your standard output "solution", you're not guaranteed to get it all nice sorted.
Apart from having the writes from different ranks well mixed, your problem is that the Fortran OPEN statement probably truncates the file to zero length, thus obliterating the previous content instead of appending to it. I'm with Vladimir F on this and would write this file only in rank 0. There are several possible cases, some of which are listed here:
each rank writes a separate VTK file and the order follows the ranks or the actual order is not significant. In that case you could simply use a DO loop in rank 0 from 0 to #ranks-1 to generate the whole list.
each rank writes a separate VTK file, but the order does not follow the ranks, e.g. rank 0 writes block3.vti, rank 1 writes block12.vti, etc. In that case you can use MPI_GATHER to collect the block number from each process into an array at rank 0 and then loop over the elements of the array.
some ranks write a VTK file, some don't, and the block order does not follow the ranks. It's similar to the previous case - just have the ranks that do not write a block send a negative block number and then rank 0 would skip the negative array elements.
block numbering follows ranks order but not all ranks write a block. In that case you can use MPI_GATHER to collect one LOGICAL value from each rank that indicates if it has written a block or not.
If you are not in a hurry, you can force the output from different tasks to be in order:
! Loop over processes in order
DO n = 0,numProcesses-1
! Write to file if it is my turn
IF(nproc == n)THEN
! Write output here
ENDIF
! This call ensures that all processes wait for each other
#ifdef MPI
CALL MPI_Barrier(mpi_comm_world,ierr)
#endif
ENDDO
This solution is simple, but not efficient for very large output. This does not seem to be your case. Make sure you flush the output buffer after each write. If using this method, make sure to do tests before implementing, as success is not guaranteed on all architectures. This method works for me for outputting large NetCDF files without the need to pass the data around.