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.
Changeset 2528 for trunk/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    • Property svn:eol-style deleted
    • Property svn:executable deleted
    r1566 r2528  
    1515   USE dom_oce        ! ocean space and time domain variables 
    1616   USE obc_oce        ! ocean open boundary conditions 
     17   USE sbc_oce        ! surface boundary condition: ocean 
     18   USE sbcapr         ! surface boundary condition: atmospheric pressure 
    1719   USE dynspg_oce     ! surface pressure gradient variables 
    1820   USE dynspg_exp     ! surface pressure gradient     (dyn_spg_exp routine) 
    1921   USE dynspg_ts      ! surface pressure gradient     (dyn_spg_ts  routine) 
    2022   USE dynspg_flt     ! surface pressure gradient     (dyn_spg_flt routine) 
     23   USE dynadv         ! dynamics: vector invariant versus flux form 
    2124   USE trdmod         ! ocean dynamics trends 
    2225   USE trdmod_oce     ! ocean variables trends 
    2326   USE prtctl         ! Print control                     (prt_ctl routine) 
    2427   USE in_out_manager ! I/O manager 
     28   USE phycst         ! physical constants 
    2529 
    2630   IMPLICIT NONE 
    2731   PRIVATE 
    2832 
    29    PUBLIC   dyn_spg   ! routine called by step module 
     33   PUBLIC   dyn_spg        ! routine called by step module 
     34   PUBLIC   dyn_spg_init   ! routine called by opa module 
    3035 
    3136   INTEGER ::   nspg = 0   ! type of surface pressure gradient scheme defined from lk_dynspg_...  
     
    3742   !! NEMO/OPA 3.2 , LODYC-IPSL  (2009) 
    3843   !! $Id$  
    39    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)  
     44   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4045   !!---------------------------------------------------------------------- 
    4146 
     
    4752      !! 
    4853      !! ** Purpose :   achieve the momentum time stepping by computing the 
    49       !!              last trend, the surface pressure gradient, and performing 
     54      !!              last trend, the surface pressure gradient including the  
     55      !!              atmospheric pressure forcing (ln_apr_dyn=T), and performing 
    5056      !!              the Leap-Frog integration. 
    5157      !!gm              In the current version only the filtered solution provide 
     
    5763      !!              - split-explicit computation: a time splitting technique is used 
    5864      !! 
     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      !! 
    5972      !! N.B. : When key_esopa is used all the scheme are tested, regardless  
    6073      !!        of the physical meaning of the results.  
     
    6376      INTEGER, INTENT(  out) ::   kindic   ! solver flag 
    6477      !! 
    65       REAL(wp) ::   z2dt   ! temporary scalar 
     78      INTEGER  ::   ji, jj, jk                             ! dummy loop indices 
     79      REAL(wp) ::   z2dt, zg_2                             ! temporary scalar 
    6680      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrdu, ztrdv   ! 3D workspace 
    6781      !!---------------------------------------------------------------------- 
     
    7488 
    7589 
    76       IF( kt == nit000 )   CALL dyn_spg_ctl      ! initialisation & control of options 
    77  
    7890      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends 
    7991         ztrdu(:,:,:) = ua(:,:,:) 
    8092         ztrdv(:,:,:) = va(:,:,:) 
    8193      ENDIF 
     94 
     95      IF( ln_apr_dyn ) THEN                   !==  Atmospheric pressure gradient  ==! 
     96         zg_2 = grav * 0.5 
     97         DO jj = 2, jpjm1                          ! gradient of Patm using inverse barometer ssh 
     98            DO ji = fs_2, fs_jpim1   ! vector opt. 
     99               spgu(ji,jj) =  zg_2 * (  ssh_ib (ji+1,jj) - ssh_ib (ji,jj)    & 
     100                  &                   + ssh_ibb(ji+1,jj) - ssh_ibb(ji,jj)  ) /e1u(ji,jj) 
     101               spgv(ji,jj) =  zg_2 * (  ssh_ib (ji,jj+1) - ssh_ib (ji,jj)    & 
     102                  &                   + ssh_ibb(ji,jj+1) - ssh_ib (ji,jj)  ) /e2v(ji,jj) 
     103            END DO 
     104         END DO 
     105         DO jk = 1, jpkm1                          ! Add the apg to the general trend 
     106            DO jj = 2, jpjm1 
     107               DO ji = fs_2, fs_jpim1   ! vector opt. 
     108                  ua(ji,jj,jk) = ua(ji,jj,jk) + spgu(ji,jj) 
     109                  va(ji,jj,jk) = va(ji,jj,jk) + spgv(ji,jj) 
     110               END DO 
     111            END DO 
     112         END DO 
     113      ENDIF 
     114 
    82115 
    83116      SELECT CASE ( nspg )                       ! compute surf. pressure gradient trend and add it to the general trend 
     
    119152 
    120153 
    121    SUBROUTINE dyn_spg_ctl 
     154   SUBROUTINE dyn_spg_init 
    122155      !!--------------------------------------------------------------------- 
    123       !!                  ***  ROUTINE dyn_spg_ctl  *** 
     156      !!                  ***  ROUTINE dyn_spg_init  *** 
    124157      !!                 
    125158      !! ** Purpose :   Control the consistency between cpp options for  
     
    131164      IF(lwp) THEN             ! Control print 
    132165         WRITE(numout,*) 
    133          WRITE(numout,*) 'dyn_spg_ctl : choice of the surface pressure gradient scheme' 
     166         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme' 
    134167         WRITE(numout,*) '~~~~~~~~~~~' 
    135168         WRITE(numout,*) '     Explicit free surface                  lk_dynspg_exp = ', lk_dynspg_exp 
     
    164197      !                        ! Control of timestep choice 
    165198      IF( lk_dynspg_ts .OR. lk_dynspg_exp ) THEN 
    166          IF( n_cla == 1 )   & 
    167            &   CALL ctl_stop( ' Crossland advection not implemented for this free surface formulation ' ) 
     199         IF( nn_cla == 1 )   CALL ctl_stop( 'Crossland advection not implemented for this free surface formulation' ) 
     200      ENDIF 
     201 
     202      !                        ! Control of momentum formulation 
     203      IF( lk_dynspg_ts .AND. lk_vvl ) THEN 
     204         IF( .NOT.ln_dynadv_vec )   CALL ctl_stop( 'Flux form not implemented for this free surface formulation' ) 
    168205      ENDIF 
    169206 
     
    178215#endif 
    179216      ! 
    180    END SUBROUTINE dyn_spg_ctl 
     217   END SUBROUTINE dyn_spg_init 
    181218 
    182219  !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.