/[MITgcm]/MITgcm/pkg/thsice/thsice_monitor.F
ViewVC logotype

Diff of /MITgcm/pkg/thsice/thsice_monitor.F

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

revision 1.8 by jmc, Sun May 15 03:04:57 2005 UTC revision 1.17 by jmc, Tue Mar 16 00:23:59 2010 UTC
# Line 8  C     !ROUTINE: THSICE_MONITOR Line 8  C     !ROUTINE: THSICE_MONITOR
8  C     !INTERFACE  C     !INTERFACE
9        SUBROUTINE THSICE_MONITOR( myTime, myIter, myThid )        SUBROUTINE THSICE_MONITOR( myTime, myIter, myThid )
10    
11  C     !DESCRIPTION: \bv  C     !DESCRIPTION:
12  C     *==========================================================*  C     Do ICE global and Hemispheric monitor output
 C     | S/R THSICE_MONITOR  
 C     | o Do ICE global & Hemispheric diagnostic  
 C     *==========================================================*  
 C     *==========================================================*  
 C     \ev  
13    
14  C     !USES:  C     !USES:
15        IMPLICIT NONE        IMPLICIT NONE
# Line 27  C     === Global variables === Line 22  C     === Global variables ===
22  #include "THSICE_PARAMS.h"  #include "THSICE_PARAMS.h"
23  #include "THSICE_VARS.h"  #include "THSICE_VARS.h"
24  #ifdef ALLOW_MONITOR  #ifdef ALLOW_MONITOR
25  #include "MONITOR.h"  # include "MONITOR.h"
26  #endif  #endif
27    
28  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
29  C     == Routine arguments ==  C     == Routine arguments ==
30  C     myTime - Current time of simulation ( s )  C     myTime :: Current time of simulation ( s )
31  C     myIter - Iteration number  C     myIter :: Iteration number
32  C     myThid -  Number of this instance of INI_FORCING  C     myThid :: my Thread Id. number
33        _RL     myTime        _RL     myTime
34        INTEGER myIter        INTEGER myIter
35        INTEGER myThid        INTEGER myThid
# Line 43  CEOP Line 38  CEOP
38  #ifdef ALLOW_THSICE  #ifdef ALLOW_THSICE
39  #ifdef ALLOW_MONITOR  #ifdef ALLOW_MONITOR
40    
41  C     == Local variables ==  C     === Functions ====
42        LOGICAL  DIFFERENT_MULTIPLE        LOGICAL  DIFFERENT_MULTIPLE
43        EXTERNAL DIFFERENT_MULTIPLE        EXTERNAL DIFFERENT_MULTIPLE
44          LOGICAL  MASTER_CPU_IO
45          EXTERNAL MASTER_CPU_IO
46    
47    C     == Local variables ==
48        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
49        CHARACTER*10 mon_var        CHARACTER*10 mon_var
50        CHARACTER*2 mon_sufx(0:2)        CHARACTER*2 mon_sufx(0:2)
51        INTEGER k        _RS locMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
52        _RS yBand(2), locDr(1)        _RS yBand(2), locDr(1)
53        _RL theMin(2), theMax(2)        _RL theMin(2), theMax(2)
54        _RL theMean(2), theVar(2), theVol(2)        _RL theMean(2), theVar(2), theVol(2)
55        _RL theMeanG, theVarG, theVolG        _RL theMeanG, theVolG
56        _RL theMean0, theMean1, theMean2, theEnergy        _RL theMean1, theMean2, theEnergy
57        _RL theMin0, theMax0, theSD, theDel2        _RL theMin0, theMax0, theSD, theDel2
58          INTEGER i,j,bi,bj
59    #ifdef ALLOW_MNC
60          INTEGER k
61    #endif
62    
63        DATA yBand / 0. , 0. /        DATA yBand / 0. , 0. /
64        DATA locDr / 1. /        DATA locDr / 1. /
# Line 63  C     == Local variables == Line 66  C     == Local variables ==
66    
67  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
68    
69        IF (        IF (
70       &   DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,deltaTclock)       &   DIFFERENT_MULTIPLE(thSIce_monFreq,myTime,deltaTclock)
71       &   .OR. myIter.EQ.nIter0 ) THEN       &   .OR. myIter.EQ.nIter0 ) THEN
72    
73          mon_write_stdout = .FALSE.          IF ( MASTER_CPU_IO(myThid) ) THEN
74          mon_write_mnc    = .FALSE.  C--   only the master thread is allowed to switch On/Off mon_write_stdout
75          IF ( thSIce_mon_stdio ) mon_write_stdout = .TRUE.  C     & mon_write_mnc (since it is the only thread that uses those flags):
76    
77              IF ( thSIce_mon_stdio ) THEN
78                mon_write_stdout = .TRUE.
79              ELSE
80                mon_write_stdout = .FALSE.
81              ENDIF
82              mon_write_mnc    = .FALSE.
83  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
84          IF (useMNC .AND. thSIce_mon_mnc) THEN            IF (useMNC .AND. thSIce_mon_mnc) THEN
85            DO k = 1,MAX_LEN_MBUF              DO k = 1,MAX_LEN_MBUF
86              mon_fname(k:k) = ' '                mon_fname(k:k) = ' '
87            ENDDO              ENDDO
88            mon_fname(1:12) = 'monitor_sice'              mon_fname(1:12) = 'monitor_sice'
89            CALL MNC_CW_APPEND_VNAME(              CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
90       &         'T', '-_-_--__-__t', 0,0, myThid)              CALL MNC_CW_I_W_S(
91            CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)       &          'I',mon_fname,1,1,'iter', myIter, myThid)
92            CALL MNC_CW_I_W_S(              CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
93       &        'I',mon_fname,1,1,'T', myIter, myThid)              CALL MNC_CW_RL_W_S(
94            CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)       &          'D',mon_fname,1,1,'T', myTime, myThid)
95            mon_write_mnc = .TRUE.              mon_write_mnc = .TRUE.
96          ENDIF            ENDIF
97  #endif /*  ALLOW_MNC  */  #endif /* ALLOW_MNC */
98    
99              IF (mon_write_stdout) THEN
100                WRITE(msgBuf,'(2A)') '// ==========================',
101         &             '============================='
102                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
103                WRITE(msgBuf,'(A)')
104         &             '// Begin MONITOR Therm.SeaIce statistics'
105                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
106                WRITE(msgBuf,'(2A)') '// ==========================',
107         &             '============================='
108                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
109              ENDIF
110    
111          IF (mon_write_stdout) THEN  C--   endif master cpu io
          _BEGIN_MASTER(myThid)  
           WRITE(msgBuf,'(A)')  
      &    '// ======================================================='  
           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)  
           WRITE(msgBuf,'(A)') '// Begin MONITOR Therm.SeaIce statistics'  
           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)  
           WRITE(msgBuf,'(A)')  
      &    '// ======================================================='  
           CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)  
          _END_MASTER(myThid)  
