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 6808 for branches/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90 – NEMO

Ignore:
Timestamp:
2016-07-19T10:38:35+02:00 (8 years ago)
Author:
jamesharle
Message:

merge with trunk@6232 for consistency with SSB code

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r5120 r6808  
    99 
    1010   !!---------------------------------------------------------------------- 
    11    !!   dyn_spg     : update the dynamics trend with the lateral diffusion 
    12    !!   dyn_spg_ctl : initialization, namelist read, and parameters control 
     11   !!   dyn_spg     : update the dynamics trend with surface pressure gradient  
     12   !!   dyn_spg_init: initialization, namelist read, and parameters control 
    1313   !!---------------------------------------------------------------------- 
    1414   USE oce            ! ocean dynamics and tracers variables 
     
    1818   USE sbc_oce        ! surface boundary condition: ocean 
    1919   USE sbcapr         ! surface boundary condition: atmospheric pressure 
    20    USE dynspg_oce     ! surface pressure gradient variables 
    2120   USE dynspg_exp     ! surface pressure gradient     (dyn_spg_exp routine) 
    2221   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 
     22   USE sbctide        !  
     23   USE updtide        !  
    2824   USE trd_oce        ! trends: ocean variables 
    2925   USE trddyn         ! trend manager: dynamics 
     
    3228   USE in_out_manager ! I/O manager 
    3329   USE lib_mpp        ! MPP library 
    34    USE solver         ! solver initialization 
    3530   USE wrk_nemo       ! Memory Allocation 
    3631   USE timing         ! Timing 
    3732 
    38  
    3933   IMPLICIT NONE 
    4034   PRIVATE 
     
    4539   INTEGER ::   nspg = 0   ! type of surface pressure gradient scheme defined from lk_dynspg_...  
    4640 
     41   !                       ! Parameter to control the surface pressure gradient scheme 
     42   INTEGER, PARAMETER ::   np_TS  = 1   ! split-explicit time stepping (Time-Splitting) 
     43   INTEGER, PARAMETER ::   np_EXP = 0   !       explicit time stepping 
     44   INTEGER, PARAMETER ::   np_NO  =-1   ! no surface pressure gradient, no scheme 
     45 
    4746   !! * Substitutions 
    48 #  include "domzgr_substitute.h90" 
    4947#  include "vectopt_loop_substitute.h90" 
    5048   !!---------------------------------------------------------------------- 
     
    5553CONTAINS 
    5654 
    57    SUBROUTINE dyn_spg( kt, kindic ) 
     55   SUBROUTINE dyn_spg( kt ) 
    5856      !!---------------------------------------------------------------------- 
    5957      !!                  ***  ROUTINE dyn_spg  *** 
    6058      !! 
    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 
     59      !! ** Purpose :   compute surface pressure gradient including the  
     60      !!              atmospheric pressure forcing (ln_apr_dyn=T). 
    6761      !! 
    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 
     62      !! ** Method  :   Two schemes: 
     63      !!              - explicit       : the spg is evaluated at now 
     64      !!              - split-explicit : a time splitting technique is used 
    7265      !! 
    7366      !!              ln_apr_dyn=T : the atmospheric pressure forcing is applied  
     
    7770      !!             Note that as all external forcing a time averaging over a two rdt 
    7871      !!             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       ! 
     72      !!---------------------------------------------------------------------- 
    8473      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index 
    85       INTEGER, INTENT(  out) ::   kindic   ! solver flag 
    8674      ! 
    8775      INTEGER  ::   ji, jj, jk                             ! dummy loop indices 
     
    9381      IF( nn_timing == 1 )  CALL timing_start('dyn_spg') 
    9482      ! 
    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  
    10183      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends 
    102          CALL wrk_alloc( jpi, jpj, jpk, ztrdu, ztrdv )  
     84         CALL wrk_alloc( jpi,jpj,jpk,  ztrdu, ztrdv )  
    10385         ztrdu(:,:,:) = ua(:,:,:) 
    10486         ztrdv(:,:,:) = va(:,:,:) 
    10587      ENDIF 
    106  
     88      ! 
    10789      IF(      ln_apr_dyn                                                &   ! atmos. pressure 
    108          .OR.  ( .NOT.lk_dynspg_ts .AND. (ln_tide_pot .AND. lk_tide) )   &   ! tide potential (no time slitting) 
     90         .OR.  ( .NOT.ln_dynspg_ts .AND. (ln_tide_pot .AND. lk_tide) )   &   ! tide potential (no time slitting) 
    10991         .OR.  nn_ice_embd == 2  ) THEN                                      ! embedded sea-ice 
    11092         ! 
     
    11698         END DO          
    11799         ! 
    118          IF( ln_apr_dyn .AND. (.NOT. lk_dynspg_ts) ) THEN                    !==  Atmospheric pressure gradient (added later in time-split case) ==! 
     100         IF( ln_apr_dyn .AND. .NOT.ln_dynspg_ts ) THEN   !==  Atmospheric pressure gradient (added later in time-split case) ==! 
    119101            zg_2 = grav * 0.5 
    120102            DO jj = 2, jpjm1                          ! gradient of Patm using inverse barometer ssh 
    121103               DO ji = fs_2, fs_jpim1   ! vector opt. 
    122104                  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) 
     105                     &                      + ssh_ibb(ji+1,jj) - ssh_ibb(ji,jj)  ) * r1_e1u(ji,jj) 
    124106                  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) 
     107                     &                      + ssh_ibb(ji,jj+1) - ssh_ibb(ji,jj)  ) * r1_e2v(ji,jj) 
    126108               END DO 
    127109            END DO 
     
    129111         ! 
    130112         !                                    !==  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 
     113         IF( .NOT.ln_dynspg_ts .AND. ( ln_tide_pot .AND. lk_tide )  ) THEN   ! N.B. added directly at sub-time-step in ts-case 
    132114            ! 
    133115            CALL upd_tide( kt )                      ! update tide potential 
     
    135117            DO jj = 2, jpjm1                         ! add tide potential forcing 
    136118               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) 
     119                  spgu(ji,jj) = spgu(ji,jj) + grav * ( pot_astro(ji+1,jj) - pot_astro(ji,jj) ) * r1_e1u(ji,jj) 
     120                  spgv(ji,jj) = spgv(ji,jj) + grav * ( pot_astro(ji,jj+1) - pot_astro(ji,jj) ) * r1_e2v(ji,jj) 
    139121               END DO  
    140122            END DO 
     
    142124         ! 
    143125         IF( nn_ice_embd == 2 ) THEN          !== embedded sea ice: Pressure gradient due to snow-ice mass ==! 
    144             CALL wrk_alloc( jpi, jpj, zpice ) 
     126            CALL wrk_alloc( jpi,jpj,  zpice ) 
    145127            !                                             
    146128            zintp = REAL( MOD( kt-1, nn_fsbc ) ) / REAL( nn_fsbc ) 
     
    149131            DO jj = 2, jpjm1 
    150132               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) 
     133                  spgu(ji,jj) = spgu(ji,jj) + ( zpice(ji+1,jj) - zpice(ji,jj) ) * r1_e1u(ji,jj) 
     134                  spgv(ji,jj) = spgv(ji,jj) + ( zpice(ji,jj+1) - zpice(ji,jj) ) * r1_e2v(ji,jj) 
    153135               END DO 
    154136            END DO 
    155137            ! 
    156             CALL wrk_dealloc( jpi, jpj, zpice )          
     138            CALL wrk_dealloc( jpi,jpj,  zpice )          
    157139         ENDIF 
    158140         ! 
    159          DO jk = 1, jpkm1                     !== Add all terms to the general trend 
     141         DO jk = 1, jpkm1                    !== Add all terms to the general trend 
    160142            DO jj = 2, jpjm1 
    161143               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    165147            END DO 
    166148         END DO     
    167           
     149         ! 
    168150!!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' ) 
     151         !     
     152      ENDIF 
     153      ! 
     154      SELECT CASE ( nspg )                   !== surface pressure gradient computed and add to the general trend ==! 
     155      CASE ( np_EXP )   ;   CALL dyn_spg_exp( kt )              ! explicit 
     156      CASE ( np_TS  )   ;   CALL dyn_spg_ts ( kt )              ! time-splitting 
    188157      END SELECT 
    189158      !                     
    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 
     159      IF( l_trddyn )   THEN                  ! save the surface pressure gradient trends for further diagnostics 
     160         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) 
     161         ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:) 
    201162         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) 
     163         CALL wrk_dealloc( jpi,jpj,jpk,   ztrdu, ztrdv )  
     164      ENDIF 
     165      !                                      ! print mean trends (used for debugging) 
    206166      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' spg  - Ua: ', mask1=umask, & 
    207167         &                       tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     
    216176      !!                  ***  ROUTINE dyn_spg_init  *** 
    217177      !!                 
    218       !! ** Purpose :   Control the consistency between cpp options for  
     178      !! ** Purpose :   Control the consistency between namelist options for  
    219179      !!              surface pressure gradient schemes 
    220180      !!---------------------------------------------------------------------- 
    221       INTEGER ::   ioptio 
     181      INTEGER ::   ioptio, ios   ! local integers 
     182      ! 
     183      NAMELIST/namdyn_spg/ ln_dynspg_exp       , ln_dynspg_ts,   & 
     184      &                    ln_bt_fw, ln_bt_av  , ln_bt_auto  ,   & 
     185      &                    nn_baro , rn_bt_cmax, nn_bt_flt 
    222186      !!---------------------------------------------------------------------- 
    223187      ! 
    224188      IF( nn_timing == 1 )  CALL timing_start('dyn_spg_init') 
    225189      ! 
    226       IF(lwp) THEN             ! Control print 
     190      REWIND( numnam_ref )              ! Namelist namdyn_spg in reference namelist : Free surface 
     191      READ  ( numnam_ref, namdyn_spg, IOSTAT = ios, ERR = 901) 
     192901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdyn_spg in reference namelist', lwp ) 
     193      ! 
     194      REWIND( numnam_cfg )              ! Namelist namdyn_spg in configuration namelist : Free surface 
     195      READ  ( numnam_cfg, namdyn_spg, IOSTAT = ios, ERR = 902 ) 
     196902   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdyn_spg in configuration namelist', lwp ) 
     197      IF(lwm) WRITE ( numond, namdyn_spg ) 
     198      ! 
     199      IF(lwp) THEN             ! Namelist print 
    227200         WRITE(numout,*) 
    228201         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme' 
    229202         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       ENDIF 
    234  
    235       IF( lk_dynspg_ts ) CALL dyn_spg_ts_init( nit000 ) 
    236       ! (do it now, to set nn_baro, used to allocate some arrays later on) 
    237       !                        ! allocate dyn_spg arrays 
    238       IF( lk_dynspg_ts ) THEN 
    239          IF( dynspg_oce_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_oce arrays') 
    240          IF( dyn_spg_ts_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_ts  arrays') 
    241          IF ((neuler/=0).AND.(ln_bt_fw)) CALL ts_rst( nit000, 'READ' ) 
    242       ENDIF 
    243  
    244       !                        ! Control of surface pressure gradient scheme options 
    245       ioptio = 0 
    246       IF(lk_dynspg_exp)   ioptio = ioptio + 1 
    247       IF(lk_dynspg_ts )   ioptio = ioptio + 1 
    248       IF(lk_dynspg_flt)   ioptio = ioptio + 1 
    249       ! 
    250       IF( ( ioptio > 1 .AND. .NOT. lk_esopa ) .OR. ( ioptio == 0 .AND. .NOT. lk_c1d ) )   & 
    251            &   CALL ctl_stop( ' Choose only one surface pressure gradient scheme with a key cpp' ) 
    252       IF( ( lk_dynspg_ts .OR. lk_dynspg_exp ) .AND. ln_isfcav )   & 
    253            &   CALL ctl_stop( ' dynspg_ts and dynspg_exp not tested with ice shelf cavity ' ) 
    254       ! 
    255       IF( lk_esopa     )   nspg = -1 
    256       IF( lk_dynspg_exp)   nspg =  0 
    257       IF( lk_dynspg_ts )   nspg =  1 
    258       IF( lk_dynspg_flt)   nspg =  2 
    259       ! 
    260       IF( lk_esopa     )   nspg = -1 
     203         WRITE(numout,*) '     Explicit free surface                  ln_dynspg_exp = ', ln_dynspg_exp 
     204         WRITE(numout,*) '     Free surface with time splitting       ln_dynspg_ts  = ', ln_dynspg_ts 
     205      ENDIF 
     206      !                          ! Control of surface pressure gradient scheme options 
     207      ;                              nspg =  np_NO    ;   ioptio = 0 
     208      IF( ln_dynspg_exp ) THEN   ;   nspg =  np_EXP   ;   ioptio = ioptio + 1   ;   ENDIF 
     209      IF( ln_dynspg_ts  ) THEN   ;   nspg =  np_TS    ;   ioptio = ioptio + 1   ;   ENDIF 
     210      ! 
     211      IF( ioptio  > 1 )   CALL ctl_stop( 'Choose only one surface pressure gradient scheme' ) 
     212      IF( ioptio == 0 )   CALL ctl_warn( 'NO surface pressure gradient trend in momentum Eqs.' ) 
     213      IF( ln_dynspg_exp .AND. ln_isfcav )   & 
     214           &   CALL ctl_stop( ' dynspg_exp not tested with ice shelf cavity ' ) 
    261215      ! 
    262216      IF(lwp) THEN 
    263217         WRITE(numout,*) 
    264          IF( nspg == -1 )   WRITE(numout,*) '     ESOPA test All scheme used' 
    265          IF( nspg ==  0 )   WRITE(numout,*) '     explicit free surface' 
    266          IF( nspg ==  1 )   WRITE(numout,*) '     free surface with time splitting scheme' 
    267          IF( nspg ==  2 )   WRITE(numout,*) '     filtered free surface' 
    268       ENDIF 
    269  
    270 #if defined key_dynspg_flt || defined key_esopa 
    271       CALL solver_init( nit000 )   ! Elliptic solver initialisation 
    272 #endif 
    273  
    274       !                        ! Control of timestep choice 
    275       IF( lk_dynspg_ts .OR. lk_dynspg_exp ) THEN 
    276          IF( nn_cla == 1 )   CALL ctl_stop( 'Crossland advection not implemented for this free surface formulation' ) 
    277       ENDIF 
    278  
    279       !               ! Control of hydrostatic pressure choice 
    280       IF( lk_dynspg_ts .AND. ln_dynhpg_imp ) THEN 
    281          CALL ctl_stop( 'Semi-implicit hpg not compatible with time splitting' ) 
     218         IF( nspg == np_EXP )   WRITE(numout,*) '     explicit free surface' 
     219         IF( nspg == np_TS  )   WRITE(numout,*) '     free surface with time splitting scheme' 
     220         IF( nspg == np_NO  )   WRITE(numout,*) '     No surface surface pressure gradient trend in momentum Eqs.' 
     221      ENDIF 
     222      ! 
     223      IF( nspg == np_TS ) THEN   ! split-explicit scheme initialisation 
     224         CALL dyn_spg_ts_init          ! do it first: set nn_baro used to allocate some arrays later on 
     225         IF( dyn_spg_ts_alloc() /= 0  )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_ts  arrays' ) 
     226         IF( neuler/=0 .AND. ln_bt_fw )   CALL ts_rst( nit000, 'READ' ) 
    282227      ENDIF 
    283228      ! 
Note: See TracChangeset for help on using the changeset viewer.