Fortran Fortran Forum for Programming Help: Resources, Tips, and Support

  • Thread starter Thread starter FUNKER
  • Start date Start date
  • Tags Tags
    Fortran Forum
Click For Summary
The discussion revolves around programming in Fortran, specifically addressing issues related to Fortran 77 and 90/95. A user seeking help with array declarations and common blocks encounters multiple errors in their code. Key points include the importance of correctly declaring arrays and understanding the limitations of common blocks in Fortran. It is emphasized that array dimensions must be defined using integer values, and the use of floating-point numbers for array sizes is incorrect. The conversation also touches on the need for proper syntax, such as starting code lines in the correct column to avoid compilation errors. Users are advised to break down their programming tasks into manageable steps, utilize pseudocode for clarity, and compile code frequently to identify errors early. Additionally, there are discussions about the inability to dynamically allocate memory in Fortran 77, contrasting it with more modern versions that allow for such flexibility. The thread concludes with inquiries about breaking loops in subroutines and plotting functions, indicating ongoing challenges faced by users in mastering Fortran programming.
  • #61
mathmate said:
Try it with the corrected parameter values and post what you see!
I TRIED THIS CODE
PHP:
mplicit none
	integer		i,j,n,m,mp,np
        parameter    (mp = 450,np = 450)     
        REAL*8       x(mp,np),v(np,np),w(np)
c        
        write(*,*) 'Enter the arrays elements'
        read(*,*) m,n
        do  i=1, m
           do  j=1, n
               read(*,*) x(i,j)
           end do
       end do 
       call svdcmp(x,m,n,mp,np,w,v)
       do  i=1, n
           print*, w(i)
           print*, v(i,i)
       end do 
       end
c
c
c-----------------------------------
        include 'SVDCMP.F'[PHP]

actually I have tried already and I've got this error
[PHP]PAUSE  no convergence in svdcmp statement executed
To resume execution, type go.  Other input will terminate the job.
 
Last edited:
Technology news on Phys.org
  • #62
PHP:
URGENT
anyone can tell me how to include NAG FORTRAN Library Routinein my code?I mean for example for the numerical recipes we just do include 'file name.f' at the end of the main program, but for NAG ROUTINES I know I need to amend the parameters of the subroutine according to my needs, but how to put them in the main program??/
 
  • #63
anyone can tell me how to include NAG FORTRAN Library Routinein my code?

NAG comes with installation manuals, depending on the version (MARK 19,20 or 21) and the computer (CRAY, Linux, DEC/VMS, Sun/Sparc, Siligon Graphics, etc.)
The installation instructions can be found here:
http://www.nag.co.uk/numeric/FL/FLinuns.asp

The routines are generally compiled for use on the respective machines in object/binary form. So if it is properly installed, you just have to make the calls with the right parameters as shown in the users manual, in much the same way you'd make the calls to sin and cos. You would not be tagging a source code at the end of your program nless you paid for the source code although I don't see that option on the price list. In any case, many of these routines have dependencies and many of them could have been written in assembler or C.

Which fortran are you running, fortran 77 or fortran 90? I don't see F77 on the NAG product list, but it doesn't mean that it is not available.
 
  • #64
PAUSE no convergence in svdcmp statement executed
To resume execution, type go. Other input will terminate the job.

Usually this means a logical error, meaning that
1. The input data is incorrect
2. The input data is correct, but the solution does not converge.
3. There is a programming error, or the inappropriate routine has been called.

It would be difficult for a third party to figure out which problem you have without a knowledge of the problem you are trying to solve, a proper understanding of your data, and a verification of the program that makes the call.

We can give it a try if you provide more information, perhaps someone else can help too.
 
  • #65
mathmate said:
We can give it a try if you provide more information, perhaps someone else can help too.
I ma trying to calculate the singular value decomposition of a given matrix, that is what I NEED TO DO, so any help to figure out the mistake in the programme in thread 61
 
Last edited:
  • #66
Do you use a Cray? Sometimes when the computer's registers have more precision than the variable, the comparison of REAL values could be thrown off. One suggested way to get around the problem is to store an intermediate value as a temporary variable before the comparison, thus forcing a rounding to the normal precision.

This rounding problem has been known to cause convergence problems in the SVDCMP code. You could try replacing lines 138 and 139 by
Code:
             TMP=(abs(rv1(l))+anorm)
             if(TMP.eq.anorm)  goto 2
C            if((abs(rv1(l))+anorm).eq.anorm)  goto 2
             TMP=(abs(w(nm))+anorm)
             if(TMP.eq.anorm)  goto 1
C            if((abs(w(nm))+anorm).eq.anorm)  goto 1
and somewhere at the beginning you need to declare TMP as REAL or REAL*8 accordingly.

