ROMS
Loading...
Searching...
No Matches
tides_date.F
Go to the documentation of this file.
1#include "cppdefs.h"
2#if !defined ANA_TIDES && \
3 (defined tide_generating_forces || \
4 defined ssh_tides || defined uv_tides)
5 SUBROUTINE tides_date (ng)
6!
7!git $Id$
8!================================================== Hernan G. Arango ===
9! Copyright (c) 2002-2025 The ROMS Group !
10! Licensed under a MIT/X style license !
11! See License_ROMS.md !
12!=======================================================================
13! !
14! This routine checks the input tide reference parameter TIDE_START, !
15! defined as the time of phase zero when preparing the input forcing !
16! tidal boundary data. The tide reference time is important and often !
17! ignored ROMS parameter by users. !
18! !
19! Currently, there are two ways to specify the "tide_start" in an !
20! application: !
21! !
22! (1) Set the "zero_phase_date" variable in the input tidal forcing !
23! NetCDF file (recommended). It a floating-point variable of the !
24! form YYYYMMDD.dddd with the following metadata: !
25! !
26! double zero_phase_date !
27! zero_phase_date:long_name = "tidal reference date for zero phase" !
28! zero_phase_date:units = "days as %Y%m%d.%f" !
29! zero_phase_date:C_format = "%13.4f" !
30! zero_phase_date:FORTRAN_format = "(f13.4)" !
31! !
32! For example, if the tide reference date is 2005-01-01 12:00:00, the !
33! zero_phase_date = 20050101.5000. Again, it corresponds to the zero !
34! tidal phase when preparing the forcing NetCDF file from the tides !
35! dataset (say, OTPS). !
36! !
37! Use "forcing/add_tide_date.m" from the ROMS Matlab repository to !
38! add the "zero_phase_date" variable to your existing tidal forcing !
39! NetCDF file. It is highly recommended to use this approach. If such !
40! a variable is found, the TIDE_START value will overwritten below. !
41! !
42! Notice that it is possible to have different reference values for !
43! "zero_phase_date" and ROMS clock defined as seconds from reference !
44! date (standard input parameter TIME_REF). If "time_ref" is earlier !
45! than "zero_phase_date", the frequencies (omega) to harmonic terms !
46! will be negative since they are computed as follows: !
47! !
48! tide_start = Rclock%tide_DateNumber(2) - !
49! Rclock%DateNumber(2)) !
50! omega = 2 * pi * (time - tide_start) / Tperiod !
51! !
52! Notice that "tide_start" (in seconds) is recomputed and the value !
53! specified in the input standard file is ignored. !
54! !
55! (2) The specify TIDE_START in the ROMS standard input file as days !
56! from the application reference time (TIME_REF) is used it the !
57! variable "zero_phase_date" is not found in the NetCDF file. In !
58! the input standard input file we have: !
59! !
60! TIDE_START = 0.0d0 ! days !
61! TIME_REF = 20050101.5d0 ! yyyymmdd.dd !
62! !
63! Usually, tide_start = 0 implies that the zero-phase's tidal forcing !
64! date is the same as the application reference date "time_ref". ROMS,!
65! does not know how to check if it is the case. Thus, it is assumed !
66! that the user was carefull when configuring his/her application. !
67! !
68!======================================================================!
69!
70 USE mod_param
71 USE mod_parallel
72 USE mod_iounits
73 USE mod_ncparam
74 USE mod_netcdf
75# if defined PIO_LIB && defined DISTRIBUTE
77# endif
78 USE mod_scalars
79!
80 USE dateclock_mod, ONLY : datenum, datestr
81 USE strings_mod, ONLY : founderror
82!
83! Imported variables declarations.
84!
85 integer, intent(in) :: ng
86!
87! Local variables declarations.
88!
89 logical :: foundit
90!
91 integer :: iday, ihour, isec, iyear, minute, month
92!
93 real(dp) :: day, sec, zero_phase_date
94!
95 character (len=19) :: string
96 character (len=*), parameter :: MyFile = &
97 & __FILE__
98!
99!-----------------------------------------------------------------------
100! Check if "zero_phase_date" variable is available in input tidal
101! forcing file.
102!-----------------------------------------------------------------------
103!
104 IF (ng.eq.1) THEN
105 IF (idtref.eq.0) THEN
106 IF (master) WRITE (stdout,10) 'idTref', trim(varname)
107 exit_flag=5
108 RETURN
109 END IF
110 END IF
111!
112 SELECT CASE (tide(1)%IOtype)
113 CASE (io_nf90)
114 CALL netcdf_inq_var (ng, inlm, tide(ng)%name, &
115 & myvarname = vname(1,idtref), &
116 & searchvar = foundit)
117 IF (foundit) THEN
118 CALL netcdf_get_fvar (ng, inlm, tide(ng)%name, &
119 & vname(1,idtref), &
120 & zero_phase_date)
121 END IF
122
123# if defined PIO_LIB && defined DISTRIBUTE
124 CASE (io_pio)
125 CALL pio_netcdf_inq_var (ng, inlm, tide(ng)%name, &
126 & myvarname = vname(1,idtref), &
127 & searchvar = foundit)
128 IF (foundit) THEN
129 CALL pio_netcdf_get_fvar (ng, inlm, tide(ng)%name, &
130 & vname(1,idtref), &
131 & zero_phase_date)
132 END IF
133# endif
134 END SELECT
135 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
136!
137! If found "zero_phase_date", decode from YYYYMMDD.dddd and compute
138! datenum. Overwrite given "TIDE_START".
139!
140 IF (foundit) THEN
141 iyear=max(1,int(zero_phase_date*0.0001_dp))
142 month=min(12,max(1,int((zero_phase_date- &
143 & real(iyear*10000,dp))*0.01_dp)))
144 day=zero_phase_date-aint(zero_phase_date*0.01_dp)*100.0_dp
145 iday=max(1,int(day))
146 sec=(day-aint(day))*86400.0_dp
147 ihour=int(sec/3600.0_dp)
148 minute=int(mod(sec,3600.0_dp)/60.0_dp)
149 isec=int(mod(sec,60.0_dp))
150 CALL datenum (rclock%tide_DateNumber, iyear, month, iday, &
151 & ihour, minute, real(isec,dp))
152 CALL datestr (rclock%tide_DateNumber(1), .true., string)
153!
154 IF (master) THEN
155 WRITE (stdout,20) 'zero_phase_date = ', zero_phase_date, &
156 & trim(tide(ng)%name), &
157 & 'tide_DateNumber = ', &
158 & rclock%tide_DateNumber(1), trim(string), &
159 & 'old tide_start = ', tide_start, &
160 & ' (days)', &
161 & 'new tide_start = ', &
162 & rclock%tide_DateNumber(1)- &
163 & rclock%DateNumber(1), ' (days)'
164 END IF
165 tide_start=rclock%tide_DateNumber(1)-rclock%DateNumber(1)
166!
167! Otherwise, compute datenum from "tide_start" and "time_ref".
168!
169 ELSE
170 rclock%tide_DateNumber(1)=rclock%DateNumber(1)+ &
171 & tide_start
172 rclock%tide_DateNumber(2)=rclock%DateNumber(2)+ &
174 CALL datestr (rclock%tide_DateNumber(1), .true., string)
175!
176 IF (master) THEN
177 WRITE (stdout,30) 'zero_phase_date', trim(tide(ng)%name), &
178 & 'given tide_start = ', tide_start, &
179 & ' (days)', &
180 & 'tide_DateNumber = ', &
181 & rclock%tide_DateNumber(1), trim(string)
182 END IF
183 END IF
184!
185 10 FORMAT (/,' TIDES_DATE - Variable index not yet loaded, ', a, &
186 & /,14x,'Update your metadata file: ',a)
187 20 FORMAT (/,2x,'TIDES_DATE - Checking tidal reference date for ', &
188 & 'zero phase: ',/,17x,a,f13.4,' (read from ',a,')', &
189 & /,17x,a,f13.4,' (',a,')',/,17x,a,f13.4,a,/,17x,a,f13.4,a)
190 30 FORMAT (/,2x,'TIDE_DATE - Checking tidal reference date for ', &
191 & 'zero phase: ',/,17x,'''',a,''' variable not found in: ', &
192 & a,/,17x,a,f13.4,a,/,17x,a,f13.4,' (',a,')')
193!
194 RETURN
195 END SUBROUTINE tides_date
196#else
197 SUBROUTINE tides_date
198 END SUBROUTINE tides_date
199#endif
subroutine, public datestr(datenumber, isdayunits, datestring)
Definition dateclock.F:447
subroutine, public datenum(datenumber, year, month, day, hour, minutes, seconds)
Definition dateclock.F:243
type(t_io), dimension(:), allocatable tide
integer stdout
character(len=256) varname
integer, parameter io_nf90
Definition mod_ncparam.F:95
integer, parameter io_pio
Definition mod_ncparam.F:96
character(len=maxlen), dimension(6, 0:nv) vname
integer idtref
subroutine, public netcdf_inq_var(ng, model, ncname, ncid, myvarname, searchvar, varid, nvardim, nvaratt)
logical master
integer, parameter inlm
Definition mod_param.F:662
subroutine, public pio_netcdf_inq_var(ng, model, ncname, piofile, myvarname, searchvar, piovar, nvardim, nvaratt)
real(dp), parameter day2sec
type(t_clock) rclock
integer exit_flag
integer noerror
real(dp) tide_start
logical function, public founderror(flag, noerr, line, routine)
Definition strings.F:52