Intel Fortran: write multi-item namelist to internal file? - fortran

I want to write a namelist with multiple items (hence multiple lines) to a character variable. The following code runs well when compiled with gfortran, but returns a write error when compiled with ifort:
program test
implicit none
type testtype
real*8 :: x
character(len=32) :: str
logical :: tf
end type testtype
type(testtype) :: thetype
integer :: iostat
character(len=1000) :: mystr(10)
namelist /THENAMELIST/ thetype
integer :: i
thetype%x = 1.0d0
thetype%str="This is a string."
thetype%tf = .true.
mystr=""
write(*,nml=THENAMELIST,delim="QUOTE")
write(mystr,THENAMELIST,iostat=iostat,delim="QUOTE")
write(*,*)"Iostat:",iostat
do i = 1, size(mystr)
write(*,*)i,trim(mystr(i))
end do
end program test
The output is the following:
> ifort -o test test.f90 ; ./test
&THENAMELIST
THETYPE%X = 1.00000000000000 ,
THETYPE%STR = "This is a string. ",
THETYPE%TF = T
/
Iostat: 66
1 &THENAMELIST THETYPE%X= 1.00000000000000 ,
2
3
4
5
6
7
8
9
10
Intel's list of run-time error messages tells me: "severe (66): Output statement overflows record".
For over completeness, using gfortran I of course get
> gfortran -o test test.f90 ; ./test
&THENAMELIST
THETYPE%X= 1.0000000000000000 ,
THETYPE%STR="This is a string. ",
THETYPE%TF=T,
/
Iostat: 0
1 &THENAMELIST
2 THETYPE%X= 1.0000000000000000 ,
3 THETYPE%STR="This is a string. ",
4 THETYPE%TF=T,
5 /
6
7
8
9
10
I have searched all over the internet, and learned that the internal file cannot be a scalar character variable, but that's about as much as I found. GFortran does accept a scalar variable and just writes newlines in that variable, but that, I guess, is non-standard fortran.
The compilers I used are:
gfortran GNU Fortran (MacPorts gcc48 4.8-20130411_0) 4.8.1 20130411 (prerelease)
ifort (IFORT) 12.0.5 20110719 (on mac)
ifort (IFORT) 13.1.1 20130313 (on GNU/Linux)
My question is: what is the error in my syntax, or how else can I write a namelist to an internal file, without having to patch the problem by writing to an actual external scratch file and read that into my variable (which is what I do now, but which is slow for large namelists)?

Related

Problems with unformatted file write/read compatibility between Intel Fortran and gfortran [duplicate]

