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/trunk/src/OCE/TRA – NEMO

source: NEMO/trunk/src/OCE/TRA/tranpc.F90

Last change on this file was 14834, checked in by hadcv, 3 years ago

#2600: Merge in dev_r14273_HPC-02_Daley_Tiling

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