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/TRP/trcsbc.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/TRP/trcsbc.F90

    r4990 r5367  
    2626 
    2727   PUBLIC   trc_sbc   ! routine called by step.F90 
     28 
     29   REAL(wp) ::   r2dt  !  time-step at surface 
    2830 
    2931   !! * Substitutions 
     
    6062      INTEGER, INTENT( in ) ::   kt          ! ocean time-step index 
    6163      ! 
    62       INTEGER  ::   ji, jj, jn           ! dummy loop indices 
    63       REAL(wp) ::   zsrau, zse3t   ! temporary scalars 
     64      INTEGER  ::   ji, jj, jn                                     ! dummy loop indices 
     65      REAL(wp) ::   zse3t, zrtrn, zratio                           ! temporary scalars 
     66      REAL(wp) ::   zswitch, zftra, zcd, zdtra, ztfx, ztra         ! temporary scalars 
    6467      CHARACTER (len=22) :: charout 
    6568      REAL(wp), POINTER, DIMENSION(:,:  ) :: zsfx 
    6669      REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrtrd 
     70 
    6771      !!--------------------------------------------------------------------- 
    6872      ! 
     
    7276                      CALL wrk_alloc( jpi, jpj,      zsfx   ) 
    7377      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrd ) 
     78      ! 
     79      zrtrn = 1.e-15_wp 
     80 
     81      SELECT CASE( nn_ice_embd )         ! levitating or embedded sea-ice option 
     82         CASE( 0    )   ;   zswitch = 1  ! (0) standard levitating sea-ice : salt exchange only 
     83         CASE( 1, 2 )   ;   zswitch = 0  ! (1) levitating sea-ice: salt and volume exchange but no pressure effect                                 
     84                                         ! (2) embedded sea-ice : salt and volume fluxes and pressure 
     85      END SELECT 
     86 
     87      IF( ln_top_euler) THEN 
     88         r2dt =  rdttrc(1)              ! = rdttrc (use Euler time stepping) 
     89      ELSE 
     90         IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
     91            r2dt = rdttrc(1)           ! = rdttrc (restarting with Euler time stepping) 
     92         ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1 
     93            r2dt = 2. * rdttrc(1)       ! = 2 rdttrc (leapfrog) 
     94         ENDIF 
     95      ENDIF 
     96 
    7497 
    7598      IF( kt == nittrc000 ) THEN 
     
    90113 
    91114      ! 0. initialization 
    92       zsrau = 1. / rau0 
    93115      DO jn = 1, jptra 
    94116         ! 
    95117         IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)  ! save trends 
    96118         !                                             ! add the trend to the general tracer trend 
    97          DO jj = 2, jpj 
    98             DO ji = fs_2, fs_jpim1   ! vector opt. 
    99                zse3t = 1. / fse3t(ji,jj,1) 
    100                tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) *  zsrau * trn(ji,jj,1,jn) * zse3t 
     119 
     120         IF ( nn_ice_tr == -1 ) THEN  ! No tracers in sea ice (null concentration in sea ice) 
     121 
     122            DO jj = 2, jpj 
     123               DO ji = fs_2, fs_jpim1   ! vector opt. 
     124                  zse3t = 1. / fse3t(ji,jj,1) 
     125                  tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) * r1_rau0 * trn(ji,jj,1,jn) * zse3t 
     126               END DO 
    101127            END DO 
    102          END DO 
     128 
     129         ELSE 
     130 
     131            DO jj = 2, jpj 
     132               DO ji = fs_2, fs_jpim1   ! vector opt. 
     133 
     134                  zse3t = 1. / fse3t(ji,jj,1) 
     135                   
     136                  ! tracer flux at the ice/ocean interface (tracer/m2/s) 
     137                  zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 
     138                  zcd   =   trc_o(ji,jj,jn) * fmmflx(ji,jj) ! concentration dilution due to freezing-melting, 
     139                                                               ! only used in the levitating sea ice case 
     140                  ! tracer flux only       : add concentration dilution term in net tracer flux, no F-M in volume flux 
     141                  ! tracer and mass fluxes : no concentration dilution term in net tracer flux, F-M term in volume flux 
     142                  ztfx  = zftra + zswitch * zcd                ! net tracer flux (+C/D if no ice/ocean mass exchange) 
     143    
     144                  zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trn(ji,jj,1,jn) ) * zse3t 
     145                  IF ( zdtra < 0. ) THEN 
     146                     zratio = -zdtra * r2dt / ( trn(ji,jj,1,jn) + zrtrn ) 
     147                     zdtra = MIN(1.0, zratio) * zdtra ! avoid negative concentrations to arise 
     148                  ENDIF 
     149                       
     150                  tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zdtra  
     151    
     152               END DO 
     153            END DO 
     154    
     155         ENDIF 
    103156          
    104157         IF( l_trdtrc ) THEN 
Note: See TracChangeset for help on using the changeset viewer.