/[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.23 by mlosch, Fri Oct 14 12:45:05 2005 UTC revision 1.26 by jmc, Tue Sep 18 21:20:06 2007 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 53  C                          are written t Line 53  C                          are written t
53       &     PTRACERS_diffKr,       &     PTRACERS_diffKr,
54       &     PTRACERS_diffKrNr,       &     PTRACERS_diffKrNr,
55       &     PTRACERS_ref,       &     PTRACERS_ref,
56         &     PTRACERS_EvPrRn,
57       &     PTRACERS_useGMRedi,       &     PTRACERS_useGMRedi,
58       &     PTRACERS_useKPP,       &     PTRACERS_useKPP,
59       &     PTRACERS_Iter0,       &     PTRACERS_Iter0,
# Line 62  C                          are written t Line 63  C                          are written t
63       &     PTRACERS_names,       &     PTRACERS_names,
64       &     PTRACERS_long_names,       &     PTRACERS_long_names,
65       &     PTRACERS_units,       &     PTRACERS_units,
66       &     PTRACERS_timeave_mnc,       &     PTRACERS_timeave_mnc,
67       &     PTRACERS_snapshot_mnc,       &     PTRACERS_snapshot_mnc,
68       &     PTRACERS_monitor_mnc,       &     PTRACERS_monitor_mnc,
69       &     PTRACERS_pickup_write_mnc,       &     PTRACERS_pickup_write_mnc,
70       &     PTRACERS_pickup_read_mnc       &     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.
# Line 88  C     Set defaults values for parameters Line 91  C     Set defaults values for parameters
91            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
92            PTRACERS_ref     (k,iTracer)=0. _d 0            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 99  C     Set defaults values for parameters Line 103  C     Set defaults values for parameters
103        ENDDO        ENDDO
104        PTRACERS_useRecords       = .FALSE.        PTRACERS_useRecords       = .FALSE.
105  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
106        PTRACERS_timeave_mnc      = timeave_mnc .AND. useMNC        PTRACERS_timeave_mnc      = useMNC .AND. timeave_mnc
107        PTRACERS_snapshot_mnc     = snapshot_mnc .AND. useMNC        PTRACERS_snapshot_mnc     = useMNC .AND. snapshot_mnc
108        PTRACERS_monitor_mnc      = monitor_mnc .AND. useMNC        PTRACERS_monitor_mnc      = useMNC .AND. monitor_mnc
109        PTRACERS_pickup_write_mnc = pickup_write_mnc .AND. useMNC        PTRACERS_pickup_write_mnc = useMNC .AND. pickup_write_mnc
110        PTRACERS_pickup_read_mnc  = pickup_read_mnc .AND. useMNC        PTRACERS_pickup_read_mnc  = useMNC .AND. pickup_read_mnc
111  #else  #else
112        PTRACERS_timeave_mnc      = .FALSE.        PTRACERS_timeave_mnc      = .FALSE.
113        PTRACERS_snapshot_mnc     = .FALSE.        PTRACERS_snapshot_mnc     = .FALSE.
# Line 113  C     Set defaults values for parameters Line 117  C     Set defaults values for parameters
117  #endif  #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 124  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 144  C     assume that all PTRACERS fields wi Line 143  C     assume that all PTRACERS fields wi
143        ENDIF        ENDIF
144  C     Check we are not trying to use more tracers than allowed  C     Check we are not trying to use more tracers than allowed
145        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
146          WRITE(msgBuf,'(A,I2,A,I2,A)')          WRITE(msgBuf,'(A,I4,A,I4,A)')
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
154        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
155          IF (PTRACERS_advScheme(iTracer).EQ.0) THEN          IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
156            WRITE(msgBuf,'(A,A,I2)')            WRITE(msgBuf,'(A,A,I3)')
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
# Line 167  C     Check that enough parameters were Line 166  C     Check that enough parameters were
166         IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN         IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
167          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
168       &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'       &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
169          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
170          WRITE(msgBuf,'(2A,I2,A)') 'PTRACERS_READPARMS:',          WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
171       &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'       &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
172          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
173          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
174         ENDIF         ENDIF
175        ENDDO        ENDDO
176  #endif  #endif
177        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
178          PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)          IF ( PTRACERS_useGMRedi(iTracer) .AND. .NOT.useGMRedi ) THEN
179       &                           .AND.useGMRedi            WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
180          PTRACERS_useKPP(iTracer) = PTRACERS_useKPP(iTracer)       &     ' pTracers_useGMRedi(',iTracer,' ) is TRUE'
181       &                        .AND.useKPP            CALL PRINT_ERROR( msgBuf, myThid )
182              WRITE(msgBuf,'(A,L5,A)')
183         &     'PTRACERS_READPARMS: But not useGMRedi (=',useGMRedi,')'
184              CALL PRINT_ERROR( msgBuf, myThid )
185              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
186            ENDIF
187            IF ( PTRACERS_useKPP(iTracer) .AND. .NOT.useKPP ) THEN
188              WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
189         &     ' pTracers_useKPP(',iTracer,' ) is TRUE'
190              CALL PRINT_ERROR( msgBuf, myThid )
191              WRITE(msgBuf,'(A,L5,A)')
192         &     'PTRACERS_READPARMS: But not useKPP (=',useKPP,')'
193              CALL PRINT_ERROR( msgBuf, myThid )
194              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
195            ENDIF
196          IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN          IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
197           DO k=1,Nr           DO k=1,Nr
198            PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)            PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
# Line 188  C     Check that enough parameters were Line 201  C     Check that enough parameters were
201        ENDDO        ENDDO
202    
203  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
204        PTRACERS_timeave_mnc      =        PTRACERS_timeave_mnc      = useMNC .AND. PTRACERS_timeave_mnc
205       &     PTRACERS_timeave_mnc      .AND. useMNC        PTRACERS_snapshot_mnc     = useMNC .AND. PTRACERS_snapshot_mnc
206        PTRACERS_snapshot_mnc     =        PTRACERS_monitor_mnc      = useMNC .AND. PTRACERS_monitor_mnc
207       &     PTRACERS_snapshot_mnc     .AND. useMNC        PTRACERS_pickup_write_mnc = useMNC .AND. PTRACERS_pickup_write_mnc
208        PTRACERS_monitor_mnc      =        PTRACERS_pickup_read_mnc  = useMNC .AND. PTRACERS_pickup_read_mnc
      &     PTRACERS_monitor_mnc      .AND. useMNC .AND. monitor_mnc  
       PTRACERS_pickup_write_mnc =  
      &     PTRACERS_pickup_write_mnc .AND. useMNC  
       PTRACERS_pickup_read_mnc  =  
      &     PTRACERS_pickup_read_mnc  .AND. useMNC  
