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

source: NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/TRA/tranpc.F90 @ 9939

Last change on this file since 9939 was 9939, checked in by gm, 6 years ago

#1911 (ENHANCE-04): RK3 branche phased with MLF@9937 branche

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