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 branches/UKMO/r5518_rm_um_cpl/NEMOGCM/NEMO/TOP_SRC/PISCES/SED – NEMO

source: branches/UKMO/r5518_rm_um_cpl/NEMOGCM/NEMO/TOP_SRC/PISCES/SED/sed.F90 @ 7141

Last change on this file since 7141 was 7141, checked in by jcastill, 7 years ago

Remove svn keywords

File size: 11.4 KB
Line 
1MODULE sed
2   !!======================================================================
3   !!                        ***  sed  ***
4   !! Sediment :   set sediment global variables
5   !!======================================================================
6#if defined key_sed
7   !! History :
8   !!        !  06-12  (C. Ethe)  Orignal
9   !!----------------------------------------------------------------------
10   USE par_sed
11   USE in_out_manager
12
13   IMPLICIT NONE
14   PUBLIC
15
16   PUBLIC sed_alloc   
17
18   USE dom_oce , ONLY :   nidom     =>   nidom          !:
19   USE dom_oce , ONLY :   glamt     =>   glamt          !: longitude of t-point (degre)
20   USE dom_oce , ONLY :   gphit     =>   gphit          !: latitude  of t-point (degre)
21   USE dom_oce , ONLY :   e3t_1d    =>   e3t_1d         !: reference depth of t-points (m)
22   USE dom_oce , ONLY :   mbkt      =>   mbkt           !: vertical index of the bottom last T- ocean level
23   USE dom_oce , ONLY :   tmask     =>   tmask          !: land/ocean mask at t-points
24   USE dom_oce , ONLY :   rdt       =>   rdt            !: time step for the dynamics
25   USE dom_oce , ONLY :   nyear     =>   nyear          !: Current year
26   USE dom_oce , ONLY :   nmonth    =>   nmonth         !: Current month
27   USE dom_oce , ONLY :   nday      =>   nday           !: Current day
28   USE dom_oce , ONLY :   ndastp    =>   ndastp         !: time step date in year/month/day aammjj
29   USE dom_oce , ONLY :   nday_year =>   nday_year      !: curent day counted from jan 1st of the current year
30   USE dom_oce , ONLY :   adatrj    =>   adatrj         !: number of elapsed days since the begining of the run
31   !                                !: it is the accumulated duration of previous runs
32   !                                !: that may have been run with different time steps.
33
34#if ! defined key_sed_off
35
36   USE oce     , ONLY :  tsn        =>   tsn             !: pot. temperature (celsius) and salinity (psu)
37
38   USE trc     , ONLY :  trn        =>   trc             !: tracer
39   USE trc     , ONLY :  nwritetrc  =>   nwritetrc       !: outputs frequency of tracer model
40
41   USE p4zsink , ONLY :  sinking    =>   sinking         !: sinking flux for POC
42#if ! defined key_kriest
43   USE p4zsink , ONLY :  sinking2   =>   sinking2        !: sinking flux for GOC
44#endif
45   USE p4zsink , ONLY :  sinkcal    =>   sinkcal         !: sinking flux for calcite
46   USE p4zsink , ONLY :  sinksil    =>   sinksil         !: sinking flux for opal ( dsi )
47
48   USE sms_pisces, ONLY : akb3      =>   akb3            !: Chemical constants 
49   USE sms_pisces, ONLY : ak13      =>   ak13            !: Chemical constants 
50   USE sms_pisces, ONLY : ak23      =>   ak23            !: Chemical constants 
51   USE sms_pisces, ONLY : akw3      =>   akw3            !: Chemical constants 
52   USE sms_pisces, ONLY : aksp      =>   aksp            !: Chemical constants 
53   USE sms_pisces, ONLY : borat     =>   borat           !: Chemical constants ( borat )
54
55#endif   
56
57
58   !! Namelist
59   REAL(wp), PUBLIC, DIMENSION(5) ::  reac                !: reactivity rc in  [l.mol-1.s-1]
60   REAL(wp), PUBLIC               ::  reac_sil            !: reactivity of silicate in  [l.mol-1.s-1]
61   REAL(wp), PUBLIC               ::  reac_clay           !: reactivity of clay in  [l.mol-1.s-1]
62   REAL(wp), PUBLIC               ::  reac_poc            !: reactivity of poc in  [l.mol-1.s-1]
63   REAL(wp), PUBLIC               ::  reac_no3            !: reactivity of no3 in  [l.mol-1.s-1]
64   REAL(wp), PUBLIC               ::  reac_cal            !: reactivity of cal in  [l.mol-1.s-1]
65   REAL(wp), PUBLIC               ::  sat_sil             !: saturation concentration for silicate in [mol.l-1]
66   REAL(wp), PUBLIC               ::  sat_clay            !: saturation concentration for clay in [mol.l-1]
67   REAL(wp), PUBLIC               ::  so2ut 
68   REAL(wp), PUBLIC               ::  srno3 
69   REAL(wp), PUBLIC               ::  spo4r 
70   REAL(wp), PUBLIC               ::  srDnit 
71   REAL(wp), PUBLIC               ::  sthro2              !: threshold O2 concen. in [mol.l-1]
72   REAL(wp), PUBLIC               ::  pdb = 0.0112372     !: 13C/12C in PD Belemnite
73   REAL(wp), PUBLIC               ::  rc13P  = 0.980      !: 13C/12C in POC = rc13P*PDB
74   REAL(wp), PUBLIC               ::  rc13Ca = 1.001      !: 13C/12C in CaCO3 = rc13Ca*PDB
75   REAL(wp), PUBLIC               ::  dtsed               !: sedimentation time step
76   REAL(wp), PUBLIC               ::  db                  !: bioturb coefficient in [cm2.s-1]
77
78   INTEGER , PUBLIC               ::  nitsed000
79   INTEGER , PUBLIC               ::  nitsedend
80   INTEGER , PUBLIC               ::  nwrised
81   INTEGER , PUBLIC               ::  nfreq
82   REAL(wp), PUBLIC               ::  dens                !: density of solid material
83   !
84   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  pwcp       !: pore water sediment data at given time-step
85   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  pwcp0      !: pore water sediment data at initial time
86   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  solcp      !: solid sediment data at given time-step
87   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  solcp0     !: solid sediment data at initial time
88
89   !! * Shared module variables
90   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  pwcp_dta   !: pore water data at given time-step
91   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrm_dta !: rain data at at initial time
92   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrm     !: rain data at given time-step
93   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rainrg     !: rain of each solid component in [g/(cm**2.s)]
94   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  fromsed    !:
95   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  tosed      !:
96   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  rloss      !:
97   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  tokbot       
98   !
99   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  temp       !: temperature
100   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  salt       !: salinity
101   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  press      !: pressure
102   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  raintg     !: total massic flux rained in each cell (sum of sol. comp.)
103   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzdep      !: total thickness of solid material rained [cm] in each cell
104   !
105   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  hipor      !: [h+] in mol/kg*densSW
106   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  co3por     !: [co3--]solid sediment at initial time
107   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  dz3d       !:  ???
108   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  volw3d     !:  ???
109   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  vols3d     !:  ???
110
111
112   !! Chemistry
113   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  densSW 
114   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  borats 
115   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  calcon2
116   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akbs 
117   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak1s 
118   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak2s   
119   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akws 
120   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak12s 
121   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak1ps 
122   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak2ps 
123   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak3ps 
124   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak12ps 
125   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  ak123ps
126   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksis 
127   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksps 
128
129   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  mol_wgt    !: molecular weight of solid sediment data
130 
131   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  trc_data    !: tracer data to share with sediment model
132   !! Geometry
133   INTEGER , PUBLIC, SAVE                          ::  jpoce, indoce !: Ocean points ( number/indices )
134   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  iarroce       !: Computation of 1D array of sediments points
135   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  epkbot        !: ocean bottom layer thickness
136   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzkbot        !: ocean bottom layer thickness in meters
137   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  tmasksed      !: sediment mask
138   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  sbathy        !: bathymetry
139   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dz            !: sediment layers thickness
140   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por           !: porosity profile     
141   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por1          !: 1-por
142   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  profsed       !: depth of middle of each layer
143   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  volw          !: volume of pore water cell fraction
144   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  vols          !: volume of solid cell fraction
145   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  diff          !: diffusion ceofficient
146   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  rdtsed        !:  sediment model time-step
147   REAL(wp)  ::   dens               !: density of solid material
148   !! Inputs / Outputs
149   CHARACTER( len = 80 ), DIMENSION(jptrased  ) ::  sedtrcl
150   CHARACTER( len = 20 ), DIMENSION(jptrased  ) ::  sedtrcd , sedtrcu
151   CHARACTER( len = 80 ), DIMENSION(jpdia3dsed) ::  seddia3l 
152   CHARACTER( len = 20 ), DIMENSION(jpdia3dsed) ::  seddia3d, seddia3u
153   CHARACTER( len = 80 ), DIMENSION(jpdia2dsed) ::  seddia2l 
154   CHARACTER( len = 20 ), DIMENSION(jpdia2dsed) ::  seddia2d, seddia2u
155   !
156   REAL(wp), PUBLIC, DIMENSION(:,:,:,:), ALLOCATABLE ::  trcsedi
157   REAL(wp), PUBLIC, DIMENSION(:,:,:,:), ALLOCATABLE ::  flxsedi3d
158   REAL(wp), PUBLIC, DIMENSION(:,:,:  ), ALLOCATABLE ::  flxsedi2d
159
160   INTEGER, PUBLIC ::  numsed = 27    ! units
161
162   !! $Id$
163CONTAINS
164
165   INTEGER FUNCTION sed_alloc()
166      !!-------------------------------------------------------------------
167      !!                    *** ROUTINE sed_alloc ***
168      !!-------------------------------------------------------------------
169      USE lib_mpp, ONLY: ctl_warn
170      !!-------------------------------------------------------------------
171      !
172      ALLOCATE( trc_dta(jpi,jpj,jdta)                                     ,   &
173         &      epkbot(jpi,jpj), sbathy(jpi,jpj)                          ,   &
174         &      tmasksed(jpi,jpj,jpksed)                                  ,   &
175         &      dz(jpksed)  , por(jpksed) , por1(jpksed), profsed(jpksed) ,   &
176         &      volw(jpksed), vols(jpksed), diff(jpksed), rdtsed(jpksed)  ,   &
177         &      trcsedi  (jpi,jpj,jpksed,jptrased)                        ,   &
178         &      flxsedi3d(jpi,jpj,jpksed,jpdia3dsed)                      ,   &
179         &      flxsedi2d(jpi,jpj,jpksed,jpdia2dsed)                      ,   &
180         &      mol_wgt(jpsol),                                           STAT=sed_alloc )
181
182      IF( sed_alloc /= 0 )   CALL ctl_warn('sed_alloc: failed to allocate arrays')
183      !
184   END FUNCTION sed_alloc
185
186#else
187   !!======================================================================
188   !! No Sediment model
189   !!======================================================================
190#endif
191
192END MODULE sed
Note: See TracBrowser for help on using the repository browser.