Values of numbers being lost (changed) when called in subroutine - fortran

I have written two .f90 text files prog1.f90:
PROGRAM prog1
READ (5,*) A,B,C
PRINT*, "A = ",A
PRINT*, "B = ",B
PRINT*, "C = ",C
CALL test(A,B,C)
END PROGRAM prog1
and aux.f90
SUBROUTINE test(E,F,G)
real(kind=8) :: E,F,G
PRINT*,"E = ",E
PRINT*,"F = ",F
PRINT*,"G = ",G
END SUBROUTINE test
Which are compiled using the Makefile:
FC = gfortran
FCFLAGS = -g -fbounds-check
FCFLAGS = -O2
FCFLAGS += -I/usr/include
PROGRAMS = prog1
all: $(PROGRAMS)
prog1: aux.o
%: %.o
$(FC) $(FCFLAGS) -o $# $^ $(LDFLAGS)
%.o: %.f90
$(FC) $(FCFLAGS) -c $<
%.o: %.F90
$(FC) $(FCFLAGS) -c $<
.PHONY: clean veryclean
clean:
rm -f *.o *.mod *.MOD
veryclean: clean
rm -f *~ $(PROGRAMS)
I use this makefile to compile prog1 and then run prog1 with the input file input.inp:
0.0033943878 0.0018085515 0.0011798956
I expect the output of this code to be
A = 0.339439E-02
B = 0.180855E-02
C = 0.117990E-02
E = 0.339439E-02
F = 0.180855E-02
G = 0.117990E-02
However it is:
A = 0.339439E-02
B = 0.180855E-02
C = 0.117990E-02
E = 0.100765847236215E-21
F = 0.750936901926887E-24
G = 0.261410786221168-313
The number are much much smaller in the subroutine and seem to have no logical connection to the original A,B and C and are returned from the subroutine as such.
I take it my error is to do with the type I am storing these numbers as, i.e. they are not read in as real(kind=8) but are being converted into this type causing the error but I am not sure what the type should be in the subroutine or if this is even the cause. I may just be missing something obvious.
Any help would be appreciated and please tell me if I need to clarify anything I have written.
Thank you for your time.
James

You made the common error to forget the IMPLICIT NONE statement at the beginning of your program. (At least, it is heavily recommended to avoid this kind of error.)
As a result, all variables starting with I, J, K, L, M or N are of type INTEGER(4) and all other variables of type REAL(4). This means, that your variables A, B and C are of REAL(4). Passing them to the subroutine results in principle in an undetected type mismatch which results in misinterpreted values.
You should always place IMPLICIT NONE at the beginning of your programs and modules to be forced to specify explicit types for your variables!

I think I have fixed this error by correcting prog1.f90:
PROGRAM prog1
real(kind=8) :: A,B,C
READ (5,*) A,B,C
PRINT*, "A = ",A
PRINT*, "B = ",B
PRINT*, "C = ",C
CALL test(A,B,C)
END PROGRAM prog1

Related

Fortran code gives outputs with only certain files

