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

Last change on this file since 1318 was 1318, checked in by raasch, 10 years ago

former files/routines cpu_log and cpu_statistics combined to one module,
which also includes the former data module cpulog from the modules-file,
module interfaces removed

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