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.
sedinitrc.F90 in NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/TOP/PISCES/SED/sedinitrc.F90 @ 13463

Last change on this file since 13463 was 13463, checked in by andmirek, 4 years ago

Ticket #2195:update to trunk 13461

File size: 6.9 KB
Line 
1MODULE sedinitrc
2   !!======================================================================
3   !!              ***  MODULE  sedinitrc  ***
4   !! Sediment : define sediment variables
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   sed_init    : initialization, namelist read, and parameters control
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE sed     ! sediment global variable
12   USE sed_oce
13   USE sedini
14   USE seddta
15   USE sedrst
16   USE sedco3
17   USE sedchem
18   USE sedarr
19   USE lib_mpp         ! distribued memory computing library
20
21
22   IMPLICIT NONE
23   PRIVATE
24
25   REAL(wp)    ::  &
26      ryear = 365. * 24. * 3600. !:  1 year converted in second
27
28   !! *  Routine accessibility
29   PUBLIC sed_initrc          ! routine called by opa.F90
30
31   !! $Id: sedini.F90 5215 2015-04-15 16:11:56Z nicolasmartin $
32CONTAINS
33
34
35   SUBROUTINE sed_initrc( Kbb, Kmm )
36      !!----------------------------------------------------------------------
37      !!                   ***  ROUTINE sed_init  ***
38      !!
39      !! ** Purpose :  Initialization of sediment module
40      !!               - Reading namelist
41      !!               - Read the deepest water layer thickness
42      !!                 ( using as mask ) in Netcdf file
43      !!               - Convert unity if necessary
44      !!               - sets initial sediment composition
45      !!                 ( only clay or reading restart file )
46      !!               - sets sediment grid, porosity and others constants
47      !!
48      !!   History :
49      !!        !  04-10  (N. Emprin, M. Gehlen )  Original code
50      !!        !  06-07  (C. Ethe)  Re-organization
51      !!----------------------------------------------------------------------
52      INTEGER, INTENT(in)  ::  Kbb, Kmm      ! time level indices
53      INTEGER :: ji, jj, ikt
54      !!----------------------------------------------------------------------
55
56
57      ! Initialize the sediment tracers concentrations
58      !------------------------------------------------
59
60      IF(lwp) WRITE(numsed,*) ' sed_initrc : Initialization of sediment concentration '
61      IF(lwp) WRITE(numsed,*) ' '
62
63      ! Determination of sediments number of points and allocate global variables
64
65      ! sets initial sediment composition
66      ! ( only clay or reading restart file )
67      !---------------------------------------
68      CALL sed_init_data( Kbb, Kmm )
69
70
71      CALL sed_init_wri
72
73
74   END SUBROUTINE sed_initrc
75
76
77   SUBROUTINE sed_init_data( Kbb, Kmm )
78      !!----------------------------------------------------------------------
79      !!                   ***  ROUTINE sed_init_data  ***
80      !!
81      !! ** Purpose :  Initialization of sediment module
82      !!               - sets initial sediment composition
83      !!                 ( only clay or reading restart file )
84      !!
85      !!   History :
86      !!        !  06-07  (C. Ethe)  original
87      !!----------------------------------------------------------------------
88      INTEGER, INTENT(in)  ::  Kbb, Kmm      ! time level indices
89 
90      ! local variables
91      INTEGER :: &
92         ji, jk, zhipor
93
94      !--------------------------------------------------------------------
95 
96
97      IF( .NOT. ln_rst_sed ) THEN
98
99         IF (lwp) WRITE(numsed,*) ' Initilization of default values of sediment components'
100
101         ! default values for initial pore water concentrations [mol/l]
102         pwcp(:,:,:) = 0.
103         ! default value for initial solid component (fraction of dry weight dim=[0])
104         ! clay
105         solcp(:,:,:) = 0.
106         solcp(:,2:jpksed,jsclay) = 1.0 * 0.965
107         solcp(:,2:jpksed,jsfeo)  = 1.0 * 0.035
108
109         ! Initialization of [h+] and [co3--]
110
111         zhipor = 8.0
112         ! Initialization of [h+] in mol/kg
113         DO jk = 1, jpksed
114            DO ji = 1, jpoce
115               hipor (ji,jk) = 10.**( -1. * zhipor )
116            ENDDO
117         ENDDO
118
119         co3por(:,:) = 1E-6
120
121      ELSE   
122 
123         IF (lwp) WRITE(numsed,*) ' Initilization of Sediment components from restart'
124
125         CALL sed_rst_cal( nitsed000, 'READ' )
126         CALL sed_rst_read
127
128      ENDIF
129
130
131      ! Load initial Pisces Data for bot. wat. Chem and fluxes
132      CALL sed_dta ( nitsed000, Kbb, Kmm ) 
133
134      ! Initialization of chemical constants
135      CALL sed_chem ( nitsed000 )
136
137      ! Stores initial sediment data for mass balance calculation
138      pwcp0 (1:jpoce,1:jpksed,1:jpwat ) = pwcp (1:jpoce,1:jpksed,1:jpwat ) 
139      solcp0(1:jpoce,1:jpksed,1:jpsol ) = solcp(1:jpoce,1:jpksed,1:jpsol) 
140
141      ! Conversion of [h+] in mol/Kg to get it in mol/l ( multiplication by density)
142      DO jk = 1, jpksed
143         hipor(1:jpoce,jk) = hipor(1:jpoce,jk) * densSW(1:jpoce)
144      ENDDO
145
146
147      ! In default case - no restart - sedco3 is run to initiate [h+] and [co32-]
148      ! Otherwise initiate values of pH and co3 read in restart
149      IF( .NOT. ln_rst_sed ) THEN
150         ! sedco3 is run to initiate[h+] [co32-] in mol/l of solution
151         CALL sed_co3 ( nitsed000 )
152
153      ENDIF
154           
155   END SUBROUTINE sed_init_data
156
157   SUBROUTINE sed_init_wri
158
159      INTEGER :: jk
160
161      IF (lwp) THEN
162         WRITE(numsed,*)' '
163         WRITE(numsed,*)'======== Write summary of sediment char.  ============'
164         WRITE(numsed,*)' '
165         WRITE(numsed,*)' '
166         WRITE(numsed,*)'-------------------------------------------------------------------'
167         WRITE(numsed,*)' Initial Conditions '
168         WRITE(numsed,*)'-------------------------------------------------------------------'
169         WRITE(numsed,*)'dzm = dzkbot minimum to calculate ', 0.
170         WRITE(numsed,*)'Local zone : jpi, jpj, jpksed : ',jpi, jpj, jpksed
171         WRITE(numsed,*)'jpoce = ',jpoce,' nbtot pts = ',jpij,' nb earth pts = ',jpij - jpoce
172         WRITE(numsed,*)'sublayer thickness dz(1) [cm] : ', dz(1)
173         WRITE(numsed,*)'Vertical domain of the sediment'
174         WRITE(numsed,*)'-------------------------------'
175         WRITE(numsed,*)' Indice, profsed, dz'
176         DO jk = 2, jpksed
177            WRITE(numsed,*) jk,profsed(jk),dz(jk) 
178         END DO
179         WRITE(numsed,*)' nb solid comp : ',jpsol
180         WRITE(numsed,*)'(1=opal,2=clay,3=POC,4=CaCO3), 5=POS, 6=POR, 7=FEO, 8=FeS'
181         WRITE(numsed,*)'weight mol 1,2,3,4,5,6,7'
182         WRITE(numsed,'(8(F0.2,3X))')mol_wgt(jsopal),mol_wgt(jsclay),mol_wgt(jspoc),mol_wgt(jscal),mol_wgt(jspos),mol_wgt(jspor),mol_wgt(jsfeo),mol_wgt(jsfes)
183         WRITE(numsed,*)'nb dissolved comp',jpwat
184         WRITE(numsed,*)'1=silicic acid,,2=O2,3=DIC,4=NO3,5=PO4,6=Alk,7=NH4,8=ODU'
185         WRITE(numsed,*)'redfield coef C,O,N P Dit '
186         WRITE(numsed,'(5(F0.2,3X))')1./spo4r,so2ut/spo4r,srno3/spo4r,spo4r/spo4r,srDnit/spo4r
187         WRITE(numsed,*) ' '
188         WRITE(numsed,*) ' End Of Initialization '
189         WRITE(numsed,*) ' '
190      ENDIF
191!
192   END SUBROUTINE sed_init_wri
193
194END MODULE sedinitrc
Note: See TracBrowser for help on using the repository browser.