source: palm/trunk/SOURCE/advec_v_ups.f90 @ 1

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 5.3 KB
Line 
1 SUBROUTINE advec_v_ups
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: advec_v_ups.f90,v $
11! Revision 1.7  2004/04/30 08:03:52  raasch
12! Enlarged transposition arrays introduced
13!
14! Revision 1.6  2003/03/16 09:25:59  raasch
15! Two underscores (_) are placed in front of all define-strings
16!
17! Revision 1.5  2001/03/29 17:36:43  raasch
18! v_ad is now allocated locally, several temporary arrays removed from
19! argument lists of spline_* and long_filter_*
20! Translation of remaining German identifiers (variables, subroutines, etc.)
21!
22! Revision 1.4  2001/01/22 08:31:10  raasch
23! Module test_variables removed
24!
25!
26! Revision 1.2  2000/01/20 09:52:54  letzel
27! All comments translated into English
28!
29! Revision 1.1  1999/02/05 08:50:32  raasch
30! Initial revision
31!
32!
33! Description:
34! ------------
35! Upstream-Spline advection of the v velocity-component. The advection process
36! is divided into three subsequent steps, one for each of the dimensions. The
37! result is stored as a tendency in array tend. The computation of the cubic
38! splines and the possible execution of the Long-filter require that all grid
39! points of the relevant dimension are available. For model runs on more than
40! one PE therefore both the advected and the advecting quantities are
41! transposed accordingly.
42!
43! Internally used arrays:
44! v_ad = scalar quantity to be advected, initialised = v at the beginning,
45!        also being used as temporary storage after each time step
46! d    = advecting component (u, v, or w)
47!------------------------------------------------------------------------------!
48
49    USE advection
50    USE arrays_3d
51    USE cpulog
52    USE grid_variables
53    USE indices
54    USE interfaces
55    USE control_parameters
56
57    IMPLICIT NONE
58
59    INTEGER ::  i, j, k
60    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  v_ad
61
62
63    CALL cpu_log( log_point_s(18), 'advec_v_ups', 'start' )
64
65#if defined( __parallel )
66
67!
68!-- Advection of v in x-direction:
69!-- Store v in temporary array v_ad (component to be advected, boundaries
70!-- are not used because they disturb the transposition)
71    ALLOCATE( v_ad(nzb+1:nzta,nys:nyna,nxl:nxra) )
72    v_ad = 0.0
73    v_ad(nzb+1:nzt,nys:nyn,nxl:nxr) = v(nzb+1:nzt,nys:nyn,nxl:nxr)
74
75!
76!-- Enlarge the size of tend, used as a working array for the transpositions
77    IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
78       DEALLOCATE( tend )
79       ALLOCATE( tend(1:nza,nys:nyna,nxl:nxra) )
80    ENDIF
81
82!
83!-- Transpose the component to be advected: z --> x
84    CALL transpose_zx( v_ad, tend, v_ad, tend, v_ad )
85
86#else
87
88!
89!-- Advection of v in x-direction:
90!-- Store v in temporary array v_ad (component to be advected)
91    ALLOCATE( v_ad(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
92    v_ad(:,:,:) = v(:,:,:)
93
94#endif
95
96!
97!-- Advecting component (u) must be averaged out on the v grid
98    d = 0.0
99    DO  i = nxl, nxr
100       DO  j = nys, nyn
101          DO  k = nzb+1, nzt
102             d(k,j,i) = 0.25 * ( u(k,j-1,i) + u(k,j-1,i+1) + &
103                                 u(k,j,i+1) + u(k,j,i) ) - u_gtrans
104          ENDDO
105       ENDDO
106    ENDDO
107
108#if defined( __parallel )
109
110!
111!-- Transpose the advecting component: z --> x
112    CALL transpose_zx( d, tend, d, tend, d )
113
114#endif
115
116!
117!-- Upstream-Spline advection of v in x-direction. Array tend comes out
118!-- as v_ad before the advection step including cyclic boundaries.
119!-- It is needed for the long filter.
120    CALL spline_x( v_ad, d, 'v' )
121
122!
123!-- Advection of v in y-direction:
124!-- advecting component (d) = component to be advected (v)
125    d(nzb+1:nzt,nys:nyn,nxl:nxr) = v(nzb+1:nzt,nys:nyn,nxl:nxr) - v_gtrans
126
127#if defined( __parallel )
128
129!
130!-- Transpose the advecting component: z --> y
131    CALL transpose_zx( d, tend, d, tend, d )
132    CALL transpose_xy( d, tend, d, tend, d )
133
134!
135!-- Transpose the component to be advected: x --> y
136    CALL transpose_xy( v_ad, tend, v_ad, tend, v_ad )
137
138#endif
139
140!
141!-- Upstream-Spline advection of v in y-direction
142    CALL spline_y( v_ad, d, 'v' )
143
144!
145!-- Advection of v in z-direction:
146!-- the advecting component (w) must be averaged out on the v grid
147!-- (weighted for non-equidistant grid)
148    DO  i = nxl, nxr
149       DO  j = nys, nyn
150          DO  k = nzb+1, nzt
151             d(k,j,i) =  ( 0.5 * ( w(k-1,j-1,i) + w(k-1,j,i) ) * &
152                                 ( zw(k) - zu(k) ) + &
153                           0.5 * ( w(k,j,i) + w(k,j-1,i) ) * &
154                                 ( zu(k) - zw(k-1) ) &
155                         ) * ddzw(k)
156          ENDDO
157       ENDDO
158    ENDDO
159
160#if defined( __parallel )
161   
162!
163!-- Transpose the component to be advected: y --> z (= y --> x + x --> z)
164    CALL transpose_yx( v_ad, tend, v_ad, tend, v_ad )
165    CALL transpose_xz( v_ad, tend, v_ad, tend, v_ad )
166
167!
168!-- Resize tend to its normal size
169    IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
170       DEALLOCATE( tend )
171       ALLOCATE( tend(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
172    ENDIF
173
174#endif
175
176!
177!-- Upstream-Spline advection of v in z-direction
178    CALL spline_z( v_ad, d, dzu, spl_tri_zu, 'v' )
179
180!
181!-- Compute the tendency term
182    DO  i = nxl, nxr
183       DO  j = nys, nyn
184          DO  k = nzb+1, nzt
185             tend(k,j,i) = ( v_ad(k,j,i) - v(k,j,i) ) / dt_3d 
186          ENDDO
187       ENDDO
188    ENDDO
189
190    DEALLOCATE( v_ad )
191
192    CALL cpu_log( log_point_s(18), 'advec_v_ups', 'stop' )
193
194 END SUBROUTINE advec_v_ups
Note: See TracBrowser for help on using the repository browser.