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
0c43cc41de Patr*0001 #include "PTRACERS_OPTIONS.h"
1198adf517 Jean*0002 #ifdef ALLOW_AUTODIFF
                0003 # include "AUTODIFF_OPTIONS.h"
                0004 #endif
0c43cc41de Patr*0005 
                0006 CBOP
                0007 C !ROUTINE: ADPTRACERS_MONITOR
                0008 
                0009 C !INTERFACE: ==========================================================
                0010       SUBROUTINE ADPTRACERS_MONITOR(
807164ee95 Jean*0011      I                    myTime, myIter, myThid )
0c43cc41de Patr*0012 
                0013 C !DESCRIPTION:
                0014 C writes out ptracer statistics
                0015 
                0016 C !USES: ===============================================================
                0017       IMPLICIT NONE
                0018 #include "SIZE.h"
                0019 #include "EEPARAMS.h"
                0020 #include "PARAMS.h"
                0021 #include "GRID.h"
                0022 #include "PTRACERS_SIZE.h"
                0023 #include "PTRACERS_PARAMS.h"
                0024 #include "PTRACERS_FIELDS.h"
                0025 #ifdef ALLOW_MONITOR
1198adf517 Jean*0026 # include "MONITOR.h"
0c43cc41de Patr*0027 #endif
1198adf517 Jean*0028 #ifdef ALLOW_AUTODIFF_MONITOR
                0029 # include "ptracers_adcommon.h"
0c43cc41de Patr*0030 #endif
                0031 
                0032 C !INPUT PARAMETERS: ===================================================
                0033 C  myTime               :: current time
                0034 C  myIter               :: current timestep
                0035 C  myThid               :: thread number
                0036       _RL     myTime
                0037       INTEGER myIter
                0038       INTEGER myThid
                0039 
                0040 C     === Functions ====
                0041       LOGICAL  DIFFERENT_MULTIPLE
                0042       EXTERNAL DIFFERENT_MULTIPLE
                0043       LOGICAL  MASTER_CPU_IO
                0044       EXTERNAL MASTER_CPU_IO
                0045 
                0046 #ifdef ALLOW_PTRACERS
                0047 #ifdef ALLOW_MONITOR
                0048 
3846922d37 Jean*0049 #ifdef ALLOW_AUTODIFF_MONITOR
                0050 
0c43cc41de Patr*0051 C !LOCAL VARIABLES: ====================================================
                0052 C  i,j                  :: loop indices
                0053 C  ip                   :: ptracer number
                0054       CHARACTER*(MAX_LEN_MBUF) msgBuf
                0055       CHARACTER*(MAX_LEN_MBUF) suff
                0056       INTEGER ip
                0057       _RL dummyRL(6)
                0058 CEOP
                0059 
                0060       IF ( DIFFERENT_MULTIPLE( adjmonitorFreq,myTime,deltaTClock )
                0061      &   ) THEN
                0062 
                0063 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0064 
                0065 C--   Ptracers field monitor start
                0066         IF ( MASTER_CPU_IO(myThid) ) THEN
                0067 C--   only the master thread is allowed to switch On/Off mon_write_stdout
                0068 C     & mon_write_mnc (since it is the only thread that uses those flags):
                0069 
                0070           IF (monitor_stdio) THEN
                0071             mon_write_stdout = .TRUE.
                0072           ELSE
                0073             mon_write_stdout = .FALSE.
                0074           ENDIF
                0075           mon_write_mnc    = .FALSE.
                0076 #ifdef ALLOW_MNC
                0077           IF (useMNC .AND. PTRACERS_monitor_mnc) THEN
                0078             WRITE(mon_fname,'(A)') 'monitor_ptracer'
                0079             CALL MNC_CW_APPEND_VNAME(
                0080      &           'T', '-_-_--__-__t', 0,0, myThid)
                0081             CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid)
                0082             CALL MNC_CW_RL_W_S(
                0083      &          'D',mon_fname,1,1,'T', myTime, myThid)
                0084             CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid)
                0085             mon_write_mnc = .TRUE.
                0086           ENDIF
                0087 #endif /* ALLOW_MNC */
                0088 
                0089           IF ( mon_write_stdout ) THEN
                0090             WRITE(msgBuf,'(2A)') '// ==========================',
                0091      &             '============================='
                0092             CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0093             WRITE(msgBuf,'(A)')
ca88f5d701 Jean*0094      &             '// Begin AD_MONITOR ptracer field statistics'
0c43cc41de Patr*0095             CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0096             WRITE(msgBuf,'(2A)') '// ==========================',
                0097      &             '============================='
                0098             CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0099           ENDIF
                0100 
                0101 C--   endif master cpu io
                0102        ENDIF
                0103 
                0104 C      Print the basic statistics of ptracer variables
                0105        CALL MON_SET_PREF('ad_trcstat_',myThid)
                0106        DO ip = 1, PTRACERS_numInUse
feb9c444ae Patr*0107          WRITE(suff,'(A9,A2)') 'adptracer',PTRACERS_ioLabel(ip)
0c43cc41de Patr*0108          CALL MON_WRITESTATS_RL(
                0109      &            Nr, adptracer(1-OLx,1-OLy,1,1,1,ip), suff,
                0110      &            hFacC, maskInC, rA ,drF, dummyRL, myThid )
                0111        ENDDO
                0112 
                0113 C--   Ptracers field monitor finish
                0114        IF ( MASTER_CPU_IO(myThid) ) THEN
                0115 C-    only the master thread is allowed to switch On/Off mon_write_stdout
                0116 C     & mon_write_mnc (since it is the only thread that uses those flags):
                0117 
                0118         IF ( mon_write_stdout ) THEN
                0119          WRITE(msgBuf,'(2A)') '// ==========================',
                0120      &        '============================='
                0121          CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0122          WRITE(msgBuf,'(A)')
ca88f5d701 Jean*0123      &        '// End AD_MONITOR ptracer field statistics'
0c43cc41de Patr*0124          CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0125          WRITE(msgBuf,'(2A)') '// ==========================',
                0126      &        '============================='
                0127          CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1)
                0128         ENDIF
                0129 
                0130         mon_write_stdout = .FALSE.
                0131         mon_write_mnc    = .FALSE.
                0132 
                0133 C-    endif master cpu io
                0134        ENDIF
                0135 
                0136 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0137 
                0138 C---  endif different multiple
                0139       ENDIF
                0140 
3846922d37 Jean*0141 #endif /* ALLOW_AUTODIFF_MONITOR */
0c43cc41de Patr*0142 
                0143 #endif /* ALLOW_MONITOR */
                0144 #endif /* ALLOW_PTRACERS */
                0145 
                0146       RETURN
                0147       END