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.
sedfunc.F90 in NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/PISCES/SED/sedfunc.F90 @ 15574

Last change on this file since 15574 was 15574, checked in by techene, 3 years ago

#2605 #2715 trunk merged into dev_r14318_RK3_stage1

File size: 3.4 KB
Line 
1MODULE sedfunc
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 sed_oce
11   USE sedini
12   USE seddsr
13   USE sedmat
14   USE lib_mpp         ! distribued memory computing library
15   USE lib_fortran
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC sed_func
21
22   !! * Module variables
23
24   !! $Id: sedsol.F90 5215 2015-04-15 16:11:56Z nicolasmartin $
25CONTAINS
26   
27   SUBROUTINE sed_func(  NEQ, X, fval0, accmask ) 
28      !!----------------------------------------------------------------------
29      !!                   ***  ROUTINE sed_sol  ***
30      !!
31      !!  ** Purpose :  computes pore water diffusion and reactions
32      !!
33      !!  ** Methode :  Computation of the redox and dissolution reactions
34      !!                in the sediment.
35      !!                The main redox reactions are solved in sed_dsr whereas
36      !!                the secondary reactions are solved in sed_dsr_redoxb.
37      !!                Inorganic dissolution is solved in sed_inorg
38      !!                A strand spliting approach is being used here (see
39      !!                sed_dsr_redoxb for more information).
40      !!                Diffusive fluxes are computed in sed_diff
41      !!
42      !!   History :
43      !!        !  98-08 (E. Maier-Reimer, Christoph Heinze )  Original code
44      !!        !  04-10 (N. Emprin, M. Gehlen ) f90
45      !!        !  06-04 (C. Ethe)  Re-organization
46      !!        !  19-08 (O. Aumont) Debugging and improvement of the model.
47      !!                             The original method is replaced by a
48      !!                             Strand splitting method which deals
49      !!                             well with stiff reactions.
50      !!----------------------------------------------------------------------
51      !! Arguments
52      INTEGER, INTENT(in) :: NEQ
53      INTEGER, DIMENSION(jpoce), INTENT(in) :: accmask
54      REAL, DIMENSION(jpoce,NEQ), INTENT(in) :: X
55      REAL, DIMENSION(jpoce,NEQ), INTENT(out) :: fval0
56      ! --- local variables
57      INTEGER  :: ji, jk, js, jn   ! dummy looop indices
58      !!
59      !!----------------------------------------------------------------------
60
61      IF( ln_timing )  CALL timing_start('sed_func')
62!
63      pwcpa(:,:,:) = 0.
64      solcpa(:,:,:) = 0.
65
66      do jn = 1, NEQ
67         jk = jarr(jn,1)
68         js = jarr(jn,2)
69         IF (js <= jpwat) THEN
70            pwcp(:,jk,js) = X(:,jn) * 1E-6 
71         ELSE
72            solcp(:,jk,js-jpwat) = X(:,jn) * 1E-6
73         ENDIF
74      END DO
75
76      CALL sed_dsr( accmask )        ! Redox reactions
77      ! Computes diffusive fluxes
78      DO jn = 1, jpvode
79         js = jsvode(jn)
80         IF (js <= jpwat) CALL sed_mat_dsr( jpksed, js, accmask )
81      END DO
82      call sed_mat_btb( jpksed, jwnh4, accmask )
83      call sed_mat_btb( jpksed, jwfe2, accmask )
84
85      do jn = 1, NEQ
86         jk = jarr(jn,1)
87         js = jarr(jn,2)
88         IF (js <= jpwat) THEN
89            fval0(:,jn) = pwcpa(:,jk,js)  * 1E6
90         ELSE
91            fval0(:,jn) = solcpa(:,jk,js-jpwat) * 1E6
92         ENDIF
93      END DO
94
95      IF( ln_timing )  CALL timing_stop('sed_func')
96!     
97   END SUBROUTINE sed_func
98
99END MODULE sedfunc
Note: See TracBrowser for help on using the repository browser.