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

  ViewVC Help
Powered by ViewVC 1.1.22