Back to home page

MITgcm

 
 

    


File indexing completed on 2025-11-07 06:08:45 UTC

view on githubraw file Latest commit b7411f1a on 2025-11-06 19:05:26 UTC
b862faca7c Jean*0001 #include "PTRACERS_OPTIONS.h"
46918f1b26 Jean*0002 #include "GAD_OPTIONS.h"
b862faca7c Jean*0003 
                0004 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0005 CBOP
                0006 C     !ROUTINE: PTRACERS_CHECK
                0007 
                0008 C     !INTERFACE:
                0009       SUBROUTINE PTRACERS_CHECK( myThid )
                0010 
                0011 C     !DESCRIPTION:
                0012 C     Print summary of PTRACERS setting and Check dependances
                0013 C     with main model and other packages
                0014 
                0015 C     !USES:
                0016       IMPLICIT NONE
                0017 #include "SIZE.h"
                0018 #include "EEPARAMS.h"
                0019 #include "PARAMS.h"
                0020 #include "PTRACERS_SIZE.h"
                0021 #include "PTRACERS_PARAMS.h"
                0022 #include "GAD.h"
                0023 
                0024 C     !INPUT PARAMETERS:
                0025       INTEGER myThid
                0026 CEOP
                0027 
                0028 #ifdef ALLOW_PTRACERS
                0029 C     !LOCAL VARIABLES:
                0030 C     iTracer    :: tracer index
                0031 C     iUnit      :: unit number for I/O
                0032 C     msgBuf     :: Informational/error message buffer
                0033       INTEGER iTracer
46918f1b26 Jean*0034       INTEGER iUnit, errCount
b862faca7c Jean*0035       CHARACTER*(MAX_LEN_MBUF) msgBuf
                0036 
                0037 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0038 
                0039       _BEGIN_MASTER(myThid)
46918f1b26 Jean*0040       errCount = 0
b862faca7c Jean*0041 
                0042       WRITE(msgBuf,'(A)') 'PTRACERS_CHECK: #define ALLOW_PTRACERS'
                0043       CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0044      &                    SQUEEZE_RIGHT, myThid )
                0045 
                0046 C--   Print a summary of pTracer parameter values:
                0047       iUnit = standardMessageUnit
                0048       WRITE(msgBuf,'(A)') '// ==================================='
                0049       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
                0050       WRITE(msgBuf,'(A)') '// PTRACERS parameters '
                0051       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
                0052       WRITE(msgBuf,'(A)') '// ==================================='
                0053       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
                0054       CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
                0055      &   'PTRACERS_numInUse =',
                0056      &   ' /* number of tracers */')
                0057       CALL WRITE_0D_I( PTRACERS_Iter0, INDEX_NONE,
                0058      &   'PTRACERS_Iter0 =',
                0059      &   ' /* timestep number when tracers are initialized */')
                0060       CALL WRITE_0D_L( PTRACERS_startAllTrc, INDEX_NONE,
                0061      &   'PTRACERS_startAllTrc =','/* all tracers start @ startTime */')
fc10d43a89 Jean*0062       CALL WRITE_0D_L( PTRACERS_doAB_onGpTr, INDEX_NONE,
                0063      &   'PTRACERS_doAB_onGpTr =',
                0064      &   '/* apply AB on Tendencies (rather than on Tracers) */')
b862faca7c Jean*0065       CALL WRITE_0D_L( PTRACERS_addSrelax2EmP, INDEX_NONE,
                0066      &   'PTRACERS_addSrelax2EmP =','/* add Salt relaxation to EmP */')
                0067       CALL WRITE_1D_RL( PTRACERS_dTLev, Nr, INDEX_K,
                0068      &   'PTRACERS_dTLev =',
                0069      &'   /* Ptracer timestep ( s ) */')
51ed6fbf34 Jean*0070       CALL WRITE_0D_RL(PTRACERS_monitorFreq, INDEX_NONE,
                0071      &   'PTRACERS_monitorFreq =',
                0072      &   ' /* Frequency^-1 for monitor output (s) */')