How big is the matrix? Can you dump the matrix and run it with the c version of svdcmp, just as another possibility?
 
  • #67
mathmate said:
Do you use a Cray? Sometimes when the computer's registers have more precision than the variable, the comparison of REAL values could be thrown off. One suggested way to get around the problem is to store an intermediate value as a temporary variable before the comparison, thus forcing a rounding to the normal precision.

This rounding problem has been known to cause convergence problems in the SVDCMP code. You could try replacing lines 138 and 139 by
Code:
             TMP=(abs(rv1(l))+anorm)
             if(TMP.eq.anorm)  goto 2
C            if((abs(rv1(l))+anorm).eq.anorm)  goto 2
             TMP=(abs(w(nm))+anorm)
             if(TMP.eq.anorm)  goto 1
C            if((abs(w(nm))+anorm).eq.anorm)  goto 1
and somewhere at the beginning you need to declare TMP as REAL or REAL*8 accordingly.

How big is the matrix? Can you dump the matrix and run it with the c version of svdcmp, just as another possibility?
No I am using Linux CenTOS 5, I have give another try with lots of changes ,But IT STILL GIVING ME the same error message
PHP:
PAUSE  no convergence in svdcmp statement executed
To resume execution, type go.  Other input will terminate the job.
[PHP], I had entered a matrix which has a singular value decomposition
 
  • #68
Did you implement the seemingly trivial code change I suggested previously?

Do you have the line:
Code:
         IF (ITS.EQ.30) PAUSE 'No convergence in 30 iterations'
in you code?
Is ITS compared to 30 or is ITS compared to N?
If N exceeds 30, it is possible that the convergence message is false.
 
Last edited:
  • #69
2. is there any suggestion form you experienced guys about rewriting
f77 codes complying with f95 styles?
You can use Michael Metcalf's convert.f90 program at
http://www.slac.stanford.edu/comp/fortran/convert.f90 to convert fixed
to free source form. I think free source form is more readable and
less error−prone. Alan Miller's to_f90.f90 program
Anyone can tell me how to use this suggestion,i mean how to write the command for this job
 
Last edited by a moderator:
  • #70
I am trying to migrate my code from f77 to f95, so need to use the module instead of common blocks, but when I have looked at it, they define the global variable which is contained in the module in a separate file, which I guess does benefit me cos I need to transfer some variables and arrays which I have got them from my main program, then I need to use them in a subroutine, as I need to share these data with such routine

PHP:
need to create a module of variables resulted from my main program then transfer it to the subroutine
 
  • #71
Please can you help me with this code in FORTRAN 95, attached with the errors
Code:
module A
   implicit none
   ! DEFINE GLOBAL DATA
   integer, parameter :: dp=kind(1.0d0)
   integer ::	i,n,n_max
   !   
   integer, parameter :: no=30
   real(kind=dp), parameter :: zero=0,one=1,two=2
   real(dp), dimension(:) :: o,A,r,t,u
   real(dp), allocatable :: z(:)
    n = size(o)
    n = size(A)
    n = size(r)
    n = size(t)
    n = size(u)
   write(*,*) 'Input the dimension of matrix z'
   read(*,*) no_max
   allocate(z(no_max))
   !
   deallocate(z)
end module A
I've written this code as an example of module in F95, but I've got these error message
PHP:
Error: A.f90, line 12: syntax error
       detected at <end-of-statement>@WRITE
*** Malformed statement
*** Malformed statement
*** Malformed statement
*** Malformed statement
[f95 terminated - errors found by pass 1]
Anyone could help me please:frown::cry::cry:
 
  • #72
Hi all!

I'm trying to model a differential equation having to do with free fall, using RK4 and Fortran 90. The equation is:

\ddot{y}(t)=-g\frac{R^2}{y^2}

The code is attached in caidalibre.f90

The big problem is that function f(y,v,t) returns an unexpected value within the main program. Moreover, the program yields results which would indicate the object is ascending, and not descending. Any insight will be greatly appreciated.

Cheers!

PS: I am using

gfortran
Using built-in specs.
Target: powerpc-apple-darwin8.9.0
Configured with: ../gcc-4.3-20070810/configure --enable-threads=posix --enable-languages=fortran
Thread model: posix
gcc version 4.3.0 20070810 (experimental)
 

Attachments

  • #73
It does not seem like you have the latest version of the program.
As it is , the values of g and R have not been tranmitted to function f.
Also the formal parameters v and t have not been used.
Do you have some data to run with?

To solve this DE, wouldn't it be simpler to integrate it w.r.t. y, unless it is an exercise on numerical analysis.
 
  • #74
