source: flex_extract.git/Source/Fortran/posnam.f90 @ dfa7dbd

ctbtodev
Last change on this file since dfa7dbd was dfa7dbd, checked in by pesei <petra seibert -@…>, 5 years ago

changes in the Fortran part and associated regression test

2019-08-21 PS
introduce the "new" versions of source files:

all .f90 free format
code beautification
regression test is OK

make new local gfortran makefiles, remove parameters not needed
anymore

change filenames rwgrib.f90 (all lower), preconvert to calc_etadot,
adapt messages and comments in calc_etadot.f90
adapt all makefiles to new filenames
adapt success message of logfiles in regression test references
redo regression test OK

provide softlinks for standards:

calc_etadot.out -> calc_etadot_fast.out
makefile_local_gfortran -> makefile_fast

provide changelog.txt in Fortran
provide readme.txt in Regression/FortranEtadot?

  • Property mode set to 100644
File size: 624 bytes
Line 
1  SUBROUTINE POSNAM(KULNAM,CDNAML)
2
3 !! position in namelist file.
4 ! author:  Mats Hamrud, ECMWF
5
6    INTEGER, INTENT(IN)       :: KULNAM
7    CHARACTER*(*), INTENT(IN) :: CDNAML
8    CHARACTER*120 CLINE
9    CHARACTER*1 CLTEST
10   
11    REWIND(KULNAM)
12    ILEN = LEN(CDNAML)
13102 CONTINUE
14      CLINE = ' '
15      READ(KULNAM,'(A)') CLINE
16      IND1 = INDEX(CLINE,'&'//CDNAML)
17      IF (IND1 .EQ. 0) GO TO 102
18      CLTEST = CLINE(IND1+ILEN+1:IND1+ILEN+1)
19    IF (LGE(CLTEST,'0') .AND. LLE(CLTEST,'9') .OR. &
20        LGE(CLTEST,'A') .AND. LLE(CLTEST,'Z')) GOTO 102
21    BACKSPACE(KULNAM)
22
23    RETURN
24   
25  END SUBROUTINE POSNAM
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG