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

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

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


Revision 1.36 - (hide annotations) (download)
Sun Sep 5 22:28:14 2010 UTC (13 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62k, checkpoint62n, checkpoint62m, checkpoint62l
Changes since 1.35: +5 -1 lines
option (flag:PTRACERS_addSrelax2EmP) to convert Salt Relax into additional EmP

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

  ViewVC Help
Powered by ViewVC 1.1.22