URGENT anyone give a suggestion how to deal with a segmentation default error when I called a NAG routine in FORTAN 77 code
 
  • #75
It is a problem that can have many causes, mostly because the program is trying to access a part (segment) of the memory where it does not have the permission to read or to write.

If your compiler has a debugging option, activate it to see if it gives more information.
If there is a compiler option to check "arrays out of bounds", activate it even though it may execute slower than without.
Check your linker report to see if there are missing modules or libraries.

If everything else fails, recheck your code to see if the sizes of arrays are large enough, and have the right addresses. Check that the parameters of calls to functions and subroutines correspond in size and type with the formal parameters defined.

Try a reduced sized problem to see if the problem persists, which may give an idea if the problem comes from arrays out of bound or otherwise.

Good luck!
 
  • #76
mathmate said:
It is a problem that can have many causes, mostly because the program is trying to access a part (segment) of the memory where it does not have the permission to read or to write.

If your compiler has a debugging option, activate it to see if it gives more information.
If there is a compiler option to check "arrays out of bounds", activate it even though it may execute slower than without.
Check your linker report to see if there are missing modules or libraries.

If everything else fails, recheck your code to see if the sizes of arrays are large enough, and have the right addresses. Check that the parameters of calls to functions and subroutines correspond in size and type with the formal parameters defined.

Try a reduced sized problem to see if the problem persists, which may give an idea if the problem comes from arrays out of bound or otherwise.

Good luck!
I guess I've done that and ckecked many times, actaully my main program call a NAG routine, and this routine call a function which also call another NAG ROUTINE. Is this possible??I think so cos I have tried with
known funcion like sin(x)
 
  • #77
Yes, this is very possible.
When they build libraries, common routines are included to be called by different functions or modules to avoid repetition of code.
What is important is to see where the program went wrong, namely arrays out of bound, calling functions with invalid parameters, or other reasons such as bad linking. Another possibility is a complication as a result of an array out of bound overwriting code, which in turn causes program execution to jump outside of the program area.
Try a different problem, a smaller problem. If your compiler has a trace function, you can know at least the last function/subroutine called, and hence narrow down the search. If the trace function allows break points, you can examine the values of the variables at different times of the execution, unless you decide to put in various print statements throughout the code.
Did you by any chance activate the array-out-of-bounds check?
 
  • #78
I am using a numerical recipe which called(brent) and when I execute the code for the results it does not give me any error message, but giving me a warning message saying
PHP:
(PAUSE  brent exceed maximum iterations statement executed
To resume execution, type go.  Other input will terminate the job.
go
Execution resumes after PAUSE.)
and I type go the execution resume and give me right results, what I am thinking is that might affect the calculation, even I tried to make the IMAX in (brent) large enough 300, but still giving me warning
 
  • #79
I am curious to know what convinced you that 300 is a big enough number. Was this problem solved using some other programs? If this is the case, would you be able to compare the results?
Did the segment violation fault problem recur?
It seems that you are getting in the arena of Numerical Recipes. I believe the author of the code is quite active in the forum. You may get some ideas from him, especially if the number of iterations are involved. Try:
http://www.nr.com/forum/
There are also bug reports for which you can search (if you are registered).
 
  • #80
I have registered in this forum, and activate my account, but when I've tried to post , they said
PHP:
you do not have permission to access this page
it seem be a problem with this forum cos there are another registered members who couldn't post their question as well
 
  • #81
anyone could show me how to
PHP:
plot with colors in GNUPLOT,
as I need to plot two functions in the same graph
 
  • #82
please can you help me how to access for example the second column of a date file, also can I read a data file {which has been created in a function} in my main programme, when I tried to do tat it gives me the following error message
Code:
list in: end of file
apparent state: unit 6 named fort.6
last format: list io
lately reading direct formatted external IO
Aborted
 
  • #83
please can anyone help me out, I want to calculate the inverse of a complex matrix by calling some NAG routine, when I compile th file it does not give me any warning OR ERROR MESSAGES, but it give any results as well. her the code
Code:
INTEGER NMAX, LDA, LWORK
       PARAMETER (NMAX=8,LDA=NMAX,LWORK=64*NMAX)
* .. Local Scalars ..
       INTEGER I,INFO, J, N
* .. Local Arrays ..
       complex A(LDA,NMAX), WORK(LWORK)
       INTEGER IPIV(NMAX)
* .. External Subroutines ..
       EXTERNAL ZGETRI, ZGETRF
* .. Executable Statements ..
       WRITE (*,*) 'F07AWF Example Program Results'
* Skip heading in data file
       open(unit=4,file='NIN', status='unknown')
       READ (*,*) N
       IF (N.LE.NMAX) THEN
