1 | MODULE sedsol |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE sedsol *** |
---|
4 | !! Sediment : dissolution and reaction in pore water related |
---|
5 | !! related to organic matter |
---|
6 | !! Diffusion of solutes in pore water |
---|
7 | !!===================================================================== |
---|
8 | !! * Modules used |
---|
9 | USE sed ! sediment global variable |
---|
10 | USE sedini |
---|
11 | USE sedfunc |
---|
12 | USE seddsr |
---|
13 | USE sedjac |
---|
14 | USE sedbtb |
---|
15 | USE sedco3 |
---|
16 | USE sedmat |
---|
17 | # if ! defined key_agrif |
---|
18 | USE trosk |
---|
19 | #endif |
---|
20 | USE lib_mpp ! distribued memory computing library |
---|
21 | USE lib_fortran |
---|
22 | |
---|
23 | IMPLICIT NONE |
---|
24 | PRIVATE |
---|
25 | |
---|
26 | PUBLIC sed_sol |
---|
27 | |
---|
28 | !! $Id: sedsol.F90 5215 2015-04-15 16:11:56Z nicolasmartin $ |
---|
29 | CONTAINS |
---|
30 | |
---|
31 | SUBROUTINE sed_sol( kt ) |
---|
32 | !!---------------------------------------------------------------------- |
---|
33 | !! *** ROUTINE sed_sol *** |
---|
34 | !! |
---|
35 | !! ** Purpose : computes pore water diffusion and reactions |
---|
36 | !! |
---|
37 | !! ** Methode : Computation of the redox and dissolution reactions |
---|
38 | !! in the sediment. |
---|
39 | !! The main redox reactions are solved in sed_dsr whereas |
---|
40 | !! the secondary reactions are solved in sed_dsr_redoxb. |
---|
41 | !! Inorganic dissolution is solved in sed_inorg |
---|
42 | !! A strand spliting approach is being used here (see |
---|
43 | !! sed_dsr_redoxb for more information). |
---|
44 | !! Diffusive fluxes are computed in sed_diff |
---|
45 | !! |
---|
46 | !! History : |
---|
47 | !! ! 98-08 (E. Maier-Reimer, Christoph Heinze ) Original code |
---|
48 | !! ! 04-10 (N. Emprin, M. Gehlen ) f90 |
---|
49 | !! ! 06-04 (C. Ethe) Re-organization |
---|
50 | !! ! 19-08 (O. Aumont) Debugging and improvement of the model. |
---|
51 | !! The original method is replaced by a |
---|
52 | !! Strand splitting method which deals |
---|
53 | !! well with stiff reactions. |
---|
54 | !!---------------------------------------------------------------------- |
---|
55 | !! Arguments |
---|
56 | INTEGER, INTENT(in) :: kt |
---|
57 | ! --- local variables |
---|
58 | INTEGER :: ji, jk, js, jw, jn, neq ! dummy looop indices |
---|
59 | REAL(wp), DIMENSION(jpoce,jpksed) :: preac |
---|
60 | # if ! defined key_agrif |
---|
61 | REAL(wp), DIMENSION( jpvode * jpksed ) :: zxin |
---|
62 | INTEGER :: JINDEX, ITOL, IJAC, MLJAC, IMAX |
---|
63 | INTEGER :: MUJAC,LE1, LJAC, LIWORK, LWORK |
---|
64 | INTEGER :: IDID, NMAXSTP, ROSM |
---|
65 | REAL(wp) :: X, XEND, H, STEPMIN |
---|
66 | REAL(wp), DIMENSION(1) :: RTOL, ATOL |
---|
67 | REAL(wp), POINTER :: WORK(:) |
---|
68 | INTEGER , POINTER :: IWORK(:) |
---|
69 | INTEGER, DIMENSION(3) :: ISTAT |
---|
70 | REAL(wp), DIMENSION(2) :: RSTAT |
---|
71 | #endif |
---|
72 | !! |
---|
73 | !!---------------------------------------------------------------------- |
---|
74 | |
---|
75 | IF( ln_timing ) CALL timing_start('sed_sol') |
---|
76 | ! |
---|
77 | IF( kt == nitsed000 ) THEN |
---|
78 | IF (lwp) THEN |
---|
79 | WRITE(numsed,*) ' sed_sol : Organic/inorganic degradation related reactions and diffusion' |
---|
80 | WRITE(numsed,*) ' ' |
---|
81 | ENDIF |
---|
82 | ! ! |
---|
83 | dens_mol_wgt(1:jpsol) = denssol / mol_wgt(1:jpsol) |
---|
84 | stepros(:) = dtsed |
---|
85 | ! |
---|
86 | ENDIF |
---|
87 | |
---|
88 | ! 1. Change of geometry |
---|
89 | ! Increase of dz3d(2) thickness : dz3d(2) = dz3d(2)+dzdep |
---|
90 | ! Warning : no change for dz(2) |
---|
91 | !--------------------------------------------------------- |
---|
92 | dz3d(1:jpoce,2) = dz3d(1:jpoce,2) + dzdep(1:jpoce) |
---|
93 | |
---|
94 | ! New values for volw3d(:,2) and vols3d(:,2) |
---|
95 | ! Warning : no change neither for volw(2) nor vols(2) |
---|
96 | !------------------------------------------------------ |
---|
97 | volw3d(1:jpoce,2) = dz3d(1:jpoce,2) * por(2) |
---|
98 | vols3d(1:jpoce,2) = dz3d(1:jpoce,2) * por1(2) |
---|
99 | |
---|
100 | ! 2. Change of previous solid fractions (due to volum changes) for k=2 |
---|
101 | !--------------------------------------------------------------------- |
---|
102 | DO js = 1, jpsol |
---|
103 | solcp(:,2,js) = solcp(:,2,js) * dz(2) / dz3d(:,2) |
---|
104 | END DO |
---|
105 | |
---|
106 | ! 3. New solid fractions (including solid rain fractions) for k=2 |
---|
107 | !------------------------------------------------------------------ |
---|
108 | DO js = 1, jpsol |
---|
109 | DO ji = 1, jpoce |
---|
110 | IF (raintg(ji) .ne. 0) THEN |
---|
111 | solcp(ji,2,js) = solcp(ji,2,js) + & |
---|
112 | & ( rainrg(ji,js) / raintg(ji) ) * ( dzdep(ji) / dz3d(ji,2) ) |
---|
113 | ! rainrm are temporary cancel |
---|
114 | rainrm(ji,js) = 0. |
---|
115 | ENDIF |
---|
116 | END DO |
---|
117 | ENDDO |
---|
118 | |
---|
119 | ! 4. Adjustment of bottom water concen.(pwcp(1)): |
---|
120 | ! We impose that pwcp(2) is constant. Including dzdep in dz3d(:,2) we assume |
---|
121 | ! that dzdep has got a porosity of por(2). So pore water volum of jk=2 increase. |
---|
122 | ! To keep pwcp(2) cste we must compensate this "increase" by a slight adjusment |
---|
123 | ! of bottom water concentration. |
---|
124 | ! This adjustment is compensate at the end of routine |
---|
125 | !------------------------------------------------------------- |
---|
126 | DO jw = 1, jpwat |
---|
127 | pwcp(:,1,jw) = pwcp(:,1,jw) - pwcp(:,2,jw) * dzdep(:) * por(2) / dzkbot(:) |
---|
128 | ENDDO |
---|
129 | |
---|
130 | ! -------------------------------------------------- |
---|
131 | ! Computation of the diffusivities |
---|
132 | ! -------------------------------------------------- |
---|
133 | DO js = 1, jpwat |
---|
134 | DO jk = 1, jpksed |
---|
135 | diff(:,jk,js) = ( diff1(js) + diff2(js) * temp(:) ) / ( 1.0 - 2.0 * log( por(jk) ) ) |
---|
136 | END DO |
---|
137 | END DO |
---|
138 | |
---|
139 | ! Impact of bioirrigation and adsorption on diffusion |
---|
140 | ! --------------------------------------------------- |
---|
141 | diff(:,:,jwsil) = diff(:,:,jwsil) * ( 1.0 + irrig(:,:) ) |
---|
142 | diff(:,:,jwoxy) = diff(:,:,jwoxy) * ( 1.0 + irrig(:,:) ) |
---|
143 | diff(:,:,jwdic) = diff(:,:,jwdic) * ( 1.0 + irrig(:,:) ) |
---|
144 | diff(:,:,jwno3) = diff(:,:,jwno3) * ( 1.0 + irrig(:,:) ) |
---|
145 | diff(:,:,jwpo4) = diff(:,:,jwpo4) * ( 1.0 + irrig(:,:) ) |
---|
146 | diff(:,:,jwalk) = diff(:,:,jwalk) * ( 1.0 + irrig(:,:) ) |
---|
147 | diff(:,:,jwh2s) = diff(:,:,jwh2s) * ( 1.0 + irrig(:,:) ) |
---|
148 | diff(:,:,jwso4) = diff(:,:,jwso4) * ( 1.0 + irrig(:,:) ) |
---|
149 | diff(:,:,jwlgw) = diff(:,:,jwlgw) * ( 1.0 + irrig(:,:) ) |
---|
150 | DO jk = 1, jpksed |
---|
151 | diff(:,jk,jwfe2) = diff(:,jk,jwfe2) * ( 1.0 + 0.1 * irrig(:,jk) ) * radsfe2(jk) |
---|
152 | diff(:,jk,jwnh4) = diff(:,jk,jwnh4) * ( 1.0 + irrig(:,jk) ) * radsnh4(jk) |
---|
153 | END DO |
---|
154 | |
---|
155 | ! Conversion of volume units |
---|
156 | !---------------------------- |
---|
157 | DO js = 1, jpsol |
---|
158 | DO jk = 1, jpksed |
---|
159 | volc(:,jk,js) = ( vols3d(:,jk) * dens_mol_wgt(js) ) / & |
---|
160 | & ( volw3d(:,jk) * 1.e-3 ) |
---|
161 | ENDDO |
---|
162 | ENDDO |
---|
163 | |
---|
164 | ! Apply bioturbation and compute the impact of the slow SMS on species |
---|
165 | CALL sed_btb( kt ) |
---|
166 | ! Recompute pH after bioturbation and slow chemistry |
---|
167 | CALL sed_co3( kt ) |
---|
168 | # if ! defined key_agrif |
---|
169 | ! The following part deals with the stiff ODEs |
---|
170 | ! This is the expensive part of the code and should be carefully |
---|
171 | ! chosen. We use the DVODE solver after many trials to find a cheap |
---|
172 | ! way to solve the ODEs. This is not necessarily the most efficient |
---|
173 | ! but this is the one that was not too much of a pain to code and that |
---|
174 | ! was the most precise and quick. |
---|
175 | ! The ones I tried : operator splitting (Strang), hybrid spectral methods |
---|
176 | ! Brent, Powell's hybrid method, ... |
---|
177 | ! --------------------------------------------------------------------- |
---|
178 | ROSM = 2 |
---|
179 | NEQ = jpvode * jpksed |
---|
180 | XEND = dtsed |
---|
181 | RTOL = 0.005 |
---|
182 | ATOL = 0.005 |
---|
183 | ITOL = 0 |
---|
184 | IJAC = 1 |
---|
185 | MLJAC = jpvode |
---|
186 | MUJAC = jpvode |
---|
187 | LE1 = 2*MLJAC+MUJAC+1 |
---|
188 | LJAC = MLJAC+MUJAC+1 |
---|
189 | LIWORK = NEQ + 2 |
---|
190 | LWORK = NEQ*(LJAC+LE1+8) + 5 |
---|
191 | ALLOCATE(WORK(LWORK), IWORK(LIWORK) ) |
---|
192 | NMAXSTP = 0 |
---|
193 | STEPMIN = dtsed |
---|
194 | |
---|
195 | DO ji = 1, jpoce |
---|
196 | X = 0.0 |
---|
197 | H = stepros(ji) |
---|
198 | WORK = 0. |
---|
199 | IWORK = 0 |
---|
200 | IWORK(2) = 6 |
---|
201 | |
---|
202 | ! Put all the species in one local array (nb of tracers * vertical |
---|
203 | ! dimension |
---|
204 | jindex = ji |
---|
205 | DO jn = 1, NEQ |
---|
206 | jk = jarr(jn,1) |
---|
207 | js = jarr(jn,2) |
---|
208 | IF (js <= jpwat) THEN |
---|
209 | zxin(jn) = pwcp(ji,jk,js) * 1E6 |
---|
210 | ELSE |
---|
211 | zxin(jn) = solcp(ji,jk,js-jpwat) * 1E6 |
---|
212 | ENDIF |
---|
213 | END DO |
---|
214 | |
---|
215 | ! Set options for VODE : banded matrix. SParse option is much more |
---|
216 | ! expensive except if one computes the sparse Jacobian explicitly |
---|
217 | ! To speed up the computation, one way is to reduce ATOL and RTOL |
---|
218 | ! which may be a good option at the beginning of the simulations |
---|
219 | ! during the spin up |
---|
220 | ! ---------------------------------------------------------------- |
---|
221 | CALL ROSK(ROSM, NEQ,JINDEX,X,zxin,XEND,H, & |
---|
222 | RTOL,ATOL,ITOL, sed_jac,IJAC,MLJAC,MUJAC, & |
---|
223 | WORK,LWORK,IWORK,LIWORK,IDID,ISTAT,RSTAT) |
---|
224 | |
---|
225 | DO jn = 1, NEQ |
---|
226 | jk = jarr(jn,1) |
---|
227 | js = jarr(jn,2) |
---|
228 | IF (js <= jpwat) THEN |
---|
229 | pwcp(ji,jk,js) = zxin(jn) * 1E-6 |
---|
230 | ELSE |
---|
231 | solcp(ji,jk,js-jpwat) = zxin(jn) * 1E-6 |
---|
232 | ENDIF |
---|
233 | END DO |
---|
234 | NMAXSTP = MAX(NMAXSTP,ISTAT(3)) |
---|
235 | STEPMIN = MIN(STEPMIN, RSTAT(1) ) |
---|
236 | stepros(ji) = RSTAT(1) |
---|
237 | END DO |
---|
238 | |
---|
239 | DEALLOCATE(WORK, IWORK) |
---|
240 | #endif |
---|
241 | |
---|
242 | preac(:,:) = 0. |
---|
243 | CALL sed_mat_dsri( jwalk, preac, pwcpa(:,:,jwalk), dtsed ) |
---|
244 | CALL sed_mat_dsri( jwpo4, preac, pwcpa(:,:,jwpo4), dtsed ) |
---|
245 | |
---|
246 | !---------------------------------- |
---|
247 | ! Back to initial geometry |
---|
248 | !----------------------------- |
---|
249 | |
---|
250 | !--------------------------------------------------------------------- |
---|
251 | ! 1/ Compensation for ajustement of the bottom water concentrations |
---|
252 | ! (see note n� 1 about *por(2)) |
---|
253 | !-------------------------------------------------------------------- |
---|
254 | DO jw = 1, jpwat |
---|
255 | pwcp(:,1,jw) = pwcp(:,1,jw) + pwcp(:,2,jw) * dzdep(:) * por(2) / dzkbot(:) |
---|
256 | ENDDO |
---|
257 | |
---|
258 | !----------------------------------------------------------------------- |
---|
259 | ! 2/ Det of new rainrg taking account of the new weight fraction |
---|
260 | ! obtained |
---|
261 | ! in dz3d(2) after diffusion/reaction (react/diffu are also in |
---|
262 | ! dzdep!) |
---|
263 | ! This new rain (rgntg rm) will be used in advection/burial routine |
---|
264 | !------------------------------------------------------------------------ |
---|
265 | DO js = 1, jpsol |
---|
266 | rainrg(:,js) = raintg(:) * solcp(:,2,js) |
---|
267 | rainrm(:,js) = rainrg(:,js) / mol_wgt(js) |
---|
268 | ENDDO |
---|
269 | |
---|
270 | ! New raintg |
---|
271 | raintg(:) = 0. |
---|
272 | DO js = 1, jpsol |
---|
273 | raintg(:) = raintg(:) + rainrg(:,js) |
---|
274 | ENDDO |
---|
275 | |
---|
276 | !-------------------------------- |
---|
277 | ! 3/ back to initial geometry |
---|
278 | !-------------------------------- |
---|
279 | dz3d (:,2) = dz(2) |
---|
280 | volw3d(:,2) = dz3d(:,2) * por(2) |
---|
281 | vols3d(:,2) = dz3d(:,2) * por1(2) |
---|
282 | |
---|
283 | IF( ln_timing ) CALL timing_stop('sed_sol') |
---|
284 | ! |
---|
285 | END SUBROUTINE sed_sol |
---|
286 | |
---|
287 | END MODULE sedsol |
---|