Back to home page

MITgcm

 
 

    


File indexing completed on 2018-03-02 18:43:02 UTC

view on githubraw file Latest commit add29e06 on 2018-01-31 20:35:05 UTC
0badf4857e Mart*0001 #include "PTRACERS_OPTIONS.h"
                0002 
                0003 CBOP
                0004 C !ROUTINE: PTRACERS_MONITOR
                0005 
                0006 C !INTERFACE: ==========================================================
                0007       SUBROUTINE PTRACERS_MONITOR(
5a216cc0f7 Jean*0008      I                    myIter, myTime, myThid )
0badf4857e Mart*0009 
                0010 C !DESCRIPTION:
                0011 C writes out ptracer statistics
                0012 
                0013 C !USES: ===============================================================
                0014       IMPLICIT NONE
                0015 #include "SIZE.h"
                0016 #include "EEPARAMS.h"
2de8f11b3e Jean*0017 #include "PARAMS.h"
0badf4857e Mart*0018 #include "GRID.h"
                0019 #include "PTRACERS_SIZE.h"
0a278985fd Jean*0020 #include "PTRACERS_PARAMS.h"
                0021 #include "PTRACERS_FIELDS.h"
0badf4857e Mart*0022 #ifdef ALLOW_MONITOR
                0023 #include "MONITOR.h"
                0024 #endif
                0025 
                0026 C !INPUT PARAMETERS: ===================================================
                0027 C  myTime               :: current time
5a216cc0f7 Jean*0028 C  myIter               :: current timestep
                0029 C  myThid               :: thread number
                0030       _RL     myTime
0badf4857e Mart*0031       INTEGER myIter
                0032       INTEGER myThid
                0033 
                0034 C     === Functions ====
94a46dfe0d Jean*0035       LOGICAL  DIFFERENT_MULTIPLE
                0036       EXTERNAL DIFFERENT_MULTIPLE
49aab2cab9 Jean*0037       LOGICAL  MASTER_CPU_IO
                0038       EXTERNAL MASTER_CPU_IO
0badf4857e Mart*0039 
                0040 #ifdef ALLOW_PTRACERS
                0041 #ifdef ALLOW_MONITOR
                0042 
                0043 C !LOCAL VARIABLES: ====================================================
                0044 C  i,j                  :: loop indices
                0045 C  ip                   :: ptracer number
5a216cc0f7 Jean*0046       CHARACTER*(MAX_LEN_MBUF) msgBuf
0badf4857e Mart*0047       CHARACTER*(MAX_LEN_MBUF) suff
5a216cc0f7 Jean*0048       INTEGER ip
b8b300fc52 Jean*0049       _RL dummyRL(6)
0badf4857e Mart*0050 CEOP
                0051 
5a216cc0f7 Jean*0052       IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,deltaTClock )
                0053      &   ) THEN
0badf4857e Mart*0054 
94a46dfe0d Jean*0055 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
0badf4857e Mart*0056 
5a216cc0f7 Jean*0057 C--   Ptracers field monitor start
49aab2cab9 Jean*0058         IF ( MASTER_CPU_IO(myThid) ) THEN
                0059 C--   only the master thread is allowed to switch On/Off mon_write_stdout
88f72205aa Jean*0060 C     & mon_write_mnc (since it is the only thread that uses those flags):
5a216cc0f7 Jean*0061 
                0062           IF (monitor_stdio) THEN
                0063             mon_write_stdout = .TRUE.
                0064           ELSE
                0065             mon_write_stdout = .FALSE.
                0066           ENDIF
                0067           mon_write_mnc    = .FALSE.
                0068 #ifdef ALLOW_MNC
                0069           IF (useMNC .AND. PTRACERS_monitor_mnc) THEN
                0070             WRITE(mon_fname,'(A)') 'monitor_ptracer'
                0071             CALL MNC_CW_APPEND_VNAME(
                0072      &           'T', '-_-_--__-__t', 0,0, myThid)
                0073             CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