112          ENDIF          ENDIF
113    
114    C--   make a local copy of iceMask into "RS" array:
115            DO bj = myByLo(myThid), myByHi(myThid)
116             DO bi = myBxLo(myThid), myBxHi(myThid)
117              DO j=1-OLy,sNy+OLy
118               DO i=1-OLx,sNx+OLx
119                locMask(i,j,bi,bj) = iceMask(i,j,bi,bj)
120               ENDDO
121              ENDDO
122             ENDDO
123            ENDDO
124    
125          CALL MON_SET_PREF('thSI_',myThid)          CALL MON_SET_PREF('thSI_',myThid)
126          CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)          CALL MON_OUT_RL('time_sec', myTime,mon_string_none,myThid)
127            
128  C-- Ice area and Ice thickness :  C-- Ice area and Ice thickness :
129          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
130       I                1, 1, 1, 2, yBand,       I                1, 1, 1, 2, yBand,
131       I                iceheight, iceMask, maskH, rA, yC, locDr,       I                iceHeight, locMask, maskInC, rA, yC, locDr,
132       O                theMin, theMax, theMean, theVar, theVol,       O                theMin, theMax, theMean, theVar, theVol,
133       I                myThid )       I                myThid )
134          theVolG= theVol(1)+theVol(2)          theVolG= theVol(1)+theVol(2)
# Line 128  C-- Ice area and Ice thickness : Line 150  C-- Ice area and Ice thickness :
150  C-- Snow thickness :  C-- Snow thickness :
151          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
152       I                1, 1, 1, 2, yBand,       I                1, 1, 1, 2, yBand,
153       I                snowheight, iceMask, maskH, rA, yC, locDr,       I                snowHeight, locMask, maskInC, rA, yC, locDr,
154       O                theMin, theMax, theMean, theVar, theVol,       O                theMin, theMax, theMean, theVar, theVol,
155       I                myThid )       I                myThid )
156          theVolG= theVol(1)+theVol(2)          theVolG= theVol(1)+theVol(2)
# Line 144  C-- Snow thickness : Line 166  C-- Snow thickness :
166          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
167          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
168    
 C-- Total Energy :  
         CALL  MON_STATS_RL(  
      I                1, Qice1, iceMask, iceheight, rA, locDr,  
      O                theMin0,theMax0,theMean1,theSD,theDel2,theVolG,  
      I                myThid )  
         CALL  MON_STATS_RL(  
      I                1, Qice2, iceMask, iceheight, rA, locDr,  
      O                theMin0,theMax0,theMean2,theSD,theDel2,theVolG,  
      I                myThid )  
         theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2  
         mon_var='TotEnerg'  
         CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)  
   
