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!

Would be happy f0r some held understanding code

Status
Not open for further replies.

Chris1599

Technical User
Jul 6, 2014
7
0
0
DE
Hello, I would be very happy if you can held me!

I don't understand what exactly IN is and does:

The code says:


Code:
INTEGER IN(NP)

Code:
DO 111 I=1,N                                                            
      IN(I)=I                                                                 
 111  CONTINUE

Code:
SUBROUTINE GASKR (PO,PU,PH,CUM,CHR,CSR,FGASR,SPALT,IN,            !      
     -                  LHYD,FUEL,IBZ,LKO)                              !      
C                                                                       !      
      IMPLICIT REAL    (M)                                              !      
      IMPLICIT LOGICAL (L)                                              !      
C                                                                       !      
      INCLUDE 'PARSTX.INC'                                                  !      
      INCLUDE 'PARPTX.INC'                                                  !      
C                                                                       !      
      DIMENSION SPALT(NP,NS)                                            !      
C                                                                       !      
      SSUM = 0.                                                         !      
      NA    = NS-1                                                      !      
C                                                                       !      
      DIF = PO-PU                                                       !      
C                                                                       !      
      DO 1 I=1,NS                                                       !      
      SSUM = SSUM+1./SPALT(IN,I)                                        !      
    1 CONTINUE                                                          !      
C                                                                       !      
      PI   = PU+DIF/SPALT(IN,1)/SSUM                                    !      
      PSUM = PI                                                         !      
C                                                                       !      
      DO 2 I=2,NA                                                       !      
      PI   = PI+DIF/SPALT(IN,I)/SSUM                                    !      
      PSUM = PSUM+PI                                                    !      
    2 CONTINUE



NP = 3
NS = 11

So SPALT should be a 2 dimensional array with 33 elements.

IN is also declared as an 1 dimensional array with 3 elements I think.

The problem is:

SSUM = SSUM+1./SPALT(IN,I)

It seems to me that there is an array in an array at SPALT and IN. But what dimension is SSUM then?

I bought books form an antiquary and spent hours, but I am not shure what happens at this point. :(


(The programs has 4900 lines, but I think I got the important lines to know what IN is.)
 
Oh...

I looked at the text twice before posting, but I forgot the title.

Can't find the "edit" button. Maybe an admin can help?

Sorry!
 
In GASKR, IN is not the array in the rest of the program. It is just an integer parameter like IBZ. You need to look for the 9th parameter in the call to GASKR.
 
Oh Yes! How easy...

Thank you!

Here is the call:

Code:
CALL GASKR (PNG(J-1),PK(1),PK(1),CUM,CHR(J),CSR(J),FGASRG(J),     !      
     -            SPALTLG,JS,LHYD,FUELG(J),IBZG(J),LKO)


I was confused, because Notepad++ displays the IN always blue, so i thought it has to be something special.

Thanks a lot! :)

Interesting that IBZ and LKO are not used in the subroutine:

subroutine_gaskr.JPG
 
It displays IN in blue because it is one of the keywords in F90
Code:
    integer, intent(in):: po
The good thing is Fortran does not have any reserved words so there is compatibility with older code which may use a new keyword as an identifier. The bad thing is editors are not syntactic parsers. They can't tell when a sequence of letters is an identifier or a keyword. They just hope that the user is sensible enough not to use a keyword as an identifier even though it is syntactically correct. They are just keywords but not reserved words so you could have an array called if and something confusing like
Code:
    integer if(50)

! logical if (spaces are not significant but allowed in variable/function names)
!       ,-- variable
    if (if(10) .eq. 1) call caul if lower
! arithmetic if
!       ,-- variable
    if (if(10)) 10, 20, 30
! logical followed by arithmetic
!   ,-- keyword        ,-- keyword
!   |   ,-- variable   |  ,-- variable
    if (if(10) .eq. 2) if(if(20)) 10, 20, 30
I've never seen anyone do this: I just used to give it as an example when I was teaching as a postgrad and ask the students to pick out the identifiers and keywords. I don't use notepad++. I guess it would make all the ifs blue.
 
Yes, Notepad++ marked all the ifs blue! :)

Unfortunately I have an other question:

There are subroutines without arguments. And I think subroutines can't manipulate variables in the main program.

