source: palm/tags/release-3.2a/SOURCE/advec_v_ups.f90 @ 2318

Last change on this file since 2318 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.9 KB
Line 
1 SUBROUTINE advec_v_ups
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: advec_v_ups.f90 4 2007-02-13 11:33:16Z suehring $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
13! Revision 1.7  2004/04/30 08:03:52  raasch
14! Enlarged transposition arrays introduced
15!
16! Revision 1.1  1999/02/05 08:50:32  raasch
17! Initial revision
18!
19!
20! Description:
21! ------------
22! Upstream-Spline advection of the v 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 = v at the beginning,
32!        also 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(18), 'advec_v_ups', 'start' )
51
52#if defined( __parallel )
53
54!
55!-- Advection of v in x-direction:
56!-- Store v 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) = v(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 v in x-direction:
77!-- Store v 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(:,:,:) = v(:,:,:)
80
81#endif
82
83!
84!-- Advecting component (u) must be averaged out on the v 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-1,i) + u(k,j-1,i+1) + &
90                                 u(k,j,i+1) + u(k,j,i) ) - u_gtrans
91          ENDDO
92       ENDDO
93    ENDDO
94
95#if defined( __parallel )
96
97!
98!-- Transpose the advecting component: z --> x
99    CALL transpose_zx( d, tend, d, tend, d )
100
101#endif
102
103!
104!-- Upstream-Spline advection of v 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, 'v' )
108
109!
110!-- Advection of v in y-direction:
111!-- advecting component (d) = component to be advected (v)
112    d(nzb+1:nzt,nys:nyn,nxl:nxr) = v(nzb+1:nzt,nys:nyn,nxl:nxr) - v_gtrans
113
114#if defined( __parallel )
115
116!
117!-- Transpose the advecting component: z --> y
118    CALL transpose_zx( d, tend, d, tend, d )
119    CALL transpose_xy( d, tend, d, tend, d )
120
121!
122!-- Transpose the component to be advected: x --> y
123    CALL transpose_xy( v_ad, tend, v_ad, tend, v_ad )
124
125#endif
126
127!
128!-- Upstream-Spline advection of v in y-direction
129    CALL spline_y( v_ad, d, 'v' )
130
131!
132!-- Advection of v in z-direction:
133!-- the advecting component (w) must be averaged out on the v grid
134!-- (weighted for non-equidistant grid)
135    DO  i = nxl, nxr
136       DO  j = nys, nyn
137          DO  k = nzb+1, nzt
138             d(k,j,i) =  ( 0.5 * ( w(k-1,j-1,i) + w(k-1,j,i) ) * &
139                                 ( zw(k) - zu(k) ) + &
140                           0.5 * ( w(k,j,i) + w(k,j-1,i) ) * &
141                                 ( zu(k) - zw(k-1) ) &
142                         ) * ddzw(k)
143          ENDDO
144       ENDDO
145    ENDDO
146
147#if defined( __parallel )
148   
149!
150!-- Transpose the component to be advected: y --> z (= y --> x + x --> z)
151    CALL transpose_yx( v_ad, tend, v_ad, tend, v_ad )
152    CALL transpose_xz( v_ad, tend, v_ad, tend, v_ad )
153
154!
155!-- Resize tend to its normal size
156    IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
157       DEALLOCATE( tend )
158       ALLOCATE( tend(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
159    ENDIF
160
161#endif
162
163!
164!-- Upstream-Spline advection of v in z-direction
165    CALL spline_z( v_ad, d, dzu, spl_tri_zu, 'v' )
166
167!
168!-- Compute the tendency term
169    DO  i = nxl, nxr
170       DO  j = nys, nyn
171          DO  k = nzb+1, nzt
172             tend(k,j,i) = ( v_ad(k,j,i) - v(k,j,i) ) / dt_3d 
173          ENDDO
174       ENDDO
175    ENDDO
176
177    DEALLOCATE( v_ad )
178
179    CALL cpu_log( log_point_s(18), 'advec_v_ups', 'stop' )
180
181 END SUBROUTINE advec_v_ups
Note: See TracBrowser for help on using the repository browser.