New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
sedorg.F90 in NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/SED/sedorg.F90 @ 10345

Last change on this file since 10345 was 10345, checked in by smasson, 5 years ago

dev_r10164_HPC09_ESIWACE_PREP_MERGE: merge with trunk@10344, see #2133

File size: 6.1 KB
Line 
1MODULE sedorg
2   !!======================================================================
3   !!              ***  MODULE  seddsr  ***
4   !!    Sediment : dissolution and reaction in pore water related
5   !!    related to organic matter
6   !!=====================================================================
7   !! * Modules used
8   USE sed     ! sediment global variable
9   USE sed_oce
10   USE sedini
11   USE seddiff
12   USE seddsr
13   USE lib_mpp         ! distribued memory computing library
14   USE lib_fortran
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC sed_org
20
21   !! * Module variables
22
23   REAL(wp) :: zadsnh4
24
25   !! $Id: seddsr.F90 5215 2015-04-15 16:11:56Z nicolasmartin $
26CONTAINS
27   
28   SUBROUTINE sed_org( kt ) 
29      !!----------------------------------------------------------------------
30      !!                   ***  ROUTINE sed_org  ***
31      !!
32      !!  ** Purpose :  computes pore water diffusion and reaction
33      !!
34      !!  ** Methode :  Computation of the redox reactions in sediment.
35      !!                The main redox reactions are solved in sed_dsr whereas
36      !!                the secondary reactions are solved in sed_dsr_redoxb.
37      !!                A strand spliting approach is being used here (see
38      !!                sed_dsr_redoxb for more information).
39      !!                Diffusive fluxes are computed in sed_diff
40      !!
41      !!   History :
42      !!        !  98-08 (E. Maier-Reimer, Christoph Heinze )  Original code
43      !!        !  04-10 (N. Emprin, M. Gehlen ) f90
44      !!        !  06-04 (C. Ethe)  Re-organization
45      !!        !  19-08 (O. Aumont) Debugging and improvement of the model.
46      !!                             The original method is replaced by a
47      !!                             Strand splitting method which deals
48      !!                             well with stiff reactions.
49      !!----------------------------------------------------------------------
50      !! Arguments
51      INTEGER, INTENT(in) ::   kt
52      ! --- local variables
53      INTEGER  :: ji, jk, js, jw, jnt   ! dummy looop indices
54      REAL(wp) :: zadsnh4
55      !!
56      !!----------------------------------------------------------------------
57
58      IF( ln_timing )  CALL timing_start('sed_org')
59!
60      IF( kt == nitsed000 ) THEN
61         IF (lwp) THEN
62            WRITE(numsed,*) ' sed_org : Organic degradation related reactions and diffusion'
63            WRITE(numsed,*) ' '
64         ENDIF
65!         !
66         dens_mol_wgt(1:jpsol) = denssol / mol_wgt(1:jpsol)
67         !
68      ENDIF
69
70      dtsed2 = dtsed / REAL( nrseddt, wp )
71
72      ! 1. Change of geometry
73      !    Increase of dz3d(2) thickness : dz3d(2) = dz3d(2)+dzdep
74      !    Warning : no change for dz(2)
75      !---------------------------------------------------------
76      dz3d(1:jpoce,2) = dz3d(1:jpoce,2) + dzdep(1:jpoce)
77
78      ! New values for volw3d(:,2) and vols3d(:,2)
79      ! Warning : no change neither for volw(2) nor  vols(2)
80      !------------------------------------------------------
81      volw3d(1:jpoce,2) = dz3d(1:jpoce,2) * por(2)
82      vols3d(1:jpoce,2) = dz3d(1:jpoce,2) * por1(2)
83
84      ! 2. Change of previous solid fractions (due to volum changes) for k=2
85      !---------------------------------------------------------------------
86
87      DO js = 1, jpsol
88         DO ji = 1, jpoce
89            solcp(ji,2,js) = solcp(ji,2,js) * dz(2) / dz3d(ji,2)
90         ENDDO
91      END DO
92
93      ! 3. New solid fractions (including solid rain fractions) for k=2
94      !------------------------------------------------------------------
95      DO js = 1, jpsol
96         DO ji = 1, jpoce
97            IF (raintg(ji) .ne. 0) THEN
98               solcp(ji,2,js) = solcp(ji,2,js) + &
99               &           ( rainrg(ji,js) / raintg(ji) ) * ( dzdep(ji) / dz3d(ji,2) )
100               ! rainrm are temporary cancel
101               rainrm(ji,js) = 0.
102            ENDIF
103         END DO
104      ENDDO
105
106      ! 4.  Adjustment of bottom water concen.(pwcp(1)):
107      !     We impose that pwcp(2) is constant. Including dzdep in dz3d(:,2) we assume
108      !     that dzdep has got a porosity of por(2). So pore water volum of jk=2 increase.
109      !     To keep pwcp(2) cste we must compensate this "increase" by a slight adjusment
110      !     of bottom water concentration.
111      !     This adjustment is compensate at the end of routine
112      !-------------------------------------------------------------
113      DO jw = 1, jpwat
114         DO ji = 1, jpoce
115            pwcp(ji,1,jw) = pwcp(ji,1,jw) - &
116               &            pwcp(ji,2,jw) * dzdep(ji) * por(2) / ( dzkbot(ji) + rtrn )
117         END DO
118      ENDDO
119
120      zadsnh4 = 1.0 / ( 1.0 + adsnh4 )
121
122      ! --------------------------------------------------
123      ! Computation of the diffusivities
124      ! --------------------------------------------------
125
126      DO js = 1, jpwat
127         DO jk = 1, jpksed
128            DO ji = 1, jpoce
129               diff(ji,jk,js) = ( diff1(js) + diff2(js) * temp(ji) ) / ( 1.0 - 2.0 * log( por(jk) ) )
130            END DO
131         END DO
132      END DO
133
134      ! Impact of bioirrigation and adsorption on diffusion
135      ! ---------------------------------------------------
136
137      diff(:,:,jwnh4) = diff(:,:,jwnh4) * ( 1.0 + irrig(:,:) ) * zadsnh4
138      diff(:,:,jwsil) = diff(:,:,jwsil) * ( 1.0 + irrig(:,:) )
139      diff(:,:,jwoxy) = diff(:,:,jwoxy) * ( 1.0 + irrig(:,:) )
140      diff(:,:,jwdic) = diff(:,:,jwdic) * ( 1.0 + irrig(:,:) )
141      diff(:,:,jwno3) = diff(:,:,jwno3) * ( 1.0 + irrig(:,:) )
142      diff(:,:,jwpo4) = diff(:,:,jwpo4) * ( 1.0 + irrig(:,:) )
143      diff(:,:,jwalk) = diff(:,:,jwalk) * ( 1.0 + irrig(:,:) )
144      diff(:,:,jwh2s) = diff(:,:,jwh2s) * ( 1.0 + irrig(:,:) )
145      diff(:,:,jwso4) = diff(:,:,jwso4) * ( 1.0 + irrig(:,:) )
146      diff(:,:,jwfe2) = diff(:,:,jwfe2) * ( 1.0 + 0.2 * irrig(:,:) )
147
148      DO jnt = 1, nrseddt
149         CALL sed_diff( kt, jnt )        ! 1st pass in diffusion to get values at t+1/2
150         CALL sed_dsr ( kt, jnt )        ! Dissolution reaction
151         CALL sed_diff( kt, jnt )        ! 2nd pass in diffusion to get values at t+1
152      END DO
153
154
155      IF( ln_timing )  CALL timing_stop('sed_org')
156!     
157   END SUBROUTINE sed_org
158
159END MODULE sedorg
Note: See TracBrowser for help on using the repository browser.