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.
tideini.F90 in NEMO/branches/2018/dev_r9838_ENHANCE04_MLF/src/OCE/SBC – NEMO

source: NEMO/branches/2018/dev_r9838_ENHANCE04_MLF/src/OCE/SBC/tideini.F90 @ 9923

Last change on this file since 9923 was 9923, checked in by gm, 6 years ago

#1911 (ENHANCE-04): step I.2: dev_r9838_ENHANCE04_MLF

  • Property svn:keywords set to Id
File size: 6.3 KB
Line 
1MODULE tideini
2   !!======================================================================
3   !!                       ***  MODULE  tideini  ***
4   !! Initialization of tidal forcing
5   !!======================================================================
6   !! History :  1.0  !  2007  (O. Le Galloudec)  Original code
7   !!----------------------------------------------------------------------
8   USE oce            ! ocean dynamics and tracers variables
9   USE dom_oce        ! ocean space and time domain
10   USE phycst         ! physical constants
11   USE daymod         ! calendar
12   USE tide_mod       !
13   !
14   USE in_out_manager ! I/O units
15   USE iom            ! xIOs server
16   USE ioipsl         ! NetCDF IPSL library
17   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
18
19   IMPLICIT NONE
20   PUBLIC
21
22   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   omega_tide   !:
23   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   v0tide       !:
24   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   utide        !:
25   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ftide        !:
26
27   !                                        !!* nam_tide namelist *
28   LOGICAL , PUBLIC ::   ln_tide             !: Use tidal components
29   LOGICAL , PUBLIC ::   ln_tide_pot         !: Apply astronomical potential
30   LOGICAL , PUBLIC ::   ln_read_load        !: Read load potential from file
31   CHARACTER(lc), PUBLIC ::   cn_tide_load      !: associated file name
32   LOGICAL , PUBLIC ::   ln_scal_load        !: Use a scalar approximation for load potential
33   REAL(wp), PUBLIC ::      rn_load             !: SSH fraction used in scalar approximation
34   LOGICAL , PUBLIC ::   ln_tide_ramp        !: Apply ramp on tides at startup
35   REAL(wp), PUBLIC ::      rn_ramp             !: Duration of ramp [days]
36   INTEGER , PUBLIC ::   nb_harmo            !: number of tidal harmonique used
37   INTEGER , PUBLIC ::   kt_tide             !: ???
38
39   INTEGER , PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ntide   !: ???
40
41   !!----------------------------------------------------------------------
42   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
43   !! $Id$
44   !! Software governed by the CeCILL licence     (./LICENSE)
45   !!----------------------------------------------------------------------
46CONTAINS
47   
48   SUBROUTINE tide_init
49      !!----------------------------------------------------------------------
50      !!                 ***  ROUTINE tide_init  ***
51      !!----------------------------------------------------------------------     
52      INTEGER  :: ji, jk
53      CHARACTER(LEN=4), DIMENSION(jpmax_harmo) :: clname
54      INTEGER  ::   ios                 ! Local integer output status for namelist read
55      !!
56      NAMELIST/nam_tide/ln_tide, ln_tide_pot, ln_scal_load, ln_read_load, cn_tide_load, &
57                  &     ln_tide_ramp, rn_load, rn_ramp, clname
58      !!----------------------------------------------------------------------
59      !
60      ! Read Namelist nam_tide
61      REWIND( numnam_ref )              ! Namelist nam_tide in reference namelist : Tides
62      READ  ( numnam_ref, nam_tide, IOSTAT = ios, ERR = 901)
63901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nam_tide in reference namelist', lwp )
64      !
65      REWIND( numnam_cfg )              ! Namelist nam_tide in configuration namelist : Tides
66      READ  ( numnam_cfg, nam_tide, IOSTAT = ios, ERR = 902 )
67902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nam_tide in configuration namelist', lwp )
68      IF(lwm) WRITE ( numond, nam_tide )
69      !
70      IF( ln_tide ) THEN
71         IF (lwp) THEN
72            WRITE(numout,*)
73            WRITE(numout,*) 'tide_init : Initialization of the tidal components'
74            WRITE(numout,*) '~~~~~~~~~ '
75            WRITE(numout,*) '   Namelist nam_tide'
76            WRITE(numout,*) '      Use tidal components                       ln_tide      = ', ln_tide
77            WRITE(numout,*) '         Apply astronomical potential            ln_tide_pot  = ', ln_tide_pot
78            WRITE(numout,*) '         Use scalar approx. for load potential   ln_scal_load = ', ln_scal_load
79            WRITE(numout,*) '            SSH fraction used in scal. approx.      rn_load   = ', rn_load
80            WRITE(numout,*) '         Read load potential from file           ln_read_load = ', ln_read_load
81            WRITE(numout,*) '         Apply ramp on tides at startup          ln_tide_ramp = ', ln_tide_ramp
82            WRITE(numout,*) '         Duration of ramp                           rn_ramp   = ', rn_ramp, ' [days]'
83         ENDIF
84      ELSE
85         rn_load = 0._wp 
86         !
87         IF(lwp) WRITE(numout,*)
88         IF(lwp) WRITE(numout,*) 'tide_init : tidal components not used (ln_tide = F)'
89         IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
90         RETURN
91      ENDIF
92      !
93      CALL tide_init_Wave
94      !
95      nb_harmo = 0
96      DO jk = 1, jpmax_harmo
97         DO ji = 1,jpmax_harmo
98            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide )   nb_harmo = nb_harmo + 1
99         END DO
100      END DO
101      !       
102      ! Ensure that tidal components have been set in namelist_cfg
103      IF( nb_harmo == 0 )   CALL ctl_stop( 'tide_init : No tidal components set in nam_tide' )
104      !
105      IF( ln_read_load.AND.(.NOT.ln_tide_pot) ) &
106          &   CALL ctl_stop('ln_read_load requires ln_tide_pot')
107      IF( ln_scal_load.AND.(.NOT.ln_tide_pot) ) &
108          &   CALL ctl_stop('ln_scal_load requires ln_tide_pot')
109      IF( ln_scal_load.AND.ln_read_load ) &
110          &   CALL ctl_stop('Choose between ln_scal_load and ln_read_load')
111      IF( ln_tide_ramp.AND.((nitend-nit000+1)*rn_Dt/rday < rn_ramp) )   &
112         &   CALL ctl_stop('rn_ramp must be lower than run duration')
113      IF( ln_tide_ramp.AND.(rn_ramp<0.) ) &
114         &   CALL ctl_stop('rn_ramp must be positive')
115      !
116      ALLOCATE( ntide(nb_harmo) )
117      DO jk = 1, nb_harmo
118         DO ji = 1, jpmax_harmo
119            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide ) THEN
120               ntide(jk) = ji
121               EXIT
122            ENDIF
123         END DO
124      END DO
125      !
126      ALLOCATE( omega_tide(nb_harmo), v0tide(nb_harmo),   &
127         &      utide     (nb_harmo), ftide (nb_harmo)  )
128      kt_tide = nit000
129      !
130      IF (.NOT.ln_scal_load )   rn_load = 0._wp
131      !
132   END SUBROUTINE tide_init
133     
134   !!======================================================================
135END MODULE tideini
Note: See TracBrowser for help on using the repository browser.