209    
210        PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)        PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)
211       &     .OR. outputTypesInclusive       &     .OR. outputTypesInclusive
# Line 209  C     Check that enough parameters were Line 217  C     Check that enough parameters were
217       &     .OR. outputTypesInclusive       &     .OR. outputTypesInclusive
218        PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)        PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)
219       &     .OR. outputTypesInclusive       &     .OR. outputTypesInclusive
         
220  #else  #else
221        PTRACERS_timeave_mnc        = .FALSE.        PTRACERS_timeave_mnc        = .FALSE.
222        PTRACERS_snapshot_mnc       = .FALSE.        PTRACERS_snapshot_mnc       = .FALSE.
# Line 222  C     Check that enough parameters were Line 229  C     Check that enough parameters were
229        PTRACERS_pickup_write_mdsio = .TRUE.        PTRACERS_pickup_write_mdsio = .TRUE.
230        PTRACERS_pickup_read_mdsio  = .TRUE.        PTRACERS_pickup_read_mdsio  = .TRUE.
231  #endif  #endif
232          
233  C--   Print a summary of pTracer parameter values:  C--   Print a summary of pTracer parameter values:
234        iUnit = standardMessageUnit        iUnit = standardMessageUnit
235        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
236        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
237        WRITE(msgBuf,'(A)') '// PTRACERS parameters '        WRITE(msgBuf,'(A)') '// PTRACERS parameters '
238        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
239        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
240        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
241        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
242       &   'PTRACERS_numInUse =',       &   'PTRACERS_numInUse =',
243       &   ' /* number of tracers */')       &   ' /* number of tracers */')
# Line 245  C--   Print a summary of pTracer paramet Line 252  C--   Print a summary of pTracer paramet
252       &   ' /* Frequency^-1 for time-Aver. output (s) */')       &   ' /* Frequency^-1 for time-Aver. output (s) */')
253        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
254       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
255          
256        CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
257       &     'PTRACERS_timeave_mnc =',       &     'PTRACERS_timeave_mnc =',
258       &     ' /* use MNC for Tave output */')       &     ' /* use MNC for Tave output */')
# Line 253  C--   Print a summary of pTracer paramet Line 260  C--   Print a summary of pTracer paramet
260       &     'PTRACERS_snapshot_mnc =',       &     'PTRACERS_snapshot_mnc =',
261       &     ' /* use MNC for snapshot output */')       &     ' /* use MNC for snapshot output */')
262        CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
263       &     'PTRACERS_pickup_write_mnc =',       &     'PTRACERS_pickup_write_mnc =',
264       &     ' /* use MNC for writing pickups */')       &     ' /* use MNC for writing pickups */')
265        CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
266       &     'PTRACERS_pickup_read_mnc =',       &     'PTRACERS_pickup_read_mnc =',
267       &     ' /* use MNC for reading pickups */')       &     ' /* use MNC for reading pickups */')
268    
269        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
270          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
271          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
272          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
273          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
274          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
275       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
276          CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
# Line 279  C--   Print a summary of pTracer paramet Line 286  C--   Print a summary of pTracer paramet
286       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
287          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
288       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
289            CALL WRITE_1D_R8( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
290         &     'PTRACERS_ref =', ' /* Reference vertical profile */')
291            CALL WRITE_0D_R8( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
292         &     'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
293    
294        ENDDO        ENDDO
295          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
296          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
297    
298          _END_MASTER(myThid)
299    C     Everyone else must wait for the parameters to be loaded
300          _BARRIER
301    
302  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
303    
304        RETURN        RETURN

Legend:
Removed from v.1.23  
changed lines
  Added in v.1.26

  ViewVC Help
Powered by ViewVC 1.1.22