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 10772 – NEMO

Changeset 10772


Ignore:
Timestamp:
2019-03-16T11:17:25+01:00 (5 years ago)
Author:
smueller
Message:

Removal of module tideini and inclusion of its contents into module tide_mod (ticket #2194)

Location:
NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE
Files:
1 deleted
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/BDY/bdytides.F90

    r10068 r10772  
    1818   USE phycst         ! physical constants 
    1919   USE bdy_oce        ! ocean open boundary conditions 
    20    USE tideini        !  
     20   USE tide_mod       !  
    2121   USE daymod         ! calendar 
    2222   ! 
  • NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/SBC/sbctide.F90

    r10068 r10772  
    1010   USE phycst         ! physical constant 
    1111   USE daymod         ! calandar 
    12    USE tideini        !  
     12   USE tide_mod       !  
    1313   ! 
    1414   USE in_out_manager ! I/O units 
  • NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/SBC/updtide.F90

    r10068 r10772  
    1313   USE phycst          ! physical constant 
    1414   USE sbctide         ! tide potential variable 
    15    USE tideini, ONLY: ln_tide_ramp, rdttideramp 
     15   USE tide_mod, ONLY: ln_tide_ramp, rdttideramp 
    1616 
    1717   IMPLICIT NONE 
  • NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/TDE/tide_mod.F90

    r10752 r10772  
    66   !! History :  1.0  !  2007  (O. Le Galloudec)  Original code 
    77   !!---------------------------------------------------------------------- 
     8   USE oce            ! ocean dynamics and tracers variables 
    89   USE dom_oce        ! ocean space and time domain 
    910   USE phycst         ! physical constant 
    1011   USE daymod         ! calendar 
     12   ! 
     13   USE in_out_manager ! I/O units 
     14   USE iom            ! xIOs server 
     15   USE ioipsl         ! NetCDF IPSL library 
     16   USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
    1117 
    1218   IMPLICIT NONE 
    1319   PRIVATE 
    1420 
     21   PUBLIC   tide_init 
    1522   PUBLIC   tide_harmo       ! called by tideini and diaharm modules 
    1623   PUBLIC   tide_init_Wave   ! called by tideini and diaharm modules 
     
    2936   TYPE(tide), PUBLIC, DIMENSION(jpmax_harmo) ::   Wave   !: 
    3037 
     38   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   omega_tide   !: 
     39   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   v0tide       !: 
     40   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   utide        !: 
     41   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ftide        !: 
     42 
     43   LOGICAL , PUBLIC ::   ln_tide         !: 
     44   LOGICAL , PUBLIC ::   ln_tide_pot     !: 
     45   LOGICAL , PUBLIC ::   ln_read_load    !: 
     46   LOGICAL , PUBLIC ::   ln_scal_load    !: 
     47   LOGICAL , PUBLIC ::   ln_tide_ramp    !: 
     48   INTEGER , PUBLIC ::   nb_harmo        !: 
     49   INTEGER , PUBLIC ::   kt_tide         !: 
     50   REAL(wp), PUBLIC ::   rdttideramp     !: 
     51   REAL(wp), PUBLIC ::   rn_scal_load    !: 
     52   CHARACTER(lc), PUBLIC ::   cn_tide_load   !:  
     53 
     54   INTEGER , PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ntide   !: 
     55 
    3156   REAL(wp) ::   sh_T, sh_s, sh_h, sh_p, sh_p1             ! astronomic angles 
    3257   REAL(wp) ::   sh_xi, sh_nu, sh_nuprim, sh_nusec, sh_R   ! 
     
    3964   !!---------------------------------------------------------------------- 
    4065CONTAINS 
     66 
     67   SUBROUTINE tide_init 
     68      !!---------------------------------------------------------------------- 
     69      !!                 ***  ROUTINE tide_init  *** 
     70      !!----------------------------------------------------------------------       
     71      INTEGER  :: ji, jk 
     72      CHARACTER(LEN=4), DIMENSION(jpmax_harmo) :: clname 
     73      INTEGER  ::   ios                 ! Local integer output status for namelist read 
     74      ! 
     75      NAMELIST/nam_tide/ln_tide, ln_tide_pot, ln_scal_load, ln_read_load, cn_tide_load, & 
     76                  &     ln_tide_ramp, rn_scal_load, rdttideramp, clname 
     77      !!---------------------------------------------------------------------- 
     78      ! 
     79      ! Read Namelist nam_tide 
     80      REWIND( numnam_ref )              ! Namelist nam_tide in reference namelist : Tides 
     81      READ  ( numnam_ref, nam_tide, IOSTAT = ios, ERR = 901) 
     82901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nam_tide in reference namelist', lwp ) 
     83      ! 
     84      REWIND( numnam_cfg )              ! Namelist nam_tide in configuration namelist : Tides 
     85      READ  ( numnam_cfg, nam_tide, IOSTAT = ios, ERR = 902 ) 
     86902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nam_tide in configuration namelist', lwp ) 
     87      IF(lwm) WRITE ( numond, nam_tide ) 
     88      ! 
     89      IF( ln_tide ) THEN 
     90         IF (lwp) THEN 
     91            WRITE(numout,*) 
     92            WRITE(numout,*) 'tide_init : Initialization of the tidal components' 
     93            WRITE(numout,*) '~~~~~~~~~ ' 
     94            WRITE(numout,*) '   Namelist nam_tide' 
     95            WRITE(numout,*) '      Use tidal components                       ln_tide      = ', ln_tide 
     96            WRITE(numout,*) '         Apply astronomical potential            ln_tide_pot  = ', ln_tide_pot 
     97            WRITE(numout,*) '         Use scalar approx. for load potential   ln_scal_load = ', ln_scal_load 
     98            WRITE(numout,*) '         Read load potential from file           ln_read_load = ', ln_read_load 
     99            WRITE(numout,*) '         Apply ramp on tides at startup          ln_tide_ramp = ', ln_tide_ramp 
     100            WRITE(numout,*) '         Fraction of SSH used in scal. approx.   rn_scal_load = ', rn_scal_load 
     101            WRITE(numout,*) '         Duration (days) of ramp                 rdttideramp  = ', rdttideramp 
     102         ENDIF 
     103      ELSE 
     104         rn_scal_load = 0._wp  
     105 
     106         IF(lwp) WRITE(numout,*) 
     107         IF(lwp) WRITE(numout,*) 'tide_init : tidal components not used (ln_tide = F)' 
     108         IF(lwp) WRITE(numout,*) '~~~~~~~~~ ' 
     109         RETURN 
     110      ENDIF 
     111      ! 
     112      CALL tide_init_Wave 
     113      ! 
     114      nb_harmo=0 
     115      DO jk = 1, jpmax_harmo 
     116         DO ji = 1,jpmax_harmo 
     117            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide )   nb_harmo = nb_harmo + 1 
     118         END DO 
     119      END DO 
     120      !        
     121      ! Ensure that tidal components have been set in namelist_cfg 
     122      IF( nb_harmo == 0 )   CALL ctl_stop( 'tide_init : No tidal components set in nam_tide' ) 
     123      ! 
     124      IF( ln_read_load.AND.(.NOT.ln_tide_pot) ) & 
     125          &   CALL ctl_stop('ln_read_load requires ln_tide_pot') 
     126      IF( ln_scal_load.AND.(.NOT.ln_tide_pot) ) & 
     127          &   CALL ctl_stop('ln_scal_load requires ln_tide_pot') 
     128      IF( ln_scal_load.AND.ln_read_load ) & 
     129          &   CALL ctl_stop('Choose between ln_scal_load and ln_read_load') 
     130      IF( ln_tide_ramp.AND.((nitend-nit000+1)*rdt/rday < rdttideramp) )   & 
     131         &   CALL ctl_stop('rdttideramp must be lower than run duration') 
     132      IF( ln_tide_ramp.AND.(rdttideramp<0.) ) & 
     133         &   CALL ctl_stop('rdttideramp must be positive') 
     134      ! 
     135      ALLOCATE( ntide(nb_harmo) ) 
     136      DO jk = 1, nb_harmo 
     137         DO ji = 1, jpmax_harmo 
     138            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide ) THEN 
     139               ntide(jk) = ji 
     140               EXIT 
     141            ENDIF 
     142         END DO 
     143      END DO 
     144      ! 
     145      ALLOCATE( omega_tide(nb_harmo), v0tide    (nb_harmo),   & 
     146         &      utide     (nb_harmo), ftide     (nb_harmo)  ) 
     147      kt_tide = nit000 
     148      ! 
     149      IF (.NOT.ln_scal_load ) rn_scal_load = 0._wp 
     150      ! 
     151   END SUBROUTINE tide_init 
     152 
    41153 
    42154   SUBROUTINE tide_init_Wave 
  • NEMO/branches/2019/dev_r10742_ENHANCE-12_SimonM-Tides/src/OCE/nemogcm.F90

    r10588 r10772  
    4646   USE closea         ! treatment of closed seas (for ln_closea) 
    4747   USE usrdef_nam     ! user defined configuration 
    48    USE tideini        ! tidal components initialization   (tide_ini routine) 
     48   USE tide_mod, ONLY : tide_init ! tidal components initialization   (tide_init routine) 
    4949   USE bdy_oce,  ONLY : ln_bdy 
    5050   USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
Note: See TracChangeset for help on using the changeset viewer.