source: palm/tags/release-3.4/SOURCE/advec_w_ups.f90 @ 232

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

Id keyword set as property for all *.f90 files

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