Compiler won't calculate variable unless I print it"" - fortran

So apparently, depending in wether i tell the program to print the variable i, or not, I get different results that should not have anything to do with wether i print it our or not.
PROGRAM hello
IMPLICIT NONE
integer :: n,i, mini
logical :: leave = .false.
read*, n
print*, is_prime(n)
!!---------------------------------------------------------------------
do i=n, n/2, -1
print*, "I= ", i !!if you comment out this line, the result will be different than if you were to keep it, try it out yourselves
if(is_prime(i)) then
mini = i
end if
end do
print*, "the lowest prime number between your number and its half is: ", mini
!!----------------------------------------------------------
CONTAINS
logical function is_prime(n)
integer::n,i
do i=2,n
if(mod(n,i) == 0 .and. (i/=1 .and. i/=n) ) then
is_prime = .false.
elseif(mod(n,i) /=0 .and. i == n-1 .and. is_prime .neqv. .false.) then
is_prime = .true.
end if
end do
return
end function
END PROGRAM
So if you were to comment out the line I pointed out, the result of "mini" will be different than if you were to keep it, as I said.
I'm fairly new at fortran so I don't know wether I'm doing something wrong, or if this has something to do with the compiler, but it seems really weird to me that putting a print*, line would in any way change the value of the variabe, and that's what seems to happen.
For example if you try it yourselve, the output of mini when the print line is in, is for exaple,, typing in 48, is 29, which is right, it's the minimum prime number between 48 and ts half, but when you tipe in 48 and the famous print line is commented out, the output will be -2, instead of 29.
Any of you know why this happenes?

#francescalus is right, the logic of is_prime is wrong.
You can tell by checking the first result (the print *, is_prime(n)) of the program.
Below, a version with a correct is_prime. I first assign .true. to the result and invalidate it to .false. when the test is true.
PROGRAM hello
IMPLICIT NONE
integer :: n,i, mini
read*, n
print*, is_prime(n)
!!---------------------------------------------------------------------
do i=n, n/2, -1
print*, "I= ", i
if(is_prime(i)) then
mini = i
end if
end do
print*, "the lowest prime number between your number and its half is: ", mini
!!----------------------------------------------------------
CONTAINS
logical function is_prime(n)
integer, intent(in) :: n
integer :: i
is_prime = .true.
do i=2,n
if(mod(n,i) == 0 .and. (i/=1 .and. i/=n) ) then
is_prime = .false.
end if
end do
end function is_prime
END PROGRAM
EDIT: I should add that the issue with the influence of the print statement comes up from time to time. When it arises, it points to a flaw in the logic of the code that then becomes sensitive to situations of ill-defined results.

Related

Getting the prime numbers till 10000 in fortran?

Im trying to print prime numbers till 10000. (display the first five for testing)
This is my program
program primes
implicit none
integer :: array(1229)
integer :: i, ind
logical :: is_prime
ind = 1
do i = 2, 10000, 1
if (is_prime(i) .eqv. .true.) then
array(ind) = i
ind = ind + 1
end if
end do
print *, array(1)
print *, array(2)
print *, array(3)
print *, array(4)
print *, array(5)
end program primes
function is_prime(n) result(ispr)
implicit none
integer :: c, i
integer, intent(in) :: n
logical :: ispr
c = 0
do i = 2, n
if (mod(i,2) == 0) then
c = c + 1
end if
end do
ispr = (c == 0)
end function is_prime
I don't know why but this is the output
9175178
6417360
5374044
6750309
7536745
Why does this happen and how to correct?
is_prime should be(n is the only divider of n besides 1 <=> c == 1)
function is_prime(n) result(ispr)
implicit none
integer :: c, i
integer, intent(in) :: n
logical :: ispr
c = 0
do i = 2, n
if (mod(n,i) == 0) then
c = c + 1
end if
end do
ispr = (c == 1)
end function is_prime
Could be optimezed by leaving the loop when c == 1 and i < n(after adding 1 to c)...
See on online fortran compiler
version with exit loop
While I am not familiar with modern Fortran, it looks to me as if function is_prime(n) result(ispr) is not working.
In the do loop in that function, you want a loop that tests thus:
is n divisible by 2?
is n divisible by 3?
is n divisible by 4?
is n divisible by 5?
and so on.
But, what it is actually doing is asking these:
is 2 divisible by 2?
is 3 divisible by 2?
is 4 divisible by 2?
is 5 divisible by 2?
and so on.
As a result, your counter will always have a non-zero value, and your function will always return false.
But, that's not the only problem. From your results, it looks like your Fortran implementation does not automatically initialize variables. Suppose I have statements like the following:
integer :: b
print *,b
What will be the result?
Remember, the names of variables represent locations in the computer's memory. If a variable is not initialized, it's value will be what was in the memory location before your program started to run. This value will not be related to your program.
I have 2 suggestions to fix the 2nd problem:
Prior to do i = 2, 10000, 1, have another loop that sets each value in array.
Set a values of each array (i) inside your do i = 2, 10000, 1 loop. One way to do this is to set one value when (is_prime(i) .eqv. .true.) is true and a different value when it is false.

