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 trunk/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/SBC/tideini.F90 @ 5009

Last change on this file since 5009 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

File size: 4.6 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
11   USE daymod
12   USE dynspg_oce
13   USE tide_mod
14   !
15   USE iom
16   USE in_out_manager  ! I/O units
17   USE ioipsl          ! NetCDF IPSL library
18   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
19
20   IMPLICIT NONE
21   PUBLIC
22
23   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   omega_tide   !:
24   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   v0tide       !:
25   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   utide        !:
26   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ftide        !:
27
28   LOGICAL , PUBLIC ::   ln_tide_pot     !:
29   LOGICAL , PUBLIC ::   ln_tide_ramp    !:
30   INTEGER , PUBLIC ::   nb_harmo                 !:
31   INTEGER , PUBLIC ::   kt_tide                  !:
32   REAL(wp), PUBLIC ::   rdttideramp              !:
33   
34   INTEGER , PUBLIC, ALLOCATABLE, DIMENSION(:) ::   ntide   !:
35
36   !!----------------------------------------------------------------------
37   !! NEMO/OPA 3.5 , NEMO Consortium (2013)
38   !! $Id: $
39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41CONTAINS
42   
43  SUBROUTINE tide_init ( kt )
44    !!----------------------------------------------------------------------
45    !!                 ***  ROUTINE tide_init  ***
46    !!----------------------------------------------------------------------     
47    !! * Local declarations
48    INTEGER  :: ji, jk
49    INTEGER, INTENT( in ) ::   kt     ! ocean time-step
50    CHARACTER(LEN=4), DIMENSION(jpmax_harmo) :: clname
51    INTEGER  ::   ios                 ! Local integer output status for namelist read
52    !
53    NAMELIST/nam_tide/ln_tide_pot, ln_tide_ramp, rdttideramp, clname
54    !!----------------------------------------------------------------------
55
56    IF ( kt == nit000 ) THEN
57       !
58       IF(lwp) THEN
59          WRITE(numout,*)
60          WRITE(numout,*) 'tide_init : Initialization of the tidal components'
61          WRITE(numout,*) '~~~~~~~~~ '
62       ENDIF
63       !
64       CALL tide_init_Wave
65       !
66       ! Read Namelist nam_tide
67       REWIND( numnam_ref )              ! Namelist nam_tide in reference namelist : Tides
68       READ  ( numnam_ref, nam_tide, IOSTAT = ios, ERR = 901)
69901    IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_tide in reference namelist', lwp )
70
71       REWIND( numnam_cfg )              ! Namelist nam_tide in configuration namelist : Tides
72       READ  ( numnam_cfg, nam_tide, IOSTAT = ios, ERR = 902 )
73902    IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_tide in configuration namelist', lwp )
74       IF(lwm) WRITE ( numond, nam_tide )
75       !
76       nb_harmo=0
77       DO jk = 1, jpmax_harmo
78          DO ji = 1,jpmax_harmo
79             IF( TRIM(clname(jk)) == Wave(ji)%cname_tide )   nb_harmo = nb_harmo + 1
80          END DO
81       END DO
82       !
83       IF(lwp) THEN
84          WRITE(numout,*) '   Namelist nam_tide'
85          WRITE(numout,*) '      Apply astronomical potential : ln_tide_pot  =', ln_tide_pot
86          WRITE(numout,*) '                                     nb_harmo     = ', nb_harmo
87          WRITE(numout,*) '                                     ln_tide_ramp = ', ln_tide_ramp 
88          WRITE(numout,*) '                                     rdttideramp  = ', rdttideramp
89       ENDIF
90       IF( ln_tide_ramp.AND.((nitend-nit000+1)*rdt/rday < rdttideramp) )   &
91          &   CALL ctl_stop('rdttideramp must be lower than run duration')
92       IF( ln_tide_ramp.AND.(rdttideramp<0.) ) &
93          &   CALL ctl_stop('rdttideramp must be positive')
94       !
95       IF( .NOT. lk_dynspg_ts )   CALL ctl_warn( 'sbc_tide : use of time splitting is recommended' )
96       !
97       ALLOCATE( ntide(nb_harmo) )
98       DO jk = 1, nb_harmo
99          DO ji = 1, jpmax_harmo
100             IF( TRIM(clname(jk)) .eq. Wave(ji)%cname_tide ) THEN
101                ntide(jk) = ji
102                EXIT
103             END IF
104          END DO
105       END DO
106       !
107       ALLOCATE( omega_tide(nb_harmo), v0tide    (nb_harmo),   &
108          &      utide     (nb_harmo), ftide     (nb_harmo)  )
109       kt_tide = kt
110       !
111      ENDIF
112      !
113   END SUBROUTINE tide_init
114     
115   !!======================================================================
116END MODULE tideini
Note: See TracBrowser for help on using the repository browser.