source: palm/trunk/SOURCE/advec_w_ups.f90 @ 2

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

Initial repository layout and content

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