source: palm/trunk/SOURCE/advec_s_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.5 KB
Line 
1 SUBROUTINE advec_s_ups( s, var_char )
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: advec_s_ups.f90,v $
11! Revision 1.6  2004/04/30 08:02:43  raasch
12! Enlarged transposition arrays introduced
13!
14! Revision 1.5  2003/03/16 09:23:56  raasch
15! Two underscores (_) are placed in front of all define-strings
16!
17! Revision 1.4  2001/03/29 17:34:05  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:46:10  raasch
23! Module test_variables removed
24!
25! Revision 1.2  2000/01/20 09:28:52  letzel
26! All comments translated into English
27!
28! Revision 1.1  1999/02/05 08:44:47  raasch
29! Initial revision
30!
31!
32! Description:
33! ------------
34! Upstream-Spline advection of scalar quantities (potential temperature,
35! turbulent kinetic energy). The advection process is divided into three
36! subsequent steps, one for each of the dimensions. The result is stored as a
37! tendency in array tend. The computation of the cubic splines and the possible
38! execution of the Long-filter require that all grid points of the relevant
39! dimension are available. For model runs on more than one PE therefore both the
40! advected and the advecting quantities are transposed accordingly.
41!
42! Actual arguments:
43! s        = scalar quantity to be advected (remains unchanged in this UP)
44! var_char = character string specifying the quantity to be advected
45!
46! Internally used arrays:
47! v_ad     = scalar quantity to be advected, initialized = s at the beginning,
48!            also being used as temporary storage after each time step
49! d        = advecting component (u, v, or w)
50!------------------------------------------------------------------------------!
51
52    USE advection
53    USE arrays_3d
54    USE cpulog
55    USE grid_variables
56    USE indices
57    USE interfaces
58    USE control_parameters
59
60    IMPLICIT NONE
61
62    CHARACTER (LEN=*) ::  var_char
63
64    INTEGER ::  i, j, k
65    REAL    ::  s(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
66    REAL, DIMENSION(:,:,:), ALLOCATABLE ::  v_ad
67
68    CALL cpu_log( log_point_s(16), 'advec_s_ups', 'start' )
69
70#if defined( __parallel )
71
72!
73!-- Advection of the scalar in x-direction:
74!-- Store the scalar in temporary array v_ad (component to be advected,
75!-- boundaries are not used because they disturb the transposition)
76    ALLOCATE( v_ad(nzb+1:nzta,nys:nyna,nxl:nxra) )
77    v_ad = 0.0
78    v_ad(nzb+1:nzt,nys:nyn,nxl:nxr) = s(nzb+1:nzt,nys:nyn,nxl:nxr)
79
80!
81!-- Enlarge the size of tend, used as a working array for the transpositions
82    IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
83       DEALLOCATE( tend )
84       ALLOCATE( tend(1:nza,nys:nyna,nxl:nxra) )
85    ENDIF
86
87!
88!-- Transpose the component to be advected: z --> x
89    CALL transpose_zx( v_ad, tend, v_ad, tend, v_ad )
90
91#else
92
93!
94!-- Advection of the scalar in x-direction:
95!-- Store the scalar 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(:,:,:) = s(:,:,:)
98
99#endif
100
101!
102!-- Advecting component (u) must be averaged out on the scalar's grid
103    DO  i = nxl, nxr
104       DO  j = nys, nyn
105          DO  k = nzb+1, nzt
106              d(k,j,i) = 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - u_gtrans
107          ENDDO
108       ENDDO
109    ENDDO
110
111#if defined( __parallel )
112
113!
114!-- Transpose the advecting componnet: z --> x
115    CALL transpose_zx( d, tend, d, tend, d )
116
117#endif
118
119!
120!-- Upstream-Spline advection of the scalar in x-direction
121    CALL spline_x( v_ad, d, var_char )
122
123!
124!-- Advection of the scalar in y-direction:
125!-- advecting component (v) must be averaged out on the scalar's grid
126    DO  i = nxl, nxr
127       DO  j = nys, nyn
128          DO  k = nzb+1, nzt
129              d(k,j,i) = 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - v_gtrans
130          ENDDO
131       ENDDO
132    ENDDO
133
134#if defined( __parallel )
135   
136!
137!-- Transpose the advecting component: z --> y
138    CALL transpose_zx( d, tend, d, tend, d )
139    CALL transpose_xy( d, tend, d, tend, d )
140
141!
142!-- Transpose the component to be advected: x --> y
143    CALL transpose_xy( v_ad, tend, v_ad, tend, v_ad )
144
145#endif
146
147!
148!-- Upstream-Spline advection of the scalar in y-direction
149    CALL spline_y( v_ad, d, var_char )
150
151!
152!-- Advection of the scalar in z-direction:
153!-- the advecting component (w) must be averaged out on the scalar's grid
154!-- (weighted for non-equidistant grid)
155    d = 0.0
156    DO  i = nxl, nxr
157       DO  j = nys, nyn
158          DO  k = nzb+1, nzt
159             d(k,j,i) =  ( w(k,j,i) * ( zu(k) - zw(k-1) ) + &
160                           w(k-1,j,i) * ( zw(k) - zu(k) ) ) * ddzw(k)
161          ENDDO
162       ENDDO
163    ENDDO
164
165#if defined( __parallel )
166
167!
168!-- Transpose the component to be advected: y --> z (= y --> x + x --> z)
169    CALL transpose_yx( v_ad, tend, v_ad, tend, v_ad )
170    CALL transpose_xz( v_ad, tend, v_ad, tend, v_ad )
171
172!
173!-- Resize tend to its normal size
174    IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
175       DEALLOCATE( tend )
176       ALLOCATE( tend(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
177    ENDIF
178
179#endif
180
181!
182!-- Upstream-Spline advection of the scalar in z-direction
183    CALL spline_z( v_ad, d, dzu, spl_tri_zu, var_char )
184
185!
186!-- Compute the tendency term
187    DO  i = nxl, nxr
188       DO  j = nys, nyn
189          DO  k = nzb+1, nzt
190             tend(k,j,i) = ( v_ad(k,j,i) - s(k,j,i) ) / dt_3d 
191          ENDDO
192       ENDDO
193    ENDDO
194
195    DEALLOCATE( v_ad )
196
197    CALL cpu_log( log_point_s(16), 'advec_s_ups', 'stop' )
198
199 END SUBROUTINE advec_s_ups
Note: See TracBrowser for help on using the repository browser.