Skip to content

Commit

Permalink
modified: qctropcy.f by Qingfu Liu
Browse files Browse the repository at this point in the history
            A bug was found that the history files (syndat_stmcat , syndat_stmcat.scr)
            save the first and last storm ID used. If the FORTRAN code finds that the
            storm ID has been used in the current hurricane season, the code will
            change the storm ID by adding 1 to the original storm ID. The fix is to
            skip the change of the storm ID.
            See also NOAA-EMC#63
  • Loading branch information
yangfanglin committed Apr 28, 2020
1 parent 9b2eca6 commit af63464
Showing 1 changed file with 14 additions and 68 deletions.
82 changes: 14 additions & 68 deletions sorc/syndat_qctropcy.fd/qctropcy.f
Original file line number Diff line number Diff line change
Expand Up @@ -4237,6 +4237,8 @@ SUBROUTINE RCNCIL(IUNTCA,IUNTCN,IUNTAL,NTEST,NOKAY,NBAD,MAXREC,
c record with only one observing rsmc. It must also be entered int
c the alias file.

istidn=0 ! Qingfu added to skip the changes of storm ID number

if(istidn .eq. 1) then

if(rsmcz(1:1) .eq. '!') then
Expand Down Expand Up @@ -11989,83 +11991,27 @@ SUBROUTINE OFILE0(IUNTOP,NFILMX,NFTOT,FILNAM)

IF(CACCES(NF) .NE. 'DIRECT') THEN
if(cpos(nf) .eq. ' ') then
if (cstat(nf).eq.'OLD') then
OPEN(UNIT=IUNIT(NF),FORM=cform(nf),STATUS='OLD',
1 ACCESS=cacces(nf),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS)
elseif (cstat(nf).eq.'NEW') then
OPEN(UNIT=IUNIT(NF),FORM=cform(nf),STATUS='NEW',
1 ACCESS=cacces(nf),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS)
elseif (cstat(nf).eq.'UNKNOWN') then
OPEN(UNIT=IUNIT(NF),FORM=cform(nf),STATUS='UNKNOWN',
1 ACCESS=cacces(nf),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS)
else
OPEN(UNIT=IUNIT(NF),FORM=cform(nf),STATUS=cstat(nf),
1 ACCESS=cacces(nf),
2 ERR=95,IOSTAT=IOS)
endif
OPEN(UNIT=IUNIT(NF),FORM=cform(nf),STATUS=cstat(nf),
1 ACCESS=cacces(nf),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS)
else
if (cstat(nf).eq.'OLD') then
open(unit=iunit(nf),form=cform(nf),status='OLD',
1 access=cacces(nf),position=cpos(nf),
2 file=filnam(nf)(1:length),err=95,iostat=ios)
elseif (cstat(nf).eq.'NEW') then
open(unit=iunit(nf),form=cform(nf),status='NEW',
1 access=cacces(nf),position=cpos(nf),
2 file=filnam(nf)(1:length),err=95,iostat=ios)
elseif (cstat(nf).eq.'UNKNOWN') then
open(unit=iunit(nf),form=cform(nf),status='UNKNOWN',
1 access=cacces(nf),position=cpos(nf),
2 file=filnam(nf)(1:length),err=95,iostat=ios)
else
open(unit=iunit(nf),form=cform(nf),status=cstat(nf),
1 access=cacces(nf),position=cpos(nf),
2 err=95,iostat=ios)
endif
open(unit=iunit(nf),form=cform(nf),status=cstat(nf),
1 access=cacces(nf),position=cpos(nf),
2 file=filnam(nf)(1:length),err=95,iostat=ios)
endif
ELSE
read(filnam(nf)(length+2:length+2+idgmax-1),37) lrec
37 format(i7)
write(6,39) lrec
39 format('...Direct access record length:',i7,'...')
if(cpos(nf) .eq. ' ') then
if (cstat(nf).eq.'OLD') then
OPEN(UNIT=IUNIT(NF),FORM=CFORM(NF),STATUS='OLD',
1 ACCESS=CACCES(NF),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS,RECL=lrec)
elseif (cstat(nf).eq.'NEW') then
OPEN(UNIT=IUNIT(NF),FORM=CFORM(NF),STATUS='NEW',
1 ACCESS=CACCES(NF),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS,RECL=lrec)
elseif (cstat(nf).eq.'UNKNOWN') then
OPEN(UNIT=IUNIT(NF),FORM=CFORM(NF),STATUS='UNKNOWN',
1 ACCESS=CACCES(NF),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS,RECL=lrec)
else
OPEN(UNIT=IUNIT(NF),FORM=CFORM(NF),STATUS=CSTAT(NF),
1 ACCESS=CACCES(NF),
2 ERR=95,IOSTAT=IOS,RECL=lrec)
endif
OPEN(UNIT=IUNIT(NF),FORM=CFORM(NF),STATUS=CSTAT(NF),
1 ACCESS=CACCES(NF),FILE=FILNAM(NF)(1:LENGTH),
2 ERR=95,IOSTAT=IOS,RECL=lrec)
else
if (cstat(nf).eq.'OLD') then
open(unit=iunit(nf),form=cform(nf),status='OLD',
1 access=cacces(nf),file=filnam(nf)(1:length),
2 position=cpos(nf),err=95,iostat=ios,recl=lrec)
elseif (cstat(nf).eq.'NEW') then
open(unit=iunit(nf),form=cform(nf),status='NEW',
1 access=cacces(nf),file=filnam(nf)(1:length),
2 position=cpos(nf),err=95,iostat=ios,recl=lrec)
elseif (cstat(nf).eq.'UNKNOWN') then
open(unit=iunit(nf),form=cform(nf),status='UNKNOWN',
1 access=cacces(nf),file=filnam(nf)(1:length),
2 position=cpos(nf),err=95,iostat=ios,recl=lrec)
else
open(unit=iunit(nf),form=cform(nf),status=cstat(nf),
1 access=cacces(nf),
2 position=cpos(nf),err=95,iostat=ios,recl=lrec)
endif
open(unit=iunit(nf),form=cform(nf),status=cstat(nf),
1 access=cacces(nf),file=filnam(nf)(1:length),
2 position=cpos(nf),err=95,iostat=ios,recl=lrec)
endif
ENDIF
ENDDO
Expand Down

0 comments on commit af63464

Please sign in to comment.