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 6004 for branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90 – NEMO

Ignore:
Timestamp:
2015-12-04T17:05:58+01:00 (9 years ago)
Author:
gm
Message:

#1613: vvl by default, step III: Merge with the trunk (free surface simplification) (see wiki)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r5845 r6004  
    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 
     
    4438 
    4539   INTEGER ::   nspg = 0   ! type of surface pressure gradient scheme defined from lk_dynspg_...  
     40 
     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 
    4645 
    4746   !! * Substitutions 
     
    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  
     
    7872      !!---------------------------------------------------------------------- 
    7973      INTEGER, INTENT(in   ) ::   kt       ! ocean time-step index 
    80       INTEGER, INTENT(  out) ::   kindic   ! solver flag 
    8174      ! 
    8275      INTEGER  ::   ji, jj, jk                             ! dummy loop indices 
     
    8881      IF( nn_timing == 1 )  CALL timing_start('dyn_spg') 
    8982      ! 
    90  
    91 !!gm NOTA BENE : the dynspg_exp and dynspg_ts should be modified so that  
    92 !!gm             they return the after velocity, not the trends (as in trazdf_imp...) 
    93 !!gm             In this case, change/simplify dynnxt 
    94  
    95  
    9683      IF( l_trddyn )   THEN                      ! temporary save of ta and sa trends 
    9784         CALL wrk_alloc( jpi,jpj,jpk,   ztrdu, ztrdv )  
     
    9986         ztrdv(:,:,:) = va(:,:,:) 
    10087      ENDIF 
    101  
     88      ! 
    10289      IF(      ln_apr_dyn                                                &   ! atmos. pressure 
    103          .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) 
    10491         .OR.  nn_ice_embd == 2  ) THEN                                      ! embedded sea-ice 
    10592         ! 
     
    11198         END DO          
    11299         ! 
    113          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) ==! 
    114101            zg_2 = grav * 0.5 
    115102            DO jj = 2, jpjm1                          ! gradient of Patm using inverse barometer ssh 
     
    124111         ! 
    125112         !                                    !==  tide potential forcing term  ==! 
    126          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 
    127114            ! 
    128115            CALL upd_tide( kt )                      ! update tide potential 
     
    152139         ENDIF 
    153140         ! 
    154          DO jk = 1, jpkm1                     !== Add all terms to the general trend 
     141         DO jk = 1, jpkm1                    !== Add all terms to the general trend 
    155142            DO jj = 2, jpjm1 
    156143               DO ji = fs_2, fs_jpim1   ! vector opt. 
     
    160147            END DO 
    161148         END DO     
    162           
     149         ! 
    163150!!gm add here a call to dyn_trd for ice pressure gradient, the surf pressure trends ???? 
    164                
    165       ENDIF 
    166  
    167       SELECT CASE ( nspg )                       ! compute surf. pressure gradient trend and add it to the general trend 
    168       !                                                      
    169       CASE (  0 )   ;   CALL dyn_spg_exp( kt )              ! explicit 
    170       CASE (  1 )   ;   CALL dyn_spg_ts ( kt )              ! time-splitting 
    171       CASE (  2 )   ;   CALL dyn_spg_flt( kt, kindic )      ! filtered 
    172       !                                                     
     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 
    173157      END SELECT 
    174158      !                     
    175       IF( l_trddyn )   THEN                      ! save the surface pressure gradient trends for further diagnostics 
    176          SELECT CASE ( nspg ) 
    177          CASE ( 0, 1 ) 
    178             ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) 
    179             ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:) 
    180          CASE( 2 ) 
    181             z2dt = 2. * rdt 
    182             IF( neuler == 0 .AND. kt == nit000 )   z2dt = rdt 
    183             ztrdu(:,:,:) = ( ua(:,:,:) - ub(:,:,:) ) / z2dt - ztrdu(:,:,:) 
    184             ztrdv(:,:,:) = ( va(:,:,:) - vb(:,:,:) ) / z2dt - ztrdv(:,:,:) 
    185          END SELECT 
     159      IF( l_trddyn )   THEN                  ! save the surface pressure gradient trends for further diagnostics 
     160         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) 
     161         ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:) 
    186162         CALL trd_dyn( ztrdu, ztrdv, jpdyn_spg, kt ) 
    187          ! 
    188163         CALL wrk_dealloc( jpi,jpj,jpk,   ztrdu, ztrdv )  
    189164      ENDIF 
    190       !                                          ! print mean trends (used for debugging) 
     165      !                                      ! print mean trends (used for debugging) 
    191166      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' spg  - Ua: ', mask1=umask, & 
    192167         &                       tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
     
    201176      !!                  ***  ROUTINE dyn_spg_init  *** 
    202177      !!                 
    203       !! ** Purpose :   Control the consistency between cpp options for  
     178      !! ** Purpose :   Control the consistency between namelist options for  
    204179      !!              surface pressure gradient schemes 
    205180      !!---------------------------------------------------------------------- 
    206       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 
    207186      !!---------------------------------------------------------------------- 
    208187      ! 
    209188      IF( nn_timing == 1 )  CALL timing_start('dyn_spg_init') 
    210189      ! 
    211       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 
    212200         WRITE(numout,*) 
    213201         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme' 
    214202         WRITE(numout,*) '~~~~~~~~~~~' 
    215          WRITE(numout,*) '     Explicit free surface                  lk_dynspg_exp = ', lk_dynspg_exp 
    216          WRITE(numout,*) '     Free surface with time splitting       lk_dynspg_ts  = ', lk_dynspg_ts 
    217          WRITE(numout,*) '     Filtered free surface cst volume       lk_dynspg_flt = ', lk_dynspg_flt 
    218       ENDIF 
    219  
    220       IF( lk_dynspg_ts ) CALL dyn_spg_ts_init( nit000 ) 
    221       ! (do it now, to set nn_baro, used to allocate some arrays later on) 
    222       !                        ! allocate dyn_spg arrays 
    223       IF( lk_dynspg_ts ) THEN 
    224          IF( dynspg_oce_alloc() /= 0 )   CALL ctl_stop('STOP', 'dyn_spg_init: failed to allocate dynspg_oce arrays') 
    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' ) 
    227       ENDIF 
    228  
    229       !                        ! Control of surface pressure gradient scheme options 
    230       ioptio = 0 
    231       IF(lk_dynspg_exp)   ioptio = ioptio + 1 
    232       IF(lk_dynspg_ts )   ioptio = ioptio + 1 
    233       IF(lk_dynspg_flt)   ioptio = ioptio + 1 
    234       ! 
    235       IF(  ioptio > 1  .OR. ( ioptio == 0 .AND. .NOT. lk_c1d ) )   & 
    236            &   CALL ctl_stop( ' Choose only one surface pressure gradient scheme with a key cpp' ) 
    237       IF( ( lk_dynspg_ts .OR. lk_dynspg_exp ) .AND. ln_isfcav )   & 
    238            &   CALL ctl_stop( ' dynspg_ts and dynspg_exp not tested with ice shelf cavity ' ) 
    239       ! 
    240       IF( lk_dynspg_exp)   nspg =  0 
    241       IF( lk_dynspg_ts )   nspg =  1 
    242       IF( lk_dynspg_flt)   nspg =  2 
     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      ! 
     214      IF( ln_dynspg_ts .AND. ln_isfcav )   CALL ctl_stop( ' dynspg_ts not tested with ice shelf cavity ' ) 
    243215      ! 
    244216      IF(lwp) THEN 
    245217         WRITE(numout,*) 
    246          IF( nspg ==  0 )   WRITE(numout,*) '     explicit free surface' 
    247          IF( nspg ==  1 )   WRITE(numout,*) '     free surface with time splitting scheme' 
    248          IF( nspg ==  2 )   WRITE(numout,*) '     filtered free surface' 
    249       ENDIF 
    250  
    251 #if defined key_dynspg_flt 
    252       CALL solver_init( nit000 )   ! Elliptic solver initialisation 
    253 #endif 
    254       !               ! Control of hydrostatic pressure choice 
    255       IF( lk_dynspg_ts .AND. ln_dynhpg_imp )   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' ) 
     227      ENDIF 
    256228      ! 
    257229      IF( nn_timing == 1 )  CALL timing_stop('dyn_spg_init') 
Note: See TracChangeset for help on using the changeset viewer.