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

Legend:
Removed from v.1.10  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22