/[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.12 by jmc, Thu Oct 28 00:32:21 2004 UTC revision 1.25 by jmc, Tue Aug 8 21:20:26 2006 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 20  C     !USES: Line 20  C     !USES:
20  #include "PTRACERS_SIZE.h"  #include "PTRACERS_SIZE.h"
21  #include "PTRACERS.h"  #include "PTRACERS.h"
22  #include "PARAMS.h"  #include "PARAMS.h"
23    #ifdef ALLOW_MNC
24    #include "MNC_PARAMS.h"
25    #endif
26    
27  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
28        INTEGER myThid        INTEGER myThid
# Line 40  C     msgBuf     :: message buffer Line 43  C     msgBuf     :: message buffer
43  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
44  C                          are written to post-processing files.  C                          are written to post-processing files.
45        NAMELIST /PTRACERS_PARM01/        NAMELIST /PTRACERS_PARM01/
46         &     PTRACERS_dumpFreq,
47       &     PTRACERS_taveFreq,       &     PTRACERS_taveFreq,
48         &     PTRACERS_monitorFreq,
49       &     PTRACERS_advScheme,       &     PTRACERS_advScheme,
50         &     PTRACERS_ImplVertAdv,
51       &     PTRACERS_diffKh,       &     PTRACERS_diffKh,
52       &     PTRACERS_diffK4,       &     PTRACERS_diffK4,
53       &     PTRACERS_diffKr,       &     PTRACERS_diffKr,
54       &     PTRACERS_diffKrNr,       &     PTRACERS_diffKrNr,
55         &     PTRACERS_ref,
56         &     PTRACERS_EvPrRn,
57       &     PTRACERS_useGMRedi,       &     PTRACERS_useGMRedi,
58       &     PTRACERS_useKPP,       &     PTRACERS_useKPP,
59         &     PTRACERS_Iter0,
60       &     PTRACERS_numInUse,       &     PTRACERS_numInUse,
61       &     PTRACERS_initialFile,       &     PTRACERS_initialFile,
62       &     PTRACERS_useRecords,       &     PTRACERS_useRecords,
63       &     PTRACERS_names,       &     PTRACERS_names,
64       &     PTRACERS_long_names,       &     PTRACERS_long_names,
65       &     PTRACERS_units,       &     PTRACERS_units,
66       &     PTRACERS_read_mnc,       &     PTRACERS_timeave_mnc,
67       &     PTRACERS_write_mnc       &     PTRACERS_snapshot_mnc,
68         &     PTRACERS_monitor_mnc,
69         &     PTRACERS_pickup_write_mnc,
70         &     PTRACERS_pickup_read_mnc
71    
72          _BEGIN_MASTER(myThid)
73    
74  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
75  C     internal flag to indicate we are in business  C     internal flag to indicate we are in business
76        PTRACERSisON=.TRUE.        PTRACERSisON=.TRUE.
77    
78  C     Set defaults values for parameters in PTRACERS.h  C     Set defaults values for parameters in PTRACERS.h
79        PTRACERS_taveFreq=taveFreq        PTRACERS_dumpFreq    = dumpFreq
80          PTRACERS_taveFreq    = taveFreq
81          PTRACERS_monitorFreq = monitorFreq
82          PTRACERS_Iter0   = 0
83        PTRACERS_numInUse=-1        PTRACERS_numInUse=-1
84        DO iTracer=1,PTRACERS_num        DO iTracer=1,PTRACERS_num
85          PTRACERS_advScheme(iTracer)=saltAdvScheme          PTRACERS_advScheme(iTracer)=saltAdvScheme
86            PTRACERS_ImplVertAdv(iTracer) = .FALSE.
87          PTRACERS_diffKh(iTracer)=diffKhS          PTRACERS_diffKh(iTracer)=diffKhS
88          PTRACERS_diffK4(iTracer)=diffK4S          PTRACERS_diffK4(iTracer)=diffK4S
89          PTRACERS_diffKr(iTracer)=UNSET_RL          PTRACERS_diffKr(iTracer)=UNSET_RL
90          DO k=1,Nr          DO k=1,Nr
91            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
92              PTRACERS_ref     (k,iTracer)=0. _d 0
93          ENDDO          ENDDO
94            PTRACERS_EvPrRn(iTracer)=UNSET_RL
95          PTRACERS_useGMRedi(iTracer)=useGMRedi          PTRACERS_useGMRedi(iTracer)=useGMRedi
96          PTRACERS_useKPP(iTracer)=useKPP          PTRACERS_useKPP(iTracer)=useKPP
97          PTRACERS_initialFile(iTracer)=' '          PTRACERS_initialFile(iTracer)=' '
# Line 81  C     Set defaults values for parameters Line 101  C     Set defaults values for parameters
101            PTRACERS_units(iTracer)(ic:ic) = ' '            PTRACERS_units(iTracer)(ic:ic) = ' '
102          ENDDO          ENDDO
103        ENDDO        ENDDO
104        PTRACERS_useRecords  = .FALSE.        PTRACERS_useRecords       = .FALSE.
105        PTRACERS_read_mdsio  = .TRUE.  #ifdef ALLOW_MNC
106        PTRACERS_read_mnc    = .FALSE.        PTRACERS_timeave_mnc      = useMNC .AND. timeave_mnc
107        PTRACERS_write_mdsio = .TRUE.        PTRACERS_snapshot_mnc     = useMNC .AND. snapshot_mnc
108        PTRACERS_write_mnc   = .FALSE.        PTRACERS_monitor_mnc      = useMNC .AND. monitor_mnc
109          PTRACERS_pickup_write_mnc = useMNC .AND. pickup_write_mnc
110          PTRACERS_pickup_read_mnc  = useMNC .AND. pickup_read_mnc
111    #else
112          PTRACERS_timeave_mnc      = .FALSE.
113          PTRACERS_snapshot_mnc     = .FALSE.
114          PTRACERS_monitor_mnc      = .FALSE.
115          PTRACERS_pickup_write_mnc = .FALSE.
116          PTRACERS_pickup_read_mnc  = .FALSE.
117    #endif
118    
119  C     Open and read the data.ptracers file  C     Open and read the data.ptracers file
       _BEGIN_MASTER(myThid)  
120        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
121        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
122       &                   SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , myThid )
123        CALL OPEN_COPY_DATA_FILE(        CALL OPEN_COPY_DATA_FILE(
124       I                   'data.ptracers', 'PTRACERS_READPARMS',       I                   'data.ptracers', 'PTRACERS_READPARMS',
125       O                   iUnit,       O                   iUnit,
# Line 99  C     Open and read the data.ptracers fi Line 127  C     Open and read the data.ptracers fi
127        READ(UNIT=iUnit,NML=PTRACERS_PARM01)        READ(UNIT=iUnit,NML=PTRACERS_PARM01)
128        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
129       &  ' PTRACERS_READPARMS: finished reading data.ptracers'       &  ' PTRACERS_READPARMS: finished reading data.ptracers'
130        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
131       &                   SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , myThid )
132    
133  C     Close the open data file  C     Close the open data file
134        CLOSE(iUnit)        CLOSE(iUnit)
       _END_MASTER(myThid)  
   
 C     Everyone else must wait for the parameters to be loaded  
       _BARRIER  
135    
136  C     Now set-up any remaining parameters that result from the input  C     Now set-up any remaining parameters that result from the input
137  C     parameters  C     parameters
# Line 123  C     Check we are not trying to use mor Line 147  C     Check we are not trying to use mor
147       &       ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,       &       ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
148       &       ' tracers at run time when only ',PTRACERS_num,       &       ' tracers at run time when only ',PTRACERS_num,
149       &       ' were specified at compile time. Naughty! '       &       ' were specified at compile time. Naughty! '
150          CALL PRINT_ERROR(msgBuf, 1)          CALL PRINT_ERROR( msgBuf, myThid )
151          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
152        ENDIF        ENDIF
153  C     Check that enough parameters were specified  C     Check that enough parameters were specified
# Line 133  C     Check that enough parameters were Line 157  C     Check that enough parameters were
157       &         ' PTRACERS_READPARMS: ',       &         ' PTRACERS_READPARMS: ',
158       &         'No advect. scheme specified for tracer #',       &         'No advect. scheme specified for tracer #',
159       &         iTracer       &         iTracer
160            CALL PRINT_ERROR(msgBuf, 1)            CALL PRINT_ERROR( msgBuf, myThid )
161            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
162          ENDIF          ENDIF
163        ENDDO        ENDDO
164    #ifndef INCLUDE_IMPLVERTADV_CODE
165          DO iTracer=1,PTRACERS_numInUse
166           IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
167            WRITE(msgBuf,'(A)')
168         &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
169            CALL PRINT_ERROR( msgBuf, myThid )
170            WRITE(msgBuf,'(2A,I2,A)') 'PTRACERS_READPARMS:',
171         &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
172            CALL PRINT_ERROR( msgBuf, myThid )
173            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
174           ENDIF
175          ENDDO
176    #endif
177        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
178          PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)          PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)
179       &                           .AND.useGMRedi       &                           .AND.useGMRedi
# Line 150  C     Check that enough parameters were Line 187  C     Check that enough parameters were
187        ENDDO        ENDDO
188    
189  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
190        IF (useMNC) THEN        PTRACERS_timeave_mnc      = useMNC .AND. PTRACERS_timeave_mnc
191  C       Set the default I/O Types        PTRACERS_snapshot_mnc     = useMNC .AND. PTRACERS_snapshot_mnc
192          IF (PTRACERS_read_mnc) PTRACERS_read_mdsio = .FALSE.        PTRACERS_monitor_mnc      = useMNC .AND. PTRACERS_monitor_mnc
193          IF ( (.NOT. outputTypesInclusive)        PTRACERS_pickup_write_mnc = useMNC .AND. PTRACERS_pickup_write_mnc
194       &       .AND. PTRACERS_write_mnc ) pickup_write_mdsio = .FALSE.        PTRACERS_pickup_read_mnc  = useMNC .AND. PTRACERS_pickup_read_mnc
195            
196  C       Initialize the MNC variable types for PTRACERS        PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)
197          CALL PTRACERS_MNC_INIT( myThid )       &     .OR. outputTypesInclusive
198        ENDIF        PTRACERS_snapshot_mdsio     = (.NOT. PTRACERS_snapshot_mnc)
199  #endif /*  ALLOW_MNC  */       &     .OR. outputTypesInclusive
200                PTRACERS_monitor_stdio      = (.NOT. PTRACERS_monitor_mnc)
201         &     .OR. outputTypesInclusive
202          PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)
203         &     .OR. outputTypesInclusive
204          PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)
205         &     .OR. outputTypesInclusive
206    #else
207          PTRACERS_timeave_mnc        = .FALSE.
208          PTRACERS_snapshot_mnc       = .FALSE.
209          PTRACERS_monitor_mnc        = .FALSE.
210          PTRACERS_pickup_write_mnc   = .FALSE.
211          PTRACERS_pickup_read_mnc    = .FALSE.
212          PTRACERS_timeave_mdsio      = .TRUE.
213          PTRACERS_snapshot_mdsio     = .TRUE.
214          PTRACERS_monitor_stdio      = .TRUE.
215          PTRACERS_pickup_write_mdsio = .TRUE.
216          PTRACERS_pickup_read_mdsio  = .TRUE.
217    #endif
218    
219  C--   Print a summary of pTracer parameter values:  C--   Print a summary of pTracer parameter values:
220        iUnit = standardMessageUnit        iUnit = standardMessageUnit
221        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
222        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
223        WRITE(msgBuf,'(A)') '// PTRACERS parameters '        WRITE(msgBuf,'(A)') '// PTRACERS parameters '
224        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
225        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
226        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
227        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
228       &   'PTRACERS_numInUse =',       &   'PTRACERS_numInUse =',
229       &   ' /* number of tracers */')       &   ' /* number of tracers */')
230          CALL WRITE_0D_I( PTRACERS_Iter0, INDEX_NONE,
231         &   'PTRACERS_Iter0 =',
232         &   ' /* timestep number when tracers are initialized */')
233          CALL WRITE_0D_R8(PTRACERS_dumpFreq, INDEX_NONE,
234         &   'PTRACERS_dumpFreq =',
235         &   ' /* Frequency^-1 for snapshot output (s) */')
236        CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,        CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,
237       &   'PTRACERS_taveFreq =',       &   'PTRACERS_taveFreq =',
238       &   ' /* Frequency^-1 for time-Aver. output (s) */')       &   ' /* Frequency^-1 for time-Aver. output (s) */')
239        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
240       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
241        CALL WRITE_0D_L( PTRACERS_write_mdsio, INDEX_NONE,  
242       &   'PTRACERS_write_mdsio =', ' /* write mdsio files */')        CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
243        CALL WRITE_0D_L( PTRACERS_write_mnc, INDEX_NONE,       &     'PTRACERS_timeave_mnc =',
244       &   'PTRACERS_write_mnc =', ' /* write mnc files */')       &     ' /* use MNC for Tave output */')
245          CALL WRITE_0D_L( PTRACERS_snapshot_mnc, INDEX_NONE,
246         &     'PTRACERS_snapshot_mnc =',
247         &     ' /* use MNC for snapshot output */')
248          CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
249         &     'PTRACERS_pickup_write_mnc =',
250         &     ' /* use MNC for writing pickups */')
251          CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
252         &     'PTRACERS_pickup_read_mnc =',
253         &     ' /* use MNC for reading pickups */')
254    
255        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
256          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
257          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
258          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
259          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
260          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
261       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
262            CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
263         &     'PTRACERS_ImplVertAdv =',
264         &     ' /* implicit vert. advection flag */')
265          CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,          CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,
266       &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')       &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
267          CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,          CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,
# Line 199  C--   Print a summary of pTracer paramet Line 272  C--   Print a summary of pTracer paramet
272       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
273          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
274       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
275            CALL WRITE_1D_R8( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
276         &     'PTRACERS_ref =', ' /* Reference vertical profile */')
277            CALL WRITE_0D_R8( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
278         &     'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
279    
280        ENDDO        ENDDO
281          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
282          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
283    
284          _END_MASTER(myThid)
285    C     Everyone else must wait for the parameters to be loaded
286          _BARRIER
287    
288  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
289    
290        RETURN        RETURN

Legend:
Removed from v.1.12  
changed lines
  Added in v.1.25

  ViewVC Help
Powered by ViewVC 1.1.22