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 5325 for branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90 – NEMO

Ignore:
Timestamp:
2015-06-01T12:00:26+02:00 (9 years ago)
Author:
aumont
Message:

various bugfixes and code changes

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5171_CNRS_LIM3_seaicebgc/NEMOGCM/NEMO/TOP_SRC/TRP/trcsbc.F90

    r5195 r5325  
    2828 
    2929   PUBLIC   trc_sbc   ! routine called by step.F90 
     30 
     31   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt  ! vertical profile time-step, = 2 rdttra 
    3032 
    3133   !! * Substitutions 
     
    6365      ! 
    6466      INTEGER  ::   ji, jj, jn                                     ! dummy loop indices 
    65       REAL(wp) ::   zse3t                                          ! temporary scalars 
     67      REAL(wp) ::   zse3t, zrtrn, zratio                           ! temporary scalars 
    6668      REAL(wp) ::   zswitch, zftra, zcd, zdtra, ztfx, ztra         ! temporary scalars 
    6769      CHARACTER (len=22) :: charout 
     
    7678                      CALL wrk_alloc( jpi, jpj,      zsfx   ) 
    7779      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrd ) 
     80      ! 
     81      zrtrn = 1.e-15_wp 
    7882 
    7983      SELECT CASE( nn_ice_embd )         ! levitating or embedded sea-ice option 
     
    8286                                         ! (2) embedded sea-ice : salt and volume fluxes and pressure 
    8387      END SELECT 
     88 
     89      IF( ln_top_euler) THEN 
     90         r2dt(:) =  rdttrc(:)              ! = rdttrc (use Euler time stepping) 
     91      ELSE 
     92         IF( neuler == 0 .AND. kt == nittrc000 ) THEN     ! at nittrc000 
     93            r2dt(:) =  rdttrc(:)           ! = rdttrc (restarting with Euler time stepping) 
     94         ELSEIF( kt <= nittrc000 + 1 ) THEN          ! at nittrc000 or nittrc000+1 
     95            r2dt(:) = 2. * rdttrc(:)       ! = 2 rdttrc (leapfrog) 
     96         ENDIF 
     97      ENDIF 
     98 
    8499 
    85100      IF( kt == nittrc000 ) THEN 
     
    99114      ENDIF 
    100115 
    101       WRITE(numout,*) ' trc_sbc initial values', trn(3,2,1,2), trb(3,2,1,2), tra(3,2,1,2) 
    102  
    103116      ! 0. initialization 
    104117      DO jn = 1, jptra 
     
    107120         !                                             ! add the trend to the general tracer trend 
    108121 
    109          IF ( nn_ice_tr == -1 ) THEN  ! identical concentrations in ice and ocean (old code) 
     122         IF ( nn_ice_tr == -1 ) THEN  ! No tracers in sea ice (null concentration in sea ice) 
    110123 
    111124            DO jj = 2, jpj 
    112125               DO ji = fs_2, fs_jpim1   ! vector opt. 
    113126                  zse3t = 1. / fse3t(ji,jj,1) 
    114                   tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) * r1_rau0 * trn(ji,jj,1,jn) * zse3t 
     127                  tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zsfx(ji,jj) * r1_rau0 * trb(ji,jj,1,jn) * zse3t 
    115128               END DO 
    116129            END DO 
     
    131144                  ztfx  = zftra + zswitch * zcd                ! net tracer flux (+C/D if no ice/ocean mass exchange) 
    132145    
    133                   zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trn(ji,jj,1,jn) ) * zse3t 
    134                   tra(ji,jj,1,jn) = MAX( tra(ji,jj,1,jn) + zdtra, 0.) ! avoid integral ocean uptake if freezing (for iron) 
     146                  zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * trb(ji,jj,1,jn) ) * zse3t 
     147                  IF ( zdtra < 0. ) THEN 
     148                     zratio = -zdtra * r2dt(1) / ( trb(ji,jj,1,jn) + zrtrn ) 
     149                     zdtra = MIN(1.0, zratio) * zdtra ! avoid negative concentrations to arise 
     150                  ENDIF 
     151                       
     152                  tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + zdtra  
    135153    
    136154               END DO 
Note: See TracChangeset for help on using the changeset viewer.