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

Last change on this file since 1037 was 1037, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 9.7 KB
Line 
1 PROGRAM palm
2
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!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: palm.f90 1037 2012-10-22 14:10:22Z raasch $
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! 1015 2012-09-27 09:23:24Z raasch
32! Version number changed from 3.8 to 3.8a.
33! OpenACC statements added + code changes required for GPU optimization
34!
35! 849 2012-03-15 10:35:09Z raasch
36! write_particles renamed lpm_write_restart_file
37!
38! 759 2011-09-15 13:58:31Z raasch
39! Splitting of parallel I/O, cpu measurement for write_3d_binary and opening
40! of unit 14 moved to here
41!
42! 495 2010-03-02 00:40:15Z raasch
43! Particle data for restart runs are only written if write_binary=.T..
44!
45! 215 2008-11-18 09:54:31Z raasch
46! Initialization of coupled runs modified for MPI-1 and moved to external
47! subroutine init_coupling
48!
49! 197 2008-09-16 15:29:03Z raasch
50! Workaround for getting information about the coupling mode
51!
52! 108 2007-08-24 15:10:38Z letzel
53! Get coupling mode from environment variable, change location of debug output
54!
55! 75 2007-03-22 09:54:05Z raasch
56! __vtk directives removed, write_particles is called only in case of particle
57! advection switched on, open unit 9 for debug output,
58! setting of palm version moved from modules to here
59!
60! RCS Log replace by Id keyword, revision history cleaned up
61!
62! Revision 1.10  2006/08/04 14:53:12  raasch
63! Distibution of run description header removed, call of header moved behind
64! init_3d_model
65!
66! Revision 1.2  2001/01/25 07:15:06  raasch
67! Program name changed to PALM, module test_variables removed.
68! Initialization of dvrp logging as well as exit of dvrp moved to new
69! subroutines init_dvrp_logging and close_dvrp (file init_dvrp.f90)
70!
71! Revision 1.1  1997/07/24 11:23:35  raasch
72! Initial revision
73!
74!
75! Description:
76! ------------
77! Large-Eddy Simulation (LES) model for the convective boundary layer,
78! optimized for use on parallel machines (implementation realized using the
79! Message Passing Interface (MPI)). The model can also be run on vector machines
80! (less well optimized) and workstations. Versions for the different types of
81! machines are controlled via cpp-directives.
82! Model runs are only feasible using the ksh-script mrun.
83!------------------------------------------------------------------------------!
84
85
86    USE arrays_3d
87    USE constants
88    USE control_parameters
89    USE cpulog
90    USE dvrp_variables
91    USE grid_variables
92    USE indices
93    USE interfaces
94    USE model_1d
95    USE particle_attributes
96    USE pegrid
97    USE spectrum
98    USE statistics
99
100#if defined( __openacc )
101    USE OPENACC
102#endif
103
104    IMPLICIT NONE
105
106!
107!-- Local variables
108    CHARACTER (LEN=9) ::  time_to_string
109    CHARACTER (LEN=1) ::  cdum
110    INTEGER           ::  i, run_description_header_i(80)
111#if defined( __openacc )
112    REAL, DIMENSION(100) ::  acc_dum
113#endif
114
115    version = 'PALM 3.9'
116
117#if defined( __parallel )
118!
119!-- MPI initialisation. comm2d is preliminary set, because
120!-- it will be defined in init_pegrid but is used before in cpu_log.
121    CALL MPI_INIT( ierr )
122    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, numprocs, ierr )
123    CALL MPI_COMM_RANK( MPI_COMM_WORLD, myid, ierr )
124    comm_palm = MPI_COMM_WORLD
125    comm2d    = MPI_COMM_WORLD
126
127!
128!-- Initialize PE topology in case of coupled runs
129    CALL init_coupling
130#endif
131
132#if defined( __openacc )
133!
134!-- Get the number of accelerator boards per node and assign the MPI processes
135!-- to these boards
136    num_acc_per_node  = ACC_GET_NUM_DEVICES( ACC_DEVICE_NVIDIA )
137    acc_rank = MOD( myid, num_acc_per_node )
138    CALL ACC_SET_DEVICE_NUM ( acc_rank, ACC_DEVICE_NVIDIA )
139!
140!-- Test output (to be removed later)
141    WRITE (*,'(A,I4,A,I3,A,I3,A,I3)') '*** Connect MPI-Task ', myid,' to CPU ',&
142                                      acc_rank, ' Devices: ', num_acc_per_node,&
143                                      ' connected to:',                        &
144                                      ACC_GET_DEVICE_NUM( ACC_DEVICE_NVIDIA )
145#endif
146!
147!-- Ensure that OpenACC first attaches the GPU devices by copying a dummy data
148!-- region
149    !$acc data copyin( acc_dum )
150
151!
152!-- Initialize measuring of the CPU-time remaining to the run
153    CALL local_tremain_ini
154
155!
156!-- Start of total CPU time measuring.
157    CALL cpu_log( log_point(1), 'total', 'start' )
158    CALL cpu_log( log_point(2), 'initialisation', 'start' )
159
160!
161!-- Open a file for debug output
162    WRITE (myid_char,'(''_'',I4.4)')  myid
163    OPEN( 9, FILE='DEBUG'//TRIM( coupling_char )//myid_char, FORM='FORMATTED' )
164
165!
166!-- Initialize dvrp logging. Also, one PE maybe split from the global
167!-- communicator for doing the dvrp output. In that case, the number of
168!-- PEs available for PALM is reduced by one and communicator comm_palm
169!-- is changed respectively.
170#if defined( __parallel )
171    CALL MPI_COMM_RANK( comm_palm, myid, ierr )
172!
173!-- TEST OUTPUT (TO BE REMOVED)
174    WRITE(9,*) '*** coupling_mode = "', TRIM( coupling_mode ), '"'
175    CALL LOCAL_FLUSH( 9 )
176    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
177       PRINT*, '*** PE', myid, ' Global target PE:', target_id, &
178               TRIM( coupling_mode )
179    ENDIF
180#endif
181
182    CALL init_dvrp_logging
183
184!
185!-- Read control parameters from NAMELIST files and read environment-variables
186    CALL parin
187
188!
189!-- Determine processor topology and local array indices
190    CALL init_pegrid
191
192!
193!-- Generate grid parameters
194    CALL init_grid
195
196!
197!-- Check control parameters and deduce further quantities
198    CALL check_parameters
199
200
201!
202!-- Initialize all necessary variables
203    CALL init_3d_model
204
205!
206!-- Output of program header
207    IF ( myid == 0 )  CALL header
208
209    CALL cpu_log( log_point(2), 'initialisation', 'stop' )
210
211!
212!-- Set start time in format hh:mm:ss
213    simulated_time_chr = time_to_string( simulated_time )
214
215!
216!-- If required, output of initial arrays
217    IF ( do2d_at_begin )  THEN
218       CALL data_output_2d( 'xy', 0 )
219       CALL data_output_2d( 'xz', 0 )
220       CALL data_output_2d( 'yz', 0 )
221    ENDIF
222    IF ( do3d_at_begin )  THEN
223       CALL data_output_3d( 0 )
224    ENDIF
225
226!
227!-- Declare and initialize variables in the accelerator memory with their
228!-- host values
229    !$acc  data copyin( diss, e, e_p, kh, km, pt, pt_p, q, ql, tend, te_m, tpt_m, tu_m, tv_m, tw_m, u, u_p, v, vpt, v_p, w, w_p )          &
230    !$acc       copyin( ddzu, ddzw, dd2zu, l_grid, l_wall, ptdf_x, ptdf_y, pt_init, rdf, rdf_sc, ug, vg, zu, zw )   &
231    !$acc       copyin( hom, qs, qsws, qswst, rif, rif_wall, shf, ts, tswst, us, usws, uswst, vsws, vswst, z0, z0h )      &
232    !$acc       copyin( fxm, fxp, fym, fyp, fwxm, fwxp, fwym, fwyp, nzb_diff_s_inner, nzb_diff_s_outer, nzb_diff_u )       &
233    !$acc       copyin( nzb_diff_v, nzb_s_inner, nzb_s_outer, nzb_u_inner )    &
234    !$acc       copyin( nzb_u_outer, nzb_v_inner, nzb_v_outer, nzb_w_inner )   &
235    !$acc       copyin( nzb_w_outer, wall_heatflux, wall_e_x, wall_e_y, wall_u, wall_v, wall_w_x, wall_w_y, wall_flags_0 )
236!
237!-- Integration of the model equations using timestep-scheme
238    CALL time_integration
239
240!
241!-- If required, write binary data for restart runs
242    IF ( write_binary(1:4) == 'true' )  THEN
243
244       CALL cpu_log( log_point(22), 'write_3d_binary', 'start' )
245
246       CALL check_open( 14 )
247
248       DO  i = 0, io_blocks-1
249          IF ( i == io_group )  THEN
250!
251!--          Write flow field data
252             CALL write_3d_binary
253          ENDIF
254#if defined( __parallel )
255          CALL MPI_BARRIER( comm2d, ierr )
256#endif
257       ENDDO
258
259       CALL cpu_log( log_point(22), 'write_3d_binary', 'stop' )
260
261!
262!--    If required, write particle data
263       IF ( particle_advection )  CALL lpm_write_restart_file
264    ENDIF
265
266!
267!-- If required, repeat output of header including the required CPU-time
268    IF ( myid == 0 )  CALL header
269!
270!-- If required, final user-defined actions, and
271!-- last actions on the open files and close files. Unit 14 was opened
272!-- in write_3d_binary but it is closed here, to allow writing on this
273!-- unit in routine user_last_actions.
274    CALL cpu_log( log_point(4), 'last actions', 'start' )
275    DO  i = 0, io_blocks-1
276       IF ( i == io_group )  THEN
277          CALL user_last_actions
278          IF ( write_binary(1:4) == 'true' )  CALL close_file( 14 )
279       ENDIF
280#if defined( __parallel )
281       CALL MPI_BARRIER( comm2d, ierr )
282#endif
283    ENDDO
284    CALL close_file( 0 )
285    CALL close_dvrp
286    CALL cpu_log( log_point(4), 'last actions', 'stop' )
287
288#if defined( __mpi2 )
289!
290!-- Test exchange via intercommunicator in case of a MPI-2 coupling
291    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
292       i = 12345 + myid
293       CALL MPI_SEND( i, 1, MPI_INTEGER, myid, 11, comm_inter, ierr )
294    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
295       CALL MPI_RECV( i, 1, MPI_INTEGER, myid, 11, comm_inter, status, ierr )
296       PRINT*, '### myid: ', myid, '   received from atmosphere:  i = ', i
297    ENDIF
298#endif
299
300!
301!-- Close the OpenACC dummy data region
302    !$acc end data
303    !$acc end data
304
305!
306!-- Take final CPU-time for CPU-time analysis
307    CALL cpu_log( log_point(1), 'total', 'stop' )
308    CALL cpu_statistics
309
310#if defined( __parallel )
311    CALL MPI_FINALIZE( ierr )
312#endif
313
314 END PROGRAM palm
Note: See TracBrowser for help on using the repository browser.