/[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.20 by edhill, Sat Jul 30 00:58:41 2005 UTC revision 1.29 by jmc, Mon Dec 17 22:03:15 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 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  #ifdef ALLOW_MNC
24  #include "MNC_PARAMS.h"  #include "MNC_PARAMS.h"
# Line 52  C                          are written t Line 52  C                          are written t
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,       &     PTRACERS_Iter0,
# Line 61  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_snapshot_mnc,       &     PTRACERS_timeave_mnc,
67       &     PTRACERS_pickup_write_mnc, PTRACERS_pickup_read_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.  c     PTRACERSisON=.TRUE.
77    C Note(jmc): remove this flag which is not really usefull (not set properly
78    C            when usePTRACERS=F and always TRUE otherwise);
79    C            much better to use "usePTRACERS" flag instead.
80    
81    C     Set ptracer IO & diagnostics labels (2 characters long)
82          CALL PTRACERS_SET_IOLABEL(
83         O                           PTRACERS_ioLabel,
84         I                           PTRACERS_num, myThid )
85    
86  C     Set defaults values for parameters in PTRACERS.h  C     Set defaults values for parameters in PTRACERS.h
87        PTRACERS_dumpFreq    = dumpFreq        PTRACERS_dumpFreq    = dumpFreq
# Line 82  C     Set defaults values for parameters Line 97  C     Set defaults values for parameters
97          PTRACERS_diffKr(iTracer)=UNSET_RL          PTRACERS_diffKr(iTracer)=UNSET_RL
98          DO k=1,Nr          DO k=1,Nr
99            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
100              PTRACERS_ref     (k,iTracer)=0. _d 0
101          ENDDO          ENDDO
102            PTRACERS_EvPrRn(iTracer)=UNSET_RL
103          PTRACERS_useGMRedi(iTracer)=useGMRedi          PTRACERS_useGMRedi(iTracer)=useGMRedi
104          PTRACERS_useKPP(iTracer)=useKPP          PTRACERS_useKPP(iTracer)=useKPP
105          PTRACERS_initialFile(iTracer)=' '          PTRACERS_initialFile(iTracer)=' '
# Line 94  C     Set defaults values for parameters Line 111  C     Set defaults values for parameters
111        ENDDO        ENDDO
112        PTRACERS_useRecords       = .FALSE.        PTRACERS_useRecords       = .FALSE.
113  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
114        PTRACERS_timeave_mnc      = timeave_mnc .AND. useMNC        PTRACERS_timeave_mnc      = useMNC .AND. timeave_mnc
115        PTRACERS_snapshot_mnc     = snapshot_mnc .AND. useMNC        PTRACERS_snapshot_mnc     = useMNC .AND. snapshot_mnc
116        PTRACERS_pickup_write_mnc = pickup_write_mnc .AND. useMNC        PTRACERS_monitor_mnc      = useMNC .AND. monitor_mnc
117        PTRACERS_pickup_read_mnc  = pickup_read_mnc .AND. useMNC        PTRACERS_pickup_write_mnc = useMNC .AND. pickup_write_mnc
118          PTRACERS_pickup_read_mnc  = useMNC .AND. pickup_read_mnc
119  #else  #else
120        PTRACERS_timeave_mnc      = .FALSE.        PTRACERS_timeave_mnc      = .FALSE.
121        PTRACERS_snapshot_mnc     = .FALSE.        PTRACERS_snapshot_mnc     = .FALSE.
122          PTRACERS_monitor_mnc      = .FALSE.
123        PTRACERS_pickup_write_mnc = .FALSE.        PTRACERS_pickup_write_mnc = .FALSE.
124        PTRACERS_pickup_read_mnc  = .FALSE.        PTRACERS_pickup_read_mnc  = .FALSE.
125  #endif  #endif
126    
127  C     Open and read the data.ptracers file  C     Open and read the data.ptracers file
       _BEGIN_MASTER(myThid)  
128        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
129        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
130       &                   SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , myThid )
131        CALL OPEN_COPY_DATA_FILE(        CALL OPEN_COPY_DATA_FILE(
132       I                   'data.ptracers', 'PTRACERS_READPARMS',       I                   'data.ptracers', 'PTRACERS_READPARMS',
133       O                   iUnit,       O                   iUnit,
# Line 117  C     Open and read the data.ptracers fi Line 135  C     Open and read the data.ptracers fi
135        READ(UNIT=iUnit,NML=PTRACERS_PARM01)        READ(UNIT=iUnit,NML=PTRACERS_PARM01)
136        WRITE(msgBuf,'(A)')        WRITE(msgBuf,'(A)')
137       &  ' PTRACERS_READPARMS: finished reading data.ptracers'       &  ' PTRACERS_READPARMS: finished reading data.ptracers'
138        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
139       &                   SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , myThid )
140    
141  C     Close the open data file  C     Close the open data file
142        CLOSE(iUnit)        CLOSE(iUnit)
       _END_MASTER(myThid)  
   
 C     Everyone else must wait for the parameters to be loaded  
       _BARRIER  
143    
144  C     Now set-up any remaining parameters that result from the input  C     Now set-up any remaining parameters that result from the input
145  C     parameters  C     parameters
# Line 137  C     assume that all PTRACERS fields wi Line 151  C     assume that all PTRACERS fields wi
151        ENDIF        ENDIF
152  C     Check we are not trying to use more tracers than allowed  C     Check we are not trying to use more tracers than allowed
153        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
154          WRITE(msgBuf,'(A,I2,A,I2,A)')          WRITE(msgBuf,'(A,I4,A,I4,A)')
155       &       ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,       &       ' PTRACERS_READPARMS: You requested',PTRACERS_numInUse,
156       &       ' tracers at run time when only ',PTRACERS_num,       &       ' tracers at run time when only',PTRACERS_num,
157       &       ' were specified at compile time. Naughty! '       &       ' were specified at compile time. Naughty! '
158          CALL PRINT_ERROR(msgBuf, 1)          CALL PRINT_ERROR( msgBuf, myThid )
159          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
160        ENDIF        ENDIF
161  C     Check that enough parameters were specified  C     Check that enough parameters were specified
162        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
163          IF (PTRACERS_advScheme(iTracer).EQ.0) THEN          IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
164            WRITE(msgBuf,'(A,A,I2)')            WRITE(msgBuf,'(A,A,I3)')
165       &         ' PTRACERS_READPARMS: ',       &         ' PTRACERS_READPARMS: ',
166       &         'No advect. scheme specified for tracer #',       &         'No advect. scheme specified for tracer #',
167       &         iTracer       &         iTracer
168            CALL PRINT_ERROR(msgBuf, 1)            CALL PRINT_ERROR( msgBuf, myThid )
169            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
170          ENDIF          ENDIF
171        ENDDO        ENDDO
# Line 160  C     Check that enough parameters were Line 174  C     Check that enough parameters were
174         IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN         IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
175          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)')
176       &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'       &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
177          CALL PRINT_ERROR( msgBuf , myThid)          CALL PRINT_ERROR( msgBuf, myThid )
178          WRITE(msgBuf,'(2A,I2,A)') 'PTRACERS_READPARMS:',          WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
179       &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'       &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
180          CALL PRINT_ERROR( msgBuf , myThid)          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  #endif  #endif
185        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
186          PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)          IF ( PTRACERS_useGMRedi(iTracer) .AND. .NOT.useGMRedi ) THEN
187       &                           .AND.useGMRedi            WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
188          PTRACERS_useKPP(iTracer) = PTRACERS_useKPP(iTracer)       &     ' pTracers_useGMRedi(',iTracer,' ) is TRUE'
189       &                        .AND.useKPP            CALL PRINT_ERROR( msgBuf, myThid )
190              WRITE(msgBuf,'(A,L5,A)')
191         &     'PTRACERS_READPARMS: But not useGMRedi (=',useGMRedi,')'
192              CALL PRINT_ERROR( msgBuf, myThid )
193              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
194            ENDIF
195            IF ( PTRACERS_useKPP(iTracer) .AND. .NOT.useKPP ) THEN
196              WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
197         &     ' pTracers_useKPP(',iTracer,' ) is TRUE'
198              CALL PRINT_ERROR( msgBuf, myThid )
199              WRITE(msgBuf,'(A,L5,A)')
200         &     'PTRACERS_READPARMS: But not useKPP (=',useKPP,')'
201              CALL PRINT_ERROR( msgBuf, myThid )
202              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
203            ENDIF
204          IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN          IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
205           DO k=1,Nr           DO k=1,Nr
206            PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)            PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
# Line 181  C     Check that enough parameters were Line 209  C     Check that enough parameters were
209        ENDDO        ENDDO
210    
211  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
212        PTRACERS_timeave_mnc      =        PTRACERS_timeave_mnc      = useMNC .AND. PTRACERS_timeave_mnc
213       &     PTRACERS_timeave_mnc .AND. useMNC        PTRACERS_snapshot_mnc     = useMNC .AND. PTRACERS_snapshot_mnc
214        PTRACERS_snapshot_mnc     =        PTRACERS_monitor_mnc      = useMNC .AND. PTRACERS_monitor_mnc
215       &     PTRACERS_snapshot_mnc .AND. useMNC        PTRACERS_pickup_write_mnc = useMNC .AND. PTRACERS_pickup_write_mnc
216        PTRACERS_pickup_write_mnc =        PTRACERS_pickup_read_mnc  = useMNC .AND. PTRACERS_pickup_read_mnc
      &     PTRACERS_pickup_write_mnc .AND. useMNC  
       PTRACERS_pickup_read_mnc  =  
      &     PTRACERS_pickup_read_mnc .AND. useMNC  
