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_r13383_HPC-02_Daley_Tiling/src/OCE/TRA – NEMO

source: NEMO/branches/2020/dev_r13383_HPC-02_Daley_Tiling/src/OCE/TRA/tranpc.F90 @ 13551

Last change on this file since 13551 was 13551, checked in by hadcv, 4 years ago

#2365: Replace trd_tra workarounds with ctl_warn if using tiling

  • Property svn:keywords set to Id
File size: 17.3 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: This change not necessary after extra haloes development (lbc_lnk removed)
20   USE domain, ONLY : dom_tile
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(ST_2D(nn_hls),jpk     )   ::   zn2              ! N^2
78      REAL(wp), DIMENSION(ST_2D(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      LOGICAL :: lp_monitor_point = .FALSE.      ! in CPU domain "nncpu"
84      !!----------------------------------------------------------------------
85      !
86      IF( ln_timing )   CALL timing_start('tra_npc')
87      !
88      IF( MOD( kt, nn_npc ) == 0 ) THEN
89         !
90         IF( l_trdtra )   THEN                    !* Save initial after fields
91            ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) )
92            ztrdt(:,:,:) = pts(:,:,:,jp_tem,Kaa)
93            ztrds(:,:,:) = pts(:,:,:,jp_sal,Kaa)
94         ENDIF
95         !
96         ! TODO: NOT TESTED- requires ORCA2
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         DO_2D( 0, 0, 0, 0 )
110            !
111            IF( tmask(ji,jj,2) == 1 ) THEN      ! At least 2 ocean points
112               !                                     ! consider one ocean column
113               zvts(:,jp_tem) = pts(ji,jj,:,jp_tem,Kaa)      ! temperature
114               zvts(:,jp_sal) = pts(ji,jj,:,jp_sal,Kaa)      ! salinity
115               !
116               zvab(:,jp_tem)  = zab(ji,jj,:,jp_tem)     ! Alpha
117               zvab(:,jp_sal)  = zab(ji,jj,:,jp_sal)     ! Beta 
118               zvn2(:)         = zn2(ji,jj,:)            ! N^2
119               !
120               IF( l_LB_debug ) THEN                  !LB debug:
121                  lp_monitor_point = .FALSE.
122                  IF( ( ji == ilc1 ).AND.( jj == jlc1 ) ) lp_monitor_point = .TRUE.
123                  ! writing only if on CPU domain where conv region is:
124                  lp_monitor_point = (narea == nncpu).AND.lp_monitor_point                     
125               ENDIF                                  !LB debug  end
126               !
127               ikbot = mbkt(ji,jj)   ! ikbot: ocean bottom T-level
128               ikp = 1                  ! because N2 is irrelevant at the surface level (will start at ikp=2)
129               ilayer = 0
130               jiter  = 0
131               l_column_treated = .FALSE.
132               !
133               DO WHILE ( .NOT. l_column_treated )
134                  !
135                  jiter = jiter + 1
136                  !
137                  IF( jiter >= 400 ) EXIT
138                  !
139                  l_bottom_reached = .FALSE.
140                  !
141                  DO WHILE ( .NOT. l_bottom_reached )
142                     !
143                     ikp = ikp + 1
144                     !
145                     !! Testing level ikp for instability
146                     !! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
147                     IF( zvn2(ikp) <  -zn2_zero ) THEN ! Instability found!
148                        !
149                        ilayer = ilayer + 1    ! yet another instable portion of the water column found....
150                        !
151                        IF( lp_monitor_point ) THEN
152                           WRITE(numout,*)
153                           IF( ilayer == 1 .AND. jiter == 1 ) THEN   ! first time a column is spoted with an instability
154                              WRITE(numout,*)
155                              WRITE(numout,*) 'Time step = ',kt,' !!!'
156                           ENDIF
157                           WRITE(numout,*)  ' * Iteration #',jiter,': found instable portion #',ilayer,   &
158                              &                                    ' in column! Starting at ikp =', ikp
159                           WRITE(numout,*)  ' *** N2 for point (i,j) = ',ji,' , ',jj
160                           DO jk = 1, klc1
161                              WRITE(numout,*) jk, zvn2(jk)
162                           END DO
163                           WRITE(numout,*)
164                        ENDIF
165                        !
166                        IF( jiter == 1 )   nnpcc = nnpcc + 1
167                        !
168                        IF( lp_monitor_point )   WRITE(numout, *) 'Negative N2 at ikp =',ikp,' for layer #', ilayer
169                        !
170                        !! ikup is the uppermost point where mixing will start:
171                        ikup = ikp - 1 ! ikup is always "at most at ikp-1", less if neutral levels overlying
172                        !
173                        !! If the points above ikp-1 have N2 == 0 they must also be mixed:
174                        IF( ikp > 2 ) THEN
175                           DO jk = ikp-1, 2, -1
176                              IF( ABS(zvn2(jk)) < zn2_zero ) THEN
177                                 ikup = ikup - 1  ! 1 more upper level has N2=0 and must be added for the mixing
178                              ELSE
179                                 EXIT
180                              ENDIF
181                           END DO
182                        ENDIF
183                        !
184                        IF( ikup < 1 )   CALL ctl_stop( 'tra_npc :  PROBLEM #1')
185                        !
186                        zsum_temp = 0._wp
187                        zsum_sali = 0._wp
188                        zsum_alfa = 0._wp
189                        zsum_beta = 0._wp
190                        zsum_z    = 0._wp
191                                                 
192                        DO jk = ikup, ikbot      ! Inside the instable (and overlying neutral) portion of the column
193                           !
194                           zdz       = e3t(ji,jj,jk,Kmm)
195                           zsum_temp = zsum_temp + zvts(jk,jp_tem)*zdz
196                           zsum_sali = zsum_sali + zvts(jk,jp_sal)*zdz
197                           zsum_alfa = zsum_alfa + zvab(jk,jp_tem)*zdz
198                           zsum_beta = zsum_beta + zvab(jk,jp_sal)*zdz
199                           zsum_z    = zsum_z    + zdz
200                           !                             
201                           IF( jk == ikbot ) EXIT ! avoid array-index overshoot in case ikbot = jpk, cause we're calling jk+1 next line
202                           !! EXIT when we have reached the last layer that is instable (N2<0) or neutral (N2=0):
203                           IF( zvn2(jk+1) > zn2_zero ) EXIT
204                        END DO
205                       
206                        ikdown = jk ! for the current unstable layer, ikdown is the deepest point with a negative or neutral N2
207                        IF( ikup == ikdown )   CALL ctl_stop( 'tra_npc :  PROBLEM #2')
208
209                        ! Mixing Temperature, salinity, alpha and beta from ikup to ikdown included:
210                        zta   = zsum_temp/zsum_z
211                        zsa   = zsum_sali/zsum_z
212                        zalfa = zsum_alfa/zsum_z
213                        zbeta = zsum_beta/zsum_z
214
215                        IF( lp_monitor_point ) THEN
216                           WRITE(numout,*) 'MIXED T, S, alfa and beta between ikup =',ikup,   &
217                              &            ' and ikdown =',ikdown,', in layer #',ilayer
218                           WRITE(numout,*) '  => Mean temp. in that portion =', zta
219                           WRITE(numout,*) '  => Mean sali. in that portion =', zsa
220                           WRITE(numout,*) '  => Mean Alfa  in that portion =', zalfa
221                           WRITE(numout,*) '  => Mean Beta  in that portion =', zbeta
222                        ENDIF
223
224                        !! Homogenaizing the temperature, salinity, alpha and beta in this portion of the column
225                        DO jk = ikup, ikdown
226                           zvts(jk,jp_tem) = zta
227                           zvts(jk,jp_sal) = zsa
228                           zvab(jk,jp_tem) = zalfa
229                           zvab(jk,jp_sal) = zbeta
230                        END DO
231                       
232                       
233                        !! Updating N2 in the relvant portion of the water column
234                        !! Temperature, Salinity, Alpha and Beta have been homogenized in the unstable portion
235                        !! => Need to re-compute N2! will use Alpha and Beta!
236                       
237                        ikup   = MAX(2,ikup)         ! ikup can never be 1 !
238                        ik_low = MIN(ikdown+1,ikbot) ! we must go 1 point deeper than ikdown!
239                       
240                        DO jk = ikup, ik_low              ! we must go 1 point deeper than ikdown!
241
242                           !! Interpolating alfa and beta at W point:
243                           zrw =  (gdepw(ji,jj,jk  ,Kmm) - gdept(ji,jj,jk,Kmm)) &
244                              & / (gdept(ji,jj,jk-1,Kmm) - gdept(ji,jj,jk,Kmm))
245                           zaw = zvab(jk,jp_tem) * (1._wp - zrw) + zvab(jk-1,jp_tem) * zrw
246                           zbw = zvab(jk,jp_sal) * (1._wp - zrw) + zvab(jk-1,jp_sal) * zrw
247
248                           !! N2 at W point, doing exactly as in eosbn2.F90:
249                           zvn2(jk) = grav*( zaw * ( zvts(jk-1,jp_tem) - zvts(jk,jp_tem) )     &
250                              &            - zbw * ( zvts(jk-1,jp_sal) - zvts(jk,jp_sal) )  )  &
251                              &       / e3w(ji,jj,jk,Kmm) * tmask(ji,jj,jk)
252
253                           !! OR, faster  => just considering the vertical gradient of density
254                           !! as only the signa maters...
255                           !zvn2(jk) = (  zaw * ( zvts(jk-1,jp_tem) - zvts(jk,jp_tem) )     &
256                           !     &      - zbw * ( zvts(jk-1,jp_sal) - zvts(jk,jp_sal) )  )
257
258                        END DO
259                     
260                        ikp = MIN(ikdown+1,ikbot)
261                       
262
263                     ENDIF  !IF( zvn2(ikp) < 0. )
264
265
266                     IF( ikp == ikbot ) l_bottom_reached = .TRUE.
267                     !
268                  END DO ! DO WHILE ( .NOT. l_bottom_reached )
269
270                  IF( ikp /= ikbot )   CALL ctl_stop( 'tra_npc :  PROBLEM #3')
271                 
272                  ! ******* At this stage ikp == ikbot ! *******
273                 
274                  IF( ilayer > 0 ) THEN      !! least an unstable layer has been found
275                     !
276                     IF( lp_monitor_point ) THEN
277                        WRITE(numout,*)
278                        WRITE(numout,*) 'After ',jiter,' iteration(s), we neutralized ',ilayer,' instable layer(s)'
279                        WRITE(numout,*) '   ==> N2 at i,j=',ji,',',jj,' now looks like this:'
280                        DO jk = 1, klc1
281                           WRITE(numout,*) jk, zvn2(jk)
282                        END DO
283                        WRITE(numout,*)
284                     ENDIF
285                     !
286                     ikp    = 1     ! starting again at the surface for the next iteration
287                     ilayer = 0
288                  ENDIF
289                  !
290                  IF( ikp >= ikbot )   l_column_treated = .TRUE.
291                  !
292               END DO ! DO WHILE ( .NOT. l_column_treated )
293
294               !! Updating pts:
295               pts(ji,jj,:,jp_tem,Kaa) = zvts(:,jp_tem)
296               pts(ji,jj,:,jp_sal,Kaa) = zvts(:,jp_sal)
297
298               !! LB:  Potentially some other global variable beside theta and S can be treated here
299               !!      like BGC tracers.
300
301               IF( lp_monitor_point )   WRITE(numout,*)
302
303            ENDIF ! IF( tmask(ji,jj,3) == 1 ) THEN
304
305         END_2D
306         !
307         IF( l_trdtra ) THEN         ! send the Non penetrative mixing trends for diagnostic
308            z1_rDt = 1._wp / (2._wp * rn_Dt)
309            ztrdt(:,:,:) = ( pts(:,:,:,jp_tem,Kaa) - ztrdt(:,:,:) ) * z1_rDt
310            ztrds(:,:,:) = ( pts(:,:,:,jp_sal,Kaa) - ztrds(:,:,:) ) * z1_rDt
311            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_npc, ztrdt )
312            CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_npc, ztrds )
313            DEALLOCATE( ztrdt, ztrds )
314         ENDIF
315         !
316         ! TEMP: This change not necessary after extra haloes development (lbc_lnk removed)
317         IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only for the full domain
318            CALL lbc_lnk_multi( 'tranpc', pts(:,:,:,jp_tem,Kaa), 'T', 1.0_wp, pts(:,:,:,jp_sal,Kaa), 'T', 1.0_wp )
319            !
320            IF( lwp .AND. l_LB_debug ) THEN
321               WRITE(numout,*) 'Exiting tra_npc , kt = ',kt,', => numb. of statically instable water-columns: ', nnpcc
322               WRITE(numout,*)
323            ENDIF
324         ENDIF
325         !
326      ENDIF   ! IF( MOD( kt, nn_npc ) == 0 ) THEN
327      !
328      IF( ln_timing )   CALL timing_stop('tra_npc')
329      !
330   END SUBROUTINE tra_npc
331
332   !!======================================================================
333END MODULE tranpc
Note: See TracBrowser for help on using the repository browser.