source: palm/trunk/SOURCE/advec_u_ups.f90 @ 1

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

Initial repository layout and content

File size: 5.6 KB
Line 
1 SUBROUTINE advec_u_ups 
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: advec_u_ups.f90,v $
11! Revision 1.6  2004/04/30 08:03:19  raasch
12! Enlarged transposition arrays introduced
13!
14! Revision 1.5  2003/03/16 09:25:07  raasch
15! Two underscores (_) are placed in front of all define-strings
16!
17! Revision 1.4  2001/03/29 17:35:32  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 04:59:29  raasch
23! Module test_variables removed
24!
25! Revision 1.2  2000/01/20 09:46:52  letzel
26! All comments translated into English
27!
28! Revision 1.1  1999/02/05 08:49:08  raasch
29! Initial revision
30!
31!
32! Description:
33! ------------
34! Upstream-Spline advection of the u velocity-component. The advection process
35! is divided into three subsequent steps, one for each of the dimensions. The
36! results 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 = u at the beginning,
44!        also 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(17), 'advec_u_ups', 'start' )
63
64#if defined( __parallel )
65
66!
67!-- Advection of u in x-direction:
68!-- Store u 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) = u(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!
86!-- Advecting component (d) = component to be advected (v_ad) (variable d is
87!-- used for storage, because it is the only one having suitable dimensions).
88!-- NOTE: here x is the first dimension and lies completely on the PE.
89    d = v_ad - u_gtrans
90
91#else
92
93!
94!-- Advection of u in x-direction:
95!-- Store u in temporary array v_ad (component to be advected)
96    ALLOCATE( v_ad(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
97    v_ad(:,:,:) = u(:,:,:)
98
99!
100!-- Advecting component (d) = component to be advected (u) (variable d is used
101!-- for storage, because it is the only one having suitable dimensions. This is
102!-- done for for reasons of compatibility with the parallel part.)
103    d(:,:,:) = u(nzb+1:nzt,nys:nyn,nxl:nxr) - u_gtrans
104
105#endif
106
107!
108!-- Upstream-Spline advection of u in x-direction. Array tend comes out
109!-- as v_ad before the advection step including cyclic boundaries.
110!-- It is needed for the long filter.
111    CALL spline_x( v_ad, d, 'u' )
112
113!
114!-- Advection of u in y-direction:
115!-- advecting component (v) must be averaged out on the u grid
116    DO  i = nxl, nxr
117       DO  j = nys, nyn
118          DO  k = nzb+1, nzt
119              d(k,j,i) = 0.25 * ( v(k,j,i-1) + v(k,j+1,i-1) + &
120                                  v(k,j,i)   + v(k,j+1,i) ) - v_gtrans
121          ENDDO
122       ENDDO
123    ENDDO
124
125#if defined( __parallel )
126
127!
128!-- Transpose the advecting component: z --> y
129    CALL transpose_zx( d, tend, d, tend, d )
130    CALL transpose_xy( d, tend, d, tend, d )
131
132!
133!-- Transpose the component to be advected: x --> y
134    CALL transpose_xy( v_ad, tend, v_ad, tend, v_ad )
135
136#endif
137
138!
139!-- Upstream-Spline advection of u in y-direction
140    CALL spline_y( v_ad, d, 'u' )
141
142!
143!-- Advection of u in z-direction:
144!-- the advecting component (w) must be averaged out on the u grid
145!-- (weighted for non-equidistant grid)
146    DO  i = nxl, nxr
147       DO  j = nys, nyn
148          DO  k = nzb+1, nzt
149             d(k,j,i) =  ( 0.5 * ( w(k,j,i)   + w(k,j,i-1)   ) * &
150                                 ( zu(k) - zw(k-1) )             &
151                         + 0.5 * ( w(k-1,j,i) + w(k-1,j,i-1) ) * &
152                                 ( zw(k) - zu(k)   )             &
153                         ) * ddzw(k)
154          ENDDO
155       ENDDO
156    ENDDO
157
158#if defined( __parallel )
159
160!
161!-- Transpose the component to be advected: y --> z (= y --> x + x --> z)
162    CALL transpose_yx( v_ad, tend, v_ad, tend, v_ad )
163    CALL transpose_xz( v_ad, tend, v_ad, tend, v_ad )
164
165!
166!-- Resize tend to its normal size
167    IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
168       DEALLOCATE( tend )
169       ALLOCATE( tend(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
170    ENDIF
171
172#endif
173
174!
175!-- Upstream-Spline advection of u in z-direction
176    CALL spline_z( v_ad, d, dzu, spl_tri_zu, 'u' )
177
178!
179!-- Compute the tendency term
180    DO  i = nxl, nxr
181       DO  j = nys, nyn
182          DO  k = nzb+1, nzt
183             tend(k,j,i) = ( v_ad(k,j,i) - u(k,j,i) ) / dt_3d 
184          ENDDO
185       ENDDO
186    ENDDO
187
188    DEALLOCATE( v_ad )
189
190    CALL cpu_log( log_point_s(17), 'advec_u_ups', 'stop' )
191
192 END SUBROUTINE advec_u_ups
Note: See TracBrowser for help on using the repository browser.