/[MITgcm]/MITgcm/pkg/land/land_monitor.F
ViewVC logotype

Diff of /MITgcm/pkg/land/land_monitor.F

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

revision 1.3 by edhill, Wed Sep 15 22:09:51 2004 UTC revision 1.12 by jmc, Wed Sep 2 21:42:43 2009 UTC
# Line 10  C     !INTERFACE: Line 10  C     !INTERFACE:
10    
11  C     !DESCRIPTION:  C     !DESCRIPTION:
12  C     Do land global and Hemispheric diagnostic  C     Do land global and Hemispheric diagnostic
13          
14  C     !USES:  C     !USES:
15        IMPLICIT NONE        IMPLICIT NONE
16  #include "LAND_SIZE.h"  #include "LAND_SIZE.h"
# Line 20  C     !USES: Line 20  C     !USES:
20  #include "LAND_PARAMS.h"  #include "LAND_PARAMS.h"
21  #include "LAND_VARS.h"  #include "LAND_VARS.h"
22  #ifdef ALLOW_MONITOR  #ifdef ALLOW_MONITOR
23  #include "MONITOR.h"  # include "MONITOR.h"
 #endif  
 #ifdef ALLOW_MNC  
 #include "MNC_PARAMS.h"  
24  #endif  #endif
25    
26  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
# Line 40  CEOP Line 37  CEOP
37  #ifdef ALLOW_LAND  #ifdef ALLOW_LAND
38  #ifdef ALLOW_MONITOR  #ifdef ALLOW_MONITOR
39    
40    C     === Functions ====
41        LOGICAL  DIFFERENT_MULTIPLE        LOGICAL  DIFFERENT_MULTIPLE
42        EXTERNAL DIFFERENT_MULTIPLE        EXTERNAL DIFFERENT_MULTIPLE
43          LOGICAL  MASTER_CPU_IO
44          EXTERNAL MASTER_CPU_IO
45    
46  C     == Local variables ==  C     == Local variables ==
47  C     nLatBnd    :: Number of latitude bands  C     nLatBnd    :: Number of latitude bands
# Line 50  C     mon_var    :: Variable sufix name Line 50  C     mon_var    :: Variable sufix name
50  C     mon_sufx   :: Latitude band sufix  C     mon_sufx   :: Latitude band sufix
51  C     n, k       :: loop counter  C     n, k       :: loop counter
52  C     yBand      :: latitude separation  C     yBand      :: latitude separation
53  C     locDr      :: thickness (= 1. here)  C     locDr      :: thickness (= 1. here)
54  C     theMin     :: lat. band minimum value  C     theMin     :: lat. band minimum value
55  C     theMax     :: lat. band maximum value  C     theMax     :: lat. band maximum value
56  C     theMean    :: lat. band mean value  C     theMean    :: lat. band mean value
57  C     theVar     :: lat. band variance  C     theVar     :: lat. band variance
58  C     theVol     :: lat. band volume (or area if locDr=1.)  C     theVol     :: lat. band volume (or area if locDr=1.)
59  C     theMeanG   :: global mean value  C     theMeanG   :: global mean value
60  C     theVarG    :: global variance  C     theVarG    :: global variance
61  C     theVolG    :: global volume (or area if locDr=1.)  C     theVolG    :: global volume (or area if locDr=1.)
62  C     theEng     :: lat. band energy content  C     theEng     :: lat. band energy content
63  C     theEnergy  :: total energy  C     theEnergy  :: total energy
# Line 78  C     theEnergy  :: total energy Line 78  C     theEnergy  :: total energy
78    
79  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
80    
81        IF ( DIFFERENT_MULTIPLE(land_monFreq,myTime,myTime-deltaTclock)        IF ( DIFFERENT_MULTIPLE(land_monFreq,myTime,deltaTClock)
82       &     .OR. myIter.EQ.nIter0 ) THEN       &     .OR. myIter.EQ.nIter0 ) THEN
83    
84          mon_write_stdout = .FALSE.          IF ( MASTER_CPU_IO(myThid) ) THEN
85          mon_write_mnc    = .FALSE.  C--   only the master thread is allowed to switch On/Off mon_write_stdout
86          IF (monitor_stdio) THEN  C     & mon_write_mnc (since it's the only thread that uses those flags):
87            mon_write_stdout = .TRUE.  
88          ENDIF           IF ( land_mon_stdio ) THEN
89               mon_write_stdout = .TRUE.
90             ELSE
91               mon_write_stdout = .FALSE.
92             ENDIF
93             mon_write_mnc    = .FALSE.
94  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
95          IF (useMNC .AND. monitor_mnc) THEN           IF ( useMNC .AND. land_mon_mnc ) THEN
96            DO k = 1,MAX_LEN_MBUF             DO k = 1,MAX_LEN_MBUF
97              mon_fname(k:k) = ' '               mon_fname(k:k) = ' '
98            ENDDO             ENDDO
99            mon_fname(1:12) = 'monitor_land'             mon_fname(1:12) = 'monitor_land'
100            CALL MNC_CW_APPEND_VNAME(             CALL MNC_CW_APPEND_VNAME(
101       &         'iter', '-_-_--__-__t', 0,0, myThid)       &          'T', '-_-_--__-__t', 0,0, myThid)
102            CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)             CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
103            CALL MNC_CW_I_W(             CALL MNC_CW_I_W_S(
104       &        'I',mon_fname,1,1,'iter', myIter, myThid)       &         'I',mon_fname,1,1,'T', myIter, myThid)
105            CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)             CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
106            mon_write_mnc = .TRUE.             mon_write_mnc = .TRUE.
107             ENDIF
108    #endif /* ALLOW_MNC */
109    
110             IF ( mon_write_stdout ) THEN
111                WRITE(msgBuf,'(2A)') '// ===========================',
112         &           '============================'
113                CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
114                WRITE(msgBuf,'(A)') '// Begin MONITOR Land statistics'
115                CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
116                WRITE(msgBuf,'(2A)') '// ===========================',
117         &           '============================'
118                CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
119              ENDIF
120    
121    C--   endif master cpu io
122          ENDIF          ENDIF
123  #endif /*  ALLOW_MNC  */  
124            CALL MON_SET_PREF('land_',myThid)
125            CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
126    
127          DO k=1,land_nLev          DO k=1,land_nLev
128            locDr(k)= 1.            locDr(k)= 1.
129          ENDDO          ENDDO
130    
        _BEGIN_MASTER(myThid)  
         IF (mon_write_stdout) THEN  
           WRITE(msgBuf,'(2A)') '// ===========================',  
      &         '============================'  
           CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)  
           WRITE(msgBuf,'(A)') '// Begin MONITOR Land statistics'  
           CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)  
           WRITE(msgBuf,'(2A)') '// ===========================',  
      &         '============================'  
           CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)  
         ENDIF  
        _END_MASTER(myThid)  
   
         CALL MON_SET_PREF('land_',myThid)  
         CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)  
           
