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

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

Last change on this file was 15450, checked in by cetlod, 3 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: 10.6 KB
Line 
1MODULE sed
2   !!======================================================================
3   !!                        ***  sed  ***
4   !! Sediment :   set sediment global variables
5   !!======================================================================
6   !! History :
7   !!        !  06-12  (C. Ethe)  Orignal
8   !!----------------------------------------------------------------------
9   USE par_sed
10   USE oce_sed
11   USE in_out_manager
12
13
14   IMPLICIT NONE
15   PUBLIC
16
17   PUBLIC sed_alloc
18
19   !! Namelist
20   REAL(wp), PUBLIC               ::  reac_sil            !: reactivity of silicate in  [l.mol-1.s-1]
21   REAL(wp), PUBLIC               ::  reac_clay           !: reactivity of clay in  [l.mol-1.s-1]
22   REAL(wp), PUBLIC               ::  reac_ligc           !: reactivity of Ligands [l.mol-1.s-1]
23   REAL(wp), PUBLIC               ::  reac_pocl           !: reactivity of pocl in  [s-1]
24   REAL(wp), PUBLIC               ::  reac_pocs           !: reactivity of pocs in  [s-1]
25   REAL(wp), PUBLIC               ::  reac_pocr           !: reactivity of pocr in  [s-1]
26   REAL(wp), PUBLIC               ::  reac_nh4            !: reactivity of NH4 in  [l.mol-1.s-1]
27   REAL(wp), PUBLIC               ::  reac_h2s            !: reactivity of ODU in  [l.mol-1.s-1]
28   REAL(wp), PUBLIC               ::  reac_fe2            !: reactivity of Fe2+ in  [l.mol-1.s-1]
29   REAL(wp), PUBLIC               ::  reac_feh2s          !: reactivity of Fe2+ in  [l.mol-1.s-1]
30   REAL(wp), PUBLIC               ::  reac_feso           !: reactivity of FeS with O2 in  [l.mol-1.s-1]
31   REAL(wp), PUBLIC               ::  reac_fesp           !: precipitation of FeS  [mol.l-1.s-1]
32   REAL(wp), PUBLIC               ::  reac_fesd           !: Dissolution  of FeS  [s-1]
33   REAL(wp), PUBLIC               ::  reac_cal            !: reactivity of cal in  [l.mol-1.s-1]
34   REAL(wp), PUBLIC               ::  adsnh4              !: adsorption coefficient of NH4
35   REAL(wp), PUBLIC               ::  adsfe2              !: adsorption coefficient of Fe2
36   REAL(wp), PUBLIC               ::  ratligc             !: C/L ratio in POC
37   REAL(wp), PUBLIC               ::  so2ut 
38   REAL(wp), PUBLIC               ::  srno3 
39   REAL(wp), PUBLIC               ::  spo4r 
40   REAL(wp), PUBLIC               ::  srDnit 
41   REAL(wp), PUBLIC               ::  dtsed               !: sedimentation time step
42   INTEGER , PUBLIC               ::  nitsed000
43   INTEGER , PUBLIC               ::  nitsedend
44   LOGICAL , PUBLIC               ::  lrst_sed       !: logical to control the trc restart write
45   LOGICAL , PUBLIC               ::  ln_rst_sed  = .TRUE.     !: initialisation from a restart file or not
46   LOGICAL , PUBLIC               ::  ln_btbz     = .FALSE.    !: Depth variation of the bioturbation coefficient
47   LOGICAL , PUBLIC               ::  ln_irrig    = .FALSE.    !: iActivation of the bioirrigation
48   LOGICAL , PUBLIC               ::  ln_sed_2way = .FALSE.    !: 2 way coupling with PISCES
49   LOGICAL , PUBLIC               ::  ln_sediment_offline = .FALSE. !: Offline mode for sediment module
50   INTEGER             , PUBLIC   ::  nn_rstsed      !: control of the time step ( 0 or 1 ) for pass. tr.
51   INTEGER , PUBLIC               ::  nn_dtsed = 1   !: frequency of step on passive tracers
52   CHARACTER(len = 80) , PUBLIC   ::  cn_sedrst_in   !: suffix of pass. tracer restart name (input)
53   CHARACTER(len = 256), PUBLIC   ::  cn_sedrst_indir  !: restart input directory
54   CHARACTER(len = 80) , PUBLIC   ::  cn_sedrst_out  !: suffix of pass. tracer restart name (output)
55   CHARACTER(len = 256), PUBLIC   ::  cn_sedrst_outdir  !: restart output directory
56   INTEGER, PUBLIC                ::  nrosorder  !: order of the rosenbrock method
57   REAL(wp), PUBLIC               ::  rosatol   !: Tolerance for absolute error
58   REAL(wp), PUBLIC               ::  rosrtol   !: Tolerance for relative error
59
60   !
61   REAL(wp), PUBLIC, DIMENSION(:,:,:),  ALLOCATABLE ::  pwcp, pwcpa
62   REAL(wp), PUBLIC, DIMENSION(:,:,:),  ALLOCATABLE ::  solcp, solcpa
63   REAL(wp), PUBLIC, DIMENSION(:,:,:),  ALLOCATABLE ::  diff
64
65   !! * Shared module variables
66   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  pwcp_dta   !: pore water data at given time-step
67   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrm_dta !: rain data at at initial time
68   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrg     !: rain of each solid component in [g/(cm**2.s)]
69   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  fromsed    !:
70   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  tosed      !:
71   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rearatpom  !:
72   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  apluss, aminuss  !:
73   !
74   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  temp       !: temperature
75   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  salt       !: salinity
76   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  fecratio   !: Fe/C ratio in falling particles to the sediments
77   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzdep, slatit, slongit   !: total thickness of solid material rained [cm] in each cell
78   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  zkbot      !: total thickness of solid material rained [cm] in each cell
79   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  wacc       !: total thickness of solid material rained [cm] in each cell
80   !
81   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  hipor      !: [h+] in mol/kg*densSW
82   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  co3por     !: [co3--]solid sediment at initial time
83   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  dz3d       !:  ???
84   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  volw3d     !:  ???
85   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  vols3d     !:  ???
86   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  volc
87   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dens_sol   !: Density of each solid fraction
88
89
90   !! Chemistry
91   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  densSW 
92   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  borats 
93   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  calcon2
94   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akbs 
95   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak1s 
96   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak2s   
97   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akws 
98   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak12s 
99   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak1ps 
100   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak2ps 
101   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak3ps 
102   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak12ps 
103   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak123ps
104   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksis 
105   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aknh3
106   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksps 
107   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akh2s
108   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  sieqs
109   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aks3s
110   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akf3s
111   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  sulfats
112   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  fluorids
113
114   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  mol_wgt    !: molecular weight of solid sediment data
115 
116   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  trc_data    !: tracer data to share with sediment model
117   !! Geometry
118   INTEGER , PUBLIC, SAVE                          ::  jpoce, indoce !: Ocean points ( number/indices )
119   INTEGER , PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  iarroce       !: Computation of 1D array of sediments points
120   INTEGER , PUBLIC, DIMENSION(:, : ), ALLOCATABLE ::  jarr       !: Computation of 1D array of sediments points
121   INTEGER , PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  jsvode, isvode   !: Computation of 1D array of sediments points
122
123   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  epkbot        !: ocean bottom layer thickness
124   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  gdepbot       !: Depth of the sediment
125   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzkbot        !: ocean bottom layer thickness in meters
126   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dz            !: sediment layers thickness
127   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por           !: porosity profile     
128   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por1          !: 1-por
129   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  volw          !: volume of pore water cell fraction
130   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  vols          !: volume of solid cell fraction
131   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  db            !: bioturbation ceofficient
132   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  irrig        !: bioturbation ceofficient
133   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  radssol, rads1sol
134   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  saturco3
135   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  rdtsed        !:  sediment model time-step
136   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  rstepros      !:  Number of iteration of rosenbrock method
137   REAL(wp)  ::   dens               !: density of solid material
138   !! Inputs / Outputs
139   CHARACTER( len = 80 ), DIMENSION(jptrased  ) ::  sedtrcl
140   CHARACTER( len = 20 ), DIMENSION(jptrased  ) ::  sedtrcd , sedtrcu
141   CHARACTER( len = 80 ), DIMENSION(jpdia3dsed) ::  seddia3l 
142   CHARACTER( len = 20 ), DIMENSION(jpdia3dsed) ::  seddia3d, seddia3u
143   CHARACTER( len = 80 ), DIMENSION(jpdia2dsed) ::  seddia2l 
144   CHARACTER( len = 20 ), DIMENSION(jpdia2dsed) ::  seddia2d, seddia2u
145   !
146
147   INTEGER, PUBLIC ::  numsed = 27    ! units
148
149   !! $Id$
150CONTAINS
151
152   INTEGER FUNCTION sed_alloc()
153      !!-------------------------------------------------------------------
154      !!                    *** ROUTINE sed_alloc ***
155      !!-------------------------------------------------------------------
156      USE lib_mpp, ONLY: ctl_stop
157      !!-------------------------------------------------------------------
158      !
159      ALLOCATE( trc_data(jpi,jpj,jpdta)                                   ,   &
160         &      epkbot(jpi,jpj), gdepbot(jpi,jpj)        ,   &
161         &      dz(jpksed)  , por(jpksed) , por1(jpksed)                  ,   &
162         &      volw(jpksed), vols(jpksed), rdtsed(jpksed)  ,   &
163         &      mol_wgt(jpsol),                                           STAT=sed_alloc )
164
165      IF( sed_alloc /= 0 )   CALL ctl_stop( 'STOP', 'sed_alloc: failed to allocate arrays' )
166      !
167   END FUNCTION sed_alloc
168
169END MODULE sed
Note: See TracBrowser for help on using the repository browser.