source: palm/trunk/SOURCE/init_slope.f90 @ 1036

Last change on this file since 1036 was 1036, checked in by raasch, 12 years ago

code has been put under the GNU General Public License (v3)

  • Property svn:keywords set to Id
File size: 4.3 KB
RevLine 
[1]1 SUBROUTINE init_slope
2
[1036]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!
[484]20! Current revisions:
[1]21! -----------------
22!
23! Former revisions:
24! -----------------
[3]25! $Id: init_slope.f90 1036 2012-10-22 13:43:42Z raasch $
[623]26!
[668]27! 667 2010-12-23 12:06:00Z suehring/gryschka
28! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
29!
[623]30! 622 2010-12-10 08:08:13Z raasch
31! optional barriers included in order to speed up collective operations
32!
33! Feb. 2007
[3]34! RCS Log replace by Id keyword, revision history cleaned up
35!
[1]36! Revision 1.5  2006/02/23 12:35:34  raasch
37! nanz_2dh renamed ngp_2dh
38!
39! Revision 1.1  2000/04/27 07:06:24  raasch
40! Initial revision
41!
42!
43! Description:
44! ------------
45! Initialization of the temperature field and other variables used in case
46! of a sloping surface.
47! Remember: when a sloping surface is used, only one constant temperature
48!           gradient is allowed!
[3]49!------------------------------------------------------------------------------!
[1]50
51    USE arrays_3d
52    USE constants
53    USE grid_variables
54    USE indices
55    USE pegrid
56    USE control_parameters
57
58    IMPLICIT NONE
59
60    INTEGER ::  i, j, k
61    REAL    ::  alpha, height, pt_value, radius
62    REAL, DIMENSION(:), ALLOCATABLE ::  pt_init_local
63
64!
65!-- Calculate reference temperature field needed for computing buoyancy
[667]66    ALLOCATE( pt_slope_ref(nzb:nzt+1,nxlg:nxrg) )
[1]67
[667]68    DO  i = nxlg, nxrg
[1]69       DO  k = nzb, nzt+1
70
71!
72!--       Compute height of grid-point relative to lower left corner of
73!--       the total domain.
74!--       First compute the distance between the actual grid point and the
75!--       lower left corner as well as the angle between the line connecting
76!--       these points and the bottom of the model.
77          IF ( k /= nzb )  THEN
78             radius = SQRT( ( i * dx )**2 + zu(k)**2 )
79             height = zu(k)
80          ELSE
81             radius = SQRT( ( i * dx )**2 )
82             height = 0.0
83          ENDIF
84          IF ( radius /= 0.0 )  THEN
85             alpha = ASIN( height / radius )
86          ELSE
87             alpha = 0.0
88          ENDIF
89!
90!--       Compute temperatures in the rotated coordinate system
91          alpha    = alpha + alpha_surface / 180.0 * pi
92          pt_value = pt_surface + radius * SIN( alpha ) * &
93                                  pt_vertical_gradient(1) / 100.0
94          pt_slope_ref(k,i) = pt_value
95       ENDDO               
96    ENDDO
97
98!
99!-- Temperature difference between left and right boundary of the total domain,
100!-- used for the cyclic boundary in x-direction
101    pt_slope_offset = (nx+1) * dx * sin_alpha_surface * &
102                      pt_vertical_gradient(1) / 100.0
103
104
105!
106!-- Following action must only be executed for initial runs
107    IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
108!
109!--    Set initial temperature equal to the reference temperature field
[667]110       DO  j = nysg, nyng
[1]111          pt(:,j,:) = pt_slope_ref
112       ENDDO
113
114!
115!--    Recompute the mean initial temperature profile (mean along x-direction of
116!--    the rotated coordinate system)
117       ALLOCATE( pt_init_local(nzb:nzt+1) )
118       pt_init_local = 0.0
119       DO  i = nxl, nxr
120          DO  j =  nys, nyn
121             DO  k = nzb, nzt+1
122                pt_init_local(k) = pt_init_local(k) + pt(k,j,i)
123             ENDDO
124          ENDDO
[622]125       ENDDO
[1]126
127#if defined( __parallel )
[622]128       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
129       CALL MPI_ALLREDUCE( pt_init_local, pt_init, nzt+2-nzb, MPI_REAL, &
130                            MPI_SUM, comm2d, ierr )
[1]131#else
[622]132       pt_init = pt_init_local
[1]133#endif
134
[622]135       pt_init = pt_init / ngp_2dh(0)
136       DEALLOCATE( pt_init_local )
[1]137
[622]138    ENDIF
[1]139
140 END SUBROUTINE init_slope
Note: See TracBrowser for help on using the repository browser.