Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Unknown Variables 1

Status
Not open for further replies.

Panavia

Technical User
Nov 14, 2010
15
0
0
DE
Hi guys,
I'm usually writing small programms in VB 2008/2010. There is a EGM96 World Geomagnetic Reference Model which has been provided by the Office of GEOINT Sciences GEOINT.
Unfortunately this Model is written in Fortran and I'm now trying to translate it into Visual Basic.

I'm doing fine up to the point, where the spline interpolation starts. There are some variables which just show up without ever beeing declared. Could somebody please explain me where those variables come from and which value they may have during runtime?

The full code looks like this:
This is the first part, which I had no problem with. I wrote the grid into an array and the other variables were easily defined. I got rid of the whole HISTO thing, since it just outputs results on a plotter.
Code:
      implicit real*8(a-h,o-z)
      real*8 south,north,west,east,dphi,dlam

      PARAMETER(IWINDO=4)
      PARAMETER(NBDR=2*IWINDO)
      PARAMETER(NLAT=721,NLON=(1441+NBDR),DLAT=0.25D0,DLON=0.25D0)
      integer*2 A1(NLON)
      REAL*4 H (nlat, nlon)
      CHARACTER NAM*41
      REAL*8 XMIN,XMAX,RDX
      DATA XMIN, XMAX, RDX, NAM/-50.,50., 2.,
     .     'GEOID HTS'/

      CALL HISTO(6,1,NAM,XMIN,XMAX,RDX,1,0.D0,1)

CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC

c data grid file
      open(1,
     .     file='WW15MGH.DAC',
     .     form='unformatted',
     .     access='direct',
     .     recl=(NLON-NBDR-1)*2,
     .     convert='big_endian',
     .     status='old')

c input file of points to be interpolated
      open(11,file='INPUT.DAT',status='old')

c output file of interpolated values
      open(20,file='OUTINTPT.DAT')

CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC

c input grid boundary and spacing
      south = -90.d0
      north = 90.d0
      west = 0.d0
      east = 360.d0
      dphi = 0.25d0
      dlam = 0.25d0

C read input grid file and store in array H
      DO I=1,NLAT
         READ(1,rec=I) (A1(K),K=1,nlon-nbdr-1)
         A1(nlon-nbdr)=A1(1)
         DO J=1,nlon-nbdr
            H(NLAT-I+1,J+nbdr/2)=A1(J)/100.d0
         ENDDO
         DO K=1,nbdr/2
            H(NLAT-I+1,K)=A1(nlon-nbdr-nbdr/2+K)/100.d0
3           H(NLAT-I+1,k+nlon-nbdr/2)=A1(K)/100.d0
         ENDDO
      ENDDO

c read in the points to be interpolated
80    READ(11,*,END=100) FLAT,FLON

c call interpolation subroutine
      CALL INTERP(IWINDO,12.D0,H,south,west-nbdr/2*dlam,DLAT,DLON,
     .            NLAT,NLON,NLAT,NLON,FLAT,FLON,UN)

      CALL HISTO(6,2,NAM,XMIN,XMAX,RDX,1,UN,1)

c output the interpolated points
       WRITE(20,997)FLAT,FLON,UN
997   format(2f14.7,f12.2)

      GOTO 80

100   CONTINUE

      CALL HISTO(6,3,NAM,XMIN,XMAX,RDX,1,0.D0,1)

      STOP
      END

Now comes the part where I have serious problems understanding what is going on. The INTERP routine calls for variables which I don't know where they come from. For example DMIN, DDFI, DDLA, PHIS...
Couls somebody please tell me where they originate and how to interpret them?

Code:
      SUBROUTINE INTERP(IWINDO,DMIN,H,PHIS,DLAW,DDFI,DDLA,NPHI,NDLA,
     .                  IPDIM,ILDIM,PHI,DLA,VALINT)

      PARAMETER(IPA1=20)
      IMPLICIT REAL*8(A-H,O-Z)
      LOGICAL LODD
      REAL*4 H(IPDIM,ILDIM)
      DIMENSION A(IPA1),R(IPA1),Q(IPA1),HC(IPA1)
      IDIM1=IPA1
      RHO=57.29577951D0
      REARTH=6371000.D0
      IF(IWINDO.LT.2) IWINDO=2
      IF(IWINDO.GT.IDIM1) IWINDO=IDIM1
      ILIM=DMIN*1000.*RHO/(REARTH*DDFI)
      JLIM=DMIN*1000.*RHO/(REARTH*DDLA*COS((PHIS+DDFI*NPHI/2.)/RHO))
      LODD=(IWINDO/2)*2.NE.IWINDO
      RI=(PHI-PHIS)/DDFI
      RJ=(DLA-DLAW)/DDLA
      IF(LODD) THEN
        I0=RI-0.5
        J0=RJ-0.5
      ELSE
        I0=RI
        J0=RJ
      ENDIF
      I0=I0-IWINDO/2+1
      J0=J0-IWINDO/2+1
      II=I0+IWINDO-1
      JJ=J0+IWINDO-1
      IF(I0.LT.0 .OR. II.GE.NPHI .OR. J0.LT.0 .OR. JJ.GE.NDLA) THEN
        WRITE(6,7008) PHI,DLA
        VALINT=999999.
        RETURN
      ELSEIF(I0.LT.ILIM .OR. II.GT.NPHI-ILIM .OR. J0.LT.JLIM .OR.
     .  JJ.GT.NDLA-JLIM) THEN
