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

Last change on this file since 2232 was 2232, checked in by suehring, 7 years ago

Adjustments according new topography and surface-modelling concept implemented

  • Property svn:keywords set to Id
File size: 15.5 KB
RevLine 
[1682]1!> @file palm.f90
[2000]2!------------------------------------------------------------------------------!
[1036]3! This file is part of PALM.
4!
[2000]5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
[1036]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!
[2101]17! Copyright 1997-2017 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[484]20! Current revisions:
[1]21! -----------------
[2232]22! Renamed wall_flags_0 and wall_flags_00 into advc_flags_1 and advc_flags_2,
23! respectively, within copyin statement. Moreover, introduced further flag
24! array wall_flags_0.
25! Remove unused variables from ONLY list.
[1834]26!
[1321]27! Former revisions:
28! -----------------
29! $Id: palm.f90 2232 2017-05-30 17:47:52Z suehring $
30!
[2179]31! 2178 2017-03-17 11:07:39Z hellstea
32! Calls for pmci_ensure_nest_mass_conservation and pres are added after
33! the nest initialization
34!
[2119]35! 2118 2017-01-17 16:38:49Z raasch
36! OpenACC directives and related code removed
37!
[2012]38! 2011 2016-09-19 17:29:57Z kanani
39! Flag urban_surface is now defined in module control_parameters.
40!
[2008]41! 2007 2016-08-24 15:47:17Z kanani
42! Temporarily added CALL for writing of restart data for urban surface model
43!
[2001]44! 2000 2016-08-20 18:09:15Z knoop
45! Forced header and separation lines into 80 columns
46!
[1977]47! 1976 2016-07-27 13:28:04Z maronga
48! Added call to radiation_last_actions for binary output of land surface model
49! data
50!
[1973]51! 1972 2016-07-26 07:52:02Z maronga
52! Added call to lsm_last_actions for binary output of land surface model data
53!
[1961]54! 1960 2016-07-12 16:34:24Z suehring
55! Separate humidity and passive scalar
56!
[1933]57! 1834 2016-04-07 14:34:20Z raasch
58! Initial version of purely vertical nesting introduced.
59!
[1834]60! 1833 2016-04-07 14:23:03Z raasch
61! required user interface version changed
62!
[1809]63! 1808 2016-04-05 19:44:00Z raasch
64! routine local_flush replaced by FORTRAN statement
65!
[1784]66! 1783 2016-03-06 18:36:17Z raasch
67! required user interface version changed
68!
[1782]69! 1781 2016-03-03 15:12:23Z raasch
70! pmc initialization moved from time_integration to here
71!
[1780]72! 1779 2016-03-03 08:01:28Z raasch
73! setting of nest_domain and coupling_char moved to the pmci
74!
[1765]75! 1764 2016-02-28 12:45:19Z raasch
76! cpp-statements for nesting removed, communicator settings cleaned up
77!
[1763]78! 1762 2016-02-25 12:31:13Z hellstea
79! Introduction of nested domain feature
80!
[1748]81! 1747 2016-02-08 12:25:53Z raasch
82! OpenACC-adjustment for new surface layer parameterization
83!
[1683]84! 1682 2015-10-07 23:56:08Z knoop
85! Code annotations made doxygen readable
86!
[1669]87! 1668 2015-09-23 13:45:36Z raasch
88! warning replaced by abort in case of failed user interface check
89!
[1667]90! 1666 2015-09-23 07:31:10Z raasch
91! check for user's interface version added
92!
[1483]93! 1482 2014-10-18 12:34:45Z raasch
94! adjustments for using CUDA-aware OpenMPI
95!
[1469]96! 1468 2014-09-24 14:06:57Z maronga
97! Adapted for use on up to 6-digit processor cores
98!
[1403]99! 1402 2014-05-09 14:25:13Z raasch
100! location messages added
101!
[1375]102! 1374 2014-04-25 12:55:07Z raasch
103! bugfix: various modules added
104!
[1321]105! 1320 2014-03-20 08:40:49Z raasch
[1320]106! ONLY-attribute added to USE-statements,
107! kind-parameters added to all INTEGER and REAL declaration statements,
108! kinds are defined in new module kinds,
109! old module precision_kind is removed,
110! revision history before 2012 removed,
111! comment fields (!:) to be used for variable explanations added to
112! all variable declaration statements
[77]113!
[1319]114! 1318 2014-03-17 13:35:16Z raasch
115! module interfaces removed
116!
[1242]117! 1241 2013-10-30 11:36:58Z heinze
118! initialization of nuding and large scale forcing from external file
119!
[1222]120! 1221 2013-09-10 08:59:13Z raasch
121! +wall_flags_00, rflags_invers, rflags_s_inner in copyin statement
122!
[1213]123! 1212 2013-08-15 08:46:27Z raasch
124! +tri in copyin statement
125!
[1182]126! 1179 2013-06-14 05:57:58Z raasch
127! ref_state added to copyin-list
128!
[1114]129! 1113 2013-03-10 02:48:14Z raasch
130! openACC statements modified
131!
[1112]132! 1111 2013-03-08 23:54:10Z raasch
133! openACC statements updated
134!
[1093]135! 1092 2013-02-02 11:24:22Z raasch
136! unused variables removed
137!
[1037]138! 1036 2012-10-22 13:43:42Z raasch
139! code put under GPL (PALM 3.9)
140!
[1017]141! 1015 2012-09-27 09:23:24Z raasch
[863]142! Version number changed from 3.8 to 3.8a.
[1017]143! OpenACC statements added + code changes required for GPU optimization
[863]144!
[850]145! 849 2012-03-15 10:35:09Z raasch
146! write_particles renamed lpm_write_restart_file
147!
[1]148! Revision 1.1  1997/07/24 11:23:35  raasch
149! Initial revision
150!
151!
152! Description:
153! ------------
[1682]154!> Large-Eddy Simulation (LES) model for the convective boundary layer,
155!> optimized for use on parallel machines (implementation realized using the
156!> Message Passing Interface (MPI)). The model can also be run on vector machines
157!> (less well optimized) and workstations. Versions for the different types of
158!> machines are controlled via cpp-directives.
159!> Model runs are only feasible using the ksh-script mrun.
[1976]160!>
161!> @todo create routine last_actions instead of calling lsm_last_actions etc.
[2007]162!> @todo eventually move CALL usm_write_restart_data to suitable location
[1]163!------------------------------------------------------------------------------!
[1682]164 PROGRAM palm
165 
[1]166
[1374]167    USE arrays_3d
[1]168
[1320]169    USE control_parameters,                                                    &
[2232]170
[2178]171        ONLY:  cloud_physics, constant_diffusion, coupling_char, coupling_mode,&
[2177]172               do2d_at_begin, do3d_at_begin, humidity, initializing_actions,   &
[2232]173               land_surface, io_blocks, io_group,                              &
[2178]174               large_scale_forcing, message_string, microphysics_seifert,      &
175               nest_domain, neutral,                                           &
[1933]176               nudging, passive_scalar, simulated_time, simulated_time_chr,    &
[2011]177               urban_surface,                                                  &
[1666]178               user_interface_current_revision,                                &
179               user_interface_required_revision, version, wall_heatflux,       &
180               write_binary
[1320]181
182    USE cpulog,                                                                &
183        ONLY:  cpu_log, log_point, cpu_statistics
184
[1374]185    USE indices,                                                               &
[2232]186        ONLY:  nbgp
[1374]187
[1320]188    USE kinds
189
[1972]190    USE land_surface_model_mod,                                                &
[2232]191        ONLY:  lsm_last_actions
[1972]192
[1320]193    USE ls_forcing_mod,                                                        &
194        ONLY:  init_ls_forcing
195
196    USE nudge_mod,                                                             &
197        ONLY:  init_nudge
198
199    USE particle_attributes,                                                   &
200        ONLY:  particle_advection
201
[1]202    USE pegrid
203
[1762]204    USE pmc_interface,                                                         &
[1933]205        ONLY:  cpl_id, nested_run, pmci_child_initialize, pmci_init,           &
[2178]206               pmci_modelconfiguration, pmci_parent_initialize,                &
207               pmci_ensure_nest_mass_conservation
[1762]208
[1976]209    USE radiation_model_mod,                                                   &
210        ONLY:  radiation, radiation_last_actions
[2232]211       
[2007]212    USE urban_surface_mod,                                                     &
[2011]213        ONLY:  usm_write_restart_data       
[1747]214
[1]215    IMPLICIT NONE
216
217!
218!-- Local variables
[1682]219    CHARACTER(LEN=9)  ::  time_to_string  !<
220    CHARACTER(LEN=10) ::  env_string      !< to store string of environment var
221    INTEGER(iwp)      ::  env_stat        !< to hold status of GET_ENV
222    INTEGER(iwp)      ::  i               !<
223    INTEGER(iwp)      ::  myid_openmpi    !< OpenMPI local rank for CUDA aware MPI
[1]224
[1539]225    version = 'PALM 4.0'
[1833]226    user_interface_required_revision = 'r1819'
[75]227
[1]228#if defined( __parallel )
229!
230!-- MPI initialisation. comm2d is preliminary set, because
231!-- it will be defined in init_pegrid but is used before in cpu_log.
232    CALL MPI_INIT( ierr )
[1762]233
234!
235!-- Initialize the coupling for nested-domain runs
[1764]236!-- comm_palm is the communicator which includes all PEs (MPI processes)
237!-- available for this (nested) model. If it is not a nested run, comm_palm
238!-- is returned as MPI_COMM_WORLD
[1762]239    CALL pmci_init( comm_palm )
240    comm2d = comm_palm
[1764]241!
242!-- Get the (preliminary) number of MPI processes and the local PE-id (in case
243!-- of a further communicator splitting in init_coupling, these numbers will
244!-- be changed in init_pegrid).
245    IF ( nested_run )  THEN
[1762]246
[1764]247       CALL MPI_COMM_SIZE( comm_palm, numprocs, ierr )
248       CALL MPI_COMM_RANK( comm_palm, myid, ierr )
[1762]249
[1764]250    ELSE
251
252       CALL MPI_COMM_SIZE( MPI_COMM_WORLD, numprocs, ierr )
253       CALL MPI_COMM_RANK( MPI_COMM_WORLD, myid, ierr )
[1]254!
[1764]255!--    Initialize PE topology in case of coupled atmosphere-ocean runs (comm_palm
256!--    will be splitted in init_coupling)
257       CALL init_coupling
258    ENDIF
[102]259#endif
260
261!
[1]262!-- Initialize measuring of the CPU-time remaining to the run
263    CALL local_tremain_ini
264
265!
266!-- Start of total CPU time measuring.
267    CALL cpu_log( log_point(1), 'total', 'start' )
268    CALL cpu_log( log_point(2), 'initialisation', 'start' )
269
270!
[206]271!-- Open a file for debug output
[1468]272    WRITE (myid_char,'(''_'',I6.6)')  myid
[206]273    OPEN( 9, FILE='DEBUG'//TRIM( coupling_char )//myid_char, FORM='FORMATTED' )
274
275!
[1]276!-- Initialize dvrp logging. Also, one PE maybe split from the global
277!-- communicator for doing the dvrp output. In that case, the number of
278!-- PEs available for PALM is reduced by one and communicator comm_palm
279!-- is changed respectively.
280#if defined( __parallel )
281    CALL MPI_COMM_RANK( comm_palm, myid, ierr )
282!
[102]283!-- TEST OUTPUT (TO BE REMOVED)
284    WRITE(9,*) '*** coupling_mode = "', TRIM( coupling_mode ), '"'
[1808]285    FLUSH( 9 )
[215]286    IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
287       PRINT*, '*** PE', myid, ' Global target PE:', target_id, &
288               TRIM( coupling_mode )
289    ENDIF
[102]290#endif
291
[108]292    CALL init_dvrp_logging
293
[102]294!
[108]295!-- Read control parameters from NAMELIST files and read environment-variables
296    CALL parin
297
298!
[1666]299!-- Check for the user's interface version
300    IF ( user_interface_current_revision /= user_interface_required_revision )  &
301    THEN
302       message_string = 'current user-interface revision "' //                  &
303                        TRIM( user_interface_current_revision ) // '" does ' // &
304                        'not match the required revision ' //                   &
305                        TRIM( user_interface_required_revision )
[1668]306        CALL message( 'palm', 'PA0169', 1, 2, 0, 6, 0 )
[1666]307    ENDIF
308
309!
[108]310!-- Determine processor topology and local array indices
311    CALL init_pegrid
312
313!
[1]314!-- Generate grid parameters
315    CALL init_grid
316
317!
[1241]318!-- Initialize nudging if required
319    IF ( nudging )  THEN
320       CALL init_nudge
321    ENDIF
322
323!
324!-- Initialize reading of large scale forcing from external file - if required
325    IF ( large_scale_forcing )  THEN
326       CALL init_ls_forcing
327    ENDIF
328
329!
[1]330!-- Check control parameters and deduce further quantities
331    CALL check_parameters
332
333!
334!-- Initialize all necessary variables
335    CALL init_3d_model
336
337!
[1762]338!-- Coupling protocol setup for nested-domain runs
[1764]339    IF ( nested_run )  THEN
340       CALL pmci_modelconfiguration
[1781]341!
[1933]342!--    Receive and interpolate initial data on children.
343!--    Child initialization must be made first if the model is both child and
[2177]344!--    parent if necessary
345       IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
346          CALL pmci_child_initialize
[1781]347!
[2177]348!--       Send initial condition data from parent to children
349          CALL pmci_parent_initialize
[1781]350!
351!--    Exchange_horiz is needed after the nest initialization
[2178]352          IF ( nest_domain )  THEN
353             CALL exchange_horiz( u, nbgp )
354             CALL exchange_horiz( v, nbgp )
355             CALL exchange_horiz( w, nbgp )
356             IF ( .NOT. neutral )  THEN
357                CALL exchange_horiz( pt, nbgp )
358             ENDIF
359             IF ( .NOT. constant_diffusion )  CALL exchange_horiz( e, nbgp )
360             IF ( humidity )  THEN
361                CALL exchange_horiz( q, nbgp )
362                IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
363!                   CALL exchange_horiz( qc, nbgp )
364                   CALL exchange_horiz( qr, nbgp ) 
365!                   CALL exchange_horiz( nc, nbgp )
366                   CALL exchange_horiz( nr, nbgp )
367                ENDIF
368             ENDIF
369             IF ( passive_scalar )  CALL exchange_horiz( s, nbgp )
370
371             CALL pmci_ensure_nest_mass_conservation
372             CALL pres
[1933]373          ENDIF
[1781]374       ENDIF
375
[1764]376    ENDIF
[1762]377
378!
[1]379!-- Output of program header
380    IF ( myid == 0 )  CALL header
381
382    CALL cpu_log( log_point(2), 'initialisation', 'stop' )
383
384!
385!-- Set start time in format hh:mm:ss
386    simulated_time_chr = time_to_string( simulated_time )
387
388!
389!-- If required, output of initial arrays
390    IF ( do2d_at_begin )  THEN
391       CALL data_output_2d( 'xy', 0 )
392       CALL data_output_2d( 'xz', 0 )
393       CALL data_output_2d( 'yz', 0 )
394    ENDIF
[1976]395
[1]396    IF ( do3d_at_begin )  THEN
397       CALL data_output_3d( 0 )
398    ENDIF
399
400!
[495]401!-- Integration of the model equations using timestep-scheme
[1]402    CALL time_integration
403
404!
[495]405!-- If required, write binary data for restart runs
406    IF ( write_binary(1:4) == 'true' )  THEN
[759]407
408       CALL cpu_log( log_point(22), 'write_3d_binary', 'start' )
409
[1402]410       CALL location_message( 'writing restart data', .FALSE. )
411
[759]412       CALL check_open( 14 )
413
414       DO  i = 0, io_blocks-1
415          IF ( i == io_group )  THEN
[1]416!
[759]417!--          Write flow field data
418             CALL write_3d_binary
419          ENDIF
420#if defined( __parallel )
421          CALL MPI_BARRIER( comm2d, ierr )
422#endif
423       ENDDO
424
[1402]425       CALL location_message( 'finished', .TRUE. )
426
[759]427       CALL cpu_log( log_point(22), 'write_3d_binary', 'stop' )
428
[495]429!
430!--    If required, write particle data
[849]431       IF ( particle_advection )  CALL lpm_write_restart_file
[2007]432!
433!--    If required, write urban surface data
434       IF (urban_surface)  CALL usm_write_restart_data
435       
[495]436    ENDIF
[1]437
438!
439!-- If required, repeat output of header including the required CPU-time
440    IF ( myid == 0 )  CALL header
441!
[1972]442!-- If required, final land surface and user-defined actions, and
[1]443!-- last actions on the open files and close files. Unit 14 was opened
444!-- in write_3d_binary but it is closed here, to allow writing on this
445!-- unit in routine user_last_actions.
446    CALL cpu_log( log_point(4), 'last actions', 'start' )
[759]447    DO  i = 0, io_blocks-1
448       IF ( i == io_group )  THEN
[1972]449          IF ( land_surface )  THEN
450             CALL lsm_last_actions
451          ENDIF
[1976]452          IF ( radiation )  THEN
453             CALL radiation_last_actions
454          ENDIF
[759]455          CALL user_last_actions
456          IF ( write_binary(1:4) == 'true' )  CALL close_file( 14 )
457       ENDIF
458#if defined( __parallel )
459       CALL MPI_BARRIER( comm2d, ierr )
460#endif
461    ENDDO
[1]462    CALL close_file( 0 )
463    CALL close_dvrp
464    CALL cpu_log( log_point(4), 'last actions', 'stop' )
465
[102]466#if defined( __mpi2 )
[1]467!
[206]468!-- Test exchange via intercommunicator in case of a MPI-2 coupling
[102]469    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
470       i = 12345 + myid
471       CALL MPI_SEND( i, 1, MPI_INTEGER, myid, 11, comm_inter, ierr )
472    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
473       CALL MPI_RECV( i, 1, MPI_INTEGER, myid, 11, comm_inter, status, ierr )
474       PRINT*, '### myid: ', myid, '   received from atmosphere:  i = ', i
475    ENDIF
476#endif
477
478!
[1]479!-- Take final CPU-time for CPU-time analysis
480    CALL cpu_log( log_point(1), 'total', 'stop' )
481    CALL cpu_statistics
482
483#if defined( __parallel )
484    CALL MPI_FINALIZE( ierr )
485#endif
486
487 END PROGRAM palm
Note: See TracBrowser for help on using the repository browser.