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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r4496 r6225  
    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 
    28    USE trdmod         ! ocean dynamics trends 
    29    USE trdmod_oce     ! ocean variables trends 
     22   USE sbctide        !  
     23   USE updtide        !  
     24   USE trd_oce        ! trends: ocean variables 
     25   USE trddyn         ! trend manager: dynamics 
     26   ! 
    3027   USE prtctl         ! Print control                     (prt_ctl routine) 
    3128   USE in_out_manager ! I/O manager 
    3229   USE lib_mpp        ! MPP library 
    33    USE solver          ! solver initialization 
    34    USE wrk_nemo        ! Memory Allocation 
    35    USE timing          ! Timing 
    36  
     30   USE wrk_nemo       ! Memory Allocation 
     31   USE timing         ! Timing 
    3732 
    3833   IMPLICIT NONE 
     
    4439   INTEGER ::   nspg = 0   ! type of surface pressure gradient scheme defined from lk_dynspg_...  
    4540 
     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 
    4646   !! * Substitutions 
    47 #  include "domzgr_substitute.h90" 
    4847#  include "vectopt_loop_substitute.h90" 
    4948   !!---------------------------------------------------------------------- 
     
    5453CONTAINS 
    5554 
    56    SUBROUTINE dyn_spg( kt, kindic ) 
     55   SUBROUTINE dyn_spg( kt ) 
    5756      !!---------------------------------------------------------------------- 
    5857      !!                  ***  ROUTINE dyn_spg  *** 
    5958      !! 
    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 
     59      !! ** Purpose :   compute surface pressure gradient including the  
     60      !!              atmospheric pressure forcing (ln_apr_dyn=T). 
    6661      !! 
    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 
     62      !! ** Method  :   Two schemes: 
     63      !!              - explicit       : the spg is evaluated at now 
     64      !!              - split-explicit : a time splitting technique is used 
    7165      !! 
    7266      !!              ln_apr_dyn=T : the atmospheric pressure forcing is applied  
     
    7670      !!             Note that as all external forcing a time averaging over a two rdt 
    7771      !!             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       ! 
     72      !!---------------------------------------------------------------------- 
    8373      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index 
    84       INTEGER, INTENT(  out) ::   kindic   ! solver flag 
    8574      ! 
    8675      INTEGER  ::   ji, jj, jk                             ! dummy loop indices 
     
    9281      IF( nn_timing == 1 )  CALL timing_start('dyn_spg') 
    9382      ! 
    94  
    95 !!gm NOTA BENE : the dynspg_exp and dynspg_ts should be modified so that  
    96 !!gm             they return the after velocity, not the trends (as in trazdf_imp...) 
    97 !!gm             In this case, change/simplify dynnxt 
    98  
    99  
    10083      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends 
    101          CALL wrk_alloc( jpi, jpj, jpk, ztrdu, ztrdv )  
     84         CALL wrk_alloc( jpi,jpj,jpk,  ztrdu, ztrdv )  
    10285         ztrdu(:,:,:) = ua(:,:,:) 
    10386         ztrdv(:,:,:) = va(:,:,:) 
    10487      ENDIF 
    105  
     88      ! 
    10689      IF(      ln_apr_dyn                                                &   ! atmos. pressure 
    107          .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) 
    10891         .OR.  nn_ice_embd == 2  ) THEN                                      ! embedded sea-ice 
    10992         ! 
     
    11598         END DO          
    11699         ! 
    117          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) ==! 
    118101            zg_2 = grav * 0.5 
    119102            DO jj = 2, jpjm1                          ! gradient of Patm using inverse barometer ssh 
    120103               DO ji = fs_2, fs_jpim1   ! vector opt. 
    121104                  spgu(ji,jj) = spgu(ji,jj) + zg_2 * (  ssh_ib (ji+1,jj) - ssh_ib (ji,jj)    & 
    122                      &                      + 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) 
    123106                  spgv(ji,jj) = spgv(ji,jj) + zg_2 * (  ssh_ib (ji,jj+1) - ssh_ib (ji,jj)    & 
    124                      &                      + 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) 
    125108               END DO 
    126109            END DO 
     
    128111         ! 
    129112         !                                    !==  tide potential forcing term  ==! 
    130          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 
    131114            ! 
    132115            CALL upd_tide( kt )                      ! update tide potential 
     
    134117            DO jj = 2, jpjm1                         ! add tide potential forcing 
    135118               DO ji = fs_2, fs_jpim1   ! vector opt. 
    136                   spgu(ji,jj) = spgu(ji,jj) + grav * ( pot_astro(ji+1,jj) - pot_astro(ji,jj) ) / e1u(ji,jj) 
    137                   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) 
    138121               END DO  
    139122            END DO 
     
    141124         ! 
    142125         IF( nn_ice_embd == 2 ) THEN          !== embedded sea ice: Pressure gradient due to snow-ice mass ==! 
    143             CALL wrk_alloc( jpi, jpj, zpice ) 
     126            CALL wrk_alloc( jpi,jpj,  zpice ) 
    144127            !                                             
    145128            zintp = REAL( MOD( kt-1, nn_fsbc ) ) / REAL( nn_fsbc ) 
     
    148131            DO jj = 2, jpjm1 
    149132               DO ji = fs_2, fs_jpim1   ! vector opt. 
    150                   spgu(ji,jj) = spgu(ji,jj) + ( zpice(ji+1,jj) - zpice(ji,jj) ) / e1u(ji,jj) 
    151                   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) 
    152135               END DO 
    153136            END DO 
    154137            ! 
    155             CALL wrk_dealloc( jpi, jpj, zpice )          
     138            CALL wrk_dealloc( jpi,jpj,  zpice )          
    156139         ENDIF 
    157140         ! 
    158          DO jk = 1, jpkm1                     !== Add all terms to the general trend 
     141         DO jk = 1, jpkm1                    !== Add all terms to the general trend 
    159142            DO jj = 2, jpjm1 
    160143               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    163146               END DO 
    164147            END DO 
    165          END DO          
    166       ENDIF 
    167  
    168       SELECT CASE ( nspg )                       ! compute surf. pressure gradient trend and add it to the general trend 
    169       !                                                      
    170       CASE (  0 )   ;   CALL dyn_spg_exp( kt )              ! explicit 
    171       CASE (  1 )   ;   CALL dyn_spg_ts ( kt )              ! time-splitting 
    172       CASE (  2 )   ;   CALL dyn_spg_flt( kt, kindic )      ! filtered 
    173       !                                                     
    174       CASE ( -1 )                                ! esopa: test all possibility with control print 
    175                         CALL dyn_spg_exp( kt ) 
    176                         CALL prt_ctl( tab3d_1=ua, clinfo1=' spg0 - Ua: ', mask1=umask, & 
    177          &                            tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    178                         CALL dyn_spg_ts ( kt ) 
    179                         CALL prt_ctl( tab3d_1=ua, clinfo1=' spg1 - Ua: ', mask1=umask, & 
    180          &                           tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    181                         CALL dyn_spg_flt( kt, kindic ) 
    182                         CALL prt_ctl( tab3d_1=ua, clinfo1=' spg2 - Ua: ', mask1=umask, & 
    183          &                            tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     148         END DO     
     149         ! 
     150!!gm add here a call to dyn_trd for ice pressure gradient, the surf pressure trends ???? 
     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 
    184157      END SELECT 
    185158      !                     
    186       IF( l_trddyn )   THEN                      ! save the surface pressure gradient trends for further diagnostics 
    187          SELECT CASE ( nspg ) 
    188          CASE ( 0, 1 ) 
    189             ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) 
    190             ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:) 
    191          CASE( 2 ) 
    192             z2dt = 2. * rdt 
    193             IF( neuler == 0 .AND. kt == nit000 ) z2dt = rdt 
    194             ztrdu(:,:,:) = ( ua(:,:,:) - ub(:,:,:) ) / z2dt - ztrdu(:,:,:) 
    195             ztrdv(:,:,:) = ( va(:,:,:) - vb(:,:,:) ) / z2dt - ztrdv(:,:,:) 
    196          END SELECT 
    197          CALL trd_mod( ztrdu, ztrdv, jpdyn_trd_spg, 'DYN', kt ) 
    198          ! 
    199          CALL wrk_dealloc( jpi, jpj, jpk, ztrdu, ztrdv )  
    200       ENDIF 
    201       !                                          ! print mean trends (used for debugging) 
     159      IF( l_trddyn )   THEN                  ! save the surface pressure gradient trends for further diagnostics 
     160         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) 
     161         ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:) 
     162         CALL trd_dyn( ztrdu, ztrdv, jpdyn_spg, kt ) 
     163         CALL wrk_dealloc( jpi,jpj,jpk,   ztrdu, ztrdv )  
     164      ENDIF 
     165      !                                      ! print mean trends (used for debugging) 
    202166      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' spg  - Ua: ', mask1=umask, & 
    203167         &                       tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     
    212176      !!                  ***  ROUTINE dyn_spg_init  *** 
    213177      !!                 
    214       !! ** Purpose :   Control the consistency between cpp options for  
     178      !! ** Purpose :   Control the consistency between namelist options for  
    215179      !!              surface pressure gradient schemes 
    216180      !!---------------------------------------------------------------------- 
    217       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 
    218186      !!---------------------------------------------------------------------- 
    219187      ! 
    220188      IF( nn_timing == 1 )  CALL timing_start('dyn_spg_init') 
    221189      ! 
    222       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 
    223200         WRITE(numout,*) 
    224201         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme' 
    225202         WRITE(numout,*) '~~~~~~~~~~~' 
    226          WRITE(numout,*) '     Explicit free surface                  lk_dynspg_exp = ', lk_dynspg_exp 
    227          WRITE(numout,*) '     Free surface with time splitting       lk_dynspg_ts  = ', lk_dynspg_ts 
    228          WRITE(numout,*) '     Filtered free surface cst volume       lk_dynspg_flt = ', lk_dynspg_flt 
    229       ENDIF 
    230  
    231       IF( lk_dynspg_ts ) CALL dyn_spg_ts_init( nit000 ) 
    232       ! (do it now, to set nn_baro, used to allocate some arrays later on) 
    233       !                        ! allocate dyn_spg arrays 
    234       IF( lk_dynspg_ts ) THEN 
    235          IF( dynspg_oce_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_oce arrays') 
    236          IF( dyn_spg_ts_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_ts  arrays') 
    237          IF ((neuler/=0).AND.(ln_bt_fw)) CALL ts_rst( nit000, 'READ' ) 
    238       ENDIF 
    239  
    240       !                        ! Control of surface pressure gradient scheme options 
    241       ioptio = 0 
    242       IF(lk_dynspg_exp)   ioptio = ioptio + 1 
    243       IF(lk_dynspg_ts )   ioptio = ioptio + 1 
    244       IF(lk_dynspg_flt)   ioptio = ioptio + 1 
    245       ! 
    246       IF( ( ioptio > 1 .AND. .NOT. lk_esopa ) .OR. ( ioptio == 0 .AND. .NOT. lk_c1d ) )   & 
    247            &   CALL ctl_stop( ' Choose only one surface pressure gradient scheme with a key cpp' ) 
    248       ! 
    249       IF( lk_esopa     )   nspg = -1 
    250       IF( lk_dynspg_exp)   nspg =  0 
    251       IF( lk_dynspg_ts )   nspg =  1 
    252       IF( lk_dynspg_flt)   nspg =  2 
    253       ! 
    254       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 ' ) 
    255215      ! 
    256216      IF(lwp) THEN 
    257217         WRITE(numout,*) 
    258          IF( nspg == -1 )   WRITE(numout,*) '     ESOPA test All scheme used' 
    259          IF( nspg ==  0 )   WRITE(numout,*) '     explicit free surface' 
    260          IF( nspg ==  1 )   WRITE(numout,*) '     free surface with time splitting scheme' 
    261          IF( nspg ==  2 )   WRITE(numout,*) '     filtered free surface' 
    262       ENDIF 
    263  
    264 #if defined key_dynspg_flt || defined key_esopa 
    265       CALL solver_init( nit000 )   ! Elliptic solver initialisation 
    266 #endif 
    267  
    268       !                        ! Control of timestep choice 
    269       IF( lk_dynspg_ts .OR. lk_dynspg_exp ) THEN 
    270          IF( nn_cla == 1 )   CALL ctl_stop( 'Crossland advection not implemented for this free surface formulation' ) 
    271       ENDIF 
    272  
    273       !               ! Control of hydrostatic pressure choice 
    274       IF( lk_dynspg_ts .AND. ln_dynhpg_imp ) THEN 
    275          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' ) 
    276227      ENDIF 
    277228      ! 
Note: See TracChangeset for help on using the changeset viewer.