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.
sedstp.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/sedstp.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

  • Property svn:keywords set to Id
File size: 3.6 KB
RevLine 
[3443]1MODULE sedstp
2   !!======================================================================
3   !!                       ***  MODULE sedstp   ***
4   !!   Sediment model : Sediment model time-stepping
5   !!======================================================================
6   USE sed      ! sediment global variables
7   USE seddta   ! data read
8   USE sedchem  ! chemical constant
9   USE sedco3   ! carbonate in sediment pore water
[10345]10   USE sedorg   ! Organic reactions and diffusion
11   USE sedinorg ! Inorganic dissolution
[3443]12   USE sedbtb   ! bioturbation
13   USE sedadv   ! vertical advection
14   USE sedmbc   ! mass balance calculation
15   USE sedsfc   ! sediment surface data
16   USE sedrst   ! restart
17   USE sedwri   ! outputs
[10345]18   USE trcdmp_sed
19   USE lib_mpp         ! distribued memory computing library
20   USE iom
[3443]21
22   IMPLICIT NONE
23   PRIVATE
24
25   !! * Routine accessibility
26   PUBLIC sed_stp  ! called by step.F90
27
[5215]28   !! $Id$
[3443]29CONTAINS
30
31   SUBROUTINE sed_stp ( kt )
32      !!---------------------------------------------------------------------
33      !!                  ***  ROUTINE sed_stp  ***
34      !!
35      !! ** Purpose :   Sediment time stepping
36      !!                Simulation of pore water chemistry
37      !!
38      !! ** Action  :
39      !!
40      !!
41      !!   History :
42      !!        !  98-08 (E. Maier-Reimer, Christoph Heinze )  Original code
43      !!        !  04-10 (N. Emprin, M. Gehlen ) coupled with PISCES
44      !!        !  06-04 (C. Ethe)  Re-organization
45      !!----------------------------------------------------------------------
46      INTEGER, INTENT(in) ::   kt       ! number of iteration
[10345]47      INTEGER :: ji,jk,js,jn,jw
[3443]48      !!----------------------------------------------------------------------
[10345]49      IF( ln_timing )      CALL timing_start('sed_stp')
50        !
51                                CALL sed_rst_opn  ( kt )       ! Open tracer restart file
52      IF( lrst_sed )            CALL sed_rst_cal  ( kt, 'WRITE' )   ! calenda
[3443]53
[10345]54      IF(ln_sediment_offline)   CALL trc_dmp_sed  ( kt )
55
56      dtsed  = r2dttrc
57!      dtsed2 = dtsed
58      IF (kt /= nitsed000) THEN
59         CALL sed_dta( kt )       ! Load  Data for bot. wat. Chem and fluxes
[3443]60      ENDIF
61
[10345]62      IF (sedmask == 1. ) THEN
63         IF( kt /= nitsed000 )  THEN
64           CALL sed_chem( kt )      ! update of chemical constant to account for salinity, temperature changes
65         ENDIF
66
67         CALL sed_btb( kt )         ! 1st pass of bioturbation at t+1/2
68         CALL sed_org( kt )         ! Organic related reactions and diffusion
69         CALL sed_inorg( kt )       ! Dissolution reaction
70         CALL sed_btb( kt )         ! 2nd pass of bioturbation at t+1
71         tokbot(:,:) = 0.0
72         DO jw = 1, jpwat
73            DO ji = 1, jpoce
74               tokbot(ji,jw) = pwcp(ji,1,jw) * 1.e-3 * dzkbot(ji)
75            END DO
76         ENDDO
77         CALL sed_adv( kt )         ! advection
78         CALL sed_co3( kt )         ! pH actualization for saving
79         ! This routine is commented out since it does not work at all
80         CALL sed_mbc( kt )         ! cumulation for mass balance calculation
81
82         IF (ln_sed_2way) CALL sed_sfc( kt )         ! Give back new bottom wat chem to tracer model
83      ENDIF
[3443]84      CALL sed_wri( kt )         ! outputs
[10345]85      IF( kt == nitsed000 ) THEN
86          CALL iom_close( numrsr )       ! close input tracer restart file
87!          IF(lwm) CALL FLUSH( numont )   ! flush namelist output
88      ENDIF
89      IF( lrst_sed )            CALL sed_rst_wri( kt )   ! restart file output
[3443]90
91      IF( kt == nitsedend )  CLOSE( numsed )
92
[10345]93      IF( ln_timing )   CALL timing_stop('sed_stp')
94
[3443]95   END SUBROUTINE sed_stp
96
97END MODULE sedstp
Note: See TracBrowser for help on using the repository browser.