* Read A from data file
       READ (4,*) ((A(I,J),J=1,N),I=1,N)
       rewind 4
       close (4)
* Factorize A
       CALL ZGETRI(N,N,A,LDA,IPIV,INFO)
       print*, 'INFO=', INFO
       IF (INFO.EQ.0) THEN
* Compute inverse of A
*
        CALL ZGETRF(N,A,LDA,IPIV,WORK,LWORK,INFO)
* Print inverse
        open(unit=5,file='Inverse-Matrix.dat', status='unknown')
        do i = 1, N
             write(5,*)  (a(i,j), j = 1, N)
        end do
        close (5)
       ELSE
           WRITE (*,*) 'The factor U is singular'
       END IF
c       rewind 5
       END IF
       END
and I give the program the same matrix which has been giuven in the example with the NAG routine.
 
  • #84
can anyone help me out I need to fit some data file to some function by using the GNUPLOT, actually I have the command, the problem my function contains
PHP:
pi
, so can I define it in GNUPLOT as i do not want to deal with as a parameter
 
  • #85
Anybody has an idea why Fortran is performing so poorly in the Computer Langauge
Benchmarks Game
?

I just started to learn Fortran, mainly because I prefer it to C/C++ and needed speed. I've always heard Fortran was faster than C/C++, and C++ could only get close to Fortan using template techniques (beside, the compiler used for Fortran is made by Intel, while the GCC are used for C/C++).
 
  • #86
please mathmate can you help me in this
Hi guys
I have a code written by fortran 77, it has been working fine, but after I add some changes. I had compiled and does not give me any error messages, but when had the command ./a.out to display the results, it says killed, and I do not have no idea what this means.
please help me out
 
  • #87
Usually killed means that the code is terminated due to some uncorrectable error, such as array out of bounds, or calling a module that is outside the user's work area (hardware violation), or code has been overwritten with data.

First check if you have any way to activate array out-of-bounds check. This is the most common problem of this kind, if the original code was well established and checked.
If it is an iterative solution of some kind, print some indicative parameters at every iteration and see if the iterations are going haywire.

If all of the above don't get you anywhere, I could look at your code if you post the working and modified codes. If the code is too long to be posted, you can PM me with your e-mail address, I will contact you. On the other hand, if it is sensitive code, I would decline to avoid getting you entangled in doubts or problems.
 
  • #88
mathmate said:
Usually killed means that the code is terminated due to some uncorrectable error, such as array out of bounds, or calling a module that is outside the user's work area (hardware violation), or code has been overwritten with data.
As I had this guess because I made change in bounds of array, then it gives me this warning, but then I changed to the previous ones, but still giving me the killed warning message, and I have so many data files in my program...
mathmate said:
If all of the above don't get you anywhere, I could look at your code if you post the working and modified codes. If the code is too long to be posted, you can PM me with your e-mail address, I will contact you. On the other hand, if it is sensitive code, I would decline to avoid getting you entangled in doubts or problems.
The matter is not a senstive code or not, but it is that the code is very long and it is difficult to follow not because I am genouse but it deals with many equations...
 
  • #89
As I had this guess because I made change in bounds of array, then it gives me this warning, but then I changed to the previous ones, but still giving me the killed warning message, and I have so many data files in my program...
This is precisely why I would like to see your two versions of code. I was planning to use the unix utility diff to find the differences between them to check out inadvertent changes. I have no interest in understanding the code, but if I do find a difference between the two (old and reconstituted), I would need access to the logic to find out the consequences of the changes.

On the other hand, if you have access to the diff utility in Unix or the equivalent, you could do the same by yourself, as you probably understand the code much better than anyone else.

By the way, I would concentrate a little on out-of-bounds errors if you have modified or had intentions to modify the dimension limits. It could be caused by overflowing data, in which case a smaller model should run perfectly.
 
  • #90
mathmate said:
On the other hand, if you have access to the diff utility in Unix or the equivalent, you could do the same by yourself, as you probably understand the code much better than anyone else.
.

Hi mathmate, how can I access such utility, what is the command shell for it...cos I AM NOT SURE IF i HAVE it or no...:smile:
 

Similar threads

  • · Replies 17 ·
Replies
17
Views
4K
  • · Replies 7 ·
Replies
7
Views
6K
  • · Replies 16 ·
Replies
16
Views
5K
  • · Replies 13 ·
Replies
13
Views
4K
  • · Replies 3 ·
Replies
3
Views
4K
Replies
6
Views
4K
  • · Replies 14 ·
Replies
14
Views
3K
  • · Replies 5 ·
Replies
5
Views
3K
  • · Replies 4 ·
Replies
4
Views
38K
  • · Replies 11 ·
Replies
11
Views
6K