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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DYN – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90 @ 3211

Last change on this file since 3211 was 3211, checked in by spickles2, 13 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 12.2 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 phycst         ! physical constants
17   USE obc_oce        ! ocean open boundary conditions
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 trdmod         ! ocean dynamics trends
26   USE trdmod_oce     ! ocean variables trends
27   USE prtctl         ! Print control                     (prt_ctl routine)
28   USE in_out_manager ! I/O manager
29   USE lib_mpp        ! MPP library
30   USE solver          ! solver initialization
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   dyn_spg        ! routine called by step module
36   PUBLIC   dyn_spg_init   ! routine called by opa module
37
38   INTEGER ::   nspg = 0   ! type of surface pressure gradient scheme defined from lk_dynspg_...
39
40   !! * Control permutation of array indices
41#  include "oce_ftrans.h90"
42#  include "dom_oce_ftrans.h90"
43#  include "obc_oce_ftrans.h90"
44#  include "sbc_oce_ftrans.h90"
45
46   !! * Substitutions
47#  include "domzgr_substitute.h90"
48#  include "vectopt_loop_substitute.h90"
49   !!----------------------------------------------------------------------
50   !! NEMO/OPA 3.2 , LODYC-IPSL  (2009)
51   !! $Id$
52   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
53   !!----------------------------------------------------------------------
54CONTAINS
55
56   SUBROUTINE dyn_spg( kt, kindic )
57      !!----------------------------------------------------------------------
58      !!                  ***  ROUTINE dyn_spg  ***
59      !!
60      !! ** Purpose :   achieve the momentum time stepping by computing the
61      !!              last trend, the surface pressure gradient including the
62      !!              atmospheric pressure forcing (ln_apr_dyn=T), and performing
63      !!              the Leap-Frog integration.
64      !!gm              In the current version only the filtered solution provide
65      !!gm            the after velocity, in the 2 other (ua,va) are still the trends
66      !!
67      !! ** Method  :   Three schemes:
68      !!              - explicit computation      : the spg is evaluated at now
69      !!              - filtered computation      : the Roulet & madec (2000) technique is used
70      !!              - split-explicit computation: a time splitting technique is used
71      !!
72      !!              ln_apr_dyn=T : the atmospheric pressure forcing is applied
73      !!             as the gradient of the inverse barometer ssh:
74      !!                apgu = - 1/rau0 di[apr] = 0.5*grav di[ssh_ib+ssh_ibb]
75      !!                apgv = - 1/rau0 dj[apr] = 0.5*grav dj[ssh_ib+ssh_ibb]
76      !!             Note that as all external forcing a time averaging over a two rdt
77      !!             period is used to prevent the divergence of odd and even time step.
78      !!
79      !! N.B. : When key_esopa is used all the scheme are tested, regardless
80      !!        of the physical meaning of the results.
81      !!----------------------------------------------------------------------
82      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released
83      USE wrk_nemo, ONLY:   ztrdu => wrk_3d_4 , ztrdv => wrk_3d_5    ! 3D workspace
84      !! DCSE_NEMO: need additional directives for renamed module variables
85!FTRANS ztrdu :I :I :z
86!FTRANS ztrdv :I :I :z
87
88      !
89      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index
90      INTEGER, INTENT(  out) ::   kindic   ! solver flag
91      !
92      INTEGER  ::   ji, jj, jk                             ! dummy loop indices
93      REAL(wp) ::   z2dt, zg_2                             ! temporary scalar
94      !!----------------------------------------------------------------------
95
96      IF( wrk_in_use(3, 4,5) ) THEN
97         CALL ctl_stop('dyn_spg: requested workspace arrays unavailable')   ;   RETURN
98      ENDIF
99
100!!gm NOTA BENE : the dynspg_exp and dynspg_ts should be modified so that
101!!gm             they return the after velocity, not the trends (as in trazdf_imp...)
102!!gm             In this case, change/simplify dynnxt
103
104
105      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends
106         ztrdu(:,:,:) = ua(:,:,:)
107         ztrdv(:,:,:) = va(:,:,:)
108      ENDIF
109
110      IF( ln_apr_dyn ) THEN                   !==  Atmospheric pressure gradient  ==!
111         zg_2 = grav * 0.5
112         DO jj = 2, jpjm1                          ! gradient of Patm using inverse barometer ssh
113            DO ji = fs_2, fs_jpim1   ! vector opt.
114               spgu(ji,jj) =  zg_2 * (  ssh_ib (ji+1,jj) - ssh_ib (ji,jj)    &
115                  &                   + ssh_ibb(ji+1,jj) - ssh_ibb(ji,jj)  ) /e1u(ji,jj)
116               spgv(ji,jj) =  zg_2 * (  ssh_ib (ji,jj+1) - ssh_ib (ji,jj)    &
117                  &                   + ssh_ibb(ji,jj+1) - ssh_ib (ji,jj)  ) /e2v(ji,jj)
118            END DO
119         END DO
120#if defined key_z_first
121         DO jj = 2, jpjm1                          ! Add the apg to the general trend
122            DO ji = 2, jpim1
123               DO jk = 1, jpkm1
124#else
125         DO jk = 1, jpkm1                          ! Add the apg to the general trend
126            DO jj = 2, jpjm1
127               DO ji = fs_2, fs_jpim1   ! vector opt.
128#endif
129                  ua(ji,jj,jk) = ua(ji,jj,jk) + spgu(ji,jj)
130                  va(ji,jj,jk) = va(ji,jj,jk) + spgv(ji,jj)
131               END DO
132            END DO
133         END DO
134      ENDIF
135
136
137      SELECT CASE ( nspg )                       ! compute surf. pressure gradient trend and add it to the general trend
138      !                                                     
139      CASE (  0 )   ;   CALL dyn_spg_exp( kt )              ! explicit
140      CASE (  1 )   ;   CALL dyn_spg_ts ( kt )              ! time-splitting
141      CASE (  2 )   ;   CALL dyn_spg_flt( kt, kindic )      ! filtered
142      !                                                   
143      CASE ( -1 )                                ! esopa: test all possibility with control print
144                        CALL dyn_spg_exp( kt )
145                        CALL prt_ctl( tab3d_1=ua, clinfo1=' spg0 - Ua: ', mask1=umask, &
146         &                            tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
147                        CALL dyn_spg_ts ( kt )
148                        CALL prt_ctl( tab3d_1=ua, clinfo1=' spg1 - Ua: ', mask1=umask, &
149         &                           tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
150                        CALL dyn_spg_flt( kt, kindic )
151                        CALL prt_ctl( tab3d_1=ua, clinfo1=' spg2 - Ua: ', mask1=umask, &
152         &                            tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
153      END SELECT
154      !                   
155      IF( l_trddyn )   THEN                      ! save the surface pressure gradient trends for further diagnostics
156         SELECT CASE ( nspg )
157         CASE ( 0, 1 )
158            ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:)
159            ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:)
160         CASE( 2 )
161            z2dt = 2. * rdt
162            IF( neuler == 0 .AND. kt == nit000 ) z2dt = rdt
163            ztrdu(:,:,:) = ( ua(:,:,:) - ub(:,:,:) ) / z2dt - ztrdu(:,:,:)
164            ztrdv(:,:,:) = ( va(:,:,:) - vb(:,:,:) ) / z2dt - ztrdv(:,:,:)
165         END SELECT
166         CALL trd_mod( ztrdu, ztrdv, jpdyn_trd_spg, 'DYN', kt )
167      ENDIF
168      !                                          ! print mean trends (used for debugging)
169      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' spg  - Ua: ', mask1=umask, &
170         &                       tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
171      !
172      IF( wrk_not_released(3, 4,5) )   CALL ctl_stop('dyn_spg: failed to release workspace arrays')
173      !
174   END SUBROUTINE dyn_spg
175
176
177   SUBROUTINE dyn_spg_init
178      !!---------------------------------------------------------------------
179      !!                  ***  ROUTINE dyn_spg_init  ***
180      !!               
181      !! ** Purpose :   Control the consistency between cpp options for
182      !!              surface pressure gradient schemes
183      !!----------------------------------------------------------------------
184      INTEGER ::   ioptio
185      !!----------------------------------------------------------------------
186
187      IF(lwp) THEN             ! Control print
188         WRITE(numout,*)
189         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme'
190         WRITE(numout,*) '~~~~~~~~~~~'
191         WRITE(numout,*) '     Explicit free surface                  lk_dynspg_exp = ', lk_dynspg_exp
192         WRITE(numout,*) '     Free surface with time splitting       lk_dynspg_ts  = ', lk_dynspg_ts
193         WRITE(numout,*) '     Filtered free surface cst volume       lk_dynspg_flt = ', lk_dynspg_flt
194      ENDIF
195
196      !                        ! allocate dyn_spg arrays
197      IF( lk_dynspg_ts ) THEN
198         IF( dynspg_oce_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_oce arrays')
199         IF( dyn_spg_ts_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_ts  arrays')
200      ENDIF
201
202      !                        ! Control of surface pressure gradient scheme options
203      ioptio = 0
204      IF(lk_dynspg_exp)   ioptio = ioptio + 1
205      IF(lk_dynspg_ts )   ioptio = ioptio + 1
206      IF(lk_dynspg_flt)   ioptio = ioptio + 1
207      !
208      IF( ( ioptio > 1 .AND. .NOT. lk_esopa ) .OR. ioptio == 0 )   &
209           &   CALL ctl_stop( ' Choose only one surface pressure gradient scheme with a key cpp' )
210      !
211      IF( lk_esopa     )   nspg = -1
212      IF( lk_dynspg_exp)   nspg =  0
213      IF( lk_dynspg_ts )   nspg =  1
214      IF( lk_dynspg_flt)   nspg =  2
215      !
216      IF( lk_esopa     )   nspg = -1
217      !
218      IF(lwp) THEN
219         WRITE(numout,*)
220         IF( nspg == -1 )   WRITE(numout,*) '     ESOPA test All scheme used'
221         IF( nspg ==  0 )   WRITE(numout,*) '     explicit free surface'
222         IF( nspg ==  1 )   WRITE(numout,*) '     free surface with time splitting scheme'
223         IF( nspg ==  2 )   WRITE(numout,*) '     filtered free surface'
224      ENDIF
225
226#if defined key_dynspg_flt || defined key_esopa
227      CALL solver_init( nit000 )   ! Elliptic solver initialisation
228#endif
229
230      !                        ! Control of timestep choice
231      IF( lk_dynspg_ts .OR. lk_dynspg_exp ) THEN
232         IF( nn_cla == 1 )   CALL ctl_stop( 'Crossland advection not implemented for this free surface formulation' )
233      ENDIF
234
235      !                        ! Control of momentum formulation
236      IF( lk_dynspg_ts .AND. lk_vvl ) THEN
237         IF( .NOT.ln_dynadv_vec )   CALL ctl_stop( 'Flux form not implemented for this free surface formulation' )
238      ENDIF
239
240#if defined key_obc
241      !                        ! Conservation of ocean volume (key_dynspg_flt)
242      IF( lk_dynspg_flt )   ln_vol_cst = .true.
243
244      !                        ! Application of Flather's algorithm at open boundaries
245      IF( lk_dynspg_flt )   ln_obc_fla = .false.
246      IF( lk_dynspg_exp )   ln_obc_fla = .true.
247      IF( lk_dynspg_ts  )   ln_obc_fla = .true.
248#endif
249      !
250   END SUBROUTINE dyn_spg_init
251
252  !!======================================================================
253END MODULE dynspg
Note: See TracBrowser for help on using the repository browser.