169  C-- Surface Temp. :  C-- Surface Temp. :
170          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
171       I                1, 1, 1, 2, yBand,       I                1, 1, 1, 2, yBand,
172       I                Tsrf, iceMask, maskH, rA, yC, locDr,       I                Tsrf, locMask, maskInC, rA, yC, locDr,
173       O                theMin, theMax, theMean, theVar, theVol,       O                theMin, theMax, theMean, theVar, theVol,
174       I                myThid )       I                myThid )
175          theVolG= theVol(1)+theVol(2)          theVolG= theVol(1)+theVol(2)
# Line 178  C-- Surface Temp. : Line 187  C-- Surface Temp. :
187          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
188          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
189    
190    C--   make a local copy of iceMask*iceHeight into "RS" array:
191            DO bj = myByLo(myThid), myByHi(myThid)
192             DO bi = myBxLo(myThid), myBxHi(myThid)
193              DO j=1-OLy,sNy+OLy
194               DO i=1-OLx,sNx+OLx
195                locMask(i,j,bi,bj)=iceMask(i,j,bi,bj)*iceHeight(i,j,bi,bj)
196               ENDDO
197              ENDDO
198             ENDDO
199            ENDDO
200    
201  C-- 1rst level (volume-mean) Temp. :  C-- 1rst level (volume-mean) Temp. :
202          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
203       I                1, 1, 1, 2, yBand,       I                1, 1, 1, 2, yBand,
204       I                Tice1, iceMask, iceheight, rA, yC, locDr,       I                Tice1, locMask, maskInC, rA, yC, locDr,
205       O                theMin, theMax, theMean, theVar, theVol,       O                theMin, theMax, theMean, theVar, theVol,
206       I                myThid )       I                myThid )
207          theVolG = theVol(1)+theVol(2)          theVolG = theVol(1)+theVol(2)
# Line 202  c       CALL MON_OUT_RL(mon_var, theVol( Line 222  c       CALL MON_OUT_RL(mon_var, theVol(
222          mon_var='Tic1_max'          mon_var='Tic1_max'
223          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
224          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
225            
226  C-- 2nd  level (volume-mean) Temp. :  C-- 2nd  level (volume-mean) Temp. :
227          CALL MON_STATS_LATBND_RL(          CALL MON_STATS_LATBND_RL(
228       I                1, 1, 1, 2, yBand,       I                1, 1, 1, 2, yBand,
229       I                Tice2, iceMask, iceheight, rA, yC, locDr,       I                Tice2, locMask, maskInC, rA, yC, locDr,
230       O                theMin, theMax, theMean, theVar, theVol,       O                theMin, theMax, theMean, theVar, theVol,
231       I                myThid )       I                myThid )
232          theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)          theMeanG= theMean(1)*theVol(1)+theMean(2)*theVol(2)
# Line 223  C-- 2nd  level (volume-mean) Temp. : Line 243  C-- 2nd  level (volume-mean) Temp. :
243          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)          CALL MON_OUT_RL(mon_var, theMax(1), mon_sufx(1), myThid)
244          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)          CALL MON_OUT_RL(mon_var, theMax(2), mon_sufx(2), myThid)
245    
246          IF (mon_write_stdout) THEN  C-- Total Energy :
247           _BEGIN_MASTER(myThid)          CALL  MON_CALC_STATS_RL(
248            WRITE(msgBuf,'(A)')       I                1, Qice1, locMask, maskInC, rA, locDr,
249       &    '// ======================================================='       O                theMin0,theMax0,theMean1,theSD,theDel2,theVolG,
250            CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)       I                myThid )
251            WRITE(msgBuf,'(A)') '// End MONITOR Therm.SeaIce statistics'          CALL  MON_CALC_STATS_RL(
252            CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)       I                1, Qice2, locMask, maskInC, rA, locDr,
253            WRITE(msgBuf,'(A)')       O                theMin0,theMax0,theMean2,theSD,theDel2,theVolG,
254       &    '// ======================================================='       I                myThid )
255            CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)          theEnergy = theEnergy -rhoi*(theMean1+theMean2)*theVolG/2
256           _END_MASTER(myThid)          mon_var='TotEnerg'
257          ENDIF          CALL MON_OUT_RL(mon_var, theEnergy, mon_sufx(0), myThid)
258    
259          mon_write_stdout = .FALSE.          IF ( MASTER_CPU_IO(myThid) ) THEN
260          mon_write_mnc    = .FALSE.  C--   only the master thread is allowed to switch On/Off mon_write_stdout
261    C     & mon_write_mnc (since it is the only thread that uses those flags):
262    
263              IF (mon_write_stdout) THEN
264                WRITE(msgBuf,'(2A)') '// ==========================',
265         &             '============================='
266                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
267                WRITE(msgBuf,'(A)')
268         &             '// End MONITOR Therm.SeaIce statistics'
269                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
270                WRITE(msgBuf,'(2A)') '// ==========================',
271         &             '============================='
272                CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
273              ENDIF
274    
275              mon_write_stdout = .FALSE.
276              mon_write_mnc    = .FALSE.
277    
278    C--   endif master cpu io
279            ENDIF
280    
281    C     endif different multiple
282        ENDIF        ENDIF
283    
284  #endif /* ALLOW_MONITOR */  #endif /* ALLOW_MONITOR */
285  #endif /* ALLOW_THSICE */  #endif /* ALLOW_THSICE */
286          
287        RETURN        RETURN
288        END        END

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.17

  ViewVC Help
Powered by ViewVC 1.1.22