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

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/TRP/trcldf.F90 @ 10946

Last change on this file since 10946 was 10946, checked in by acc, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Convert STO, TRD and USR modules and all knock on effects of these conversions. Note change to USR module may have implications for the TEST CASES (not tested yet). Standard SETTE tested only

  • Property svn:keywords set to Id
File size: 10.1 KB
RevLine 
[2030]1MODULE trcldf
2   !!======================================================================
3   !!                       ***  MODULE  trcldf  ***
[3294]4   !! Ocean Passive tracers : lateral diffusive trends
[2030]5   !!=====================================================================
[5836]6   !! History :  1.0  ! 2005-11  (G. Madec)  Original code
7   !!            3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!            3.7  ! 2014-03  (G. Madec)  LDF simplification
[2030]9   !!----------------------------------------------------------------------
10#if defined key_top
11   !!----------------------------------------------------------------------
12   !!   'key_top'                                                TOP models
13   !!----------------------------------------------------------------------
[6140]14   !!   trc_ldf       : update the tracer trend with the lateral diffusion
15   !!   trc_ldf_ini   : initialization, namelist read, and parameters control
[2030]16   !!----------------------------------------------------------------------
[6140]17   USE trc            ! ocean passive tracers variables
18   USE oce_trc        ! ocean dynamics and active tracers
[9019]19   USE ldftra         ! lateral diffusion: eddy diffusivity & EIV coeff.
20   USE ldfslp         ! Lateral diffusion: slopes of neutral surfaces
[6140]21   USE traldf_lap_blp ! lateral diffusion: lap/bilaplacian iso-level      operator  (tra_ldf_lap/_blp   routine)
22   USE traldf_iso     ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso        routine)
23   USE traldf_triad   ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_     triad routine)
24   USE trd_oce        ! trends: ocean variables
25   USE trdtra         ! trends manager: tracers
[5836]26   !
[6140]27   USE prtctl_trc     ! Print control
[2030]28
29   IMPLICIT NONE
30   PRIVATE
31
[5836]32   PUBLIC   trc_ldf   
33   PUBLIC   trc_ldf_ini   
34   !
[9490]35   !                                      !!: ** lateral mixing namelist (nam_trcldf) **
[9526]36   LOGICAL , PUBLIC ::   ln_trcldf_OFF     !: No operator (no explicit lateral diffusion)
[9490]37   LOGICAL , PUBLIC ::   ln_trcldf_tra     !: use active tracer operator
38   REAL(wp), PUBLIC ::      rn_ldf_multi      !: multiplier of T-S eddy diffusivity to obtain the passive tracer one
39   REAL(wp), PUBLIC ::      rn_fact_lap       !: enhanced Equatorial zonal diffusivity coefficent
[5836]40   !
[9490]41   INTEGER  ::   nldf_trc = 0   ! type of lateral diffusion used defined from ln_traldf_... (namlist logicals)
42   REAL(wp) ::   rldf           ! multiplier between active and passive tracers eddy diffusivity   [-]
[6140]43   
[2030]44   !! * Substitutions
45#  include "vectopt_loop_substitute.h90"
46   !!----------------------------------------------------------------------
[10067]47   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[3294]48   !! $Id$
[10068]49   !! Software governed by the CeCILL license (see ./LICENSE)
[2030]50   !!----------------------------------------------------------------------
51CONTAINS
52
[10946]53   SUBROUTINE trc_ldf( kt, Kmm, Krhs )
[2030]54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_ldf  ***
[3294]56      !!
[2030]57      !! ** Purpose :   compute the lateral ocean tracer physics.
58      !!
59      !!----------------------------------------------------------------------
60      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
[10946]61      INTEGER, INTENT( in ) ::   Kmm, Krhs  ! ocean time-level index
[6140]62      !
[6403]63      INTEGER            :: ji, jj, jk, jn
64      REAL(wp)           :: zdep
[2030]65      CHARACTER (len=22) :: charout
[9125]66      REAL(wp), DIMENSION(jpi,jpj,jpk)   ::   zahu, zahv
[3294]67      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd
[2030]68      !!----------------------------------------------------------------------
[3294]69      !
[9526]70      IF( ln_trcldf_OFF )   RETURN        ! not lateral diffusion applied on passive tracers
[9490]71      !
[9124]72      IF( ln_timing )   CALL timing_start('trc_ldf')
[3294]73      !
74      IF( l_trdtrc )  THEN
[9125]75         ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) )
[7753]76         ztrtrd(:,:,:,:)  = tra(:,:,:,:)
[2030]77      ENDIF
[6403]78      !                                  !* set the lateral diffusivity coef. for passive tracer     
[7753]79      zahu(:,:,:) = rldf * ahtu(:,:,:) 
80      zahv(:,:,:) = rldf * ahtv(:,:,:)
[6403]81      !                                  !* Enhanced zonal diffusivity coefficent in the equatorial domain
82      DO jk= 1, jpk
83         DO jj = 1, jpj
84            DO ji = 1, jpi
85               IF( gdept_n(ji,jj,jk) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN
86                  zdep = MAX( gdept_n(ji,jj,jk) - 1000., 0. ) / 1000.
87                  zahu(ji,jj,jk) = zahu(ji,jj,jk) * MAX( 1., rn_fact_lap * EXP( -zdep ) )
88               ENDIF
89            END DO
90         END DO
91      END DO
92      !
[9490]93      SELECT CASE ( nldf_trc )                 !* compute lateral mixing trend and add it to the general trend
[5836]94      !
95      CASE ( np_lap   )                               ! iso-level laplacian
[9490]96         CALL tra_ldf_lap  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb,      tra, jptra,    1     )
[5836]97      CASE ( np_lap_i )                               ! laplacian : standard iso-neutral operator (Madec)
[9490]98         CALL tra_ldf_iso  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,    1     )
[5836]99      CASE ( np_lap_it )                              ! laplacian : triad iso-neutral operator (griffies)
[10922]100         CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,    1    , Kmm )
[5836]101      CASE ( np_blp , np_blp_i , np_blp_it )          ! bilaplacian: all operator (iso-level, -neutral)
[10922]102         CALL tra_ldf_blp  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb     , tra, jptra, nldf_trc, Kmm )
[2030]103      END SELECT
104      !
[6140]105      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics
[2030]106        DO jn = 1, jptra
[7753]107           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn)
[10946]108           CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) )
[2030]109        END DO
[9125]110        DEALLOCATE( ztrtrd )
[2030]111      ENDIF
[6140]112      !               
113      IF( ln_ctl ) THEN                        ! print mean trends (used for debugging)
114         WRITE(charout, FMT="('ldf ')")
115         CALL prt_ctl_trc_info(charout)
116         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
[2030]117      ENDIF
118      !
[9124]119      IF( ln_timing )   CALL timing_stop('trc_ldf')
[3294]120      !
[2030]121   END SUBROUTINE trc_ldf
122
123
[5836]124   SUBROUTINE trc_ldf_ini
[2030]125      !!----------------------------------------------------------------------
126      !!                  ***  ROUTINE ldf_ctl  ***
[3294]127      !!
[5836]128      !! ** Purpose :   Define the operator for the lateral diffusion
[2030]129      !!
[9526]130      !! ** Method  : - ln_trcldf_tra=T : use nldf_tra set in ldftra module
[9490]131      !!              to defined the passive tracer lateral diffusive operator
[9526]132      !!              - ln_trcldf_OFF=T : no explicit diffusion used
[2030]133      !!----------------------------------------------------------------------
[9490]134      INTEGER ::   ios, ioptio   ! local integers
[6140]135      !!
[9526]136      NAMELIST/namtrc_ldf/ ln_trcldf_OFF , ln_trcldf_tra,   &   ! operator & direction
[9490]137         &                 rn_ldf_multi  , rn_fact_lap          ! coefficient
[2030]138      !!----------------------------------------------------------------------
[6140]139      !
[9490]140      IF(lwp) THEN
141         WRITE(numout,*)
142         WRITE(numout,*) 'trc_ldf_ini : lateral passive tracer diffusive operator'
143         WRITE(numout,*) '~~~~~~~~~~~'
144      ENDIF
145      !
[6140]146      REWIND( numnat_ref )             !  namtrc_ldf in reference namelist
[5836]147      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
[6140]148903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
149      !
150      REWIND( numnat_cfg )             !  namtrc_ldf in configuration namelist
[5836]151      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
[9169]152904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
[5836]153      IF(lwm) WRITE ( numont, namtrc_ldf )
[6140]154      !
155      IF(lwp) THEN                     ! Namelist print
[5836]156         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
[9526]157         WRITE(numout,*) '      no explicit diffusion                 ln_trcldf_OFF   = ', ln_trcldf_OFF
[9490]158         WRITE(numout,*) '      use active tracer operator            ln_trcldf_tra   = ', ln_trcldf_tra
159         WRITE(numout,*) '      diffusivity coefficient :'
[9526]160         WRITE(numout,*) '         multiplier of TRA coef. for TRC       rn_ldf_multi = ', rn_ldf_multi
161         WRITE(numout,*) '         enhanced zonal Eq. laplacian coef.    rn_fact_lap  = ', rn_fact_lap
[6403]162
[5836]163      ENDIF
164      !     
165      !                                ! control the namelist parameters
[9490]166      nldf_trc = np_ERROR
167      ioptio   = 0
[9526]168      IF( ln_trcldf_OFF  ) THEN   ;   nldf_trc = np_no_ldf   ;   ioptio = ioptio + 1   ;   ENDIF
[9490]169      IF( ln_trcldf_tra  ) THEN   ;   nldf_trc = nldf_tra    ;   ioptio = ioptio + 1   ;   ENDIF
170      IF( ioptio /=  1   )   CALL ctl_stop( 'trc_ldf_ini: use ONE of the 2 operator options (NONE/tra)' )
[5836]171     
[9490]172      !                                ! multiplier : passive/active tracers ration
173      IF( ln_traldf_lap ) THEN               ! laplacian operator
174         rldf = rn_ldf_multi                       ! simple multiplier
175      ELSEIF( ln_traldf_blp ) THEN           ! bilaplacian operator:
176         rldf = SQRT( ABS( rn_ldf_multi )  )       ! the coef. used is the SQRT of the bilaplacian coef.
[2030]177      ENDIF
[5836]178      !
[2030]179      IF(lwp) THEN
180         WRITE(numout,*)
[9490]181         SELECT CASE( nldf_trc )
[9019]182         CASE( np_no_ldf )   ;   WRITE(numout,*) '      ===>>   NO lateral diffusion'
183         CASE( np_lap    )   ;   WRITE(numout,*) '      ===>>   laplacian iso-level operator'
184         CASE( np_lap_i  )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (standard)'
185         CASE( np_lap_it )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (triad)'
186         CASE( np_blp    )   ;   WRITE(numout,*) '      ===>>   bilaplacian iso-level operator'
187         CASE( np_blp_i  )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (standard)'
188         CASE( np_blp_it )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (triad)'
[6140]189         END SELECT
[2030]190      ENDIF
191      !
[5836]192   END SUBROUTINE trc_ldf_ini
[9019]193
[2030]194#endif
195   !!======================================================================
196END MODULE trcldf
Note: See TracBrowser for help on using the repository browser.