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 branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/dev_r2586_dynamic_mem/NEMOGCM/NEMO/OPA_SRC/TRA/tranpc.F90 @ 2696

Last change on this file since 2696 was 2690, checked in by gm, 13 years ago

dynamic mem: #785 ; homogeneization of the coding style associated with dyn allocation

  • Property svn:keywords set to Id
File size: 10.0 KB
Line 
1MODULE tranpc
2   !!==============================================================================
3   !!                       ***  MODULE  tranpc  ***
4   !! Ocean active tracers:  non penetrative convection 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   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   tra_npc : apply the non penetrative convection scheme
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and active tracers
17   USE dom_oce         ! ocean space and time domain
18   USE zdf_oce         ! ocean vertical physics
19   USE trdmod_oce      ! ocean active tracer trends
20   USE trdtra          ! ocean active tracer trends
21   USE eosbn2          ! equation of state (eos routine)
22   USE lbclnk          ! lateral boundary conditions (or mpp link)
23   USE in_out_manager  ! I/O manager
24   USE lib_mpp         ! MPP library
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   tra_npc       ! routine called by step.F90
30
31   !! * Substitutions
32#  include "domzgr_substitute.h90"
33   !!----------------------------------------------------------------------
34   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
35   !! $Id$
36   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
37   !!----------------------------------------------------------------------
38CONTAINS
39
40   SUBROUTINE tra_npc( kt )
41      !!----------------------------------------------------------------------
42      !!                  ***  ROUTINE tranpc  ***
43      !!
44      !! ** Purpose :   Non penetrative convective adjustment scheme. solve
45      !!      the static instability of the water column on after fields
46      !!      while conserving heat and salt contents.
47      !!
48      !! ** Method  :   The algorithm used converges in a maximium of jpk
49      !!      iterations. instabilities are treated when the vertical density
50      !!      gradient is less than 1.e-5.
51      !!      l_trdtra=T: the trend associated with this algorithm is saved.
52      !!
53      !! ** Action  : - (ta,sa) after the application od the npc scheme
54      !!              - save the associated trends (ttrd,strd) ('key_trdtra')
55      !!
56      !! References : Madec, et al., 1991, JPO, 21, 9, 1349-1371.
57      !!----------------------------------------------------------------------
58      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released, wrk_in_use_xz, wrk_not_released_xz
59      USE wrk_nemo, ONLY:   ztrdt => wrk_3d_1 , ztrds => wrk_3d_2 , zrhop => wrk_3d_3
60      USE wrk_nemo, ONLY:   zwx   => wrk_xz_1 , zwy   => wrk_xz_2 , zwz   => wrk_xz_3
61      !
62      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
63      !
64      INTEGER  ::   ji, jj, jk   ! dummy loop indices
65      INTEGER  ::   inpcc        ! number of statically instable water column
66      INTEGER  ::   inpci        ! number of iteration for npc scheme
67      INTEGER  ::   jiter, jkdown, jkp        ! ???
68      INTEGER  ::   ikbot, ik, ikup, ikdown   ! ???
69      REAL(wp) ::   ze3tot, zta, zsa, zraua, ze3dwn
70      !!----------------------------------------------------------------------
71
72      ! Strictly 1 and 2 3D workspaces only needed if(l_trdtra) but it doesn't
73      ! cost us anything and makes code simpler.
74      IF( wrk_in_use(3, 1,2,3) .OR. wrk_in_use_xz(1,2,3) ) THEN
75         CALL ctl_stop('tra_npc: requested workspace arrays unavailable')   ;   RETURN
76      ENDIF
77
78      IF( MOD( kt, nn_npc ) == 0 ) THEN
79
80         inpcc = 0
81         inpci = 0
82
83         CALL eos( tsa, rhd, zrhop )         ! Potential density
84
85         IF( l_trdtra )   THEN                    !* Save ta and sa trends
86            ztrdt(:,:,:) = tsa(:,:,:,jp_tem) 
87            ztrds(:,:,:) = tsa(:,:,:,jp_sal)
88         ENDIF
89
90         !                                                ! ===============
91         DO jj = 1, jpj                                   !  Vertical slab
92            !                                             ! ===============
93            !  Static instability pointer
94            ! ----------------------------
95            DO jk = 1, jpkm1
96               DO ji = 1, jpi
97                  zwx(ji,jk) = ( zrhop(ji,jj,jk) - zrhop(ji,jj,jk+1) ) * tmask(ji,jj,jk+1)
98               END DO
99            END DO
100
101            ! 1.1 do not consider the boundary points
102
103            ! even if east-west cyclic b. c. do not considere ji=1 or jpi
104            DO jk = 1, jpkm1
105               zwx( 1 ,jk) = 0.e0
106               zwx(jpi,jk) = 0.e0
107            END DO
108            ! even if south-symmetric b. c. used, do not considere jj=1
109            IF( jj == 1 )   zwx(:,:) = 0.e0
110
111            DO jk = 1, jpkm1
112               DO ji = 1, jpi
113                  zwx(ji,jk) = 1.
114                  IF( zwx(ji,jk) < 1.e-5 ) zwx(ji,jk) = 0.e0
115               END DO
116            END DO
117
118            zwy(:,1) = 0.e0
119            DO ji = 1, jpi
120               DO jk = 1, jpkm1
121                  zwy(ji,1) = zwy(ji,1) + zwx(ji,jk)
122               END DO
123            END DO
124
125            zwz(1,1) = 0.e0
126            DO ji = 1, jpi
127               zwz(1,1) = zwz(1,1) + zwy(ji,1)
128            END DO
129
130            inpcc = inpcc + NINT( zwz(1,1) )
131
132
133            ! 2. Vertical mixing for each instable portion of the density profil
134            ! ------------------------------------------------------------------
135
136            IF( zwz(1,1) /= 0.e0 ) THEN         ! -->> the density profil is statically instable :
137               DO ji = 1, jpi
138                  IF( zwy(ji,1) /= 0.e0 ) THEN
139                     !
140                     ikbot = mbkt(ji,jj)        ! ikbot: ocean bottom T-level
141                     !
142                     DO jiter = 1, jpk          ! vertical iteration
143                        !
144                        ! search of ikup : the first static instability from the sea surface
145                        !
146                        ik = 0
147220                     CONTINUE
148                        ik = ik + 1
149                        IF( ik >= ikbot ) GO TO 200
150                        zwx(ji,ik) = zrhop(ji,jj,ik) - zrhop(ji,jj,ik+1)
151                        IF( zwx(ji,ik) <= 0.e0 ) GO TO 220
152                        ikup = ik
153                        ! the density profil is instable below ikup
154                        ! ikdown : bottom of the instable portion of the density profil
155                        ! search of ikdown and vertical mixing from ikup to ikdown
156                        !
157                        ze3tot= fse3t(ji,jj,ikup)
158                        zta   = tsa  (ji,jj,ikup,jp_tem)
159                        zsa   = tsa  (ji,jj,ikup,jp_sal)
160                        zraua = zrhop(ji,jj,ikup)
161                        !
162                        DO jkdown = ikup+1, ikbot-1
163                           IF( zraua <= zrhop(ji,jj,jkdown) ) THEN
164                              ikdown = jkdown
165                              GO TO 240
166                           ENDIF
167                           ze3dwn =  fse3t(ji,jj,jkdown)
168                           ze3tot =  ze3tot + ze3dwn
169                           zta   = ( zta*(ze3tot-ze3dwn) + tsa(ji,jj,jkdown,jp_tem)*ze3dwn )/ze3tot
170                           zsa   = ( zsa*(ze3tot-ze3dwn) + tsa(ji,jj,jkdown,jp_sal)*ze3dwn )/ze3tot
171                           zraua = ( zraua*(ze3tot-ze3dwn) + zrhop(ji,jj,jkdown)*ze3dwn )/ze3tot
172                           inpci = inpci+1
173                        END DO
174                        ikdown = ikbot-1
175240                     CONTINUE
176                        !
177                        DO jkp = ikup, ikdown-1
178                           tsa  (ji,jj,jkp,jp_tem) = zta
179                           tsa  (ji,jj,jkp,jp_sal) = zsa
180                           zrhop(ji,jj,jkp       ) = zraua
181                        END DO
182                        IF (ikdown == ikbot-1 .AND. zraua >= zrhop(ji,jj,ikdown) ) THEN
183                           tsa  (ji,jj,jkp,jp_tem) = zta
184                           tsa  (ji,jj,jkp,jp_sal) = zsa
185                           zrhop(ji,jj,ikdown    ) = zraua
186                        ENDIF
187                     END DO
188                  ENDIF
189200               CONTINUE
190               END DO
191               ! <<-- no more static instability on slab jj
192            ENDIF
193            !                                             ! ===============
194         END DO                                           !   End of slab
195         !                                                ! ===============
196         !
197         IF( l_trdtra )   THEN         ! save the Non penetrative mixing trends for diagnostic
198            ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
199            ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
200            CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_npc, ztrdt )
201            CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_npc, ztrds )
202         ENDIF
203     
204         ! Lateral boundary conditions on ( ta, sa )   ( Unchanged sign)
205         ! ------------------------------============
206         CALL lbc_lnk( tsa(:,:,:,jp_tem), 'T', 1. )   ;   CALL lbc_lnk( tsa(:,:,:,jp_sal), 'T', 1. )
207     
208
209         !  2. non penetrative convective scheme statistics
210         !  -----------------------------------------------
211         IF( nn_npcp /= 0 .AND. MOD( kt, nn_npcp ) == 0 ) THEN
212            IF(lwp) WRITE(numout,*)' kt=',kt, ' number of statically instable',   &
213               &                   ' water column : ',inpcc, ' number of iteration : ',inpci
214         ENDIF
215         !
216      ENDIF
217      !
218      IF( wrk_not_released(3, 1,2,3) .OR.   &
219          wrk_not_released_xz(1,2,3) )   CALL ctl_stop('tra_npc: failed to release workspace arrays')
220      !
221   END SUBROUTINE tra_npc
222
223   !!======================================================================
224END MODULE tranpc
Note: See TracBrowser for help on using the repository browser.