C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/ptracers/ptracers_monitor.F,v 1.12 2006/08/08 21:24:31 jmc Exp $ C $Name: $ #include "PTRACERS_OPTIONS.h" CBOP C !ROUTINE: PTRACERS_MONITOR C !INTERFACE: ========================================================== SUBROUTINE PTRACERS_MONITOR( I myIter, myTime, myThid ) C !DESCRIPTION: C writes out ptracer statistics C !USES: =============================================================== IMPLICIT NONE #include "SIZE.h" #include "EEPARAMS.h" #include "EESUPPORT.h" #include "PARAMS.h" #include "GRID.h" #include "PTRACERS_SIZE.h" #include "PTRACERS.h" #ifdef ALLOW_MONITOR #include "MONITOR.h" #endif C !INPUT PARAMETERS: =================================================== C myTime :: current time C myIter :: current timestep C myThid :: thread number _RL myTime INTEGER myIter INTEGER myThid C === Functions ==== LOGICAL DIFFERENT_MULTIPLE EXTERNAL DIFFERENT_MULTIPLE #ifdef ALLOW_PTRACERS #ifdef ALLOW_MONITOR C !LOCAL VARIABLES: ==================================================== C i,j :: loop indices C ip :: ptracer number CHARACTER*(MAX_LEN_MBUF) msgBuf CHARACTER*(MAX_LEN_MBUF) suff INTEGER ip CEOP IF ( DIFFERENT_MULTIPLE( PTRACERS_monitorFreq,myTime,deltaTClock ) & ) THEN C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| C-- Ptracers field monitor start #ifdef ALLOW_USE_MPI IF ( .NOT.useSingleCPUIO .OR. mpiMyId.EQ.0 ) THEN #endif /* ALLOW_USE_MPI */ _BEGIN_MASTER(myThid) C- only the master thread is allowed to switch On/Off mon_write_stdout C & mon_write_mnc (since it's the only thread that uses those flags): IF (monitor_stdio) THEN mon_write_stdout = .TRUE. ELSE mon_write_stdout = .FALSE. ENDIF mon_write_mnc = .FALSE. #ifdef ALLOW_MNC IF (useMNC .AND. PTRACERS_monitor_mnc) THEN WRITE(mon_fname,'(A)') 'monitor_ptracer' CALL MNC_CW_APPEND_VNAME( & 'T', '-_-_--__-__t', 0,0, myThid) CALL MNC_CW_SET_UDIM(mon_fname, -1, myThid) CALL MNC_CW_I_W_S( & 'I',mon_fname,1,1,'T', myIter, myThid) CALL MNC_CW_SET_UDIM(mon_fname, 0, myThid) mon_write_mnc = .TRUE. ENDIF #endif /* ALLOW_MNC */ IF ( mon_write_stdout ) THEN WRITE(msgBuf,'(2A)') '// ==========================', & '=============================' CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1) WRITE(msgBuf,'(A)') & '// Begin MONITOR ptracer field 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) #ifdef ALLOW_USE_MPI ENDIF #endif /* ALLOW_USE_MPI */ C-- Ptracers field monitor : compute stats & write IF ( PTRACERS_monitorFreq .NE. monitorFreq & .OR. (useMNC.AND.PTRACERS_monitor_mnc) ) THEN C repeat printing of time to make grepping easier, default is not C to do this, because the default is to use the same monitorFreq C for ptracers as for the dynamics variables. CALL MON_SET_PREF('trctime',myThid) CALL MON_OUT_I( '_tsnumber', myIter,mon_string_none,myThid) CALL MON_OUT_RL('_secondsf', myTime,mon_string_none,myThid) ENDIF C Print the basic statistics of ptracer variables CALL MON_SET_PREF('trcstat_',myThid) DO ip = 1, PTRACERS_numInUse WRITE(suff,'(A7,I2.2)') 'ptracer',ip c WRITE(suff,'(A7,I3.3)') 'ptrac_', ip CALL MON_PRINTSTATS_RL( & Nr, ptracer(1-Olx,1-Oly,1,1,1,ip), & suff, maskC,hFacC,rA ,drF,myThid) ENDDO C-- Ptracers field monitor finish #ifdef ALLOW_USE_MPI IF ( .NOT. useSingleCPUIO .OR. mpiMyId .EQ. 0 ) THEN #endif /* ALLOW_USE_MPI */ _BEGIN_MASTER(myThid) C- only the master thread is allowed to switch On/Off mon_write_stdout C & mon_write_mnc (since it's the only thread that uses those flags): IF ( mon_write_stdout ) THEN WRITE(msgBuf,'(2A)') '// ==========================', & '=============================' CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1) WRITE(msgBuf,'(A)') & '// End MONITOR ptracers field statistics' CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1) WRITE(msgBuf,'(2A)') '// ==========================', & '=============================' CALL PRINT_MESSAGE( msgBuf, mon_ioUnit, SQUEEZE_RIGHT , 1) ENDIF mon_write_stdout = .FALSE. mon_write_mnc = .FALSE. _END_MASTER(myThid) #ifdef ALLOW_USE_MPI ENDIF #endif /* ALLOW_USE_MPI */ C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| C endif different multiple ENDIF #endif /* ALLOW_MONITOR */ #endif /* ALLOW_PTRACERS */ RETURN END