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/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/SBC – NEMO

source: NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/SBC/tideini.F90 @ 11671

Last change on this file since 11671 was 11671, checked in by acc, 5 years ago

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Final, non-substantive changes to complete this branch. These changes remove all REWIND statements on the old namelist fortran units (now character variables for internal files). These changes have been left until last since they are easily repeated via a script and it may be preferable to use the previous revision for merge purposes and reapply these last changes separately. This branch has been fully SETTE tested.

  • Property svn:keywords set to Id
File size: 5.7 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 ::   rn_scal_load    !:
36   CHARACTER(lc), PUBLIC ::   cn_tide_load   !:
37
38   INTEGER , PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ntide   !:
39
40   !!----------------------------------------------------------------------
41   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
42   !! $Id$
43   !! Software governed by the CeCILL license (see ./LICENSE)
44   !!----------------------------------------------------------------------
45CONTAINS
46   
47   SUBROUTINE tide_init
48      !!----------------------------------------------------------------------
49      !!                 ***  ROUTINE tide_init  ***
50      !!----------------------------------------------------------------------     
51      INTEGER  :: ji, jk
52      CHARACTER(LEN=4), DIMENSION(jpmax_harmo) :: clname
53      INTEGER  ::   ios                 ! Local integer output status for namelist read
54      !
55      NAMELIST/nam_tide/ln_tide, ln_tide_pot, ln_scal_load, ln_read_load, cn_tide_load, &
56                  &     ln_tide_ramp, rn_scal_load, rdttideramp, clname
57      !!----------------------------------------------------------------------
58      !
59      ! Read Namelist nam_tide
60      READ  ( numnam_ref, nam_tide, IOSTAT = ios, ERR = 901)
61901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nam_tide in reference namelist' )
62      !
63      READ  ( numnam_cfg, nam_tide, IOSTAT = ios, ERR = 902 )
64902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nam_tide in configuration namelist' )
65      IF(lwm) WRITE ( numond, nam_tide )
66      !
67      IF( ln_tide ) THEN
68         IF (lwp) THEN
69            WRITE(numout,*)
70            WRITE(numout,*) 'tide_init : Initialization of the tidal components'
71            WRITE(numout,*) '~~~~~~~~~ '
72            WRITE(numout,*) '   Namelist nam_tide'
73            WRITE(numout,*) '      Use tidal components                       ln_tide      = ', ln_tide
74            WRITE(numout,*) '         Apply astronomical potential            ln_tide_pot  = ', ln_tide_pot
75            WRITE(numout,*) '         Use scalar approx. for load potential   ln_scal_load = ', ln_scal_load
76            WRITE(numout,*) '         Read load potential from file           ln_read_load = ', ln_read_load
77            WRITE(numout,*) '         Apply ramp on tides at startup          ln_tide_ramp = ', ln_tide_ramp
78            WRITE(numout,*) '         Fraction of SSH used in scal. approx.   rn_scal_load = ', rn_scal_load
79            WRITE(numout,*) '         Duration (days) of ramp                 rdttideramp  = ', rdttideramp
80         ENDIF
81      ELSE
82         rn_scal_load = 0._wp 
83
84         IF(lwp) WRITE(numout,*)
85         IF(lwp) WRITE(numout,*) 'tide_init : tidal components not used (ln_tide = F)'
86         IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
87         RETURN
88      ENDIF
89      !
90      CALL tide_init_Wave
91      !
92      nb_harmo=0
93      DO jk = 1, jpmax_harmo
94         DO ji = 1,jpmax_harmo
95            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide )   nb_harmo = nb_harmo + 1
96         END DO
97      END DO
98      !       
99      ! Ensure that tidal components have been set in namelist_cfg
100      IF( nb_harmo == 0 )   CALL ctl_stop( 'tide_init : No tidal components set in nam_tide' )
101      !
102      IF( ln_read_load.AND.(.NOT.ln_tide_pot) ) &
103          &   CALL ctl_stop('ln_read_load requires ln_tide_pot')
104      IF( ln_scal_load.AND.(.NOT.ln_tide_pot) ) &
105          &   CALL ctl_stop('ln_scal_load requires ln_tide_pot')
106      IF( ln_scal_load.AND.ln_read_load ) &
107          &   CALL ctl_stop('Choose between ln_scal_load and ln_read_load')
108      IF( ln_tide_ramp.AND.((nitend-nit000+1)*rdt/rday < rdttideramp) )   &
109         &   CALL ctl_stop('rdttideramp must be lower than run duration')
110      IF( ln_tide_ramp.AND.(rdttideramp<0.) ) &
111         &   CALL ctl_stop('rdttideramp must be positive')
112      !
113      ALLOCATE( ntide(nb_harmo) )
114      DO jk = 1, nb_harmo
115         DO ji = 1, jpmax_harmo
116            IF( TRIM(clname(jk)) == Wave(ji)%cname_tide ) THEN
117               ntide(jk) = ji
118               EXIT
119            ENDIF
120         END DO
121      END DO
122      !
123      ALLOCATE( omega_tide(nb_harmo), v0tide    (nb_harmo),   &
124         &      utide     (nb_harmo), ftide     (nb_harmo)  )
125      kt_tide = nit000
126      !
127      IF (.NOT.ln_scal_load ) rn_scal_load = 0._wp
128      !
129   END SUBROUTINE tide_init
130     
131   !!======================================================================
132END MODULE tideini
Note: See TracBrowser for help on using the repository browser.