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

Last change on this file since 550 was 484, checked in by raasch, 14 years ago

typo in file headers removed

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