So how does this work? How get the results in main program?

I would be really happy about an answer. :)

Code:
CALL FLAGE

Code:
SUBROUTINE FLAGE                                                  !      
C                                                                       !      
      INCLUDE 'VERTTX.INC'                                                  !      
C                                                                       !      
      DIMENSION FTW(NP)                                                 !      
C                                                                       !      
C                                                                       !      
      FIR = 5.E-06                                                      !      
      FOE = 1.E-07                                                      !      
C                                                                       !      
C                                                                       !      
      DO 1 K=1,N                                                        !      
C                                                                       !      
      CSSA = CSS(K)+DR(K)*CPI                                           !      
      IF ( K .EQ. N ) FIR=FOE                                           !      
C                                                                       !      
      SRR    = FSUMRD(K)/CUM/CHR(K)*FIR                                 !      
      SRA    = FSUMAD(K)/(CUM-CPI*CBR(K))*CBR(K)*FIR                    !      
C                                                                       !      
      ASMD(K) = AS(K)*EXP(-ABS(FFVL(K))*SRR)+(CDZ-CDK(K))/2.*CSSA       !      
      IF(FSUMRD(K).LT.0.) ASMD(K) = 10.*AS(K)                           !      
      IRAD(K) = 0                                                       !      
      IF (FSUMRD(K).LT.0.) IRAD(K) = 1                                  !      
      TWMAX(K)  = .9 * ATAN((CHN(K)-CHR(K))/CBR(K))                     !      
C                                                                       !      
C                                                                       !      
      FTW(K)    = 1.-ABS(TWISTD(K)/TWMAX(K))                            !      
C                                                                       !      
      AFOMD(K)  = AFO1(K)*(100.-POSD(K))/100.*FTW(K)                    !      
     -          +AFO2(K)*EXP(-ABS(FFVO(K))*MAX(0.,SRA))                 !      
     -          +CSSA*(CDZ-CDK(K))/2.                                   !      
      IF ( K .EQ. N ) GOTO 11                                           !      
C                                                                       !      
      AFUMD(K)  = AFU2(K)*POSD(K)/100.*FTW(K)                           !      
     -          +AFU1(K)*EXP(ABS(FFVU(K))*MIN(0.,SRA))                  !      
     -          +CSSA*(CDZ-CDK(K+1))/2.                                 !      
C                                                                       !      
   11 CONTINUE                                                          !      
C                                                                       !      
    1 CONTINUE                                                          !      
C                                                                       !      
C                                                                       !      
C *************                 ********************                    !      
C                                                                       !      
      IF ( .NOT. LDG ) GOTO 9                                           !      
C                                                                       !      
      FIR = 5.E-06                                                      !      
C                                                                       !      
      DO 2 K=1,N                                                        !      
C                                                                       !      
      CSSA = CSS(K)+DR(K)*CPI                                           !      
      IF ( K .EQ. N ) FIR=FOE                                           !      
C                                                                       !      
      SRR    = FSUMRG(K)/CUM/CHR(K)*FIR                                 !      
      SRA    = FSUMAG(K)/(CUM-CPI*CBR(K))*CBR(K)*FIR                    !      
C                                                                       !      
      ASMG(K) = AS(K)*EXP(-ABS(FFVL(K))*SRR)+(CDZ-CDK(K))/2.*CSSA       !      
      IF(FSUMRG(K).LT.0.) ASMG(K) = 10.*AS(K)                           !      
      IRAG(K) = 0                                                       !      
      IF (FSUMRG(K).LT.0.) IRAG(K) = 1                                  !      
C                                                                       !      
      FTW(K)    = 1.-ABS(TWISTG(K)/TWMAX(K))                            !      
C                                                                       !      
      AFOMG(K)  = AFO1(K)*(100.-POSG(K))/100.*FTW(K)                    !      
     -          +AFO2(K)*EXP(-ABS(FFVO(K))*MAX(0.,SRA))                 !      
     -          +CSSA*(CDZ-CDK(K))/2.                                   !      
C                                                                       !      
C                                                                       !      
      IF ( K .EQ. N ) GOTO 22                                           !      
C                                                                       !      
      AFUMG(K)  = AFU2(K)*POSG(K)/100.*FTW(K)                           !      
     -          +AFU1(K)*EXP(ABS(FFVU(K))*MIN(0.,SRA))                  !      
     -          +CSSA*(CDZ-CDK(K+1))/2.                                 !      
