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 10985 for NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcsbc.F90 – NEMO

Ignore:
Timestamp:
2019-05-15T21:19:35+02:00 (5 years ago)
Author:
acc
Message:

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : interface changes to tra and trc routines for design compliance and consistency. Fully SETTE tested (non-AGRIF, only)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcsbc.F90

    r10966 r10985  
    3737CONTAINS 
    3838 
    39    SUBROUTINE trc_sbc ( kt, Kmm, Krhs ) 
     39   SUBROUTINE trc_sbc ( kt, Kmm, ptr, Krhs ) 
    4040      !!---------------------------------------------------------------------- 
    4141      !!                  ***  ROUTINE trc_sbc  *** 
     
    5858      !! 
    5959      !!---------------------------------------------------------------------- 
    60       INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    61       INTEGER, INTENT(in) ::   Kmm, Krhs  ! time level indices 
     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 
    6263      ! 
    6364      INTEGER  ::   ji, jj, jn                      ! dummy loop indices 
     
    119120            DO jj = 2, jpj 
    120121               DO ji = fs_2, fs_jpim1   ! vector opt. 
    121                   sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * tr(ji,jj,1,jn,Kmm) 
     122                  sbc_trc(ji,jj,jn) = zsfx(ji,jj) * r1_rau0 * ptr(ji,jj,1,jn,Kmm) 
    122123               END DO 
    123124            END DO 
     
    138139                  ztfx  = zftra                             ! net tracer flux 
    139140                  ! 
    140                   zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * tr(ji,jj,1,jn,Kmm) )  
     141                  zdtra = r1_rau0 * ( ztfx + zsfx(ji,jj) * ptr(ji,jj,1,jn,Kmm) )  
    141142                  IF ( zdtra < 0. ) THEN 
    142                      zratio = -zdtra * zse3t * r2dttrc / ( tr(ji,jj,1,jn,Kmm) + zrtrn ) 
     143                     zratio = -zdtra * zse3t * r2dttrc / ( ptr(ji,jj,1,jn,Kmm) + zrtrn ) 
    143144                     zdtra = MIN(1.0, zratio) * zdtra ! avoid negative concentrations to arise 
    144145                  ENDIF 
     
    153154      DO jn = 1, jptra 
    154155         ! 
    155          IF( l_trdtrc )   ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs)  ! save trends 
     156         IF( l_trdtrc )   ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs)  ! save trends 
    156157         ! 
    157158         DO jj = 2, jpj 
    158159            DO ji = fs_2, fs_jpim1   ! vector opt. 
    159160               zse3t = zfact / e3t(ji,jj,1,Kmm) 
    160                tr(ji,jj,1,jn,Krhs) = tr(ji,jj,1,jn,Krhs) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t 
     161               ptr(ji,jj,1,jn,Krhs) = ptr(ji,jj,1,jn,Krhs) + ( sbc_trc_b(ji,jj,jn) + sbc_trc(ji,jj,jn) ) * zse3t 
    161162            END DO 
    162163         END DO 
    163164         ! 
    164165         IF( l_trdtrc ) THEN 
    165             ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs) - ztrtrd(:,:,:) 
     166            ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs) - ztrtrd(:,:,:) 
    166167            CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_nsr, ztrtrd ) 
    167168         END IF 
     
    184185      IF( ln_ctl )   THEN 
    185186         WRITE(charout, FMT="('sbc ')") ;  CALL prt_ctl_trc_info(charout) 
    186                                            CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     187                                           CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    187188      ENDIF 
    188189      IF( l_trdtrc )  DEALLOCATE( ztrtrd ) 
     
    197198   !!---------------------------------------------------------------------- 
    198199CONTAINS 
    199    SUBROUTINE trc_sbc (kt)              ! Empty routine 
    200       INTEGER, INTENT(in) :: kt 
     200   SUBROUTINE trc_sbc ( kt, Kmm, ptr, Krhs )      ! Empty routine 
     201      INTEGER,                                    INTENT(in   ) :: kt        ! ocean time-step index 
     202      INTEGER,                                    INTENT(in   ) :: Kmm, Krhs ! time level indices 
     203      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr       ! passive tracers and RHS of tracer equation 
    201204      WRITE(*,*) 'trc_sbc: You should not have seen this print! error?', kt 
    202205   END SUBROUTINE trc_sbc 
Note: See TracChangeset for help on using the changeset viewer.