/[MITgcm]/MITgcm_contrib/darwin2/pkg/darwin/darwin_readparams.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/darwin/darwin_readparams.F

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


Revision 1.9 - (hide annotations) (download)
Wed Dec 4 21:21:32 2013 UTC (11 years, 7 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt65w_20160512, ctrb_darwin2_ckpt65j_20150225, ctrb_darwin2_ckpt66g_20170424, ctrb_darwin2_ckpt66k_20171025, ctrb_darwin2_ckpt66n_20180118, ctrb_darwin2_ckpt65v_20160409, ctrb_darwin2_ckpt65s_20160114, ctrb_darwin2_ckpt65_20140718, ctrb_darwin2_ckpt66d_20170214, ctrb_darwin2_ckpt64r_20131210, ctrb_darwin2_ckpt65m_20150615, ctrb_darwin2_ckpt65q_20151118, ctrb_darwin2_ckpt65o_20150914, ctrb_darwin2_ckpt65p_20151023, ctrb_darwin2_ckpt65e_20140929, ctrb_darwin2_ckpt64v_20140411, ctrb_darwin2_ckpt64z_20140711, ctrb_darwin2_ckpt65l_20150504, ctrb_darwin2_ckpt65z_20160929, ctrb_darwin2_ckpt65n_20150729, ctrb_darwin2_ckpt64y_20140622, ctrb_darwin2_ckpt65d_20140915, ctrb_darwin2_ckpt64t_20140202, ctrb_darwin2_ckpt66h_20170602, ctrb_darwin2_ckpt64s_20140105, ctrb_darwin2_ckpt64x_20140524, ctrb_darwin2_ckpt65x_20160612, ctrb_darwin2_ckpt66f_20170407, ctrb_darwin2_ckpt65g_20141120, ctrb_darwin2_ckpt65k_20150402, ctrb_darwin2_ckpt64w_20140502, ctrb_darwin2_ckpt66a_20161020, ctrb_darwin2_ckpt65f_20141014, ctrb_darwin2_ckpt66b_20161219, ctrb_darwin2_ckpt64u_20140308, ctrb_darwin2_ckpt65i_20150123, ctrb_darwin2_ckpt66j_20170815, ctrb_darwin2_ckpt65y_20160801, ctrb_darwin2_ckpt66c_20170121, ctrb_darwin2_ckpt65a_20140728, ctrb_darwin2_ckpt65b_20140812, ctrb_darwin2_ckpt65t_20160221, ctrb_darwin2_ckpt66o_20180209, ctrb_darwin2_ckpt66e_20170314, ctrb_darwin2_ckpt65u_20160315, ctrb_darwin2_ckpt65r_20151221, ctrb_darwin2_ckpt66i_20170718, ctrb_darwin2_ckpt65c_20140830, ctrb_darwin2_ckpt66l_20171025, ctrb_darwin2_ckpt65h_20141217, ctrb_darwin2_ckpt66m_20171213, HEAD
Changes since 1.8: +3 -2 lines
clean up multi-threading directives

1 jahn 1.9 C $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/darwin/darwin_readparams.F,v 1.8 2013/04/16 20:21:57 jahn Exp $
2 jahn 1.2 C $Name: $
3 jahn 1.1
4     #include "DARWIN_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DARWIN_READPARMS
8    
9     C !INTERFACE: ==========================================================
10     SUBROUTINE DARWIN_READPARMS( myThid )
11    
12     C !DESCRIPTION:
13     C Initialize DARWIN parameters, read in data.darwin
14    
15     C !USES: ===============================================================
16     IMPLICIT NONE
17     #include "SIZE.h"
18     #include "EEPARAMS.h"
19     #include "PARAMS.h"
20     #include "GCHEM.h"
21     #include "DARWIN_SIZE.h"
22     #include "DARWIN_IO.h"
23     #include "DARWIN_PARAMS.h"
24     #ifdef WAVEBANDS
25     #include "SPECTRAL_SIZE.h"
26     #include "SPECTRAL.h"
27     #include "WAVEBANDS_PARAMS.h"
28     #endif
29    
30     C !INPUT PARAMETERS: ===================================================
31     C myThid :: thread number
32     INTEGER myThid
33    
34     C !OUTPUT PARAMETERS: ==================================================
35     C none
36    
37     #ifdef ALLOW_DARWIN
38    
39     C !LOCAL VARIABLES: ====================================================
40     C iUnit :: unit number for I/O
41     C msgBuf :: message buffer
42     INTEGER iUnit,errIO
43     CHARACTER*(MAX_LEN_MBUF) msgBuf
44     #if defined(WAVEBANDS) || defined(OASIM)
45     INTEGER ilam,i
46     _RL planck, c, hc, oavo, hcoavo, rlamm
47     #endif
48     CEOP
49    
50     NAMELIST /DARWIN_FORCING/
51     & darwin_iceFile,
52     & darwin_ironFile,
53     & darwin_PARFile,
54     & darwin_nutWVelFile,
55     & darwin_PO4_relaxFile, darwin_NO3_relaxFile,
56     & darwin_FeT_relaxFile, darwin_Si_relaxFile,
57     & darwin_PO4_fluxFile, darwin_NO3_fluxFile,
58     & darwin_FeT_fluxFile, darwin_Si_fluxFile,
59     & darwin_waterabsorbFile, darwin_phytoabsorbFile,
60     & darwin_surfacespecFile, darwin_acdomFile,
61     & darwin_particleabsorbFile,
62     #ifdef OASIM
63     & darwin_oasim_edFile, darwin_oasim_esFile,
64     #endif
65     & darwin_relaxscale,
66     & darwin_ForcingPeriod, darwin_ForcingCycle,
67 jahn 1.2 & darwin_PARunits, darwin_W_to_uEins,
68 jahn 1.3 & darwin_ironUnits,
69     & darwin_dustFrac,
70 jahn 1.1 #ifdef ALLOW_PAR_DAY
71     & darwin_PARavPeriod,
72     #endif
73     & darwin_seed
74    
75     #if defined(WAVEBANDS) || defined(OASIM)
76     NAMELIST /DARWIN_SPECTRAL_PARM/
77     & darwin_waves
78     #ifdef WAVEBANDS
79 jahn 1.4 & ,darwin_wavebands
80 jahn 1.1 #ifdef DAR_CALC_ACDOM
81 jahn 1.8 & ,darwin_Sdom, darwin_lambda_aCDOM, darwin_aCDOM_fac
82 jahn 1.1 #endif
83     #ifdef DAR_DIAG_ACDOM
84     & ,darwin_diag_acdom_ilam
85     #endif
86     #ifdef DAR_RADTRANS
87     & ,darwin_PAR_ilamLo
88     & ,darwin_PAR_ilamHi
89     & ,darwin_radmodThresh
90     & ,darwin_Dmax
91     & ,darwin_rmus
92     & ,darwin_rmuu
93     & ,darwin_bbw
94     & ,darwin_bbphy
95     & ,darwin_bbmin
96     & ,darwin_radtrans_kmax
97     & ,darwin_radtrans_niter
98     & ,darwin_part_size_P
99     #endif
100     #endif /* WAVEBANDS */
101     #endif /* WAVEBANDS || OASIM */
102    
103     #ifdef DAR_DIAG_CHL
104     NAMELIST /DARWIN_CHL/
105     & Geider_Bigalphachl, Geider_smallalphachl,
106     & Geider_Bigchl2cmax, Geider_smallchl2cmax,
107     & Geider_Bigchl2cmin,
108     & Doney_Bmin, Doney_Bmax, Doney_PARstar,
109     & Cloern_A, Cloern_B, Cloern_C, Cloern_chl2cmin
110     #endif
111    
112     #ifdef ALLOW_CARBON
113     NAMELIST /DIC_FORCING/
114     & DIC_windFile, DIC_atmospFile,
115     & dic_pCO2, dic_int1, dic_int2, dic_int3, dic_int4
116     #endif
117    
118 jahn 1.9 _BEGIN_MASTER(myThid)
119    
120 jahn 1.1 C Set defaults values for parameters in DARWIN_IO.h
121     darwin_iceFile=' '
122     darwin_ironFile=' '
123     darwin_PARFile=' '
124     darwin_nutWVelFile=' '
125     darwin_PO4_relaxFile=' '
126     darwin_NO3_relaxFile=' '
127     darwin_FeT_relaxFile=' '
128     darwin_Si_relaxFile=' '
129     darwin_PO4_fluxFile=' '
130     darwin_NO3_fluxFile=' '
131     darwin_FeT_fluxFile=' '
132     darwin_Si_fluxFile=' '
133     darwin_waterabsorbFile=' '
134     darwin_phytoabsorbFile=' '
135     darwin_particleabsorbFile=' '
136     darwin_surfacespecFile=' '
137     darwin_acdomFile=' '
138     darwin_oasim_edFile=' '
139     darwin_oasim_esFile=' '
140 jahn 1.2 darwin_PARunits='Ein/m2/d '
141     darwin_W_to_uEins=1. _d 0/0.2174 _d 0
142 jahn 1.3 darwin_ironUnits='mol Fe/m2/s '
143     darwin_dustFrac=0.035 _d 0
144 jahn 1.1 darwin_relaxscale=0. _d 0
145     darwin_seed=0
146     c default periodic forcing to same as for GCHEM
147     darwin_forcingPeriod=gchem_ForcingPeriod
148     darwin_forcingCycle=gchem_ForcingCycle
149    
150     #ifdef ALLOW_CARBON
151     DIC_windFile = ' '
152     DIC_atmospFile= ' '
153     dic_int1 = 0
154     dic_int2 = 0
155     dic_int3 = 0
156     dic_int4 = 0
157     dic_pCO2 = 0. _d 0
158     #endif
159    
160     #ifdef ALLOW_PAR_DAY
161     darwin_PARavPeriod=86400. _d 0
162     #endif
163    
164     #if defined(WAVEBANDS) || defined(OASIM)
165     DO ilam=1,tlam
166     darwin_waves(ilam) = 0
167     ENDDO
168     #endif
169    
170     #ifdef WAVEBANDS
171 jahn 1.4 DO ilam=1,tlam+1
172 jahn 1.7 darwin_wavebands(ilam) = -1
173 jahn 1.4 ENDDO
174 jahn 1.1 #ifdef DAR_CALC_ACDOM
175     darwin_Sdom = 0.014 _d 0
176 jahn 1.8 darwin_lambda_aCDOM = 450 _d 0
177     darwin_aCDOM_fac = 0.2 _d 0
178 jahn 1.1 #endif
179     #ifdef DAR_DIAG_ACDOM
180     c value >= 100 will be converted to index in wavebands_init_fixed
181     darwin_diag_acdom_ilam = 450
182     #endif
183     #ifdef DAR_RADTRANS
184     darwin_PAR_ilamLo = 1
185     darwin_PAR_ilamHi = tlam
186     darwin_radmodThresh = 1 _d -4
187     darwin_Dmax = 500 _d 0
188     darwin_rmus = 1.0/0.83 _d 0
189     darwin_rmuu = 1.0/0.4 _d 0
190     darwin_bbmin = 0.0002 _d 0
191     darwin_bbw = 0.5 _d 0
192     do i=1,tnabp
193     darwin_bbphy(i) = 0 _d 0
194     enddo
195     darwin_radtrans_kmax = Nr
196 jahn 1.5 darwin_radtrans_niter = -2
197 jahn 1.1 darwin_part_size_P = 1 _d -15 ! mmol P per particle
198     #endif
199     #endif /* WAVEBANDS */
200    
201     C Open and read the data.darwin file
202     WRITE(msgBuf,'(A)') ' DARWIN_READPARMS: opening data.darwin'
203     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
204     & SQUEEZE_RIGHT , 1)
205     CALL OPEN_COPY_DATA_FILE(
206     I 'data.darwin', 'DARWIN_READPARAMS',
207     O iUnit,
208     I myThid )
209     READ(UNIT=iUnit,NML=DARWIN_FORCING)
210     #ifdef ALLOW_PAR_DAY
211     darwin_PARnav = NINT(darwin_PARavPeriod*nsubtime/dTtracerLev(1))
212     #endif
213 jahn 1.2 C factor for conversion to uEin/m2/s
214     IF ( darwin_PARunits(1:16) .EQ. 'uEin/m2/s ' ) THEN
215     darwin_PARFileConv = 1. _d 0
216     ELSEIF ( darwin_PARunits(1:16) .EQ. 'Ein/m2/d ' ) THEN
217     darwin_PARFileConv = 1. _d 6/86400. _d 0
218     ELSEIF ( darwin_PARunits(1:16) .EQ. 'W/m2 ' ) THEN
219     darwin_PARFileConv = darwin_W_to_uEins
220     ELSE
221     WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:',
222     & 'darwin_PARunits must be one of Ein/m2/d, uEin/m2/s, W/m2'
223     CALL PRINT_ERROR( msgBuf , 1)
224     STOP 'unknown darwin_PARunits'
225     ENDIF
226 jahn 1.1
227 jahn 1.3 C factor for conversion to mmol Fe/m2/s (bioavailable fraction is done later)
228     IF ( darwin_ironUnits(1:16) .EQ. 'mol Fe/m2/s ' ) THEN
229     darwin_ironFileConv = 1000. _d 0
230     ELSEIF ( darwin_ironUnits(1:16) .EQ. 'kg dust/m2/s ' ) THEN
231     darwin_ironFileConv = 1000.*darwin_dustFrac*1000./55.845 _d 0
232     ELSE
233     WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:',
234     & 'darwin_ironUnits must be one of mol Fe/m2/s, kg dust/m2/s'
235     CALL PRINT_ERROR( msgBuf , 1)
236     STOP 'unknown darwin_Feunits'
237     ENDIF
238    
239 jahn 1.1 #ifdef DAR_DIAG_CHL
240     C default values
241     C Geider: chl:c = max(chl2cmin, chl2cmax/(1+(chl2cmax*alphachl*PARday)/(2*Pcm)))
242     C Pcm = mu*limit*phytoTempFunction
243     Geider_smallalphachl = 2. _d -6 ! mmol C (mg Chl)-1 m2 (uEin)-1
244     Geider_Bigalphachl = 1. _d -6 ! mmol C (mg Chl)-1 m2 (uEin)-1
245     Geider_smallchl2cmax = 0.35 _d 0 ! mg Chl (mmol C)-1
246     Geider_Bigchl2cmax = 0.65 _d 0 ! mg Chl (mmol C)-1
247     Geider_smallchl2cmin = 0.003 _d 0 * 12. _d 0 ! mg Chl a/mmol C
248     Geider_Bigchl2cmin = 0.003 _d 0 * 12. _d 0 ! mg Chl a/mmol C
249    
250     C Doney: chl:c = (Bmax - (Bmax-Bmin)*MIN(1,PARday/PARstar))*limit
251     Doney_Bmax = 12. _d 0 / 37. _d 0 ! mg Chl a/mmol C
252     Doney_Bmin = 12. _d 0 / 90. _d 0 ! mg Chl a/mmol C
253     Doney_PARstar = 90. _d 0 / 0.2174 _d 0 ! uEin/m2/s
254    
255     C Cloern: chl:c = chl2cmin + A*exp(B*T)*exp(-C*PARday)*limit
256     Cloern_chl2cmin = 0.003 _d 0 * 12. _d 0 ! mg Chl a/mmol C
257     Cloern_A = 0.0154 _d 0 * 12. _d 0 ! mg Chl a/mmol C
258     Cloern_B = 0.050 _d 0 ! (degree C)^{-1}
259     Cloern_C = 0.059 _d 0 * 86400. _d 0 / 1. _d 6 ! m^2 s/uEin
260    
261     READ(UNIT=iUnit,NML=DARWIN_CHL)
262     #endif /* DAR_DIAG_CHL */
263    
264     #ifdef ALLOW_CARBON
265     READ(UNIT=iUnit,NML=DIC_FORCING)
266     #endif
267    
268     #ifdef DAR_RADTRANS
269     #ifndef DAR_NONSPECTRAL_BACKSCATTERING_RATIO
270     DO i=1,tnabp
271     IF ( darwin_bbphy(i) .NE. 0 _d 0 ) THEN
272     WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:',
273     & 'darwin_bbphy is obsolete.'
274     CALL PRINT_ERROR( msgBuf , 1)
275     WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:',
276     & 'Backscattering coefficients are now read from'
277     CALL PRINT_ERROR( msgBuf , 1)
278     WRITE(msgBuf,'(2A)') 'S/R DARWIN_READPARMS:',
279     & 'darwin_phytoabsorbFile.'
280     CALL PRINT_ERROR( msgBuf , 1)
281     ENDIF
282     ENDDO
283     #endif
284     #endif
285    
286     #if defined(WAVEBANDS) || defined(OASIM)
287     READ(UNIT=iUnit,NML=DARWIN_SPECTRAL_PARM,IOSTAT=errIO)
288     IF ( errIO .LT. 0 ) THEN
289     WRITE(msgBuf,'(A)')
290     & 'S/R DARWIN_READPARMS'
291     CALL PRINT_ERROR( msgBuf , 1)
292     WRITE(msgBuf,'(A)')
293     & 'Error reading darwin package'
294     CALL PRINT_ERROR( msgBuf , 1)
295     WRITE(msgBuf,'(A)')
296     & 'parameter file "data.darwin"'
297     CALL PRINT_ERROR( msgBuf , 1)
298     WRITE(msgBuf,'(A)')
299     & 'Problem in namelist DARWIN_SPECTRAL_PARM'
300     CALL PRINT_ERROR( msgBuf , 1)
301     STOP 'ABNORMAL END: S/R DARWIN_READPARMS'
302     ENDIF
303     #endif
304    
305     WRITE(msgBuf,'(A)')
306     & ' DARWIN_READPARMS: finished reading data.darwin'
307     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
308     & SQUEEZE_RIGHT , 1)
309    
310     C Close the open data file
311     CLOSE(iUnit)
312    
313     #if defined(WAVEBANDS) || defined(OASIM)
314 jahn 1.4 IF ( darwin_waves(1).EQ.0.0 .AND. tlam.EQ.13 ) THEN
315     darwin_waves(1) = 400
316     darwin_waves(2) = 425
317     darwin_waves(3) = 450
318     darwin_waves(4) = 475
319     darwin_waves(5) = 500
320     darwin_waves(6) = 525
321     darwin_waves(7) = 550
322     darwin_waves(8) = 575
323     darwin_waves(9) = 600
324     darwin_waves(10) = 625
325     darwin_waves(11) = 650
326     darwin_waves(12) = 675
327     darwin_waves(13) = 700
328     IF ( darwin_wavebands(1).NE.0.0 ) THEN
329     WRITE(msgBuf,'(2A)') 'DARWIN_READPARMS: ',
330     & 'darwin_wavebands given without darwin_waves.'
331     CALL PRINT_ERROR( msgBuf, myThid )
332     WRITE(msgBuf,'(2A)') 'DARWIN_READPARMS: ',
333     & 'using standard waveband centers 400, 425, ...'
334     CALL PRINT_ERROR( msgBuf, myThid )
335     WRITE(msgBuf,'(2A)') 'DARWIN_READPARMS: ',
336     & 'provide darwin_waves if this is not desired.'
337     CALL PRINT_ERROR( msgBuf, myThid )
338     ENDIF
339     ENDIF
340 jahn 1.1 c Quanta conversion
341     planck = 6.6256 _d -34 !Plancks constant J sec
342     c = 2.998 _d 8 !speed of light m/sec
343     hc = 1.0/(planck*c)
344     oavo = 1.0/6.023 _d 23 ! 1/Avogadros number
345     hcoavo = hc*oavo
346     do ilam = 1,tlam
347     rlamm = darwin_waves(ilam)*1 _d -9 !lambda in m
348     WtouEins(ilam) = 1 _d 6*rlamm*hcoavo !Watts to uEin/s conversion
349 jahn 1.4 IF ( rlamm .EQ. 0.0 ) THEN
350     WRITE(msgBuf,'(2A)') 'DARWIN_READPARMS: ',
351     & 'please provide wavelengths in darwin_waves.'
352     CALL PRINT_ERROR( msgBuf, myThid )
353     STOP 'ABNORMAL END: S/R DARWIN_READPARMS'
354     ENDIF
355 jahn 1.1 enddo
356     #endif
357    
358     C-- Print a summary of parameter values:
359     iUnit = standardMessageUnit
360     WRITE(msgBuf,'(A)') '// ==================================='
361     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
362     WRITE(msgBuf,'(A)') '// darwin parameters '
363     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
364     WRITE(msgBuf,'(A)') '// ==================================='
365     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
366     CALL WRITE_0D_I( darwin_seed, INDEX_NONE,
367     & 'darwin_seed =',
368     & ' /* seed for random number generator */')
369    
370     WRITE(msgBuf,'(A)') ' -----------------------------------'
371     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
372    
373     #if defined(WAVEBANDS) || defined(OASIM)
374 jahn 1.6 CALL WRITE_1D_RL( darwin_waves, tlam, 0,
375 jahn 1.1 & 'darwin_waves =',
376     &' /* "central" wavelengths of wavebands */')
377     #endif
378     #ifdef WAVEBANDS
379     #ifdef DAR_CALC_ACDOM
380     CALL WRITE_0D_RL( darwin_Sdom, INDEX_NONE,
381     & 'darwin_Sdom =',
382     &' /* spectral slope for aCDOM */')
383     #endif
384     #ifdef DAR_DIAG_ACDOM
385     CALL WRITE_0D_I( darwin_diag_acdom_ilam, INDEX_NONE,
386     & 'darwin_diag_acdom_ilam =',
387     &' /* waveband to use for aCDOM diagnostic */')
388     #endif
389     #ifdef DAR_RADTRANS
390     CALL WRITE_0D_I( darwin_PAR_ilamLo, INDEX_NONE,
391     & 'darwin_PAR_ilamLo =',
392     &' /* waveband index of PAR lower bound */')
393     CALL WRITE_0D_I( darwin_PAR_ilamHi, INDEX_NONE,
394     & 'darwin_PAR_ilamHi =',
395     &' /* waveband index of PAR upper bound */')
396     CALL WRITE_0D_RL( darwin_radmodThresh, INDEX_NONE,
397     & 'darwin_radmodThresh =',
398     &' /* threshold for calling radmod (W/m2/waveband) */')
399     CALL WRITE_0D_RL( darwin_Dmax, INDEX_NONE,
400     & 'darwin_Dmax =',
401     &' /* depth at which Ed is assumed zero */')
402     CALL WRITE_0D_RL( darwin_rmus, INDEX_NONE,
403     & 'darwin_rmus =',
404     &' /* inverse average cosine of downward diffuse irradiance */')
405     CALL WRITE_0D_RL( darwin_rmuu, INDEX_NONE,
406     & 'darwin_rmuu =',
407     &' /* inverse average cosine of upward diffuse irradiance */')
408     CALL WRITE_0D_RL( darwin_bbw, INDEX_NONE,
409     & 'darwin_bbw =',
410     &' /* backscattering to forward scattering ratio for water */')
411     CALL WRITE_0D_RL( darwin_bbmin, INDEX_NONE,
412     & 'darwin_bbmin =',
413     &' /* minimum backscattering coefficient (1/m) */')
414     CALL WRITE_1D_RL( darwin_bbphy, tnabp, 0,
415     & 'darwin_bbphy =',
416     &' /* backscattering to forward scattering ratio for phyto */')
417     CALL WRITE_0D_I( darwin_radtrans_kmax, INDEX_NONE,
418     & 'darwin_radtrans_kmax =',
419     &' /* deepest level in which to compute irradiances */')
420     CALL WRITE_0D_I( darwin_radtrans_niter, INDEX_NONE,
421     & 'darwin_radtrans_niter =',
422 jahn 1.5 &' /* iterations/method for solveing 3-stream equations */')
423 jahn 1.1 #endif /* DAR_RADTRANS */
424     #endif /* WAVEBANDS */
425    
426     WRITE(msgBuf,'(A)') ' ==================================='
427     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
428    
429     _END_MASTER(myThid)
430    
431     C Everyone else must wait for the parameters to be loaded
432     _BARRIER
433    
434     #endif /* ALLOW_DARWIN */
435    
436     RETURN
437     END

  ViewVC Help
Powered by ViewVC 1.1.22