source: palm/trunk/SOURCE/disturb_heatflux.f90 @ 555

Last change on this file since 555 was 555, checked in by raasch, 14 years ago

New:
---

Changed:


Documentation for surface_heatflux in case of prandtl_layer = .F. improved.

bugfix for wrong netcdf/3.6.3 module on lcsgi (mbuild, mrun)

Errors:


Bugfix in if statement (disturb_heatflux)

Bugfix: in 2201 statement: closing " was missing (interpret_config)

Bugfix: default setting of nzb_local for flat topography (init_grid)

Bugfix: wrong dimension used for ts_value_l (user_statistics)

disturb_heatflux, init_grid, interpret_config, user_statistics

  • Property svn:keywords set to Id
File size: 2.0 KB
Line 
1 SUBROUTINE disturb_heatflux
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! Bugfix in if statement
7!
8! Former revisions:
9! -----------------
10! $Id: disturb_heatflux.f90 555 2010-09-07 07:32:53Z raasch $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
13! Revision 1.7  2006/08/04 14:35:07  raasch
14! Additional parameter in function random_gauss which limits the range of the
15! created random numbers, izuf renamed iran
16!
17! Revision 1.1  1998/03/25 20:03:47  raasch
18! Initial revision
19!
20!
21! Description:
22! ------------
23! Generate random, normally distributed heatflux values and store them as the
24! near-surface heatflux.
25! On parallel computers, too, this random generator is called at all grid points
26! of the total array in order to guarantee the same random distribution of the
27! total array regardless of the number of processors used during the model run.
28!------------------------------------------------------------------------------!
29
30    USE arrays_3d
31    USE control_parameters
32    USE cpulog
33    USE grid_variables
34    USE indices
35    USE interfaces
36
37    IMPLICIT NONE
38
39    INTEGER ::  i, j
40    REAL    ::  random_gauss, randomnumber
41
42
43    CALL cpu_log( log_point(23), 'disturb_heatflux', 'start' )
44
45!
46!-- Generate random disturbances and store them
47    DO  i = 0, nx
48       DO  j = 0, ny
49          randomnumber = random_gauss( iran, 5.0 )
50          IF ( nxl <= i  .AND.  nxr >= i  .AND.  nys <= j  .AND.  nyn >= j ) &
51          THEN
52             IF ( nzb_s_inner(j,i) == 0 )  THEN
53                shf(j,i) = randomnumber * surface_heatflux
54             ELSE
55!
56!--             Over topography surface_heatflux is replaced by wall_heatflux(0)
57                shf(j,i) = randomnumber * wall_heatflux(0)
58             ENDIF
59          ENDIF
60       ENDDO
61    ENDDO
62
63!
64!-- Exchange lateral boundary conditions for the heatflux array
65    CALL exchange_horiz_2d( shf )
66
67    CALL cpu_log( log_point(23), 'disturb_heatflux', 'stop' )
68
69
70 END SUBROUTINE disturb_heatflux
Note: See TracBrowser for help on using the repository browser.