/[MITgcm]/MITgcm/pkg/diagnostics/diagnostics_write.F
ViewVC logotype

Diff of /MITgcm/pkg/diagnostics/diagnostics_write.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.1 by molod, Thu Feb 12 16:18:21 2004 UTC revision 1.30 by jmc, Wed Jan 3 00:29:59 2007 UTC
# Line 1  Line 1 
1        subroutine diagnostics_write ( nymd,nhms,nymd0,nhms0,xlabel,  C $Header$
2       .                     vars,grid,earth,ocean,land,physics,coupling,  C $Name$
      .                     diag,plist,nplist,dlist,ndlist,nrtype )  
3    
4    #include "DIAG_OPTIONS.h"
5    
6          SUBROUTINE DIAGNOSTICS_WRITE ( myTime, myIter, myThid )
7  C***********************************************************************  C***********************************************************************
8  C  Purpose  C  Purpose
9  C  -------  C  -------
10  C     Output sequence for the (multiple) diagnostics output files  C    Output sequence for the (multiple) diagnostics output files
11  C  C
12  C  Arguments  Description  C  Arguments  Description
13  C  ----------------------  C  ----------------------
14  C     nymd ..... Current   YYMMDD  C     myTime :: Current time of simulation ( s )
15  C     nhms ..... Current   HHMMSS  C     myIter :: Current Iteration Number
16  C     nymd0 .... Beginning YYMMDD  C     myThid :: my Thread Id number
 C     nhms0 .... Beginning HHMMSS  
 C     xlabel ... Character*80 Description of Experiment  
 C     jobid .... Character*8  Job Identifier  
 C     vars ..... Dynamics State Data Structure  
 C     grid ..... Dynamics Grid  Data Structure  
 C     physics .. Physics  State Data Structure  
 C     land ..... Land State     Data Structure  
 C     earth .... Earth Model    Data Structure  
 C     ocean .... Ocean Model    Data Structure  
 C     coupling . Coupling       Data Structure  
 C     diag ..... Diagnostics    Data Structure  
 C      plist ... Prognostic History List Data Structure  
 C     nplist ... Number of distinct Prognostic History Lists  
 C      dlist ... Diagnostic History List Data Structure  
 C     ndlist ... Number of distinct Diagnostic History Lists  
 C     nrtype ... Output Record Type:  0   After  Analysis or Straight Forecast  
 C                                    -1   Before Analysis  
 C                                     1   Assimilation (w/IAU)  
 C  
17  C***********************************************************************  C***********************************************************************
18  c Diagnostics Common         IMPLICIT NONE
19  c -----------------  #include "EEPARAMS.h"
20  #include "SIZE.h"  #include "SIZE.h"
21  #include "fizhi_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
22  #include "diagnostics_SIZE.h"  #include "PARAMS.h"
23  #include "diagnostics.h"  #include "DIAGNOSTICS.h"
24    
25        integer   nrtype  C     !INPUT PARAMETERS:
26        integer   ndlist        _RL     myTime
27        integer   nplist        INTEGER myIter, myThid
       integer   ndindx (ndiagt)  
   
       character*80 xlabel  
       character* 8 jobid  
       integer      nymd,nhms,nymd0,nhms0  
