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.
dynspg.F90 in branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90 @ 11101

Last change on this file since 11101 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 14.3 KB
Line 
1MODULE dynspg
2   !!======================================================================
3   !!                       ***  MODULE  dynspg  ***
4   !! Ocean dynamics:  surface pressure gradient control
5   !!======================================================================
6   !! History :  1.0  ! 2005-12  (C. Talandier, G. Madec, V. Garnier)  Original code
7   !!            3.2  ! 2009-07  (R. Benshila)  Suppression of rigid-lid option
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   dyn_spg     : update the dynamics trend with the lateral diffusion
12   !!   dyn_spg_ctl : initialization, namelist read, and parameters control
13   !!----------------------------------------------------------------------
14   USE oce            ! ocean dynamics and tracers variables
15   USE dom_oce        ! ocean space and time domain variables
16   USE c1d            ! 1D vertical configuration
17   USE phycst         ! physical constants
18   USE sbc_oce        ! surface boundary condition: ocean
19   USE sbcapr         ! surface boundary condition: atmospheric pressure
20   USE dynspg_oce     ! surface pressure gradient variables
21   USE dynspg_exp     ! surface pressure gradient     (dyn_spg_exp routine)
22   USE dynspg_ts      ! surface pressure gradient     (dyn_spg_ts  routine)
23   USE dynspg_flt     ! surface pressure gradient     (dyn_spg_flt routine)
24   USE dynadv         ! dynamics: vector invariant versus flux form
25   USE dynhpg, ONLY: ln_dynhpg_imp
26   USE sbctide
27   USE updtide
28   USE trd_oce        ! trends: ocean variables
29   USE trddyn         ! trend manager: dynamics
30   !
31   USE prtctl         ! Print control                     (prt_ctl routine)
32   USE in_out_manager ! I/O manager
33   USE lib_mpp        ! MPP library
34   USE solver         ! solver initialization
35   USE wrk_nemo       ! Memory Allocation
36   USE timing         ! Timing
37
38
39   IMPLICIT NONE
40   PRIVATE
41
42   PUBLIC   dyn_spg        ! routine called by step module
43   PUBLIC   dyn_spg_init   ! routine called by opa module
44
45   INTEGER ::   nspg = 0   ! type of surface pressure gradient scheme defined from lk_dynspg_...
46
47   !! * Substitutions
48#  include "domzgr_substitute.h90"
49#  include "vectopt_loop_substitute.h90"
50   !!----------------------------------------------------------------------
51   !! NEMO/OPA 3.2 , LODYC-IPSL  (2009)
52   !! $Id$
53   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
54   !!----------------------------------------------------------------------
55CONTAINS
56
57   SUBROUTINE dyn_spg( kt, kindic )
58      !!----------------------------------------------------------------------
59      !!                  ***  ROUTINE dyn_spg  ***
60      !!
61      !! ** Purpose :   achieve the momentum time stepping by computing the
62      !!              last trend, the surface pressure gradient including the
63      !!              atmospheric pressure forcing (ln_apr_dyn=T), and performing
64      !!              the Leap-Frog integration.
65      !!gm              In the current version only the filtered solution provide
66      !!gm            the after velocity, in the 2 other (ua,va) are still the trends
67      !!
68      !! ** Method  :   Three schemes:
69      !!              - explicit computation      : the spg is evaluated at now
70      !!              - filtered computation      : the Roulet & madec (2000) technique is used
71      !!              - split-explicit computation: a time splitting technique is used
72      !!
73      !!              ln_apr_dyn=T : the atmospheric pressure forcing is applied
74      !!             as the gradient of the inverse barometer ssh:
75      !!                apgu = - 1/rau0 di[apr] = 0.5*grav di[ssh_ib+ssh_ibb]
76      !!                apgv = - 1/rau0 dj[apr] = 0.5*grav dj[ssh_ib+ssh_ibb]
77      !!             Note that as all external forcing a time averaging over a two rdt
78      !!             period is used to prevent the divergence of odd and even time step.
79      !!
80      !! N.B. : When key_esopa is used all the scheme are tested, regardless
81      !!        of the physical meaning of the results.
82      !!----------------------------------------------------------------------
83      !
84      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index
85      INTEGER, INTENT(  out) ::   kindic   ! solver flag
86      !
87      INTEGER  ::   ji, jj, jk                             ! dummy loop indices
88      REAL(wp) ::   z2dt, zg_2, zintp, zgrau0r             ! temporary scalar
89      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdu, ztrdv
90      REAL(wp), POINTER, DIMENSION(:,:)   ::  zpice
91      !!----------------------------------------------------------------------
92      !
93      IF( nn_timing == 1 )  CALL timing_start('dyn_spg')
94      !
95
96!!gm NOTA BENE : the dynspg_exp and dynspg_ts should be modified so that
97!!gm             they return the after velocity, not the trends (as in trazdf_imp...)
98!!gm             In this case, change/simplify dynnxt
99
100
101      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends
102         CALL wrk_alloc( jpi, jpj, jpk, ztrdu, ztrdv ) 
103         ztrdu(:,:,:) = ua(:,:,:)
104         ztrdv(:,:,:) = va(:,:,:)
105      ENDIF
106
107      IF(      ln_apr_dyn                                                &   ! atmos. pressure
108         .OR.  ( .NOT.lk_dynspg_ts .AND. (ln_tide_pot .AND. lk_tide) )   &   ! tide potential (no time slitting)
109         .OR.  nn_ice_embd == 2  ) THEN                                      ! embedded sea-ice
110         !
111         DO jj = 2, jpjm1
112            DO ji = fs_2, fs_jpim1   ! vector opt.
113               spgu(ji,jj) = 0._wp
114               spgv(ji,jj) = 0._wp
115            END DO
116         END DO         
117         !
118         IF( ln_apr_dyn .AND. (.NOT. lk_dynspg_ts) ) THEN                    !==  Atmospheric pressure gradient (added later in time-split case) ==!
119            zg_2 = grav * 0.5
120            DO jj = 2, jpjm1                          ! gradient of Patm using inverse barometer ssh
121               DO ji = fs_2, fs_jpim1   ! vector opt.
122                  spgu(ji,jj) = spgu(ji,jj) + zg_2 * (  ssh_ib (ji+1,jj) - ssh_ib (ji,jj)    &
123                     &                      + ssh_ibb(ji+1,jj) - ssh_ibb(ji,jj)  ) /e1u(ji,jj)
124                  spgv(ji,jj) = spgv(ji,jj) + zg_2 * (  ssh_ib (ji,jj+1) - ssh_ib (ji,jj)    &
125                     &                      + ssh_ibb(ji,jj+1) - ssh_ibb(ji,jj)  ) /e2v(ji,jj)
126               END DO
127            END DO
128         ENDIF
129         !
130         !                                    !==  tide potential forcing term  ==!
131         IF( .NOT.lk_dynspg_ts .AND. ( ln_tide_pot .AND. lk_tide )  ) THEN   ! N.B. added directly at sub-time-step in ts-case
132            !
133            CALL upd_tide( kt )                      ! update tide potential
134            !
135            DO jj = 2, jpjm1                         ! add tide potential forcing
136               DO ji = fs_2, fs_jpim1   ! vector opt.
137                  spgu(ji,jj) = spgu(ji,jj) + grav * ( pot_astro(ji+1,jj) - pot_astro(ji,jj) ) / e1u(ji,jj)
138                  spgv(ji,jj) = spgv(ji,jj) + grav * ( pot_astro(ji,jj+1) - pot_astro(ji,jj) ) / e2v(ji,jj)
139               END DO
140            END DO
141         ENDIF
142         !
143         IF( nn_ice_embd == 2 ) THEN          !== embedded sea ice: Pressure gradient due to snow-ice mass ==!
144            CALL wrk_alloc( jpi, jpj, zpice )
145            !                                           
146            zintp = REAL( MOD( kt-1, nn_fsbc ) ) / REAL( nn_fsbc )
147            zgrau0r     = - grav * r1_rau0
148            zpice(:,:) = (  zintp * snwice_mass(:,:) + ( 1.- zintp ) * snwice_mass_b(:,:)  ) * zgrau0r
149            DO jj = 2, jpjm1
150               DO ji = fs_2, fs_jpim1   ! vector opt.
151                  spgu(ji,jj) = spgu(ji,jj) + ( zpice(ji+1,jj) - zpice(ji,jj) ) / e1u(ji,jj)
152                  spgv(ji,jj) = spgv(ji,jj) + ( zpice(ji,jj+1) - zpice(ji,jj) ) / e2v(ji,jj)
153               END DO
154            END DO
155            !
156            CALL wrk_dealloc( jpi, jpj, zpice )         
157         ENDIF
158         !
159         DO jk = 1, jpkm1                     !== Add all terms to the general trend
160            DO jj = 2, jpjm1
161               DO ji = fs_2, fs_jpim1   ! vector opt.
162                  ua(ji,jj,jk) = ua(ji,jj,jk) + spgu(ji,jj)
163                  va(ji,jj,jk) = va(ji,jj,jk) + spgv(ji,jj)
164               END DO
165            END DO
166         END DO   
167         
168!!gm add here a call to dyn_trd for ice pressure gradient, the surf pressure trends ????
169             
170      ENDIF
171
172      SELECT CASE ( nspg )                       ! compute surf. pressure gradient trend and add it to the general trend
173      !                                                     
174      CASE (  0 )   ;   CALL dyn_spg_exp( kt )              ! explicit
175      CASE (  1 )   ;   CALL dyn_spg_ts ( kt )              ! time-splitting
176      CASE (  2 )   ;   CALL dyn_spg_flt( kt, kindic )      ! filtered
177      !                                                   
178      CASE ( -1 )                                ! esopa: test all possibility with control print
179                        CALL dyn_spg_exp( kt )
180                        CALL prt_ctl( tab3d_1=ua, clinfo1=' spg0 - Ua: ', mask1=umask, &
181         &                            tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
182                        CALL dyn_spg_ts ( kt )
183                        CALL prt_ctl( tab3d_1=ua, clinfo1=' spg1 - Ua: ', mask1=umask, &
184         &                           tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
185                        CALL dyn_spg_flt( kt, kindic )
186                        CALL prt_ctl( tab3d_1=ua, clinfo1=' spg2 - Ua: ', mask1=umask, &
187         &                            tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
188      END SELECT
189      !                   
190      IF( l_trddyn )   THEN                      ! save the surface pressure gradient trends for further diagnostics
191         SELECT CASE ( nspg )
192         CASE ( 0, 1 )
193            ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:)
194            ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:)
195         CASE( 2 )
196            z2dt = 2. * rdt
197            IF( neuler == 0 .AND. kt == nit000 )   z2dt = rdt
198            ztrdu(:,:,:) = ( ua(:,:,:) - ub(:,:,:) ) / z2dt - ztrdu(:,:,:)
199            ztrdv(:,:,:) = ( va(:,:,:) - vb(:,:,:) ) / z2dt - ztrdv(:,:,:)
200         END SELECT
201         CALL trd_dyn( ztrdu, ztrdv, jpdyn_spg, kt )
202         !
203         CALL wrk_dealloc( jpi, jpj, jpk, ztrdu, ztrdv ) 
204      ENDIF
205      !                                          ! print mean trends (used for debugging)
206      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' spg  - Ua: ', mask1=umask, &
207         &                       tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
208      !
209      IF( nn_timing == 1 )  CALL timing_stop('dyn_spg')
210      !
211   END SUBROUTINE dyn_spg
212
213
214   SUBROUTINE dyn_spg_init
215      !!---------------------------------------------------------------------
216      !!                  ***  ROUTINE dyn_spg_init  ***
217      !!               
218      !! ** Purpose :   Control the consistency between cpp options for
219      !!              surface pressure gradient schemes
220      !!----------------------------------------------------------------------
221      INTEGER ::   ioptio
222      !!----------------------------------------------------------------------
223      !
224      IF( nn_timing == 1 )  CALL timing_start('dyn_spg_init')
225      !
226      IF(lwp) THEN             ! Control print
227         WRITE(numout,*)
228         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme'
229         WRITE(numout,*) '~~~~~~~~~~~'
230         WRITE(numout,*) '     Explicit free surface                  lk_dynspg_exp = ', lk_dynspg_exp
231         WRITE(numout,*) '     Free surface with time splitting       lk_dynspg_ts  = ', lk_dynspg_ts
232         WRITE(numout,*) '     Filtered free surface cst volume       lk_dynspg_flt = ', lk_dynspg_flt
233         IF(lflush) CALL flush(numout)
234      ENDIF
235
236      IF( lk_dynspg_ts ) CALL dyn_spg_ts_init( nit000 )
237      ! (do it now, to set nn_baro, used to allocate some arrays later on)
238      !                        ! allocate dyn_spg arrays
239      IF( lk_dynspg_ts ) THEN
240         IF( dynspg_oce_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_oce arrays')
241         IF( dyn_spg_ts_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_ts  arrays')
242         IF ((neuler/=0).AND.(ln_bt_fw)) CALL ts_rst( nit000, 'READ' )
243      ENDIF
244
245      !                        ! Control of surface pressure gradient scheme options
246      ioptio = 0
247      IF(lk_dynspg_exp)   ioptio = ioptio + 1
248      IF(lk_dynspg_ts )   ioptio = ioptio + 1
249      IF(lk_dynspg_flt)   ioptio = ioptio + 1
250      !
251      IF( ( ioptio > 1 .AND. .NOT. lk_esopa ) .OR. ( ioptio == 0 .AND. .NOT. lk_c1d ) )   &
252           &   CALL ctl_stop( ' Choose only one surface pressure gradient scheme with a key cpp' )
253      IF( ( lk_dynspg_ts .OR. lk_dynspg_exp ) .AND. ln_isfcav )   &
254           &   CALL ctl_stop( ' dynspg_ts and dynspg_exp not tested with ice shelf cavity ' )
255      !
256      IF( lk_esopa     )   nspg = -1
257      IF( lk_dynspg_exp)   nspg =  0
258      IF( lk_dynspg_ts )   nspg =  1
259      IF( lk_dynspg_flt)   nspg =  2
260      !
261      IF( lk_esopa     )   nspg = -1
262      !
263      IF(lwp) THEN
264         WRITE(numout,*)
265         IF( nspg == -1 )   WRITE(numout,*) '     ESOPA test All scheme used'
266         IF( nspg ==  0 )   WRITE(numout,*) '     explicit free surface'
267         IF( nspg ==  1 )   WRITE(numout,*) '     free surface with time splitting scheme'
268         IF( nspg ==  2 )   WRITE(numout,*) '     filtered free surface'
269         IF(lflush) CALL flush(numout)
270      ENDIF
271
272#if defined key_dynspg_flt || defined key_esopa
273      CALL solver_init( nit000 )   ! Elliptic solver initialisation
274#endif
275
276      !                        ! Control of timestep choice
277      IF( lk_dynspg_ts .OR. lk_dynspg_exp ) THEN
278         IF( nn_cla == 1 )   CALL ctl_stop( 'Crossland advection not implemented for this free surface formulation' )
279      ENDIF
280
281      !               ! Control of hydrostatic pressure choice
282      IF( lk_dynspg_ts .AND. ln_dynhpg_imp ) THEN
283         CALL ctl_stop( 'Semi-implicit hpg not compatible with time splitting' )
284      ENDIF
285      !
286      IF( nn_timing == 1 )  CALL timing_stop('dyn_spg_init')
287      !
288   END SUBROUTINE dyn_spg_init
289
290  !!======================================================================
291END MODULE dynspg
Note: See TracBrowser for help on using the repository browser.