/[MITgcm]/MITgcm_contrib/darwin2/pkg/quota/quota_init_vari.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/quota/quota_init_vari.F

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


Revision 1.7 - (hide annotations) (download)
Tue May 19 14:32:43 2015 UTC (10 years, 2 months ago) by benw
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt65w_20160512, ctrb_darwin2_ckpt66g_20170424, ctrb_darwin2_ckpt66k_20171025, ctrb_darwin2_ckpt66n_20180118, ctrb_darwin2_ckpt65v_20160409, ctrb_darwin2_ckpt65s_20160114, ctrb_darwin2_ckpt66d_20170214, ctrb_darwin2_ckpt65m_20150615, ctrb_darwin2_ckpt65q_20151118, ctrb_darwin2_ckpt65o_20150914, ctrb_darwin2_ckpt65p_20151023, ctrb_darwin2_ckpt65z_20160929, ctrb_darwin2_ckpt65n_20150729, ctrb_darwin2_ckpt66h_20170602, ctrb_darwin2_ckpt65x_20160612, ctrb_darwin2_ckpt66f_20170407, ctrb_darwin2_ckpt66a_20161020, ctrb_darwin2_ckpt66b_20161219, ctrb_darwin2_ckpt66j_20170815, ctrb_darwin2_ckpt65y_20160801, ctrb_darwin2_ckpt66c_20170121, 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_ckpt66l_20171025, ctrb_darwin2_ckpt66m_20171213, HEAD
Changes since 1.6: +17 -6 lines
Ben Ward - some superficial structural changes allowing runs with no pfts
         - more significant structural and parameter changes to follow later

