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/trcldf.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/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      ! 
Note: See TracChangeset for help on using the changeset viewer.