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

source: branches/2011/UKMO_MERCATOR_obc_bdy_merge/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90 @ 2797

Last change on this file since 2797 was 2797, checked in by davestorkey, 13 years ago

Delete BDY module and first implementation of new OBC module.

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