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

Last change on this file since 2 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 6.3 KB
Line 
1#if defined( __vtk )
2 SUBROUTINE palm
3#else
4 PROGRAM palm
5#endif
6
7!------------------------------------------------------------------------------!
8! Actual revisions:
9! -----------------
10! TEST: open(9)
11!
12! Former revisions:
13! -----------------
14! $Log: palm.f90,v $
15! Revision 1.10  2006/08/04 14:53:12  raasch
16! Distibution of run description header removed, call of header moved behind
17! init_3d_model
18!
19! Revision 1.9  2006/02/23 12:44:43  raasch
20! plot_.. renamed data_output_..
21!
22! Revision 1.8  2004/04/30 12:31:07  raasch
23! Missing cpp-instructions added, leap_frog changed to time_integration
24!
25! Revision 1.7  2003/05/09 14:46:49  raasch
26! String converted to integer before send via broadcast due to Linux MPICH
27! problem
28!
29! Revision 1.6  2003/03/16 09:42:17  raasch
30! Two underscores (_) are placed in front of all define-strings
31!
32! Revision 1.5  2002/12/19 15:53:59  raasch
33! Routine local_tremain_ini moved from init_3d_model to here
34!
35! Revision 1.4  2001/08/21 09:53:35  raasch
36! comm_palm is now used as the global communicator since one PE maybe split from
37! MPI_COMM_WORLD for usage in dvrp-graphics
38!
39! Revision 1.3  2001/03/30 07:39:41  raasch
40! Translation of remaining German identifiers (variables, subroutines, etc.),
41! closing of unit 14 moved from routine write_3d_binary to this routine
42!
43! Revision 1.2  2001/01/25 07:15:06  raasch
44! Program name changed to PALM, module test_variables removed.
45! Initialization of dvrp logging as well as exit of dvrp moved to new
46! subroutines init_dvrp_logging and close_dvrp (file init_dvrp.f90)
47!
48! Revision 1.23  2001/01/05 15:13:51  raasch
49! +module spectrum
50!
51! Revision 1.22  2001/01/02 17:32:55  raasch
52! Subroutine close_files renamed to close_file, now called with an argument
53!
54! Revision 1.21  2000/12/28 13:32:16  raasch
55! Call of MPI_FINALIZE moved to the end of the program. At the beginning
56! comm2d is set to MPI_COMM_WORLD (it was undefined before).
57! Call of write_particles at the end. Open and close of DVRP-Software at the
58! beginning and at the end (optionally, by cpp-directives)
59!
60! Revision 1.20  2000/04/27 06:42:43  raasch
61! closing call to dvrp-software (if used) at the end of the run,
62! old revision remarks deleted
63!
64! Revision 1.19  2000/01/25 15:29:23  letzel
65! All comments translated into English
66!
67! Revision 1.18  1999/11/25 16:27:49  raasch
68! Bei Benutzung von VTK-Grafik wird Modell als UP in C++ - Programm eingebunden
69!
70! Revision 1.1  1997/07/24 11:23:35  raasch
71! Initial revision
72!
73!
74! Description:
75! ------------
76! Large-Eddy Simulation (LES) model for the convective boundary layer,
77! optimized for use on parallel machines (implementation realized using the
78! Message Passing Interface (MPI)). The model can also be run on vector machines
79! (less well optimized) and workstations. Versions for the different types of
80! machines are controlled via cpp-directives.
81! Model runs are only feasible using the ksh-script mrun.
82!------------------------------------------------------------------------------!
83
84
85    USE arrays_3d
86    USE constants
87    USE cpulog
88    USE dvrp_variables
89    USE grid_variables
90    USE indices
91    USE interfaces
92    USE model_1d
93    USE particle_attributes
94    USE pegrid
95    USE spectrum
96    USE statistics
97    USE control_parameters
98
99    IMPLICIT NONE
100
101!
102!-- Local variables
103    CHARACTER (LEN=9) ::  time_to_string
104    CHARACTER (LEN=1) ::  cdum
105    INTEGER           ::  i, run_description_header_i(80)
106
107#if defined( __parallel )
108!
109!-- MPI initialisation. comm2d is preliminary set, because
110!-- it will be defined in init_pegrid but is used before in cpu_log.
111    CALL MPI_INIT( ierr )
112    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, numprocs, ierr )
113    comm_palm = MPI_COMM_WORLD
114    comm2d    = MPI_COMM_WORLD
115#endif
116
117!
118!-- Initialize measuring of the CPU-time remaining to the run
119    CALL local_tremain_ini
120
121!
122!-- Start of total CPU time measuring.
123    CALL cpu_log( log_point(1), 'total', 'start' )
124    CALL cpu_log( log_point(2), 'initialisation', 'start' )
125
126!
127!-- Initialize dvrp logging. Also, one PE maybe split from the global
128!-- communicator for doing the dvrp output. In that case, the number of
129!-- PEs available for PALM is reduced by one and communicator comm_palm
130!-- is changed respectively.
131#if defined( __parallel )
132    CALL MPI_COMM_RANK( comm_palm, myid, ierr )
133#endif
134    CALL init_dvrp_logging
135
136!
137!-- Read control parameters from NAMELIST files and read environment-variables
138    CALL parin
139
140!
141!-- Determine processor topology and local array indices
142    CALL init_pegrid
143
144!
145!-- Generate grid parameters
146    CALL init_grid
147
148!
149!-- Check control parameters and deduce further quantities
150    CALL check_parameters
151
152    OPEN( 9, FILE='DEBUG'//myid_char, FORM='FORMATTED' )
153!
154!-- Initialize all necessary variables
155    CALL init_3d_model
156
157!
158!-- Output of program header
159    IF ( myid == 0 )  CALL header
160
161    CALL cpu_log( log_point(2), 'initialisation', 'stop' )
162
163!
164!-- Set start time in format hh:mm:ss
165    simulated_time_chr = time_to_string( simulated_time )
166
167!
168!-- If required, output of initial arrays
169    IF ( do2d_at_begin )  THEN
170       CALL data_output_2d( 'xy', 0 )
171       CALL data_output_2d( 'xz', 0 )
172       CALL data_output_2d( 'yz', 0 )
173    ENDIF
174    IF ( do3d_at_begin )  THEN
175       CALL data_output_3d( 0 )
176    ENDIF
177
178!
179!-- Integration of the model equations using the leap-frog scheme
180    CALL time_integration
181
182!
183!-- If required, write binary data for model continuation runs
184    IF ( write_binary(1:4) == 'true' )  CALL write_3d_binary
185
186!
187!-- If required, write binary particle data
188    CALL write_particles
189
190!
191!-- If required, repeat output of header including the required CPU-time
192    IF ( myid == 0 )  CALL header
193
194!
195!-- If required, final user-defined actions, and
196!-- last actions on the open files and close files. Unit 14 was opened
197!-- in write_3d_binary but it is closed here, to allow writing on this
198!-- unit in routine user_last_actions.
199    CALL cpu_log( log_point(4), 'last actions', 'start' )
200    CALL user_last_actions
201    IF ( write_binary(1:4) == 'true' )  CALL close_file( 14 )
202    CALL close_file( 0 )
203    CALL close_dvrp
204    CALL cpu_log( log_point(4), 'last actions', 'stop' )
205
206!
207!-- Take final CPU-time for CPU-time analysis
208    CALL cpu_log( log_point(1), 'total', 'stop' )
209    CALL cpu_statistics
210
211#if defined( __parallel )
212    CALL MPI_FINALIZE( ierr )
213#endif
214
215#if defined( __vtk )
216 END SUBROUTINE palm
217#else
218 END PROGRAM palm
219#endif
220
221
Note: See TracBrowser for help on using the repository browser.