I have 4 .mtx files that I am reading the values from. Two of them run perfectly when read from with no issues and produce the correct outputs into a .DAT file. However, the last 2 are extremely large files; it appears the code correctly reads from the files and runs, but I get no outputs and no errors when reading from these 2...not even the code timer prints the time. Any help is much appreciated! Here is the code:
program proj2matrixC40
implicit none
integer,parameter::dp=selected_real_kind(15,307)
! Set Global Variables
real(kind=dp), allocatable::Ax(:,:),A(:,:),Iglobal(:,:)
integer::At(1,3)
integer::nnz,w,n,k,ii,ff,kk
real(kind=dp)::t1,t2
call cpu_time(t1)
open(unit=78,file="e40r5000.mtx",status='old')
read(78,*) At
close(unit=78)
nnz = At(1,3)
n = At(1,1)
k = 40
kk = 35
allocate(Ax(nnz+1,3),A(nnz,3),Iglobal(k,k))
open(unit=61,file="e40r5000.mtx",status='old')
do w=1,nnz+1
read(61,*) Ax(w,:)
end do
open (unit = 53, file = "proj2matrixC40points.dat")
do ff=1,k
do ii=1,k
Iglobal(ii,ff) = (ii/ff)*(ff/ii)
end do
end do
A(1:nnz,:) = Ax(2:nnz+1,:)
call Arno(A)
call cpu_time(t2)
print '("Time elapsed = ",f10.8," seconds")', (t2 - t1)
contains
subroutine Arno(a)
real(kind=dp), intent(in)::a(:,:)
real(kind=dp),dimension(k,k)::H
real(kind=dp),dimension(k,k+1)::u,q,qconj
real(kind=dp),dimension(k,1)::x0
integer::j,f
call random_number(x0)
q(:,1) = x0(:,1)/norm2(x0(:,1))
do f=1,k
call spmat(a,q(:,f),u(:,f))
do j=1,f
qconj(j,:) = (q(:,j))
H(j,f) = dot_product(qconj(j,:),u(:,f))
u(:,f) = u(:,f) - H(j,f)*q(:,j)
end do
if (f.lt.k) then
H(f+1,f) = norm2(u(:,f))
if (H(f+1,f)==0) then
print *, "Matrix is reducible"
stop
end if
q(:,f+1) = u(:,f)/H(f+1,f)
end if
if (f==k) then
call qrit(H)
end if
end do
end subroutine
! QR Iteration with Shifts Subroutine
subroutine qrit(a)
real(kind=dp), intent(in)::a(:,:)
real(kind=dp)::sigmak
real(kind=dp),dimension(kk,k)::dia
real(kind=dp),dimension(k,k)::Qfinal,Rfinal,HH
real(kind=dp),dimension(k,k,kk)::H0,needQR
integer::v,z
HH = a
H0(:,:,1) = HH
do v=1,kk
sigmak = H0(k,k,v)
if (v-1==0) then
needQR(:,:,v) = HH - sigmak*Iglobal
else
needQR(:,:,v) = H0(:,:,v-1) - sigmak*Iglobal
end if
call givens2(needQR(:,:,v),Rfinal,Qfinal)
H0(:,:,v) = matmul(Rfinal,Qfinal) + sigmak*Iglobal
do z = 1,k
dia(v,z) = H0(z,z,v)
write(53,*) v," ", dia(v,z) ! Write values to .DAT file
end do
end do
end subroutine
! Sparse Matrix Vector Multiplication Subroutine
subroutine spmat(a,b,c)
real(kind=dp), intent(in)::a(:,:)
real(kind=dp), intent(in), dimension(k,1)::b
real(kind=dp), intent(out), dimension(k,1)::c
integer::m,rowi,columni
real(kind=dp), dimension(k,1)::x,y
x = b
y(:,1) = 0
do m = 1,nnz
rowi = a(m,1)
columni = a(m,2)
y(rowi,1) = y(rowi,1) + a(m,3)*x(columni,1)
end do
c(:,1) = y(:,1)
end subroutine
! QR Factorization Givens Rotations Subroutine
subroutine givens2(a,Rfinal,Qfinal)
real(kind=dp), intent(in)::a(:,:)
real(kind=dp), dimension(k,k,(k*k))::G,QQ
real(kind=dp), dimension(k,k), intent(out)::Rfinal,Qfinal
real(kind=dp), dimension(k,k)::I2,y,aa
real(kind=dp), dimension(1,k)::ek1,ek2
real(kind=dp)::c,s
integer::kt,m,nn,j,i,l,p
m = size(a,1)
nn = size(a,2)
aa = a
i = 1
do kt=1,nn-1
do j=m,kt+1,-1
if (aa(j,kt).eq.0) then
continue
else
ek1(1,:) = 0
ek2(1,:) = 0
do p=1,m
do l=1,m
I2(l,p) = (l/p)*(p/l)
end do
end do
c = aa(kt,kt)/sqrt(aa(kt,kt)**2 + aa(j,kt)**2)
s = aa(j,kt)/sqrt(aa(kt,kt)**2 + aa(j,kt)**2)
ek1(1,kt) = c
ek1(1,j) = s
ek2(1,kt) = -s
ek2(1,j) = c
I2(kt,:) = ek1(1,:)
I2(j,:) = ek2(1,:)
G(:,:,i) = I2
if (i.eq.1) then
QQ(:,:,i) = G(:,:,i)
else
QQ(:,:,i) = matmul(G(:,:,i),QQ(:,:,i-1))
end if
y = matmul(G(:,:,i),aa)
aa = y
if (kt.eq.nn-1) then
if (j.eq.kt+1) then
Qfinal = transpose(QQ(:,:,i))
Rfinal = aa
end if
end if
i = i + 1
end if
end do
end do
end subroutine
end program proj2matrixC40
A couple notes. The line which I put asterisks around (for this question) call mat_print('H',H) can't be deleted otherwise I get the wrong answers (this is strange...thoughts?). Also so your computer won't freeze opening the big files, their names are 'e40r5000.mtx' and 's3dkt3m2.mtx' (these are the two I have issues with). I am using gfortran version 8.1.0
Here is the link to the files
https://1drv.ms/f/s!AjG0dE43DVddaJfY62ABE8Yq3CI
When you need to add a call to a subroutine that shouldn't actually change anything in order to get things working, you probably have a memory corruption. This happens most often when you access arrays outside of their boundaries.
I have compiled it with some run time checks:
gfortran -o p2m -g -O0 -fbacktrace -fcheck=all -Wall proj2mat.f90
And it's already giving me some issues:
It's warning me about implicit type conversions. That shouldn't be too much of an issue if you trust your data.
In line 46 you have an array length mismatch (x0(:, 1) has length 40, q(:,1) is 41)
Similarly on line 108 (x=b) x is really large, but b is only 41 long.
I have stopped now, but I implore you to go through your code and clean it up. Use the compiler options above which will let you know when and where there is an array bound violation.

GCC (MingW) + LD generate nearly empty executable. Why?