131  C-- Snow thickness :  C-- Snow thickness :
132          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
133       I                1, 1, 1, nLatBnd, yBand,       I                1, 1, 1, nLatBnd, yBand,
# Line 153  C-- Snow thickness : Line 158  C-- Snow thickness :
158            WRITE(msgBuf,'(A,1PE16.9,A,0P9F7.2)') '%MON LAND : Area=',            WRITE(msgBuf,'(A,1PE16.9,A,0P9F7.2)') '%MON LAND : Area=',
159       &      theVolG, ' ; Lat sep=', (yBand(n),n=2,nLatBnd)       &      theVolG, ' ; Lat sep=', (yBand(n),n=2,nLatBnd)
160            CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)            CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
161            WRITE(msgBuf,'(A,1P9E16.9)') '%MON LAND : LatA=',            WRITE(msgBuf,'(A,1P9E16.9)') '%MON LAND : LatA=',
162       &                              (theVol(n),n=1,nLatBnd)       &                              (theVol(n),n=1,nLatBnd)
163            CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)            CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
164            _END_MASTER(myThid)            _END_MASTER(myThid)
165          ENDIF          ENDIF
166    
 C-- Total Energy :  
         CALL MON_STATS_LATBND_RL(  
      I                land_nLev, 1, 0, nLatBnd, yBand,  
      I                land_enthalp, land_frc, maskH, rA, yC, land_dzF,  
      O                theMin, theMax, theMean, theVar, theVol,  
      I                myThid )  
         theEnergy = 0.  
         DO n=1,nLatBnd  
          theEng(n) = theEng(n) + theMean(n)*theVol(n)  
          theEnergy = theEnergy + theEng(n)  
         ENDDO  
         mon_var='TotEnerg'  
         CALL MON_OUT_RL(mon_var,theEnergy, mon_sufx(0), myThid)  
         CALL MON_OUT_RL(mon_var,theEng(1), mon_sufx(1), myThid)  
         CALL MON_OUT_RL(mon_var,theEng(2), mon_sufx(2), myThid)  
         CALL MON_OUT_RL(mon_var,theEng(3), mon_sufx(3), myThid)  
   
