source: palm/tags/release-3.9/SOURCE/init_slope.f90 @ 3968

Last change on this file since 3968 was 1037, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 4.4 KB
Line 
1 SUBROUTINE init_slope
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23! Former revisions:
24! -----------------
25! $Id: init_slope.f90 1037 2012-10-22 14:10:22Z suehring $
26!
27! 1036 2012-10-22 13:43:42Z raasch
28! code put under GPL (PALM 3.9)
29!
30! 667 2010-12-23 12:06:00Z suehring/gryschka
31! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
32!
33! 622 2010-12-10 08:08:13Z raasch
34! optional barriers included in order to speed up collective operations
35!
36! Feb. 2007
37! RCS Log replace by Id keyword, revision history cleaned up
38!
39! Revision 1.5  2006/02/23 12:35:34  raasch
40! nanz_2dh renamed ngp_2dh
41!
42! Revision 1.1  2000/04/27 07:06:24  raasch
43! Initial revision
44!
45!
46! Description:
47! ------------
48! Initialization of the temperature field and other variables used in case
49! of a sloping surface.
50! Remember: when a sloping surface is used, only one constant temperature
51!           gradient is allowed!
52!------------------------------------------------------------------------------!
53
54    USE arrays_3d
55    USE constants
56    USE grid_variables
57    USE indices
58    USE pegrid
59    USE control_parameters
60
61    IMPLICIT NONE
62
63    INTEGER ::  i, j, k
64    REAL    ::  alpha, height, pt_value, radius
65    REAL, DIMENSION(:), ALLOCATABLE ::  pt_init_local
66
67!
68!-- Calculate reference temperature field needed for computing buoyancy
69    ALLOCATE( pt_slope_ref(nzb:nzt+1,nxlg:nxrg) )
70
71    DO  i = nxlg, nxrg
72       DO  k = nzb, nzt+1
73
74!
75!--       Compute height of grid-point relative to lower left corner of
76!--       the total domain.
77!--       First compute the distance between the actual grid point and the
78!--       lower left corner as well as the angle between the line connecting
79!--       these points and the bottom of the model.
80          IF ( k /= nzb )  THEN
81             radius = SQRT( ( i * dx )**2 + zu(k)**2 )
82             height = zu(k)
83          ELSE
84             radius = SQRT( ( i * dx )**2 )
85             height = 0.0
86          ENDIF
87          IF ( radius /= 0.0 )  THEN
88             alpha = ASIN( height / radius )
89          ELSE
90             alpha = 0.0
91          ENDIF
92!
93!--       Compute temperatures in the rotated coordinate system
94          alpha    = alpha + alpha_surface / 180.0 * pi
95          pt_value = pt_surface + radius * SIN( alpha ) * &
96                                  pt_vertical_gradient(1) / 100.0
97          pt_slope_ref(k,i) = pt_value
98       ENDDO               
99    ENDDO
100
101!
102!-- Temperature difference between left and right boundary of the total domain,
103!-- used for the cyclic boundary in x-direction
104    pt_slope_offset = (nx+1) * dx * sin_alpha_surface * &
105                      pt_vertical_gradient(1) / 100.0
106
107
108!
109!-- Following action must only be executed for initial runs
110    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
111!
112!--    Set initial temperature equal to the reference temperature field
113       DO  j = nysg, nyng
114          pt(:,j,:) = pt_slope_ref
115       ENDDO
116
117!
118!--    Recompute the mean initial temperature profile (mean along x-direction of
119!--    the rotated coordinate system)
120       ALLOCATE( pt_init_local(nzb:nzt+1) )
121       pt_init_local = 0.0
122       DO  i = nxl, nxr
123          DO  j =  nys, nyn
124             DO  k = nzb, nzt+1
125                pt_init_local(k) = pt_init_local(k) + pt(k,j,i)
126             ENDDO
127          ENDDO
128       ENDDO
129
130#if defined( __parallel )
131       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
132       CALL MPI_ALLREDUCE( pt_init_local, pt_init, nzt+2-nzb, MPI_REAL, &
133                            MPI_SUM, comm2d, ierr )
134#else
135       pt_init = pt_init_local
136#endif
137
138       pt_init = pt_init / ngp_2dh(0)
139       DEALLOCATE( pt_init_local )
140
141    ENDIF
142
143 END SUBROUTINE init_slope
Note: See TracBrowser for help on using the repository browser.