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 6864 for branches – NEMO

Changeset 6864 for branches


Ignore:
Timestamp:
2016-08-12T15:16:27+02:00 (8 years ago)
Author:
lovato
Message:

#1729 - trunk: removed key_tide from the code and set usage of ln_tide. Tested with AMM12 and ORCA2_LIM_PISCES.

Location:
branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/CONFIG/AMM12/EXP00/namelist_cfg

    r6862 r6864  
    189189/ 
    190190!----------------------------------------------------------------------- 
    191 &nam_tide      !   tide parameters (#ifdef key_tide) 
    192 !----------------------------------------------------------------------- 
     191&nam_tide      !   tide parameters 
     192!----------------------------------------------------------------------- 
     193   ln_tide     = .true. 
    193194   clname(1)     =   'Q1'   !  name of constituent 
    194195   clname(2)     =   'O1' 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/CONFIG/AMM12/cpp_AMM12.fcm

    r6862 r6864  
    1  bld::tool::fppkeys key_tide key_zdfgls key_diainstant key_mpp_mpi key_iomput 
     1 bld::tool::fppkeys key_zdfgls key_diainstant key_mpp_mpi key_iomput 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/CONFIG/SHARED/namelist_ref

    r6863 r6864  
    611611/ 
    612612!----------------------------------------------------------------------- 
    613 &nam_tide      !   tide parameters                                      ("key_tide") 
    614 !----------------------------------------------------------------------- 
     613&nam_tide      !   tide parameters 
     614!----------------------------------------------------------------------- 
     615   ln_tide     = .false. 
    615616   ln_tide_pot = .true.    !  use tidal potential forcing 
    616617   ln_tide_ramp= .false.   ! 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdydta.F90

    r6862 r6864  
    3232#endif 
    3333   USE sbcapr 
     34   USE sbctide  , ONLY: ln_tide ! Tidal forcing or not 
    3435 
    3536   IMPLICIT NONE 
     
    377378      END DO  ! ib_bdy 
    378379 
    379 #if defined key_tide 
    380       IF (ln_dynspg_ts) THEN      ! Fill temporary arrays with slow-varying bdy data                            
    381          DO ib_bdy = 1, nb_bdy    ! Tidal component added in ts loop 
    382             IF ( nn_dyn2d_dta(ib_bdy) .ge. 2 ) THEN 
    383                nblen => idx_bdy(ib_bdy)%nblen 
    384                nblenrim => idx_bdy(ib_bdy)%nblenrim 
    385                IF( cn_dyn2d(ib_bdy) == 'frs' ) THEN; ilen1(:)=nblen(:) ; ELSE ; ilen1(:)=nblenrim(:) ; ENDIF  
    386                IF ( dta_bdy(ib_bdy)%ll_ssh ) dta_bdy_s(ib_bdy)%ssh(1:ilen1(1)) = dta_bdy(ib_bdy)%ssh(1:ilen1(1)) 
    387                IF ( dta_bdy(ib_bdy)%ll_u2d ) dta_bdy_s(ib_bdy)%u2d(1:ilen1(2)) = dta_bdy(ib_bdy)%u2d(1:ilen1(2)) 
    388                IF ( dta_bdy(ib_bdy)%ll_v2d ) dta_bdy_s(ib_bdy)%v2d(1:ilen1(3)) = dta_bdy(ib_bdy)%v2d(1:ilen1(3)) 
    389             ENDIF 
    390          END DO 
    391       ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
    392          ! 
    393          CALL bdy_dta_tides( kt=kt, time_offset=time_offset ) 
     380      IF ( ln_tide ) THEN 
     381         IF (ln_dynspg_ts) THEN      ! Fill temporary arrays with slow-varying bdy data                            
     382            DO ib_bdy = 1, nb_bdy    ! Tidal component added in ts loop 
     383               IF ( nn_dyn2d_dta(ib_bdy) .ge. 2 ) THEN 
     384                  nblen => idx_bdy(ib_bdy)%nblen 
     385                  nblenrim => idx_bdy(ib_bdy)%nblenrim 
     386                  IF( cn_dyn2d(ib_bdy) == 'frs' ) THEN; ilen1(:)=nblen(:) ; ELSE ; ilen1(:)=nblenrim(:) ; ENDIF  
     387                  IF ( dta_bdy(ib_bdy)%ll_ssh ) dta_bdy_s(ib_bdy)%ssh(1:ilen1(1)) = dta_bdy(ib_bdy)%ssh(1:ilen1(1)) 
     388                  IF ( dta_bdy(ib_bdy)%ll_u2d ) dta_bdy_s(ib_bdy)%u2d(1:ilen1(2)) = dta_bdy(ib_bdy)%u2d(1:ilen1(2)) 
     389                  IF ( dta_bdy(ib_bdy)%ll_v2d ) dta_bdy_s(ib_bdy)%v2d(1:ilen1(3)) = dta_bdy(ib_bdy)%v2d(1:ilen1(3)) 
     390               ENDIF 
     391            END DO 
     392         ELSE ! Add tides if not split-explicit free surface else this is done in ts loop 
     393            ! 
     394            CALL bdy_dta_tides( kt=kt, time_offset=time_offset ) 
     395         ENDIF 
    394396      ENDIF 
    395 #endif 
    396397 
    397398      IF ( ln_apr_obc ) THEN 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r6863 r6864  
    2222   USE bdydta         ! open boundary cond. setting   (bdy_dta_init routine) 
    2323   USE bdytides       ! open boundary cond. setting   (bdytide_init routine) 
    24    USE sbctide  , ONLY: lk_tide ! Tidal forcing or not 
     24   USE sbctide  , ONLY: ln_tide ! Tidal forcing or not 
    2525   USE phycst   , ONLY: rday 
    2626   ! 
     
    105105         ! 
    106106         ! Open boundaries initialisation of tidal harmonic forcing 
    107          IF( lk_tide ) CALL bdytide_init 
     107         IF( ln_tide ) CALL bdytide_init 
    108108         ! 
    109109      ELSE 
     
    224224              CASE DEFAULT   ;   CALL ctl_stop( 'nn_dyn2d_dta must be between 0 and 3' ) 
    225225           END SELECT 
    226            IF (( nn_dyn2d_dta(ib_bdy) .ge. 2 ).AND.(.NOT.lk_tide)) THEN 
    227              CALL ctl_stop( 'You must activate key_tide to add tidal forcing at open boundaries' ) 
     226           IF (( nn_dyn2d_dta(ib_bdy) .ge. 2 ).AND.(.NOT.ln_tide)) THEN 
     227             CALL ctl_stop( 'You must activate with ln_tide to add tidal forcing at open boundaries' ) 
    228228           ENDIF 
    229229        ENDIF 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DIA/diaharm.F90

    r6140 r6864  
    66   !! History :  3.1  !  2007  (O. Le Galloudec, J. Chanut)  Original code 
    77   !!---------------------------------------------------------------------- 
    8 #if defined key_diaharm && defined key_tide 
     8#if defined key_diaharm 
    99   !!---------------------------------------------------------------------- 
    1010   !!   'key_diaharm' 
    11    !!   'key_tide' 
    1211   !!---------------------------------------------------------------------- 
    1312   USE oce             ! ocean dynamics and tracers variables 
     
    1615   USE daymod 
    1716   USE tide_mod 
     17   USE sbctide  , ONLY: ln_tide ! Tidal forcing or not 
    1818   ! 
    1919   USE in_out_manager  ! I/O units 
     
    8282         WRITE(numout,*) '~~~~~~~ ' 
    8383      ENDIF 
     84      ! 
     85      IF( .NOT. ln_tyde )   CALL ctl_stop( 'dia_harm_init : ln_tyde must be true for harmonic analysis') 
    8486      ! 
    8587      CALL tide_init_Wave 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r6140 r6864  
    8888      ! 
    8989      IF(      ln_apr_dyn                                                &   ! atmos. pressure 
    90          .OR.  ( .NOT.ln_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. ln_tide) )   &   ! tide potential (no time slitting) 
    9191         .OR.  nn_ice_embd == 2  ) THEN                                      ! embedded sea-ice 
    9292         ! 
     
    111111         ! 
    112112         !                                    !==  tide potential forcing term  ==! 
    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 
     113         IF( .NOT.ln_dynspg_ts .AND. ( ln_tide_pot .AND. ln_tide )  ) THEN   ! N.B. added directly at sub-time-step in ts-case 
    114114            ! 
    115115            CALL upd_tide( kt )                      ! update tide potential 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_ts.F90

    r6862 r6864  
    607607         !                                                !  ------------------ 
    608608         ! Update only tidal forcing at open boundaries 
    609 #if defined key_tide 
    610          IF( ln_bdy      .AND. lk_tide )   CALL bdy_dta_tides( kt, kit=jn, time_offset= noffset+1 ) 
    611          IF( ln_tide_pot .AND. lk_tide )   CALL upd_tide     ( kt, kit=jn, time_offset= noffset   ) 
    612 #endif 
     609         IF( ln_bdy      .AND. ln_tide )   CALL bdy_dta_tides( kt, kit=jn, time_offset= noffset+1 ) 
     610         IF( ln_tide_pot .AND. ln_tide )   CALL upd_tide     ( kt, kit=jn, time_offset= noffset   ) 
    613611         ! 
    614612         ! Set extrapolation coefficients for predictor step: 
     
    860858         ! 
    861859         ! Add tidal astronomical forcing if defined 
    862          IF ( lk_tide.AND.ln_tide_pot ) THEN 
     860         IF ( ln_tide.AND.ln_tide_pot ) THEN 
    863861            DO jj = 2, jpjm1 
    864862               DO ji = fs_2, fs_jpim1   ! vector opt. 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/sbctide.F90

    r6140 r6864  
    2222   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:) ::   pot_astro   ! 
    2323 
    24 #if defined key_tide 
    2524   !!---------------------------------------------------------------------- 
    26    !!   'key_tide' :                                        tidal potential 
     25   !!   tidal potential 
    2726   !!---------------------------------------------------------------------- 
    2827   !!   sbc_tide            :  
     
    3029   !!---------------------------------------------------------------------- 
    3130 
    32    LOGICAL, PUBLIC, PARAMETER ::   lk_tide  = .TRUE. 
    3331   REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   amp_pot, phi_pot 
    3432 
     
    125123   END SUBROUTINE tide_init_potential 
    126124 
    127 #else 
    128   !!---------------------------------------------------------------------- 
    129   !!   Default case :   Empty module 
    130   !!---------------------------------------------------------------------- 
    131   LOGICAL, PUBLIC, PARAMETER ::   lk_tide = .FALSE. 
    132 CONTAINS 
    133   SUBROUTINE sbc_tide( kt )      ! Empty routine 
    134     INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
    135     WRITE(*,*) 'sbc_tide: You should not have seen this print! error?', kt 
    136   END SUBROUTINE sbc_tide 
    137 #endif 
    138  
    139125  !!====================================================================== 
    140126END MODULE sbctide 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/tideini.F90

    r6140 r6864  
    2525   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ftide        !: 
    2626 
     27   LOGICAL , PUBLIC ::   ln_tide         !: 
    2728   LOGICAL , PUBLIC ::   ln_tide_pot     !: 
    2829   LOGICAL , PUBLIC ::   ln_tide_ramp    !: 
     
    4849      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    4950      ! 
    50       NAMELIST/nam_tide/ln_tide_pot, ln_tide_ramp, rdttideramp, clname 
     51      NAMELIST/nam_tide/ln_tide, ln_tide_pot, ln_tide_ramp, rdttideramp, clname 
    5152      !!---------------------------------------------------------------------- 
    52       ! 
    53       IF(lwp) THEN 
    54          WRITE(numout,*) 
    55          WRITE(numout,*) 'tide_init : Initialization of the tidal components' 
    56          WRITE(numout,*) '~~~~~~~~~ ' 
    57       ENDIF 
    58       ! 
    59       CALL tide_init_Wave 
    6053      ! 
    6154      ! Read Namelist nam_tide 
     
    6962      IF(lwm) WRITE ( numond, nam_tide ) 
    7063      ! 
     64      IF (ln_tide) THEN 
     65         IF (lwp) THEN 
     66            WRITE(numout,*) 
     67            WRITE(numout,*) 'tide_init : Initialization of the tidal components' 
     68            WRITE(numout,*) '~~~~~~~~~ ' 
     69            WRITE(numout,*) '   Namelist nam_tide' 
     70            WRITE(numout,*) '              Use tidal components : ln_tide      = ', ln_tide 
     71            WRITE(numout,*) '      Apply astronomical potential : ln_tide_pot  = ', ln_tide_pot 
     72            WRITE(numout,*) '                                     nb_harmo     = ', nb_harmo 
     73            WRITE(numout,*) '                                     ln_tide_ramp = ', ln_tide_ramp 
     74            WRITE(numout,*) '                                     rdttideramp  = ', rdttideramp 
     75         ENDIF 
     76      ELSE 
     77         IF(lwp) WRITE(numout,*) 
     78         IF(lwp) WRITE(numout,*) 'tide_init : tidal components not used (ln_tide = F)' 
     79         IF(lwp) WRITE(numout,*) '~~~~~~~~~ ' 
     80         RETURN 
     81      ENDIF 
     82      ! 
     83      CALL tide_init_Wave 
     84      ! 
    7185      nb_harmo=0 
    7286      DO jk = 1, jpmax_harmo 
     
    7993      IF( nb_harmo == 0 )   CALL ctl_stop( 'tide_init : No tidal components set in nam_tide' ) 
    8094      ! 
    81       IF(lwp) THEN 
    82          WRITE(numout,*) '   Namelist nam_tide' 
    83          WRITE(numout,*) '      Apply astronomical potential : ln_tide_pot  =', ln_tide_pot 
    84          WRITE(numout,*) '                                     nb_harmo     = ', nb_harmo 
    85          WRITE(numout,*) '                                     ln_tide_ramp = ', ln_tide_ramp  
    86          WRITE(numout,*) '                                     rdttideramp  = ', rdttideramp 
    87       ENDIF 
    8895      IF( ln_tide_ramp.AND.((nitend-nit000+1)*rdt/rday < rdttideramp) )   & 
    8996         &   CALL ctl_stop('rdttideramp must be lower than run duration') 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/SBC/updtide.F90

    r5913 r6864  
    55   !!====================================================================== 
    66   !! History :  9.0  !  07  (O. Le Galloudec)  Original code 
    7    !!---------------------------------------------------------------------- 
    8 #if defined key_tide 
    9    !!---------------------------------------------------------------------- 
    10    !!   'key_tide' :                                        tidal potential 
    117   !!---------------------------------------------------------------------- 
    128   !!   upd_tide       : update tidal potential 
     
    8177   END SUBROUTINE upd_tide 
    8278 
    83 #else 
    84   !!---------------------------------------------------------------------- 
    85   !!   Dummy module :                                        NO TIDE 
    86   !!---------------------------------------------------------------------- 
    87 CONTAINS 
    88   SUBROUTINE upd_tide( kt, kit, time_offset )  ! Empty routine 
    89     INTEGER, INTENT(in)           ::   kt      !  integer  arg, dummy routine 
    90     INTEGER, INTENT(in), OPTIONAL ::   kit     !  optional arg, dummy routine 
    91     INTEGER, INTENT(in), OPTIONAL ::   time_offset !  optional arg, dummy routine 
    92     WRITE(*,*) 'upd_tide: You should not have seen this print! error?', kt 
    93   END SUBROUTINE upd_tide 
    94  
    95 #endif 
    96  
    9779  !!====================================================================== 
    9880 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6862 r6864  
    5252#endif 
    5353   USE tideini        ! tidal components initialization   (tide_ini routine) 
    54    USE bdy_oce   , ONLY: ln_bdy 
     54   USE bdy_oce ONLY: ln_bdy 
    5555   USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
    56    USE sbctide, ONLY  : lk_tide 
    5756   USE istate         ! initial state setting          (istate_init routine) 
    5857   USE ldfdyn         ! lateral viscosity setting      (ldfdyn_init routine) 
     
    432431      !                                      ! external forcing  
    433432!!gm to be added : creation and call of sbc_apr_init 
    434       IF( lk_tide       )   CALL    tide_init   ! tidal harmonics 
     433                            CALL    tide_init   ! tidal harmonics 
    435434                            CALL     sbc_init   ! surface boundary conditions (including sea-ice) 
    436435                            CALL     bdy_init   ! Open boundaries initialisation 
  • branches/2016/dev_r6522_SIMPLIF_3/NEMOGCM/NEMO/OPA_SRC/step.F90

    r6862 r6864  
    104104      ! Update external forcing (tides, open boundaries, and surface boundary condition (including sea-ice) 
    105105      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    106       IF( lk_tide    )   CALL sbc_tide( kstp )                   ! update tide potential 
     106      IF( ln_tide    )   CALL sbc_tide( kstp )                   ! update tide potential 
    107107      IF( ln_apr_dyn )   CALL sbc_apr ( kstp )                   ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib)  
    108108      IF( ln_bdy     )   CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
Note: See TracChangeset for help on using the changeset viewer.