/[MITgcm]/MITgcm/pkg/ptracers/ptracers_readparms.F
ViewVC logotype

Diff of /MITgcm/pkg/ptracers/ptracers_readparms.F

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

revision 1.13 by mlosch, Sun Nov 28 23:50:59 2004 UTC revision 1.37 by jmc, Tue Nov 16 17:46:00 2010 UTC
# Line 6  C $Name$ Line 6  C $Name$
6  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7  CBOP  CBOP
8  C     !ROUTINE: PTRACERS_READPARMS  C     !ROUTINE: PTRACERS_READPARMS
9          
10  C     !INTERFACE:  C     !INTERFACE:
11        SUBROUTINE PTRACERS_READPARMS( myThid )        SUBROUTINE PTRACERS_READPARMS( myThid )
12          
13  C     !DESCRIPTION:  C     !DESCRIPTION:
14  C     Initialize PTRACERS parameters, read in data.ptracers  C     Initialize PTRACERS parameters, read in data.ptracers
15    
# Line 17  C     !USES: Line 17  C     !USES:
17        IMPLICIT NONE        IMPLICIT NONE
18  #include "SIZE.h"  #include "SIZE.h"
19  #include "EEPARAMS.h"  #include "EEPARAMS.h"
20    #ifdef ALLOW_LONGSTEP
21    #include "LONGSTEP_PARAMS.h"
22    #endif
23  #include "PTRACERS_SIZE.h"  #include "PTRACERS_SIZE.h"
24  #include "PTRACERS.h"  #include "PTRACERS_PARAMS.h"
25  #include "PARAMS.h"  #include "PARAMS.h"
26    #ifdef ALLOW_MNC
27    #include "MNC_PARAMS.h"
28    #endif
29    
30  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
31        INTEGER myThid        INTEGER myThid
32  CEOP  CEOP
33    
34  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
35    C     !FUNCTIONS
36          LOGICAL  GAD_VALID_ADVSCHEME
37          EXTERNAL GAD_VALID_ADVSCHEME
38    
39  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
40  C     k,iTracer  :: loop indices  C     k,iTracer  :: loop indices
# Line 34  C     msgBuf     :: message buffer Line 43  C     msgBuf     :: message buffer
43        INTEGER k, iTracer        INTEGER k, iTracer
44        INTEGER iUnit        INTEGER iUnit
45        INTEGER ic        INTEGER ic
46          LOGICAL validNum
47        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
48        _RL PTRACERS_diffKr(PTRACERS_num)        _RL PTRACERS_diffKr(PTRACERS_num)
49          _RL tauTr1ClimRelax
50    
51  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
52  C                          are written to post-processing files.  C                          are written to post-processing files.
53    C     tauTr1ClimRelax :: old parameter (will be removed 1 day)
54        NAMELIST /PTRACERS_PARM01/        NAMELIST /PTRACERS_PARM01/
55         &     tauTr1ClimRelax,
56         &     PTRACERS_dumpFreq,
57       &     PTRACERS_taveFreq,       &     PTRACERS_taveFreq,
58       &     PTRACERS_monitorFreq,       &     PTRACERS_monitorFreq,
59       &     PTRACERS_advScheme,       &     PTRACERS_advScheme,
60         &     PTRACERS_ImplVertAdv,
61       &     PTRACERS_diffKh,       &     PTRACERS_diffKh,
62       &     PTRACERS_diffK4,       &     PTRACERS_diffK4,
63       &     PTRACERS_diffKr,       &     PTRACERS_diffKr,
64       &     PTRACERS_diffKrNr,       &     PTRACERS_diffKrNr,
65         &     PTRACERS_ref,
66         &     PTRACERS_EvPrRn,
67         &     PTRACERS_addSrelax2EmP,
68       &     PTRACERS_useGMRedi,       &     PTRACERS_useGMRedi,
69         &     PTRACERS_useDWNSLP,
70       &     PTRACERS_useKPP,       &     PTRACERS_useKPP,
71         &     PTRACERS_Iter0,
72       &     PTRACERS_numInUse,       &     PTRACERS_numInUse,
73       &     PTRACERS_initialFile,       &     PTRACERS_initialFile,
74       &     PTRACERS_useRecords,       &     PTRACERS_useRecords,
75       &     PTRACERS_names,       &     PTRACERS_names,
76       &     PTRACERS_long_names,       &     PTRACERS_long_names,
77       &     PTRACERS_units,       &     PTRACERS_units,
78       &     PTRACERS_read_mnc,       &     PTRACERS_timeave_mnc,
79       &     PTRACERS_write_mnc       &     PTRACERS_snapshot_mnc,
80         &     PTRACERS_monitor_mnc,
81         &     PTRACERS_pickup_write_mnc,
82         &     PTRACERS_pickup_read_mnc
83    
84          _BEGIN_MASTER(myThid)
85    
86  C     This routine has been called by the main model so we set our  C     This routine has been called by the main model so we set our
87  C     internal flag to indicate we are in business  C     internal flag to indicate we are in business
88        PTRACERSisON=.TRUE.  c     PTRACERSisON=.TRUE.
89    C Note(jmc): remove this flag which is not really usefull (not set properly
90    C            when usePTRACERS=F and always TRUE otherwise);
91    C            much better to use "usePTRACERS" flag instead.
92    
93    C     Set ptracer IO & diagnostics labels (2 characters long)
94          CALL PTRACERS_SET_IOLABEL(
95         O                           PTRACERS_ioLabel,
96         I                           PTRACERS_num, myThid )
97    
98  C     Set defaults values for parameters in PTRACERS.h  C     Set defaults values for parameters in PTRACERS.h
99          PTRACERS_dumpFreq    = dumpFreq
100        PTRACERS_taveFreq    = taveFreq        PTRACERS_taveFreq    = taveFreq
101        PTRACERS_monitorFreq = monitorFreq        PTRACERS_monitorFreq = monitorFreq
102          PTRACERS_Iter0   = 0
103        PTRACERS_numInUse=-1        PTRACERS_numInUse=-1
104        DO iTracer=1,PTRACERS_num        DO iTracer=1,PTRACERS_num
105          PTRACERS_advScheme(iTracer)=saltAdvScheme          PTRACERS_advScheme(iTracer)=saltAdvScheme
106            PTRACERS_ImplVertAdv(iTracer) = .FALSE.
107          PTRACERS_diffKh(iTracer)=diffKhS          PTRACERS_diffKh(iTracer)=diffKhS
108          PTRACERS_diffK4(iTracer)=diffK4S          PTRACERS_diffK4(iTracer)=diffK4S
109          PTRACERS_diffKr(iTracer)=UNSET_RL          PTRACERS_diffKr(iTracer)=UNSET_RL
110          DO k=1,Nr          DO k=1,Nr
111            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
112              PTRACERS_ref     (k,iTracer)=0. _d 0
113          ENDDO          ENDDO
114            PTRACERS_EvPrRn(iTracer)=UNSET_RL
115          PTRACERS_useGMRedi(iTracer)=useGMRedi          PTRACERS_useGMRedi(iTracer)=useGMRedi
116          PTRACERS_useKPP(iTracer)=useKPP          PTRACERS_useDWNSLP(iTracer)=useDOWN_SLOPE
117            PTRACERS_useKPP(iTracer)   =useKPP
118          PTRACERS_initialFile(iTracer)=' '          PTRACERS_initialFile(iTracer)=' '
119          DO ic = 1,MAX_LEN_FNAM          DO ic = 1,MAX_LEN_FNAM
120            PTRACERS_names(iTracer)(ic:ic) = ' '            PTRACERS_names(iTracer)(ic:ic) = ' '
# Line 83  C     Set defaults values for parameters Line 122  C     Set defaults values for parameters
122            PTRACERS_units(iTracer)(ic:ic) = ' '            PTRACERS_units(iTracer)(ic:ic) = ' '
123          ENDDO          ENDDO
124        ENDDO        ENDDO
125        PTRACERS_useRecords  = .FALSE.        PTRACERS_addSrelax2EmP    = .FALSE.
126        PTRACERS_read_mdsio  = .TRUE.        PTRACERS_useRecords       = .FALSE.
127        PTRACERS_read_mnc    = .FALSE.  #ifdef ALLOW_MNC
128        PTRACERS_write_mdsio = .TRUE.        PTRACERS_timeave_mnc      = useMNC .AND. timeave_mnc
129        PTRACERS_write_mnc   = .FALSE.        PTRACERS_snapshot_mnc     = useMNC .AND. snapshot_mnc
130          PTRACERS_monitor_mnc      = useMNC .AND. monitor_mnc
131          PTRACERS_pickup_write_mnc = useMNC .AND. pickup_write_mnc
132          PTRACERS_pickup_read_mnc  = useMNC .AND. pickup_read_mnc
133    #else
134          PTRACERS_timeave_mnc      = .FALSE.
135          PTRACERS_snapshot_mnc     = .FALSE.
136          PTRACERS_monitor_mnc      = .FALSE.
137          PTRACERS_pickup_write_mnc = .FALSE.
138          PTRACERS_pickup_read_mnc  = .FALSE.
139    #endif
140          tauTr1ClimRelax = 0.
141          DO k = 1,Nr
142    #ifdef ALLOW_LONGSTEP
143            PTRACERS_dTLev(k) = LS_nIter*dTtracerLev(k)
144    #else
145            PTRACERS_dTLev(k) = dTtracerLev(k)
146    #endif
147          ENDDO
148    
149  C     Open and read the data.ptracers file  C     Open and read the data.ptracers file
       _BEGIN_MASTER(myThid)  
