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_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/SED/sedfunc.F90 @ 15115

Last change on this file since 15115 was 15075, checked in by aumont, 3 years ago

major update of the sediment module

File size: 3.3 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, JINDEX, T, X, fval0 ) 
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, JINDEX
53      REAL(wp), INTENT(in) :: T
54      REAL, DIMENSION(NEQ), INTENT(in) :: X
55      REAL, DIMENSION(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      ji = JINDEX
64      pwcpa(ji,:,:) = 0.
65      solcpa(ji,:,:) = 0.
66
67      do jn = 1, NEQ
68         jk = jarr(jn,1)
69         js = jarr(jn,2)
70         IF (js <= jpwat) THEN
71            pwcp(ji,jk,js) = X(jn) * 1E-6 
72         ELSE
73            solcp(ji,jk,js-jpwat) = X(jn) * 1E-6
74         ENDIF
75      END DO
76
77      CALL sed_dsr ( ji )        ! Redox reactions
78      ! Computes diffusive fluxes
79      DO jn = 1, jpvode
80         js = jsvode(jn)
81         IF (js <= jpwat) CALL sed_mat_dsr( ji, js, dtsed )
82      END DO
83
84      do jn = 1, NEQ
85         jk = jarr(jn,1)
86         js = jarr(jn,2)
87         IF (js <= jpwat) THEN
88            fval0(jn) = pwcpa(ji,jk,js)  * 1E6 / dtsed
89         ELSE
90            fval0(jn) = solcpa(ji,jk,js-jpwat) * 1E6 / dtsed
91         ENDIF
92      END DO
93
94      IF( ln_timing )  CALL timing_stop('sed_func')
95!     
96   END SUBROUTINE sed_func
97
98END MODULE sedfunc
Note: See TracBrowser for help on using the repository browser.