C                                                                       !      
C                                                                       !      
   22 CONTINUE                                                          !      
C                                                                       !      
    2 CONTINUE                                                          !      
C                                                                       !      
C                                                                       !      
    9 RETURN                                                            !      
C                                                                       !      
      END
 
Are there any common blocks in vertix.inc? Does the main program include vertix.inc? If so, then the communication is through the common blocks.
 
Oh yes:

Main program:

Code:
     PROGRAM KOWING                                                    !      
C                                                                       !      
C                                                                       !      
      INCLUDE 'VERTTX.INC'                                              !
C                                                                       !
CALL SOP1 (IBS,LBS)                                                     !      
      CALL DAT1                                                         !      
      CALL DAT2                                                         !      
      CALL DAT3                                                         !      
      CALL DAT4                                                         !      
      CALL DAT5                                                         !      
      CALL SOP2 (N,LDG,LHYD)                                            !      
C                                                                       !      
      CALL AUSG                                                         !      
      CALL MASS                                                         !      
C                                                                       !      
      CALL LIESKW (1)                                                   !      
C                                                                       !      
      CALL VORBEL                                                       !      
C                                                                       !      
C                                                                       !      
C                                                                       !      
      DO 9000 K=1,2                                                     !      
C                                                                       !      
      KS = K                                                            !      
C                                                                       !      
C                                                                       !      
      DO 8000 I=ISTART,KW         !*************************************!      
C                                                                       !      
      IS = I


And this is VERTTX.INC:

Code:
C ---------------------V-BLOCK------------------------------------------!     
C                                                                       !     
CCOMDECK VERTTX                                                         !     
C     ***1****#****2****#****3****#****4****#****5****#****6****#****7**!     
C                                                                       !     
C           BLOCK FOR  KOWING  AND ALL K-U-PROGRAMS                     !     
C                                                                       !     
C        AT "INCLUDE 'VERTTX'" IT HAS TO BE COPIED FOR COMPILING        !   
C                                                                       !     
C         "!" HAVE TO BE DELETED IN FIRST COLUMN                        !     
C                                                                       !     
C     ***1****#****2****#****3****#****4****#****5****#****6****#****7**!     
C                                                                       !     
C                                                                       !     
      IMPLICIT REAL    (M)                                              !     
      IMPLICIT LOGICAL (L)                                              !     
C                                                                       !     
      INCLUDE 'PARPTX.INC'                                              !     
      INCLUDE 'PARSTX.INC'                                              !     
      INCLUDE 'PARITX.INC'                                              !     
      INCLUDE 'PAROTX.INC'                                              !     
C                                                                       !     
      PARAMETER (NZ=2,ND=21)                                            !     