This question already has answers here:
Unexpected "padding" in a Fortran unformatted file
(4 answers)
Closed 2 years ago.
I am trying to use a code on both Windows with an Intel compiler and on Mac OS with gfortran 6.5.0 and can't get the gfortran version to read parts of an unformatted file written on Windows. I wrote a test code that has the problematic section and verified it works in writing and reading the file on the Intel compiler and on the gfortran compiler. However, if I comment out the write portion and just try to read the file written on the Windows side of the machine (Parallels) with the gfortran version, some of the data is not read properly. I'm including the test code below. The "cel(1), f_ei,f_en,f_egyro,f_wall,f_ex,f_wallBC =" data are not read correctly (the data before that are read in properly, however). Is there some incompatibility in unformatted files?
PROGRAM Testo
IMPLICIT NONE
INTEGER, PARAMETER :: ncelMAX=6800
REAL*8 :: dt
LOGICAL :: MagON,BFmesh
INTEGER :: nslice_Ver, nslice_verzr, nslice_Edg, nslice_edgzr
INTEGER :: nFluid, nChrge, nCel, nBCs, nEdg, nVer , nCelzr, nBCszr, nEdgzr, &
nVerzr, MinSliceCel, MaxSliceCel, MinSliceCelzr, MaxSliceCelzr
TYPE cell_obj
INTEGER*4 verNo(4),edgNo(4)
INTEGER*4 Bln !BField Mesh
REAL*8 f_ei,f_en,f_egyro,f_wall,f_ex, f_wallBC
END TYPE cell_obj
TYPE(cell_obj) cel(ncelMAX)
dt = 2.0E-8
MagON = .TRUE.
BFmesh = .TRUE.
nslice_Ver = 1
nslice_verzr = 2
nslice_Edg = 3
nslice_edgzr = 4
nFluid = 3
nChrge = 3
nCel = 3000
nBCs = 4000
nEdg = 5000
nVer = 6000
nCelzr = 7000
nBCszr = 8000
nEdgzr = 9000
nVerzr = 10000
MinSliceCel = 100
MaxSliceCel = 200
MinSliceCelzr = 300
MaxSliceCelzr = 400
cel(1)%verNo(1) = 1
cel(1)%verNo(2) = 2
cel(1)%verNo(3) = 3
cel(1)%verNo(4) = 4
cel(1)%edgNo(1) = 1
cel(1)%edgNo(2) = 2
cel(1)%edgNo(3) = 3
cel(1)%edgNo(4) = 4
cel(1)%Bln = 1000
cel(1)%f_ei = 2.0E6
cel(1)%f_en = 2.0E7
cel(1)%f_egyro = 2.0E8
cel(1)%f_wall = 3.0E6
cel(1)%f_ex = 3.0E7
cel(1)%f_wallBC = 3.0E8
OPEN(UNIT=10,FILE='restartData_TEST',FORM='UNFORMATTED')
REWIND(10)
WRITE(10) dt, MagON, nslice_Ver, nslice_Edg, nslice_verzr, nslice_edgzr, BFmesh
WRITE(10) nFluid, nChrge, nCel, nBCs, nEdg, nVer , nCelzr, nBCszr, nEdgzr, nVerzr, MinSliceCel, MaxSliceCel,MinSliceCelzr,MaxSliceCelzr
WRITE(10) cel
CLOSE(10)
OPEN(UNIT=10,FILE='restartData_TEST',FORM='UNFORMATTED')
REWIND(10)
READ(10) dt,MagON,nslice_Ver,nslice_Edg, nslice_verzr, nslice_edgzr, BFmesh
PRINT *, "First line = ", dt,MagON,nslice_Ver,nslice_Edg, nslice_verzr, nslice_edgzr, BFmesh
READ(10) nFluid, nChrge, nCel, nBCs, nEdg, nVer , nCelzr, nBCszr, nEdgzr, nVerzr, MinSliceCel, MaxSliceCel,MinSliceCelzr,MaxSliceCelzr
PRINT *, "Second line = ", nFluid, nChrge, nCel, nBCs, nEdg, nVer , nCelzr, nBCszr, nEdgzr, nVerzr, MinSliceCel, MaxSliceCel,MinSliceCelzr,MaxSliceCelzr
READ(10) cel
PRINT *, "cel(1), verNo(4),edgNo(4) = ",cel(1)%verNo(1),cel(1)%verNo(2),cel(1)%verNo(3),cel(1)%verNo(4),cel(1)%edgNo(1),cel(1)%edgNo(2),cel(1)%edgNo(3),cel(1)%edgNo(4)
PRINT *, "cel(1), Bln = ",cel(1)%Bln
PRINT *, "cel(1), f_ei,f_en,f_egyro,f_wall,f_ex,f_wallBC = ",cel(1)%f_ei,cel(1)%f_en,cel(1)%f_egyro,cel(1)%f_wall,cel(1)%f_ex,cel(1)%f_wallBC
PAUSE 'DONE'
END PROGRAM Testo
There is absolutely no guarantee of the portability of Fortran unformatted files - if you don't use exactly the same hardware and compiler combination (down to the version of the compiler) all bets are off. If you need portability use a formatted file, or possibly stream I/O, or probably best one of the portable data formats such as netcdf (https://www.unidata.ucar.edu/software/netcdf/) or hdf5 (https://www.hdfgroup.org/solutions/hdf5/)
Also please don't use the non standard real*8 and integer*4 - see Fortran 90 kind parameter for how to do it properly

String array being nullified when passing

