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.
Changeset 10345 for NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/SED/sed.F90 – NEMO

Ignore:
Timestamp:
2018-11-21T11:25:53+01:00 (5 years ago)
Author:
smasson
Message:

dev_r10164_HPC09_ESIWACE_PREP_MERGE: merge with trunk@10344, see #2133

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/TOP/PISCES/SED/sed.F90

    r9124 r10345  
    77   !!        !  06-12  (C. Ethe)  Orignal 
    88   !!---------------------------------------------------------------------- 
    9 #if defined key_sed 
    10    !!---------------------------------------------------------------------- 
    11    !!   'key_sed'                                                  Sediment  
    12    !!---------------------------------------------------------------------- 
    139   USE par_sed 
     10   USE oce_sed 
    1411   USE in_out_manager 
     12 
    1513 
    1614   IMPLICIT NONE 
    1715   PUBLIC 
    1816 
    19    PUBLIC sed_alloc    
    20  
    21    USE dom_oce , ONLY :   nidom     =>   nidom          !: 
    22    USE dom_oce , ONLY :   glamt     =>   glamt          !: longitude of t-point (degre) 
    23    USE dom_oce , ONLY :   gphit     =>   gphit          !: latitude  of t-point (degre) 
    24    USE dom_oce , ONLY :   e3t_1d    =>   e3t_1d         !: reference depth of t-points (m) 
    25    USE dom_oce , ONLY :   mbkt      =>   mbkt           !: vertical index of the bottom last T- ocean level 
    26    USE dom_oce , ONLY :   tmask     =>   tmask          !: land/ocean mask at t-points 
    27    USE dom_oce , ONLY :   rdt       =>   rdt            !: time step for the dynamics 
    28    USE dom_oce , ONLY :   nyear     =>   nyear          !: Current year 
    29    USE dom_oce , ONLY :   nmonth    =>   nmonth         !: Current month 
    30    USE dom_oce , ONLY :   nday      =>   nday           !: Current day 
    31    USE dom_oce , ONLY :   ndastp    =>   ndastp         !: time step date in year/month/day aammjj 
    32    USE dom_oce , ONLY :   nday_year =>   nday_year      !: curent day counted from jan 1st of the current year 
    33    USE dom_oce , ONLY :   adatrj    =>   adatrj         !: number of elapsed days since the begining of the run 
    34    !                                !: it is the accumulated duration of previous runs 
    35    !                                !: that may have been run with different time steps. 
    36  
    37 #if ! defined key_sed_off 
    38  
    39    USE oce     , ONLY :  tsn        =>   tsn             !: pot. temperature (celsius) and salinity (psu) 
    40  
    41    USE trc     , ONLY :  trn        =>   trc             !: tracer  
    42    USE trc     , ONLY :  nwritetrc  =>   nwritetrc       !: outputs frequency of tracer model 
    43  
    44    USE p4zsink , ONLY :  sinking    =>   sinking         !: sinking flux for POC 
    45    USE p4zsink , ONLY :  sinking2   =>   sinking2        !: sinking flux for GOC 
    46    USE p4zsink , ONLY :  sinkcal    =>   sinkcal         !: sinking flux for calcite 
    47    USE p4zsink , ONLY :  sinksil    =>   sinksil         !: sinking flux for opal ( dsi ) 
    48  
    49    USE sms_pisces, ONLY : akb3      =>   akb3            !: Chemical constants   
    50    USE sms_pisces, ONLY : ak13      =>   ak13            !: Chemical constants   
    51    USE sms_pisces, ONLY : ak23      =>   ak23            !: Chemical constants   
    52    USE sms_pisces, ONLY : akw3      =>   akw3            !: Chemical constants   
    53    USE sms_pisces, ONLY : aksp      =>   aksp            !: Chemical constants   
    54    USE sms_pisces, ONLY : borat     =>   borat           !: Chemical constants ( borat )  
    55  
    56 #endif    
    57  
     17   PUBLIC sed_alloc 
    5818 
    5919   !! Namelist 
    60    REAL(wp), PUBLIC, DIMENSION(5) ::  reac                !: reactivity rc in  [l.mol-1.s-1] 
    6120   REAL(wp), PUBLIC               ::  reac_sil            !: reactivity of silicate in  [l.mol-1.s-1] 
    6221   REAL(wp), PUBLIC               ::  reac_clay           !: reactivity of clay in  [l.mol-1.s-1] 
    63    REAL(wp), PUBLIC               ::  reac_poc            !: reactivity of poc in  [l.mol-1.s-1] 
    64    REAL(wp), PUBLIC               ::  reac_no3            !: reactivity of no3 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] 
    6532   REAL(wp), PUBLIC               ::  reac_cal            !: reactivity of cal in  [l.mol-1.s-1] 
    66    REAL(wp), PUBLIC               ::  sat_sil             !: saturation concentration for silicate in [mol.l-1] 
    67    REAL(wp), PUBLIC               ::  sat_clay            !: saturation concentration for clay in [mol.l-1] 
     33   REAL(wp), PUBLIC               ::  adsnh4              !: adsorption coefficient of NH4 
     34   REAL(wp), PUBLIC               ::  ratligc             !: C/L ratio in POC 
    6835   REAL(wp), PUBLIC               ::  so2ut  
    6936   REAL(wp), PUBLIC               ::  srno3  
    7037   REAL(wp), PUBLIC               ::  spo4r  
    7138   REAL(wp), PUBLIC               ::  srDnit  
    72    REAL(wp), PUBLIC               ::  sthro2              !: threshold O2 concen. in [mol.l-1] 
    73    REAL(wp), PUBLIC               ::  pdb = 0.0112372     !: 13C/12C in PD Belemnite 
    74    REAL(wp), PUBLIC               ::  rc13P  = 0.980      !: 13C/12C in POC = rc13P*PDB 
    75    REAL(wp), PUBLIC               ::  rc13Ca = 1.001      !: 13C/12C in CaCO3 = rc13Ca*PDB 
    7639   REAL(wp), PUBLIC               ::  dtsed               !: sedimentation time step 
    77    REAL(wp), PUBLIC               ::  db                  !: bioturb coefficient in [cm2.s-1] 
    78  
     40   REAL(wp), PUBLIC               ::  dtsed2              !: sedimentation time step 
    7941   INTEGER , PUBLIC               ::  nitsed000 
    8042   INTEGER , PUBLIC               ::  nitsedend 
    81    INTEGER , PUBLIC               ::  nwrised 
    82    INTEGER , PUBLIC               ::  nfreq 
    83    REAL(wp), PUBLIC               ::  dens                !: density of solid material 
     43   INTEGER, PUBLIC                ::  nrseddt 
     44   REAL    , PUBLIC               ::  sedmask 
     45   REAL(wp), PUBLIC               ::  denssol                !: density of solid material 
     46   INTEGER , PUBLIC               ::  numrsr, numrsw   !: logical unit for sed restart (read and write) 
     47   LOGICAL , PUBLIC               ::  lrst_sed       !: logical to control the trc restart write 
     48   LOGICAL , PUBLIC               ::  ln_rst_sed  = .TRUE.     !: initialisation from a restart file or not 
     49   LOGICAL , PUBLIC               ::  ln_btbz     = .FALSE.    !: Depth variation of the bioturbation coefficient 
     50   LOGICAL , PUBLIC               ::  ln_irrig    = .FALSE.    !: iActivation of the bioirrigation 
     51   LOGICAL , PUBLIC               ::  ln_sed_2way = .FALSE.    !: 2 way coupling with PISCES 
     52   LOGICAL , PUBLIC               ::  ln_sediment_offline = .FALSE. !: Offline mode for sediment module 
     53   INTEGER             , PUBLIC   ::  nn_rstsed      !: control of the time step ( 0 or 1 ) for pass. tr. 
     54   INTEGER , PUBLIC               ::  nn_dtsed = 1   !: frequency of step on passive tracers 
     55   CHARACTER(len = 80) , PUBLIC   ::  cn_sedrst_in   !: suffix of pass. tracer restart name (input) 
     56   CHARACTER(len = 256), PUBLIC   ::  cn_sedrst_indir  !: restart input directory 
     57   CHARACTER(len = 80) , PUBLIC   ::  cn_sedrst_out  !: suffix of pass. tracer restart name (output) 
     58   CHARACTER(len = 256), PUBLIC   ::  cn_sedrst_outdir  !: restart output directory 
     59 
    8460   ! 
    8561   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  pwcp       !: pore water sediment data at given time-step 
     
    8763   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  solcp      !: solid sediment data at given time-step 
    8864   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  solcp0     !: solid sediment data at initial time 
     65   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  trc_dta 
     66   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  diff 
    8967 
    9068   !! * Shared module variables 
     
    10280   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  press      !: pressure 
    10381   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  raintg     !: total massic flux rained in each cell (sum of sol. comp.) 
     82   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  fecratio   !: Fe/C ratio in falling particles to the sediments 
    10483   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzdep      !: total thickness of solid material rained [cm] in each cell 
     84   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  zkbot      !: total thickness of solid material rained [cm] in each cell 
     85   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  wacc       !: total thickness of solid material rained [cm] in each cell 
    10586   ! 
    10687   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  hipor      !: [h+] in mol/kg*densSW  
     
    127108   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksis  
    128109   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aksps  
     110   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  sieqs 
     111   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  aks3s 
     112   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  akf3s 
     113   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  sulfats 
     114   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  fluorids 
    129115 
    130116   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  mol_wgt    !: molecular weight of solid sediment data 
     
    133119   !! Geometry 
    134120   INTEGER , PUBLIC, SAVE                          ::  jpoce, indoce !: Ocean points ( number/indices ) 
    135    REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  iarroce       !: Computation of 1D array of sediments points 
     121   INTEGER , PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  iarroce       !: Computation of 1D array of sediments points 
    136122   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  epkbot        !: ocean bottom layer thickness 
     123   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  gdepbot       !: Depth of the sediment 
    137124   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dzkbot        !: ocean bottom layer thickness in meters 
    138    REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::  tmasksed      !: sediment mask 
    139    REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  sbathy        !: bathymetry 
    140125   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  dz            !: sediment layers thickness 
    141126   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por           !: porosity profile      
    142127   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  por1          !: 1-por  
    143    REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  profsed       !: depth of middle of each layer 
    144128   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  volw          !: volume of pore water cell fraction 
    145129   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  vols          !: volume of solid cell fraction 
    146    REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  diff          !: diffusion ceofficient 
     130   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  db            !: bioturbation ceofficient 
     131   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE ::  irrig        !: bioturbation ceofficient 
    147132   REAL(wp), PUBLIC, DIMENSION(:    ), ALLOCATABLE ::  rdtsed        !:  sediment model time-step 
     133   REAL(wp), PUBLIC, DIMENSION(:,:  ), ALLOCATABLE :: sedligand 
    148134   REAL(wp)  ::   dens               !: density of solid material 
    149135   !! Inputs / Outputs 
     
    171157      !!------------------------------------------------------------------- 
    172158      ! 
    173       ALLOCATE( trc_dta(jpi,jpj,jdta)                                     ,   & 
    174          &      epkbot(jpi,jpj), sbathy(jpi,jpj)                          ,   & 
    175          &      tmasksed(jpi,jpj,jpksed)                                  ,   & 
    176          &      dz(jpksed)  , por(jpksed) , por1(jpksed), profsed(jpksed) ,   & 
    177          &      volw(jpksed), vols(jpksed), diff(jpksed), rdtsed(jpksed)  ,   & 
     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)  ,   & 
    178163         &      trcsedi  (jpi,jpj,jpksed,jptrased)                        ,   & 
    179164         &      flxsedi3d(jpi,jpj,jpksed,jpdia3dsed)                      ,   & 
    180          &      flxsedi2d(jpi,jpj,jpksed,jpdia2dsed)                      ,   & 
     165         &      flxsedi2d(jpi,jpj,jpdia2dsed)                             ,   & 
    181166         &      mol_wgt(jpsol),                                           STAT=sed_alloc ) 
    182167 
     
    185170   END FUNCTION sed_alloc 
    186171 
    187 #else 
    188    !!====================================================================== 
    189    !! No Sediment model 
    190    !!====================================================================== 
    191 #endif 
    192  
    193172END MODULE sed 
Note: See TracChangeset for help on using the changeset viewer.