b862faca7c Jean*0073       CALL WRITE_0D_RL(PTRACERS_dumpFreq, INDEX_NONE,
                0074      &   'PTRACERS_dumpFreq =',
                0075      &   ' /* Frequency^-1 for snapshot output (s) */')
                0076       CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
                0077      &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
                0078 
                0079       CALL WRITE_0D_L( PTRACERS_snapshot_mnc, INDEX_NONE,
                0080      &     'PTRACERS_snapshot_mnc =',
                0081      &     ' /* use MNC for snapshot output */')
                0082       CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
                0083      &     'PTRACERS_pickup_write_mnc =',
                0084      &     ' /* use MNC for writing pickups */')
                0085       CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
                0086      &     'PTRACERS_pickup_read_mnc =',
                0087      &     ' /* use MNC for reading pickups */')
                0088 
                0089       DO iTracer=1,PTRACERS_numInUse
                0090         WRITE(msgBuf,'(A)') ' -----------------------------------'
                0091         CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0092         WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
                0093         CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0094         CALL WRITE_0D_C( PTRACERS_names(iTracer), -1, INDEX_NONE,
                0095      &     'PTRACERS_names =', ' /* Tracer short name */')
                0096         CALL WRITE_0D_C( PTRACERS_long_names(iTracer), -1, INDEX_NONE,
                0097      &     'PTRACERS_long_names =', ' /* Tracer long name */')
                0098         CALL WRITE_0D_C( PTRACERS_ioLabel(iTracer), 0, INDEX_NONE,
                0099      &     'PTRACERS_ioLabel =', ' /* tracer IO Label */')
                0100         IF ( .NOT.PTRACERS_startAllTrc )
                0101      &  CALL WRITE_0D_RL( PTRACERS_startStepFwd(iTracer), INDEX_NONE,
                0102      &     'PTRACERS_startStepFwd =', ' /* tracer starting time */')
                0103         CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
                0104      &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
                0105         CALL WRITE_0D_L( PTRACERS_SOM_Advection(iTracer), INDEX_NONE,
                0106      &     'PTRACERS_SOM_Advection =',
                0107      &     ' /* tracer uses SOM advection scheme */')
                0108         CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
                0109      &     'PTRACERS_ImplVertAdv =',
                0110      &     ' /* implicit vert. advection flag */')
fc10d43a89 Jean*0111         CALL WRITE_0D_L( PTRACERS_MultiDimAdv(iTracer), INDEX_NONE,
                0112      &     'PTRACERS_MultiDimAdv =',
                0113      &     ' /* tracer uses Multi-Dim advection */')
                0114         CALL WRITE_0D_L( PTRACERS_AdamsBashGtr(iTracer), INDEX_NONE,
                0115      &     'PTRACERS_AdamsBashGtr =',
                0116      &     ' /* apply AB on tracer tendency */')
                0117         CALL WRITE_0D_L( PTRACERS_AdamsBash_Tr(iTracer), INDEX_NONE,
                0118      &     'PTRACERS_AdamsBash_Tr =',
                0119      &     ' /* apply AB on passive tracer */')
