/[MITgcm]/MITgcm_contrib/darwin2/pkg/monod/monod_generate_zoo.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/monod/monod_generate_zoo.F

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


Revision 1.1 - (hide annotations) (download)
Wed Apr 13 18:56:25 2011 UTC (14 years, 3 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt62v_20110413, ctrb_darwin2_ckpt62y_20110526, ctrb_darwin2_ckpt62x_20110513, ctrb_darwin2_ckpt62w_20110426, ctrb_darwin2_ckpt63c_20111011, ctrb_darwin2_ckpt63b_20110830, ctrb_darwin2_ckpt63a_20110804, ctrb_darwin2_ckpt63_20110728, ctrb_darwin2_baseline, ctrb_darwin2_ckpt62z_20110622
darwin2 initial checkin

1 jahn 1.1 #include "CPP_OPTIONS.h"
2     #include "PTRACERS_OPTIONS.h"
3     #include "DARWIN_OPTIONS.h"
4    
5     #ifdef ALLOW_PTRACERS
6     #ifdef ALLOW_MONOD
7    
8     c ==========================================================
9     c SUBROUTINE MONOD_GENERATE_ZOO
10     c generate parameters for zooplankton
11     c initial simple 2 species setup
12     c Stephanie Dutkiewicz Spring 2009
13     c ==========================================================
14     SUBROUTINE MONOD_GENERATE_ZOO(myThid)
15    
16     implicit none
17     #include "EEPARAMS.h"
18     #include "MONOD_SIZE.h"
19     #include "DARWIN_PARAMS.h"
20     #include "MONOD.h"
21    
22    
23    
24     C !INPUT PARAMETERS: ===================================================
25     C myThid :: thread number
26     INTEGER myThid
27    
28     C === Functions ===
29     _RL DARWIN_RANDOM
30     EXTERNAL DARWIN_RANDOM
31     _RL DARWIN_RANDOM_NORMAL
32     EXTERNAL DARWIN_RANDOM_NORMAL
33    
34     C !LOCAL VARIABLES:
35     C === Local variables ===
36     C msgBuf - Informational/error meesage buffer
37     CHARACTER*(MAX_LEN_MBUF) msgBuf
38    
39     _RL dm
40     _RL volp
41     _RL PI
42     INTEGER np
43     INTEGER nz
44     INTEGER signvar
45     PARAMETER ( PI = 3.14159265358979323844D0 )
46    
47     CEOP
48     c
49    
50     #ifdef OLD_GRAZE
51     c for zooplankton
52     c assume zoo(1) = small, zoo(2) = big
53     c then grazing efficiency according to size
54     zoosize(1) = 0.0 _d 0
55     zoosize(2) = 1.0 _d 0
56     IF ( nzmax.GT.2 ) THEN
57     WRITE(msgBuf,'(2A,I5)') 'MONOD_GENERATE_ZOO: ',
58     & 'nzmax = ', nzmax
59     CALL PRINT_ERROR( msgBuf , 1)
60     WRITE(msgBuf,'(2A)') 'MONOD_GENERATE_ZOO: ',
61     & 'please provide size info for nz > 2'
62     CALL PRINT_ERROR( msgBuf , 1)
63     STOP 'ABNORMAL END: S/R MONOD_GENERATE_ZOO'
64     ENDIF
65    
66     c grazing rates according to "allometry"
67     c big grazers preferentially eat big phyto etc...
68     do np=1,npmax
69     do nz=1,nzmax
70     if(zoosize(nz) .eq. physize(np))then
71     graze(np,nz) = GrazeFast
72     else
73     graze(np,nz) = GrazeSlow
74     end if
75     if (diacoc(np).eq.1) then
76     graze(np,nz)= graze(np,nz)*diatomgraz
77     endif
78     if (diacoc(np).eq.2) then
79     graze(np,nz)= graze(np,nz)*coccograz
80     endif
81     if (diacoc(np).eq.0.and.physize(np).eq.1) then
82     graze(np,nz)= graze(np,nz)*olargegraz
83     endif
84     end do
85     end do
86    
87     c zooplankton export/mortality
88     c small zooplankton (zoosize = 0.) lower export fraction
89     do nz = 1, nzmax
90     if(zoosize(nz) .eq. 0.0)then
91     ExportFracZ(nz) = ZooexfacSmall
92     mortzoo(nz) = ZoomortSmall
93     else
94     ExportFracZ(nz) = ZooexfacBig
95     mortzoo(nz) = ZoomortBig
96     endif
97     end do
98     #endif
99    
100    
101     #ifndef OLD_GRAZE
102     c for zooplankton
103     c assume zoo(1) = small, zoo(2) = big
104     zoosize(1) = 0.0 _d 0
105     zoosize(2) = 1.0 _d 0
106     grazemax(1) = GrazeFast
107     grazemax(2) = GrazeFast
108     ExportFracZ(1)=ZooexfacSmall
109     ExportFracZ(2)=ZooexfacBig
110     mortzoo(1) = ZoomortSmall
111     mortzoo(2) = ZoomortBig
112     ExportFracGraz(1)=ExGrazFracbig
113     ExportFracGraz(2)=ExGrazFracsmall
114     IF ( nzmax.GT.2 ) THEN
115     WRITE(msgBuf,'(2A,I5)') 'MONOD_GENERATE_ZOO: ',
116     & 'nzmax = ', nzmax
117     CALL PRINT_ERROR( msgBuf , 1)
118     WRITE(msgBuf,'(2A)') 'MONOD_GENERATE_ZOO: ',
119     & 'please provide size info for nz > 2'
120     CALL PRINT_ERROR( msgBuf , 1)
121     STOP 'ABNORMAL END: S/R MONOD_GENERATE_ZOO'
122     ENDIF
123     c
124     do nz=1,nzmax
125     c size of phytoplankton
126     if(zoosize(nz).eq. 1.0 _d 0)then
127     dm = 300. _d 0 ! diameter (micrometer)
128     else
129     dm = 30. _d 0 ! diameter (micrometer)
130     end if
131     c phytoplankton volume in micrometers cubed
132     volp=4. _d 0/3. _d 0 *PI*(dm/2. _d 0)**3 _d 0
133     c
134     c common block variables (in m and m3)
135     zoo_esd(nz)=dm* 1. _d -6
136     zoo_vol(nz)=volp* 1. _d -18
137     c palatibity according to "allometry"
138     c big grazers preferentially eat big phyto etc...
139     do np=1,npmax
140     if (zoosize(nz).eq.physize(np)) then
141     palat(np,nz)=palathi
142     asseff(np,nz)=GrazeEffmod
143     else
144     palat(np,nz)=palatlo
145     if (physize(np).eq.0. _d 0) then
146     asseff(np,nz)=GrazeEffhi
147     else
148     asseff(np,nz)=GrazeEfflow
149     endif
150     endif
151     c diatoms even less palatible
152     if (diacoc(np).eq.1. _d 0) then
153     palat(np,nz)= palat(np,nz)*diatomgraz
154     endif
155     c coccolithophes less palatible
156     if (diacoc(np).eq.2. _d 0) then
157     palat(np,nz)= palat(np,nz)*coccograz
158     endif
159     c other large phyto less palatible
160     if (diacoc(np).eq.0. _d 0 .and.physize(np).eq.1. _d 0) then
161     palat(np,nz)= palat(np,nz)*olargegraz
162     endif
163     c need something in here for tricho
164     enddo
165     enddo
166     #endif
167    
168     RETURN
169     END
170     #endif /*MONOD*/
171     #endif /*ALLOW_PTRACERS*/
172    
173     c ===========================================================

  ViewVC Help
Powered by ViewVC 1.1.22