C                                                                       !     
      COMMON/BL02/CDZ,CUM,CHB,CLP,CPI,CG,CDREH,KW,II,IG,ISTART          !     
      COMMON/BL03/CSM(NP),CEM(NP),CMYRK(NP),XSKR(NP)                    !     
      COMMON/BL04/FMMM,FBAP,FMYM,FBOG,FCEK                              !     
      COMMON/BL05D/LKO,LROD(NP),LRUD(NP),LBS,LEINT,IBS,LSTBD(NP)        !     
      COMMON/BL05G/LROG(NP),LRUG(NP),LDG,LSTBG(NP)                      !     
      COMMON/BL06/N,NR,N1,NA,CDK(NP),CDN(NP),CHK(NP),CHN(NP)            !     
      COMMON/BL07/RAUNO(NP),RAUNU(NP-1),RAUR(NP)                        !     
      COMMON/BL08/CHR(NP),CBR(NP),CSR(NP),CHO,                          !     
     -             CFT(NP),CSS(NP),CBOLZ(NP),FAKMAS                     !     
      COMMON/BL09/VERRO(NP,NS),VERRU(NP,NS),VERRNO(NP,NS),              !     
     -            VERRNU(NP,NS),VERRL(NP,NS)                            !     
      COMMON/BL10D/SPALTOD(NP,NS),SPALTUD(NP,NS),SPALTLD(NP,NS)         !     
      COMMON/BL10G/SPALTOG(NP,NS),SPALTUG(NP,NS),SPALTLG(NP,NS)         !     
      COMMON/BL11/TWISTD(NP),TWISTG(NP),TWMAX(NP),ALZ,EPSS              !     
      COMMON/BL12/TF,TR(NP),TK,TZO,TZU,CKAPPA,CRGAS,CETA,CTB,CTC        !     
      COMMON/BL13D/PV(NZ),PK(NZ),DELD(NZ),DELPD(NZ),RKAD(NZ),           !     
     -             RKAPD(NZ),RKA2PD(NZ),H0(ND),D0(ND),DR(NP)            !     
      COMMON/BL13G/DELG(NZ),DELPG(NZ),RKAG(NZ),RKAPG(NZ),RKA2PG(NZ)     !     
      COMMON/BL14/FAKA,EXP1,EXP2,COMEGA,CR,CPLEUV,DELTT,DELTT1,DELTG    !     
      COMMON/BL15/AFO1(NP),AFO2(NP),AFU1(NP-1),AFU2(NP-1),AS(NP)        !     
      COMMON/BL16D/AFOMD(NP),AFUMD(NP-1),ASMD(NP)                       !     
      COMMON/BL16G/AFOMG(NP),AFUMG(NP-1),ASMG(NP)                       !     
      COMMON/BL17/FFVO(NP),FFVU(NP),FFVL(NP),FDA(NP),FFA(NP)            !     
      COMMON/BL18D/VHD(NP-1),VND(NP-1),PSIO(NP),PSIU(NP),PSIL(NP)       !     
      COMMON/BL18G/VHG(NP-1),VNG(NP-1)                                  !     
      COMMON/BL19D/MHD(NP-1),MND(NP-1),PHD(NP-1),PND(NP-1)              !     
      COMMON/BL19G/MHG(NP-1),MNG(NP-1),PHG(NP-1),PNG(NP-1)              !     
      COMMON/BL20/PHI,XK,XKP,XK2P,XRPD(NP),XRPG(NP),PMI,PMR(NP),PMRG    !     
      COMMON/BL21D/POSD(NP),FGASAD(NP),FMASAD(NP),FREIBAD(NP),FSUMAD(NP)!     
      COMMON/BL21G/POSG(NP),FGASAG(NP),FMASAG(NP),FREIBAG(NP),FSUMAG(NP)!     
      COMMON/BL22D/FREIBRD(NP),FGASRD(NP),FSUMRD(NP),MRING(NP)          !     
      COMMON/BL22G/FREIBRG(NP),FGASRG(NP),FSUMRG(NP)                    !     
      COMMON/BL23/DELTM1D,DELTM2D,MGASP,SUMB,DELTM1G,DELTM2G            !     
      COMMON/BL24/PSIAQ,AQR(NP-1),AQK(NP-1)                             !     
      COMMON/BL25/FBIEGD(NP),FBIEGG(NP),IRAD(NP),IRAG(NP)               !     
C                                                                       !     
C              FOR PORGAMMPART HYDRODYNAMIK                             !     
C                                                                       !     
      COMMON/BL26D/BMIND(NP),BFILMD(NP),VPOELD,VPOELSD(NP)              !     
      COMMON/BL26G/BMING(NP),BFILMG(NP),VPOELG,VPOELSG(NP)              !     
      COMMON/BL27/HPD(NP),HP0D(NP),HPG(NP),HP0G(NP)                     !     
      COMMON/BL28D/FUELD(NP),IBZD(NP),OELFD(NO),LFLABD(NP),VOASP        !     
      COMMON/BL28G/FUELG(NP),IBZG(NP),OELFG(NO),LFLABG(NP)              !     
      COMMON/BL29/HMAXP(NP),HMAXN(NP),HMIN(NP),HKT(NP)                  !     
      COMMON/BL30/CMYRZ(NP),FAKV,EPSF,EPRG                              !     
      COMMON/BL31/LFLAGD(NP),LFLAGG(NP),LHYD,LSQU,LFUL,LTWI,LBST        !     
      COMMON/BL32D/FUELPD(NP),FUELND(NP),HUELPD(NP),HUELND(NP)          !     
      COMMON/BL32G/FUELPG(NP),FUELNG(NP),HUELPG(NP),HUELNG(NP)          !     
