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

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

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


Revision 1.6 - (hide annotations) (download)
Wed Dec 4 21:18:51 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.5: +5 -1 lines
only master thread reads

1 jahn 1.6 C $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/darwin/wavebands_init_fixed.F,v 1.5 2013/04/16 20:21:57 jahn Exp $
2 jahn 1.2 C $Name: $
3 jahn 1.1
4     c ANNA wavebands_init_fixed.F reads-in and assigns input paramters for WAVEBANDS.
5    
6     #include "DARWIN_OPTIONS.h"
7    
8     CBOP
9     C !ROUTINE: WAVEBANDS_INIT_FIXED
10     C !INTERFACE:
11     subroutine wavebands_init_fixed(myThid)
12    
13     C !DESCRIPTION: \bv
14     C *==========================================================*
15     C | SUBROUTINE WAVEBANDS_INIT_FIXED
16     C | o reads-in and assigns input paramters for WAVEBANDS.
17     C *==========================================================*
18     C \ev
19    
20     C !USES:
21     implicit none
22     C == Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "DARWIN_SIZE.h"
27     #include "SPECTRAL_SIZE.h"
28     #include "SPECTRAL.h"
29     #include "WAVEBANDS_PARAMS.h"
30     #include "DARWIN_IO.h"
31    
32     C !INPUT/OUTPUT PARAMETERS:
33     C == Routine arguments ==
34     C myThid :: my Thread Id number
35     integer myThid
36     CEOP
37    
38     #ifdef WAVEBANDS
39    
40     C !LOCAL VARIABLES:
41     C == Local variables ==
42     c local variables
43     CHARACTER*(MAX_LEN_MBUF) msgBuf
44     character*80 title
45     integer iUnit
46     integer swlambda,splambda,ssflambda
47     _RL sap,sap_ps,sbp,sbbp
48     _RL saw,sbw
49     _RL ssf
50     c _RL planck, c, hc, oavo, hcoavo, rlamm
51     #ifdef DAR_CALC_ACDOM
52 jahn 1.5 _RL rlam
53 jahn 1.1 #else
54     _RL sacdom
55     #endif
56     c local indeces
57     integer nabp,i,ilam
58    
59 jahn 1.6 _BEGIN_MASTER(myThid)
60    
61 jahn 1.4 C fill in missing waveband information:
62     C "representative values" darwin_waves need not be centered within
63     C waveband boundaries darwin_wavebands, so both may be given
64     C if representative values are not given, compute from waveband
65     C boundaries
66 jahn 1.1 do i = 1,tlam
67 jahn 1.4 if (darwin_waves(i) .gt. 0) then
68     pwaves(i) = darwin_waves(i)
69     elseif (darwin_wavebands(i).ge.0 .and.
70     & darwin_wavebands(i+1).ge.0 ) then
71     pwaves(i) = .5*(darwin_wavebands(i)+darwin_wavebands(i+1))
72     else
73     WRITE(msgBuf,'(3A)') 'WAVEBANDS_INIT_FIXED: ',
74     & 'please provide wavelengths in darwin_waves or ',
75     & 'waveband boundaries in darwin_wavebands.'
76     CALL PRINT_ERROR( msgBuf, myThid )
77     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
78     endif
79     enddo
80    
81     C if waveband boundaries not given, compute from representative values
82     C these will be used to compute waveband widths
83     do i=1,tlam+1
84     if (darwin_wavebands(i).LT.0) then
85     C put boundaries half-way between central values
86     C but first and last boundary are at first and last "central" value
87     if (i.eq.1) then
88     darwin_wavebands(i) = pwaves(1)
89     elseif (i.le.tlam) then
90     darwin_wavebands(i) = .5*(pwaves(i-1)+pwaves(i))
91     else
92     darwin_wavebands(i) = pwaves(tlam)
93     endif
94     endif
95 jahn 1.1 enddo
96    
97 jahn 1.4 C waveband widths used to compute total PAR and alpha_mean
98 jahn 1.1 wb_totalWidth = 0.0
99     do i=1,tlam
100 jahn 1.4 wb_width(i) = darwin_wavebands(i+1) - darwin_wavebands(i)
101 jahn 1.1 wb_totalWidth = wb_totalWidth + wb_width(i)
102 jahn 1.4 C allow for zero-width wavebands...
103     if (wb_width(i).LT.0) then
104     WRITE(msgBuf,'(2A,I3)') 'WAVEBANDS_INIT_FIXED: ',
105     & 'negative waveband width encountered, waveband: ',i
106     CALL PRINT_ERROR( msgBuf, myThid )
107     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
108     & 'Please check darwin_waves and darwin_wavebands.'
109     CALL PRINT_ERROR( msgBuf, myThid )
110     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED: wavebands:'
111     CALL PRINT_ERROR( msgBuf, myThid )
112     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
113     & ' idx low rep high width'
114     CALL PRINT_ERROR( msgBuf, myThid )
115     do ilam=1,tlam
116     WRITE(msgBuf,'(A,I4,F10.3,I6,F10.3,F9.3)')
117     & 'WAVEBANDS_INIT_FIXED: ', ilam,darwin_wavebands(ilam),
118     & pwaves(ilam),darwin_wavebands(ilam+1),wb_width(ilam)
119     CALL PRINT_ERROR( msgBuf, myThid )
120     enddo
121     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
122     endif
123 jahn 1.1 enddo
124 jahn 1.4 C ...but require at least one non-zero-width band
125 jahn 1.1 if (wb_totalWidth.LE.0) then
126 jahn 1.4 #ifdef OASIM
127     if (tlam.eq.1) then
128     C in this case it doesn't matter, just make non-zero for
129     C alpha_mean computation
130     wb_width(1) = 1.
131     wb_totalWidth = 1.
132     else
133     #else
134     if (.TRUE.) then
135     #endif
136 jahn 1.1 WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
137 jahn 1.4 & 'need to provide waveband boundaries in darwin_wavebands.'
138 jahn 1.1 CALL PRINT_ERROR( msgBuf, myThid )
139     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
140 jahn 1.4 endif
141 jahn 1.1 endif
142    
143    
144     c Water data files
145     if (darwin_waterabsorbFile .NE. ' ' ) THEN
146     CALL MDSFINDUNIT( iUnit, myThid )
147     open(iUnit,file=darwin_waterabsorbFile,
148     & status='old',form='formatted')
149     do i = 1,6 ! six lines of text for the header
150     read(iUnit,'(a50)')title ! trucates or pads (with spaces) to 50 characters length
151     enddo
152     do ilam = 1,tlam
153     read(iUnit,20)swlambda,saw,sbw
154     if (swlambda.NE.pwaves(ilam)) then
155     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
156     & "wavelength for water spectrum doesn't match darwin_waves:"
157     CALL PRINT_ERROR( msgBuf, myThid )
158 jahn 1.3 WRITE(msgBuf,'(2A,I3,A,I4,A,I4)') 'WAVEBANDS_INIT_FIXED: ',
159 jahn 1.1 & 'ilam', ilam, ': ', swlambda, ' versus ', pwaves(ilam)
160     CALL PRINT_ERROR( msgBuf, myThid )
161     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
162     endif
163     aw(ilam) = saw
164     bw(ilam) = sbw
165     enddo
166     close(iUnit)
167     20 format(i5,f15.4,f10.4)
168     else
169     WRITE(msgBuf,'(A)')
170     & 'WAVEBANDS_INIT_FIXED: need to specify water absorption'
171     CALL PRINT_ERROR( msgBuf, myThid )
172     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
173     endif
174    
175    
176     c phyto data files
177     c ANNA phyto input data files must have a column for absorption by PS pigs
178     c ANNA easiest way to 'turn off' PS for growth is to put same values in both abs columns
179     if (darwin_phytoabsorbFile.NE. ' ' ) THEN
180     CALL MDSFINDUNIT( iUnit, myThid )
181     open(iUnit,file=darwin_phytoabsorbFile,
182     & status='old',form='formatted')
183     do i = 1,6 ! six lines of text for the header
184     read(iUnit,'(a50)')title
185     enddo
186     sbbp = 0. _d 0
187     do nabp = 1,tnabp
188     read(iUnit,'(a50)')title ! reads one line of text for the phytoplankton type header
189     do ilam = 1,tlam
190     #ifdef DAR_NONSPECTRAL_BACKSCATTERING_RATIO
191     read(iUnit,30)splambda,sap,sap_ps,sbp
192     #else
193     read(iUnit,'(i4,3f10.0,f20.0)')splambda,sap,sap_ps,sbp,sbbp
194     #endif
195     if (splambda.NE.pwaves(ilam)) then
196     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
197     & "wavelength for phyto spectrum doesn't match darwin_waves:"
198     CALL PRINT_ERROR( msgBuf, myThid )
199 jahn 1.3 WRITE(msgBuf,'(2A,I3,A,I4,A,I4)') 'WAVEBANDS_INIT_FIXED: ',
200 jahn 1.1 & 'ilam', ilam, ': ', splambda, ' versus ', pwaves(ilam)
201     CALL PRINT_ERROR( msgBuf, myThid )
202     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
203     endif
204     ap(nabp,ilam) = sap
205     ap_ps(nabp,ilam) = sap_ps
206     bp(nabp,ilam) = sbp
207     bbp(nabp,ilam) = sbbp
208     enddo
209     enddo
210     close(iUnit)
211     30 format(i4,3f10.4)
212     else
213     WRITE(msgBuf,'(A)')
214     & 'WAVEBANDS_INIT_FIXED: need to specify phyto absorption'
215     CALL PRINT_ERROR( msgBuf, myThid )
216     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
217     endif
218    
219    
220     #ifndef OASIM
221     c QQ NEED IN HERE ifndef OASIM
222     c surface spectrum for initial use
223     if (darwin_surfacespecFile .NE. ' ' ) THEN
224     CALL MDSFINDUNIT( iUnit, myThid )
225     open(iUnit,file=darwin_surfacespecFile,
226     & status='old',form='formatted')
227     do i = 1,3 ! three lines of text for the header
228     read(iUnit,'(a50)')title
229     enddo
230     do ilam = 1,tlam
231     read(iUnit,40)ssflambda,ssf
232     if (ssflambda.NE.pwaves(ilam)) then
233     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
234     & "wavelength for surface spectrum doesn't match darwin_waves:"
235     CALL PRINT_ERROR( msgBuf, myThid )
236 jahn 1.3 WRITE(msgBuf,'(2A,I3,A,I4,A,I4)') 'WAVEBANDS_INIT_FIXED: ',
237 jahn 1.1 & 'ilam', ilam, ': ', ssflambda, ' versus ', pwaves(ilam)
238     CALL PRINT_ERROR( msgBuf, myThid )
239     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
240     endif
241     sf(ilam) = ssf
242     enddo
243     close(iUnit)
244     40 format(i5,f15.6)
245     else
246     WRITE(msgBuf,'(A)')
247     & 'WAVEBANDS_INIT_FIXED: need surface spectrum'
248     CALL PRINT_ERROR( msgBuf, myThid )
249     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
250     endif
251     #endif /* not OASIM */
252    
253    
254     c absorption by cdom
255     #ifndef DAR_CALC_ACDOM
256     c if no file given then CDOM is zero
257     if (darwin_acdomFile.NE. ' ' ) THEN
258     CALL MDSFINDUNIT( iUnit, myThid )
259     open(iUnit,file=darwin_acdomFile,
260     & status='old',form='formatted')
261     do i = 1,6 ! six lines of text for the header
262     read(iUnit,'(a50)')title
263     enddo
264     do i = 1,tlam
265     read(iUnit,50)sacdom
266     acdom(i) = sacdom
267     enddo
268     close(iUnit)
269     50 format(f10.4)
270     else
271     WRITE(msgBuf,'(A)')
272     & 'WAVEBANDS_INIT_FIXED: no aCDOM'
273     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
274     & SQUEEZE_RIGHT, 1 )
275    
276     do i = 1,tlam
277     acdom(i) = 0. _d 0
278     enddo
279     endif
280     #else /* DAR_CALC_ACDOM */
281     c for 3-D or for direct comparison to RADTRANS would need the same formulation for CDOM as in radtrans.
282     c CDOM absorption exponent
283 jahn 1.5 nlaCDOM = 0
284 jahn 1.1 do ilam = 1,tlam
285 jahn 1.5 if (pwaves(ilam) .eq. darwin_lambda_aCDOM) nlaCDOM = ilam
286 jahn 1.1 rlam = float(pwaves(ilam))
287 jahn 1.5 excdom(ilam) = exp(-darwin_Sdom*(rlam-darwin_lambda_aCDOM))
288 jahn 1.1 enddo
289 jahn 1.5 if (nlaCDOM.eq.0) then
290     WRITE(msgBuf,'(A,I3,A)')
291     & 'WAVEBANDS_INIT_FIXED: no waveband found at ',
292     & darwin_lambda_aCDOM, ' nm (needed for DAR_CALC_ACDOM).'
293     CALL PRINT_ERROR( msgBuf, myThid )
294     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
295     endif
296 jahn 1.1
297     WRITE(msgBuf,'(A,1P1E20.12)')
298 jahn 1.4 & 'WAVEBANDS_INIT_FIXED: darwin_aCDOM_fac = ',darwin_aCDOM_fac
299     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
300     & SQUEEZE_RIGHT, 1 )
301     WRITE(msgBuf,'(A,1P1E20.12)')
302 jahn 1.1 & 'WAVEBANDS_INIT_FIXED: darwin_Sdom = ', darwin_Sdom
303     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
304     & SQUEEZE_RIGHT, 1 )
305 jahn 1.5 WRITE(msgBuf,'(A,I3,A,I4)')
306     & 'WAVEBANDS_INIT_FIXED: nlaCDOM = ', nlaCDOM, ', lambda = ',
307     & pwaves(nlaCDOM)
308 jahn 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
309     & SQUEEZE_RIGHT, 1 )
310     #endif /* DAR_CALC_ACDOM */
311    
312     #ifdef DAR_DIAG_ACDOM
313     c find waveband index for acdom diagnostic
314     if (darwin_diag_acdom_ilam.GE.100) then
315     do ilam = 1,tlam
316     if (pwaves(ilam) .eq. darwin_diag_acdom_ilam) then
317     darwin_diag_acdom_ilam = ilam
318     goto 60
319     endif
320     enddo
321 jahn 1.5 WRITE(msgBuf,'(2A,I3,A)') 'WAVEBANDS_INIT_FIXED: ',
322     & 'darwin_diag_acdom_ilam =',darwin_diag_acdom_ilam,
323     & ' not found in darwin_waves'
324     CALL PRINT_ERROR( msgBuf, myThid )
325     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
326 jahn 1.1 60 continue
327     endif
328    
329     WRITE(msgBuf,'(A,I3,A,I4)')
330     & 'WAVEBANDS_INIT_FIXED: aCDOM diag ilam = ',
331     & darwin_diag_acdom_ilam, ', lambda = ',
332     & pwaves(darwin_diag_acdom_ilam)
333     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
334     & SQUEEZE_RIGHT, 1 )
335     #endif
336    
337 jahn 1.4 WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
338     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
339     & SQUEEZE_RIGHT, 1 )
340     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED: wavebands:'
341     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
342     & SQUEEZE_RIGHT,myThid)
343     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
344     & ' idx low rep high width'
345     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
346     & SQUEEZE_RIGHT,myThid)
347     do i=1,tlam
348     WRITE(msgBuf,'(A,I4,F10.3,I6,F10.3,F9.3)')
349     & 'WAVEBANDS_INIT_FIXED: ', i,
350     & darwin_wavebands(i),pwaves(i),darwin_wavebands(i+1),wb_width(i)
351     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
352     & SQUEEZE_RIGHT,myThid)
353     enddo
354     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
355     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
356     & SQUEEZE_RIGHT, 1 )
357    
358 jahn 1.1 #ifdef DAR_RADTRANS
359     c absorption and scattering by particles
360     if (darwin_particleabsorbFile .NE. ' ' ) THEN
361     CALL MDSFINDUNIT( iUnit, myThid )
362     open(iUnit,file=darwin_particleabsorbFile,
363     & status='old',form='formatted')
364     do i = 1,6 ! six lines of text for the header
365     read(iUnit,'(a50)')title ! trucates or pads (with spaces) to 50 characters length
366     enddo
367     do ilam = 1,tlam
368     read(iUnit,'(I4,3F15.0)')splambda,sap,sbp,sbbp
369     if (splambda.NE.pwaves(ilam)) then
370     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: ',
371     & "wavelength for particle spectrum doesn't match darwin_waves:"
372     CALL PRINT_ERROR( msgBuf, myThid )
373 jahn 1.3 WRITE(msgBuf,'(2A,I3,A,I4,A,I4)') 'WAVEBANDS_INIT_FIXED: ',
374 jahn 1.1 & 'ilam', ilam, ': ', splambda, ' versus ', pwaves(ilam)
375     CALL PRINT_ERROR( msgBuf, myThid )
376     STOP 'ABNORMAL END: S/R WAVEBANDS_INIT_FIXED'
377     endif
378     apart(ilam) = sap
379     bpart(ilam) = sbp
380     bbpart(ilam) = sbbp
381     apart_P(ilam) = sap/darwin_part_size_P
382     bpart_P(ilam) = sbp/darwin_part_size_P
383     bbpart_P(ilam) = sbbp/darwin_part_size_P
384     enddo
385     close(iUnit)
386     else
387     do ilam = 1,tlam
388     apart(ilam) = 0. _d 0
389     bpart(ilam) = 0. _d 0
390     bbpart(ilam) = 0. _d 0
391     apart_P(ilam) = 0. _d 0
392     bpart_P(ilam) = 0. _d 0
393     bbpart_P(ilam) = 0. _d 0
394     enddo
395     endif
396    
397     c print a summary
398     #ifndef OASIM
399     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED: surface spectrum:'
400     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
401     & SQUEEZE_RIGHT, 1 )
402     WRITE(msgBuf,'(A,A)') 'WAVEBANDS_INIT_FIXED: ',
403     & ' lam sf'
404     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
405     & SQUEEZE_RIGHT, 1 )
406     do ilam = 1,tlam
407     WRITE(msgBuf,'(A,I4,F15.6)') 'WAVEBANDS_INIT_FIXED: ',
408     & pwaves(ilam), sf(ilam)
409     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
410     & SQUEEZE_RIGHT, 1 )
411     enddo
412     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
413     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
414     & SQUEEZE_RIGHT, 1 )
415     #endif
416     c
417     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED: water spectra:'
418     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
419     & SQUEEZE_RIGHT, 1 )
420     WRITE(msgBuf,'(A,A)') 'WAVEBANDS_INIT_FIXED: ',
421     & ' lam aw bw'
422     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
423     & SQUEEZE_RIGHT, 1 )
424     do ilam = 1,tlam
425     WRITE(msgBuf,'(A,I4,F15.4,F10.4)') 'WAVEBANDS_INIT_FIXED: ',
426     & pwaves(ilam), aw(ilam), bw(ilam)
427     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
428     & SQUEEZE_RIGHT, 1 )
429     enddo
430     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
431     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
432     & SQUEEZE_RIGHT, 1 )
433     c
434     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED: phyto spectra:'
435     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
436     & SQUEEZE_RIGHT, 1 )
437     do nabp = 1,tnabp
438     WRITE(msgBuf,'(A,I4)') 'WAVEBANDS_INIT_FIXED: type ',nabp
439     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
440     & SQUEEZE_RIGHT, 1 )
441     WRITE(msgBuf,'(A,A)') 'WAVEBANDS_INIT_FIXED: ',
442     & ' lam ap ap_ps bp bbp'
443     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
444     & SQUEEZE_RIGHT, 1 )
445     do ilam = 1,tlam
446     WRITE(msgBuf,'(A,I4,3F10.4,F20.9)') 'WAVEBANDS_INIT_FIXED: ',
447     & pwaves(ilam), ap(nabp,ilam), ap_ps(nabp,ilam),
448     & bp(nabp,ilam), bbp(nabp,ilam)
449     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
450     & SQUEEZE_RIGHT, 1 )
451     enddo
452     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
453     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
454     & SQUEEZE_RIGHT, 1 )
455     enddo
456     c
457     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED: particulate spectra:'
458     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
459     & SQUEEZE_RIGHT, 1 )
460     WRITE(msgBuf,'(A,A)') 'WAVEBANDS_INIT_FIXED: ',
461     & ' lam apart bpart bbpart'
462     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
463     & SQUEEZE_RIGHT, 1 )
464     do ilam = 1,tlam
465     WRITE(msgBuf,'(A,I4,1P3G15.6)')'WAVEBANDS_INIT_FIXED: ',
466     & pwaves(ilam), apart(ilam), bpart(ilam), bbpart(ilam)
467     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
468     & SQUEEZE_RIGHT, 1 )
469     enddo
470     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
471     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
472     & SQUEEZE_RIGHT, 1 )
473     c
474     WRITE(msgBuf,'(2A)') 'WAVEBANDS_INIT_FIXED: particulate spectra ',
475     & 'in phosphorus units:'
476     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
477     & SQUEEZE_RIGHT, 1 )
478     WRITE(msgBuf,'(A,A)') 'WAVEBANDS_INIT_FIXED: ',
479     & ' lam apart_P bpart_P bbpart_P'
480     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
481     & SQUEEZE_RIGHT, 1 )
482     do ilam = 1,tlam
483     WRITE(msgBuf,'(A,I4,2F15.9,F15.12)') 'WAVEBANDS_INIT_FIXED: ',
484     & pwaves(ilam), apart_P(ilam), bpart_P(ilam), bbpart_P(ilam)
485     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
486     & SQUEEZE_RIGHT, 1 )
487     enddo
488     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
489     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
490     & SQUEEZE_RIGHT, 1 )
491     c
492     #ifndef DAR_CALC_ACDOM
493     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED: CDOM spectrum:'
494     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
495     & SQUEEZE_RIGHT, 1 )
496     WRITE(msgBuf,'(A,A)') 'WAVEBANDS_INIT_FIXED: ',
497     & ' lam aCDOM'
498     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
499     & SQUEEZE_RIGHT, 1 )
500     do ilam = 1,tlam
501     WRITE(msgBuf,'(A,I4,F10.4)') 'WAVEBANDS_INIT_FIXED: ',
502     & pwaves(ilam), acdom(ilam)
503     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
504     & SQUEEZE_RIGHT, 1 )
505     enddo
506     WRITE(msgBuf,'(A)') 'WAVEBANDS_INIT_FIXED:'
507     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
508     & SQUEEZE_RIGHT, 1 )
509     #endif
510    
511     c constants
512     pid = DACOS(-1.0D0)
513     rad = 180.0D0/pid
514     #endif
515    
516 jahn 1.6 _END_MASTER(myThid)
517    
518 jahn 1.1 #endif /* WAVEBANDS */
519    
520     return
521     end
522    

  ViewVC Help
Powered by ViewVC 1.1.22