/[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.4 - (hide annotations) (download)
Tue Nov 28 15:45:22 2017 UTC (7 years, 7 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt66n_20180118, ctrb_darwin2_ckpt66o_20180209, ctrb_darwin2_ckpt66m_20171213, HEAD
Changes since 1.3: +2 -2 lines
fix bug in monod_generate_zoo: ExGrazFracSmall and ExGrazFracBig were swapped

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 stephd 1.2 mortzoo2(nz) = ZoomortSmall2
94 jahn 1.1 else
95     ExportFracZ(nz) = ZooexfacBig
96     mortzoo(nz) = ZoomortBig
97 stephd 1.2 mortzoo2(nz) = ZoomortBig2
98 jahn 1.1 endif
99     end do
100     #endif
101    
102    
103     #ifndef OLD_GRAZE
104     c for zooplankton
105     c assume zoo(1) = small, zoo(2) = big
106     zoosize(1) = 0.0 _d 0
107     zoosize(2) = 1.0 _d 0
108     grazemax(1) = GrazeFast
109     grazemax(2) = GrazeFast
110     ExportFracZ(1)=ZooexfacSmall
111     ExportFracZ(2)=ZooexfacBig
112     mortzoo(1) = ZoomortSmall
113     mortzoo(2) = ZoomortBig
114 stephd 1.2 mortzoo2(1) = ZoomortSmall2
115     mortzoo2(2) = ZoomortBig2
116 jahn 1.4 ExportFracGraz(1)=ExGrazFracSmall
117     ExportFracGraz(2)=ExGrazFracBig
118 jahn 1.1 IF ( nzmax.GT.2 ) THEN
119     WRITE(msgBuf,'(2A,I5)') 'MONOD_GENERATE_ZOO: ',
120     & 'nzmax = ', nzmax
121     CALL PRINT_ERROR( msgBuf , 1)
122     WRITE(msgBuf,'(2A)') 'MONOD_GENERATE_ZOO: ',
123     & 'please provide size info for nz > 2'
124     CALL PRINT_ERROR( msgBuf , 1)
125     STOP 'ABNORMAL END: S/R MONOD_GENERATE_ZOO'
126     ENDIF
127     c
128     do nz=1,nzmax
129     c size of phytoplankton
130     if(zoosize(nz).eq. 1.0 _d 0)then
131     dm = 300. _d 0 ! diameter (micrometer)
132     else
133     dm = 30. _d 0 ! diameter (micrometer)
134     end if
135     c phytoplankton volume in micrometers cubed
136     volp=4. _d 0/3. _d 0 *PI*(dm/2. _d 0)**3 _d 0
137     c
138     c common block variables (in m and m3)
139     zoo_esd(nz)=dm* 1. _d -6
140     zoo_vol(nz)=volp* 1. _d -18
141 jahn 1.3 #ifdef FIX_ZOO_QUOTAS
142     R_NP_zoo(nz)=val_R_NP_zoo
143     R_FeP_zoo(nz)=val_RFeP_zoo
144     R_SiP_zoo(nz)=val_R_SiP_zoo
145     R_PC_zoo(nz)=val_R_PC_zoo
146     #endif
147 jahn 1.1 c palatibity according to "allometry"
148     c big grazers preferentially eat big phyto etc...
149     do np=1,npmax
150     if (zoosize(nz).eq.physize(np)) then
151     palat(np,nz)=palathi
152     asseff(np,nz)=GrazeEffmod
153     else
154     palat(np,nz)=palatlo
155     if (physize(np).eq.0. _d 0) then
156     asseff(np,nz)=GrazeEffhi
157     else
158     asseff(np,nz)=GrazeEfflow
159     endif
160     endif
161     c diatoms even less palatible
162     if (diacoc(np).eq.1. _d 0) then
163     palat(np,nz)= palat(np,nz)*diatomgraz
164     endif
165     c coccolithophes less palatible
166     if (diacoc(np).eq.2. _d 0) then
167     palat(np,nz)= palat(np,nz)*coccograz
168     endif
169     c other large phyto less palatible
170     if (diacoc(np).eq.0. _d 0 .and.physize(np).eq.1. _d 0) then
171     palat(np,nz)= palat(np,nz)*olargegraz
172     endif
173     c need something in here for tricho
174     enddo
175     enddo
176     #endif
177    
178     RETURN
179     END
180     #endif /*MONOD*/
181     #endif /*ALLOW_PTRACERS*/
182    
183     c ===========================================================

  ViewVC Help
Powered by ViewVC 1.1.22