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_crs.F90 in branches/UKMO/dev_r10171_test_crs_AMM7/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/dev_r10171_test_crs_AMM7/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf_crs.F90 @ 10207

Last change on this file since 10207 was 10207, checked in by cmao, 6 years ago

remove svn keyword

  • Property svn:executable set to *
File size: 12.4 KB
Line 
1MODULE trcldf_crs
2   !!======================================================================
3   !!                       ***  MODULE  trcldf  ***
4   !! Ocean Passive 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   !!----------------------------------------------------------------------
9#if defined key_top
10   !!----------------------------------------------------------------------
11   !!   'key_top'                                                TOP models
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
14   !!   trc_ldf     : update the tracer trend with the lateral diffusion
15   !!       ldf_ctl : initialization, namelist read, and parameters control
16   !!----------------------------------------------------------------------
17   USE oce_trc         ! ocean dynamics and active tracers
18   USE trc             ! ocean passive tracers variables
19   USE trcnam_trp      ! passive tracers transport namelist variables
20   !USE ldftra_oce      ! lateral diffusion coefficient on tracers
21   USE ldftra_oce,ONLY: ln_traldf_grif,rn_aht_0,rn_ahtb_0,lk_traldf_eiv     ! lateral diffusion coefficient on tracers
22   USE ldfslp          ! ???
23   USE traldf_iso_crs      ! lateral mixing            (tra_ldf_iso routine)
24   USE trd_oce
25   USE trdtra
26   USE prtctl_trc      ! Print control
27   !USE crs
28   USE trc_oce, ONLY : lk_offline 
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   trc_ldf_crs    ! called by step.F90
34   !                                                 !!: ** lateral mixing namelist (nam_trcldf) **
35   REAL(wp) ::  rldf_rat    ! ratio between active and passive tracers diffusive coefficient
36   INTEGER  ::  nldf = 0   ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals)
37   !! * Substitutions
38#  include "domzgr_substitute.h90"
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
42   !! $Id$
43   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE trc_ldf_crs( kt )
49      !!----------------------------------------------------------------------
50      !!                  ***  ROUTINE tra_ldf  ***
51      !!
52      !! ** Purpose :   compute the lateral ocean tracer physics.
53      !!
54      !!----------------------------------------------------------------------
55      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
56      !!
57      INTEGER            :: ji,jj,jk,jn
58      REAL(wp)           :: zdep
59      CHARACTER (len=22) :: charout
60      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd
61      !!----------------------------------------------------------------------
62      !
63      IF( nn_timing == 1 )   CALL timing_start('trc_ldf')
64      !
65      IF( kt == nittrc000 )   CALL ldf_ctl          ! initialisation & control of options
66
67      rldf = rldf_rat
68      !
69      r_fact_lap(:,:,:) = 1.
70      DO jk= 1, jpk
71         DO jj = 1, jpj
72            DO ji = 1, jpi
73               IF( fsdept(ji,jj,jk) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN
74                  zdep = MAX( fsdept(ji,jj,jk) - 1000., 0. ) / 1000.
75                  r_fact_lap(ji,jj,jk) = MAX( 1., rn_fact_lap * EXP( -zdep ) )
76               ENDIF
77            END DO
78         END DO
79      END DO
80
81      IF( l_trdtrc )  THEN
82         CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrtrd )
83         ztrtrd(:,:,:,:)  = tra(:,:,:,:)
84      ENDIF
85
86      SELECT CASE ( nldf )                       ! compute lateral mixing trend and add it to the general trend
87      CASE ( 1 )                                                                                            ! rotated laplacian
88                        CALL tra_ldf_iso_crs     ( kt, nittrc000, 'TRC', gtru ,gtrv , trb, tra, jptra, rn_ahtb_0 )
89         !
90      CASE ( -1 )                                     ! esopa: test all possibility with control print
91                                            CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
92         CALL tra_ldf_iso_crs     ( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra, rn_ahtb_0 )
93         WRITE(charout, FMT="('ldf1 ')") ;  CALL prt_ctl_trc_info(charout)
94                                            CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
95      END SELECT
96      !
97      IF( l_trdtrc )   THEN                      ! save the horizontal diffusive trends for further diagnostics
98        DO jn = 1, jptra
99           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn)
100           CALL trd_tra( kt, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) )
101        END DO
102        CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd )
103      ENDIF
104      !                                          ! print mean trends (used for debugging)
105      IF( ln_ctl )   THEN
106         WRITE(charout, FMT="('ldf ')") ;  CALL prt_ctl_trc_info(charout)
107                                           CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
108      ENDIF
109      !
110      IF( nn_timing == 1 )   CALL timing_stop('trc_ldf')
111      !
112   END SUBROUTINE trc_ldf_crs
113
114
115   SUBROUTINE ldf_ctl
116      !!----------------------------------------------------------------------
117      !!                  ***  ROUTINE ldf_ctl  ***
118      !!
119      !! ** Purpose :   Choice of the operator for the lateral tracer diffusion
120      !!
121      !! ** Method  :   set nldf from the namtra_ldf logicals
122      !!      nldf == -2   No lateral diffusion
123      !!      nldf == -1   ESOPA test: ALL operators are used
124      !!      nldf ==  0   laplacian operator
125      !!      nldf ==  1   Rotated laplacian operator
126      !!      nldf ==  2   bilaplacian operator
127      !!      nldf ==  3   Rotated bilaplacian
128      !!----------------------------------------------------------------------
129      INTEGER ::   ioptio, ierr         ! temporary integers
130      !!----------------------------------------------------------------------
131
132      IF (ABS(rn_aht_0) < 2._wp*TINY(1.e0)) THEN
133       !  IF (ABS(rn_ahtrc_0) < 2._wp*TINY(1.e0)) THEN  !! cc
134       !     rldf_rat = 1.0_wp
135       !  ELSE
136       !     CALL ctl_stop( 'STOP', 'ldf_ctl : cannot define rldf_rat, rn_aht_0==0, rn_ahtrc_0 /=0' )
137       !  END IF
138          rldf_rat = 1.0_wp !!cc
139      ELSE
140         rldf_rat = rn_ahtrc_0 / rn_aht_0
141      END IF
142      !  Define the lateral mixing oparator for tracers
143      ! ===============================================
144
145      !                               ! control the input
146      ioptio = 0
147      IF( ln_trcldf_lap   )   ioptio = ioptio + 1
148      IF( ln_trcldf_bilap )   ioptio = ioptio + 1
149      IF( ioptio >  1 )   CALL ctl_stop( '          use ONE or NONE of the 2 lap/bilap operator type on tracer' )
150      IF( ioptio == 0 )   nldf = -2   ! No lateral diffusion
151      ioptio = 0
152      IF( ln_trcldf_level )   ioptio = ioptio + 1
153      IF( ln_trcldf_hor   )   ioptio = ioptio + 1
154      IF( ln_trcldf_iso   )   ioptio = ioptio + 1
155      IF( ioptio /= 1 )   CALL ctl_stop( '          use only ONE direction (level/hor/iso)' )
156
157      ! defined the type of lateral diffusion from ln_trcldf_... logicals
158      ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully
159      ierr = 0
160      IF( ln_trcldf_lap ) THEN       ! laplacian operator
161         IF ( ln_zco ) THEN                ! z-coordinate
162            IF ( ln_trcldf_level )   nldf = 0      ! iso-level  (no rotation)
163            IF ( ln_trcldf_hor   )   nldf = 0      ! horizontal (no rotation)
164            IF ( ln_trcldf_iso   )   nldf = 1      ! isoneutral (   rotation)
165         ENDIF
166         IF ( ln_zps ) THEN             ! z-coordinate
167            IF ( ln_trcldf_level )   ierr = 1      ! iso-level not allowed
168            IF ( ln_trcldf_hor   )   nldf = 0      ! horizontal (no rotation)
169            IF ( ln_trcldf_iso   )   nldf = 1      ! isoneutral (   rotation)
170         ENDIF
171         IF ( ln_sco ) THEN             ! z-coordinate
172            IF ( ln_trcldf_level )   nldf = 0      ! iso-level  (no rotation)
173            IF ( ln_trcldf_hor   )   nldf = 1      ! horizontal (   rotation)
174            IF ( ln_trcldf_iso   )   nldf = 1      ! isoneutral (   rotation)
175         ENDIF
176      ENDIF
177
178      IF( ln_trcldf_bilap ) THEN      ! bilaplacian operator
179         IF ( ln_zco ) THEN                ! z-coordinate
180            IF ( ln_trcldf_level )   nldf = 2      ! iso-level  (no rotation)
181            IF ( ln_trcldf_hor   )   nldf = 2      ! horizontal (no rotation)
182            IF ( ln_trcldf_iso   )   ierr = 2      ! isoneutral (   rotation)
183         ENDIF
184         IF ( ln_zps ) THEN             ! z-coordinate
185            IF ( ln_trcldf_level )   ierr = 1      ! iso-level not allowed
186            IF ( ln_trcldf_hor   )   nldf = 2      ! horizontal (no rotation)
187            IF ( ln_trcldf_iso   )   ierr = 2      ! isoneutral (   rotation)
188         ENDIF
189         IF ( ln_sco ) THEN             ! z-coordinate
190            IF ( ln_trcldf_level )   nldf = 2      ! iso-level  (no rotation)
191            IF ( ln_trcldf_hor   )   nldf = 3      ! horizontal (   rotation)
192            IF ( ln_trcldf_iso   )   ierr = 2      ! isoneutral (   rotation)
193         ENDIF
194      ENDIF
195
196      IF( ierr == 1 )   CALL ctl_stop( ' iso-level in z-coordinate - partial step, not allowed' )
197      IF( ierr == 2 )   CALL ctl_stop( ' isoneutral bilaplacian operator does not exist' )
198      IF( lk_traldf_eiv .AND. .NOT.ln_trcldf_iso )   &
199           CALL ctl_stop( '          eddy induced velocity on tracers',   &
200           &              ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion' )
201      IF( nldf == 1 .OR. nldf == 3 ) THEN      ! rotation
202         IF( .NOT.lk_ldfslp )   CALL ctl_stop( '          the rotation of the diffusive tensor require key_ldfslp' )
203#if defined key_offline
204         l_traldf_rot = .TRUE.                 ! needed for trazdf_imp
205#endif
206      ENDIF
207
208      IF( lk_esopa ) THEN
209         IF(lwp) WRITE(numout,*) '          esopa control: use all lateral physics options'
210         nldf = -1
211      ENDIF
212
213      IF(lwp) THEN
214         WRITE(numout,*)
215         IF( nldf == -2 )   WRITE(numout,*) '          NO lateral diffusion'
216         IF( nldf == -1 )   WRITE(numout,*) '          ESOPA test All scheme used'
217         IF( nldf ==  0 )   WRITE(numout,*) '          laplacian operator'
218         IF( nldf ==  1 )   WRITE(numout,*) '          Rotated laplacian operator'
219         IF( nldf ==  2 )   WRITE(numout,*) '          bilaplacian operator'
220         IF( nldf ==  3 )   WRITE(numout,*) '          Rotated bilaplacian'
221      ENDIF
222
223      IF( ln_trcldf_bilap ) THEN
224         IF(lwp) WRITE(numout,*) '          biharmonic tracer diffusion'
225         IF( rn_ahtrc_0 > 0 .AND. .NOT. lk_esopa )   CALL ctl_stop( 'The horizontal diffusivity coef. rn_ahtrc_0 must be negative' )
226      ELSE
227         IF(lwp) WRITE(numout,*) '          harmonic tracer diffusion (default)'
228         IF( rn_ahtrc_0 < 0 .AND. .NOT. lk_esopa )   CALL ctl_stop('The horizontal diffusivity coef. rn_ahtrc_0 must be positive' )
229      ENDIF
230
231      ! ratio between active and passive tracers diffusive coef.
232      IF (ABS(rn_aht_0) < 2._wp*TINY(1.e0)) THEN
233       !  IF (ABS(rn_ahtrc_0) < 2._wp*TINY(1.e0)) THEN   !!cc
234       !     rldf_rat = 1.0_wp
235       !  ELSE
236       !     CALL ctl_stop( 'STOP', 'ldf_ctl : cannot define rldf_rat, rn_aht_0==0, rn_ahtrc_0 /=0' )
237       !  END IF
238          rldf_rat = 1.0_wp   !!cc
239      ELSE
240         rldf_rat = rn_ahtrc_0 / rn_aht_0
241      END IF
242      IF( rldf_rat < 0 ) THEN
243         IF( .NOT.lk_offline ) THEN
244            CALL ctl_stop( 'Choose the same type of diffusive scheme both for active & passive tracers' )
245         ELSE
246            CALL ctl_stop( 'Change the sign of rn_aht_0 in namelist to -/+1' )
247         ENDIF
248      ENDIF
249      !
250   END SUBROUTINE ldf_ctl
251#else
252   !!----------------------------------------------------------------------
253   !!   Default option                                         Empty module
254   !!----------------------------------------------------------------------
255CONTAINS
256   SUBROUTINE trc_ldf_crs( kt )
257      INTEGER, INTENT(in) :: kt
258      WRITE(*,*) 'trc_ldf: You should not have seen this print! error?', kt
259   END SUBROUTINE trc_ldf_crs
260#endif
261   !!======================================================================
262END MODULE trcldf_crs
Note: See TracBrowser for help on using the repository browser.