51b16d3111 Davi*0074             CALL MNC_CW_RL_W_S(
                0075      &          'D',mon_fname,1,1,'T', myTime, myThid)
5a216cc0f7 Jean*0076             CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
                0077             mon_write_mnc = .TRUE.
                0078           ENDIF
51b16d3111 Davi*0079 #endif /* ALLOW_MNC */
5a216cc0f7 Jean*0080 
                0081           IF ( mon_write_stdout ) THEN
                0082             WRITE(msgBuf,'(2A)') '// ==========================',
                0083      &             '============================='
                0084             CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0085             WRITE(msgBuf,'(A)')
                0086      &             '// Begin MONITOR ptracer field statistics'
                0087             CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0088             WRITE(msgBuf,'(2A)') '// ==========================',
                0089      &             '============================='
                0090             CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0091           ENDIF
                0092 
49aab2cab9 Jean*0093 C--   endif master cpu io
0badf4857e Mart*0094        ENDIF
                0095 
5a216cc0f7 Jean*0096 C--   Ptracers field monitor : compute stats & write
                0097        IF ( PTRACERS_monitorFreq .NE. monitorFreq
                0098      &     .OR. (useMNC.AND.PTRACERS_monitor_mnc) ) THEN
                0099 C      repeat printing of time to make grepping easier, default is not
                0100 C      to do this, because the default is to use the same monitorFreq
                0101 C      for ptracers as for the dynamics variables.
0badf4857e Mart*0102          CALL MON_SET_PREF('trctime',myThid)
                0103          CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid)
                0104          CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid)
5a216cc0f7 Jean*0105        ENDIF
                0106 C      Print the basic statistics of ptracer variables
0badf4857e Mart*0107        CALL MON_SET_PREF('trcstat_',myThid)
                0108        DO ip = 1, PTRACERS_numInUse
01111eb599 Jean*0109          WRITE(suff,'(A7,A2)') 'ptracer',PTRACERS_ioLabel(ip)
                0110 c        WRITE(suff,'(A6,I4.4)') 'ptrac', ip
b8b300fc52 Jean*0111          CALL MON_WRITESTATS_RL(
                0112      &            Nr, pTracer(1-OLx,1-OLy,1,1,1,ip), suff,
                0113      &            hFacC, maskInC, rA ,drF, dummyRL, myThid )
0badf4857e Mart*0114        ENDDO
                0115 
5a216cc0f7 Jean*0116 C--   Ptracers field monitor finish
49aab2cab9 Jean*0117        IF ( MASTER_CPU_IO(myThid) ) THEN
5a216cc0f7 Jean*0118 C-    only the master thread is allowed to switch On/Off mon_write_stdout
88f72205aa Jean*0119 C     & mon_write_mnc (since it is the only thread that uses those flags):
5a216cc0f7 Jean*0120 
                0121         IF ( mon_write_stdout ) THEN
0badf4857e Mart*0122          WRITE(msgBuf,'(2A)') '// ==========================',
                0123      &        '============================='
                0124          CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
5a216cc0f7 Jean*0125          WRITE(msgBuf,'(A)')
ca88f5d701 Jean*0126      &        '// End MONITOR ptracer field statistics'
5a216cc0f7 Jean*0127          CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
0badf4857e Mart*0128          WRITE(msgBuf,'(2A)') '// ==========================',
                0129      &        '============================='
                0130          CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0131         ENDIF
                0132 
                0133         mon_write_stdout = .FALSE.
5a216cc0f7 Jean*0134         mon_write_mnc    = .FALSE.
                0135 
49aab2cab9 Jean*0136 C-    endif master cpu io
0badf4857e Mart*0137        ENDIF
de55280acd Mart*0138 
5a216cc0f7 Jean*0139 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
de55280acd Mart*0140 
49aab2cab9 Jean*0141 C---  endif different multiple
0badf4857e Mart*0142       ENDIF
                0143 
                0144 #endif /* ALLOW_MONITOR */
                0145 #endif /* ALLOW_PTRACERS */
                0146 
                0147       RETURN
                0148       END