150        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
151        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
152       &                   SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , myThid )
153        CALL OPEN_COPY_DATA_FILE(        CALL OPEN_COPY_DATA_FILE(
154       I                   'data.ptracers', 'PTRACERS_READPARMS',       I                   'data.ptracers', 'PTRACERS_READPARMS',
155       O                   iUnit,       O                   iUnit,
# Line 101  C     Open and read the data.ptracers fi Line 157  C     Open and read the data.ptracers fi
157        READ(UNIT=iUnit,NML=PTRACERS_PARM01)        READ(UNIT=iUnit,NML=PTRACERS_PARM01)
158        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
159       &  ' PTRACERS_READPARMS: finished reading data.ptracers'       &  ' PTRACERS_READPARMS: finished reading data.ptracers'
160        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
161       &                   SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , myThid )
162    
163  C     Close the open data file  C     Close the open data file
164        CLOSE(iUnit)        CLOSE(iUnit)
       _END_MASTER(myThid)  
   
 C     Everyone else must wait for the parameters to be loaded  
       _BARRIER  
165    
166  C     Now set-up any remaining parameters that result from the input  C     Now set-up any remaining parameters that result from the input
167  C     parameters  C     parameters
168    
169    C     Tracer 1 climatology relaxation time scale (<- but the code is gone !)
170          IF ( tauTr1ClimRelax .EQ. 0. ) THEN
171           lambdaTr1ClimRelax = 0.
172          ELSE
173           lambdaTr1ClimRelax = 1./tauTr1ClimRelax
174          ENDIF
175    
176  C     If PTRACERS_numInUse was not set in data.ptracers then we can  C     If PTRACERS_numInUse was not set in data.ptracers then we can
177  C     assume that all PTRACERS fields will be in use  C     assume that all PTRACERS fields will be in use
178        IF (PTRACERS_numInUse.LT.0) THEN        IF (PTRACERS_numInUse.LT.0) THEN
# Line 121  C     assume that all PTRACERS fields wi Line 180  C     assume that all PTRACERS fields wi
180        ENDIF        ENDIF
181  C     Check we are not trying to use more tracers than allowed  C     Check we are not trying to use more tracers than allowed
182        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
183          WRITE(msgBuf,'(A,I2,A,I2,A)')          WRITE(msgBuf,'(A,I4,A,I4,A)')
184       &       ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,       &       ' PTRACERS_READPARMS: You requested',PTRACERS_numInUse,
185       &       ' tracers at run time when only ',PTRACERS_num,       &       ' tracers at run time when only',PTRACERS_num,
186       &       ' were specified at compile time. Naughty! '       &       ' were specified at compile time. Naughty! '
187          CALL PRINT_ERROR(msgBuf, 1)          CALL PRINT_ERROR( msgBuf, myThid )
188          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
189        ENDIF        ENDIF
190  C     Check that enough parameters were specified  C     Check for valid advection-scheme number
191        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
192          IF (PTRACERS_advScheme(iTracer).EQ.0) THEN          validNum = GAD_VALID_ADVSCHEME( PTRACERS_advScheme(iTracer) )
193            WRITE(msgBuf,'(A,A,I2)')          IF ( .NOT.validNum ) THEN
194       &         ' PTRACERS_READPARMS: ',           WRITE(msgBuf,'(2A,I6)') 'PTRACERS_READPARMS: ',
195       &         'No advect. scheme specified for tracer #',       &   'invalid advection scheme number=',PTRACERS_advScheme(iTracer)
196       &         iTracer           CALL PRINT_ERROR( msgBuf, myThid )
197            CALL PRINT_ERROR(msgBuf, 1)           WRITE(msgBuf,'(2A,I6)') 'PTRACERS_READPARMS: ',
198            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'       &   'for tracer #', iTracer
199             CALL PRINT_ERROR( msgBuf, myThid )
200             STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
201          ENDIF          ENDIF
202        ENDDO        ENDDO
203    #ifndef INCLUDE_IMPLVERTADV_CODE
204        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
205          PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)         IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
206       &                           .AND.useGMRedi          WRITE(msgBuf,'(A)')
207          PTRACERS_useKPP(iTracer) = PTRACERS_useKPP(iTracer)       &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
208       &                        .AND.useKPP          CALL PRINT_ERROR( msgBuf, myThid )
209            WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
210         &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
211            CALL PRINT_ERROR( msgBuf, myThid )
212            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
213           ENDIF
214          ENDDO
215          IF ( PTRACERS_dTLev(1).NE.PTRACERS_dTLev(Nr)
216         &     .AND. implicitDiffusion ) THEN
217            WRITE(msgBuf,'(A)')
218         &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
219            CALL PRINT_ERROR( msgBuf , myThid)
220            WRITE(msgBuf,'(2A)') 'PTRACERS_READPARMS: ',
221         &   'but implicitDiffusion=T with non-uniform PTRACERS_dTLev'
222            CALL PRINT_ERROR( msgBuf , myThid)
223            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
224          ENDIF
225    #endif
226          DO iTracer=1,PTRACERS_numInUse
227            IF ( PTRACERS_useGMRedi(iTracer) .AND. .NOT.useGMRedi ) THEN
228              WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
229         &     ' pTracers_useGMRedi(',iTracer,' ) is TRUE'
230              CALL PRINT_ERROR( msgBuf, myThid )
231              WRITE(msgBuf,'(A,L5,A)')
232         &     'PTRACERS_READPARMS: But not useGMRedi (=',useGMRedi,')'
233              CALL PRINT_ERROR( msgBuf, myThid )
234              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
235            ENDIF
236            IF ( PTRACERS_useDWNSLP(iTracer) .AND. .NOT.useDOWN_SLOPE ) THEN
237              WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
238         &     ' pTracers_useDWNSLP(',iTracer,' ) is TRUE'
239              CALL PRINT_ERROR( msgBuf, myThid )
240              WRITE(msgBuf,'(2A,L5,A)') 'PTRACERS_READPARMS:',
241         &     ' But not useDOWN_SLOPE (=', useDOWN_SLOPE, ')'
242              CALL PRINT_ERROR( msgBuf, myThid )
243              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
244            ENDIF
245            IF ( PTRACERS_useKPP(iTracer) .AND. .NOT.useKPP ) THEN
246              WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
247         &     ' pTracers_useKPP(',iTracer,' ) is TRUE'
248              CALL PRINT_ERROR( msgBuf, myThid )
249              WRITE(msgBuf,'(A,L5,A)')
250         &     'PTRACERS_READPARMS: But not useKPP (=',useKPP,')'
251              CALL PRINT_ERROR( msgBuf, myThid )
252              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
253            ENDIF
254          IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN          IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
255           DO k=1,Nr           DO k=1,Nr
256            PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)            PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
# Line 152  C     Check that enough parameters were Line 259  C     Check that enough parameters were
259        ENDDO        ENDDO
260    
261  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
262        IF (useMNC) THEN        PTRACERS_timeave_mnc      = useMNC .AND. PTRACERS_timeave_mnc
263  C       Set the default I/O Types        PTRACERS_snapshot_mnc     = useMNC .AND. PTRACERS_snapshot_mnc
264          IF (PTRACERS_read_mnc) PTRACERS_read_mdsio = .FALSE.        PTRACERS_monitor_mnc      = useMNC .AND. PTRACERS_monitor_mnc
265          IF ( (.NOT. outputTypesInclusive)        PTRACERS_pickup_write_mnc = useMNC .AND. PTRACERS_pickup_write_mnc
266       &       .AND. PTRACERS_write_mnc ) pickup_write_mdsio = .FALSE.        PTRACERS_pickup_read_mnc  = useMNC .AND. PTRACERS_pickup_read_mnc
267          IF ( (.NOT. outputTypesInclusive)  
268       &       .AND. PTRACERS_write_mnc ) PTRACERS_write_mdsio = .FALSE.        PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)
269                 &     .OR. outputTypesInclusive
270  C       Initialize the MNC variable types for PTRACERS        PTRACERS_snapshot_mdsio     = (.NOT. PTRACERS_snapshot_mnc)
271          CALL PTRACERS_MNC_INIT( myThid )       &     .OR. outputTypesInclusive
272        ENDIF        PTRACERS_monitor_stdio      = (.NOT. PTRACERS_monitor_mnc)
273  #endif /*  ALLOW_MNC  */       &     .OR. outputTypesInclusive
274                PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)
275         &     .OR. outputTypesInclusive
276          PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)
277         &     .OR. outputTypesInclusive
278    #else
279          PTRACERS_timeave_mnc        = .FALSE.
280          PTRACERS_snapshot_mnc       = .FALSE.
281          PTRACERS_monitor_mnc        = .FALSE.
282          PTRACERS_pickup_write_mnc   = .FALSE.
283          PTRACERS_pickup_read_mnc    = .FALSE.
284          PTRACERS_timeave_mdsio      = .TRUE.
285          PTRACERS_snapshot_mdsio     = .TRUE.
286          PTRACERS_monitor_stdio      = .TRUE.
287          PTRACERS_pickup_write_mdsio = .TRUE.
288          PTRACERS_pickup_read_mdsio  = .TRUE.
289    #endif
290    
291  C--   Print a summary of pTracer parameter values:  C--   Print a summary of pTracer parameter values:
292        iUnit = standardMessageUnit        iUnit = standardMessageUnit
293        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
294        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
295        WRITE(msgBuf,'(A)') '// PTRACERS parameters '        WRITE(msgBuf,'(A)') '// PTRACERS parameters '
296        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
297        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
298        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
299        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
300       &   'PTRACERS_numInUse =',       &   'PTRACERS_numInUse =',
301       &   ' /* number of tracers */')       &   ' /* number of tracers */')
302        CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,        CALL WRITE_0D_I( PTRACERS_Iter0, INDEX_NONE,
303         &   'PTRACERS_Iter0 =',
304         &   ' /* timestep number when tracers are initialized */')
305          CALL WRITE_0D_L( PTRACERS_addSrelax2EmP, INDEX_NONE,
306         &   'PTRACERS_addSrelax2EmP =','/* add Salt relaxation to EmP */')
307          CALL WRITE_1D_RL( PTRACERS_dTLev, Nr, INDEX_K,
308         &   'PTRACERS_dTLev =',
309         &'   /* Ptracer timestep ( s ) */')
310          CALL WRITE_0D_RL(PTRACERS_dumpFreq, INDEX_NONE,
311         &   'PTRACERS_dumpFreq =',
312         &   ' /* Frequency^-1 for snapshot output (s) */')
313          CALL WRITE_0D_RL(PTRACERS_taveFreq, INDEX_NONE,
314       &   'PTRACERS_taveFreq =',       &   'PTRACERS_taveFreq =',
315       &   ' /* Frequency^-1 for time-Aver. output (s) */')       &   ' /* Frequency^-1 for time-Aver. output (s) */')
316        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
317       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
318        CALL WRITE_0D_L( PTRACERS_write_mdsio, INDEX_NONE,  
319       &   'PTRACERS_write_mdsio =', ' /* write mdsio files */')        CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
320        CALL WRITE_0D_L( PTRACERS_write_mnc, INDEX_NONE,       &     'PTRACERS_timeave_mnc =',
321       &   'PTRACERS_write_mnc =', ' /* write mnc files */')       &     ' /* use MNC for Tave output */')
322          CALL WRITE_0D_L( PTRACERS_snapshot_mnc, INDEX_NONE,
323         &     'PTRACERS_snapshot_mnc =',
324         &     ' /* use MNC for snapshot output */')
325          CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
326         &     'PTRACERS_pickup_write_mnc =',
327         &     ' /* use MNC for writing pickups */')
328          CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
329         &     'PTRACERS_pickup_read_mnc =',
330         &     ' /* use MNC for reading pickups */')
331    
332        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
333          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
334          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
335          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
336          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
337            CALL WRITE_0D_C( PTRACERS_ioLabel(iTracer), 0, INDEX_NONE,
338         &     'PTRACERS_ioLabel =', ' /* tracer IO Label */')
339          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
340       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
341          CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
342         &     'PTRACERS_ImplVertAdv =',
343         &     ' /* implicit vert. advection flag */')
344            CALL WRITE_0D_RL( PTRACERS_diffKh(iTracer), INDEX_NONE,
345       &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')       &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
346          CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,          CALL WRITE_0D_RL( PTRACERS_diffK4(iTracer), INDEX_NONE,
347       &     'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')       &     'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
348          CALL WRITE_1D_R8( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,          CALL WRITE_1D_RL( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
349       &     'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')       &     'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
350          CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
351       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
352            CALL WRITE_0D_L( PTRACERS_useDWNSLP(iTracer), INDEX_NONE,
353         &     'PTRACERS_useDWNSLP =', ' /* apply DOWN-SLOPE Flow */')
354          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
355       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
356            CALL WRITE_1D_RL( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
357         &     'PTRACERS_ref =', ' /* Reference vertical profile */')
358            CALL WRITE_0D_RL( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
359         &     'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
360    
361        ENDDO        ENDDO
362          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
363          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
364    
365          _END_MASTER(myThid)
366    C     Everyone else must wait for the parameters to be loaded
367          _BARRIER
368    
369  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
370    
371        RETURN        RETURN
372        END        END
   

Legend:
Removed from v.1.13  
changed lines
  Added in v.1.37

  ViewVC Help
Powered by ViewVC 1.1.22