28    
29  c Local variables  c Local variables
30  c ===============  c ===============
31        integer   nd        INTEGER   n
32        integer   ndsum        INTEGER   myItM1, wrIter
33        integer   n,rc        LOGICAL   dump2fileNow, write2file
34        integer   nymdt,nhmst        _RL       phiSec, freqSec, wrTime
35    #ifdef ALLOW_FIZHI
36          LOGICAL alarm2
37          CHARACTER *9 tagname
38    #endif
39    
40          LOGICAL  DIFF_PHASE_MULTIPLE
41          EXTERNAL DIFF_PHASE_MULTIPLE
42    
43          IF ( myIter.NE.nIter0 ) THEN
44            myItM1 = myIter - 1
45    
46    C***********************************************************************
47    C***   Check to see if its time for Diagnostic Output                ***
48    C***********************************************************************
49    
50            write2file = .FALSE.
51            DO n = 1,nlists
52              freqSec = freq(n)
53              phiSec = phase(n)
54    
55              IF ( freqSec.LT.0. ) THEN
56    C--     write snap-shot with suffix = myIter to be consistent with
57    C       time-average diagnostics (e.g., freq=-1 & freq=1):
58    c           wrIter = myIter
59    c           wrTime = myTime
60    C--     write snap-shot with suffix = myIter-1 to be consistent with
61    C       state-variable time-step:
62                wrIter = myItM1
63                wrTime = myTime - deltaTclock
64              ELSE
65                wrIter = myIter
66                wrTime = myTime
67              ENDIF
68              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
69         &                                        wrTime, deltaTclock )
70    #ifdef ALLOW_FIZHI
71              IF ( useFIZHI ) THEN
72               WRITE(tagname,'(A,I2.2)')'diagtag',n
73               dump2fileNow = alarm2(tagname)
74              ENDIF
75    #endif
76    #ifdef ALLOW_CAL
77              IF ( useCAL ) THEN
78                CALL CAL_TIME2DUMP( freqSec, deltaTClock,
79         U                          dump2fileNow,
80         I                          myTime, myIter, myThid )
81              ENDIF
82    #endif /* ALLOW_CAL */
83              IF ( dumpAtLast .AND. myTime.EQ.endTime
84         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
85              IF ( dump2fileNow ) THEN
86                write2file = .TRUE.
87                CALL DIAGNOSTICS_OUT(n,wrIter,wrTime,myThid)
88              ENDIF
89            ENDDO
90    
91    C---   Check to see if its time for Statistics Diag. Output
92    
93            DO n = 1,diagSt_nbLists
94              freqSec = diagSt_freq(n)
95              phiSec = diagSt_phase(n)
96    
97              IF ( freqSec.LT.0. ) THEN
98    C--     write snap-shot with suffix = myIter to be consistent with
99    C       time-average diagnostics (e.g., freq=-1 & freq=1):
100    c           wrIter = myIter
101    c           wrTime = myTime
102    C--     write snap-shot with suffix = myIter-1 to be consistent with
103    C       state-variable time-step:
104                wrIter = myItM1
105                wrTime = myTime - deltaTclock
106              ELSE
107                wrIter = myIter
108                wrTime = myTime
109              ENDIF
110              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
111         &                                        wrTime, deltaTclock )
112    #ifdef ALLOW_FIZHI
113              IF ( useFIZHI ) THEN
114               WRITE(tagname,'(A,I2.2)')'diagStg',n
115               dump2fileNow = alarm2(tagname)
116              ENDIF
117    #endif
118              IF ( dumpAtLast .AND. myTime.EQ.endTime
119         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
120              IF ( dump2fileNow ) THEN
121                write2file = .TRUE.
122                CALL DIAGSTATS_OUTPUT(n,wrTime,wrIter,myThid)
123              ENDIF
124            ENDDO
125    
126    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
127    
128            IF ( write2file ) THEN
129              IF ( debugLevel.GE.debLevB ) THEN
130                CALL DIAGNOSTICS_SUMMARY( myTime, myIter, myThid )
131              ENDIF
132    C-      wait for everyone before setting arrays to zero:
133              _BARRIER
134            ENDIF
135    
136    C--     Clear storage space:
137    
138            DO n = 1,nlists
139              freqSec = freq(n)
140              phiSec = phase(n)
141    
142              wrTime = myTime
143              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
144              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
145         &                                        wrTime, deltaTclock )
146    #ifdef ALLOW_FIZHI
147              IF ( useFIZHI ) THEN
148               WRITE(tagname,'(A,I2.2)')'diagtag',n
149               dump2fileNow = alarm2(tagname)
150              ENDIF
151    #endif
152    #ifdef ALLOW_CAL
153              IF ( useCAL ) THEN
154                CALL CAL_TIME2DUMP( freqSec, deltaTClock,
155         U                          dump2fileNow,
156         I                          myTime, myIter, myThid )
157              ENDIF
158    #endif /* ALLOW_CAL */
159              IF ( dumpAtLast .AND. myTime.EQ.endTime
160         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
161              IF ( dump2fileNow ) CALL DIAGNOSTICS_CLEAR(n,myThid)
162            ENDDO
163    
164            DO n = 1,diagSt_nbLists
165              freqSec = diagSt_freq(n)
166              phiSec = diagSt_phase(n)
167              wrTime = myTime
168              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
169              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
170         &                                        wrTime, deltaTclock )
171    #ifdef ALLOW_FIZHI
172              IF ( useFIZHI ) THEN
173               WRITE(tagname,'(A,I2.2)')'diagStg',n
174               dump2fileNow = alarm2(tagname)
175              ENDIF
176    #endif
177              IF ( dumpAtLast .AND. myTime.EQ.endTime
178         &                    .AND. freqSec.GE.0. ) dump2fileNow = .TRUE.
179              IF ( dump2fileNow ) CALL DIAGSTATS_CLEAR( n, myThid )
180            ENDDO
181    
182  c HHMMSS event timestep counter  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
183  c =============================        ENDIF
       integer  alarm, nalarm,  mhms  
       alarm( mhms ) = nalarm ( mhms, nymd, nhms, nymd0, 0     )  
