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

Last change on this file since 171 was 164, checked in by raasch, 16 years ago

optimization of transpositions for 2D decompositions, workaround for using -env option with mpiexec, adjustments for lcxt4

  • Property svn:keywords set to Id
File size: 6.9 KB
Line 
1 PROGRAM palm
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Workaround for getting information about the coupling mode
7!
8! Former revisions:
9! -----------------
10! $Id: palm.f90 164 2008-05-15 08:46:15Z raasch $
11!
12! 108 2007-08-24 15:10:38Z letzel
13! Get coupling mode from environment variable, change location of debug output
14!
15! 75 2007-03-22 09:54:05Z raasch
16! __vtk directives removed, write_particles is called only in case of particle
17! advection switched on, open unit 9 for debug output,
18! setting of palm version moved from modules to here
19!
20! RCS Log replace by Id keyword, revision history cleaned up
21!
22! Revision 1.10  2006/08/04 14:53:12  raasch
23! Distibution of run description header removed, call of header moved behind
24! init_3d_model
25!
26! Revision 1.2  2001/01/25 07:15:06  raasch
27! Program name changed to PALM, module test_variables removed.
28! Initialization of dvrp logging as well as exit of dvrp moved to new
29! subroutines init_dvrp_logging and close_dvrp (file init_dvrp.f90)
30!
31! Revision 1.1  1997/07/24 11:23:35  raasch
32! Initial revision
33!
34!
35! Description:
36! ------------
37! Large-Eddy Simulation (LES) model for the convective boundary layer,
38! optimized for use on parallel machines (implementation realized using the
39! Message Passing Interface (MPI)). The model can also be run on vector machines
40! (less well optimized) and workstations. Versions for the different types of
41! machines are controlled via cpp-directives.
42! Model runs are only feasible using the ksh-script mrun.
43!------------------------------------------------------------------------------!
44
45
46    USE arrays_3d
47    USE constants
48    USE control_parameters
49    USE cpulog
50    USE dvrp_variables
51    USE grid_variables
52    USE indices
53    USE interfaces
54    USE model_1d
55    USE particle_attributes
56    USE pegrid
57    USE spectrum
58    USE statistics
59
60    IMPLICIT NONE
61
62!
63!-- Local variables
64    CHARACTER (LEN=9) ::  time_to_string
65    CHARACTER (LEN=1) ::  cdum
66    INTEGER           ::  i, run_description_header_i(80)
67
68    version = 'PALM 3.4a'
69
70#if defined( __parallel )
71!
72!-- MPI initialisation. comm2d is preliminary set, because
73!-- it will be defined in init_pegrid but is used before in cpu_log.
74    CALL MPI_INIT( ierr )
75    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, numprocs, ierr )
76    comm_palm = MPI_COMM_WORLD
77    comm2d    = MPI_COMM_WORLD
78#endif
79
80#if defined( __mpi2 )
81!
82!-- Get information about the coupling mode from the environment variable
83!-- which has been set by the mpiexec command.
84!-- This method is currently not used because the mpiexec command is not
85!-- available on some machines
86!    CALL local_getenv( 'coupling_mode', 13, coupling_mode, i )
87!    IF ( i == 0 )  coupling_mode = 'uncoupled'
88!    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
89
90!
91!-- Get information about the coupling mode from standard input (PE0 only) and
92!-- distribute it to the other PEs
93    CALL MPI_COMM_RANK( MPI_COMM_WORLD, myid, ierr )
94    IF ( myid == 0 )  THEN
95       READ (*,*,ERR=10,END=10)  coupling_mode
9610     IF ( TRIM( coupling_mode ) == 'atmosphere_to_ocean' )  THEN
97          i = 1
98       ELSEIF ( TRIM( coupling_mode ) ==  'ocean_to_atmosphere' )  THEN
99          i = 2
100       ELSE
101          i = 0
102       ENDIF
103    ENDIF
104    CALL MPI_BCAST( i, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
105    IF ( i == 0 )  THEN
106       coupling_mode = 'uncoupled'
107    ELSEIF ( i == 1 )  THEN
108       coupling_mode = 'atmosphere_to_ocean'
109    ELSEIF ( i == 2 )  THEN
110       coupling_mode = 'ocean_to_atmosphere'
111    ENDIF
112    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
113#endif
114
115!
116!-- Initialize measuring of the CPU-time remaining to the run
117    CALL local_tremain_ini
118
119!
120!-- Start of total CPU time measuring.
121    CALL cpu_log( log_point(1), 'total', 'start' )
122    CALL cpu_log( log_point(2), 'initialisation', 'start' )
123
124!
125!-- Initialize dvrp logging. Also, one PE maybe split from the global
126!-- communicator for doing the dvrp output. In that case, the number of
127!-- PEs available for PALM is reduced by one and communicator comm_palm
128!-- is changed respectively.
129#if defined( __parallel )
130    CALL MPI_COMM_RANK( comm_palm, myid, ierr )
131#endif
132
133!
134!-- Open a file for debug output
135    WRITE (myid_char,'(''_'',I4.4)')  myid
136    OPEN( 9, FILE='DEBUG'//TRIM( coupling_char )//myid_char, FORM='FORMATTED' )
137
138#if defined( __mpi2 )
139!
140!-- TEST OUTPUT (TO BE REMOVED)
141    WRITE(9,*) '*** coupling_mode = "', TRIM( coupling_mode ), '"'
142    CALL LOCAL_FLUSH( 9 )
143    print*, '*** PE', myid, '  ', TRIM( coupling_mode )
144#endif
145
146    CALL init_dvrp_logging
147
148!
149!-- Read control parameters from NAMELIST files and read environment-variables
150    CALL parin
151
152!
153!-- Determine processor topology and local array indices
154    CALL init_pegrid
155
156!
157!-- Generate grid parameters
158    CALL init_grid
159
160!
161!-- Check control parameters and deduce further quantities
162    CALL check_parameters
163
164!
165!-- Initialize all necessary variables
166    CALL init_3d_model
167
168!
169!-- Output of program header
170    IF ( myid == 0 )  CALL header
171
172    CALL cpu_log( log_point(2), 'initialisation', 'stop' )
173
174!
175!-- Set start time in format hh:mm:ss
176    simulated_time_chr = time_to_string( simulated_time )
177
178!
179!-- If required, output of initial arrays
180    IF ( do2d_at_begin )  THEN
181       CALL data_output_2d( 'xy', 0 )
182       CALL data_output_2d( 'xz', 0 )
183       CALL data_output_2d( 'yz', 0 )
184    ENDIF
185    IF ( do3d_at_begin )  THEN
186       CALL data_output_3d( 0 )
187    ENDIF
188
189!
190!-- Integration of the model equations using the leap-frog scheme
191    CALL time_integration
192
193!
194!-- If required, write binary data for model continuation runs
195    IF ( write_binary(1:4) == 'true' )  CALL write_3d_binary
196
197!
198!-- If required, write binary particle data
199    IF ( particle_advection )  CALL write_particles
200
201!
202!-- If required, repeat output of header including the required CPU-time
203    IF ( myid == 0 )  CALL header
204
205!
206!-- If required, final user-defined actions, and
207!-- last actions on the open files and close files. Unit 14 was opened
208!-- in write_3d_binary but it is closed here, to allow writing on this
209!-- unit in routine user_last_actions.
210    CALL cpu_log( log_point(4), 'last actions', 'start' )
211    CALL user_last_actions
212    IF ( write_binary(1:4) == 'true' )  CALL close_file( 14 )
213    CALL close_file( 0 )
214    CALL close_dvrp
215    CALL cpu_log( log_point(4), 'last actions', 'stop' )
216
217#if defined( __mpi2 )
218!
219!-- Test exchange via intercommunicator
220    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
221       i = 12345 + myid
222       CALL MPI_SEND( i, 1, MPI_INTEGER, myid, 11, comm_inter, ierr )
223    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
224       CALL MPI_RECV( i, 1, MPI_INTEGER, myid, 11, comm_inter, status, ierr )
225       PRINT*, '### myid: ', myid, '   received from atmosphere:  i = ', i
226    ENDIF
227#endif
228
229!
230!-- Take final CPU-time for CPU-time analysis
231    CALL cpu_log( log_point(1), 'total', 'stop' )
232    CALL cpu_statistics
233
234#if defined( __parallel )
235    CALL MPI_FINALIZE( ierr )
236#endif
237
238 END PROGRAM palm
239
Note: See TracBrowser for help on using the repository browser.