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/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/PISCES/SED/seddta.F90 @ 10975

Last change on this file since 10975 was 10975, checked in by acc, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Finish converting all TOP routines and knock-on effects of these conversions. Fully SETTE tested (SETTE tests 1-6 and 9). This completes the first stage conversion of TRA and TOP but need to revisit and pass ts and tr arrays through the argument lists where appropriate.

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