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

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

unused variables remove from several routines

  • Property svn:keywords set to Id
File size: 9.9 KB
RevLine 
[1]1 PROGRAM palm
2
[1036]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!
[484]20! Current revisions:
[1]21! -----------------
[1092]22! unused variables removed
[77]23!
24! Former revisions:
25! -----------------
26! $Id: palm.f90 1092 2013-02-02 11:24:22Z raasch $
27!
[1037]28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
[1017]31! 1015 2012-09-27 09:23:24Z raasch
[863]32! Version number changed from 3.8 to 3.8a.
[1017]33! OpenACC statements added + code changes required for GPU optimization
[863]34!
[850]35! 849 2012-03-15 10:35:09Z raasch
36! write_particles renamed lpm_write_restart_file
37!
[760]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!
[496]42! 495 2010-03-02 00:40:15Z raasch
43! Particle data for restart runs are only written if write_binary=.T..
44!
[226]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!
[198]49! 197 2008-09-16 15:29:03Z raasch
50! Workaround for getting information about the coupling mode
51!
[110]52! 108 2007-08-24 15:10:38Z letzel
53! Get coupling mode from environment variable, change location of debug output
54!
[77]55! 75 2007-03-22 09:54:05Z raasch
[70]56! __vtk directives removed, write_particles is called only in case of particle
[75]57! advection switched on, open unit 9 for debug output,
58! setting of palm version moved from modules to here
[1]59!
[3]60! RCS Log replace by Id keyword, revision history cleaned up
61!
[1]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
[102]88    USE control_parameters
[1]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
[1015]100#if defined( __openacc )
101    USE OPENACC
102#endif
103
[1]104    IMPLICIT NONE
105
106!
107!-- Local variables
108    CHARACTER (LEN=9) ::  time_to_string
[1092]109    INTEGER           ::  i
[1015]110#if defined( __openacc )
111    REAL, DIMENSION(100) ::  acc_dum
112#endif
[1]113
[1036]114    version = 'PALM 3.9'
[75]115
[1]116#if defined( __parallel )
117!
118!-- MPI initialisation. comm2d is preliminary set, because
119!-- it will be defined in init_pegrid but is used before in cpu_log.
120    CALL MPI_INIT( ierr )
121    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, numprocs, ierr )
[206]122    CALL MPI_COMM_RANK( MPI_COMM_WORLD, myid, ierr )
[1]123    comm_palm = MPI_COMM_WORLD
124    comm2d    = MPI_COMM_WORLD
125
126!
[206]127!-- Initialize PE topology in case of coupled runs
128    CALL init_coupling
[102]129#endif
130
[1015]131#if defined( __openacc )
[102]132!
[1015]133!-- Get the number of accelerator boards per node and assign the MPI processes
134!-- to these boards
[1092]135    PRINT*, '*** ACC_DEVICE_NVIDIA = ', ACC_DEVICE_NVIDIA
[1015]136    num_acc_per_node  = ACC_GET_NUM_DEVICES( ACC_DEVICE_NVIDIA )
[1092]137    IF ( numprocs == 1  .AND.  num_acc_per_node > 0 )  num_acc_per_node = 1
138    PRINT*, '*** myid = ', myid, ' num_acc_per_node = ', num_acc_per_node
[1015]139    acc_rank = MOD( myid, num_acc_per_node )
[1092]140!    STOP '****'
[1015]141    CALL ACC_SET_DEVICE_NUM ( acc_rank, ACC_DEVICE_NVIDIA )
142!
143!-- Test output (to be removed later)
144    WRITE (*,'(A,I4,A,I3,A,I3,A,I3)') '*** Connect MPI-Task ', myid,' to CPU ',&
145                                      acc_rank, ' Devices: ', num_acc_per_node,&
146                                      ' connected to:',                        &
147                                      ACC_GET_DEVICE_NUM( ACC_DEVICE_NVIDIA )
148#endif
[1092]149
[1015]150!
151!-- Ensure that OpenACC first attaches the GPU devices by copying a dummy data
152!-- region
153    !$acc data copyin( acc_dum )
154
155!
[1]156!-- Initialize measuring of the CPU-time remaining to the run
157    CALL local_tremain_ini
158
159!
160!-- Start of total CPU time measuring.
161    CALL cpu_log( log_point(1), 'total', 'start' )
162    CALL cpu_log( log_point(2), 'initialisation', 'start' )
163
164!
[206]165!-- Open a file for debug output
166    WRITE (myid_char,'(''_'',I4.4)')  myid
167    OPEN( 9, FILE='DEBUG'//TRIM( coupling_char )//myid_char, FORM='FORMATTED' )
168
169!
[1]170!-- Initialize dvrp logging. Also, one PE maybe split from the global
171!-- communicator for doing the dvrp output. In that case, the number of
172!-- PEs available for PALM is reduced by one and communicator comm_palm
173!-- is changed respectively.
174#if defined( __parallel )
175    CALL MPI_COMM_RANK( comm_palm, myid, ierr )
176!
[102]177!-- TEST OUTPUT (TO BE REMOVED)
178    WRITE(9,*) '*** coupling_mode = "', TRIM( coupling_mode ), '"'
179    CALL LOCAL_FLUSH( 9 )
[215]180    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
181       PRINT*, '*** PE', myid, ' Global target PE:', target_id, &
182               TRIM( coupling_mode )
183    ENDIF
[102]184#endif
185
[108]186    CALL init_dvrp_logging
187
[102]188!
[108]189!-- Read control parameters from NAMELIST files and read environment-variables
190    CALL parin
191
192!
193!-- Determine processor topology and local array indices
194    CALL init_pegrid
195
196!
[1]197!-- Generate grid parameters
198    CALL init_grid
199
200!
201!-- Check control parameters and deduce further quantities
202    CALL check_parameters
203
[667]204
[1]205!
206!-- Initialize all necessary variables
207    CALL init_3d_model
208
209!
210!-- Output of program header
211    IF ( myid == 0 )  CALL header
212
213    CALL cpu_log( log_point(2), 'initialisation', 'stop' )
214
215!
216!-- Set start time in format hh:mm:ss
217    simulated_time_chr = time_to_string( simulated_time )
218
219!
220!-- If required, output of initial arrays
221    IF ( do2d_at_begin )  THEN
222       CALL data_output_2d( 'xy', 0 )
223       CALL data_output_2d( 'xz', 0 )
224       CALL data_output_2d( 'yz', 0 )
225    ENDIF
226    IF ( do3d_at_begin )  THEN
227       CALL data_output_3d( 0 )
228    ENDIF
229
230!
[1015]231!-- Declare and initialize variables in the accelerator memory with their
232!-- host values
233    !$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 )          &
234    !$acc       copyin( ddzu, ddzw, dd2zu, l_grid, l_wall, ptdf_x, ptdf_y, pt_init, rdf, rdf_sc, ug, vg, zu, zw )   &
235    !$acc       copyin( hom, qs, qsws, qswst, rif, rif_wall, shf, ts, tswst, us, usws, uswst, vsws, vswst, z0, z0h )      &
236    !$acc       copyin( fxm, fxp, fym, fyp, fwxm, fwxp, fwym, fwyp, nzb_diff_s_inner, nzb_diff_s_outer, nzb_diff_u )       &
237    !$acc       copyin( nzb_diff_v, nzb_s_inner, nzb_s_outer, nzb_u_inner )    &
238    !$acc       copyin( nzb_u_outer, nzb_v_inner, nzb_v_outer, nzb_w_inner )   &
239    !$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 )
240!
[495]241!-- Integration of the model equations using timestep-scheme
[1]242    CALL time_integration
243
244!
[495]245!-- If required, write binary data for restart runs
246    IF ( write_binary(1:4) == 'true' )  THEN
[759]247
248       CALL cpu_log( log_point(22), 'write_3d_binary', 'start' )
249
250       CALL check_open( 14 )
251
252       DO  i = 0, io_blocks-1
253          IF ( i == io_group )  THEN
[1]254!
[759]255!--          Write flow field data
256             CALL write_3d_binary
257          ENDIF
258#if defined( __parallel )
259          CALL MPI_BARRIER( comm2d, ierr )
260#endif
261       ENDDO
262
263       CALL cpu_log( log_point(22), 'write_3d_binary', 'stop' )
264
[495]265!
266!--    If required, write particle data
[849]267       IF ( particle_advection )  CALL lpm_write_restart_file
[495]268    ENDIF
[1]269
270!
271!-- If required, repeat output of header including the required CPU-time
272    IF ( myid == 0 )  CALL header
273!
274!-- If required, final user-defined actions, and
275!-- last actions on the open files and close files. Unit 14 was opened
276!-- in write_3d_binary but it is closed here, to allow writing on this
277!-- unit in routine user_last_actions.
278    CALL cpu_log( log_point(4), 'last actions', 'start' )
[759]279    DO  i = 0, io_blocks-1
280       IF ( i == io_group )  THEN
281          CALL user_last_actions
282          IF ( write_binary(1:4) == 'true' )  CALL close_file( 14 )
283       ENDIF
284#if defined( __parallel )
285       CALL MPI_BARRIER( comm2d, ierr )
286#endif
287    ENDDO
[1]288    CALL close_file( 0 )
289    CALL close_dvrp
290    CALL cpu_log( log_point(4), 'last actions', 'stop' )
291
[102]292#if defined( __mpi2 )
[1]293!
[206]294!-- Test exchange via intercommunicator in case of a MPI-2 coupling
[102]295    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
296       i = 12345 + myid
297       CALL MPI_SEND( i, 1, MPI_INTEGER, myid, 11, comm_inter, ierr )
298    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
299       CALL MPI_RECV( i, 1, MPI_INTEGER, myid, 11, comm_inter, status, ierr )
300       PRINT*, '### myid: ', myid, '   received from atmosphere:  i = ', i
301    ENDIF
302#endif
303
304!
[1015]305!-- Close the OpenACC dummy data region
306    !$acc end data
307    !$acc end data
308
309!
[1]310!-- Take final CPU-time for CPU-time analysis
311    CALL cpu_log( log_point(1), 'total', 'stop' )
312    CALL cpu_statistics
313
314#if defined( __parallel )
315    CALL MPI_FINALIZE( ierr )
316#endif
317
318 END PROGRAM palm
Note: See TracBrowser for help on using the repository browser.