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 2371 for branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_iso_grif.F90 – NEMO

Ignore:
Timestamp:
2010-11-10T16:38:27+01:00 (14 years ago)
Author:
acc
Message:

nemo_v3_3_beta. Improvement of the Griffies operator code (#680). Some aspects are still undergoing scientific assessment but the code structure is ready for release. Dynamical allocation of the large triad arrays has been introduced to reduce memory when the new operator is not in use.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRA/traldf_iso_grif.F90

    r2287 r2371  
    11MODULE traldf_iso_grif 
    2    !!============================================================================== 
     2   !!====================================================================== 
    33   !!                   ***  MODULE  traldf_iso_grif  *** 
    4    !! Ocean active tracers:  horizontal component of the lateral tracer mixing trend 
    5    !!============================================================================== 
    6    !! History :   9.0  !  06-10  (C. Harris) 
     4   !! Ocean  tracers:  horizontal component of the lateral tracer mixing trend 
     5   !!====================================================================== 
     6   !! History : 3.3  ! 2010-10  (G. Nurser, C. Harris, G. Madec)   
     7   !!                !          Griffies operator version adapted from traldf_iso.F90 
    78   !!---------------------------------------------------------------------- 
    89#if   defined key_ldfslp   ||   defined key_esopa 
     
    1415   !!                       and with the vertical part of 
    1516   !!                       the isopycnal or geopotential s-coord. operator  
    16    !!                       vector optimization, use k-j-i loops. 
    17    !!---------------------------------------------------------------------- 
    18  
     17   !!---------------------------------------------------------------------- 
    1918   USE oce             ! ocean dynamics and active tracers 
    2019   USE dom_oce         ! ocean space and time domain 
    2120   USE ldftra_oce      ! ocean active tracers: lateral physics 
    22    USE trdmod          ! ocean active tracers trends  
    23    USE trdmod_oce      ! ocean variables trends 
    2421   USE zdf_oce         ! ocean vertical physics 
    2522   USE in_out_manager  ! I/O manager 
     23   USE iom             ! 
    2624   USE ldfslp          ! iso-neutral slopes 
    2725   USE diaptr          ! poleward transport diagnostics 
    28    USE prtctl          ! Print control 
     26   USE trc_oce         ! share passive tracers/Ocean variables 
     27#if defined key_diaar5 
     28   USE phycst          ! physical constants 
     29   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
     30#endif 
    2931 
    3032   IMPLICIT NONE 
     
    3234 
    3335   PUBLIC tra_ldf_iso_grif   ! routine called by traldf.F90 
     36 
     37   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::   psix_eiv 
     38   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::   psiy_eiv 
     39   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE ::   ah_wslp2 
    3440 
    3541   !! * Substitutions 
    3642#  include "domzgr_substitute.h90" 
    3743#  include "ldftra_substitute.h90" 
     44#  include "vectopt_loop_substitute.h90" 
    3845#  include "ldfeiv_substitute.h90" 
    39 #  include "vectopt_loop_substitute.h90" 
    40  
    4146   !!---------------------------------------------------------------------- 
    4247   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     
    4752CONTAINS 
    4853 
    49    SUBROUTINE tra_ldf_iso_grif( kt ) 
     54  SUBROUTINE tra_ldf_iso_grif( kt, cdtype, pgu, pgv,  & 
     55       &                                ptb, pta, kjpt, pahtb0 ) 
     56    !!---------------------------------------------------------------------- 
     57    !!                  ***  ROUTINE tra_ldf_iso_grif  *** 
     58    !! 
     59    !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive  
     60    !!      trend for a laplacian tensor (ezxcept the dz[ dz[.] ] term) and  
     61    !!      add it to the general trend of tracer equation. 
     62    !! 
     63    !! ** Method  :   The horizontal component of the lateral diffusive trends  
     64    !!      is provided by a 2nd order operator rotated along neural or geopo- 
     65    !!      tential surfaces to which an eddy induced advection can be added 
     66    !!      It is computed using before fields (forward in time) and isopyc- 
     67    !!      nal or geopotential slopes computed in routine ldfslp. 
     68    !! 
     69    !!      1st part :  masked horizontal derivative of T  ( di[ t ] ) 
     70    !!      ========    with partial cell update if ln_zps=T. 
     71    !! 
     72    !!      2nd part :  horizontal fluxes of the lateral mixing operator 
     73    !!      ========     
     74    !!         zftu = (aht+ahtb0) e2u*e3u/e1u di[ tb ] 
     75    !!               - aht       e2u*uslp    dk[ mi(mk(tb)) ] 
     76    !!         zftv = (aht+ahtb0) e1v*e3v/e2v dj[ tb ] 
     77    !!               - aht       e2u*vslp    dk[ mj(mk(tb)) ] 
     78    !!      take the horizontal divergence of the fluxes: 
     79    !!         difft = 1/(e1t*e2t*e3t) {  di-1[ zftu ] +  dj-1[ zftv ]  } 
     80    !!      Add this trend to the general trend (ta,sa): 
     81    !!         ta = ta + difft 
     82    !! 
     83    !!      3rd part: vertical trends of the lateral mixing operator 
     84    !!      ========  (excluding the vertical flux proportional to dk[t] ) 
     85    !!      vertical fluxes associated with the rotated lateral mixing: 
     86    !!         zftw =-aht {  e2t*wslpi di[ mi(mk(tb)) ] 
     87    !!                     + e1t*wslpj dj[ mj(mk(tb)) ]  } 
     88    !!      take the horizontal divergence of the fluxes: 
     89    !!         difft = 1/(e1t*e2t*e3t) dk[ zftw ] 
     90    !!      Add this trend to the general trend (ta,sa): 
     91    !!         pta = pta + difft 
     92    !! 
     93    !! ** Action :   Update pta arrays with the before rotated diffusion 
     94    !!---------------------------------------------------------------------- 
     95    USE oce,   zftu => ua   ! use ua as workspace 
     96    USE oce,   zftv => va   ! use va as workspace 
     97    !! 
     98    INTEGER                              , INTENT(in   ) ::   kt         ! ocean time-step index 
     99    CHARACTER(len=3)                     , INTENT(in   ) ::   cdtype     ! =TRA or TRC (tracer indicator) 
     100    INTEGER                              , INTENT(in   ) ::   kjpt       ! number of tracers 
     101    REAL(wp), DIMENSION(jpi,jpj    ,kjpt), INTENT(in   ) ::   pgu, pgv   ! tracer gradient at pstep levels 
     102    REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(in   ) ::   ptb        ! before and now tracer fields 
     103    REAL(wp), DIMENSION(jpi,jpj,jpk,kjpt), INTENT(inout) ::   pta        ! tracer trend  
     104    REAL(wp)                             , INTENT(in   ) ::   pahtb0     ! background diffusion coef 
     105    !! 
     106    INTEGER  ::  ji, jj, jk,jn   ! dummy loop indices 
     107    INTEGER  ::  ip,jp,kp        ! dummy loop indices 
     108    INTEGER  ::  iku, ikv        ! temporary integer 
     109    INTEGER  ::  ierr            ! temporary integer 
     110    REAL(wp) ::  zmsku, zabe1, zcof1, zcoef3   ! local scalars 
     111    REAL(wp) ::  zmskv, zabe2, zcof2, zcoef4   !   -      - 
     112    REAL(wp) ::  zcoef0, zbtr                  !   -      - 
     113    REAL(wp), DIMENSION(jpi,jpj,0:1) ::   zdkt               ! 2D+1 workspace 
     114    REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdit, zdjt, ztfw   ! 3D workspace 
     115      ! 
     116    REAL(wp) ::   zslope_skew,zslope_iso,zslope2, zbu, zbv 
     117    REAL(wp) ::   ze1ur,zdxt,ze2vr,ze3wr,zdyt,zdzt 
     118    REAL(wp) ::   ah,zah_slp,zaei_slp 
     119#if defined key_diaar5 
     120    REAL(wp), DIMENSION(jpi,jpj)     ::   z2d                ! 2D workspace 
     121    REAL(wp)                         ::   zztmp              ! local scalar 
     122#endif 
    50123      !!---------------------------------------------------------------------- 
    51       !!                  ***  ROUTINE tra_ldf_iso_grif  *** 
    52       !! 
    53       !! ** Purpose :   Compute the before horizontal tracer (t & s) diffusive  
    54       !!      trend for a laplacian tensor (except the dz[ dz[.] ] term) and  
    55       !!      add it to the general trend of tracer equation. 
    56       !! 
    57       !! ** Method  :   The horizontal component of the lateral diffusive trends  
    58       !!      is provided by a 2nd order operator rotated along neutral or geopo- 
    59       !!      tential surfaces to which an eddy induced advection can be added 
    60       !!      It is computed using before fields (forward in time) 
    61       !! 
    62       !!      1st part :  masked horizontal derivative of T & S ( di[ t ] ) 
    63       !!      ========    with partial cell update if ln_zps=T. 
    64       !! 
    65       !!      2nd part :  horizontal fluxes of the lateral mixing operator 
    66       !!      ========     
    67       !!      take the horizontal divergence of the fluxes: 
    68       !!         difft = 1/(e1t*e2t*e3t) {  di-1[ zftu ] +  dj-1[ zftv ]  } 
    69       !!      Add this trend to the general trend (ta,sa): 
    70       !!         ta = ta + difft 
    71       !! 
    72       !!      3rd part: vertical trends of the lateral mixing operator 
    73       !!      ========  (excluding the vertical flux proportional to dk[t] ) 
    74       !!      vertical fluxes associated with the rotated lateral mixing: 
    75  
    76       !!      take the horizontal divergence of the fluxes: 
    77       !!         difft = 1/(e1t*e2t*e3t) dk[ zftw ] 
    78       !!      Add this trend to the general trend (ta,sa): 
    79       !!         ta = ta + difft 
    80       !! 
    81       !! ** Action : 
    82       !!         Update (ta,sa) arrays with the before rotated diffusion trend 
    83       !!            (except the dk[ dk[.] ] term) 
    84       !! 
     124 
     125    IF( kt == nit000 )  THEN 
     126       IF(lwp) WRITE(numout,*) 
     127       IF(lwp) WRITE(numout,*) 'tra_ldf_iso_grif : rotated laplacian diffusion operator on ', cdtype 
     128       IF(lwp) WRITE(numout,*) '                   WARNING: STILL UNDER TEST, NOT RECOMMENDED. USE AT YOUR OWN PERIL' 
     129       IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
     130       ALLOCATE( ah_wslp2(jpi,jpj,jpk) , STAT=ierr ) 
     131       IF( ierr > 0 ) THEN 
     132          CALL ctl_stop( 'tra_ldf_iso_grif : unable to allocate Griffies operator ah_wslp2 ' )   ;   RETURN 
     133       ENDIF 
     134       IF( ln_traldf_gdia ) THEN 
     135          ALLOCATE( psix_eiv(jpi,jpj,jpk) , psiy_eiv(jpi,jpj,jpk) , STAT=ierr ) 
     136          IF( ierr > 0 ) THEN 
     137             CALL ctl_stop( 'tra_ldf_iso_grif : unable to allocate Griffies operator diagnostics ' )   ;   RETURN 
     138          ENDIF 
     139       ENDIF 
     140    ENDIF 
     141 
     142      !                                                
    85143      !!---------------------------------------------------------------------- 
    86       USE oce           , zftv => ua   ! use ua as workspace 
    87       USE oce           , zfsv => va   ! use va as workspace 
    88       !! 
    89       INTEGER, INTENT( in ) ::   kt        ! ocean time-step index 
    90       !! 
    91       INTEGER  ::   ji, jj, jk, ip, jp, kp    ! dummy loop indices 
    92       INTEGER  ::   iku, ikv                  ! temporary integer 
    93       REAL(wp) ::   zatempu, zdx, zta         ! temporary scalars 
    94       REAL(wp) ::   zatempv, zdy, zsa         !    "         " 
    95       REAL(wp) ::   zslopec, zdsloper, zepsln !    "         " 
    96       REAL(wp) ::   zsxe, za_sxe, zfact       !    "         " 
    97       REAL(wp) ::   zbtr                      !    "         " 
    98       REAL(wp), DIMENSION(2) ::   zdelta   ! 1D workspace 
    99       REAL(wp), DIMENSION(jpi,jpj)     ::   zftu   ! 2D workspace 
    100       REAL(wp), DIMENSION(jpi,jpj)     ::   zfsu   !    "           " 
    101       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdit, zdjt, zdkt     ! 3D workspace 
    102       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zdis, zdjs, zdks     !  "      " 
    103  
    104  
    105  
     144      !!   0 - calculate  ah_wslp2, psix_eiv, psiy_eiv  
    106145      !!---------------------------------------------------------------------- 
    107146 
    108       IF( kt == nit000 ) THEN 
    109          IF(lwp) WRITE(numout,*) 
    110          IF(lwp) WRITE(numout,*) 'tra_ldf_iso_grif : rotated laplacian diffusion operator' 
    111          IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~~' 
    112       ENDIF 
    113  
    114       IF ( .NOT. lk_traldf_eiv ) THEN 
    115         fsaeiu(:,:,:)=0.0 
    116         fsaeiv(:,:,:)=0.0 
    117         fsaeiw(:,:,:)=0.0 
    118       ENDIF 
    119  
    120       DO jk=1,jpkm1 
    121       DO jj=1,jpjm1 
    122       DO ji=1,fs_jpim1 
    123                ftu(ji,jj,jk)=ftud(ji,jj,jk)+ftu(ji,jj,jk)*(fsahtu(ji,jj,jk)-fsaeiu(ji,jj,jk)) 
    124                fsu(ji,jj,jk)=fsud(ji,jj,jk)+fsu(ji,jj,jk)*(fsahtu(ji,jj,jk)-fsaeiu(ji,jj,jk)) 
    125                ftv(ji,jj,jk)=ftvd(ji,jj,jk)+ftv(ji,jj,jk)*(fsahtv(ji,jj,jk)-fsaeiv(ji,jj,jk)) 
    126                fsv(ji,jj,jk)=fsvd(ji,jj,jk)+fsv(ji,jj,jk)*(fsahtv(ji,jj,jk)-fsaeiv(ji,jj,jk)) 
     147!!gm Future development: consider using Ah defined at T-points and attached to the 4 t-point triads 
     148 
     149    ah_wslp2(:,:,:) = 0.0 
     150    IF( ln_traldf_gdia ) THEN 
     151       psix_eiv(:,:,:) = 0.0 
     152       psiy_eiv(:,:,:) = 0.0 
     153    ENDIF 
     154 
     155    DO ip=0,1 
     156       DO kp=0,1 
     157          DO jk=1,jpkm1 
     158             DO jj=1,jpjm1 
     159                DO ji=1,fs_jpim1 
     160                   ze3wr=1.0_wp/fse3w(ji+ip,jj,jk+kp) 
     161                   zbu = 0.25_wp*e1u(ji,jj)*e2u(ji,jj)*fse3u(ji,jj,jk) 
     162                   ah = fsahtu(ji,jj,jk)                                  !  fsaht(ji+ip,jj,jk) 
     163                   zslope_skew = triadi_g(ji+ip,jj,jk,1-ip,kp) 
     164                   zslope2=(zslope_skew & 
     165                        & - umask(ji,jj,jk+kp)*(fsdept(ji+1,jj,jk) - fsdept(ji ,jj ,jk))*ze1ur & 
     166                        & )**2 
     167                   ah_wslp2(ji+ip,jj,jk+kp)=ah_wslp2(ji+ip,jj,jk+kp) + & 
     168                        & ah*((zbu*ze3wr)/(e1t(ji+ip,jj)*e2t(ji+ip,jj)))*zslope2 
     169                   IF( ln_traldf_gdia ) THEN 
     170                      zaei_slp = fsaeiw(ji+ip,jj,jk)*zslope_skew!fsaeit(ji+ip,jj,jk)*zslope_skew 
     171                      psix_eiv(ji,jj,jk+kp) = psix_eiv(ji,jj,jk+kp) + 0.25_wp*zaei_slp 
     172                   ENDIF 
     173                END DO 
     174             END DO 
     175          END DO 
     176       END DO 
     177    END DO 
     178 
     179    DO jp=0,1 
     180       DO kp=0,1 
     181          DO jk=1,jpkm1 
     182             DO jj=1,jpjm1 
     183                DO ji=1,fs_jpim1 
     184                   ze3wr=1.0_wp/fse3w(ji,jj+jp,jk+kp) 
     185                   zbv = 0.25_wp*e1v(ji,jj)*e2v(ji,jj)*fse3v(ji,jj,jk) 
     186                   ah = fsahtu(ji,jj,jk)!fsaht(ji,jj+jp,jk) 
     187                   zslope_skew = triadj_g(ji,jj+jp,jk,1-jp,kp) 
     188                   zslope2=(zslope_skew - vmask(ji,jj,jk+kp)*(fsdept(ji,jj+1,jk) - fsdept(ji ,jj ,jk))*ze2vr & 
     189                        & )**2 
     190                   ah_wslp2(ji,jj+jp,jk+kp)=ah_wslp2(ji,jj+jp,jk+kp) + & 
     191                        & ah*((zbv*ze3wr)/(e1t(ji,jj+jp)*e2t(ji,jj+jp)))*zslope2 
     192                   IF( ln_traldf_gdia ) THEN 
     193                      zaei_slp = fsaeiw(ji,jj+jp,jk) * zslope_skew     !fsaeit(ji,jj+jp,jk)*zslope_skew 
     194                      psiy_eiv(ji,jj,jk+kp) = psiy_eiv(ji,jj,jk+kp) + 0.25_wp*zaei_slp 
     195                   ENDIF 
     196                END DO 
     197             END DO 
     198          END DO 
     199       END DO 
    127200      END DO 
    128       END DO 
    129       END DO 
    130  
    131       DO jk = 1, jpkm1 
    132  
    133          ! II.4 Second derivative (divergence) and add to the general trend 
    134          ! ---------------------------------------------------------------- 
    135          DO jj = 2 , jpjm1 
    136             DO ji = fs_2, fs_jpim1   ! vector opt. 
    137                zbtr= 1. / ( e1t(ji,jj)*e2t(ji,jj)*fse3t(ji,jj,jk) ) 
    138                zta = zbtr * ( ftu(ji,jj,jk) - ftu(ji-1,jj,jk) + ftv(ji,jj,jk) - ftv(ji,jj-1,jk)  ) 
    139                zsa = zbtr * ( fsu(ji,jj,jk) - fsu(ji-1,jj,jk) + fsv(ji,jj,jk) - fsv(ji,jj-1,jk)  ) 
    140                ta (ji,jj,jk) = ta (ji,jj,jk) + zta 
    141                sa (ji,jj,jk) = sa (ji,jj,jk) + zsa 
     201 
     202      ! 
     203      !                                                          ! =========== 
     204      DO jn = 1, kjpt                                            ! tracer loop 
     205         !                                                       ! =========== 
     206         ! Zero fluxes for each tracer 
     207         ztfw(:,:,:) = 0._wp 
     208         zftu(:,:,:) = 0._wp 
     209         zftv(:,:,:) = 0._wp 
     210         !                                                
     211         DO jk = 1, jpkm1                          !==  before lateral T & S gradients at T-level jk  ==! 
     212            DO jj = 1, jpjm1 
     213               DO ji = 1, fs_jpim1   ! vector opt. 
     214                  zdit(ji,jj,jk) = ( ptb(ji+1,jj  ,jk,jn) - ptb(ji,jj,jk,jn) ) * umask(ji,jj,jk) 
     215                  zdjt(ji,jj,jk) = ( ptb(ji  ,jj+1,jk,jn) - ptb(ji,jj,jk,jn) ) * vmask(ji,jj,jk) 
     216               END DO 
    142217            END DO 
    143218         END DO 
    144          !                                          ! =============== 
    145       END DO                                        !   End of slab   
    146       !                                             ! =============== 
    147  
    148       IF( ln_diaptr .AND. ( MOD( kt, nf_ptr ) == 0 ) ) THEN   ! Poleward diffusive heat and salt transports 
    149          pht_ldf(:) = ptr_vj( zftv(:,:,:) ) 
    150          pst_ldf(:) = ptr_vj( zfsv(:,:,:) ) 
    151       ENDIF 
    152  
    153       !!---------------------------------------------------------------------- 
    154       !!   III - vertical trend of T & S (extra diagonal terms only) 
    155       !!---------------------------------------------------------------------- 
    156  
    157       ! I.5 Divergence of vertical fluxes added to the general tracer trend 
    158       ! ------------------------------------------------------------------- 
    159  
    160       DO jk=1,jpk 
    161       DO jj=2,jpjm1 
    162       DO ji=fs_2,fs_jpim1 
    163                tfw(ji,jj,jk)=tfw(ji,jj,jk)*(fsahtw(ji,jj,jk)+fsaeiw(ji,jj,jk)) 
    164                sfw(ji,jj,jk)=sfw(ji,jj,jk)*(fsahtw(ji,jj,jk)+fsaeiw(ji,jj,jk)) 
    165       END DO 
    166       END DO 
    167       END DO 
    168  
    169       DO jk = 1, jpkm1 
    170          DO jj = 2, jpjm1 
    171             DO ji = fs_2, fs_jpim1   ! vector opt. 
    172                zbtr =  1. / ( e1t(ji,jj)*e2t(ji,jj)*fse3t(ji,jj,jk) ) 
    173                zta  = (  tfw(ji,jj,jk) - tfw(ji,jj,jk+1)  ) * zbtr 
    174                zsa  = (  sfw(ji,jj,jk) - sfw(ji,jj,jk+1)  ) * zbtr 
    175                ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
    176                sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
     219         IF( ln_zps ) THEN                               ! partial steps: correction at the last level 
     220# if defined key_vectopt_loop 
     221            DO jj = 1, 1 
     222               DO ji = 1, jpij-jpi   ! vector opt. (forced unrolling) 
     223# else 
     224            DO jj = 1, jpjm1 
     225               DO ji = 1, jpim1 
     226# endif 
     227                  iku = MIN( mbathy(ji,jj), mbathy(ji+1,jj  ) ) - 1                ! last level 
     228                  ikv = MIN( mbathy(ji,jj), mbathy(ji  ,jj+1) ) - 1 
     229                  zdit(ji,jj,iku) = pgu(ji,jj,jn)           
     230                  zdjt(ji,jj,ikv) = pgv(ji,jj,jn)       
     231               END DO 
    177232            END DO 
    178          END DO 
    179       END DO 
    180       ! 
    181       DO jk=1,jpk 
    182       DO jj=2,jpjm1 
    183       DO ji=fs_2,fs_jpim1 
    184        psix_eiv(ji,jj,jk) = psix_eiv(ji,jj,jk)*fsaeiu(ji,jj,jk) 
    185        psiy_eiv(ji,jj,jk) = psiy_eiv(ji,jj,jk)*fsaeiv(ji,jj,jk) 
    186       END DO 
    187       END DO 
    188       END DO 
    189  
    190    END SUBROUTINE tra_ldf_iso_grif 
     233         ENDIF 
     234 
     235         !!---------------------------------------------------------------------- 
     236         !!   II - horizontal trend  (full) 
     237         !!---------------------------------------------------------------------- 
     238         ! 
     239         DO jk = 1, jpkm1 
     240            ! 
     241            !                    !==  Vertical tracer gradient at level jk and jk+1 
     242            zdkt(:,:,1) = ( ptb(:,:,jk,jn) - ptb(:,:,jk+1,jn) ) * tmask(:,:,jk+1) 
     243            ! 
     244            !                          ! surface boundary condition: zdkt(jk=1)=zdkt(jk=2) 
     245            IF( jk == 1 ) THEN   ;   zdkt(:,:,0) = zdkt(:,:,1) 
     246            ELSE                 ;   zdkt(:,:,0) = ( ptb(:,:,jk-1,jn) - ptb(:,:,jk,jn) ) * tmask(:,:,jk) 
     247            ENDIF 
     248 
     249            IF( .NOT. l_triad_iso ) THEN 
     250               triadi = triadi_g 
     251               triadj = triadj_g 
     252            ENDIF 
     253 
     254            DO ip=0,1              !==  Horizontal & vertical fluxes 
     255               DO kp=0,1 
     256                  DO jj=1,jpjm1 
     257                     DO ji=1,fs_jpim1 
     258                        ze1ur = 1._wp / e1u(ji,jj) 
     259                        zdxt = zdit(ji,jj,jk) * ze1ur 
     260                        ze3wr = 1._wp/fse3w(ji+ip,jj,jk+kp) 
     261                        zdzt  = zdkt(ji+ip,jj,kp) * ze3wr 
     262                        zslope_skew = triadi_g(ji+ip,jj,jk,1-ip,kp) 
     263                        zslope_iso  = triadi(ji+ip,jj,jk,1-ip,kp) 
     264 
     265                        zbu = 0.25_wp * e1u(ji,jj) * e2u(ji,jj) * fse3u(ji,jj,jk) 
     266                        ah = fsahtu(ji,jj,jk)!*umask(ji,jj,jk+kp)         !fsaht(ji+ip,jj,jk)             ===>>  ???? 
     267                        zah_slp = ah*zslope_iso 
     268                        zaei_slp = fsaeiw(ji+ip,jj,jk) * zslope_skew    !fsaeit(ji+ip,jj,jk)*zslope_skew 
     269                        zftu(ji,jj,jk)  = zftu(ji,jj,jk) - (ah*zdxt + (zah_slp - zaei_slp)*zdzt)*zbu*ze1ur 
     270                        ztfw(ji+ip,jj,jk+kp) = ztfw(ji+ip,jj,jk+kp) - (zah_slp + zaei_slp)*zdxt *zbu*ze3wr 
     271                     END DO 
     272                  END DO 
     273               END DO 
     274            END DO 
     275 
     276            DO jp=0,1 
     277               DO kp=0,1 
     278                  DO jj=1,jpjm1 
     279                     DO ji=1,fs_jpim1 
     280                        ze2vr = 1._wp/e2v(ji,jj) 
     281                        zdyt = zdjt(ji,jj,jk)*ze2vr 
     282                        ze3wr = 1._wp/fse3w(ji,jj+jp,jk+kp) 
     283                        zdzt = zdkt(ji,jj+jp,kp) * ze3wr 
     284                        zslope_skew = triadj_g(ji,jj+jp,jk,1-jp,kp) 
     285                        zslope_iso = triadj(ji,jj+jp,jk,1-jp,kp) 
     286                        zbv = 0.25_wp * e1v(ji,jj) * e2v(ji,jj) * fse3v(ji,jj,jk) 
     287                        ah    = fsahtv(ji,jj,jk)!*vmask(ji,jj,jk+kp)         !fsaht(ji,jj+jp,jk) 
     288                        zah_slp = ah * zslope_iso 
     289                        zaei_slp = fsaeiw(ji,jj+jp,jk)*zslope_skew!fsaeit(ji,jj+jp,jk)*zslope_skew 
     290                        zftv(ji,jj,jk) = zftv(ji,jj,jk) - (ah*zdyt + (zah_slp - zaei_slp)*zdzt)*zbv*ze2vr 
     291                        ztfw(ji,jj+jp,jk+kp) = ztfw(ji,jj+jp,jk+kp) - (zah_slp + zaei_slp)*zdyt*zbv*ze3wr 
     292                     END DO 
     293                  END DO 
     294               END DO 
     295            END DO 
     296 
     297          !                        !==  divergence and add to the general trend  ==! 
     298          DO jj = 2 , jpjm1 
     299             DO ji = fs_2, fs_jpim1   ! vector opt. 
     300                zbtr = 1._wp / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) ) 
     301                pta(ji,jj,jk,jn) = pta(ji,jj,jk,jn) + zbtr * (   zftu(ji-1,jj,jk) - zftu(ji,jj,jk)   & 
     302                  &                                            + zftv(ji,jj-1,jk) - zftv(ji,jj,jk)   ) 
     303             END DO 
     304          END DO 
     305          ! 
     306       END DO 
     307       ! 
     308       DO jk = 1, jpkm1            !== Divergence of vertical fluxes added to the general tracer trend 
     309          DO jj = 2, jpjm1 
     310             DO ji = fs_2, fs_jpim1   ! vector opt. 
     311                pta(ji,jj,jk,jn) = pta(ji,jj,jk,jn) + (  ztfw(ji,jj,jk+1) - ztfw(ji,jj,jk)  )   & 
     312                  &                                 / ( e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk) ) 
     313             END DO 
     314          END DO 
     315       END DO 
     316       ! 
     317       !                            ! "Poleward" diffusive heat or salt transports (T-S case only) 
     318       IF( cdtype == 'TRA' .AND. ln_diaptr .AND. ( MOD( kt, nf_ptr ) == 0 ) ) THEN 
     319         IF( jn == jp_tem)   pht_ldf(:) = ptr_vj( zftv(:,:,:) )        ! 3.3  names 
     320         IF( jn == jp_sal)   pst_ldf(:) = ptr_vj( zftv(:,:,:) ) 
     321       ENDIF 
     322 
     323#if defined key_diaar5 
     324       IF( cdtype == 'TRA' .AND. jn == jp_tem  ) THEN 
     325          zztmp = 0.5 * rau0 * rcp  
     326          z2d(:,:) = 0.e0  
     327          DO jk = 1, jpkm1 
     328             DO jj = 2, jpjm1 
     329                DO ji = fs_2, fs_jpim1   ! vector opt. 
     330                   z2d(ji,jj) = z2d(ji,jj) + zztmp * zftu(ji,jj,jk)       & 
     331                        &       * ( ptn(ji,jj,jk,jn) + ptn(ji+1,jj,jk,jn) ) * e1u(ji,jj) * fse3u(ji,jj,jk)  
     332                END DO 
     333             END DO 
     334          END DO 
     335          CALL lbc_lnk( z2d, 'U', -1. ) 
     336          CALL iom_put( "udiff_heattr", z2d )                  ! heat transport in i-direction 
     337          z2d(:,:) = 0.e0  
     338          DO jk = 1, jpkm1 
     339             DO jj = 2, jpjm1 
     340                DO ji = fs_2, fs_jpim1   ! vector opt. 
     341                   z2d(ji,jj) = z2d(ji,jj) + zztmp * zftv(ji,jj,jk)       & 
     342                        &       * ( ptn(ji,jj,jk,jn) + ptn(ji,jj+1,jk,jn) ) * e2v(ji,jj) * fse3v(ji,jj,jk)  
     343                END DO 
     344             END DO 
     345          END DO 
     346          CALL lbc_lnk( z2d, 'V', -1. ) 
     347          CALL iom_put( "vdiff_heattr", z2d )                  !  heat transport in i-direction 
     348       END IF 
     349#endif 
     350       ! 
     351    END DO 
     352    ! 
     353  END SUBROUTINE tra_ldf_iso_grif 
    191354 
    192355#else 
     
    196359CONTAINS 
    197360   SUBROUTINE tra_ldf_iso_grif( kt )               ! Empty routine 
    198       WRITE(*,*) 'tra_ldf_iso_grif: You should not have seen this print! error?', kt 
     361      WRITE(*,*) 'tra_ldf_iso: You should not have seen this print! error?', kt 
    199362   END SUBROUTINE tra_ldf_iso_grif 
    200363#endif 
Note: See TracChangeset for help on using the changeset viewer.