source: palm/trunk/SOURCE/advec_v_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.9 KB
Line 
1 SUBROUTINE advec_v_ups
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: advec_v_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.7  2004/04/30 08:03:52  raasch
19! Enlarged transposition arrays introduced
20!
21! Revision 1.1  1999/02/05 08:50:32  raasch
22! Initial revision
23!
24!
25! Description:
26! ------------
27! Upstream-Spline advection of the v 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 = v at the beginning,
37!        also 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(18), 'advec_v_ups', 'start' )
56
57#if defined( __parallel )
58
59!
60!-- Advection of v in x-direction:
61!-- Store v 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) = v(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 v in x-direction:
82!-- Store v 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(:,:,:) = v(:,:,:)
85
86#endif
87
88!
89!-- Advecting component (u) must be averaged out on the v 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-1,i) + u(k,j-1,i+1) + &
95                                 u(k,j,i+1) + u(k,j,i) ) - u_gtrans
96          ENDDO
97       ENDDO
98    ENDDO
99
100#if defined( __parallel )
101
102!
103!-- Transpose the advecting component: z --> x
104    CALL transpose_zx( d, tend, d )
105
106#endif
107
108!
109!-- Upstream-Spline advection of v 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, 'v' )
113
114!
115!-- Advection of v in y-direction:
116!-- advecting component (d) = component to be advected (v)
117    d(nzb+1:nzt,nys:nyn,nxl:nxr) = v(nzb+1:nzt,nys:nyn,nxl:nxr) - v_gtrans
118
119#if defined( __parallel )
120
121!
122!-- Transpose the advecting component: z --> y
123    CALL transpose_zx( d, tend, d )
124    CALL transpose_xy( d, tend, d )
125
126!
127!-- Transpose the component to be advected: x --> y
128    CALL transpose_xy( v_ad, tend, v_ad )
129
130#endif
131
132!
133!-- Upstream-Spline advection of v in y-direction
134    CALL spline_y( v_ad, d, 'v' )
135
136!
137!-- Advection of v in z-direction:
138!-- the advecting component (w) must be averaged out on the v grid
139!-- (weighted for non-equidistant grid)
140    DO  i = nxl, nxr
141       DO  j = nys, nyn
142          DO  k = nzb+1, nzt
143             d(k,j,i) =  ( 0.5 * ( w(k-1,j-1,i) + w(k-1,j,i) ) * &
144                                 ( zw(k) - zu(k) ) + &
145                           0.5 * ( w(k,j,i) + w(k,j-1,i) ) * &
146                                 ( zu(k) - zw(k-1) ) &
147                         ) * ddzw(k)
148          ENDDO
149       ENDDO
150    ENDDO
151
152#if defined( __parallel )
153   
154!
155!-- Transpose the component to be advected: y --> z (= y --> x + x --> z)
156    CALL transpose_yx( v_ad, tend, v_ad )
157    CALL transpose_xz( v_ad, tend, v_ad )
158
159!
160!-- Resize tend to its normal size
161    IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
162       DEALLOCATE( tend )
163       ALLOCATE( tend(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
164    ENDIF
165
166#endif
167
168!
169!-- Upstream-Spline advection of v in z-direction
170    CALL spline_z( v_ad, d, dzu, spl_tri_zu, 'v' )
171
172!
173!-- Compute the tendency term
174    DO  i = nxl, nxr
175       DO  j = nys, nyn
176          DO  k = nzb+1, nzt
177             tend(k,j,i) = ( v_ad(k,j,i) - v(k,j,i) ) / dt_3d 
178          ENDDO
179       ENDDO
180    ENDDO
181
182    DEALLOCATE( v_ad )
183
184    CALL cpu_log( log_point_s(18), 'advec_v_ups', 'stop' )
185
186 END SUBROUTINE advec_v_ups
Note: See TracBrowser for help on using the repository browser.