C     ***1****#****2****#****3****#****4****#****5****#****6****#****7**!     
C                                                                       !     
C                                                                       !     
C ---------------------PARAMETER-LISTING---------------------------------!     
C                                                                       !     
CCOMDECK PARPTX                                                         !     
C                                                                       !     
cau      PARAMETER (NP=4)                                               !     
C                                                                       !     
C                                                                       !     
CCOMDECK PARSTX                                                         !     
C                                                                       !     
cau      PARAMETER (NS=11)                                              !     
C                                                                       !     
C                                                                       !     
CCOMDECK PARITX                                                         !     
C                                                                       !     
cau      PARAMETER (NI=50)                                              !     
C                                                                       !     
C                                                                       !     
CCOMDECK PAROTX                                                         !     
C                                                                       !     
cau      PARAMETER (NO=180)                                             !     
C                                                                       !


So you are right. VERTTX.INC is in the main program and in the subroutine.

And when it is included, both can handle with the included parameters?

And things like "BL02" are the names of the memory in which the follwing parameter are saved?
 
If an item is marked as a parameter, it is a constant. To avoid confusion, use the word arguments.

A common block is basically named global storage, so setting the value which is in one common block in one subroutine will be remembered when it gets to the next subroutine that uses it.

As for coding techniques, there are a few schools of thought. Say you have 3 common blocks
Code:
      common /A/airy,ask
      common /B/berry,bask
      common /C/cherry,cask
The main program will include all of them regardless of whether it uses them or not. If say routine abbey only needs common blocks A and B and routine acey only needs A and C, then you'd have
Code:
      subroutine abbey
      common /A/airy,ask
      common /B/berry,bask
      ...
      end

      subroutine acey
      common /A/airy,ask
      common /C/cherry,cask
      ...
      end
Including C in abbey and B in acey is totally unnecessary. This can get hugely repetitive and sooner or later, someone will make a typing mistake and you'd be hunting it for ages. A common mistake with common blocks is miss out a comma. Then instead of 5 variables, you get 4 and everything shifts up. Even worse if you have mixed types. This can happen accidentally during editing, especially on windowed systems.

What you find in a lot of coding is people get lazy. They can't be bothered to work out what every routine needs so they group all the common blocks together in one header file and include it in every routine, regardless of what the routine uses. The way I'd normally do this is to have include file per common block
Code:
!
      real airy, ask
      common /A/ airy,ask
Code:
!
      real berry,bask
      common /B/ berry,bask
Code:
!
      real cherry,cask
      common /C/ cherry,cask
Then in the code
Code:
      subroutine abbey
      implicit none
      include 'A.inc'
      include 'B.inc'
      ...
      end

      subroutine acey
      implicit none
      include 'A.inc'
      include 'C.inc'
      ...
      end
There are lots of debates as to which is the better technique since reading one file and processing a huge symbol table may be faster than reading several files and processing a small symbol table as file reads may take longer. It makes a lot of difference if the include files live on a networked drive (yes - why would anyone do anything so daft? but it happens, even in huge corporations).

I prefer the separate include file technique since each file tells you everything that is in the block, including the types but that is just me. Forums like these wouldn't exist if everyone thought the same.
 
Thanks a lot! :)

Ok I understand, I should have used the word "argument" instead of "parameter" in this case.

Your style is much more comfortable to read than the program I have to read.

This thing was programmed by an engineer in the 80'. Probably I am the first man who looks at the code since it was programmed. It has also a lot of GOTOs in it....

Thank you! :)
 
Nothing wrong with gotos - there is a reason why they are there. Just that some people abuse them. It is like opium - OK to use it for pain relief but some people abuse it. GOTOs are great for error handling and getting out of heavily nested loops.

The way to understand goto type programs is to draw a flowchart. Then pretend that the start and finish are the top and bottom of a piece of string. Just pull it straight. All of a sudden, a fairly complex piece of code will look very simple. You can't do that with languages like C or C++ but with Fortran, it is really easy.
 
Hi!
I drew a flowchart and then it was no problem! :) In Matlab I use now while loops with "if - continue" or "if-break". Luckily the GOTOs are just used and not abused, but my matlab code is much more easy to read.

Perhaps there will be an other question, but I dont't think so.

Then thanks a lot!
Bye!
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top