ROMS
Loading...
Searching...
No Matches
ana_wwave.h
Go to the documentation of this file.
1!!
2 SUBROUTINE ana_wwave (ng, tile, model)
3!
4!! git $Id$
5!!======================================================================
6!! Copyright (c) 2002-2025 The ROMS Group !
7!! Licensed under a MIT/X style license !
8!! See License_ROMS.md !
9!=======================================================================
10! !
11! This subroutine sets wind induced wave amplitude, direction and !
12! period to be used in the bottom boundary layer formulation. !
13! !
14!=======================================================================
15!
16 USE mod_param
17 USE mod_forces
18 USE mod_grid
19 USE mod_ncparam
20!
21! Imported variable declarations.
22!
23 integer, intent(in) :: ng, tile, model
24!
25! Local variable declarations.
26!
27 character (len=*), parameter :: MyFile = &
28 & __FILE__
29!
30#include "tile.h"
31!
32 CALL ana_wwave_tile (ng, tile, model, &
33 & lbi, ubi, lbj, ubj, &
34 & imins, imaxs, jmins, jmaxs, &
35#ifdef WAVES_DIR
36 & forces(ng) % Dwave, &
37#endif
38#ifdef WAVES_HEIGHT
39 & forces(ng) % Hwave, &
40#endif
41#ifdef WAVES_LENGTH
42 & forces(ng) % Lwave, &
43#endif
44#ifdef WAVES_TOP_PERIOD
45 & forces(ng) % Pwave_top, &
46#endif
47#ifdef WAVES_BOT_PERIOD
48 & forces(ng) % Pwave_bot, &
49#endif
50#ifdef WAVES_UB
51 & forces(ng) % Uwave_rms, &
52#endif
53 & grid(ng) % angler, &
54 & grid(ng) % h)
55!
56! Set analytical header file name used.
57!
58#ifdef DISTRIBUTE
59 IF (lanafile) THEN
60#else
61 IF (lanafile.and.(tile.eq.0)) THEN
62#endif
63 ananame(37)=myfile
64 END IF
65!
66 RETURN
67 END SUBROUTINE ana_wwave
68!
69!***********************************************************************
70 SUBROUTINE ana_wwave_tile (ng, tile, model, &
71 & LBi, UBi, LBj, UBj, &
72 & IminS, ImaxS, JminS, JmaxS, &
73#ifdef WAVES_DIR
74 & Dwave, &
75#endif
76#ifdef WAVES_HEIGHT
77 & Hwave, &
78#endif
79#ifdef WAVES_LENGTH
80 & Lwave, &
81#endif
82#ifdef WAVES_TOP_PERIOD
83 & Pwave_top, &
84#endif
85#ifdef WAVES_BOT_PERIOD
86 & Pwave_bot, &
87#endif
88#ifdef WAVES_UB
89 & Uwave_rms, &
90#endif
91 & angler, h)
92!***********************************************************************
93!
94 USE mod_param
95 USE mod_scalars
96!
98#ifdef DISTRIBUTE
100#endif
101!
102! Imported variable declarations.
103!
104 integer, intent(in) :: ng, tile, model
105 integer, intent(in) :: LBi, UBi, LBj, UBj
106 integer, intent(in) :: IminS, ImaxS, JminS, JmaxS
107!
108#ifdef ASSUMED_SHAPE
109 real(r8), intent(in) :: angler(LBi:,LBj:)
110 real(r8), intent(in) :: h(LBi:,LBj:)
111# ifdef WAVES_DIR
112 real(r8), intent(inout) :: Dwave(LBi:,LBj:)
113# endif
114# ifdef WAVES_HEIGHT
115 real(r8), intent(inout) :: Hwave(LBi:,LBj:)
116# endif
117# ifdef WAVES_LENGTH
118 real(r8), intent(inout) :: Lwave(LBi:,LBj:)
119# endif
120# ifdef WAVES_TOP_PERIOD
121 real(r8), intent(inout) :: Pwave_top(LBi:,LBj:)
122# endif
123# ifdef WAVES_BOT_PERIOD
124 real(r8), intent(inout) :: Pwave_bot(LBi:,LBj:)
125# endif
126# ifdef WAVES_UB
127 real(r8), intent(inout) :: Uwave_rms(LBi:,LBj:)
128# endif
129
130#else
131
132 real(r8), intent(in) :: angler(LBi:UBi,LBj:UBj)
133 real(r8), intent(in) :: h(LBi:UBi,LBj:UBj)
134# ifdef WAVES_DIR
135 real(r8), intent(inout) :: Dwave(LBi:UBi,LBj:UBj)
136# endif
137# ifdef WAVES_HEIGHT
138 real(r8), intent(inout) :: Hwave(LBi:UBi,LBj:UBj)
139# endif
140# ifdef WAVES_LENGTH
141 real(r8), intent(inout) :: Lwave(LBi:UBi,LBj:UBj)
142# endif
143# ifdef WAVES_TOP_PERIOD
144 real(r8), intent(inout) :: Pwave_top(LBi:UBi,LBj:UBj)
145# endif
146# ifdef WAVES_BOT_PERIOD
147 real(r8), intent(inout) :: Pwave_bot(LBi:UBi,LBj:UBj)
148# endif
149# ifdef WAVES_UB
150 real(r8), intent(inout) :: Uwave_rms(LBi:UBi,LBj:UBj)
151# endif
152#endif
153!
154! Local variable declarations.
155!
156 integer :: i, j
157!
158 real(r8) :: cff, wdir
159#if defined LAKE_SIGNELL
160 real(r8) :: cff1, mxst, ramp_u, ramp_time, ramp_d
161#endif
162
163#include "set_bounds.h"
164!
165!-----------------------------------------------------------------------
166! Set wind induced wave amplitude (m), direction (radians) and
167! period (s) at RHO-points.
168!-----------------------------------------------------------------------
169!
170#if defined BL_TEST
171 wdir=210.0_r8*deg2rad
172 DO j=jstrt,jendt
173 DO i=istrt,iendt
174# ifdef WAVES_DIR
175 dwave(i,j)=wdir
176# endif
177# ifdef WAVES_HEIGHT
178 hwave(i,j)=0.5_r8
179# endif
180# ifdef WAVES_BOT_PERIOD
181 pwave_bot(i,j)=8.0_r8
182# endif
183 END DO
184 END DO
185#elif defined LAKE_SIGNELL
186 mxst=0.25_r8 ! Wave amplitude (1/2 wave height) (meters)
187 ramp_u=15.0_r8 ! start ramp UP at RAMP_UP (hours)
188 ramp_time=10.0_r8 ! ramp from 0 to 1 over RAMP_TIME (hours)
189 ramp_d=50.0_r8 ! start ramp DOWN at RAMP_DOWN (hours)
190 DO j=jstrt,jendt
191 DO i=istrt,iendt
192# ifdef WAVES_DIR
193 dwave(i,j)=270.0_r8*deg2rad
194# endif
195# ifdef WAVES_HEIGHT
196 hwave(i,j)=max((cff1*mxst),0.01_r8)
197# endif
198# ifdef WAVES_BOT_PERIOD
199 pwave_bot(i,j)=5.0_r8 ! wave period (seconds)
200 cff1=min((0.5_r8*(tanh((time(ng)/3600.0_r8-ramp_u)/ &
201 & (ramp_time/5.0_r8))+1.0_r8)), &
202 & (1.0_r8-(0.5_r8*(tanh((time(ng)/3600.0_r8-ramp_d)/ &
203 & (ramp_time/5.0_r8))+1.0_r8))))
204# endif
205 END DO
206 END DO
207#elif defined NJ_BIGHT
208!! wdir=210.0_r8*deg2rad
209 wdir=150.0_r8*deg2rad
210 IF ((tdays(ng)-dstart).lt.1.5_r8) THEN
211 cff=tanh(0.5_r8*(tdays(ng)-dstart))
212 cff=1.0_r8
213 ELSE
214 cff=1.0_r8
215 END IF
216 DO j=jstrt,jendt
217 DO i=istrt,iendt
218# ifdef WAVES_DIR
219 dwave(i,j)=wdir-angler(i,j)
220# endif
221# ifdef WAVES_HEIGHT
222 hwave(i,j)=0.12_r8
223# endif
224# ifdef WAVES_BOT_PERIOD
225 pwave_bot(i,j)=10.0_r8
226# endif
227 END DO
228 END DO
229#elif defined SED_TOY
230 DO j=jstrt,jendt
231 DO i=istrt,iendt
232# ifdef WAVES_DIR
233 dwave(i,j)=90.0_r8*deg2rad
234# endif
235# ifdef WAVES_HEIGHT
236 hwave(i,j)=2.0_r8
237# endif
238# ifdef WAVES_LENGTH
239 lwave(i,j)=20.0_r8
240# endif
241# ifdef WAVES_BOT_PERIOD
242 pwave_bot(i,j)=8.0_r8
243# endif
244 END DO
245 END DO
246#else
247 ana_wwave: no values provided for hwave, dwave, pwave, lwave.
248#endif
249!
250! Exchange boundary data.
251!
252#if defined WAVES_DIR
253 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
254 CALL exchange_r2d_tile (ng, tile, &
255 & lbi, ubi, lbj, ubj, &
256 & dwave)
257 END IF
258# ifdef DISTRIBUTE
259 CALL mp_exchange2d (ng, tile, model, 1, &
260 & lbi, ubi, lbj, ubj, &
261 & nghostpoints, &
262 & ewperiodic(ng), nsperiodic(ng), &
263 & dwave)
264# endif
265#endif
266
267#ifdef WAVES_HEIGHT
268 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
269 CALL exchange_r2d_tile (ng, tile, &
270 & lbi, ubi, lbj, ubj, &
271 & hwave)
272 END IF
273# ifdef DISTRIBUTE
274 CALL mp_exchange2d (ng, tile, model, 1, &
275 & lbi, ubi, lbj, ubj, &
276 & nghostpoints, &
277 & ewperiodic(ng), nsperiodic(ng), &
278 & hwave)
279# endif
280#endif
281
282#ifdef WAVES_LENGTH
283 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
284 CALL exchange_r2d_tile (ng, tile, &
285 & lbi, ubi, lbj, ubj, &
286 & lwave)
287 END IF
288# ifdef DISTRIBUTE
289 CALL mp_exchange2d (ng, tile, model, 1, &
290 & lbi, ubi, lbj, ubj, &
291 & nghostpoints, &
292 & ewperiodic(ng), nsperiodic(ng), &
293 & lwave)
294# endif
295#endif
296
297#ifdef WAVES_TOP_PERIOD
298 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
299 CALL exchange_r2d_tile (ng, tile, &
300 & lbi, ubi, lbj, ubj, &
301 & pwave_top)
302 END IF
303# ifdef DISTRIBUTE
304 CALL mp_exchange2d (ng, tile, model, 1, &
305 & lbi, ubi, lbj, ubj, &
306 & nghostpoints, &
307 & ewperiodic(ng), nsperiodic(ng), &
308 & pwave_top)
309# endif
310#endif
311
312#ifdef WAVES_BOT_PERIOD
313 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
314 CALL exchange_r2d_tile (ng, tile, &
315 & lbi, ubi, lbj, ubj, &
316 & pwave_bot)
317 END IF
318# ifdef DISTRIBUTE
319 CALL mp_exchange2d (ng, tile, model, 1, &
320 & lbi, ubi, lbj, ubj, &
321 & nghostpoints, &
322 & ewperiodic(ng), nsperiodic(ng), &
323 & pwave_bot)
324# endif
325#endif
326
327#ifdef WAVES_UB
328 IF (ewperiodic(ng).or.nsperiodic(ng)) THEN
329 CALL exchange_r2d_tile (ng, tile, &
330 & lbi, ubi, lbj, ubj, &
331 & uwave_rms)
332 END IF
333# ifdef DISTRIBUTE
334 CALL mp_exchange2d (ng, tile, model, 1, &
335 & lbi, ubi, lbj, ubj, &
336 & nghostpoints, &
337 & ewperiodic(ng), nsperiodic(ng), &
338 & uwave_rms)
339# endif
340#endif
341!
342 RETURN
343 END SUBROUTINE ana_wwave_tile
subroutine ana_wwave(ng, tile, model)
Definition ana_wwave.h:3
subroutine ana_wwave_tile(ng, tile, model, lbi, ubi, lbj, ubj, imins, imaxs, jmins, jmaxs, dwave, hwave, lwave, pwave_top, pwave_bot, uwave_rms, angler, h)
Definition ana_wwave.h:92
subroutine exchange_r2d_tile(ng, tile, lbi, ubi, lbj, ubj, a)
type(t_forces), dimension(:), allocatable forces
Definition mod_forces.F:554
type(t_grid), dimension(:), allocatable grid
Definition mod_grid.F:365
logical lanafile
character(len=256), dimension(39) ananame
integer nghostpoints
Definition mod_param.F:710
logical, dimension(:), allocatable ewperiodic
logical, dimension(:), allocatable nsperiodic
real(dp), dimension(:), allocatable tdays
real(dp) dstart
real(dp), parameter deg2rad
real(dp), dimension(:), allocatable time
subroutine mp_exchange2d(ng, tile, model, nvar, lbi, ubi, lbj, ubj, nghost, ew_periodic, ns_periodic, a, b, c, d)