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 @ 13970

Last change on this file since 13970 was 13970, checked in by andmirek, 3 years ago

Ticket #2462 into the trunk

  • Property svn:keywords set to Id
File size: 10.8 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_fes            !: reactivity of Fe with H2S in  [l.mol-1.s-1]
31   REAL(wp), PUBLIC               ::  reac_feso           !: reactivity of FeS with O2 in  [l.mol-1.s-1]
32   REAL(wp), PUBLIC               ::  reac_cal            !: reactivity of cal in  [l.mol-1.s-1]
33   REAL(wp), PUBLIC               ::  adsnh4              !: adsorption coefficient of NH4
34   REAL(wp), PUBLIC               ::  ratligc             !: C/L ratio in POC
35   REAL(wp), PUBLIC               ::  so2ut 
36   REAL(wp), PUBLIC               ::  srno3 
37   REAL(wp), PUBLIC               ::  spo4r 
38   REAL(wp), PUBLIC               ::  srDnit 
39   REAL(wp), PUBLIC               ::  dtsed               !: sedimentation time step
40   REAL(wp), PUBLIC               ::  dtsed2              !: sedimentation time step
41   INTEGER , PUBLIC               ::  nitsed000
42   INTEGER , PUBLIC               ::  nitsedend
43   INTEGER, PUBLIC                ::  nrseddt
44   REAL    , PUBLIC               ::  sedmask
45   REAL(wp), PUBLIC               ::  denssol                !: density of solid material
46   LOGICAL , PUBLIC               ::  lrst_sed       !: logical to control the trc restart write
47   LOGICAL , PUBLIC               ::  ln_rst_sed  = .TRUE.     !: initialisation from a restart file or not
48   LOGICAL , PUBLIC               ::  ln_btbz     = .FALSE.    !: Depth variation of the bioturbation coefficient
49   LOGICAL , PUBLIC               ::  ln_irrig    = .FALSE.    !: iActivation of the bioirrigation
50   LOGICAL , PUBLIC               ::  ln_sed_2way = .FALSE.    !: 2 way coupling with PISCES
51   LOGICAL , PUBLIC               ::  ln_sediment_offline = .FALSE. !: Offline mode for sediment module
52   INTEGER             , PUBLIC   ::  nn_rstsed      !: control of the time step ( 0 or 1 ) for pass. tr.
53   INTEGER , PUBLIC               ::  nn_dtsed = 1   !: frequency of step on passive tracers
54   CHARACTER(len = 80) , PUBLIC   ::  cn_sedrst_in   !: suffix of pass. tracer restart name (input)
55   CHARACTER(len = 256), PUBLIC   ::  cn_sedrst_indir  !: restart input directory
56   CHARACTER(len = 80) , PUBLIC   ::  cn_sedrst_out  !: suffix of pass. tracer restart name (output)
57   CHARACTER(len = 256), PUBLIC   ::  cn_sedrst_outdir  !: restart output directory
58
59   !
60   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  pwcp       !: pore water sediment data at given time-step
61   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  pwcp0      !: pore water sediment data at initial time
62   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  solcp      !: solid sediment data at given time-step
63   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  solcp0     !: solid sediment data at initial time
64   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  trc_dta
65   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  diff
66
67   !! * Shared module variables
68   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  pwcp_dta   !: pore water data at given time-step
69   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrm_dta !: rain data at at initial time
70   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrm     !: rain data at given time-step
71   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrg     !: rain of each solid component in [g/(cm**2.s)]
72   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  fromsed    !:
73   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  tosed      !:
74   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rloss      !:
75   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  tokbot       
76   !
77   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  temp       !: temperature
78   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  salt       !: salinity
79   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  press      !: pressure
80   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  raintg     !: total massic flux rained in each cell (sum of sol. comp.)
81   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  fecratio   !: Fe/C ratio in falling particles to the sediments
82   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzdep      !: total thickness of solid material rained [cm] in each cell
83   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  zkbot      !: total thickness of solid material rained [cm] in each cell
84   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  wacc       !: total thickness of solid material rained [cm] in each cell
85   !
86   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  hipor      !: [h+] in mol/kg*densSW
87   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  co3por     !: [co3--]solid sediment at initial time
88   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  dz3d       !:  ???
89   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  volw3d     !:  ???
90   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  vols3d     !:  ???
91
92
93   !! Chemistry
94   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  densSW 
95   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  borats 
96   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  calcon2
97   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akbs 
98   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak1s 
99   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak2s   
100   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akws 
101   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak12s 
102   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak1ps 
103   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak2ps 
104   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak3ps 
105   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak12ps 
106   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak123ps
107   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksis 
108   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksps 
109   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  sieqs
110   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aks3s
111   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akf3s
112   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  sulfats
113   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  fluorids
114
115   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  mol_wgt    !: molecular weight of solid sediment data
116 
117   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  trc_data    !: tracer data to share with sediment model
118   !! Geometry
119   INTEGER , PUBLIC, SAVE                          ::  jpoce, indoce !: Ocean points ( number/indices )
120   INTEGER , PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  iarroce       !: Computation of 1D array of sediments points
121   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  epkbot        !: ocean bottom layer thickness
122   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  gdepbot       !: Depth of the sediment
123   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzkbot        !: ocean bottom layer thickness in meters
124   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dz            !: sediment layers thickness
125   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por           !: porosity profile     
126   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por1          !: 1-por
127   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  volw          !: volume of pore water cell fraction
128   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  vols          !: volume of solid cell fraction
129   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  db            !: bioturbation ceofficient
130   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  irrig        !: bioturbation ceofficient
131   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  rdtsed        !:  sediment model time-step
132   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE :: sedligand
133   REAL(wp)  ::   dens               !: density of solid material
134   !! Inputs / Outputs
135   CHARACTER( len = 80 ), DIMENSION(jptrased  ) ::  sedtrcl
136   CHARACTER( len = 20 ), DIMENSION(jptrased  ) ::  sedtrcd , sedtrcu
137   CHARACTER( len = 80 ), DIMENSION(jpdia3dsed) ::  seddia3l 
138   CHARACTER( len = 20 ), DIMENSION(jpdia3dsed) ::  seddia3d, seddia3u
139   CHARACTER( len = 80 ), DIMENSION(jpdia2dsed) ::  seddia2l 
140   CHARACTER( len = 20 ), DIMENSION(jpdia2dsed) ::  seddia2d, seddia2u
141   !
142   REAL(wp), PUBLIC, DIMENSION(:,:,:,:), ALLOCATABLE ::  trcsedi
143   REAL(wp), PUBLIC, DIMENSION(:,:,:,:), ALLOCATABLE ::  flxsedi3d
144   REAL(wp), PUBLIC, DIMENSION(:,:,:  ), ALLOCATABLE ::  flxsedi2d
145
146   INTEGER, PUBLIC ::  numsed = 27    ! units
147
148   !! $Id$
149CONTAINS
150
151   INTEGER FUNCTION sed_alloc()
152      !!-------------------------------------------------------------------
153      !!                    *** ROUTINE sed_alloc ***
154      !!-------------------------------------------------------------------
155      USE lib_mpp, ONLY: ctl_stop
156      !!-------------------------------------------------------------------
157      !
158      ALLOCATE( trc_data(jpi,jpj,jpdta)                                   ,   &
159         &      epkbot(jpi,jpj), gdepbot(jpi,jpj)        ,   &
160         &      dz(jpksed)  , por(jpksed) , por1(jpksed)                  ,   &
161         &      volw(jpksed), vols(jpksed), rdtsed(jpksed)  ,   &
162         &      trcsedi  (jpi,jpj,jpksed,jptrased)                        ,   &
163         &      flxsedi3d(jpi,jpj,jpksed,jpdia3dsed)                      ,   &
164         &      flxsedi2d(jpi,jpj,jpdia2dsed)                             ,   &
165         &      mol_wgt(jpsol),                                           STAT=sed_alloc )
166
167      IF( sed_alloc /= 0 )   CALL ctl_stop( 'STOP', 'sed_alloc: failed to allocate arrays' )
168      !
169   END FUNCTION sed_alloc
170
171END MODULE sed
Note: See TracBrowser for help on using the repository browser.