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.
seddta.F90 in NEMO/trunk/src/TOP/PISCES/SED – NEMO

source: NEMO/trunk/src/TOP/PISCES/SED/seddta.F90

Last change on this file was 15450, checked in by cetlod, 2 years ago

Some updates to make the PISCES/SED module usable. Totally orthogonal with no effect on other parts of the code

  • Property svn:keywords set to Id
File size: 9.2 KB
Line 
1MODULE seddta
2   !!======================================================================
3   !!                     ***  MODULE  seddta  ***
4   !! Sediment data  :  read sediment input data from a file
5   !!=====================================================================
6
7   !! * Modules used
8   USE sed
9   USE sedarr
10   USE sedini
11   USE phycst, ONLY : rday
12   USE iom
13   USE lib_mpp         ! distribued memory computing library
14
15   IMPLICIT NONE
16   PRIVATE
17
18   !! * Routine accessibility
19   PUBLIC sed_dta   !
20
21   !! *  Module variables
22   REAL(wp) ::  conv2    ! [kg/m2/month]-->[g/cm2/s] ( 1 month has 30 days )
23
24   !! * Substitutions
25#  include "do_loop_substitute.h90"
26#  include "domzgr_substitute.h90"
27
28CONTAINS
29
30   !!---------------------------------------------------------------------------
31   !!   sed_dta  : read the NetCDF data file in online version using module iom
32   !!---------------------------------------------------------------------------
33
34   SUBROUTINE sed_dta( kt, Kbb, Kmm )
35      !!----------------------------------------------------------------------
36      !!                   ***  ROUTINE sed_dta  ***
37      !!                   
38      !! ** Purpose :   Reads data from a netcdf file and
39      !!                initialization of rain and pore water (k=1) components
40      !!
41      !!
42      !!   History :
43      !!        !  04-10  (N. Emprin, M. Gehlen )  Original code
44      !!        !  06-04  (C. Ethe)  Re-organization ; Use of iom
45      !!----------------------------------------------------------------------
46
47      !! Arguments
48      INTEGER, INTENT( in ) ::   kt    ! time-step
49      INTEGER, INTENT( in ) ::   Kbb, Kmm ! time level indices
50
51      !! * Local declarations
52      INTEGER  ::  ji, jj, js, jw, ikt
53
54      REAL(wp), DIMENSION(jpoce) :: zdtap, zdtag
55      REAL(wp), DIMENSION(jpi,jpj) :: zwsbio4, zwsbio3, zddust
56      REAL(wp) :: zf0, zf1, zf2, zkapp, zratio, zdep
57      REAL(wp) :: zzf0, zf0s, zf0b, zzf1, zf1s, zf1b, zzf2, zf2s, zf2b
58
59      !----------------------------------------------------------------------
60
61      ! Initialization of sediment variable
62      ! Spatial dimension is merged, and unity converted if needed
63      !-------------------------------------------------------------
64
65      IF( ln_timing )  CALL timing_start('sed_dta')
66
67      IF (lwp) THEN
68         WRITE(numsed,*)
69         WRITE(numsed,*) ' sed_dta : Bottom layer fields'
70         WRITE(numsed,*) ' ~~~~~~'
71         WRITE(numsed,*) ' Data from SMS model'
72         WRITE(numsed,*)
73      ENDIF
74
75
76      ! open file
77      IF( kt == nitsed000 ) THEN
78         IF (lwp) WRITE(numsed,*) ' sed_dta : Sediment fields'
79         dtsed = rDt_trc
80         conv2 = 1.0e+3 /  1.0e+4 
81      ENDIF
82
83      ! Initialization of temporaries arrays 
84      zdtap(:)    = 0. 
85      zdtag(:)    = 0. 
86      zddust(:,:) = 0.0
87
88      ! reading variables
89      IF (lwp) WRITE(numsed,*)
90      IF (lwp) WRITE(numsed,*) ' sed_dta : Bottom layer fields at time  kt = ', kt
91      ! reading variables
92      !
93      !    Sinking speeds of detritus is increased with depth as shown
94      !    by data and from the coagulation theory
95      !    -----------------------------------------------------------
96      IF (ln_sediment_offline) THEN
97         DO_2D( 0, 0, 0, 0 )
98            ikt = mbkt(ji,jj)
99            zwsbio4(ji,jj) = wsbio2 / rday
100            zwsbio3(ji,jj) = wsbio  / rday
101         END_2D
102      ELSE
103         DO_2D( 0, 0, 0, 0 )
104            ikt = mbkt(ji,jj)
105            zdep = e3t(ji,jj,ikt,Kmm) / rDt_trc
106            zwsbio4(ji,jj) = MIN( 0.99 * zdep, wsbio4(ji,jj,ikt) / rday )
107            zwsbio3(ji,jj) = MIN( 0.99 * zdep, wsbio3(ji,jj,ikt) / rday )
108         END_2D
109      ENDIF
110
111      trc_data(:,:,:) = 0.
112      DO_2D( 0, 0, 0, 0 )
113         ikt = mbkt(ji,jj)
114         IF ( tmask(ji,jj,ikt) == 1.0 ) THEN
115            trc_data(ji,jj,jwsil) = tr(ji,jj,ikt,jpsil,Kbb)
116            trc_data(ji,jj,jwoxy) = tr(ji,jj,ikt,jpoxy,Kbb)
117            trc_data(ji,jj,jwdic) = tr(ji,jj,ikt,jpdic,Kbb)
118            trc_data(ji,jj,jwno3) = tr(ji,jj,ikt,jpno3,Kbb) * redNo3 / redC
119            trc_data(ji,jj,jwpo4) = tr(ji,jj,ikt,jppo4,Kbb) / redC
120            trc_data(ji,jj,jwalk) = tr(ji,jj,ikt,jptal,Kbb) 
121            trc_data(ji,jj,jwnh4) = tr(ji,jj,ikt,jpnh4,Kbb) * redNo3 / redC 
122            trc_data(ji,jj,jwh2s) = 0.0
123            trc_data(ji,jj,jwso4) = 0.14 * ts(ji,jj,ikt,jp_sal,Kmm) / 1.80655 / 96.062
124            trc_data(ji,jj,jwfe2) = tr(ji,jj,ikt,jpfer,Kbb)
125            trc_data(ji,jj,jwlgw) = 1E-9
126            trc_data(ji,jj,12 )   = MIN(tr(ji,jj,ikt,jpgsi,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3
127            trc_data(ji,jj,13 )   = MIN(tr(ji,jj,ikt,jppoc,Kbb), 1E-4) * zwsbio3(ji,jj) * 1E3
128            trc_data(ji,jj,14 )   = MIN(tr(ji,jj,ikt,jpgoc,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3
129            trc_data(ji,jj,15)    = MIN(tr(ji,jj,ikt,jpcal,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3
130            trc_data(ji,jj,16)    = ts(ji,jj,ikt,jp_tem,Kmm)
131            trc_data(ji,jj,17)    = ts(ji,jj,ikt,jp_sal,Kmm)
132            trc_data(ji,jj,18 )   = ( tr(ji,jj,ikt,jpsfe,Kbb) * zwsbio3(ji,jj) + tr(ji,jj,ikt,jpbfe,Kbb)  &
133            &                       * zwsbio4(ji,jj)  ) * 1E3 / ( trc_data(ji,jj,13 ) + trc_data(ji,jj,14 ) + rtrn )
134            trc_data(ji,jj,18 )   = MIN(1E-3, trc_data(ji,jj,18 ) )
135         ENDIF
136      END_2D
137
138      ! Pore water initial concentration [mol/l] in  k=1
139      !-------------------------------------------------
140      DO jw = 1, jpwat
141         CALL pack_arr ( jpoce,  pwcp_dta(1:jpoce,jw), trc_data(1:jpi,1:jpj,jw), iarroce(1:jpoce) )
142      END DO
143
144      !  Solid components :
145      !-----------------------
146      !  Sinking fluxes for OPAL in mol.m-2.s-1 ; conversion in mol.cm-2.s-1
147      CALL pack_arr ( jpoce, rainrm_dta(1:jpoce,jsopal), trc_data(1:jpi,1:jpj,12), iarroce(1:jpoce) ) 
148      rainrm_dta(1:jpoce,jsopal) = rainrm_dta(1:jpoce,jsopal) * 1e-4
149
150      !  Sinking fluxes for POC in mol.m-2.s-1 ; conversion in mol.cm-2.s-1
151      CALL pack_arr ( jpoce, zdtap(1:jpoce), trc_data(1:jpi,1:jpj,13) , iarroce(1:jpoce) )     
152      CALL pack_arr ( jpoce, zdtag(1:jpoce), trc_data(1:jpi,1:jpj,14) , iarroce(1:jpoce) )
153      DO ji = 1, jpoce
154         zzf2 = 2E-2
155         zzf1 = 0.3
156         zzf0 = 1.0 - zzf1 - zzf2
157         zf0s = zzf0
158         zf1s = zzf1
159         zf2s = 1.0 - zf1s - zf0s
160         zf0b = zzf0
161         zf1b = zzf1
162         zf2b = 1.0 - zf1b - zf0b
163         rainrm_dta(ji,jspoc) =   ( zdtap(ji) * zf0s +  zdtag(ji) * zf0b ) * 1e-4
164         rainrm_dta(ji,jspos) =   ( zdtap(ji) * zf1s +  zdtag(ji) * zf1b ) * 1e-4
165         rainrm_dta(ji,jspor) =   ( zdtap(ji) * zf2s +  zdtag(ji) * zf2b ) * 1e-4
166      END DO
167
168      !  Sinking fluxes for Calcite in mol.m-2.s-1 ; conversion in mol.cm-2.s-1
169      CALL pack_arr ( jpoce,  rainrm_dta(1:jpoce,jscal), trc_data(1:jpi,1:jpj,15), iarroce(1:jpoce) )
170      rainrm_dta(1:jpoce,jscal) = rainrm_dta(1:jpoce,jscal) * 1e-4
171
172      ! vector temperature [°C] and salinity
173      CALL pack_arr ( jpoce,  temp(1:jpoce), trc_data(1:jpi,1:jpj,16), iarroce(1:jpoce) )
174      CALL pack_arr ( jpoce,  salt(1:jpoce), trc_data(1:jpi,1:jpj,17), iarroce(1:jpoce) )
175     
176      ! Clay rain rate in [mol/(cm**2.s)]
177      ! inputs data in [kg.m-2.sec-1] ---> 1e+3/(1e+4) [g.cm-2.s-1]   
178      ! divided after by molecular weight g.mol-1     
179      CALL pack_arr ( jpoce,  rainrm_dta(1:jpoce,jsclay), dust(1:jpi,1:jpj), iarroce(1:jpoce) )
180      rainrm_dta(1:jpoce,jsclay) = rainrm_dta(1:jpoce,jsclay) * conv2 / mol_wgt(jsclay)   &
181      &                            + wacc(1:jpoce) * por1(2) * dens_sol(jsclay) / mol_wgt(jsclay) / ( rday * 365.0 )
182      rainrm_dta(1:jpoce,jsfeo)  = rainrm_dta(1:jpoce,jsclay) * mol_wgt(jsclay) / mol_wgt(jsfeo) * 0.035 * 0.5
183      rainrm_dta(1:jpoce,jsclay) = rainrm_dta(1:jpoce,jsclay) * ( 1.0 - 0.035 * 0.5 ) 
184      CALL unpack_arr ( jpoce, zddust(1:jpi,1:jpj), iarroce(1:jpoce), wacc(1:jpoce) )
185      zddust(:,:) = dust(:,:) + zddust(:,:) / ( rday * 365.0 ) * por1(2) * dens_sol(jsclay) / conv2
186
187!    rainrm_dta(1:jpoce,jsclay) = 1.0E-4 * conv2 / mol_wgt(jsclay)
188
189      ! Iron monosulphide rain rates. Set to 0
190      rainrm_dta(1:jpoce,jsfes)  = 0. 
191
192      ! Fe/C ratio in sinking particles that fall to the sediments
193      CALL pack_arr ( jpoce,  fecratio(1:jpoce), trc_data(1:jpi,1:jpj,18), iarroce(1:jpoce) )
194
195      ! sediment pore water at 1st layer (k=1)
196      pwcp(1:jpoce,1,1:jpwat) = pwcp_dta(1:jpoce,1:jpwat)
197
198      ! Calculation of raintg of each sol. comp.: rainrm in [g/(cm**2.s)]
199      DO js = 1, jpsol
200         rainrg(1:jpoce,js) = rainrm_dta(1:jpoce,js) * mol_wgt(js)
201      ENDDO
202
203      ! computation of dzdep = total thickness of solid material rained [cm] in each cell
204      dzdep(:) = 0.
205      DO js = 1, jpsol
206         dzdep(1:jpoce) = dzdep(1:jpoce) + rainrg(1:jpoce,js) * dtsed / ( dens_sol(js) * por1(2) )
207      END DO
208
209      IF( lk_iomput ) THEN
210          IF( iom_use("sflxclay" ) ) CALL iom_put( "sflxclay", zddust(:,:) * 1E3 / 1.E4 )
211          IF( iom_use("sflxcal" ) )  CALL iom_put( "sflxcal", trc_data(:,:,15) / 1.E4 )
212          IF( iom_use("sflxbsi" ) )  CALL iom_put( "sflxbsi", trc_data(:,:,12) / 1.E4 )
213          IF( iom_use("sflxpoc" ) )  CALL iom_put( "sflxpoc", ( trc_data(:,:,13) + trc_data(:,:,14) ) / 1.E4 )
214      ENDIF
215
216      IF( ln_timing )  CALL timing_stop('sed_dta')
217     
218   END SUBROUTINE sed_dta
219
220END MODULE seddta
Note: See TracBrowser for help on using the repository browser.