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 branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SBC/tideini.F90 @ 11101

Last change on this file since 11101 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 4.9 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          IF(lflush) CALL flush(numout)
63       ENDIF
64       !
65       CALL tide_init_Wave
66       !
67       ! Read Namelist nam_tide
68       REWIND( numnam_ref )              ! Namelist nam_tide in reference namelist : Tides
69       READ  ( numnam_ref, nam_tide, IOSTAT = ios, ERR = 901)
70901    IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_tide in reference namelist', lwp )
71
72       REWIND( numnam_cfg )              ! Namelist nam_tide in configuration namelist : Tides
73       READ  ( numnam_cfg, nam_tide, IOSTAT = ios, ERR = 902 )
74902    IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_tide in configuration namelist', lwp )
75       IF(lwm .AND. nprint > 2) WRITE ( numond, nam_tide )
76       !
77       nb_harmo=0
78       DO jk = 1, jpmax_harmo
79          DO ji = 1,jpmax_harmo
80             IF( TRIM(clname(jk)) == Wave(ji)%cname_tide )   nb_harmo = nb_harmo + 1
81          END DO
82       END DO
83       !       
84       ! Ensure that tidal components have been set in namelist_cfg
85       IF( nb_harmo .EQ. 0 ) CALL ctl_stop( 'tide_init : No tidal components set in nam_tide' )
86       !
87       IF(lwp) THEN
88          WRITE(numout,*) '   Namelist nam_tide'
89          WRITE(numout,*) '      Apply astronomical potential : ln_tide_pot  =', ln_tide_pot
90          WRITE(numout,*) '                                     nb_harmo     = ', nb_harmo
91          WRITE(numout,*) '                                     ln_tide_ramp = ', ln_tide_ramp 
92          WRITE(numout,*) '                                     rdttideramp  = ', rdttideramp
93          IF(lflush) CALL flush(numout)
94       ENDIF
95       IF( ln_tide_ramp.AND.((nitend-nit000+1)*rdt/rday < rdttideramp) )   &
96          &   CALL ctl_stop('rdttideramp must be lower than run duration')
97       IF( ln_tide_ramp.AND.(rdttideramp<0.) ) &
98          &   CALL ctl_stop('rdttideramp must be positive')
99       !
100       IF( .NOT. lk_dynspg_ts )   CALL ctl_warn( 'sbc_tide : use of time splitting is recommended' )
101       !
102       ALLOCATE( ntide(nb_harmo) )
103       DO jk = 1, nb_harmo
104          DO ji = 1, jpmax_harmo
105             IF( TRIM(clname(jk)) .eq. Wave(ji)%cname_tide ) THEN
106                ntide(jk) = ji
107                EXIT
108             END IF
109          END DO
110       END DO
111       !
112       ALLOCATE( omega_tide(nb_harmo), v0tide    (nb_harmo),   &
113          &      utide     (nb_harmo), ftide     (nb_harmo)  )
114       kt_tide = kt
115       !
116      ENDIF
117      !
118   END SUBROUTINE tide_init
119     
120   !!======================================================================
121END MODULE tideini
Note: See TracBrowser for help on using the repository browser.