c        IF(NPOINT.LE.ILIST) WRITE(6,7009) PHI,DLA
        VALINT=999999.
        RETURN
      ENDIF
7008  FORMAT(' ',2F10.6,' STATION TOO NEAR GRID BOUNDARY  - NO INT.'
     .,' POSSIBLE|')
7009  FORMAT(' ',2F10.6,' STATION OUTSIDE ACCEPTABLE AREA - NO INT.'
     .,' PERFORMED|')
      IF(IWINDO.GT.2) THEN
        DO 110 I=1,IWINDO
          DO 111 J=1,IWINDO
            A(J)=H(I0+I,J0+J)
111       CONTINUE
          CALL INITSP(A,IWINDO,R,Q)
          HC(I)=SPLINE(RJ-J0+1.,A,IWINDO,R)
110     CONTINUE
        CALL INITSP(HC,IWINDO,R,Q)
        VALINT=SPLINE(RI-I0+1.,HC,IWINDO,R)
      ELSE
        VALINT=BILIN(RI+1.,RJ+1.,H,NPHI,NDLA,IPDIM,ILDIM)
      ENDIF
      RETURN
      END
Thanks a lot!
Tobias
 

You have to compare the calling sequence with the subroutine definition :

Code:
      SUBROUTINE INTERP(IWINDO,DMIN,H,PHIS,DLAW,DDFI,DDLA,NPHI,NDLA,
     .                  IPDIM,ILDIM,PHI,DLA,VALINT)

and

Code:
      CALL INTERP(IWINDO,12.D0,H,south,west-nbdr/2*dlam,DLAT,DLON,
     .            NLAT,NLON,NLAT,NLON,FLAT,FLON,UN)

In the subroutine definition, an argument like DMIN is called a "DUMMY" argument. In the call statement, each argument is called an "ACTUAL" argument. Each actual argument has to match the corresponding dummy argument in type (integer,real,real*8,character ...) and nature (scalar, array). But the names are not tested and have not to be identical, even if it is often easier to keep identical names.

For instance the second actual argument is "12.D0". It corresponds to the dummy argument DMIN. Its means that DMIN=12.D0 during this calling sequence. This transfer is valid as far as DMIN, in the subroutine INTERP, is a scalar double precision real value used only as input data (because a value like 12.D0 cannot be changed : this is a constant !).

Now, rewriting a FORTRAN code into Visual Basic is really strange. You must have very good reason to rewrite a code which runs correctly. The only reason you gave (because you use to program in Visual Basic) is not valid because you will have to learn FORTRAN to rewrite that code. So don't do that for this unique reason !

It is surely better to couple your visual basic programs with this FORTRAN code.


François Jacq
 
The variables that show up without being declared, something that I personally hate btw, are declared in
Code:
implicit real*8(a-h,o-z)
Which means that all variables starting with a,b,c,...upto...h and all starting with o,p,q,....,upto z are reals all from i..n are integers. In fact this statement seems redundant to me as in fortran 77 this is a standard convention.

About their value? No idea, you probably know better than anyone on this forum about the value they should contain.

If you want to detect all these non-declared variables, change "implicit real*8(a-h,o-z)" into "implicit none" and the compiler will give errors for not declaring those undeclared variables.
 
Thanks a lot. Now it makes sens!

To FJacq: Awesome. I couldn't find this information in any general description about the Fortran language. Or it may have been hidden well. The point you are making about rewriting the code into Visual Basic is true. Unfortunately I'm just a novice VB programmer and have absolutely no clue how to couple the two languages like you recommended. For me it looked mor convenient to "simply" translate one language to the other...
Do you know a good source of information addressing this issue?

To GerritGrot: Thanks for the info. I Have read about this when I was searching for the "implicit" statement. Fortunately this is not used in VB.

Cheers,
Tobias
 
I couldn't find this information in any general description about the Fortran language. Or it may have been hidden well.

It is hidden because this is the behavior in most compiled programming languages like FORTRAN, C, C++, JAVA,... as well as high level scripting languages like PYTHON, PERL...

Shell languages also propose dummy arguments with standard names ($1 $2 ... for bash or csh and %1 %2 in DOS/Windows batch files), even if passing information with global environment variables is often applied too.

They are finally very few exceptions like the BASIC and the oldest scripting languages.

The reason is simple : manipulating only global variables, which may be accessible freely by all the part of a software, becomes rapidly intractable when the software size increases. This is why most languages proposes the use of subroutines/functions/procedures with dummy arguments which allows the programmer to share the programming work in independent smaller parts communicating with the rest of the software by the classical actual/dummy argument transfer.

For instance, the subroutine INTERP may be called several times with several different sets of actual arguments.

It is very important to understand that the internal variables defined inside such a subroutine are private. For instance, the variable RHO is independent to any variable RHO defined in other parts of the software. Each subroutine/function represents a closed environment with few doors. The main door is the list of arguments.

With BASIC-like languages, it is very difficult to avoid mistakes due to the use of the same variable name for two different purposes, just because these languages manipulate only a single global name space.

At last, notice that most languages propose other information transfer techniques. For instance FORTRAN handles COMMON and MODULEs (global entities in named spaces). C manages only a single global name space for "external" entities. C++ manages many name spaces. Object oriented languages (C++,JAVA...) also propose CLASSES.



François Jacq
 
Thanks a lot!
That's really good information. Thanks to you the code makes sense to me now.
I think, I have understood everey bit of it now.
I even may take a look into the other languages you mentioned as well.

Tobias
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top