/[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.14 by jmc, Sat May 14 20:45:27 2005 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
 c -----------------  
19  #include "SIZE.h"  #include "SIZE.h"
20  #include "fizhi_SIZE.h"  #include "DIAGNOSTICS_SIZE.h"
21  #include "diagnostics_SIZE.h"  #include "DIAGNOSTICS.h"
22  #include "diagnostics.h"  #include "EEPARAMS.h"
23    #include "PARAMS.h"
24        integer   nrtype  #ifdef ALLOW_FIZHI
25        integer   ndlist  #include "chronos.h"
26        integer   nplist  #endif
27        integer   ndindx (ndiagt)  
28    C     !INPUT PARAMETERS:
29        character*80 xlabel        _RL     myTime
30        character* 8 jobid        INTEGER myIter, myThid
       integer      nymd,nhms,nymd0,nhms0  
31    
32  c Local variables  c Local variables
33  c ===============  c ===============
34        integer   nd        INTEGER   n
35        integer   ndsum        INTEGER   myItM1, wrIter
36        integer   n,rc        LOGICAL   dump2fileNow
37        integer   nymdt,nhmst        _RL       phiSec, freqSec, wrTime
38    #ifdef ALLOW_CAL
39          INTEGER thisdate(4), prevdate(4)
40  c HHMMSS event timestep counter  #endif
41  c =============================  #ifdef ALLOW_FIZHI
42        integer  alarm, nalarm,  mhms        integer nsecf2,yymmdd,hhmmss
43        alarm( mhms ) = nalarm ( mhms, nymd, nhms, nymd0, 0     )  #endif
44    
45  C***********************************************************************        LOGICAL  DIFF_PHASE_MULTIPLE
46  C*                      Check for Prognostic Output                    *        EXTERNAL DIFF_PHASE_MULTIPLE
47  C***********************************************************************  
48        do n=1,nplist        IF ( myIter.NE.nIter0 ) THEN
49        if( alarm(plist(n)%frequency).eq.0 ) then          myItM1 = myIter - 1
50         call progsig (nymd,nhms,nymd0,nhms0,xlabel,jobid,nrtype,plist(n),  
51       .                   vars,grid,earth,ocean,land,physics,coupling )  C***********************************************************************
52        endif  C***   Check to see IF its time for Diagnostic Output                ***
53        enddo  C***********************************************************************
54  C***********************************************************************  
55  C*                      Check for Diagnostic Output                    *  #ifdef ALLOW_CAL
56  C***********************************************************************          IF ( calendarDumps ) THEN
57        do n=1,ndlist  C-    Determine calendar dates for this and previous time step.
58        call chkdiag(dlist(n),nymd,nhms,nymd0,nhms0,ndindx,ndsum,nymdt,             call cal_GetDate(myiter  ,mytime            ,thisdate,mythid)
59       .                                  nhmst)             call cal_GetDate(myiter-1,mytime-deltaTClock,prevdate,mythid)
60        if (ndsum.ne.0) then          ENDIF
61        call diagout( nymdt,nhmst,nymd0,nhms0,xlabel,ndindx,nrtype,  #endif
62       .     dlist(n),qdiag)  
63        endif          DO n = 1,nlists
64        enddo            freqSec = freq(n)
65              phiSec = phase(n)
66  c Clear Outputed Diagnostics  #ifdef ALLOW_FIZHI
67  c --------------------------           if( useFIZHI) then
68        do n=1,ndlist            yymmdd = int(freq(n))
69        call chkdiag(n,nymd,nhms,nymd0,nhms0,ndindx,ndsum,nymdt,nhmst)            hhmmss = int((freq(n) - int(freq(n)))*1.e6)
70        if (ndsum.ne.0) then            freqSec = nsecf2(hhmmss,yymmdd,nymd)
71        call clrindx ( diag,ndindx )            yymmdd = int(phase(n))
72        endif            hhmmss = int((phase(n) - int(phase(n)))*1.e6)
73        enddo            phiSec = nsecf2(hhmmss,yymmdd,nymd)
74             endif
75        return  #endif
       end  
       subroutine chkdiag(nl,nymd,nhms,nymd0,nhms0,ndindx,ndsum,nymdt,nhmst)  
       implicit none  
76    
77  #include "SIZE.h"            IF ( freqSec.LT.0. ) THEN
78  #include "fizhi_SIZE.h"  C--     write snap-shot with suffix = myIter to be consistent with
79  #include "diagnostics_SIZE.h"  C       time-average diagnostics (e.g., freq=-1 & freq=1):
80  #include "diagnostics.h"  c           wrIter = myIter
81    c           wrTime = myTime
82        integer nymd,nhms,nymd0,nhms0,nymdt,nhmst,ndsum  C--     write snap-shot with suffix = myIter-1 to be consistent with
83        integer ndindx(ndiagt)  C       state-variable time-step:
84                wrIter = myItM1
85        integer nymdd,nhmsd,ntick,nafreq,n,m,ndum              wrTime = myTime - deltaTclock
86        integer nsecf,nalarm            ELSE
87                wrIter = myIter
88        nymdt = nymd              wrTime = myTime
89        nhmst = nhms            ENDIF
90        nymdd = nymd0            dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
91        nhmsd = nhms0       &                                        wrTime, deltaTclock )
92    
93  c Initialize Diagnostic Index  #ifdef ALLOW_CAL
94  c ---------------------------            IF ( calendarDumps .AND. (
95        do n=1,ndiagt       &     ( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 ) .OR.
96        ndindx(n) = 0       &     ( freqSec.GE.31104000 .AND. freqSec.LE.31968000 ))) THEN
97        enddo  C--   Convert approximate months (30-31 days) and years (360-372 days)
98    C     to exact calendar months and years.
99  c Fill Current Diagnostic Index             dump2fileNow = .FALSE.
100  c -----------------------------  C-    Monthly freqSec:
101        ndsum  = 0             IF( freqSec.GE. 2592000 .AND. freqSec.LE. 2678400 .AND.
102        nafreq = frequency(nl)       &        (thisdate(1)-prevdate(1)).GT.50   ) dump2fileNow = .TRUE.
103        if( nalarm( nafreq,nymd,nhms,nymdd,nhmsd ).eq.0 ) then  C-    Yearly  freqSec:
104               IF( freqSec.GE.31104000 .AND. freqSec.LE.31968000 .AND.
105        do n=1,nfield(nl)       &        (thisdate(1)-prevdate(1)).GT.5000 ) dump2fileNow = .TRUE.
106           do m=1,ndiagt            ENDIF
107           if( fields(nl,n).eq.cdiag_(m) .and. idiag(m).ne.0 ) then  #endif
108           ndsum = ndsum  + 1  
109           ndindx (ndsum) = m            IF ( dump2fileNow ) THEN
110                CALL DIAGNOSTICS_OUT(n,wrIter,myThid)
111              ENDIF
112            ENDDO
113    
114    C-      wait for everyone before setting arrays to zero:
115            _BARRIER
116            DO n = 1,nlists
117              freqSec = freq(n)
118              phiSec = phase(n)
119    #ifdef ALLOW_FIZHI
120             if( useFIZHI) then
121              yymmdd = int(freq(n))
122              hhmmss = int((freq(n) - int(freq(n)))*1.e6)
123              freqSec = nsecf2(hhmmss,yymmdd,nymd)
124              yymmdd = int(phase(n))
125              hhmmss = int((phase(n) - int(phase(n)))*1.e6)
126              phiSec = nsecf2(hhmmss,yymmdd,nymd)
127           endif           endif
128           enddo  #endif
129        enddo            wrTime = myTime
130              IF ( freqSec.LT.0. ) wrTime = myTime - deltaTclock
131              dump2fileNow = DIFF_PHASE_MULTIPLE( phiSec, freqSec,
132         &                                        wrTime, deltaTclock )
133    
134        endif            IF ( dump2fileNow ) CALL CLRINDX(n,myThid)
135        return          ENDDO
       end  
136    
137        function chklist (name,list)  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
138        implicit none        ENDIF
139  #include "SIZE.h"  
140  #include "fizhi_SIZE.h"        RETURN
141  #include "diagnostics_SIZE.h"        END
 #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.14

  ViewVC Help
Powered by ViewVC 1.1.22