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 branches/2015/dev_merge_2015/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2015/dev_merge_2015/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90 @ 6060

Last change on this file since 6060 was 6060, checked in by timgraham, 9 years ago

Merged dev_r5836_noc2_VVL_BY_DEFAULT into branch

  • Property svn:keywords set to Id
File size: 14.9 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   !!----------------------------------------------------------------------
[6060]14   !!   trc_ldf       : update the tracer trend with the lateral diffusion
15   !!   trc_ldf_ini   : initialization, namelist read, and parameters control
[2030]16   !!----------------------------------------------------------------------
[6060]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
[5836]25   !
[6060]26   USE prtctl_trc     ! Print control
[2030]27
28   IMPLICIT NONE
29   PRIVATE
30
[5836]31   PUBLIC   trc_ldf   
32   PUBLIC   trc_ldf_ini   
33   !
34   LOGICAL , PUBLIC ::   ln_trcldf_lap       !:   laplacian operator
35   LOGICAL , PUBLIC ::   ln_trcldf_blp       !: bilaplacian operator
36   LOGICAL , PUBLIC ::   ln_trcldf_lev       !: iso-level   direction
37   LOGICAL , PUBLIC ::   ln_trcldf_hor       !: horizontal  direction (rotation to geopotential)
38   LOGICAL , PUBLIC ::   ln_trcldf_iso       !: iso-neutral direction (standard)
39   LOGICAL , PUBLIC ::   ln_trcldf_triad     !: iso-neutral direction (triad)
40   REAL(wp), PUBLIC ::   rn_ahtrc_0          !:   laplacian diffusivity coefficient for passive tracer [m2/s]
41   REAL(wp), PUBLIC ::   rn_bhtrc_0          !: bilaplacian      -          --     -       -   [m4/s]
42   !
[6060]43   !                      !!: ** lateral mixing namelist (nam_trcldf) **
44   REAL(wp) ::  rldf       ! ratio between active and passive tracers diffusive coefficient
45   
[3294]46   INTEGER  ::  nldf = 0   ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals)
[5836]47   
[2030]48   !! * Substitutions
49#  include "vectopt_loop_substitute.h90"
50   !!----------------------------------------------------------------------
[5836]51   !! NEMO/TOP 3.7 , NEMO Consortium (2014)
[3294]52   !! $Id$
[2287]53   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2030]54   !!----------------------------------------------------------------------
55CONTAINS
56
57   SUBROUTINE trc_ldf( kt )
58      !!----------------------------------------------------------------------
59      !!                  ***  ROUTINE tra_ldf  ***
[3294]60      !!
[2030]61      !! ** Purpose :   compute the lateral ocean tracer physics.
62      !!
63      !!----------------------------------------------------------------------
64      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
[6060]65      !
[2030]66      INTEGER            :: jn
67      CHARACTER (len=22) :: charout
[5836]68      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zahu, zahv
[3294]69      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd
[2030]70      !!----------------------------------------------------------------------
[3294]71      !
72      IF( nn_timing == 1 )   CALL timing_start('trc_ldf')
73      !
74      IF( l_trdtrc )  THEN
[5836]75         CALL wrk_alloc( jpi,jpj,jpk,jptra,   ztrtrd )
[2030]76         ztrtrd(:,:,:,:)  = tra(:,:,:,:)
77      ENDIF
[5836]78      !
79      !                                        !* set the lateral diffusivity coef. for passive tracer     
80      CALL wrk_alloc( jpi,jpj,jpk,   zahu, zahv )
81      zahu(:,:,:) = rldf * ahtu(:,:,:)
82      zahv(:,:,:) = rldf * ahtv(:,:,:)
[2030]83
[5836]84      SELECT CASE ( nldf )                     !* compute lateral mixing trend and add it to the general trend
85      !
86      CASE ( np_lap   )                               ! iso-level laplacian
87         CALL tra_ldf_lap  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb,      tra, jptra,  1   )
[2030]88         !
[5836]89      CASE ( np_lap_i )                               ! laplacian : standard iso-neutral operator (Madec)
90         CALL tra_ldf_iso  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   )
91         !
92      CASE ( np_lap_it )                              ! laplacian : triad iso-neutral operator (griffies)
93         CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   )
94         !
95      CASE ( np_blp , np_blp_i , np_blp_it )          ! bilaplacian: all operator (iso-level, -neutral)
96         CALL tra_ldf_blp  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb     , tra, jptra, nldf )
97         !
[2030]98      END SELECT
99      !
[6060]100      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics
[2030]101        DO jn = 1, jptra
102           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn)
[4990]103           CALL trd_tra( kt, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) )
[2030]104        END DO
[3294]105        CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd )
[2030]106      ENDIF
[6060]107      !               
108      IF( ln_ctl ) THEN                        ! print mean trends (used for debugging)
109         WRITE(charout, FMT="('ldf ')")
110         CALL prt_ctl_trc_info(charout)
111         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
[2030]112      ENDIF
113      !
[5836]114      CALL wrk_dealloc( jpi,jpj,jpk,   zahu, zahv )
115      !
[3294]116      IF( nn_timing == 1 )   CALL timing_stop('trc_ldf')
117      !
[2030]118   END SUBROUTINE trc_ldf
119
120
[5836]121   SUBROUTINE trc_ldf_ini
[2030]122      !!----------------------------------------------------------------------
123      !!                  ***  ROUTINE ldf_ctl  ***
[3294]124      !!
[5836]125      !! ** Purpose :   Define the operator for the lateral diffusion
[2030]126      !!
127      !! ** Method  :   set nldf from the namtra_ldf logicals
128      !!      nldf ==  0   laplacian operator
129      !!      nldf ==  1   Rotated laplacian operator
130      !!      nldf ==  2   bilaplacian operator
131      !!      nldf ==  3   Rotated bilaplacian
132      !!----------------------------------------------------------------------
[5836]133      INTEGER ::   ioptio, ierr   ! temporary integers
134      INTEGER ::   ios            ! Local integer output status for namelist read
[6060]135      !!
[5836]136      NAMELIST/namtrc_ldf/ ln_trcldf_lap, ln_trcldf_blp,                                  &
137         &                 ln_trcldf_lev, ln_trcldf_hor, ln_trcldf_iso, ln_trcldf_triad,  &
138         &                 rn_ahtrc_0   , rn_bhtrc_0
[2030]139      !!----------------------------------------------------------------------
[6060]140      !
141      REWIND( numnat_ref )             !  namtrc_ldf in reference namelist
[5836]142      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
[6060]143903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
144      !
145      REWIND( numnat_cfg )             !  namtrc_ldf in configuration namelist
[5836]146      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
[6060]147904   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
[5836]148      IF(lwm) WRITE ( numont, namtrc_ldf )
[6060]149      !
150      IF(lwp) THEN                     ! Namelist print
[5836]151         WRITE(numout,*)
152         WRITE(numout,*) 'trc_ldf_ini : lateral tracer diffusive operator'
153         WRITE(numout,*) '~~~~~~~~~~~'
154         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
155         WRITE(numout,*) '      operator'
156         WRITE(numout,*) '           laplacian                 ln_trcldf_lap   = ', ln_trcldf_lap
157         WRITE(numout,*) '         bilaplacian                 ln_trcldf_blp   = ', ln_trcldf_blp
158         WRITE(numout,*) '      direction of action'
159         WRITE(numout,*) '         iso-level                   ln_trcldf_lev   = ', ln_trcldf_lev
160         WRITE(numout,*) '         horizontal (geopotential)   ln_trcldf_hor   = ', ln_trcldf_hor
161         WRITE(numout,*) '         iso-neutral (standard)      ln_trcldf_iso   = ', ln_trcldf_iso
162         WRITE(numout,*) '         iso-neutral (triad)         ln_trcldf_triad = ', ln_trcldf_triad
163         WRITE(numout,*) '      diffusivity coefficient'
164         WRITE(numout,*) '           laplacian                 rn_ahtrc_0      = ', rn_ahtrc_0
165         WRITE(numout,*) '         bilaplacian                 rn_bhtrc_0      = ', rn_bhtrc_0
166      ENDIF
167      !     
168      !                                ! control the namelist parameters
[2030]169      ioptio = 0
[5836]170      IF( ln_trcldf_lap )   ioptio = ioptio + 1
171      IF( ln_trcldf_blp )   ioptio = ioptio + 1
172      IF( ioptio >  1   )   CALL ctl_stop( 'trc_ldf_ctl: use ONE or NONE of the 2 lap/bilap operator type on tracer' )
173      IF( ioptio == 0   )   nldf = np_no_ldf   ! No lateral diffusion
174     
175      IF( ln_trcldf_lap .AND. ln_trcldf_blp )   CALL ctl_stop( 'trc_ldf_ctl: bilaplacian should be used on both TRC and TRA' )
176      IF( ln_trcldf_blp .AND. ln_trcldf_lap )   CALL ctl_stop( 'trc_ldf_ctl:   laplacian should be used on both TRC and TRA' )
[6060]177      !
[2030]178      ioptio = 0
[5836]179      IF( ln_trcldf_lev )   ioptio = ioptio + 1
180      IF( ln_trcldf_hor )   ioptio = ioptio + 1
181      IF( ln_trcldf_iso )   ioptio = ioptio + 1
182      IF( ioptio /= 1   )   CALL ctl_stop( 'trc_ldf_ctl: use only ONE direction (level/hor/iso)' )
[6060]183      !
[2030]184      ! defined the type of lateral diffusion from ln_trcldf_... logicals
185      ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully
186      ierr = 0
[5836]187      IF( ln_trcldf_lap ) THEN      !==  laplacian operator  ==!
[2030]188         IF ( ln_zco ) THEN                ! z-coordinate
[5836]189            IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level = horizontal (no rotation)
190            IF ( ln_trcldf_hor   )   nldf = np_lap     ! iso-level = horizontal (no rotation)
191            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard  (   rotation)
192            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad     (   rotation)
[2030]193         ENDIF
[5836]194         IF ( ln_zps ) THEN             ! z-coordinate with partial step
195            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed
196            IF ( ln_trcldf_hor   )   nldf = np_lap     ! horizontal (no rotation)
197            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation)
198            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation)
[2030]199         ENDIF
[5836]200         IF ( ln_sco ) THEN             ! s-coordinate
201            IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level  (no rotation)
202            IF ( ln_trcldf_hor   )   nldf = np_lap_it  ! horizontal (   rotation)       !!gm   a checker....
203            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation)
204            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation)
[2030]205         ENDIF
[5836]206         !                                ! diffusivity ratio: passive / active tracers
[6060]207         IF( ABS(rn_aht_0) < 2._wp*TINY(1._wp) ) THEN
208            IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1._wp) ) THEN
[5836]209               rldf = 1.0_wp
210            ELSE
[6060]211               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' )
[5836]212            ENDIF
213         ELSE
214            rldf = rn_ahtrc_0 / rn_aht_0
215         ENDIF
[2030]216      ENDIF
[5836]217      !
218      IF( ln_trcldf_blp ) THEN      !==  bilaplacian operator  ==!
[2030]219         IF ( ln_zco ) THEN                ! z-coordinate
[5836]220            IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level = horizontal (no rotation)
221            IF ( ln_trcldf_hor   )   nldf = np_blp     ! iso-level = horizontal (no rotation)
222            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation)
223            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation)
[2030]224         ENDIF
[5836]225         IF ( ln_zps ) THEN             ! z-coordinate with partial step
226            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed
227            IF ( ln_trcldf_hor   )   nldf = np_blp     ! horizontal (no rotation)
228            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation)
229            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation)
[2030]230         ENDIF
[5836]231         IF ( ln_sco ) THEN             ! s-coordinate
232            IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level  (no rotation)
233            IF ( ln_trcldf_hor   )   nldf = np_blp_it  ! horizontal (   rotation)       !!gm   a checker....
234            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation)
235            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation)
[2030]236         ENDIF
[5836]237         !                                ! diffusivity ratio: passive / active tracers
[6060]238         IF( ABS(rn_bht_0) < 2._wp*TINY(1._wp) ) THEN
239            IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1._wp) ) THEN
[5836]240               rldf = 1.0_wp
241            ELSE
[6060]242               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' )
[5836]243            ENDIF
244         ELSE
245            rldf = SQRT(  ABS( rn_bhtrc_0 / rn_bht_0 )  )
246         ENDIF
[2030]247      ENDIF
[5836]248      !
[6060]249      IF( ierr == 1 )   CALL ctl_stop( 'trc_ldf_ctl: iso-level in z-partial step, not allowed' )
250      IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   CALL ctl_stop( 'trc_ldf_ctl: eiv requires isopycnal laplacian diffusion' )
251      IF( nldf == 1 .OR. nldf == 3 )   l_ldfslp = .TRUE.    ! slope of neutral surfaces required
[5836]252      !
[2030]253      IF(lwp) THEN
254         WRITE(numout,*)
[6060]255         SELECT CASE( nldf )
256         CASE( np_no_ldf )   ;   WRITE(numout,*) '          NO lateral diffusion'
257         CASE( np_lap    )   ;   WRITE(numout,*) '          laplacian iso-level operator'
258         CASE( np_lap_i  )   ;   WRITE(numout,*) '          Rotated laplacian operator (standard)'
259         CASE( np_lap_it )   ;   WRITE(numout,*) '          Rotated laplacian operator (triad)'
260         CASE( np_blp    )   ;   WRITE(numout,*) '          bilaplacian iso-level operator'
261         CASE( np_blp_i  )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (standard)'
262         CASE( np_blp_it )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (triad)'
263         END SELECT
[2030]264      ENDIF
265      !
[5836]266   END SUBROUTINE trc_ldf_ini
[2030]267#else
268   !!----------------------------------------------------------------------
269   !!   Default option                                         Empty module
270   !!----------------------------------------------------------------------
271CONTAINS
272   SUBROUTINE trc_ldf( kt )
273      INTEGER, INTENT(in) :: kt
274      WRITE(*,*) 'trc_ldf: You should not have seen this print! error?', kt
275   END SUBROUTINE trc_ldf
276#endif
277   !!======================================================================
278END MODULE trcldf
Note: See TracBrowser for help on using the repository browser.