167  C-- Surface Temp. :  C-- Surface Temp. :
168          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
169       I                1, 1, 1, nLatBnd, yBand,       I                1, 1, 1, nLatBnd, yBand,
# Line 231  C-- 1rst level (volume-mean) Temp. : Line 219  C-- 1rst level (volume-mean) Temp. :
219          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
220          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
221          CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)          CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
222            
223  C-- 2nd  level (volume-mean) Temp. :  C-- 2nd  level (volume-mean) Temp. :
224          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
225       I                land_nLev, 1, 2, nLatBnd, yBand,       I                land_nLev, 1, 2, nLatBnd, yBand,
# Line 259  C-- 2nd  level (volume-mean) Temp. : Line 247  C-- 2nd  level (volume-mean) Temp. :
247          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
248          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
249          CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)          CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
250            
251    C-- Total Energy :
252            DO k=1,land_nLev
253              locDr(k)= land_dzF(k)
254            ENDDO
255            CALL MON_STATS_LATBND_RL(
256         I                land_nLev, 1, 0, nLatBnd, yBand,
257         I                land_enthalp, land_frc, maskH, rA, yC, locDr,
258         O                theMin, theMax, theMean, theVar, theVol,
259         I                myThid )
260            theEnergy = 0.
261            DO n=1,nLatBnd
262             theEng(n) = theEng(n) + theMean(n)*theVol(n)
263             theEnergy = theEnergy + theEng(n)
264            ENDDO
265            mon_var='TotEnerg'
266            CALL MON_OUT_RL(mon_var,theEnergy, mon_sufx(0), myThid)
267            CALL MON_OUT_RL(mon_var,theEng(1), mon_sufx(1), myThid)
268            CALL MON_OUT_RL(mon_var,theEng(2), mon_sufx(2), myThid)
269            CALL MON_OUT_RL(mon_var,theEng(3), mon_sufx(3), myThid)
270    
271  C-- Soil water content (level 1+2):  C-- Soil water content (level 1+2):
272          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
273       I                land_nLev, 1, 0, nLatBnd, yBand,       I                land_nLev, 1, 0, nLatBnd, yBand,
274       I                land_groundW, land_frc, maskH, rA, yC, land_dzF,       I                land_groundW, land_frc, maskH, rA, yC, locDr,
275       O                theMin, theMax, theMean, theVar, theVol,       O                theMin, theMax, theMean, theVar, theVol,
276       I                myThid )       I                myThid )
277          theVolG = 0.          theVolG = 0.
# Line 287  c       mon_var='grdW_max' Line 295  c       mon_var='grdW_max'
295  c       CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)  c       CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
296  c       CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)  c       CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
297  c       CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)  c       CALL MON_OUT_RL(mon_var, theMax(3), mon_sufx(3), myThid)
           
        _BEGIN_MASTER(myThid)  
         IF (mon_write_stdout) THEN  
           WRITE(msgBuf,'(2A)') '// ===========================',  
      &         '============================'  
           CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)  
           WRITE(msgBuf,'(A)') '// End MONITOR Land statistics'  
           CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)  
           WRITE(msgBuf,'(2A)') '// ===========================',  
      &         '============================'  
           CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)  
         ENDIF  
        _END_MASTER(myThid)  
298    
299          mon_write_stdout = .FALSE.          IF ( MASTER_CPU_IO(myThid) ) THEN
300          mon_write_mnc    = .FALSE.  C--   only the master thread is allowed to switch On/Off mon_write_stdout
301    C     & mon_write_mnc (since it's the only thread that uses those flags):
302    
303              IF (mon_write_stdout) THEN
304                WRITE(msgBuf,'(2A)') '// ===========================',
305         &           '============================'
306                CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
307                WRITE(msgBuf,'(A)') '// End MONITOR Land statistics'
308                CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
309                WRITE(msgBuf,'(2A)') '// ===========================',
310         &           '============================'
311                CALL PRINT_MESSAGE(msgBuf, mon_ioUnit, SQUEEZE_RIGHT, 1)
312              ENDIF
313    
314              mon_write_stdout = .FALSE.
315              mon_write_mnc    = .FALSE.
316    
317    C--   endif master cpu io
318            ENDIF
319    
320    C     endif different multiple
321        ENDIF        ENDIF
322    
323  #endif /* ALLOW_MONITOR */  #endif /* ALLOW_MONITOR */
324  #endif /* ALLOW_LAND */  #endif /* ALLOW_LAND */
325          
326        RETURN        RETURN
327        END        END

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.12

  ViewVC Help
Powered by ViewVC 1.1.22