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 7351 for branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90 – NEMO

Ignore:
Timestamp:
2016-11-28T17:04:10+01:00 (7 years ago)
Author:
emanuelaclementi
Message:

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90

    r5836 r7351  
    1212   !!   'key_top'                                                TOP models 
    1313   !!---------------------------------------------------------------------- 
    14    !!   trc_ldf      : update the tracer trend with the lateral diffusion 
    15    !!   trc_ldf_ini  : initialization, namelist read, and parameters control 
    16    !!---------------------------------------------------------------------- 
    17    USE trc           ! ocean passive tracers variables 
    18    USE oce_trc       ! ocean dynamics and active tracers 
    19    USE ldfslp        ! lateral diffusion: iso-neutral slope 
    20    USE traldf_lap    ! lateral diffusion: laplacian iso-level            operator  (tra_ldf_lap   routine) 
    21    USE traldf_iso    ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso   routine) 
    22    USE traldf_triad  ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_triad routine) 
    23    USE traldf_blp    ! lateral diffusion (iso-level lap/blp)                       (tra_ldf_lap   routine) 
    24    USE trd_oce       ! trends: ocean variables 
    25    USE trdtra        ! trends manager: tracers  
     14   !!   trc_ldf       : update the tracer trend with the lateral diffusion 
     15   !!   trc_ldf_ini   : initialization, namelist read, and parameters control 
     16   !!---------------------------------------------------------------------- 
     17   USE trc            ! ocean passive tracers variables 
     18   USE oce_trc        ! ocean dynamics and active tracers 
     19   USE ldfslp         ! lateral diffusion: iso-neutral slope 
     20   USE traldf_lap_blp ! lateral diffusion: lap/bilaplacian iso-level      operator  (tra_ldf_lap/_blp   routine) 
     21   USE traldf_iso     ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso        routine) 
     22   USE traldf_triad   ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_     triad routine) 
     23   USE trd_oce        ! trends: ocean variables 
     24   USE trdtra         ! trends manager: tracers 
    2625   ! 
    27    USE prtctl_trc      ! Print control 
     26   USE prtctl_trc     ! Print control 
    2827 
    2928   IMPLICIT NONE 
     
    4140   REAL(wp), PUBLIC ::   rn_ahtrc_0          !:   laplacian diffusivity coefficient for passive tracer [m2/s] 
    4241   REAL(wp), PUBLIC ::   rn_bhtrc_0          !: bilaplacian      -          --     -       -   [m4/s] 
     42   REAL(wp), PUBLIC ::   rn_fact_lap         !: Enhanced zonal diffusivity coefficent in the equatorial domain 
    4343   ! 
    44                                                  !!: ** lateral mixing namelist (nam_trcldf) ** 
    45    REAL(wp) ::  rldf    ! ratio between active and passive tracers diffusive coefficient 
     44   !                      !!: ** lateral mixing namelist (nam_trcldf) ** 
     45   REAL(wp) ::  rldf       ! ratio between active and passive tracers diffusive coefficient 
     46    
    4647   INTEGER  ::  nldf = 0   ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals) 
    4748    
    4849   !! * Substitutions 
    49 #  include "domzgr_substitute.h90" 
    5050#  include "vectopt_loop_substitute.h90" 
    5151   !!---------------------------------------------------------------------- 
     
    6464      !!---------------------------------------------------------------------- 
    6565      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    66       !! 
    67       INTEGER            :: jn 
     66      ! 
     67      INTEGER            :: ji, jj, jk, jn 
     68      REAL(wp)           :: zdep 
    6869      CHARACTER (len=22) :: charout 
    6970      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zahu, zahv 
     
    7778         ztrtrd(:,:,:,:)  = tra(:,:,:,:) 
    7879      ENDIF 
    79       ! 
    80       !                                        !* set the lateral diffusivity coef. for passive tracer       
     80      !                                  !* set the lateral diffusivity coef. for passive tracer       
    8181      CALL wrk_alloc( jpi,jpj,jpk,   zahu, zahv ) 
    82       zahu(:,:,:) = rldf * ahtu(:,:,:) 
     82      zahu(:,:,:) = rldf * ahtu(:,:,:)  
    8383      zahv(:,:,:) = rldf * ahtv(:,:,:) 
    84  
     84      !                                  !* Enhanced zonal diffusivity coefficent in the equatorial domain 
     85      DO jk= 1, jpk 
     86         DO jj = 1, jpj 
     87            DO ji = 1, jpi 
     88               IF( gdept_n(ji,jj,jk) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN 
     89                  zdep = MAX( gdept_n(ji,jj,jk) - 1000., 0. ) / 1000. 
     90                  zahu(ji,jj,jk) = zahu(ji,jj,jk) * MAX( 1., rn_fact_lap * EXP( -zdep ) ) 
     91               ENDIF 
     92            END DO 
     93         END DO 
     94      END DO 
     95      ! 
    8596      SELECT CASE ( nldf )                     !* compute lateral mixing trend and add it to the general trend 
    8697      ! 
     
    99110      END SELECT 
    100111      ! 
    101       IF( l_trdtrc )   THEN                    ! save the horizontal diffusive trends for further diagnostics 
     112      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics 
    102113        DO jn = 1, jptra 
    103114           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn) 
     
    106117        CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd ) 
    107118      ENDIF 
    108       !                                        ! print mean trends (used for debugging) 
    109       IF( ln_ctl ) THEN 
    110          WRITE(charout, FMT="('ldf ')")   ;   CALL prt_ctl_trc_info(charout) 
    111                                               CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     119      !                 
     120      IF( ln_ctl ) THEN                        ! print mean trends (used for debugging) 
     121         WRITE(charout, FMT="('ldf ')") 
     122         CALL prt_ctl_trc_info(charout) 
     123         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    112124      ENDIF 
    113125      ! 
     
    133145      INTEGER ::   ioptio, ierr   ! temporary integers 
    134146      INTEGER ::   ios            ! Local integer output status for namelist read 
    135       ! 
     147      !! 
    136148      NAMELIST/namtrc_ldf/ ln_trcldf_lap, ln_trcldf_blp,                                  & 
    137149         &                 ln_trcldf_lev, ln_trcldf_hor, ln_trcldf_iso, ln_trcldf_triad,  & 
    138          &                 rn_ahtrc_0   , rn_bhtrc_0 
    139       !!---------------------------------------------------------------------- 
    140       REWIND( numnat_ref )              !  namtrc_ldf in reference namelist  
     150         &                 rn_ahtrc_0   , rn_bhtrc_0, rn_fact_lap   
     151      !!---------------------------------------------------------------------- 
     152      ! 
     153      REWIND( numnat_ref )             !  namtrc_ldf in reference namelist  
    141154      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903) 
    142 903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp ) 
    143  
    144       REWIND( numnat_cfg )              !  namtrc_ldf in configuration namelist  
     155903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp ) 
     156      ! 
     157      REWIND( numnat_cfg )             !  namtrc_ldf in configuration namelist  
    145158      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 ) 
    146 904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp ) 
     159904   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp ) 
    147160      IF(lwm) WRITE ( numont, namtrc_ldf ) 
    148  
    149       IF(lwp) THEN                    ! Namelist print 
     161      ! 
     162      IF(lwp) THEN                     ! Namelist print 
    150163         WRITE(numout,*) 
    151164         WRITE(numout,*) 'trc_ldf_ini : lateral tracer diffusive operator' 
     
    163176         WRITE(numout,*) '           laplacian                 rn_ahtrc_0      = ', rn_ahtrc_0 
    164177         WRITE(numout,*) '         bilaplacian                 rn_bhtrc_0      = ', rn_bhtrc_0 
     178         WRITE(numout,*) '      enhanced zonal diffusivity     rn_fact_lap     = ', rn_fact_lap 
     179 
    165180      ENDIF 
    166181      !       
     
    174189      IF( ln_trcldf_lap .AND. ln_trcldf_blp )   CALL ctl_stop( 'trc_ldf_ctl: bilaplacian should be used on both TRC and TRA' ) 
    175190      IF( ln_trcldf_blp .AND. ln_trcldf_lap )   CALL ctl_stop( 'trc_ldf_ctl:   laplacian should be used on both TRC and TRA' ) 
    176        
     191      ! 
    177192      ioptio = 0 
    178193      IF( ln_trcldf_lev )   ioptio = ioptio + 1 
     
    180195      IF( ln_trcldf_iso )   ioptio = ioptio + 1 
    181196      IF( ioptio /= 1   )   CALL ctl_stop( 'trc_ldf_ctl: use only ONE direction (level/hor/iso)' ) 
    182  
     197      ! 
    183198      ! defined the type of lateral diffusion from ln_trcldf_... logicals 
    184199      ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully 
     
    204219         ENDIF 
    205220         !                                ! diffusivity ratio: passive / active tracers  
    206          IF( ABS(rn_aht_0) < 2._wp*TINY(1.e0) ) THEN 
    207             IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1.e0) ) THEN 
     221         IF( ABS(rn_aht_0) < 2._wp*TINY(1._wp) ) THEN 
     222            IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1._wp) ) THEN 
    208223               rldf = 1.0_wp 
    209224            ELSE 
    210                CALL ctl_stop( 'STOP', 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
     225               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
    211226            ENDIF 
    212227         ELSE 
     
    235250         ENDIF 
    236251         !                                ! diffusivity ratio: passive / active tracers  
    237          IF( ABS(rn_bht_0) < 2._wp*TINY(1.e0) ) THEN 
    238             IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1.e0) ) THEN 
     252         IF( ABS(rn_bht_0) < 2._wp*TINY(1._wp) ) THEN 
     253            IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1._wp) ) THEN 
    239254               rldf = 1.0_wp 
    240255            ELSE 
    241                CALL ctl_stop( 'STOP', 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
     256               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
    242257            ENDIF 
    243258         ELSE 
     
    246261      ENDIF 
    247262      ! 
    248       IF( ierr == 1 )   CALL ctl_stop( ' iso-level in z-coordinate - partial step, not allowed' ) 
    249       IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   & 
    250            CALL ctl_stop( '          eddy induced velocity on tracers',   & 
    251            &              ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion' ) 
    252       IF( nldf == 1 .OR. nldf == 3 ) THEN      ! rotation 
    253          IF( .NOT.l_ldfslp )   CALL ctl_stop( '          the rotation of the diffusive tensor require l_ldfslp' ) 
    254       ENDIF 
     263      IF( ierr == 1 )   CALL ctl_stop( 'trc_ldf_ctl: iso-level in z-partial step, not allowed' ) 
     264      IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   CALL ctl_stop( 'trc_ldf_ctl: eiv requires isopycnal laplacian diffusion' ) 
     265      IF( nldf == 1 .OR. nldf == 3 )   l_ldfslp = .TRUE.    ! slope of neutral surfaces required  
    255266      ! 
    256267      IF(lwp) THEN 
    257268         WRITE(numout,*) 
    258          IF( nldf == np_no_ldf )   WRITE(numout,*) '          NO lateral diffusion' 
    259          IF( nldf == np_lap    )   WRITE(numout,*) '          laplacian iso-level operator' 
    260          IF( nldf == np_lap_i  )   WRITE(numout,*) '          Rotated laplacian operator (standard)' 
    261          IF( nldf == np_lap_it )   WRITE(numout,*) '          Rotated laplacian operator (triad)' 
    262          IF( nldf == np_blp    )   WRITE(numout,*) '          bilaplacian iso-level operator' 
    263          IF( nldf == np_blp_i  )   WRITE(numout,*) '          Rotated bilaplacian operator (standard)' 
    264          IF( nldf == np_blp_it )   WRITE(numout,*) '          Rotated bilaplacian operator (triad)' 
     269         SELECT CASE( nldf ) 
     270         CASE( np_no_ldf )   ;   WRITE(numout,*) '          NO lateral diffusion' 
     271         CASE( np_lap    )   ;   WRITE(numout,*) '          laplacian iso-level operator' 
     272         CASE( np_lap_i  )   ;   WRITE(numout,*) '          Rotated laplacian operator (standard)' 
     273         CASE( np_lap_it )   ;   WRITE(numout,*) '          Rotated laplacian operator (triad)' 
     274         CASE( np_blp    )   ;   WRITE(numout,*) '          bilaplacian iso-level operator' 
     275         CASE( np_blp_i  )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (standard)' 
     276         CASE( np_blp_it )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (triad)' 
     277         END SELECT 
    265278      ENDIF 
    266279      ! 
Note: See TracChangeset for help on using the changeset viewer.