I am having trouble passing a string array. Consider the following example code:
! -- Module to declare variable
module my_data
implicit none
! -- Declare as deferred-length allocatable array
character(len=:), dimension(:), allocatable :: str_array
end module my_data
! -- Module to call subroutine
module my_subs
implicit none
contains
subroutine a(str_array)
character(len=*), dimension(:), intent(IN) :: str_array
integer :: i, j
character :: c
do i=1,size(str_array)
do j=1,len_trim(str_array(i))
c = str_array(i)(j:j)
! -- Write i, j, character, and int representation
write(*,*) 'In call: ', i, j, ' "'//c//'", ichar = ', ichar(c)
enddo
enddo
end subroutine a
end module my_subs
! -- Main program
program main
use my_data, only : str_array
use my_subs, only : a
implicit none
integer, parameter :: strlen = 200
integer :: N, i, j
character :: c
! -- Size of str array
N = 2
! -- Allocate str_array, syntax from https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/287349
allocate(character(strlen) :: str_array(N))
! -- Set both to the same string
str_array = 'abc'
do i=1,size(str_array)
do j=1,len_trim(str_array(i))
c = str_array(i)(j:j)
! -- Write i, j, character, and int representation
write(*,*) 'In main: ', i, j, ' "'//c//'", ichar = ', ichar(c)
enddo
enddo
call a(str_array)
end program main
The string array is declared as an array of assumed-length elements (from the wiki). I allocate and set the values of the string (two elements, both to abc for this example). The main routine outputs full details about the string, then calls a subroutine which also outputs the (hopefully same) full details.
Using PGI, GCC, or Intel 15.0, I get the result I expect:
chaud106#ln0005 [~/Testing] % ifort --version && ifort -check all -warn all main.f90 && ./a.out
ifort (IFORT) 15.0.3 20150407
Copyright (C) 1985-2015 Intel Corporation. All rights reserved.
In main: 1 1 "a", ichar = 97
In main: 1 2 "b", ichar = 98
In main: 1 3 "c", ichar = 99
In main: 2 1 "a", ichar = 97
In main: 2 2 "b", ichar = 98
In main: 2 3 "c", ichar = 99
In call: 1 1 "a", ichar = 97
In call: 1 2 "b", ichar = 98
In call: 1 3 "c", ichar = 99
In call: 2 1 "a", ichar = 97
In call: 2 2 "b", ichar = 98
In call: 2 3 "c", ichar = 99
However, Intel 18.0 sets the second element of the character array (all 3 characters) to the null character:
chaud106#ln0005 [~/Testing] % ifort --version && ifort -check all -warn all main.f90 && ./a.out
ifort (IFORT) 18.0.0 20170811
Copyright (C) 1985-2017 Intel Corporation. All rights reserved.
In main: 1 1 "a", ichar = 97
In main: 1 2 "b", ichar = 98
In main: 1 3 "c", ichar = 99
In main: 2 1 "a", ichar = 97
In main: 2 2 "b", ichar = 98
In main: 2 3 "c", ichar = 99
In call: 1 1 "a", ichar = 97
In call: 1 2 "b", ichar = 98
In call: 1 3 "c", ichar = 99
In call: 2 1 "", ichar = 0
In call: 2 2 "", ichar = 0
In call: 2 3 "", ichar = 0
I have several questions related to this behavior:
Why is this occurring? I was thinking it could be related to Intel enforcing lhs-reallocation, but I'm not sure. Adding -assume norealloc_lhs didn't change anything.
What is the correct syntax to pass a string array like this? Could I declare it differently and avoid this problem?
The versions of Intel I have access to on this machine have the following behavior:
ifort (IFORT) 15.0.2 20150121 - No nullification
ifort (IFORT) 15.0.3 20150407 - No nullification
ifort (IFORT) 16.0.3 20160415 - No nullification
ifort (IFORT) 17.0.4 20170411 - Nullifies
ifort (IFORT) 18.0.0 20170811 - Nullifies
On a different machine, I don't have any latest Intel:
ifort (IFORT) 14.0.2 20140120 - No nullification
ifort (IFORT) 16.0.0 20150815 - No nullification
Your program works as expected with ifort 18.0.3.
I haven't tried with lots of previous versions, but I note that 17.0.1 was the point at which Fortran 2003 automatic allocation on intrinsic assignment became the default in that compiler.
The problematic line appears to be
str_array = 'abc'
Here, str_array should first be deallocated, because the right-hand side is an expression with different length parameter from the left-hand side. Then it would be allocated as a character of length 3 (length of the right-hand side) and shape [2] as before (the right-hand side is scalar). And that does happen, as can be seen with SIZE(str_array) and LEN(str_array). Something goes a little awry later on when using it as an actual argument, though.
There are ways to work around this problem with 18.0.1:
give the dummy argument the value attribute;
str_array = ['abc','abc'] (previous allocation not required);
str_array(:) = 'abc' (if you don't want the reallocation).
Many others likely available, depending on exactly what you need. Upgrade your compiler to the latest version if you can, though.

How do I compile this Fortran code with new 2017 ifort?

I have the following fortran code that compiles with pre 2017 ifort:
program parallel_m
contains
character(500) function PARALLEL_message(i_ss)
character(50) :: Short_Description = " "
integer :: i_s =0
integer :: n_threads = 0
!
PARALLEL_message=" "
!
if (i_s>0) then
if (len_trim("test this ")==0) return
endif
!
if (i_s==0) then
PARALLEL_message=trim("10")//"(CPU)"
if (n_threads>0) PARALLEL_message=trim(PARALLEL_message)//"-"//trim("200")//"(threads)"
else
PARALLEL_message=trim("a")//"(environment)-"//&
& trim("a")//"(CPUs)-"//&
& trim("a")//"(ROLEs)"
endif
!
end function
end program parallel_m
Going through the preprocessor :
icc -ansi -E example.F > test.f90
Which produces:
# 1 "mod.F"
program parallel_m
contains
character(500) function PARALLEL_message(i_ss)
character(50) :: Short_Description = " "
integer :: i_s =0
integer :: n_threads = 0
!
PARALLEL_message=" "
!
if (i_s>0) then
if (len_trim("test this ")==0) return
endif
!
if (i_s==0) then
PARALLEL_message=trim("10")
if (n_threads>0) PARALLEL_message=trim(PARALLEL_message)
else
PARALLEL_message=trim("a")
& trim("a")
& trim("a")
endif
!
end function
end program parallel_m
This unfortunately with intel 2017 does not compile, the same
output compiles without complaint on 2016 and 2015 ifort releases.
this is the error that I get:
mod.F(19): error #5082: Syntax error, found '&' when expecting one of: <LABEL> <END-OF-STATEMENT> ; TYPE INTEGER REAL COMPLEX BYTE CHARACTER CLASS DOUBLE ...
& trim("a")
------------------------^
mod.F(20): error #5082: Syntax error, found '&' when expecting one of: <LABEL> <END-OF-STATEMENT> ; TYPE INTEGER REAL COMPLEX BYTE CHARACTER CLASS DOUBLE ...
& trim("a")
------------------------^
compilation aborted for test.f90 (code 1)
Your program is illegal Fortran after the preprocessing because the // is interpretted as a C comment.
Simply do not use icc but ifort. Ifort is for Fortran, icc is for C. Ifort uses a different preprocessor fpp which does not discard //.

Fortran - nf90_open - SIGSEGV

I am using an old fortran program given to me to open a netcdf file, read its contents, perform some calculations and interpolation, and write the data to another file format. I have very little experience in fortran, so please any help would be deeply appreciated.
The program is compiled successfully:
ifort -c -CB -CU -ftrapuv -par_report0 -vec_report0 -heap-arrays -O0 -stand f90 -check all -traceback -fstack-protector -assume protect_parens -implicitnone -debug -gen-interfaces -check arg_temp_created -ftrapuv -g -convert big_endian -I/opt/cray/netcdf/4.3.0/INTEL/130/include/ CAM_netcdf_to_WRF_intermediate.f90 ; ifort CAM_netcdf_to_WRF_intermediate.o -L/opt/cray/netcdf/4.3.0/INTEL/130/lib -lnetcdf -lnetcdff
The program crashes, running out of bounds while trying to read in the netcdf file:
Program received signal SIGSEGV, Segmentation fault.
0x00007ffff7657d33 in nf_open_ (A1=0x18 <Address 0x18 out of bounds>, A2=0x4e04bc <__NLITPACK_19>,
A3=0x7fffffff90ec, C1=128) at fort-control.c:27
27 fort-control.c: No such file or directory.
Running GDB, using 'bt full':
Program received signal SIGSEGV, Segmentation fault.
0x00007ffff7657d33 in nf_open_ (A1=0x18 <Address 0x18 out of bounds>, A2=0x4e04bc <__NLITPACK_19>,
A3=0x7fffffff90ec, C1=128) at fort-control.c:27
27 fort-control.c: No such file or directory.
(gdb) bt full
#0 0x00007ffff7657d33 in nf_open_ (A1=0x18 <Address 0x18 out of bounds>,
A2=0x4e04bc <__NLITPACK_19>, A3=0x7fffffff90ec, C1=128) at fort-control.c:27
B1 = 0x0
B3 = 5113020
#1 0x00007ffff76630ac in NETCDF::nf90_open (
path=<error reading variable: Cannot access memory at address 0x18>, mode=0, ncid=-858993460,
chunksize=<error reading variable: Cannot access memory at address 0x0>,
cache_size=<error reading variable: Cannot access memory at address 0x0>,
cache_nelems=<error reading variable: Cannot access memory at address 0x0>,
cache_preemption=<error reading variable: Cannot access memory at address 0x0>,
comm=<error reading variable: Cannot access memory at address 0x0>,
info=<error reading variable: Cannot access memory at address 0x0>, .tmp.PATH.len_V$ffc=128)
at netcdf4_file.f90:64
nf90_open = -144388088
ret = 0
preemption_out = 0
nelems_out = -1
size_out = 0
preemption_in = 32767
nelems_in = -134664192
size_in = 32767
The program is below:
program CAM_netcdf_to_WRF_intermediate
use netcdf
implicit none
! Declarations:
integer, parameter :: outfile_diagnostics = 16
integer, parameter :: infile_CAM_files_and_dates = 15
character(len=24) :: HDATE
! dimensions:
integer, parameter :: nx_CAM=288,ny_CAM=192,nz_CAM=26 &
,nfields=5,nfields2d=9,nfields2d_to_read=5 &
,nz_soil=4,nz_CLM=1,nfields_soil=2
integer, parameter :: nz_WRF=38
character(len=128) :: netcdf_cam_filename,netcdf_clm_filename,netcdf_pop_filename
character(len=128) :: netcdf_ice_filename
integer :: iEOF
logical :: EOF
! open outpuf log file:
open(outfile_diagnostics,form='formatted',file="Output/CCSM2WRF.log")
! read the first date and netcdf file name from the input file:
open(infile_CAM_files_and_dates,form='formatted',file="Input/CCSM2WRF.input")
read(infile_CAM_files_and_dates,*,iostat=iEOF) netcdf_cam_filename,netcdf_clm_filename,&
netcdf_pop_filename,netcdf_ice_filename,hdate
if (iEOF<0) then;
print *, "EOF True"
EOF=.true.;
else;
print *, "EOF False"
EOF=.false.;
end if
call dummy_read(nz_WRF,hdate,outfile_diagnostics,netcdf_cam_filename &
,netcdf_clm_filename,netcdf_pop_filename &
,netcdf_ice_filename,nx_CAM,ny_CAM,nz_CAM)
stop
end program CAM_netcdf_to_WRF_intermediate
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
SUBROUTINE HANDLE_ERR(STATUS)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
use netcdf
implicit none
INTEGER STATUS
IF (STATUS .NE. NF90_NOERR) THEN
PRINT *, NF90_STRERROR(STATUS)
STOP 'Stopped'
ENDIF
END SUBROUTINE HANDLE_ERR
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Subroutine dummy_read &
(nz_WRF,outfile_diagnostics,netcdf_cam_filename &
,netcdf_clm_filename,netcdf_pop_filename,netcdf_ice_filename &
,nx_CAM,ny_CAM,nz_CAM)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
use netcdf
implicit none
integer :: nz_WRF
integer :: nx_CAM,ny_CAM,nz_CAM
character(len=128) :: filename
character(len=24) :: HDATE
integer :: outfile_diagnostics
integer :: STATUS, NCID, NCID_clm, NCID_pop, NCID_ice
character(len=128) :: netcdf_cam_filename, netcdf_clm_filename, netcdf_pop_filename
character(len=128) :: netcdf_ice_filename
! open output files for metgrid in WRF/WPS intermediate format:
write(filename,'("Output/FILE:",A13)') hdate(1:13)
write(outfile_diagnostics,*) "output intermediate file filename=",filename
open(10,form='unformatted',file=filename)
write(filename,'("Output/SST:",A13)') hdate(1:13)
write(outfile_diagnostics,*) "output intermediate SST file filename=",filename
open(11,form='unformatted',file=filename)
STATUS = NF90_OPEN(netcdf_cam_filename, 0, NCID)
! STATUS = NF90_OPEN(path = "Inputdata/ind/cam_CCSM4_historical_197909-197912-1979090100.nc", mode= 0, ncid = NCID)
IF (STATUS .NE. NF90_NOERR) CALL HANDLE_ERR(STATUS)
print *, "first status conditional statement"
STATUS = NF90_OPEN(netcdf_clm_filename, 0, NCID_clm)
IF (STATUS .NE. NF90_NOERR) CALL HANDLE_ERR(STATUS)
STATUS = NF90_OPEN(netcdf_pop_filename, 0, NCID_pop)
IF (STATUS .NE. NF90_NOERR) CALL HANDLE_ERR(STATUS)
STATUS = NF90_OPEN(netcdf_ice_filename, 0, NCID_ice)
IF (STATUS .NE. NF90_NOERR) CALL HANDLE_ERR(STATUS)
status=NF90_CLOSE(NCID)
status=NF90_CLOSE(NCID_clm)
status=NF90_CLOSE(NCID_pop)
status=NF90_CLOSE(NCID_ice)
print *, "Leaving dummy, going to MAIN"
return
end Subroutine dummy_read
The open statement works if I hard-code the path of the netcdf file (see the commented out line within the dummy_read subroutine). Printing out the netcdf_cam_filename within main returns a valid string, however printing out the string within the dummy_read subroutine returns an empty string. I am uncertain why the netcdf_cam_filename string is not making it into the subroutine correctly.
Please ask if you need additional information. I only posted pieces of the code that I think applies to the error. Thanks in advance.
Your subroutine call is mismatched to the actual definition.
Your call to dummy_read is:
call dummy_read(nz_WRF,hdate,outfile_diagnostics,netcdf_cam_filename &
,netcdf_clm_filename,netcdf_pop_filename &
,netcdf_ice_filename,nx_CAM,ny_CAM,nz_CAM)
While your declaration of dummy_read is:
Subroutine dummy_read &
(nz_WRF,outfile_diagnostics,netcdf_cam_filename &
,netcdf_clm_filename,netcdf_pop_filename,netcdf_ice_filename &
,nx_CAM,ny_CAM,nz_CAM)
Or shown a different way:
call dummy_read(nz_WRF,hdate, outfile_diagnostics,netcdf_cam_filename,netcdf_clm_filename,netcdf_pop_filename,netcdf_ice_filename,nx_CAM,ny_CAM,nz_CAM)
Subroutine dummy_read(nz_WRF,outfile_diagnostics,netcdf_cam_filename,netcdf_clm_filename,netcdf_pop_filename,netcdf_ice_filename,nx_CAM, ny_CAM,nz_CAM)
Which results in an argument mismatch. The dummy argument outfile_diagnostics is associated with the actual argument hdate and so on. You are passing 10 arguments to a subroutine declared to take 9.
You might wonder why the compiler produced an executable in such a case rather than producing an error. This is because you are calling the procedure with an implicit interface and Fortran trusts you to do the right thing. Fortran can detect argument mismatches but to do so you need to provide an explicit interface. Aside from explicitly declaring the interface, the easiest ways to do this are to either make the procedure a module procedure (by putting the subroutine into a module) or an internal procedure (by putting the procedure in the main program after a contains statement).
You can also ask the compiler to provide high levels of warnings to avoid this problem. Compiling with gfortran with -Wall produces this warning with your code:
call dummy_read(nz_WRF,hdate,outfile_diagnostics,netcdf_cam_filename &
1
Warning: Type mismatch in argument 'outfile_diagnostics' at (1); passed CHARACTER(1) to INTEGER(4)
Adiitionally, ifort provides the option -gen-interfaces flag that will automatically generate modules to contain external procedures. I would however consider this a tool to help port code to newer language standards than something to rely on.

How to write output to a string in fortran?

I need to write a formated output to a string DTSTR. It use to work under layhe fortran but not gfortran
INTEGER*2 MON,DAY,YEAR,HR,MINUTE,SEC,HUND
CHARACTER DY*2
CHARACTER DTSTR*24
COMMON /RD/ DTSTR
...
...
WRITE(DTSTR,10)MON,DAY,YEAR,HR,MINUTE,DY,' ]'
10 FORMAT('[ ',I2,'-',I2.2,'-',I4,2X,I2,':',I2.2,1X,2A2)
it empty just a empty line. If i use following it correctly output. But i want to store this string. Is it possible to do that with gnu fortran.
WRITE(*,10)MON,DAY,YEAR,HR,MINUTE,DY,' ]'
update
I am trying to compile following file. I think the problem might be with the COMMON.
PROGRAM HELO
CALL DOTIME
WRITE(*,5700)DTSTR
5700 FORMAT(24X,A24/)
END
SUBROUTINE DOTIME
C
IMPLICIT NONE
INTEGER*2 MON,DAY,YEAR,HR,MINUTE,SEC,HUND
CHARACTER DY*2
CHARACTER DTSTR*24
COMMON /RD/ DTSTR
integer values(8)
call date_and_time(VALUES=values)
YEAR = values(1)
MON = values(2)
DAY = values(3)
HR = values(5)
MINUTE = values(6)
SEC = values(7)
HUND = values(8)
C =================================================
C
C Incompitable function => CALL GETDAT(YEAR,MON,DAY)
C Incompitable function => GETTIM(HR,MINUTE,SEC,HUND)
IF(HR .GE. 12)THEN
IF(HR .NE. 12)HR=HR-12
DY='PM'
ELSE
DY='AM'
ENDIF
WRITE(DTSTR,10)MON,DAY,YEAR,HR,MINUTE,DY,' ]'
10 FORMAT('[ ',I2,'-',I2.2,'-',I4,2X,I2,':',I2.2,1X,2A2)
RETURN
END
Hmm? It works just fine for me:
program testwrite
implicit none
INTEGER :: MON,DAY,YEAR,HR,MINUTE,SEC,HUND
CHARACTER(LEN=2) :: DY
CHARACTER(LEN=24) :: DTSTR
MON = 4
DAY = 27
YEAR= 2010
HR = 13
MINUTE = 27
SEC = 0
HUND = 0
DY ='WE'
WRITE(DTSTR,10)MON,DAY,YEAR,HR,MINUTE,DY,' ]'
10 FORMAT('[ ',I2,'-',I2.2,'-',I4,2X,I2,':',I2.2,1X,2A2)
print *,'<',trim(DTSTR),'>'
end program testwrite
gives
<[ 4-27-2010 13:27 WE ]>
just as one would expect. Works with several versions of gfortran I have kicking around.
Update: Yes, the problem is in your common block. The common block isn't declared in the main program. But really, it's much simpler and much, much better practice just to pass the string as an argument:
PROGRAM HELO
IMPLICIT NONE
CHARACTER(LEN=24) :: DTSTR
CALL DOTIME(DTSTR)
WRITE(*,5700)DTSTR
5700 FORMAT(24X,A24/)
END
SUBROUTINE DOTIME(DTSTR)
C
IMPLICIT NONE
INTEGER*2 MON,DAY,YEAR,HR,MINUTE,SEC,HUND
CHARACTER DY*2
CHARACTER(LEN=24), INTENT(OUT) :: DTSTR