1 jahn 1.1 C $Name: $
2    
3     #include "CPP_OPTIONS.h"
4     #include "DARWIN_OPTIONS.h"
5    
6     #ifdef ALLOW_PTRACERS
7     #ifdef ALLOW_DARWIN
8     #ifdef ALLOW_QUOTA
9    
10     c ==========================================================
11     c SUBROUTINE QUOTA_INIT_VARI()
12     c initialize stuff for generalized quota plankton model
13     c adapted from NPZD2Fe - Mick Follows, Fall 2005
14     c modified - Stephanie Dutkiewicz, Spring 2006
15     c modified - Ben Ward, 2009/2010
16     c ==========================================================
17     c
18     SUBROUTINE QUOTA_INIT_VARI(myThid)
19    
20     IMPLICIT NONE
21    
22     #include "SIZE.h"
23     #include "GRID.h"
24     #include "DYNVARS.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "QUOTA_SIZE.h"
28     #include "QUOTA.h"
29     c#include "GCHEM.h"
30     #include "DARWIN_IO.h"
31    
32     C !INPUT PARAMETERS: ===================================================
33     C myThid :: thread number
34     INTEGER myThid
35    
36     C === Functions ===
37     _RL DARWIN_RANDOM
38     EXTERNAL DARWIN_RANDOM
39    
40     C !LOCAL VARIABLES:
41     C === Local variables ===
42     C msgBuf - Informational/error meesage buffer
43     CHARACTER*(MAX_LEN_MBUF) msgBuf
44     CHARACTER*(MAX_LEN_MBUF) char_str
45     INTEGER char_n
46     INTEGER IniUnit1, IniUnit2, IniUnit3, IniUnit4, IniUnit5
47    
48     INTEGER bi, bj, k, i, j, iPAR
49     INTEGER ii,io,jp,jp2,ko
50     _RL pday
51     c length of day (seconds)
52     pday = 86400.0 _d 0
53     CEOP
54    
55     WRITE(msgBuf,'(A)')
56     & '// ======================================================='
57     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
58     & SQUEEZE_RIGHT, myThid )
59     WRITE(msgBuf,'(A)') '// Quota init variables >>> START <<<'
60     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
61     & SQUEEZE_RIGHT, myThid )
62     WRITE(msgBuf,'(A)')
63     & '// ======================================================='
64     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65     & SQUEEZE_RIGHT, myThid )
66    
67     c test....................
68     c write(6,*)'testing in npzd2fe_init_vari '
69     c test....................
70    
71    
72     c set up ecosystem coefficients
73     c
74    
75     c initialize total number of functional groups tried
76     ngroups = 0
77     CALL quota_generate_phyto(MyThid)
78     c %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
79    
80     c %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
81     c %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
82     c write out initial plankton and organic matter characteristics
83     CALL MDSFINDUNIT( IniUnit1, mythid )
84     open(IniUnit1,file='plankton-ini-char.dat',status='unknown')
85     CALL MDSFINDUNIT( IniUnit2, mythid )
86     open(IniUnit2,file='plankton_ini_char_nohead.dat',
87     & status='unknown')
88     c-----------------------------------------------
89 benw 1.7 char_str=' bio_vol diameter qcarbon'
90     & //' biosink mortality'
91 jahn 1.1 & //' respiration autotrophy pp_opt'
92 benw 1.7 char_n=96
93 jahn 1.1 c loop elements
94     do ii=1,iimax
95     WRITE(msgBuf,'(I1)'),ii
96     char_str=char_str(1:char_n)//' vmaxi_'//msgBuf(1:1)
97     char_n=char_n+12
98     enddo
99     do ii=2,iimax ! skip carbon
100     WRITE(msgBuf,'(I1)'),ii
101     char_str=char_str(1:char_n)//' kn_'//msgBuf(1:1)
102     char_n=char_n+12
103     enddo
104     c loop quotas
105     do io=2,iomax-iChl ! skip carbon
106     WRITE(msgBuf,'(I1)'),io
107     char_str=char_str(1:char_n)//' qmin_'//msgBuf(1:1)
108     & //' qmax_'//msgBuf(1:1)
109     char_n=char_n+24
110     enddo
111     do io=1,iomax-iChl
112     WRITE(msgBuf,'(I1)'),io
113     if (io.eq.iCarb.or.io.eq.iNitr.or.io.eq.iPhos) then
114     char_str=char_str(1:char_n)//' excretn_'//msgBuf(1:1)
115     char_n=char_n+12
116     endif
117     char_str=char_str(1:char_n)//' beta_mort_'//msgBuf(1:1)
118     & //' beta_graz_'//msgBuf(1:1)
119     char_n=char_n+24
120     enddo
121     c
122     char_str=char_str(1:char_n)//' alphachl'
123     & //' maxgraz k_graz'
124     char_n=char_n+36
125 benw 1.7 #ifdef ALLOWPFT
126     char_str=char_str(1:char_n)//' PFT'
127     char_n=char_n+12
128     #endif
129 jahn 1.1 write(IniUnit1,'(A)'),char_str(1:char_n)
130     c-----------------------------------------------
131     do jp = 1, npmax
132 benw 1.7 write(msgBuf,120)biovol(jp),
133     & 2. _d 0 * (0.2387 _d 0 * biovol(jp)) ** 0.3333 _d 0,
134     & qcarbon(jp),
135     & biosink(jp)*pday,kmort(jp)*pday,
136 jahn 1.1 & respiration(jp)*pday,autotrophy(jp),pp_opt(jp)
137     char_str=msgBuf
138 benw 1.7 char_n=96
139 jahn 1.1 c loop elements
140     do ii=1,iimax
141     write(msgBuf,111)vmaxi(ii,jp)*pday
142     char_str=char_str(1:char_n)//msgBuf
143     char_n=char_n+12
144     enddo
145     do ii=2,iimax ! skip carbon
146     write(msgBuf,111)kn(ii,jp)
147     char_str=char_str(1:char_n)//msgBuf
148     char_n=char_n+12
149     enddo
150     c loop quotas
151     do io=2,iomax-iChl ! skip carbon
152     write(msgBuf,112)qmin(io,jp),qmax(io,jp)
153     char_str=char_str(1:char_n)//msgBuf
154     char_n=char_n+24
155     enddo
156     do io=1,iomax-iChl
157     if (io.eq.iCarb.or.io.eq.iNitr.or.io.eq.iPhos) then
158     write(msgBuf,111)kexc(io,jp)*pday
159     char_str=char_str(1:char_n)//msgBuf
160     char_n=char_n+12
161     endif
162     write(msgBuf,112)beta_mort(io,jp),beta_graz(io,jp)
163     char_str=char_str(1:char_n)//msgBuf
164     char_n=char_n+24
165     enddo
166     write(msgBuf,113)alphachl(jp),
167     & graz(jp)*pday,kg(jp)
168     char_str=char_str(1:char_n)//msgBuf
169     char_n=char_n+36
170 benw 1.7 #ifdef ALLOWPFT
171     write(msgBuf,111),float(pft(jp))
172     char_str=char_str(1:char_n)//msgBuf
173     char_n=char_n+12
174     #endif
175 jahn 1.1 c-----------------------------------------------
176     write(IniUnit1,'(A)')char_str(1:char_n)
177     write(IniUnit2,'(A)')char_str(1:char_n)
178     enddo
179     c<><><><><><><><><><><><><><><><><><><><><><><><><><>
180     close(IniUnit2)
181     close(IniUnit1)
182     c-----------------------------------------------
183     c write out grazing max rate and half sat matrices
184     CALL MDSFINDUNIT( IniUnit3, mythid )
185     open(IniUnit3,file='plankton-grazing.dat',status='unknown')
186     ! max ingestion rates
187     do jp=1,npmax
188     char_n=0
189     do jp2=1,npmax
190     write(msgBuf,'(e9.3)')graz(jp)*pday
191     char_str=char_str(1:char_n)//msgBuf(1:10)
192     char_n=char_n+10
193     enddo
194     write(IniUnit3,'(A)')char_str(1:char_n)
195     enddo
196     char_n=0
197     do jp2=1,npmax
198     char_str=char_str(1:char_n)//'----------'
199     char_n=char_n+10
200     enddo
201     write(IniUnit3,'(A)')char_str(1:char_n)
202     ! 1/2-saturations
203     do jp=1,npmax
204     char_n=0
205     do jp2=1,npmax
206     write(msgBuf,'(e9.3)')kg(jp)
207     char_str=char_str(1:char_n)//msgBuf(1:10)
208     char_n=char_n+10
209     enddo
210     write(IniUnit3,'(A)')char_str(1:char_n)
211     enddo
212     char_n=0
213     do jp2=1,npmax
214     char_str=char_str(1:char_n)//'----------'
215     char_n=char_n+10
216     enddo
217     write(IniUnit3,'(A)')char_str(1:char_n)
218     ! predator prey-preference
219     do jp=1,npmax
220     char_n=0
221     do jp2=1,npmax
222     write(msgBuf,'(e9.3)')graz_pref(jp,jp2)
223     char_str=char_str(1:char_n)//msgBuf(1:10)
224     char_n=char_n+10
225     enddo
226     write(IniUnit3,'(A)')char_str(1:char_n)
227     enddo
228     c<><><><><><><><><><><><><><><><><><><><><><><><><><>
229     close(IniUnit3)
230     c-----------------------------------------------
231     c write out organic matter remineralisation rates
232 jahn 1.4 CALL MDSFINDUNIT( IniUnit4, mythid )
233 jahn 1.1 open(IniUnit4,file='plankton-orgmat.dat',status='unknown')
234     ! DOM remineralisation rates
235     char_n=0
236     do io=1,iomax-iChl
237     if (io.ne.iSili) then
238     write(msgBuf,'(e9.3)')remin(io,1)*pday
239     char_str=char_str(1:char_n)//msgBuf(1:10)
240     endif
241     char_n=char_n+10
242     enddo
243     write(IniUnit4,'(A)')char_str(1:char_n)
244     ! POM remineralisation rates
245     char_n=0
246     do io=1,iomax-iChl
247     write(msgBuf,'(e9.3)')remin(io,2)*pday
248     char_str=char_str(1:char_n)//msgBuf(1:10)
249     char_n=char_n+10
250     enddo
251     write(IniUnit4,'(A)')char_str(1:char_n)
252     c<><><><><><><><><><><><><><><><><><><><><><><><><><>
253     close(IniUnit4)
254     c-----------------------------------------------
255     111 format(1e12.4)
256     112 format(2e12.4)
257     113 format(3e12.4)
258     114 format(4e12.4)
259     115 format(5e12.4)
260     116 format(6e12.4)
261     118 format(8e12.4)
262     120 format(10e12.4)
263     c %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
264     c %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
265     CALL LEF_ZERO( inputFe,myThid )
266     CALL LEF_ZERO( sur_par,myThid )
267     #ifdef NUT_SUPPLY
268     DO bj = myByLo(myThid), myByHi(myThid)
269     DO bi = myBxLo(myThid), myBxHi(myThid)
270     DO j=1-Oly,sNy+Oly
271     DO i=1-Olx,sNx+Olx
272     DO k=1,nR
273     nut_wvel(i,j,k,bi,bj) = 0. _d 0
274     ENDDO
275     ENDDO
276     ENDDO
277     ENDDO
278     ENDDO
279     #endif
280    
281     #ifdef ALLOW_PAR_DAY
282     DO iPAR=1,2
283     DO bj=myByLo(myThid), myByHi(myThid)
284     DO bi=myBxLo(myThid), myBxHi(myThid)
285     DO k=1,nR
286     DO j=1-Oly,sNy+Oly
287     DO i=1-Olx,sNx+Olx
288     PARday(i,j,k,bi,bj,iPAR) = 0. _d 0
289     ENDDO
290     ENDDO
291     ENDDO
292     ENDDO
293     ENDDO
294     ENDDO
295     IF ( .NOT. ( startTime .EQ. baseTime .AND. nIter0 .EQ. 0
296     & .AND. pickupSuff .EQ. ' ') ) THEN
297     COJ should probably initialize from a file when nIter0 .EQ. 0
298     CALL DARWIN_READ_PICKUP( nIter0, myThid )
299     ENDIF
300     #endif
301     c
302     #ifdef ALLOW_TIMEAVE
303     c set arrays to zero if first timestep
304     DO bj = myByLo(myThid), myByHi(myThid)
305     DO bi = myBxLo(myThid), myBxHi(myThid)
306     CALL TIMEAVE_RESET(PARave, Nr, bi, bj, myThid)
307     CALL TIMEAVE_RESET(PPave, Nr, bi, bj, myThid)
308     c CALL TIMEAVE_RESET(SURave, 1, bi, bj, myThid)
309     WRITE(msgbuf,'(A)')
310     & 'QQ start timeave'
311     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
312     & SQUEEZE_RIGHT , mythid)
313    
314 jahn 1.6 DAR_TimeAve(bi,bj) = 0. _d 0
315 jahn 1.1 ENDDO
316     ENDDO
317     #endif /* ALLOW_TIMEAVE */
318    
319     #ifdef CHECK_CONS
320     coj find unused units for darwin_cons output
321 jahn 1.5 CALL MDSFINDUNIT( DAR_cons_unitC, mythid )
322     open(DAR_cons_unitC,file='darwin_cons_C.txt',status='unknown')
323     CALL MDSFINDUNIT( DAR_cons_unitN, mythid )
324     open(DAR_cons_unitN,file='darwin_cons_N.txt',status='unknown')
325     #ifdef PQUOTA
326     CALL MDSFINDUNIT( DAR_cons_unitP, mythid )
327     open(DAR_cons_unitP,file='darwin_cons_P.txt',status='unknown')
328     #endif
329     #ifdef FQUOTA
330     CALL MDSFINDUNIT( DAR_cons_unitF, mythid )
331     open(DAR_cons_unitF,file='darwin_cons_Fe.txt',status='unknown')
332     #endif
333     #ifdef SQUOTA
334     CALL MDSFINDUNIT( DAR_cons_unitS, mythid )
335     open(DAR_cons_unitS,file='darwin_cons_Si.txt',status='unknown')
336     #endif
337 jahn 1.1 #endif
338    
339     c test....................
340     c write(6,*)'finishing darwin_init_vari '
341     c test....................
342     WRITE(msgBuf,'(A)')
343     & '// ======================================================='
344     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
345     & SQUEEZE_RIGHT, myThid )
346     WRITE(msgBuf,'(A)') '// Darwin init variables >>> END <<<'
347     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
348     & SQUEEZE_RIGHT, myThid )
349     WRITE(msgBuf,'(A)')
350     & '// ======================================================='
351     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
352     & SQUEEZE_RIGHT, myThid )
353    
354     RETURN
355     END
356     #endif /*ALLOW_QUOTA*/
357     #endif /*ALLOW_DARWIN*/
358     #endif /*ALLOW_PTRACERS*/
359     c ==========================================================
360    

  ViewVC Help
Powered by ViewVC 1.1.22