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 – 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)

Location:
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP
Files:
6 edited

Legend:

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

    r10966 r10985  
    2020   !!    trc_bbl      : update the tracer trends due to the bottom boundary layer (advective and/or diffusive) 
    2121   !!---------------------------------------------------------------------- 
    22    USE oce_trc        ! ocean dynamics and active tracers variables 
     22   USE oce_trc        ! ocean dynamics and passive tracers variables 
    2323   USE trc            ! ocean passive tracers variables 
    2424   USE trd_oce        ! trends: ocean variables 
     
    3636CONTAINS 
    3737 
    38    SUBROUTINE trc_bbl( kt, Kbb, Kmm, Krhs ) 
     38   SUBROUTINE trc_bbl( kt, Kbb, Kmm, ptr, Krhs ) 
    3939      !!---------------------------------------------------------------------- 
    4040      !!                  ***  ROUTINE bbl  *** 
     
    4545      !! 
    4646      !!----------------------------------------------------------------------   
    47       INTEGER, INTENT( in ) ::   kt   ! ocean time-step  
    48       INTEGER, INTENT( in ) ::   Kbb, Kmm, Krhs  ! time level indices 
     47      INTEGER,                                    INTENT( in  ) :: kt              ! ocean time-step  
     48      INTEGER,                                    INTENT( in  ) :: Kbb, Kmm, Krhs  ! time level indices 
     49      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr             ! passive tracers and RHS of tracer equation 
    4950      INTEGER :: jn                   ! loop index 
    5051      CHARACTER (len=22) :: charout 
     
    6162      IF( l_trdtrc )  THEN 
    6263         ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) ) ! temporary save of trends 
    63          ztrtrd(:,:,:,:)  = tr(:,:,:,:,Krhs) 
     64         ztrtrd(:,:,:,:)  = ptr(:,:,:,:,Krhs) 
    6465      ENDIF 
    6566 
     
    6768      IF( nn_bbl_ldf == 1 ) THEN 
    6869         ! 
    69          CALL tra_bbl_dif( tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, Kmm )   
     70         CALL tra_bbl_dif( ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, Kmm )   
    7071         IF( ln_ctl )   THEN 
    7172            WRITE(charout, FMT="(' bbl_dif')")  ;  CALL prt_ctl_trc_info(charout) 
    72             CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     73            CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    7374         ENDIF 
    7475         ! 
     
    7879      IF( nn_bbl_adv /= 0 ) THEN 
    7980         ! 
    80          CALL tra_bbl_adv( tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, Kmm )   
     81         CALL tra_bbl_adv( ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, Kmm )   
    8182         IF( ln_ctl )   THEN 
    8283            WRITE(charout, FMT="(' bbl_adv')")  ;  CALL prt_ctl_trc_info(charout) 
    83             CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     84            CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    8485         ENDIF 
    8586         ! 
     
    8889      IF( l_trdtrc )   THEN                      ! save the horizontal diffusive trends for further diagnostics 
    8990        DO jn = 1, jptra 
    90            ztrtrd(:,:,:,jn) = tr(:,:,:,jn,Krhs) - ztrtrd(:,:,:,jn) 
     91           ztrtrd(:,:,:,jn) = ptr(:,:,:,jn,Krhs) - ztrtrd(:,:,:,jn) 
    9192           CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_bbl, ztrtrd(:,:,:,jn) ) 
    9293        END DO 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcdmp.F90

    r10966 r10985  
    6363 
    6464 
    65    SUBROUTINE trc_dmp( kt, Kbb, Kmm, Krhs ) 
     65   SUBROUTINE trc_dmp( kt, Kbb, Kmm, ptr, Krhs ) 
    6666      !!---------------------------------------------------------------------- 
    6767      !!                   ***  ROUTINE trc_dmp  *** 
     
    8282      !!              - save the trends ('key_trdmxl_trc') 
    8383      !!---------------------------------------------------------------------- 
    84       INTEGER, INTENT(in) ::   kt              ! ocean time-step index 
    85       INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! time level indices 
     84      INTEGER,                                    INTENT(in   ) :: kt              ! ocean time-step index 
     85      INTEGER,                                    INTENT(in   ) :: Kbb, Kmm, Krhs  ! time level indices 
     86      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr             ! passive tracers and RHS of tracer equation 
    8687      ! 
    8788      INTEGER ::   ji, jj, jk, jn, jl   ! dummy loop indices 
     
    101102         DO jn = 1, jptra                                           ! tracer loop 
    102103            !                                                       ! =========== 
    103             IF( l_trdtrc ) ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs)    ! save trends  
     104            IF( l_trdtrc ) ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs)    ! save trends  
    104105            ! 
    105106            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     
    114115                     DO jj = 2, jpjm1 
    115116                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    116                            tr(ji,jj,jk,jn,Krhs) = tr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - tr(ji,jj,jk,jn,Kbb) ) 
     117                           ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) ) 
    117118                        END DO 
    118119                     END DO 
     
    124125                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    125126                           IF( avt(ji,jj,jk) <= avt_c )  THEN  
    126                               tr(ji,jj,jk,jn,Krhs) = tr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - tr(ji,jj,jk,jn,Kbb) ) 
     127                              ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) ) 
    127128                           ENDIF 
    128129                        END DO 
     
    135136                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    136137                           IF( gdept(ji,jj,jk,Kmm) >= hmlp (ji,jj) ) THEN 
    137                               tr(ji,jj,jk,jn,Krhs) = tr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - tr(ji,jj,jk,jn,Kbb) ) 
     138                              ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) ) 
    138139                           END IF 
    139140                        END DO 
     
    146147            ! 
    147148            IF( l_trdtrc ) THEN 
    148                ztrtrd(:,:,:) = tr(:,:,:,jn,Krhs) -  ztrtrd(:,:,:) 
     149               ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs) -  ztrtrd(:,:,:) 
    149150               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_dmp, ztrtrd ) 
    150151            END IF 
     
    160161         WRITE(charout, FMT="('dmp ')") 
    161162         CALL prt_ctl_trc_info(charout) 
    162          CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     163         CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    163164      ENDIF 
    164165      ! 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcldf.F90

    r10980 r10985  
    5151CONTAINS 
    5252 
    53    SUBROUTINE trc_ldf( kt, Kbb, Kmm, Krhs ) 
     53   SUBROUTINE trc_ldf( kt, Kbb, Kmm, ptr, Krhs ) 
    5454      !!---------------------------------------------------------------------- 
    5555      !!                  ***  ROUTINE tra_ldf  *** 
     
    5858      !! 
    5959      !!---------------------------------------------------------------------- 
    60       INTEGER, INTENT( in ) ::   kt              ! ocean time-step index 
    61       INTEGER, INTENT( in ) ::   Kbb, Kmm, Krhs  ! ocean time-level index 
     60      INTEGER,                                    INTENT(in   ) :: kt              ! ocean time-step index 
     61      INTEGER,                                    INTENT(in   ) :: Kbb, Kmm, Krhs  ! ocean time-level index 
     62      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr             ! passive tracers and RHS of tracer equation 
    6263      ! 
    6364      INTEGER            :: ji, jj, jk, jn 
    6465      REAL(wp)           :: zdep 
    6566      CHARACTER (len=22) :: charout 
    66       REAL(wp), DIMENSION(jpi,jpj,jpk)  ::   zahu, zahv 
    67       REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd 
     67      REAL(wp),          DIMENSION(jpi,jpj,jpk) ::   zahu, zahv 
     68      REAL(wp), POINTER, DIMENSION(:,:,:,:)     ::   ztrtrd 
    6869      !!---------------------------------------------------------------------- 
    6970      ! 
     
    7475      IF( l_trdtrc )  THEN 
    7576         ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) ) 
    76          ztrtrd(:,:,:,:)  = tr(:,:,:,:,Krhs) 
     77         ztrtrd(:,:,:,:)  = ptr(:,:,:,:,Krhs) 
    7778      ENDIF 
    7879      !                                  !* set the lateral diffusivity coef. for passive tracer       
     
    9596      CASE ( np_lap   )                                                                                    ! iso-level laplacian 
    9697         CALL tra_ldf_lap  ( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            & 
    97            &                     tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs),                  jptra, 1 ) 
     98           &                     ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs),                   jptra, 1 ) 
    9899      CASE ( np_lap_i )                                                                                    ! laplacian : standard iso-neutral operator (Madec) 
    99100         CALL tra_ldf_iso  ( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            & 
    100            &                     tr(:,:,:,:,Kbb), tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, 1 ) 
     101           &                     ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, 1 ) 
    101102      CASE ( np_lap_it )                                                                                   ! laplacian : triad iso-neutral operator (griffies) 
    102103         CALL tra_ldf_triad( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            & 
    103            &                     tr(:,:,:,:,Kbb), tr(:,:,:,:,Kbb), tr(:,:,:,:,Krhs), jptra, 1 ) 
     104           &                     ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, 1 ) 
    104105      CASE ( np_blp , np_blp_i , np_blp_it )                                                               ! bilaplacian: all operator (iso-level, -neutral) 
    105106         CALL tra_ldf_blp  ( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            & 
    106            &                     tr(:,:,:,:,Kbb) , tr(:,:,:,:,Krhs),                 jptra, nldf_trc ) 
     107           &                     ptr(:,:,:,:,Kbb) , ptr(:,:,:,:,Krhs),                 jptra, nldf_trc ) 
    107108      END SELECT 
    108109      ! 
    109110      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics 
    110111        DO jn = 1, jptra 
    111            ztrtrd(:,:,:,jn) = tr(:,:,:,jn,Krhs) - ztrtrd(:,:,:,jn) 
     112           ztrtrd(:,:,:,jn) = ptr(:,:,:,jn,Krhs) - ztrtrd(:,:,:,jn) 
    112113           CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) ) 
    113114        END DO 
     
    118119         WRITE(charout, FMT="('ldf ')") 
    119120         CALL prt_ctl_trc_info(charout) 
    120          CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     121         CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    121122      ENDIF 
    122123      ! 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcrad.F90

    r10966 r10985  
    3737CONTAINS 
    3838 
    39    SUBROUTINE trc_rad( kt, Kbb, Kmm, Krhs ) 
     39   SUBROUTINE trc_rad( kt, Kbb, Kmm, Krhs, ptr ) 
    4040      !!---------------------------------------------------------------------- 
    4141      !!                  ***  ROUTINE trc_rad  *** 
     
    5252      !!                (the total CFC content is not strictly preserved) 
    5353      !!---------------------------------------------------------------------- 
    54       INTEGER, INTENT(in) ::   kt              ! ocean time-step index 
    55       INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! time level indices 
     54      INTEGER,                                    INTENT(in   ) :: kt              ! ocean time-step index 
     55      INTEGER,                                    INTENT(in   ) :: Kbb, Kmm, Krhs  ! time level indices 
     56      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr             ! passive tracers and RHS of tracer equation 
    5657      ! 
    5758      CHARACTER (len=22) :: charout 
     
    6061      IF( ln_timing )   CALL timing_start('trc_rad') 
    6162      ! 
    62       IF( ln_age     )   CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_age , jp_age                )  !  AGE 
    63       IF( ll_cfc     )   CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_cfc0, jp_cfc1               )  !  CFC model 
    64       IF( ln_c14     )   CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_c14 , jp_c14                )  !  C14 
    65       IF( ln_pisces  )   CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model 
    66       IF( ln_my_trc  )   CALL trc_rad_sms( kt, Kmm, Krhs, tr(:,:,:,:,Kbb), tr(:,:,:,:,Kmm), jp_myt0, jp_myt1               )  !  MY_TRC model 
     63      IF( ln_age     )   CALL trc_rad_sms( kt, Kmm, Krhs, ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kmm), jp_age , jp_age                )  !  AGE 
     64      IF( ll_cfc     )   CALL trc_rad_sms( kt, Kmm, Krhs, ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kmm), jp_cfc0, jp_cfc1               )  !  CFC model 
     65      IF( ln_c14     )   CALL trc_rad_sms( kt, Kmm, Krhs, ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kmm), jp_c14 , jp_c14                )  !  C14 
     66      IF( ln_pisces  )   CALL trc_rad_sms( kt, Kmm, Krhs, ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kmm), jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model 
     67      IF( ln_my_trc  )   CALL trc_rad_sms( kt, Kmm, Krhs, ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kmm), jp_myt0, jp_myt1               )  !  MY_TRC model 
    6768      ! 
    6869      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
    6970         WRITE(charout, FMT="('rad')") 
    7071         CALL prt_ctl_trc_info( charout ) 
    71          CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Kmm), mask=tmask, clinfo=ctrcnm ) 
     72         CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Kmm), mask=tmask, clinfo=ctrcnm ) 
    7273      ENDIF 
    7374      ! 
  • 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 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trctrp.F90

    r10966 r10985  
    6161      IF( .NOT. lk_c1d ) THEN 
    6262         ! 
    63                                 CALL trc_sbc    ( kt,      Kmm, Krhs )      ! surface boundary condition 
    64          IF( ln_trabbl )        CALL trc_bbl    ( kt, Kbb, Kmm, Krhs )      ! advective (and/or diffusive) bottom boundary layer scheme 
    65          IF( ln_trcdmp )        CALL trc_dmp    ( kt, Kbb, Kmm, Krhs )      ! internal damping trends 
     63                                CALL trc_sbc    ( kt,      Kmm, tr, Krhs )  ! surface boundary condition 
     64         IF( ln_trabbl )        CALL trc_bbl    ( kt, Kbb, Kmm, tr, Krhs )  ! advective (and/or diffusive) bottom boundary layer scheme 
     65         IF( ln_trcdmp )        CALL trc_dmp    ( kt, Kbb, Kmm, tr, Krhs )  ! internal damping trends 
    6666         IF( ln_bdy )           CALL trc_bdy_dmp( kt, Kbb,      Krhs )      ! BDY damping trends 
    6767                                CALL trc_adv    ( kt, Kbb, Kmm, tr, Krhs )  ! horizontal & vertical advection  
     
    7373         ENDIF 
    7474         !                                                       
    75                                 CALL trc_ldf    ( kt, Kbb, Kmm, Krhs )     ! lateral mixing 
     75                                CALL trc_ldf    ( kt, Kbb, Kmm,       tr, Krhs )  ! lateral mixing 
    7676#if defined key_agrif 
    7777         IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_trc       ! tracers sponge 
     
    7979                                CALL trc_zdf    ( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer   ==> after 
    8080                                CALL trc_nxt    ( kt, Kbb, Kmm, Krhs )            ! tracer fields at next time step      
    81          IF( ln_trcrad )        CALL trc_rad    ( kt, Kbb, Kmm, Krhs )            ! Correct artificial negative concentrations 
     81         IF( ln_trcrad )        CALL trc_rad    ( kt, Kbb, Kmm, Krhs, tr       )  ! Correct artificial negative concentrations 
    8282         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kt, Kbb, Kmm )                  ! internal damping trends on closed seas only 
    8383 
    8484         ! 
    8585      ELSE                                               ! 1D vertical configuration 
    86                                 CALL trc_sbc( kt,      Kmm, Krhs )            ! surface boundary condition 
    87          IF( ln_trcdmp )        CALL trc_dmp( kt, Kbb, Kmm, Krhs )            ! internal damping trends 
     86                                CALL trc_sbc( kt,      Kmm,       tr, Krhs )  ! surface boundary condition 
     87         IF( ln_trcdmp )        CALL trc_dmp( kt, Kbb, Kmm,       tr, Krhs )  ! internal damping trends 
    8888                                CALL trc_zdf( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer ==> after 
    8989                                CALL trc_nxt( kt, Kbb, Kmm, Krhs )            ! tracer fields at next time step      
    90           IF( ln_trcrad )       CALL trc_rad( kt, Kbb, Kmm, Krhs )            ! Correct artificial negative concentrations 
     90          IF( ln_trcrad )       CALL trc_rad( kt, Kbb, Kmm, Krhs, tr       )  ! Correct artificial negative concentrations 
    9191         ! 
    9292      END IF 
Note: See TracChangeset for help on using the changeset viewer.