How can I create code for specific variable?

I want to embed a code for Fortran 95.
For example: I have read an integer variable
read *, x
for instance x=4. and my source creates four loop which has four loop variable
loop1:do a=1,16
loop2:do b=1,16
loop3:do c=1,16
loop4:do d=1,16
........smt......
end do loop4
end do loop3
end do loop2
end do loop1
I'm working on a such a code that tries for finding a magic square. I can find a magic code by using a algorithm for odd numbered square matrices. probably, I also can generate a magic square which is even numbered and double-even numbered. however , I'm trying to improve my coding skills by writing a program that tries element by element to find magic square.
implicit integer (a-z)
counte=possibility counter , magcon=magic square generated counter
god and devil are logical variables. But I used them as integer.
integer GG(3,3),COUNTE,magcon
integer god,devil
open(55,file='mymagics')
COUNTE=0
magcon=0
loop1:do a=9,1,-1
loop2:do b=9,1,-1
loop3:do c=9,1,-1
loop4:do d=9,1,-1
loop5:do e=9,1,-1
loop6:do f=9,1,-1
loop7:do g=9,1,-1
loop8:do h=9,1,-1
loop9:do i=9,1,-1
these loops are for evaluating elements
GG(1,1)=a
GG(1,2)=b
GG(1,3)=c
GG(2,1)=d
GG(2,2)=e
GG(2,3)=f
GG(3,1)=g
GG(3,2)=h
GG(3,3)=i
call elementcontrol(gg,devil)
if(devil.eq.1)then
call magiccontrol(GG,god)
else if(devil.eq.0) then
cycle
endif
COUNTE=COUNTE+1
if(allah.eq.1) then
magcon=magcon+1
write(55,66)
write(55,*) counte ,"possibility is tried"
write(55,*)"**************************************"
write(55,*)"**************************************"
write(55,*)"**************************************"
write(55,*)"--------------------------------------"
write(55,*)GG(1,1),GG(1,2),GG(1,3)
write(55,*)GG(2,1),GG(2,2),GG(2,3)
write(55,*)GG(3,1),GG(3,2),GG(3,3)
write(55,*)"--------------------------------------"
write(55,*)"**************************************"
write(55,*)"**************************************"
write(55,*)"**************************************"
write(55,66)
66 format(//)
else
print *, counte ,"possibility is unvalid"
end if
enddo loop9
enddo loop8
enddo loop7
enddo loop6
enddo loop5
enddo loop4
enddo loop3
enddo loop2
enddo loop1
print *, "finally done!"
print *, magcon,"magic square is found"
stop
end
subroutine magiccontrol(magic,logic)
integer logic,z
integer magic(3,3),sumrow(3),sumcol(3),sumdia(2)
these are row,column and diagonal sum finder
do z=1,3
sumrow(z)=0
sumcol(z)=0
sumdia(z)=0
end do
do 31 k=1,3
do 31 l=1,3
sumrow(k)=sumrow(k)+(magic(k,l))
31 continue
do 52 m=1,3
do 52 n=1,3
sumcol(m)=sumcol(m)+(magic(n,m))
52 continue
do 69 i=1,3
sumdia(1)=sumdia(1)+magic(i,i)
sumdia(2)=sumdia(2)+magic((4-i),i)
69 continue
loop1:do y=1,3
loop2:do f=1,3
loop3:do x=1,2
if(sumrow(y).eq.15) then
if(sumcol(f).eq.15)then
if(sumdia(x).eq.15)then
logic=1
else
logic=0
exit loop1
end if
else
logic=0
exit loop1
end if
else
logic=0
exit loop1
end if
end do loop3
end do loop2
end do loop1
15 is magic constant. loops are for evaluate whether a aquare is magic or not.
end
subroutine elementcontrol(elecon,logic2)
integer elecon(3,3),a1,a2,a3,a4,a5,a6,coun(9)
do a4=1,9
coun(a4)=0
end do
logic2=0
do a1=1,9
do a2=1,3
do a3=1,3
if(a1.eq.elecon(a2,a3))then
coun(a1)=coun(a1)+1
end if
end do
end do
end do
do a5=1,9
do a6=1,9
if(a5.ne.a6) then
if(coun(a5).eq.coun(a6)) then
logic2=1
else
logic2=0
exit
end if
else
cycle
end if
end do
end do
there loops are to evaluate whether every element is different from each other or not.
end
Now the problem is that if I will be inclined to increase number of rows and columns of magic square, I have to rewrite element specifier loops. But I'm not willing to that. So I want to declare a variable,read it , and be able to make program create do loops as read.
I wish I was crystal clear about what I want to know.
The test could look something like this:
LOGICAL FUNCTION IsMagical(dim_o_square, SquareData)
IMPLICIT NONE
INTEGER , INTENT(IN ) :: Dim_o_Square
REAL, DIMENSION(Dim_o_Square, Dim_o_Square), INTENT(IN ) :: SquareData
REAL, DIMENSION(Dim_o_Square) :: Row_Sum, Col_Sum
REAL :: Diag_Sum
IsMagical = .FALSE.
INTEGER :: I
IF(Dim_o_Square < 2) THEN
WRITE(*,*) '[SubMagic?:line10] DIMENSION of square is hosed'
RETURN
ENDIF
! Fill the data to determine PFM'ness
DIAG = 0
DO I = 1, Dim_o_Square
COL_Sum(I) = SUM(SquareData(:,I))
ROW_Sum(I) = SUM(SquareData(I,:))
DIAG_Sum = Diag + SquareData(I,I)
ENDDO
! Test for PFM'ness
DO I = 2, Dim_o_Square
IF( COL(I) /= Diag .OR. ROW(I) /= Diag ) THEN
RETURN
ENDIF
ENDDO
!Must be magical at this point...
IsMagical = .TRUE.
WRITE(*,*) '[SubMagic?:line40] Magical and sum value (Row/Col/Diag)=', DIAG_Sum
RETURN
END FUNCTION IsMagical
Perhaps there is some carry over in concepts for producing the square?

Do-loop ignores if-statement

I'm trying to use an if statement in a do loop which is supposed to generate prime numbers. For that I used modulo to sort out the numbers. After it found a prime number I want it to go a step further and add 1 so that the next prime number can be found and added to the array pzahl. My problem is that the loop seems to ignore that it should go a step further with plauf after it found a prime number so that it just keeps going till infinity... I tried to rearrange the contents of the loop and if statement but it's just not working. Here is the code:
PROGRAM Primzahlen
IMPLICIT NONE
INTEGER :: start, plauf, n, a
INTEGER, ALLOCATABLE, DIMENSION(:) :: pzahlen !array into which the prime numbers should be added
INTEGER :: input
INTEGER, DIMENSION(:), ALLOCATABLE :: alle
PRINT *, "How many prime numbers should be listed"
READ (*,*) input
ALLOCATE (pzahlen(input))
pzahlen(1) = 1
start = 2
plauf = 1
loop1: DO
ALLOCATE(alle(start))
loop2: DO n = 1,start
alle(n)= MODULO(start,n)
END DO loop2
IF (minval(alle) /= 0) THEN ! This is what it seems to ignore.
plauf= plauf + 1
pzahlen(plauf) = start
PRINT *, plauf
END IF
start = start + 1
IF (plauf == eingabe) then
EXIT
END IF
PRINT *, alle
DEALLOCATE(alle)
END DO loop1
PRINT *, "prime numbers:" , pzahlen(1:input)
END PROGRAM Primzahlen
I use the gfortran compiler and write it in Emacs if that helps to know.
It's not ignoring it, it executes correctly:
loop2: DO n = 1,start
alle(n)= MODULO(start,n)
END DO loop2
It doesn't matter what start is, alle(1) will always be zero, as every integer is evenly divisible by 1. That means that minval(alle) will also always be zero, which means that the condition minval(alle) /= 0 is never true, and the statement will never execute.
Added: The last value, alle(start), will also be zero, as every number is evenly divisible by itself.

FORTRAN logic notproblem

If I just use my function once, it works properly. If I make it do a loop like down below, the four lines of commented code, my code malfunctions. I can't really figure out why it will always return T or F for every other number after the initial value.
Asterisks are in the parenthesis of WRITE and READ but it doesn't show up here for some reason.
PROGRAM PRIME
INTEGER :: N = 0, i = 1,x = 0
LOGICAL :: IP
WRITE (*,*) "Enter a number:"
READ (*,*) N
!DO WHILE ( N < 1000)
IP = IsPrime(N)
WRITE (*,*) IP, N
!N = N + 1
!END DO
read(*,*) x
CONTAINS
FUNCTION IsPrime(N)
LOGICAL :: IsPrime
INTEGER, INTENT(IN) :: N
IsPrime = .TRUE.
IF (N == 2) THEN
WRITE (*,*) N
ELSE
DO WHILE (i <= (N/2))
i = i + 2
IF (mod(N,i) == 0) THEN
IsPrime = .FALSE.
END IF
END DO
END IF
RETURN
END FUNCTION IsPrime
END PROGRAM PRIME
You're forgetting to reset i to 1 during each call to IsPrime.
The first time IsPrime is called, i=1 from the top of program main. However, i is incremented during the first IsPrime call to something other than 1 so the second call starts with i/=0.
Note that because IsPrime is contained within program main, IsPrime inherits i from program main.
I'm also bound to remind you to use implicit none everywhere to avoid other errors, although it's not a problem in this case.

Whats wrong with my Hermite Interpolation in Fortran?

Hermite Interpolation woes
I am trying to find the Newton Dividing Differences for the function and derivative values of a given set of x's. I'm running into serious problems with my code working for tiny examples, but failing on bigger one's. As is clearly visible, my answers are very much larger than they original function values.
Does anybody have any idea what I'm doing wrong?
program inter
implicit none
integer ::n,m
integer ::i
real(kind=8),allocatable ::xVals(:),fxVals(:),newtonDivDiff(:),dxVals(:),zxVals(:),zdxVals(:),zfxVals(:)
real(kind=8) ::Px
real(kind=8) ::x
Open(Unit=8,File="data/xVals")
Open(Unit=9,File="data/fxVals")
Open(Unit=10,File="data/dxVals")
n = 4 ! literal number of data pts
m = n*2+1
!after we get the data points allocate the space
allocate(xVals(0:n))
allocate(fxVals(0:n))
allocate(dxVals(0:n))
allocate(newtonDivDiff(0:n))
!allocate the zvalue arrays
allocate(zxVals(0:m))
allocate(zdxVals(0:m))
allocate(zfxVals(0:m))
!since the size is the same we can read in one loop
do i=0,n
Read(8,*) xVals(i)
Read(9,*) fxVals(i)
Read(10,*) dxVals(i)
end do
! contstruct the z illusion
do i=0,m,2
zxVals(i) = xVals(i/2)
zxVals(i+1) = xVals(i/2)
zdxVals(i) = dxVals(i/2)
zdxVals(i+1) = dxVals(i/2)
zfxVals(i) = fxVals(i/2)
zfxVals(i+1) = fxVals(i/2)
end do
!slightly modified business as usual
call getNewtonDivDiff(zxVals,zdxVals,zfxVals,newtonDivDiff,m)
do i=0,n
call evaluatePolynomial(m,newtonDivDiff,xVals(i),Px,zxVals)
print*, xVals(i) ,Px
end do
close(8)
close(9)
close(10)
stop
deallocate(xVals,fxVals,dxVals,newtonDivDiff,zxVals,zdxVals,zfxVals)
end program inter
subroutine getNewtonDivDiff(xVals,dxVals,fxVals,newtonDivDiff,n)
implicit none
integer ::i,k
integer, intent(in) ::n
real(kind=8), allocatable,dimension(:,:) ::table
real(kind=8),intent(in) ::xVals(0:n),dxVals(0:n),fxVals(0:n)
real(kind=8), intent(inout) ::newtonDivDiff(0:n)
allocate(table(0:n,0:n))
table = 0.0d0
do i=0,n
table(i,0) = fxVals(i)
end do
do k=1,n
do i = k,n
if( k .eq. 1 .and. mod(i,2) .eq. 1) then
table(i,k) = dxVals(i)
else
table(i,k) = (table(i,k-1) - table(i-1,k-1))/(xVals(i) - xVals(i-k))
end if
end do
end do
do i=0,n
newtonDivDiff(i) = table(i,i)
!print*, newtonDivDiff(i)
end do
deallocate(table)
end subroutine getNewtonDivDiff
subroutine evaluatePolynomial(n,newtonDivDiff,x,Px,xVals)
implicit none
integer,intent(in) ::n
real(kind=8),intent(in) ::newtonDivDiff(0:n),xVals(0:n)
real(kind=8),intent(in) ::x
real(kind=8), intent(out) ::Px
integer ::i
Px = newtonDivDiff(n)
do i=n,1,-1
Px = Px * (x- xVals(i-1)) + newtonDivDiff(i-1)
end do
end subroutine evaluatePolynomial
Values
x f(x) f'(x)
1.16, 1.2337, 2.6643
1.32, 1.6879, 2.9989
1.48, 2.1814, 3.1464
1.64, 2.6832, 3.0862
1.8, 3.1553, 2.7697
Output
1.1599999999999999 62.040113431002474
1.3200000000000001 180.40121445431600
1.4800000000000000 212.36319446149312
1.6399999999999999 228.61845650513027
1.8000000000000000 245.11610836104515
You are accessing array newtonDivDiff out of bounds.
You are first allocating it as 0:n (main program's n) then you are passing to subroutine getNewtonDivDiff as 0:n (the subroutine's n) but you pass m (m=n*2+1) to the argument n. That means you tell the subroutine that the array has bounds 0:m which is 0:9, but it has only bounds 0:4.
It is quite difficult to debug the program as it stands, I had to use valgrind. If you move your subroutines to a module and change the dummy arguments to assumed shape arrays (:,:) then the bound checking in gfortran (-fcheck=all) will catch the error.
Other notes:
kind=8 is ugly, 8 can mean different things for different compilers. If you want 64bit variables, you can use kind=real64 (real64 comes from module iso_fortran_env in Fortran 2008) or use selected_real_kind() (Fortran 90 kind parameter)
You do not have to deallocate your local arrays in the subroutines, they are deallocated automatically.
Your deallocate statement in the main program is after the stop statement, it will never be executed. I would just delete the stop, there is no reason to have it.