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 5367 for branches/2015/dev_r5204_CNRS_PISCES_dcy/NEMOGCM/NEMO/TOP_SRC/trc.F90 – NEMO

Ignore:
Timestamp:
2015-06-05T13:34:40+02:00 (9 years ago)
Author:
cetlod
Message:

NEMOGCM_dev_r5204_CNRS_PISCES_dcy : merge in dev_r5171_CNRS_LIM3_seaicebgc

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5204_CNRS_PISCES_dcy/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r5236 r5367  
    3434   REAL(wp), PUBLIC                                                ::  areatot        !: total volume  
    3535   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  cvol           !: volume correction -degrad option-  
    36    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trn            !: traceur concentration for now time step 
    37    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  tra            !: traceur concentration for next time step 
    38    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trb            !: traceur concentration for before time step 
     36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trn            !: tracer concentration for now time step 
     37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  tra            !: tracer concentration for next time step 
     38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:)         ::  trb            !: tracer concentration for before time step 
     39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  trc_i          !: prescribed tracer concentration in sea ice for SBC 
     40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:  )         ::  trc_o          !: prescribed tracer concentration in ocean for SBC 
     41   INTEGER             , PUBLIC                                    ::  nn_ice_tr      !: handling of sea ice tracers 
    3942 
    4043   !! interpolated gradient 
     
    4447   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtrui          !: hor. gradient at u-points at top    ocean level 
    4548   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)           ::  gtrvi          !: hor. gradient at v-points at top    ocean level 
    46    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)             ::  qsr_mean       !: i-horizontal velocity average     [m/s] 
    4749    
    4850   !! passive tracers  (input and output) 
     
    5759   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_out  !: suffix of pass. tracer restart name (output) 
    5860   REAL(wp)            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::  rdttrc         !: vertical profile of passive tracer time step 
    59    LOGICAL             , PUBLIC                                    ::  ln_top_euler   !: boolean term for euler integration  
     61   LOGICAL             , PUBLIC                                    ::  ln_top_euler  !: boolean term for euler integration  
    6062   LOGICAL             , PUBLIC                                    ::  ln_trcdta      !: Read inputs data from files 
    6163   LOGICAL             , PUBLIC                                    ::  ln_trcdmp      !: internal damping flag 
    6264   LOGICAL             , PUBLIC                                    ::  ln_trcdmp_clo  !: internal damping flag on closed seas 
    63    INTEGER             , PUBLIC                                    ::  nittrc000      !: first time step of passive tracers model 
    64    LOGICAL             , PUBLIC                                    ::  l_trcdm2dc     !: Diurnal cycle for TOP 
     65   INTEGER             , PUBLIC                                    ::  nittrc000       !: first time step of passive tracers model 
     66 
     67   !! Information for the ice module for tracers 
     68   !! ------------------------------------------ 
     69   TYPE TRC_I_NML                    !--- Ice tracer namelist structure 
     70         REAL(wp)         :: trc_ratio  ! ice-ocean trc ratio 
     71         REAL(wp)         :: trc_prescr ! prescribed ice trc cc 
     72         CHARACTER(len=2) :: ctrc_o     ! choice of ocean trc cc 
     73   END TYPE 
     74 
     75   REAL(wp), DIMENSION(jptra), PUBLIC         :: trc_ice_ratio, & ! ice-ocean tracer ratio 
     76                                                 trc_ice_prescr   ! prescribed ice trc cc 
     77   CHARACTER(len=2), DIMENSION(jptra), PUBLIC :: cn_trc_o ! choice of ocean tracer cc 
    6578 
    6679   !! information for outputs 
     
    187200      ! 
    188201      ALLOCATE( trn(jpi,jpj,jpk,jptra), trb(jpi,jpj,jpk,jptra), tra(jpi,jpj,jpk,jptra),       &   
     202         &      trc_i(jpi,jpj,jptra)  , trc_o(jpi,jpj,jptra)                          ,       & 
    189203         &      gtru (jpi,jpj,jptra)  , gtrv (jpi,jpj,jptra)                          ,       & 
    190204         &      gtrui(jpi,jpj,jptra)  , gtrvi(jpi,jpj,jptra)                          ,       & 
    191205         &      cvol(jpi,jpj,jpk)     , rdttrc(jpk)           , trai(jptra)           ,       & 
    192206         &      ctrcnm(jptra)         , ctrcln(jptra)         , ctrcun(jptra)         ,       &  
    193          &      ln_trc_ini(jptra)     , ln_trc_wri(jptra) , qsr_mean(jpi,jpj)         ,  STAT = trc_alloc  )   
     207         &      ln_trc_ini(jptra)     , ln_trc_wri(jptra)                             ,  STAT = trc_alloc  )   
    194208 
    195209      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays') 
Note: See TracChangeset for help on using the changeset viewer.