source: palm/trunk/SOURCE/palm.f90 @ 63

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

preliminary update of further changes, advec_particles is not running!

  • Property svn:keywords set to Id
File size: 4.6 KB
Line 
1 PROGRAM palm
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! __vtk directives removed, open unit 9 for debug output
7!
8! Former revisions:
9! -----------------
10! $Id: palm.f90 57 2007-03-09 12:05:41Z raasch $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
13! Revision 1.10  2006/08/04 14:53:12  raasch
14! Distibution of run description header removed, call of header moved behind
15! init_3d_model
16!
17! Revision 1.2  2001/01/25 07:15:06  raasch
18! Program name changed to PALM, module test_variables removed.
19! Initialization of dvrp logging as well as exit of dvrp moved to new
20! subroutines init_dvrp_logging and close_dvrp (file init_dvrp.f90)
21!
22! Revision 1.1  1997/07/24 11:23:35  raasch
23! Initial revision
24!
25!
26! Description:
27! ------------
28! Large-Eddy Simulation (LES) model for the convective boundary layer,
29! optimized for use on parallel machines (implementation realized using the
30! Message Passing Interface (MPI)). The model can also be run on vector machines
31! (less well optimized) and workstations. Versions for the different types of
32! machines are controlled via cpp-directives.
33! Model runs are only feasible using the ksh-script mrun.
34!------------------------------------------------------------------------------!
35
36
37    USE arrays_3d
38    USE constants
39    USE cpulog
40    USE dvrp_variables
41    USE grid_variables
42    USE indices
43    USE interfaces
44    USE model_1d
45    USE particle_attributes
46    USE pegrid
47    USE spectrum
48    USE statistics
49    USE control_parameters
50
51    IMPLICIT NONE
52
53!
54!-- Local variables
55    CHARACTER (LEN=9) ::  time_to_string
56    CHARACTER (LEN=1) ::  cdum
57    INTEGER           ::  i, run_description_header_i(80)
58
59#if defined( __parallel )
60!
61!-- MPI initialisation. comm2d is preliminary set, because
62!-- it will be defined in init_pegrid but is used before in cpu_log.
63    CALL MPI_INIT( ierr )
64    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, numprocs, ierr )
65    comm_palm = MPI_COMM_WORLD
66    comm2d    = MPI_COMM_WORLD
67#endif
68
69!
70!-- Initialize measuring of the CPU-time remaining to the run
71    CALL local_tremain_ini
72
73!
74!-- Start of total CPU time measuring.
75    CALL cpu_log( log_point(1), 'total', 'start' )
76    CALL cpu_log( log_point(2), 'initialisation', 'start' )
77
78!
79!-- Initialize dvrp logging. Also, one PE maybe split from the global
80!-- communicator for doing the dvrp output. In that case, the number of
81!-- PEs available for PALM is reduced by one and communicator comm_palm
82!-- is changed respectively.
83#if defined( __parallel )
84    CALL MPI_COMM_RANK( comm_palm, myid, ierr )
85#endif
86    CALL init_dvrp_logging
87
88!
89!-- Read control parameters from NAMELIST files and read environment-variables
90    CALL parin
91
92!
93!-- Determine processor topology and local array indices
94    CALL init_pegrid
95
96!
97!-- Open a file for debug output
98    OPEN( 9, FILE='DEBUG'//myid_char, FORM='FORMATTED' )
99
100!
101!-- Generate grid parameters
102    CALL init_grid
103
104!
105!-- Check control parameters and deduce further quantities
106    CALL check_parameters
107
108!
109!-- Initialize all necessary variables
110    CALL init_3d_model
111
112!
113!-- Output of program header
114    IF ( myid == 0 )  CALL header
115
116    CALL cpu_log( log_point(2), 'initialisation', 'stop' )
117
118!
119!-- Set start time in format hh:mm:ss
120    simulated_time_chr = time_to_string( simulated_time )
121
122!
123!-- If required, output of initial arrays
124    IF ( do2d_at_begin )  THEN
125       CALL data_output_2d( 'xy', 0 )
126       CALL data_output_2d( 'xz', 0 )
127       CALL data_output_2d( 'yz', 0 )
128    ENDIF
129    IF ( do3d_at_begin )  THEN
130       CALL data_output_3d( 0 )
131    ENDIF
132
133!
134!-- Integration of the model equations using the leap-frog scheme
135    CALL time_integration
136
137!
138!-- If required, write binary data for model continuation runs
139    IF ( write_binary(1:4) == 'true' )  CALL write_3d_binary
140
141!
142!-- If required, write binary particle data
143    CALL write_particles
144
145!
146!-- If required, repeat output of header including the required CPU-time
147    IF ( myid == 0 )  CALL header
148
149!
150!-- If required, final user-defined actions, and
151!-- last actions on the open files and close files. Unit 14 was opened
152!-- in write_3d_binary but it is closed here, to allow writing on this
153!-- unit in routine user_last_actions.
154    CALL cpu_log( log_point(4), 'last actions', 'start' )
155    CALL user_last_actions
156    IF ( write_binary(1:4) == 'true' )  CALL close_file( 14 )
157    CALL close_file( 0 )
158    CALL close_dvrp
159    CALL cpu_log( log_point(4), 'last actions', 'stop' )
160
161!
162!-- Take final CPU-time for CPU-time analysis
163    CALL cpu_log( log_point(1), 'total', 'stop' )
164    CALL cpu_statistics
165
166#if defined( __parallel )
167    CALL MPI_FINALIZE( ierr )
168#endif
169
170 END PROGRAM palm
171
Note: See TracBrowser for help on using the repository browser.