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.
tranpc.F90 in NEMO/branches/2020/dev_14237_KERNEL-01_IMMERSE_SEAMOUNT/src/OCE/TRA – NEMO

source: NEMO/branches/2020/dev_14237_KERNEL-01_IMMERSE_SEAMOUNT/src/OCE/TRA/tranpc.F90 @ 14676

Last change on this file since 14676 was 14215, checked in by acc, 3 years ago

trunk changes to swap the order of arguments to the DO LOOP macros. These changes result in a more natural i-j-k ordering as explained in #2595. SETTE is passed before and after these changes and results are unchanged. This fixes #2595

  • Property svn:keywords set to Id
File size: 17.1 KB
Line 
1MODULE tranpc
2   !!==============================================================================
3   !!                       ***  MODULE  tranpc  ***
4   !! Ocean active tracers:  non penetrative convective adjustment scheme
5   !!==============================================================================
6   !! History :  1.0  ! 1990-09  (G. Madec)  Original code
7   !!                 ! 1996-01  (G. Madec)  statement function for e3
8   !!   NEMO     1.0  ! 2002-06  (G. Madec)  free form F90
9   !!            3.0  ! 2008-06  (G. Madec)  applied on ta, sa and called before tranxt in step.F90
10   !!            3.3  ! 2010-05  (C. Ethe, G. Madec)  merge TRC-TRA
11   !!            3.6  ! 2015-05  (L. Brodeau) new algorithm based on local Brunt-Vaisala freq.
12   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   tra_npc       : apply the non penetrative convection scheme
16   !!----------------------------------------------------------------------
17   USE oce            ! ocean dynamics and active tracers
18   USE dom_oce        ! ocean space and time domain
19   ! TEMP: [tiling] This change not necessary after extra haloes development (lbc_lnk removed)
20   USE domtile
21   USE phycst         ! physical constants
22   USE zdf_oce        ! ocean vertical physics
23   USE trd_oce        ! ocean active tracer trends
24   USE trdtra         ! ocean active tracer trends
25   USE eosbn2         ! equation of state (eos routine)
26   !
27   USE lbclnk         ! lateral boundary conditions (or mpp link)
28   USE in_out_manager ! I/O manager
29   USE lib_mpp        ! MPP library
30   USE timing         ! Timing
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   tra_npc    ! routine called by step.F90
36
37   INTEGER  ::   nnpcc        ! number of statically instable water column
38
39   !! * Substitutions
40#  include "do_loop_substitute.h90"
41#  include "domzgr_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
44   !! $Id$
45   !! Software governed by the CeCILL license (see ./LICENSE)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE tra_npc( kt, Kmm, Krhs, pts, Kaa )
50      !!----------------------------------------------------------------------
51      !!                  ***  ROUTINE tranpc  ***
52      !!
53      !! ** Purpose : Non-penetrative convective adjustment scheme. solve
54      !!      the static instability of the water column on after fields
55      !!      while conserving heat and salt contents.
56      !!
57      !! ** Method  : updated algorithm able to deal with non-linear equation of state
58      !!              (i.e. static stability computed locally)
59      !!
60      !! ** Action  : - tsa: after tracers with the application of the npc scheme
61      !!              - send the associated trends for on-line diagnostics (l_trdtra=T)
62      !!
63      !! References :     Madec, et al., 1991, JPO, 21, 9, 1349-1371.
64      !!----------------------------------------------------------------------
65      INTEGER,                                   INTENT(in   ) :: kt              ! ocean time-step index
66      INTEGER,                                   INTENT(in   ) :: Kmm, Krhs, Kaa  ! time level indices
67      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts             ! active tracers and RHS of tracer equation
68      !
69      INTEGER  ::   ji, jj, jk   ! dummy loop indices
70      INTEGER  ::   jiter, ikbot, ikp, ikup, ikdown, ilayer, ik_low   ! local integers
71      LOGICAL  ::   l_bottom_reached, l_column_treated
72      REAL(wp) ::   zta, zalfa, zsum_temp, zsum_alfa, zaw, zdz, zsum_z
73      REAL(wp) ::   zsa, zbeta, zsum_sali, zsum_beta, zbw, zrw, z1_rDt
74      REAL(wp), PARAMETER ::   zn2_zero = 1.e-14_wp             ! acceptance criteria for neutrality (N2==0)
75      REAL(wp), DIMENSION(    jpk     )   ::   zvn2             ! vertical profile of N2 at 1 given point...
76      REAL(wp), DIMENSION(    jpk,jpts)   ::   zvts, zvab       ! vertical profile of T & S , and  alpha & betaat 1 given point
77      REAL(wp), DIMENSION(A2D(nn_hls),jpk     )   ::   zn2              ! N^2
78      REAL(wp), DIMENSION(A2D(nn_hls),jpk,jpts)   ::   zab              ! alpha and beta
79      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds ! 3D workspace
80      !
81      LOGICAL, PARAMETER :: l_LB_debug = .FALSE. ! set to true if you want to follow what is
82      INTEGER :: ilc1, jlc1, klc1, nncpu         ! actually happening in a water column at point "ilc1, jlc1"
83      INTEGER :: isi, isj, iei, iej
84      LOGICAL :: lp_monitor_point = .FALSE.      ! in CPU domain "nncpu"
85      !!----------------------------------------------------------------------
86      !
87      IF( ln_timing )   CALL timing_start('tra_npc')
88      !
89      IF( MOD( kt, nn_npc ) == 0 ) THEN
90         !
91         IF( l_trdtra )   THEN                    !* Save initial after fields
92            ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) )
93            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kaa)
94            ztrds(:,:,:) = pts(:,:,:,jp_sal,Kaa)
95         ENDIF
96         !
97         IF( l_LB_debug ) THEN
98            ! Location of 1 known convection site to follow what's happening in the water column
99            ilc1 = 45 ;  jlc1 = 3 ; !  ORCA2 4x4, Antarctic coast, more than 2 unstable portions in the  water column...
100            nncpu = 1  ;            ! the CPU domain contains the convection spot
101            klc1 =  mbkt(ilc1,jlc1) ! bottom of the ocean for debug point...
102         ENDIF
103         !
104         CALL eos_rab( pts(:,:,:,:,Kaa), zab, Kmm )         ! after alpha and beta (given on T-points)
105         CALL bn2    ( pts(:,:,:,:,Kaa), zab, zn2, Kmm )    ! after Brunt-Vaisala  (given on W-points)
106         !
107         IF( ntile == 0 .OR. ntile == 1 ) nnpcc = 0         ! Do only on the first tile
108         !
109         IF( ntsi == Nis0 ) THEN ; isi = nn_hls ; ELSE ; isi = 0 ; ENDIF    ! Avoid double-counting when using tiling
110         IF( ntsj == Njs0 ) THEN ; isj = nn_hls ; ELSE ; isj = 0 ; ENDIF
111         IF( ntei == Nie0 ) THEN ; iei = nn_hls ; ELSE ; iei = 0 ; ENDIF
112         IF( ntej == Nje0 ) THEN ; iej = nn_hls ; ELSE ; iej = 0 ; ENDIF
113         !
114         DO_2D( isi, iei, isj, iej )                        ! interior column only
115            !
116            IF( tmask(ji,jj,2) == 1 ) THEN      ! At least 2 ocean points
117               !                                     ! consider one ocean column
118               zvts(:,jp_tem) = pts(ji,jj,:,jp_tem,Kaa)      ! temperature
119               zvts(:,jp_sal) = pts(ji,jj,:,jp_sal,Kaa)      ! salinity
120               !
121               zvab(:,jp_tem)  = zab(ji,jj,:,jp_tem)     ! Alpha
122               zvab(:,jp_sal)  = zab(ji,jj,:,jp_sal)     ! Beta
123               zvn2(:)         = zn2(ji,jj,:)            ! N^2
124               !
125               IF( l_LB_debug ) THEN                  !LB debug:
126                  lp_monitor_point = .FALSE.
127                  IF( ( ji == ilc1 ).AND.( jj == jlc1 ) ) lp_monitor_point = .TRUE.
128                  ! writing only if on CPU domain where conv region is:
129                  lp_monitor_point = (narea == nncpu).AND.lp_monitor_point
130               ENDIF                                  !LB debug  end
131               !
132               ikbot = mbkt(ji,jj)   ! ikbot: ocean bottom T-level
133               ikp = 1                  ! because N2 is irrelevant at the surface level (will start at ikp=2)
134               ilayer = 0
135               jiter  = 0
136               l_column_treated = .FALSE.
137               !
138               DO WHILE ( .NOT. l_column_treated )
139                  !
140                  jiter = jiter + 1
141                  !
142                  IF( jiter >= 400 ) EXIT
143                  !
144                  l_bottom_reached = .FALSE.
145                  !
146                  DO WHILE ( .NOT. l_bottom_reached )
147                     !
148                     ikp = ikp + 1
149                     !
150                     !! Testing level ikp for instability
151                     !! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
152                     IF( zvn2(ikp) <  -zn2_zero ) THEN ! Instability found!
153                        !
154                        ilayer = ilayer + 1    ! yet another instable portion of the water column found....
155                        !
156                        IF( lp_monitor_point ) THEN
157                           WRITE(numout,*)
158                           IF( ilayer == 1 .AND. jiter == 1 ) THEN   ! first time a column is spoted with an instability
159                              WRITE(numout,*)
160                              WRITE(numout,*) 'Time step = ',kt,' !!!'
161                           ENDIF
162                           WRITE(numout,*)  ' * Iteration #',jiter,': found instable portion #',ilayer,   &
163                              &                                    ' in column! Starting at ikp =', ikp
164                           WRITE(numout,*)  ' *** N2 for point (i,j) = ',ji,' , ',jj
165                           DO jk = 1, klc1
166                              WRITE(numout,*) jk, zvn2(jk)
167                           END DO
168                           WRITE(numout,*)
169                        ENDIF
170                        !
171                        IF( jiter == 1 )   nnpcc = nnpcc + 1
172                        !
173                        IF( lp_monitor_point )   WRITE(numout, *) 'Negative N2 at ikp =',ikp,' for layer #', ilayer
174                        !
175                        !! ikup is the uppermost point where mixing will start:
176                        ikup = ikp - 1 ! ikup is always "at most at ikp-1", less if neutral levels overlying
177                        !
178                        !! If the points above ikp-1 have N2 == 0 they must also be mixed:
179                        IF( ikp > 2 ) THEN
180                           DO jk = ikp-1, 2, -1
181                              IF( ABS(zvn2(jk)) < zn2_zero ) THEN
182                                 ikup = ikup - 1  ! 1 more upper level has N2=0 and must be added for the mixing
183                              ELSE
184                                 EXIT
185                              ENDIF
186                           END DO
187                        ENDIF
188                        !
189                        IF( ikup < 1 )   CALL ctl_stop( 'tra_npc :  PROBLEM #1')
190                        !
191                        zsum_temp = 0._wp
192                        zsum_sali = 0._wp
193                        zsum_alfa = 0._wp
194                        zsum_beta = 0._wp
195                        zsum_z    = 0._wp
196
197                        DO jk = ikup, ikbot      ! Inside the instable (and overlying neutral) portion of the column
198                           !
199                           zdz       = e3t(ji,jj,jk,Kmm)
200                           zsum_temp = zsum_temp + zvts(jk,jp_tem)*zdz
201                           zsum_sali = zsum_sali + zvts(jk,jp_sal)*zdz
202                           zsum_alfa = zsum_alfa + zvab(jk,jp_tem)*zdz
203                           zsum_beta = zsum_beta + zvab(jk,jp_sal)*zdz
204                           zsum_z    = zsum_z    + zdz
205                           !
206                           IF( jk == ikbot ) EXIT ! avoid array-index overshoot in case ikbot = jpk, cause we're calling jk+1 next line
207                           !! EXIT when we have reached the last layer that is instable (N2<0) or neutral (N2=0):
208                           IF( zvn2(jk+1) > zn2_zero ) EXIT
209                        END DO
210
211                        ikdown = jk ! for the current unstable layer, ikdown is the deepest point with a negative or neutral N2
212                        IF( ikup == ikdown )   CALL ctl_stop( 'tra_npc :  PROBLEM #2')
213
214                        ! Mixing Temperature, salinity, alpha and beta from ikup to ikdown included:
215                        zta   = zsum_temp/zsum_z
216                        zsa   = zsum_sali/zsum_z
217                        zalfa = zsum_alfa/zsum_z
218                        zbeta = zsum_beta/zsum_z
219
220                        IF( lp_monitor_point ) THEN
221                           WRITE(numout,*) 'MIXED T, S, alfa and beta between ikup =',ikup,   &
222                              &            ' and ikdown =',ikdown,', in layer #',ilayer
223                           WRITE(numout,*) '  => Mean temp. in that portion =', zta
224                           WRITE(numout,*) '  => Mean sali. in that portion =', zsa
225                           WRITE(numout,*) '  => Mean Alfa  in that portion =', zalfa
226                           WRITE(numout,*) '  => Mean Beta  in that portion =', zbeta
227                        ENDIF
228
229                        !! Homogenaizing the temperature, salinity, alpha and beta in this portion of the column
230                        DO jk = ikup, ikdown
231                           zvts(jk,jp_tem) = zta
232                           zvts(jk,jp_sal) = zsa
233                           zvab(jk,jp_tem) = zalfa
234                           zvab(jk,jp_sal) = zbeta
235                        END DO
236
237
238                        !! Updating N2 in the relvant portion of the water column
239                        !! Temperature, Salinity, Alpha and Beta have been homogenized in the unstable portion
240                        !! => Need to re-compute N2! will use Alpha and Beta!
241
242                        ikup   = MAX(2,ikup)         ! ikup can never be 1 !
243                        ik_low = MIN(ikdown+1,ikbot) ! we must go 1 point deeper than ikdown!
244
245                        DO jk = ikup, ik_low              ! we must go 1 point deeper than ikdown!
246
247                           !! Interpolating alfa and beta at W point:
248                           zrw =  (gdepw(ji,jj,jk  ,Kmm) - gdept(ji,jj,jk,Kmm)) &
249                              & / (gdept(ji,jj,jk-1,Kmm) - gdept(ji,jj,jk,Kmm))
250                           zaw = zvab(jk,jp_tem) * (1._wp - zrw) + zvab(jk-1,jp_tem) * zrw
251                           zbw = zvab(jk,jp_sal) * (1._wp - zrw) + zvab(jk-1,jp_sal) * zrw
252
253                           !! N2 at W point, doing exactly as in eosbn2.F90:
254                           zvn2(jk) = grav*( zaw * ( zvts(jk-1,jp_tem) - zvts(jk,jp_tem) )     &
255                              &            - zbw * ( zvts(jk-1,jp_sal) - zvts(jk,jp_sal) )  )  &
256                              &       / e3w(ji,jj,jk,Kmm) * tmask(ji,jj,jk)
257
258                           !! OR, faster  => just considering the vertical gradient of density
259                           !! as only the signa maters...
260                           !zvn2(jk) = (  zaw * ( zvts(jk-1,jp_tem) - zvts(jk,jp_tem) )     &
261                           !     &      - zbw * ( zvts(jk-1,jp_sal) - zvts(jk,jp_sal) )  )
262
263                        END DO
264
265                        ikp = MIN(ikdown+1,ikbot)
266
267
268                     ENDIF  !IF( zvn2(ikp) < 0. )
269
270
271                     IF( ikp == ikbot ) l_bottom_reached = .TRUE.
272                     !
273                  END DO ! DO WHILE ( .NOT. l_bottom_reached )
274
275                  IF( ikp /= ikbot )   CALL ctl_stop( 'tra_npc :  PROBLEM #3')
276
277                  ! ******* At this stage ikp == ikbot ! *******
278
279                  IF( ilayer > 0 ) THEN      !! least an unstable layer has been found
280                     !
281                     IF( lp_monitor_point ) THEN
282                        WRITE(numout,*)
283                        WRITE(numout,*) 'After ',jiter,' iteration(s), we neutralized ',ilayer,' instable layer(s)'
284                        WRITE(numout,*) '   ==> N2 at i,j=',ji,',',jj,' now looks like this:'
285                        DO jk = 1, klc1
286                           WRITE(numout,*) jk, zvn2(jk)
287                        END DO
288                        WRITE(numout,*)
289                     ENDIF
290                     !
291                     ikp    = 1     ! starting again at the surface for the next iteration
292                     ilayer = 0
293                  ENDIF
294                  !
295                  IF( ikp >= ikbot )   l_column_treated = .TRUE.
296                  !
297               END DO ! DO WHILE ( .NOT. l_column_treated )
298
299               !! Updating pts:
300               pts(ji,jj,:,jp_tem,Kaa) = zvts(:,jp_tem)
301               pts(ji,jj,:,jp_sal,Kaa) = zvts(:,jp_sal)
302
303               !! LB:  Potentially some other global variable beside theta and S can be treated here
304               !!      like BGC tracers.
305
306               IF( lp_monitor_point )   WRITE(numout,*)
307
308            ENDIF ! IF( tmask(ji,jj,3) == 1 ) THEN
309
310         END_2D
311         !
312         IF( l_trdtra ) THEN         ! send the Non penetrative mixing trends for diagnostic
313            z1_rDt = 1._wp / (2._wp * rn_Dt)
314            ztrdt(:,:,:) = ( pts(:,:,:,jp_tem,Kaa) - ztrdt(:,:,:) ) * z1_rDt
315            ztrds(:,:,:) = ( pts(:,:,:,jp_sal,Kaa) - ztrds(:,:,:) ) * z1_rDt
316            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_npc, ztrdt )
317            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_npc, ztrds )
318            DEALLOCATE( ztrdt, ztrds )
319         ENDIF
320         !
321         IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain
322            IF( lwp .AND. l_LB_debug ) THEN
323               WRITE(numout,*) 'Exiting tra_npc , kt = ',kt,', => numb. of statically instable water-columns: ', nnpcc
324               WRITE(numout,*)
325            ENDIF
326         ENDIF
327         !
328      ENDIF   ! IF( MOD( kt, nn_npc ) == 0 ) THEN
329      !
330      IF( ln_timing )   CALL timing_stop('tra_npc')
331      !
332   END SUBROUTINE tra_npc
333
334   !!======================================================================
335END MODULE tranpc
Note: See TracBrowser for help on using the repository browser.