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 11949 for NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcsbc.F90 – NEMO

Ignore:
Timestamp:
2019-11-22T15:29:17+01:00 (4 years ago)
Author:
acc
Message:

Merge in changes from 2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps. This just creates a fresh copy of this branch to use as the merge base. See ticket #2341

Location:
NEMO/branches/2019/dev_r11943_MERGE_2019/src
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src

    • Property svn:mergeinfo deleted
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcsbc.F90

    r10788 r11949  
    3737CONTAINS 
    3838 
    39    SUBROUTINE trc_sbc ( kt ) 
     39   SUBROUTINE trc_sbc ( kt, Kmm, ptr, Krhs ) 
    4040      !!---------------------------------------------------------------------- 
    4141      !!                  ***  ROUTINE trc_sbc  *** 
     
    4949      !!            The surface freshwater flux modify the ocean volume 
    5050      !!         and thus the concentration of a tracer as : 
    51       !!            tra = tra + emp * trn / e3t   for k=1 
     51      !!            tr(Krhs) = tr(Krhs) + emp * tr(Kmm) / e3t   for k=1 
    5252      !!         where emp, the surface freshwater budget (evaporation minus 
    5353      !!         precipitation ) given in kg/m2/s is divided 
    5454      !!         by 1035 kg/m3 (density of ocean water) to obtain m/s. 
    5555      !! 
    56       !! ** Action  : - Update the 1st level of tra with the trend associated 
     56      !! ** Action  : - Update the 1st level of tr(:,:,:,:,Krhs) with the trend associated 
    5757      !!                with the tracer surface boundary condition  
    5858      !! 
    5959      !!---------------------------------------------------------------------- 
    60       INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     60      INTEGER,                                    INTENT(in   ) :: kt        ! ocean time-step index 
     61      INTEGER,                                    INTENT(in   ) :: Kmm, Krhs ! time level indices 
     62      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr       ! passive tracers and RHS of tracer equation 
    6163      ! 
    6264      INTEGER  ::   ji, jj, jn                      ! dummy loop indices 
     
    8284         IF( ln_rsttr .AND. .NOT.ln_top_euler .AND.   &                     ! Restart: read in restart  file 
    8385            iom_varid( numrtr, 'sbc_'//TRIM(ctrcnm(1))//'_b', ldstop = .FALSE. ) > 0 ) THEN 
    84             IF(lwp) WRITE(numout,*) '          nittrc000-nn_dttrc surface tracer content forcing fields red in the restart file' 
     86            IF(lwp) WRITE(numout,*) '          nittrc000-1 surface tracer content forcing fields read in the restart file' 
    8587            zfact = 0.5_wp 
    8688            DO jn = 1, jptra 
     
    102104      ENDIF 
    103105 
    104       ! Coupling online : river runoff is added to the horizontal divergence (hdivn) in the subroutine sbc_rnf_div  
     106      ! Coupling online : river runoff is added to the horizontal divergence (hdiv) in the subroutine sbc_rnf_div  
    105107      ! one only consider the concentration/dilution effect due to evaporation minus precipitation + freezing/melting of sea-ice 
    106108      ! Coupling offline : runoff are in emp which contains E-P-R 
     
    120122            DO jj = 2, jpj 
    121123               DO ji = fs_2, fs_jpim1   ! vector opt. 
    122                   sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * trn(ji,jj,1,jn) 
     124                  sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * ptr(ji,jj,1,jn,Kmm) 
    123125               END DO 
    124126            END DO 
     
    130132            DO jj = 2, jpj 
    131133               DO ji = fs_2, fs_jpim1   ! vector opt. 
    132                   sbc_trc(ji,jj,jn) = ( zsfx(ji,jj) + fmmflx(ji,jj) ) * r1_rau0 * trn(ji,jj,1,jn) 
     134                  sbc_trc(ji,jj,jn) = ( zsfx(ji,jj) + fmmflx(ji,jj) ) * r1_rau0 * ptr(ji,jj,1,jn,Kmm) 
    133135               END DO 
    134136            END DO 
     
    140142            DO jj = 2, jpj 
    141143               DO ji = fs_2, fs_jpim1   ! vector opt. 
    142                   zse3t = 1. / e3t_n(ji,jj,1) 
     144                  zse3t = 1. / e3t(ji,jj,1,Kmm) 
    143145                  ! tracer flux at the ice/ocean interface (tracer/m2/s) 
    144146                  zftra = - trc_i(ji,jj,jn) * fmmflx(ji,jj) ! uptake of tracer in the sea ice 
     
    148150                  ztfx  = zftra                        ! net tracer flux 
    149151                  ! 
    150                   zdtra = r1_rau0 * ( ztfx + ( zsfx(ji,jj) + fmmflx(ji,jj) ) * trn(ji,jj,1,jn) )  
     152                  zdtra = r1_rau0 * ( ztfx + ( zsfx(ji,jj) + fmmflx(ji,jj) ) * ptr(ji,jj,1,jn,Kmm) )  
    151153                  IF ( zdtra < 0. ) THEN 
    152                      zdtra  = MAX(zdtra, -trn(ji,jj,1,jn) * e3t_n(ji,jj,1) / r2dttrc )   ! avoid negative concentrations to arise 
     154                     zdtra  = MAX(zdtra, -ptr(ji,jj,1,jn,Kmm) * e3t(ji,jj,1,Kmm) / r2dttrc )   ! avoid negative concentrations to arise 
    153155                  ENDIF 
    154156                  sbc_trc(ji,jj,jn) =  zdtra  
     
    162164      DO jn = 1, jptra 
    163165         ! 
    164          IF( l_trdtrc )   ztrtrd(:,:,:) = tra(:,:,:,jn)  ! save trends 
     166         IF( l_trdtrc )   ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs)  ! save trends 
    165167         ! 
    166168         DO jj = 2, jpj 
    167169            DO ji = fs_2, fs_jpim1   ! vector opt. 
    168                zse3t = zfact / e3t_n(ji,jj,1) 
    169                tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t 
     170               zse3t = zfact / e3t(ji,jj,1,Kmm) 
     171               ptr(ji,jj,1,jn,Krhs) = ptr(ji,jj,1,jn,Krhs) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t 
    170172            END DO 
    171173         END DO 
    172174         ! 
    173175         IF( l_trdtrc ) THEN 
    174             ztrtrd(:,:,:) = tra(:,:,:,jn) - ztrtrd(:,:,:) 
    175             CALL trd_tra( kt, 'TRC', jn, jptra_nsr, ztrtrd ) 
     176            ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs) - ztrtrd(:,:,:) 
     177            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_nsr, ztrtrd ) 
    176178         END IF 
    177179         !                                                       ! =========== 
     
    193195      IF( ln_ctl )   THEN 
    194196         WRITE(charout, FMT="('sbc ')") ;  CALL prt_ctl_trc_info(charout) 
    195                                            CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     197                                           CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    196198      ENDIF 
    197199      IF( l_trdtrc )  DEALLOCATE( ztrtrd ) 
     
    205207   !!   Dummy module :                      NO passive tracer 
    206208   !!---------------------------------------------------------------------- 
     209   USE par_oce 
     210   USE par_trc 
    207211CONTAINS 
    208    SUBROUTINE trc_sbc (kt)              ! Empty routine 
    209       INTEGER, INTENT(in) :: kt 
     212   SUBROUTINE trc_sbc ( kt, Kmm, ptr, Krhs )      ! Empty routine 
     213      INTEGER,                                    INTENT(in   ) :: kt        ! ocean time-step index 
     214      INTEGER,                                    INTENT(in   ) :: Kmm, Krhs ! time level indices 
     215      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr       ! passive tracers and RHS of tracer equation 
    210216      WRITE(*,*) 'trc_sbc: You should not have seen this print! error?', kt 
    211217   END SUBROUTINE trc_sbc 
Note: See TracChangeset for help on using the changeset viewer.