184    
185  C***********************************************************************        RETURN
186  C*                      Check for Prognostic Output                    *        END
 C***********************************************************************  
       do n=1,nplist  
       if( alarm(plist(n)%frequency).eq.0 ) then  
        call progsig (nymd,nhms,nymd0,nhms0,xlabel,jobid,nrtype,plist(n),  
      .                   vars,grid,earth,ocean,land,physics,coupling )  
       endif  
       enddo  
 C***********************************************************************  
 C*                      Check for Diagnostic Output                    *  
 C***********************************************************************  
       do n=1,ndlist  
       call chkdiag(dlist(n),nymd,nhms,nymd0,nhms0,ndindx,ndsum,nymdt,  
      .                                  nhmst)  
       if (ndsum.ne.0) then  
       call diagout( nymdt,nhmst,nymd0,nhms0,xlabel,ndindx,nrtype,  
      .     dlist(n),qdiag)  
       endif  
       enddo  
   
 c Clear Outputed Diagnostics  
 c --------------------------  
       do n=1,ndlist  
       call chkdiag(n,nymd,nhms,nymd0,nhms0,ndindx,ndsum,nymdt,nhmst)  
       if (ndsum.ne.0) then  
       call clrindx ( diag,ndindx )  
       endif  
       enddo  
   
       return  
       end  
       subroutine chkdiag(nl,nymd,nhms,nymd0,nhms0,ndindx,ndsum,nymdt,nhmst)  
       implicit none  
   
 #include "SIZE.h"  
 #include "fizhi_SIZE.h"  
 #include "diagnostics_SIZE.h"  
 #include "diagnostics.h"  
   
       integer nymd,nhms,nymd0,nhms0,nymdt,nhmst,ndsum  
       integer ndindx(ndiagt)  
   
       integer nymdd,nhmsd,ntick,nafreq,n,m,ndum  
       integer nsecf,nalarm  
   
       nymdt = nymd  
       nhmst = nhms  
       nymdd = nymd0  
       nhmsd = nhms0  
   
 c Initialize Diagnostic Index  
 c ---------------------------  
       do n=1,ndiagt  
       ndindx(n) = 0  
       enddo  
   
 c Fill Current Diagnostic Index  
 c -----------------------------  
       ndsum  = 0  
       nafreq = frequency(nl)  
       if( nalarm( nafreq,nymd,nhms,nymdd,nhmsd ).eq.0 ) then  
   
       do n=1,nfield(nl)  
          do m=1,ndiagt  
          if( fields(nl,n).eq.cdiag_(m) .and. idiag(m).ne.0 ) then  
          ndsum = ndsum  + 1  
          ndindx (ndsum) = m  
          endif  
          enddo  
       enddo  
   
       endif  
       return  
       end  
   
       function chklist (name,list)  
       implicit none  
 #include "SIZE.h"  
 #include "fizhi_SIZE.h"  
 #include "diagnostics_SIZE.h"  
 #include "diagnostics.h"  
       logical  chklist  
       character*8 name  
       integer n  
       chklist = .false.  
       do n=1,nfield(nl)  
       if( fields(nl,n).eq.name ) chklist = .true.  
       enddo  
       return  
       end  

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.30

  ViewVC Help
Powered by ViewVC 1.1.22