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/UKMO/r12083_India_uncoupled/src/OCE/SBC – NEMO

source: NEMO/branches/UKMO/r12083_India_uncoupled/src/OCE/SBC/tideini.F90 @ 12453

Last change on this file since 12453 was 12453, checked in by jcastill, 4 years ago

First implementation of the branch - compiling after merge

File size: 6.2 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   LOGICAL , PUBLIC ::   ln_tide         !:
28   LOGICAL , PUBLIC ::   ln_tide_pot     !:
29   LOGICAL , PUBLIC ::   ln_read_load    !:
30   LOGICAL , PUBLIC ::   ln_scal_load    !:
31   LOGICAL , PUBLIC ::   ln_tide_ramp    !:
32   INTEGER , PUBLIC ::   nb_harmo        !:
33   INTEGER , PUBLIC ::   kt_tide         !:
34   REAL(wp), PUBLIC ::   rdttideramp     !:
35   REAL(wp), PUBLIC ::   dn_love_number  !:
36   REAL(wp), PUBLIC ::   rn_scal_load    !:
37   CHARACTER(lc), PUBLIC ::   cn_tide_load   !:
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 license (see ./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_scal_load, rdttideramp, dn_love_number, 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' )
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' )
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,*) '         Read load potential from file           ln_read_load = ', ln_read_load
80            WRITE(numout,*) '         Apply ramp on tides at startup          ln_tide_ramp = ', ln_tide_ramp
81            WRITE(numout,*) '                                              dn_love_number  = ', dn_love_number
82            WRITE(numout,*) '         Fraction of SSH used in scal. approx.   rn_scal_load = ', rn_scal_load
83            WRITE(numout,*) '         Duration (days) of ramp                 rdttideramp  = ', rdttideramp
84         ENDIF
85      ELSE
86         rn_scal_load = 0._wp 
87
88         IF(lwp) WRITE(numout,*)
89         IF(lwp) WRITE(numout,*) 'tide_init : tidal components not used (ln_tide = F)'
90         IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
91         RETURN
92      ENDIF
93      !
94      CALL tide_init_Wave
95      !
96      nb_harmo=0
97      DO jk = 1, jpmax_harmo
98         DO ji = 1,jpmax_harmo
99            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide )   nb_harmo = nb_harmo + 1
100         END DO
101      END DO
102      !       
103      IF (ln_tide .and.lwp) WRITE(numout,*) '                                     nb_harmo     = ', nb_harmo
104
105      ! Ensure that tidal components have been set in namelist_cfg
106      IF( nb_harmo == 0 )   CALL ctl_stop( 'tide_init : No tidal components set in nam_tide' )
107      !
108      IF( ln_read_load.AND.(.NOT.ln_tide_pot) ) &
109          &   CALL ctl_stop('ln_read_load requires ln_tide_pot')
110      IF( ln_scal_load.AND.(.NOT.ln_tide_pot) ) &
111          &   CALL ctl_stop('ln_scal_load requires ln_tide_pot')
112      IF( ln_scal_load.AND.ln_read_load ) &
113          &   CALL ctl_stop('Choose between ln_scal_load and ln_read_load')
114      IF( ln_tide_ramp.AND.((nitend-nit000+1)*rdt/rday < rdttideramp) )   &
115         &   CALL ctl_stop('rdttideramp must be lower than run duration')
116      IF( ln_tide_ramp.AND.(rdttideramp<0.) ) &
117         &   CALL ctl_stop('rdttideramp must be positive')
118      !
119      ALLOCATE( ntide(nb_harmo) )
120      DO jk = 1, nb_harmo
121         DO ji = 1, jpmax_harmo
122            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide ) THEN
123               ntide(jk) = ji
124               EXIT
125            ENDIF
126         END DO
127      END DO
128      !
129      ALLOCATE( omega_tide(nb_harmo), v0tide    (nb_harmo),   &
130         &      utide     (nb_harmo), ftide     (nb_harmo)  )
131      kt_tide = nit000
132      !
133      IF (.NOT.ln_scal_load ) rn_scal_load = 0._wp
134      !
135   END SUBROUTINE tide_init
136     
137   !!======================================================================
138END MODULE tideini
Note: See TracBrowser for help on using the repository browser.