ROMS
Loading...
Searching...
No Matches
ana_spinning.h
Go to the documentation of this file.
1!!
2 SUBROUTINE ana_spinning (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 time-variable rotation force as the sum of !
12! Coriolis and Centripetal accelerations. This is used in polar !
13! coordinate applications (annulus grid). !
14! !
15!=======================================================================
16!
17 USE mod_param
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_spinning_tile (ng, tile, model, &
33 & lbi, ubi, lbj, ubj, &
34 & imins, imaxs, jmins, jmaxs, &
35#ifdef SPHERICAL
36 & grid(ng) % lonr, &
37 & grid(ng) % latr, &
38#else
39 & grid(ng) % xr, &
40 & grid(ng) % yr, &
41#endif
42 & grid(ng) % f, &
43 & grid(ng) % omn, &
44 & grid(ng) % fomn)
45!
46! Set analytical header file name used.
47!
48#ifdef DISTRIBUTE
49 IF (lanafile) THEN
50#else
51 IF (lanafile.and.(tile.eq.0)) THEN
52#endif
53 ananame(26)=myfile
54 END IF
55!
56 RETURN
57 END SUBROUTINE ana_spinning
58!
59!***********************************************************************
60 SUBROUTINE ana_spinning_tile (ng, tile, model, &
61 & LBi, UBi, LBj, UBj, &
62 & IminS, ImaxS, JminS, JmaxS, &
63#ifdef SPHERICAL
64 & lonr, latr &
65#else
66 & xr, yr, &
67#endif
68 & f, omn, fomn)
69!***********************************************************************
70!
71 USE mod_param
72 USE mod_scalars
73!
74! Imported variable declarations.
75!
76 integer, intent(in) :: ng, tile, model
77 integer, intent(in) :: LBi, UBi, LBj, UBj
78 integer, intent(in) :: IminS, ImaxS, JminS, JmaxS
79!
80#ifdef ASSUMED_SHAPE
81 real(r8), intent(in) :: f(LBi:,LBj:)
82 real(r8), intent(in) :: omn(LBi:,LBj:)
83# ifdef SPHERICAL
84 real(r8), intent(in) :: lonr(LBi:,LBj:)
85 real(r8), intent(in) :: latr(LBi:,LBj:)
86# else
87 real(r8), intent(in) :: xr(LBi:,LBj:)
88 real(r8), intent(in) :: yr(LBi:,LBj:)
89# endif
90 real(r8), intent(out) :: fomn(LBi:,LBj:)
91#else
92 real(r8), intent(in) :: f(LBi:UBi,LBj:UBj)
93 real(r8), intent(in) :: omn(LBi:UBi,LBj:UBj)
94# ifdef SPHERICAL
95 real(r8), intent(in) :: lonr(LBi:UBi,LBj:UBj)
96 real(r8), intent(in) :: latr(LBi:UBi,LBj:UBj)
97# else
98 real(r8), intent(in) :: xr(LBi:UBi,LBj:UBj)
99 real(r8), intent(in) :: yr(LBi:UBi,LBj:UBj)
100# endif
101 real(r8), intent(out) :: fomn(LBi:UBi,LBj:UBj)
102#endif
103!
104! Local variable declarations.
105!
106#ifdef LAB_CANYON
107 real(r8), parameter :: Omega0 = 2.0_r8*pi/25.0_r8
108 real(r8), parameter :: Width = 0.20_r8
109 real(r8), parameter :: Ro = 0.10_r8
110 real(r8), parameter :: Rs = 0.55_r8
111 real(r8), parameter :: little_omega = 2.0_r8*pi/24.0_r8
112 real(r8), parameter :: Bu = 10.0_r8
113 real(r8), parameter :: hd = 0.125_r8
114
115 real(r8) :: Omega1, Omega1_of_t, Ro_t
116 real(r8) :: fcor, d_rho_dz, d_Omega1_dt, time_fac
117#endif
118
119#include "set_bounds.h"
120!
121!-----------------------------------------------------------------------
122! Compute time-varying rotation force: Coriolis plus Centripetal
123! accelerations.
124!-----------------------------------------------------------------------
125!
126#ifdef LAB_CANYON
127 fcor=2.0_r8*omega0
128 omega1=fcor*width*ro/rs
129 ro_t=little_omega/fcor
130 d_rho_dz=(1000.0_r8*bu/g)*(fcor*width/hd)**2
131 time_fac=1.0_r8+(omega1/omega0)*sin(little_omega*time(ng))
132 omega1_of_t=omega1*sin(little_omega*time(ng))
133 d_omega1_dt=omega1*little_omega*cos(little_omega*time(ng))
134!
135 DO j=jstrt,jendt
136 DO i=istrt,iendt
137 fomn(i,j)=(f(i,j)*time_fac+ &
138 & sqrt(xr(i,j)*xr(i,j)+yr(i,j)*yr(i,j))* &
139 & ((2.0_r8*omega0+omega1_of_t)*omega1_of_t))* &
140 & omn(i,j)
141 END DO
142 END DO
143#endif
144!
145 RETURN
146 END SUBROUTINE ana_spinning_tile
subroutine ana_spinning(ng, tile, model)
Definition ana_spinning.h:3
subroutine ana_spinning_tile(ng, tile, model, lbi, ubi, lbj, ubj, imins, imaxs, jmins, jmaxs, lonr, latr xr, yr, f, omn, fomn)
type(t_grid), dimension(:), allocatable grid
Definition mod_grid.F:365
logical lanafile
character(len=256), dimension(39) ananame
real(dp) g
real(dp), dimension(:), allocatable time
real(dp), parameter pi