b862faca7c Jean*0120         CALL WRITE_0D_RL( PTRACERS_diffKh(iTracer), INDEX_NONE,
                0121      &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
                0122         CALL WRITE_0D_RL( PTRACERS_diffK4(iTracer), INDEX_NONE,
                0123      &     'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
                0124         CALL WRITE_1D_RL( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
                0125      &     'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
                0126         CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
                0127      &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
                0128         CALL WRITE_0D_L( PTRACERS_useDWNSLP(iTracer), INDEX_NONE,
                0129      &     'PTRACERS_useDWNSLP =', ' /* apply DOWN-SLOPE Flow */')
                0130         CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
                0131      &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
46918f1b26 Jean*0132 #ifdef GAD_SMOLARKIEWICZ_HACK
                0133         CALL WRITE_0D_L( PTRACERS_stayPositive(iTracer), INDEX_NONE,
                0134      &     'PTRACERS_stayPositive =',
                0135      &     ' /* use Smolarkiewicz Hack for this tracer */')
                0136 #endif
b862faca7c Jean*0137         CALL WRITE_1D_RL( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
                0138      &     'PTRACERS_ref =', ' /* Reference vertical profile */')
                0139         CALL WRITE_0D_RL( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
                0140      &     'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
                0141 
                0142       ENDDO
                0143       WRITE(msgBuf,'(A)') ' -----------------------------------'
                0144       CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
                0145 
                0146 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0147 
                0148       IF ( PTRACERS_Iter0.GE.nEndIter ) THEN
                0149         WRITE(msgBuf,'(2A)') '** WARNING ** PTRACERS_CHECK:',
                0150      &       ' PTRACERS_Iter0 beyond run-end (=nEndIter)'
                0151         CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
                0152      &                      SQUEEZE_RIGHT, myThid )
                0153         WRITE(msgBuf,'(2A)') '** WARNING ** PTRACERS_CHECK:',
                0154      &       ' ==> do not load initial conditions nor pickup file'
                0155         CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
                0156      &                      SQUEEZE_RIGHT, myThid )
                0157       ELSEIF ( PTRACERS_Iter0.GT.nIter0 ) THEN
46918f1b26 Jean*0158         WRITE(msgBuf,'(2A)') 'PTRACERS_CHECK:',
b862faca7c Jean*0159      &       ' wrong setting of PTRACERS_Iter0 :'
                0160         CALL PRINT_ERROR( msgBuf, myThid )
46918f1b26 Jean*0161         WRITE(msgBuf,'(2A)') 'PTRACERS_CHECK:',
b862faca7c Jean*0162      &       ' nIter0 < PTRACERS_Iter0 < nEndIter not supported'
                0163         CALL PRINT_ERROR( msgBuf, myThid )
46918f1b26 Jean*0164         errCount = errCount + 1
b862faca7c Jean*0165       ENDIF
                0166 
                0167 #ifndef INCLUDE_IMPLVERTADV_CODE
                0168       DO iTracer=1,PTRACERS_numInUse
                0169        IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
                0170         WRITE(msgBuf,'(A)')
                0171      &   'PTRACERS_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
                0172         CALL PRINT_ERROR( msgBuf, myThid )
46918f1b26 Jean*0173         WRITE(msgBuf,'(2A,I4,A)') 'PTRACERS_CHECK:',
b862faca7c Jean*0174      &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
                0175         CALL PRINT_ERROR( msgBuf, myThid )
46918f1b26 Jean*0176         errCount = errCount + 1
b862faca7c Jean*0177        ENDIF
                0178       ENDDO
                0179       IF ( PTRACERS_dTLev(1).NE.PTRACERS_dTLev(Nr)
                0180      &     .AND. implicitDiffusion ) THEN
                0181         WRITE(msgBuf,'(A)')
                0182      &   'PTRACERS_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
                0183         CALL PRINT_ERROR( msgBuf , myThid)
                0184         WRITE(msgBuf,'(2A)') 'PTRACERS_CHECK: ',
                0185      &   'but implicitDiffusion=T with non-uniform PTRACERS_dTLev'
                0186         CALL PRINT_ERROR( msgBuf , myThid)
46918f1b26 Jean*0187         errCount = errCount + 1
b862faca7c Jean*0188       ENDIF
                0189 #endif
                0190       DO iTracer=1,PTRACERS_numInUse
46918f1b26 Jean*0191        IF ( PTRACERS_useGMRedi(iTracer) .AND. .NOT.useGMRedi ) THEN
                0192         WRITE(msgBuf,'(2A,I4,A)') 'PTRACERS_CHECK:',
                0193      &    ' pTracers_useGMRedi(',iTracer,' ) is TRUE'
                0194         CALL PRINT_ERROR( msgBuf, myThid )
                0195         WRITE(msgBuf,'(A,L5,A)')
                0196      &    'PTRACERS_CHECK: But not useGMRedi (=',useGMRedi,')'
                0197         CALL PRINT_ERROR( msgBuf, myThid )
                0198         errCount = errCount + 1
                0199        ENDIF
                0200        IF ( PTRACERS_useDWNSLP(iTracer) .AND. .NOT.useDOWN_SLOPE ) THEN
                0201         WRITE(msgBuf,'(2A,I4,A)') 'PTRACERS_CHECK:',
                0202      &    ' pTracers_useDWNSLP(',iTracer,' ) is TRUE'
                0203         CALL PRINT_ERROR( msgBuf, myThid )
                0204         WRITE(msgBuf,'(2A,L5,A)') 'PTRACERS_CHECK:',
                0205      &    ' But not useDOWN_SLOPE (=', useDOWN_SLOPE, ')'
                0206         CALL PRINT_ERROR( msgBuf, myThid )
                0207         errCount = errCount + 1
                0208        ENDIF
                0209        IF ( PTRACERS_useKPP(iTracer) .AND. .NOT.useKPP ) THEN
                0210         WRITE(msgBuf,'(2A,I4,A)') 'PTRACERS_CHECK:',
                0211      &    ' pTracers_useKPP(',iTracer,' ) is TRUE'
                0212         CALL PRINT_ERROR( msgBuf, myThid )
                0213         WRITE(msgBuf,'(A,L5,A)')
                0214      &    'PTRACERS_CHECK: But not useKPP (=',useKPP,')'
                0215         CALL PRINT_ERROR( msgBuf, myThid )
                0216         errCount = errCount + 1
                0217        ENDIF
                0218 #ifndef GAD_SMOLARKIEWICZ_HACK
                0219        IF ( PTRACERS_stayPositive(iTracer) ) THEN
                0220         WRITE(msgBuf,'(2A)') 'PTRACERS_CHECK:',
                0221      &    ' Smolarkiewicz Hack code is not compiled'
                0222         CALL PRINT_ERROR( msgBuf, myThid )
                0223         WRITE(msgBuf,'(2A,I4,A)') 'PTRACERS_CHECK:',
                0224      &    ' but needed to keep pTracer(', iTracer, ' ) positive.'
                0225         CALL PRINT_ERROR( msgBuf, myThid )
                0226         WRITE(msgBuf,'(2A)') 'PTRACERS_CHECK: Re-compile with: ',
                0227      &    ' #define GAD_SMOLARKIEWICZ_HACK in GAD_OPTIONS.h'
                0228         CALL PRINT_ERROR( msgBuf , myThid)
                0229         errCount = errCount + 1
                0230        ENDIF
                0231 #endif /* ndef GAD_SMOLARKIEWICZ_HACK */
7448700841 Mart*0232 #ifndef PTRACERS_ALLOW_DYN_STATE
                0233        IF ( PTRACERS_SOM_Advection(iTracer) ) THEN
                0234         WRITE(msgBuf,'(2A,I4,A)') 'PTRACERS_CHECK:',
                0235      &    ' PTRACERS_SOM_Advection(', iTracer, ') = T, but'
                0236         CALL PRINT_ERROR( msgBuf, myThid )
                0237         WRITE(msgBuf,'(3A)') 'PTRACERS_CHECK:',
                0238      &    ' PTRACERS_ALLOW_DYN_STATE is not defined',
                0239      &    ' in PTRACERS_OPTIONS.h.'
                0240         CALL PRINT_ERROR( msgBuf, myThid )
                0241         errCount = errCount + 1
                0242        ENDIF
                0243 #endif
b862faca7c Jean*0244       ENDDO
                0245 
46918f1b26 Jean*0246       IF ( errCount.GE.1 ) THEN
                0247         WRITE(msgBuf,'(A,I5,A)')
                0248      &       'PTRACERS_CHECK: detected', errCount,' fatal error(s)'
                0249         CALL PRINT_ERROR( msgBuf, myThid )
                0250         CALL ALL_PROC_DIE( 0 )
                0251         STOP 'ABNORMAL END: S/R PTRACERS_CHECK'
                0252       ENDIF
                0253 
b862faca7c Jean*0254       _END_MASTER(myThid)
                0255 C     Everyone else must wait for the parameters to be loaded
                0256       _BARRIER
                0257 
                0258 #endif /* ALLOW_PTRACERS */
                0259 
                0260       RETURN
                0261       END