For a specific requirement, I need my binary to fall below 510bytes.
Doing the program in assembler, I get <100 bytes, while adding same code in C++, the resulting code is over 1K. Looking the resulting binary, mostly all ( + 90%) is full of 0x00 characters (Only a few characters at the beginning and end are really populated).
Currently building commands:
gcc -Wall -Os -s -Wl,--stack,32 -nostdinc -nostdinc++ -fno-ident -fno-builtin -I. -c -o cppFile.coff cppFile.cpp
nasm -f elf -o main.elf main.asm
ld -T link.ld -o out.elf main.elf cppFile.coff
objcopy -O binary out.elf out.bin
Size of files generated:
cppFile.coff = 684 bytes
main.elf = 640
out.elf = 2707
out.bin = 1112
When not linking to the cppFile.coff (with only one empty function)
out.elf = 1984
out.bin = 31 (tested and working)
Why GCC or LD add so many nul charactres?
How to remove this empty space?
ENTRY(start)
phys = 0x7c00;
HEAP_SIZE = 0;
SECTIONS
{
.text phys : AT(phys) {
code = .;
*(.text)
*(.rodata)
}
.data : AT(phys + (data - code))
{
data = .;
*(.data)
}
.bss : AT(phys + (bss - code))
{
bss = .;
*(.bss)
}
end = .;
}

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 //.

OCaml : Unbound Module.function value

I'm new to OCaml and I am a little confused about Modules.
I tried to implement a really simple test but I can't compile it...
Here are the files (I'm on Linux by the way) :
main.ml
let main () =
if ((Array.length Sys.argv) > 2 && int_of_string Sys.argv.(1) > 1 && int_of_string Sys.argv.(2) > 1)
then
begin
Printf.printf "Args = %d && %d\n" (int_of_string Sys.argv.(1)) (int_of_string Sys.argv.(2));
Laby.initLaby (int_of_string Sys.argv.(1)) (int_of_string Sys.argv.(2))
end
else
Printf.printf "Usage : ./test x y n"
let _ = main ()
Laby.ml
let initLaby (x : int) (y : int) =
let testCell = Cell.initCell 0 1 in
begin
Printf.printf "Init Laby with X(%d) / Y(%d)\n" x y;
Cell.printCell testCell;
end
Cell.ml
module type CELL =
sig
type t
val initCell : int -> int -> t
val printCell : t -> unit
end
module Cell : CELL =
struct
type t = (int * int)
let initCell (x : int) (y : int) =
(x, y)
let printCell (x, y) =
Printf.printf "Cell -> X(%d) / Y(%d)\n" x y
end
Cell.mli
module type CELL =
sig
type t
val initCell : int -> int -> t
val printCell : t -> unit
end
module Cell : CELL
And here is the Makefile :
NAME = test
ML = Cell.ml \
Laby.ml \
main.ml
MLI = Cell.mli
CMI = $(MLI:.mli=.cmi)
CMO = $(ML:.ml=.cmo)
CMX = $(ML:.ml=.cmx)
OCAMLDPE = ocamldep
CAMLFLAGS = -w Aelz -warn-error A
OCAMLC = ocamlc $(CAMLFLAGS)
OCAMLOPT = ocamlopt $(CAMLFLAGS)
OCAMLDOC = ocamldoc -html -d $(ROOT)/doc
all: .depend $(CMI) $(NAME)
byte: .depend $(CMI) $(NAME).byte
$(NAME): $(CMX)
#$(OCAMLOPT) -o $# $(CMX)
#echo "[OK] $(NAME) linked"
$(NAME).byte: $(CMO)
#$(OCAMLC) -o $# $(CMO)
#echo "[OK] $(NAME).byte linked"
%.cmx: %.ml
#$(OCAMLOPT) -c $<
#echo "[OK] [$<] builded"
%.cmo: %.ml
#$(OCAMLC) -c $<
#echo "[OK] [$<] builded"
%.cmi: %.mli
#$(OCAMLC) -c $<
#echo "[OK] [$<] builded"
documentation: $(CMI)
#$(OCAMLDOC) $(MLI)
#echo "[OK] Documentation"
re: fclean all
clean:
#/bin/rm -f *.cm* *.o .depend *~
#echo "[OK] clean"
fclean: clean
#/bin/rm -f $(NAME) $(NAME).byte
#echo "[OK] fclean"
.depend:
#/bin/rm -f .depend
#$(OCAMLDPE) $(MLI) $(ML) > .depend
#echo "[OK] dependencies"
Here is the output of the Makefile :
[OK] dependencies
[OK] [Cell.mli] builded
[OK] [Cell.ml] builded
File "Laby.ml", line 3, characters 17-30:
Error: Unbound value Cell.initCell
Makefile:47: recipe for target 'Laby.cmx' failed
make: *** [Laby.cmx] Error 2
I think it's a compilation error, since it seems to not found the Cell module, but I can't make it works...
What am I doing wrong, and how can I fix it?
Each .ml file serves as its own module. You seem to have module Cell inside cell.ml which is double. You would have to address that function as Cell.Cell.initCell. Or open Cell in laby.ml. Also, I think .ml file names are conventionally lowercase? Aside: why does make output wrong english?

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

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)?