217    
218        PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)        PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)
219       &     .OR. outputTypesInclusive       &     .OR. outputTypesInclusive
220        PTRACERS_snapshot_mdsio     = (.NOT. PTRACERS_snapshot_mnc)        PTRACERS_snapshot_mdsio     = (.NOT. PTRACERS_snapshot_mnc)
221       &     .OR. outputTypesInclusive       &     .OR. outputTypesInclusive
222          PTRACERS_monitor_stdio      = (.NOT. PTRACERS_monitor_mnc)
223         &     .OR. outputTypesInclusive
224        PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)        PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)
225       &     .OR. outputTypesInclusive       &     .OR. outputTypesInclusive
226        PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)        PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)
227       &     .OR. outputTypesInclusive       &     .OR. outputTypesInclusive
         
       IF (useMNC) THEN  
 C       Initialize the MNC variable types for PTRACERS  
         CALL PTRACERS_MNC_INIT( myThid )  
       ENDIF  
228  #else  #else
229        PTRACERS_timeave_mnc        = .FALSE.        PTRACERS_timeave_mnc        = .FALSE.
230        PTRACERS_snapshot_mnc       = .FALSE.        PTRACERS_snapshot_mnc       = .FALSE.
231          PTRACERS_monitor_mnc        = .FALSE.
232        PTRACERS_pickup_write_mnc   = .FALSE.        PTRACERS_pickup_write_mnc   = .FALSE.
233        PTRACERS_pickup_read_mnc    = .FALSE.        PTRACERS_pickup_read_mnc    = .FALSE.
234        PTRACERS_timeave_mdsio      = .TRUE.        PTRACERS_timeave_mdsio      = .TRUE.
235        PTRACERS_snapshot_mdsio     = .TRUE.        PTRACERS_snapshot_mdsio     = .TRUE.
236          PTRACERS_monitor_stdio      = .TRUE.
237        PTRACERS_pickup_write_mdsio = .TRUE.        PTRACERS_pickup_write_mdsio = .TRUE.
238        PTRACERS_pickup_read_mdsio  = .TRUE.        PTRACERS_pickup_read_mdsio  = .TRUE.
239  #endif  #endif
240          
241  C--   Print a summary of pTracer parameter values:  C--   Print a summary of pTracer parameter values:
242        iUnit = standardMessageUnit        iUnit = standardMessageUnit
243        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
244        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
245        WRITE(msgBuf,'(A)') '// PTRACERS parameters '        WRITE(msgBuf,'(A)') '// PTRACERS parameters '
246        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
247        WRITE(msgBuf,'(A)') '// ==================================='        WRITE(msgBuf,'(A)') '// ==================================='
248        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)        CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
249        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,        CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
250       &   'PTRACERS_numInUse =',       &   'PTRACERS_numInUse =',
251       &   ' /* number of tracers */')       &   ' /* number of tracers */')
# Line 236  C--   Print a summary of pTracer paramet Line 260  C--   Print a summary of pTracer paramet
260       &   ' /* Frequency^-1 for time-Aver. output (s) */')       &   ' /* Frequency^-1 for time-Aver. output (s) */')
261        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
262       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')       &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
263          
264        CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
265       &     'PTRACERS_timeave_mnc =',       &     'PTRACERS_timeave_mnc =',
266       &     ' /* use MNC for Tave output */')       &     ' /* use MNC for Tave output */')
# Line 244  C--   Print a summary of pTracer paramet Line 268  C--   Print a summary of pTracer paramet
268       &     'PTRACERS_snapshot_mnc =',       &     'PTRACERS_snapshot_mnc =',
269       &     ' /* use MNC for snapshot output */')       &     ' /* use MNC for snapshot output */')
270        CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
271       &     'PTRACERS_pickup_write_mnc =',       &     'PTRACERS_pickup_write_mnc =',
272       &     ' /* use MNC for writing pickups */')       &     ' /* use MNC for writing pickups */')
273        CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,        CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
274       &     'PTRACERS_pickup_read_mnc =',       &     'PTRACERS_pickup_read_mnc =',
275       &     ' /* use MNC for reading pickups */')       &     ' /* use MNC for reading pickups */')
276    
277        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
278          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
279          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
280          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer          WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
281          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
282            CALL WRITE_0D_C( PTRACERS_ioLabel(iTracer), 0, INDEX_NONE,
283         &     'PTRACERS_ioLabel =', ' /* tracer IO Label */')
284          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,          CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
285       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')       &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
286          CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
# Line 270  C--   Print a summary of pTracer paramet Line 296  C--   Print a summary of pTracer paramet
296       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')       &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
297          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,          CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
298       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')       &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
299            CALL WRITE_1D_R8( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
300         &     'PTRACERS_ref =', ' /* Reference vertical profile */')
301            CALL WRITE_0D_R8( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
302         &     'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
303    
304        ENDDO        ENDDO
305          WRITE(msgBuf,'(A)') ' -----------------------------------'          WRITE(msgBuf,'(A)') ' -----------------------------------'
306          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
307    
308          _END_MASTER(myThid)
309    C     Everyone else must wait for the parameters to be loaded
310          _BARRIER
311    
312  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
313    
314        RETURN        RETURN

Legend:
Removed from v.1.20  
changed lines
  Added in v.1.29

  ViewVC Help
Powered by ViewVC 1.1.22