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.
traldf.F90 in branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/OPA_SRC/TRA/traldf.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 8 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 11.5 KB
Line 
1MODULE traldf
2   !!======================================================================
3   !!                       ***  MODULE  traldf  ***
4   !! Ocean Active tracers : lateral diffusive trends
5   !!=====================================================================
6   !! History :  9.0  ! 2005-11  (G. Madec)  Original code
7   !!  NEMO      3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!            3.7  ! 2013-12  (G. Madec) remove the optional computation from T & S anomaly profiles and traldf_bilapg
9   !!             -   ! 2013-12  (F. Lemarie, G. Madec)  triad operator (Griffies) + Method of Stabilizing Correction
10   !!             -   ! 2014-01  (G. Madec, S. Masson)  restructuration/simplification of lateral diffusive operators
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   tra_ldf      : update the tracer trend with the lateral diffusion
15   !!   tra_ldf_init : initialization, namelist read, and parameters control
16   !!----------------------------------------------------------------------
17   USE oce           ! ocean dynamics and tracers
18   USE dom_oce       ! ocean space and time domain
19   USE phycst        ! physical constants
20   USE ldftra        ! lateral diffusion: eddy diffusivity & EIV coeff.
21   USE ldfslp        ! lateral diffusion: iso-neutral slope
22   USE traldf_lap    ! lateral diffusion: laplacian iso-level            operator  (tra_ldf_lap   routine)
23   USE traldf_iso    ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso   routine)
24   USE traldf_triad  ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_triad routine)
25   USE traldf_blp    ! lateral diffusion (iso-level lap/blp)                       (tra_ldf_lap   routine)
26   USE trd_oce       ! trends: ocean variables
27   USE trdtra        ! ocean active tracers trends
28   !
29   USE prtctl         ! Print control
30   USE in_out_manager ! I/O manager
31   USE lib_mpp        ! distribued memory computing library
32   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
33   USE wrk_nemo       ! Memory allocation
34   USE timing         ! Timing
35
36   IMPLICIT NONE
37   PRIVATE
38
39   PUBLIC   tra_ldf        ! called by step.F90
40   PUBLIC   tra_ldf_init   ! called by nemogcm.F90
41   !
42   INTEGER ::   nldf = 0   ! type of lateral diffusion used defined from ln_traldf_... (namlist logicals)
43   
44   !! * Substitutions
45#  include "domzgr_substitute.h90"
46#  include "vectopt_loop_substitute.h90"
47   !!----------------------------------------------------------------------
48   !! NEMO/OPA 3.7 , NEMO Consortium (2015)
49   !! $Id$
50   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
51   !!----------------------------------------------------------------------
52CONTAINS
53
54   SUBROUTINE tra_ldf( kt )
55      !!----------------------------------------------------------------------
56      !!                  ***  ROUTINE tra_ldf  ***
57      !!
58      !! ** Purpose :   compute the lateral ocean tracer physics.
59      !!----------------------------------------------------------------------
60      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
61      !!
62      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdt, ztrds
63      !!----------------------------------------------------------------------
64      !
65      IF( nn_timing == 1 )   CALL timing_start('tra_ldf')
66      !
67      IF( l_trdtra )   THEN                    !* Save ta and sa trends
68         CALL wrk_alloc( jpi,jpj,jpk,   ztrdt, ztrds ) 
69         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) 
70         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
71      ENDIF
72      !
73      SELECT CASE ( nldf )                     !* compute lateral mixing trend and add it to the general trend
74      !
75      CASE ( np_lap   )                                  ! laplacian: iso-level operator
76         CALL tra_ldf_lap  ( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb,      tsa, jpts,  1   )
77      CASE ( np_lap_i )                                  ! laplacian: standard iso-neutral operator (Madec)
78         CALL tra_ldf_iso  ( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb, tsb, tsa, jpts,  1   )
79      CASE ( np_lap_it )                                 ! laplacian: triad iso-neutral operator (griffies)
80         CALL tra_ldf_triad( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb, tsb, tsa, jpts,  1   )
81      CASE ( np_blp , np_blp_i , np_blp_it )             ! bilaplacian: iso-level & iso-neutral operators
82         CALL tra_ldf_blp  ( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb      , tsa, jpts, nldf )
83      END SELECT
84
85      IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics
86         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
87         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
88         CALL trd_tra( kt, 'TRA', jp_tem, jptra_ldf, ztrdt )
89         CALL trd_tra( kt, 'TRA', jp_sal, jptra_ldf, ztrds )
90         CALL wrk_dealloc( jpi,jpj,jpk,   ztrdt, ztrds ) 
91      ENDIF
92      !                                        !* print mean trends (used for debugging)
93      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' ldf  - Ta: ', mask1=tmask,               &
94         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
95      !
96      IF( nn_timing == 1 )   CALL timing_stop('tra_ldf')
97      !
98   END SUBROUTINE tra_ldf
99
100
101   SUBROUTINE tra_ldf_init
102      !!----------------------------------------------------------------------
103      !!                  ***  ROUTINE tra_ldf_init  ***
104      !!
105      !! ** Purpose :   Choice of the operator for the lateral tracer diffusion
106      !!
107      !! ** Method  :   set nldf from the namtra_ldf logicals
108      !!----------------------------------------------------------------------
109      INTEGER ::   ioptio, ierr   ! temporary integers
110      !!----------------------------------------------------------------------
111      !
112      IF(lwp) THEN                     ! Namelist print
113         WRITE(numout,*)
114         WRITE(numout,*) 'tra_ldf_init : lateral tracer diffusive operator'
115         WRITE(numout,*) '~~~~~~~~~~~'
116         WRITE(numout,*) '   Namelist namtra_ldf already read in ldftra module'
117         WRITE(numout,*) '   see ldf_tra_init report for lateral mixing parameters'
118         WRITE(numout,*)
119      ENDIF
120      !                                   ! use of lateral operator or not
121      nldf   = np_ERROR
122      ioptio = 0
123      IF( ln_traldf_lap )   ioptio = ioptio + 1
124      IF( ln_traldf_blp )   ioptio = ioptio + 1
125      IF( ioptio >  1   )   CALL ctl_stop( 'tra_ldf_init: use ONE or NONE of the 2 lap/bilap operator type on tracer' )
126      IF( ioptio == 0   )   nldf = np_no_ldf     ! No lateral diffusion
127      !
128      IF( nldf /= np_no_ldf ) THEN        ! direction ==>> type of operator 
129         ioptio = 0
130         IF( ln_traldf_lev )   ioptio = ioptio + 1
131         IF( ln_traldf_hor )   ioptio = ioptio + 1
132         IF( ln_traldf_iso )   ioptio = ioptio + 1
133         IF( ioptio >  1 )   CALL ctl_stop( 'tra_ldf_init: use only ONE direction (level/hor/iso)' )
134         !
135         !                                ! defined the type of lateral diffusion from ln_traldf_... logicals
136         ierr = 0
137         IF( ln_traldf_lap ) THEN         ! laplacian operator
138            IF ( ln_zco ) THEN               ! z-coordinate
139               IF ( ln_traldf_lev   )   nldf = np_lap     ! iso-level = horizontal (no rotation)
140               IF ( ln_traldf_hor   )   nldf = np_lap     ! iso-level = horizontal (no rotation)
141               IF ( ln_traldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard  (   rotation)
142               IF ( ln_traldf_triad )   nldf = np_lap_it  ! iso-neutral: triad     (   rotation)
143            ENDIF
144            IF ( ln_zps ) THEN               ! z-coordinate with partial step
145               IF ( ln_traldf_lev   )   ierr = 1          ! iso-level not allowed
146               IF ( ln_traldf_hor   )   nldf = np_lap     ! horizontal             (no rotation)
147               IF ( ln_traldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard     (rotation)
148               IF ( ln_traldf_triad )   nldf = np_lap_it  ! iso-neutral: triad        (rotation)
149            ENDIF
150            IF ( ln_sco ) THEN               ! s-coordinate
151               IF ( ln_traldf_lev   )   nldf = np_lap     ! iso-level              (no rotation)
152               IF ( ln_traldf_hor   )   nldf = np_lap_i   ! horizontal             (   rotation)
153               IF ( ln_traldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard  (   rotation)
154               IF ( ln_traldf_triad )   nldf = np_lap_it  ! iso-neutral: triad     (   rotation)
155            ENDIF
156         ENDIF
157         !
158         IF( ln_traldf_blp ) THEN         ! bilaplacian operator
159            IF ( ln_zco ) THEN               ! z-coordinate
160               IF ( ln_traldf_lev   )   nldf = np_blp     ! iso-level = horizontal (no rotation)
161               IF ( ln_traldf_hor   )   nldf = np_blp     ! iso-level = horizontal (no rotation)
162               IF ( ln_traldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard  (   rotation)
163               IF ( ln_traldf_triad )   nldf = np_blp_it  ! iso-neutral: triad     (   rotation)
164            ENDIF
165            IF ( ln_zps ) THEN               ! z-coordinate with partial step
166               IF ( ln_traldf_lev   )   ierr = 1          ! iso-level not allowed
167               IF ( ln_traldf_hor   )   nldf = np_blp     ! horizontal             (no rotation)
168               IF ( ln_traldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard  (   rotation)
169               IF ( ln_traldf_triad )   nldf = np_blp_it  ! iso-neutral: triad     (   rotation)
170            ENDIF
171            IF ( ln_sco ) THEN               ! s-coordinate
172               IF ( ln_traldf_lev   )   nldf = np_blp     ! iso-level              (no rotation)
173               IF ( ln_traldf_hor   )   nldf = np_blp_it  ! horizontal             (   rotation)
174               IF ( ln_traldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard  (   rotation)
175               IF ( ln_traldf_triad )   nldf = np_blp_it  ! iso-neutral: triad     (   rotation)
176            ENDIF
177         ENDIF
178      ENDIF
179      !
180      IF( ierr == 1 )   CALL ctl_stop( ' iso-level in z-coordinate - partial step, not allowed' )
181      IF( ln_ldfeiv .AND. .NOT.( ln_traldf_iso .OR. ln_traldf_triad ) )                                    &
182           &            CALL ctl_stop( '          eddy induced velocity on tracers requires isopycnal',    &
183           &                                                                    ' laplacian diffusion' )
184      IF(  nldf == np_lap_i .OR. nldf == np_lap_it .OR. &
185         & nldf == np_blp_i .OR. nldf == np_blp_it  )   l_ldfslp = .TRUE.    ! slope of neutral surfaces required
186      !
187      IF(lwp) THEN
188         WRITE(numout,*)
189         IF( nldf == np_no_ldf )   WRITE(numout,*) '          NO lateral diffusion'
190         IF( nldf == np_lap    )   WRITE(numout,*) '          laplacian iso-level operator'
191         IF( nldf == np_lap_i  )   WRITE(numout,*) '          Rotated laplacian operator (standard)'
192         IF( nldf == np_lap_it )   WRITE(numout,*) '          Rotated laplacian operator (triad)'
193         IF( nldf == np_blp    )   WRITE(numout,*) '          bilaplacian iso-level operator'
194         IF( nldf == np_blp_i  )   WRITE(numout,*) '          Rotated bilaplacian operator (standard)'
195         IF( nldf == np_blp_it )   WRITE(numout,*) '          Rotated bilaplacian operator (triad)'
196      ENDIF
197      !
198   END SUBROUTINE tra_ldf_init
199
200   !!======================================================================
201END MODULE traldf
Note: See TracBrowser for help on using the repository browser.