source: palm/trunk/SOURCE/module_interface.f90 @ 4017

Last change on this file since 4017 was 4017, checked in by schwenkel, 5 years ago

Modularization of all lagrangian particle model code components

  • Property svn:keywords set to Id
File size: 74.9 KB
RevLine 
[3637]1!> @file module_interface.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
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.
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!
[3648]17! Copyright 1997-2019 Leibniz Universitaet Hannover
[3637]18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
[3745]23!
[3637]24! Former revisions:
25! -----------------
[3770]26! $Id: module_interface.f90 4017 2019-06-06 12:16:46Z schwenkel $
[4004]27! local_pf need INTENT(INOUT) attribute rather than INTENT(OUT). This is
28! because INTENT(OUT) sets the array to not-defined. Especially for outputs that
29! are not defined everywhere, e.g. land-surface outputs, this will be
30! problematic as NaN will be output.   
31!
32! 3987 2019-05-22 09:52:13Z kanani
[3987]33! Introduce switchable DEBUG file output via debug_message routine
34!
35! 3956 2019-05-07 12:32:52Z monakurppa
[3956]36! - Added calls for salsa_non_advective_processes and
37!   salsa_exchange_horiz_bounds
38! - Moved the call for salsa_data_output_2d/3d before that of
39!   radiation_data_output_2d/3d. radiation_data_output_2d/3d tries to read a
40!   salsa output variable and encounters a segmentation fault for "Ntot" due
41!   to the shortoutput name
42!
43! 3931 2019-04-24 16:34:28Z schwenkel
[3931]44! Changed non_transport_physics to non_advective_processes
45!
46! 3930 2019-04-24 14:57:18Z forkel
[3929]47! Correct/complete module_interface introduction for chemistry model
48!
49! 3887 2019 -04-12 08:47:41Z schwenkel
[3885]50! Changes related to global restructuring of location messages and introduction
51! of additional debug messages
[3929]52
53! 3880 2019 -04-08 21:43:02Z knoop
[3864]54! Add a call for salsa_prognostic_equations
55!
56! 3840 2019-03-29 10:35:52Z knoop
[3806]57! bugfix: intent of dummy arguments changed to inout
58!
59! 3770 2019-02-28 11:22:32Z moh.hefny
[3769]60! removed unused variables in module_interface_check_data_output_ts
[3770]61!
[3769]62! 3767 08:18:02Z raasch
[3767]63! unused variable file_index removed from subroutine parameter list
64!
65! 3766 2019-02-26 16:23:41Z raasch
[3766]66! first argument removed from module_interface_rrd_*, statement added to avoid
67! compiler warning about unused variable, file reformatted with respect to coding
68! standards
69!
70! 3762 2019-02-25 16:54:16Z suehring
[3762]71! only pass required arguments to surface_data_output_rrd_local
72!
73! 3747 2019-02-16 15:15:23Z gronemeier
[3747]74! Call user_init_arrays
75!
76! 3745 2019-02-15 18:57:56Z suehring
[3745]77! Add indoor model
78!
79! 3744 2019-02-15 18:38:58Z suehring
[3739]80! Removed bio_check_parameters as the method is empty.
81!
82! 3735 2019-02-12 09:52:40Z dom_dwd_user
[3735]83! Accepting variable j from check_parameters and passing it to
84! bio_check_data_output
85! Add required restart data for surface output module
86!
87! 3731 2019-02-11 13:06:27Z suehring
[3717]88! Add check_parameters routine for virtual measurements
89!
90! 3711 2019-01-31 13:44:26Z knoop
[3711]91! Introduced module_interface_init_checks for post-init checks
92!
93! 3705 2019-01-29 19:56:39Z suehring
[3705]94! Add last_actions for virtual measurements
95!
96! 3704 2019-01-29 19:51:41Z suehring
[3685]97! Some interface calls moved to module_interface + cleanup
98!
99! 3684 2019-01-20 20:20:58Z knoop
[3655]100! Bugfix: made unit intend INOUT
101!
102! 3650 2019-01-04 13:01:33Z kanani
[3650]103! Add restart routines for biometeorology
104!
105! 3649 2019-01-02 16:52:21Z suehring
[3649]106! Initialize strings, in order to avoid compiler warnings for non-initialized
107! characters with intent(out) attribute
108!
109! 3648 2019-01-02 16:35:46Z suehring
[3648]110! Rename subroutines for surface-data output
111!
112! 3641 2018-12-23 22:10:01Z knoop
[3637]113! Initial implementation of the PALM module interface
114!
115!
116! Description:
117! ------------
118!> This is the interface between the PALM model core and all its modules.
119!>
[3731]120!> @todo Re-format module to be consistent with coding standard
[3637]121!------------------------------------------------------------------------------!
[3766]122 MODULE module_interface
[3637]123
[3766]124    USE indices,                                                               &
125        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt
[3637]126
[3766]127    USE kinds
[3637]128
[3766]129!
130!-- load module-specific control parameters.
131!-- ToDo: move all of them to respective module or a dedicated central module
132    USE control_parameters,                                                    &
[3987]133        ONLY:  air_chemistry,                                                  &
134               biometeorology,                                                 &
135               debug_output,                                                   &
136               debug_output_timestep,                                          &
[3766]137               indoor_model,                                                   &
138               land_surface,                                                   &
139               large_scale_forcing,                                            &
140               nesting_offline,                                                &
141               nudging,                                                        &
142               ocean_mode,                                                     &
143               plant_canopy,                                                   &
144               salsa,                                                          &
145               surface_output,                                                 &
146               syn_turb_gen,                                                   &
147               urban_surface,                                                  &
148               virtual_flight,                                                 &
149               virtual_measurement,                                            &
150               wind_turbine
[3637]151
[3766]152!
153!-- load interface routines of all PALM modules
154    USE biometeorology_mod,                                                    &
155        ONLY:  bio_parin,                                                      &
156               bio_check_data_output,                                          &
157               bio_init,                                                       &
158               bio_init_checks,                                                &
159               bio_header,                                                     &
160               bio_3d_data_averaging,                                          &
161               bio_data_output_2d,                                             &
162               bio_data_output_3d,                                             &
163               bio_rrd_global,                                                 &
164               bio_rrd_local,                                                  &
165               bio_wrd_global,                                                 &
166               bio_wrd_local
[3637]167
[3766]168    USE bulk_cloud_model_mod,                                                  &
169        ONLY:  bulk_cloud_model,                                               &
170               bcm_parin,                                                      &
171               bcm_check_parameters,                                           &
172               bcm_check_data_output_pr,                                       &
173               bcm_check_data_output,                                          &
174               bcm_init_arrays,                                                &
175               bcm_init,                                                       &
176               bcm_header,                                                     &
[3870]177               bcm_actions,                                                    &
[3931]178               bcm_non_advective_processes,                                    &
[3956]179               bcm_exchange_horiz,                                             &
[3870]180               bcm_prognostic_equations,                                       &
[3766]181               bcm_swap_timelevel,                                             &
182               bcm_3d_data_averaging,                                          &
183               bcm_data_output_2d,                                             &
184               bcm_data_output_3d,                                             &
185               bcm_rrd_global,                                                 &
186               bcm_wrd_global,                                                 &
187               bcm_rrd_local,                                                  &
188               bcm_wrd_local
[3637]189
190   USE chemistry_model_mod,                                                    &
191       ONLY:  chem_parin,                                                      &
192              chem_check_parameters,                                           &
193              chem_check_data_output_pr,                                       &
194              chem_check_data_output,                                          &
[3929]195              chem_exchange_horiz_bounds,                                      &
[3685]196              chem_init_arrays,                                                &
197              chem_init,                                                       &
[3637]198              chem_header,                                                     &
[3877]199              chem_actions,                                                    &
[3930]200              chem_non_advective_processes,                                    &
[3880]201              chem_prognostic_equations,                                       &
[3637]202              chem_swap_timelevel,                                             &
203              chem_3d_data_averaging,                                          &
204              chem_data_output_2d,                                             &
205              chem_data_output_3d,                                             &
206              chem_statistics,                                                 &
207              chem_rrd_local,                                                  &
[3887]208              chem_wrd_local
[3637]209
[3766]210    USE flight_mod,                                                            &
211        ONLY:  flight_parin,                                                   &
212               flight_header,                                                  &
213               flight_init,                                                    &
214               flight_rrd_global,                                              &
215               flight_wrd_global
[3637]216
[3766]217    USE gust_mod,                                                              &
218        ONLY:  gust_module_enabled,                                            &
219               gust_parin,                                                     &
220               gust_check_parameters,                                          &
221               gust_check_data_output_pr,                                      &
222               gust_check_data_output,                                         &
223               gust_init_arrays,                                               &
224               gust_init,                                                      &
225               gust_header,                                                    &
226               gust_actions,                                                   &
[3837]227               gust_prognostic_equations,                                      &
[3766]228               gust_swap_timelevel,                                            &
229               gust_3d_data_averaging,                                         &
230               gust_data_output_2d,                                            &
231               gust_data_output_3d,                                            &
232               gust_statistics,                                                &
233               gust_rrd_global,                                                &
234               gust_wrd_global,                                                &
235               gust_rrd_local,                                                 &
236               gust_wrd_local
[3637]237
[3766]238    USE indoor_model_mod,                                                      &
239        ONLY:  im_parin,                                                       &
240               im_check_data_output,                                           &
241               im_check_parameters,                                            &
242               im_data_output_3d,                                              &
243               im_init
[4017]244               
245    USE lagrangian_particle_model_mod,                                         &
246        ONLY:  lpm_parin,                                                      &
247               lpm_header,                                                     &
248               lpm_check_parameters,                                           &
249               lpm_init,                                                       &
250               lpm_actions,                                                    &
251               lpm_rrd_global,                                                 &
252               lpm_rrd_local,                                                  &
253               lpm_wrd_local,                                                  &
254               lpm_wrd_global
255               
[3766]256    USE land_surface_model_mod,                                                &
257        ONLY:  lsm_parin,                                                      &
258               lsm_check_parameters,                                           &
259               lsm_check_data_output_pr,                                       &
260               lsm_check_data_output,                                          &
261               lsm_init_arrays,                                                &
262               lsm_init,                                                       &
263               lsm_header,                                                     &
264               lsm_swap_timelevel,                                             &
265               lsm_3d_data_averaging,                                          &
266               lsm_data_output_2d,                                             &
267               lsm_rrd_local,                                                  &
268               lsm_wrd_local
[3637]269
[3766]270    USE lsf_nudging_mod,                                                       &
271        ONLY:  lsf_nudging_check_parameters,                                   &
272               lsf_nudging_check_data_output_pr,                               &
273               lsf_init,                                                       &
274               nudge_init,                                                     &
275               lsf_nudging_header
[3637]276
[3766]277    USE multi_agent_system_mod,                                                &
278        ONLY:  mas_parin
[3637]279
[3766]280    USE nesting_offl_mod,                                                      &
281        ONLY:  nesting_offl_parin,                                             &
282               nesting_offl_check_parameters,                                  &
283               nesting_offl_header
[3637]284
[3766]285    USE ocean_mod,                                                             &
286        ONLY:  ocean_parin,                                                    &
287               ocean_check_parameters,                                         &
288               ocean_check_data_output_pr,                                     &
289               ocean_check_data_output,                                        &
290               ocean_init_arrays,                                              &
291               ocean_init,                                                     &
292               ocean_header,                                                   &
[3873]293               ocean_actions,                                                  &
[3840]294               ocean_prognostic_equations,                                     &
[3766]295               ocean_swap_timelevel,                                           &
296               ocean_3d_data_averaging,                                        &
297               ocean_data_output_2d,                                           &
298               ocean_data_output_3d,                                           &
299               ocean_rrd_global,                                               &
300               ocean_wrd_global,                                               &
301               ocean_rrd_local,                                                &
302               ocean_wrd_local
[4017]303               
304    USE particle_attributes,                                                   &
305        ONLY:  particle_advection               
[3637]306
[3766]307    USE plant_canopy_model_mod,                                                &
308         ONLY: pcm_parin,                                                      &
309               pcm_check_parameters,                                           &
310               pcm_check_data_output,                                          &
311               pcm_init,                                                       &
312               pcm_header,                                                     &
313               pcm_data_output_3d
[3637]314
[3766]315    USE radiation_model_mod,                                                   &
316        ONLY:  radiation,                                                      &
317               radiation_parin,                                                &
318               radiation_check_parameters,                                     &
319               radiation_check_data_output_ts,                                 &
320               radiation_check_data_output_pr,                                 &
321               radiation_check_data_output,                                    &
322               radiation_init,                                                 &
323               radiation_header,                                               &
324               radiation_3d_data_averaging,                                    &
325               radiation_data_output_2d,                                       &
326               radiation_data_output_3d,                                       &
327               radiation_rrd_local,                                            &
328               radiation_wrd_local
[3637]329
[3766]330    USE salsa_mod,                                                             &
331        ONLY:  salsa_parin,                                                    &
332               salsa_check_parameters,                                         &
333               salsa_check_data_output,                                        &
334               salsa_init_arrays,                                              &
335               salsa_init,                                                     &
336               salsa_header,                                                   &
[3871]337               salsa_actions,                                                  &
[3956]338               salsa_non_advective_processes,                                  &
339               salsa_exchange_horiz_bounds,                                    &
[3864]340               salsa_prognostic_equations,                                     &
[3766]341               salsa_swap_timelevel,                                           &
342               salsa_3d_data_averaging,                                        &
343               salsa_data_output_2d,                                           &
344               salsa_data_output_3d,                                           &
345               salsa_rrd_local,                                                &
346               salsa_wrd_local
[3637]347
[3766]348    USE spectra_mod,                                                           &
349        ONLY:  calculate_spectra,                                              &
350               spectra_parin,                                                  &
351               spectra_check_parameters,                                       &
352               spectra_header
[3637]353
[3766]354    USE surface_data_output_mod,                                               &
355        ONLY:  surface_data_output_parin,                                      &
356               surface_data_output_check_parameters,                           &
357               surface_data_output_init_arrays,                                &
358               surface_data_output_rrd_local,                                  &
359               surface_data_output_rrd_global,                                 &
360               surface_data_output_wrd_local,                                  &
361               surface_data_output_wrd_global
[3637]362
[3766]363    USE synthetic_turbulence_generator_mod,                                    &
364        ONLY:  stg_parin,                                                      &
365               stg_check_parameters,                                           &
366               stg_header,                                                     &
367               stg_rrd_global,                                                 &
368               stg_wrd_global
[3637]369
[3766]370    USE urban_surface_mod,                                                     &
371        ONLY:  usm_parin,                                                      &
372               usm_check_parameters,                                           &
373               usm_check_data_output,                                          &
374               usm_init_arrays,                                                &
375               usm_init,                                                       &
376               usm_swap_timelevel,                                             &
377               usm_3d_data_averaging,                                          &
378               usm_rrd_local,                                                  &
379               usm_wrd_local
[3637]380
[3766]381    USE user,                                                                  &
382        ONLY:  user_module_enabled,                                            &
383               user_parin,                                                     &
384               user_check_parameters,                                          &
385               user_check_data_output_ts,                                      &
386               user_check_data_output_pr,                                      &
387               user_check_data_output,                                         &
388               user_init,                                                      &
389               user_init_arrays,                                               &
390               user_header,                                                    &
391               user_actions,                                                   &
392               user_3d_data_averaging,                                         &
393               user_data_output_2d,                                            &
394               user_data_output_3d,                                            &
395               user_statistics,                                                &
396               user_rrd_global,                                                &
397               user_rrd_local,                                                 &
398               user_wrd_global,                                                &
399               user_wrd_local,                                                 &
400               user_last_actions
[3684]401
[3766]402    USE virtual_measurement_mod,                                               &
403        ONLY:  vm_check_parameters,                                            &
404               vm_init,                                                        &
405               vm_last_actions,                                                &
406               vm_parin
[3637]407
[3766]408    USE wind_turbine_model_mod,                                                &
409        ONLY:  wtm_parin,                                                      &
410               wtm_check_parameters,                                           &
411               wtm_init_arrays,                                                &
412               wtm_init,                                                       &
[3875]413               wtm_actions,                                                    &
[3766]414               wtm_rrd_global,                                                 &
415               wtm_wrd_global
[3637]416
[3766]417    IMPLICIT NONE
[3637]418
[3766]419    PRIVATE
[3637]420
421!
[3766]422!-- Public functions
423    PUBLIC                                                                     &
424       module_interface_parin,                                                 &
425       module_interface_check_parameters,                                      &
426       module_interface_check_data_output_ts,                                  &
427       module_interface_check_data_output_pr,                                  &
428       module_interface_check_data_output,                                     &
429       module_interface_init_masks,                                            &
430       module_interface_define_netcdf_grid,                                    &
431       module_interface_init_arrays,                                           &
432       module_interface_init,                                                  &
433       module_interface_init_checks,                                           &
434       module_interface_header,                                                &
435       module_interface_actions,                                               &
[3931]436       module_interface_non_advective_processes,                               &
[3887]437       module_interface_exchange_horiz,                                        &
[3837]438       module_interface_prognostic_equations,                                  &
[3766]439       module_interface_swap_timelevel,                                        &
440       module_interface_3d_data_averaging,                                     &
441       module_interface_data_output_2d,                                        &
442       module_interface_data_output_3d,                                        &
443       module_interface_statistics,                                            &
444       module_interface_rrd_global,                                            &
445       module_interface_wrd_global,                                            &
446       module_interface_rrd_local,                                             &
447       module_interface_wrd_local,                                             &
448       module_interface_last_actions
[3637]449
450
[3766]451    INTERFACE module_interface_parin
452       MODULE PROCEDURE module_interface_parin
453    END INTERFACE module_interface_parin
[3637]454
[3766]455    INTERFACE module_interface_check_parameters
456       MODULE PROCEDURE module_interface_check_parameters
457    END INTERFACE module_interface_check_parameters
[3637]458
[3766]459    INTERFACE module_interface_check_data_output_ts
460       MODULE PROCEDURE module_interface_check_data_output_ts
461    END INTERFACE module_interface_check_data_output_ts
[3700]462
[3766]463    INTERFACE module_interface_check_data_output_pr
464       MODULE PROCEDURE module_interface_check_data_output_pr
465    END INTERFACE module_interface_check_data_output_pr
[3637]466
[3766]467    INTERFACE module_interface_check_data_output
468       MODULE PROCEDURE module_interface_check_data_output
469    END INTERFACE module_interface_check_data_output
[3637]470
[3766]471    INTERFACE module_interface_init_masks
472       MODULE PROCEDURE module_interface_init_masks
473    END INTERFACE module_interface_init_masks
[3687]474
[3766]475    INTERFACE module_interface_define_netcdf_grid
476       MODULE PROCEDURE module_interface_define_netcdf_grid
477    END INTERFACE module_interface_define_netcdf_grid
[3637]478
[3766]479    INTERFACE module_interface_init_arrays
480       MODULE PROCEDURE module_interface_init_arrays
481    END INTERFACE module_interface_init_arrays
[3637]482
[3766]483    INTERFACE module_interface_init
484       MODULE PROCEDURE module_interface_init
485    END INTERFACE module_interface_init
[3637]486
[3766]487    INTERFACE module_interface_init_checks
488       MODULE PROCEDURE module_interface_init_checks
489    END INTERFACE module_interface_init_checks
[3711]490
[3766]491    INTERFACE module_interface_header
492       MODULE PROCEDURE module_interface_header
493    END INTERFACE module_interface_header
[3637]494
[3766]495    INTERFACE module_interface_actions
496       MODULE PROCEDURE module_interface_actions
497       MODULE PROCEDURE module_interface_actions_ij
498    END INTERFACE module_interface_actions
[3637]499
[3931]500    INTERFACE module_interface_non_advective_processes
501       MODULE PROCEDURE module_interface_non_advective_processes
502       MODULE PROCEDURE module_interface_non_advective_processes_ij
503    END INTERFACE module_interface_non_advective_processes
[3887]504   
505    INTERFACE module_interface_exchange_horiz
506       MODULE PROCEDURE module_interface_exchange_horiz
507    END INTERFACE module_interface_exchange_horiz
508   
[3837]509    INTERFACE module_interface_prognostic_equations
510       MODULE PROCEDURE module_interface_prognostic_equations
511       MODULE PROCEDURE module_interface_prognostic_equations_ij
512    END INTERFACE module_interface_prognostic_equations
513
[3766]514    INTERFACE module_interface_swap_timelevel
515       MODULE PROCEDURE module_interface_swap_timelevel
516    END INTERFACE module_interface_swap_timelevel
[3637]517
[3766]518    INTERFACE module_interface_3d_data_averaging
519       MODULE PROCEDURE module_interface_3d_data_averaging
520    END INTERFACE module_interface_3d_data_averaging
[3637]521
[3766]522    INTERFACE module_interface_data_output_2d
523       MODULE PROCEDURE module_interface_data_output_2d
524    END INTERFACE module_interface_data_output_2d
[3637]525
[3766]526    INTERFACE module_interface_data_output_3d
527       MODULE PROCEDURE module_interface_data_output_3d
528    END INTERFACE module_interface_data_output_3d
[3637]529
[3766]530    INTERFACE module_interface_statistics
531       MODULE PROCEDURE module_interface_statistics
532    END INTERFACE module_interface_statistics
[3637]533
[3766]534    INTERFACE module_interface_rrd_global
535       MODULE PROCEDURE module_interface_rrd_global
536    END INTERFACE module_interface_rrd_global
[3637]537
[3766]538    INTERFACE module_interface_wrd_global
539       MODULE PROCEDURE module_interface_wrd_global
540    END INTERFACE module_interface_wrd_global
[3637]541
[3766]542    INTERFACE module_interface_rrd_local
543       MODULE PROCEDURE module_interface_rrd_local
544    END INTERFACE module_interface_rrd_local
[3637]545
[3766]546    INTERFACE module_interface_wrd_local
547       MODULE PROCEDURE module_interface_wrd_local
548    END INTERFACE module_interface_wrd_local
[3637]549
[3766]550    INTERFACE module_interface_last_actions
551       MODULE PROCEDURE module_interface_last_actions
552    END INTERFACE module_interface_last_actions
[3637]553
[3687]554
[3766]555 CONTAINS
[3637]556
557
558!------------------------------------------------------------------------------!
559! Description:
560! ------------
561!> Read module-specific parameter namelists
562!------------------------------------------------------------------------------!
[3766]563 SUBROUTINE module_interface_parin
[3637]564
565
[3987]566    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'start' )
567
[3766]568    CALL bio_parin
569    CALL bcm_parin
570    CALL chem_parin
571    CALL flight_parin ! ToDo: rename module to match filename
572    CALL gust_parin
573    CALL im_parin
[4017]574    CALL lpm_parin     
[3766]575    CALL lsm_parin
576    ! ToDo: create parin routine for large_scale_forcing and nudging (should be seperate modules or new module switch)
577    CALL mas_parin
578    CALL nesting_offl_parin
579    CALL ocean_parin
580    CALL pcm_parin
581    CALL radiation_parin
582    CALL salsa_parin
583    CALL spectra_parin
584    CALL surface_data_output_parin
585    CALL stg_parin
586    CALL user_parin ! ToDo: make user code a single Fortran module
587    CALL usm_parin
588    CALL vm_parin
589    CALL wtm_parin
[3637]590
[3987]591    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'end' )
[3637]592
[3987]593
[3766]594 END SUBROUTINE module_interface_parin
[3637]595
596
597!------------------------------------------------------------------------------!
598! Description:
599! ------------
600!> Perform module-specific initialization checks
601!------------------------------------------------------------------------------!
[3766]602 SUBROUTINE module_interface_check_parameters
[3637]603
604
[3987]605    IF ( debug_output )  CALL debug_message( 'checking module-specific parameters', 'start' )
606
[3766]607    IF ( bulk_cloud_model )     CALL bcm_check_parameters
608    IF ( air_chemistry )        CALL chem_check_parameters
609    IF ( gust_module_enabled )  CALL gust_check_parameters
610    IF ( indoor_model )         CALL im_check_parameters
[4017]611    IF ( particle_advection )   CALL lpm_check_parameters       
[3766]612    IF ( land_surface )         CALL lsm_check_parameters
613    IF ( large_scale_forcing  .OR.  nudging )  CALL lsf_nudging_check_parameters ! ToDo: create single module switch
614    IF ( nesting_offline )      CALL nesting_offl_check_parameters
615    IF ( ocean_mode )           CALL ocean_check_parameters
616    IF ( plant_canopy )         CALL pcm_check_parameters
617    IF ( radiation )            CALL radiation_check_parameters
618    IF ( salsa )                CALL salsa_check_parameters
619    IF ( calculate_spectra )    CALL spectra_check_parameters
620    IF ( surface_output )       CALL surface_data_output_check_parameters
621    IF ( syn_turb_gen )         CALL stg_check_parameters
622    IF ( urban_surface )        CALL usm_check_parameters
623    IF ( virtual_measurement )  CALL vm_check_parameters
624    IF ( wind_turbine )         CALL wtm_check_parameters
625    IF ( user_module_enabled )  CALL user_check_parameters
[3637]626
[3987]627    IF ( debug_output )  CALL debug_message( 'checking module-specific parameters', 'end' )
[3637]628
[3987]629
[3766]630 END SUBROUTINE module_interface_check_parameters
[3637]631
632
633!------------------------------------------------------------------------------!
634! Description:
635! ------------
[3700]636!> Check module-specific data output of timeseries
637!------------------------------------------------------------------------------!
[3766]638 SUBROUTINE module_interface_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
[3700]639
640
[3766]641    INTEGER(iwp),      INTENT(IN)    ::  dots_max !< variable output array index
642    INTEGER(iwp),      INTENT(INOUT)    ::  dots_num !< variable output array index
643    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT) :: dots_label
644    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT) :: dots_unit
[3700]645
646
[3987]647    IF ( debug_output )  CALL debug_message( 'checking module-specific data output ts', 'start' )
648
[3766]649    IF ( radiation )  THEN
[3769]650       CALL radiation_check_data_output_ts( dots_max, dots_num )
[3766]651    ENDIF
[3700]652
[3766]653    IF ( user_module_enabled )  THEN
654       CALL user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
655    ENDIF
[3700]656
[3987]657    IF ( debug_output )  CALL debug_message( 'checking module-specific data output ts', 'end' )
[3700]658
[3987]659
[3766]660 END SUBROUTINE module_interface_check_data_output_ts
[3700]661
662
663!------------------------------------------------------------------------------!
664! Description:
665! ------------
[3637]666!> Check module-specific data output of profiles
667!------------------------------------------------------------------------------!
[3766]668 SUBROUTINE module_interface_check_data_output_pr( variable, var_count, unit,  &
669                                                   dopr_unit )
[3637]670
671
[3766]672    CHARACTER (LEN=*), INTENT(IN)    ::  variable  !< variable name
673    INTEGER(iwp),      INTENT(IN)    ::  var_count !< variable output array index
674    CHARACTER (LEN=*), INTENT(INOUT) ::  unit      !< physical unit of variable
675    CHARACTER (LEN=*), INTENT(OUT)   ::  dopr_unit !< local value of dopr_unit
[3637]676
[3987]677
678    IF ( debug_output )  CALL debug_message( 'checking module-specific data output pr', 'start' )
679
[3766]680    IF ( unit == 'illegal' .AND.  bulk_cloud_model )  THEN
681       CALL bcm_check_data_output_pr( variable, var_count, unit, dopr_unit )
682    ENDIF
[3637]683
[3766]684    IF ( unit == 'illegal' .AND.  air_chemistry )  THEN
685       CALL chem_check_data_output_pr( variable, var_count, unit, dopr_unit )
686    ENDIF
[3637]687
[3766]688    IF ( unit == 'illegal'  .AND.  gust_module_enabled  )  THEN
689       CALL gust_check_data_output_pr( variable, var_count, unit, dopr_unit )
690    ENDIF
[3637]691
[3766]692    IF ( unit == 'illegal' )  THEN ! ToDo: add module switch if possible
693       CALL lsm_check_data_output_pr( variable, var_count, unit, dopr_unit )
694    ENDIF
[3637]695
[3766]696    IF ( unit == 'illegal' )  THEN ! ToDo: add module switch if possible
697       CALL lsf_nudging_check_data_output_pr( variable, var_count, unit, dopr_unit )
698    ENDIF
[3637]699
[3766]700    IF ( unit == 'illegal'  .AND.  ocean_mode )  THEN
701       CALL ocean_check_data_output_pr( variable, var_count, unit, dopr_unit )
702    ENDIF
[3637]703
[3766]704    IF ( unit == 'illegal'  .AND.  radiation )  THEN
705       CALL radiation_check_data_output_pr( variable, var_count, unit, dopr_unit )
706    ENDIF
[3637]707
[3766]708    IF ( unit == 'illegal'  .AND.  user_module_enabled )  THEN
709       unit = '' ! ToDo: Seems like a hack. Find a general soultion!
710       CALL user_check_data_output_pr( variable, var_count, unit, dopr_unit )
711    ENDIF
[3637]712
[3987]713    IF ( debug_output )  CALL debug_message( 'checking module-specific data output pr', 'end' )
[3637]714
[3987]715
[3766]716 END SUBROUTINE module_interface_check_data_output_pr
[3637]717
718!------------------------------------------------------------------------------!
719! Description:
720! ------------
721!> Check module-specific 2D and 3D data output
722!------------------------------------------------------------------------------!
[3766]723 SUBROUTINE module_interface_check_data_output( variable, unit, i, j, ilen, k )
[3637]724
725
[3766]726    CHARACTER (LEN=*), INTENT(IN)    ::  variable !< variable name
727    CHARACTER (LEN=*), INTENT(INOUT) ::  unit     !< physical unit of variable
[3637]728
[3766]729    INTEGER(iwp),      INTENT(IN)    :: i         !< ToDo: remove dummy argument, instead pass string from data_output
730    INTEGER(iwp),      INTENT(IN)    :: j         !< average quantity? 0 = no, 1 = yes
731    INTEGER(iwp),      INTENT(IN)    :: ilen      !< ToDo: remove dummy argument, instead pass string from data_output
732    INTEGER(iwp),      INTENT(IN)    :: k         !< ToDo: remove dummy argument, instead pass string from data_output
[3637]733
[3987]734
735    IF ( debug_output )  CALL debug_message( 'checking module-specific data output 2d/3d', 'start' )
736
[3766]737    IF ( unit == 'illegal'  .AND.  biometeorology )  THEN
738       CALL bio_check_data_output( variable, unit, i, j, ilen, k )
739    ENDIF
[3637]740
[3766]741    IF ( unit == 'illegal'  .AND.  bulk_cloud_model  )  THEN
742       CALL bcm_check_data_output( variable, unit )
743    ENDIF
[3637]744
[3766]745    IF ( unit == 'illegal'  .AND.  air_chemistry                               &
746         .AND.  (variable(1:3) == 'kc_' .OR. variable(1:3) == 'em_') )  THEN  ! ToDo: remove aditional conditions
747       CALL chem_check_data_output( variable, unit, i, ilen, k )
748    ENDIF
[3637]749
[3766]750    IF ( unit == 'illegal'  .AND.  gust_module_enabled  )  THEN
751       CALL gust_check_data_output( variable, unit )
752    ENDIF
[3637]753
[3766]754    IF ( unit == 'illegal' )  THEN  ! ToDo: add module switch if possible
755       CALL lsm_check_data_output( variable, unit, i, ilen, k )
756    ENDIF
[3637]757
[3766]758    IF ( unit == 'illegal'  .AND.  ocean_mode )  THEN
759       CALL ocean_check_data_output( variable, unit )
760    ENDIF
[3637]761
[3766]762    IF ( unit == 'illegal'  .AND.  plant_canopy                                &
763         .AND.  variable(1:4) == 'pcm_' )  THEN  ! ToDo: remove aditional conditions
764       CALL pcm_check_data_output( variable, unit )
765    ENDIF
[3637]766
[3766]767    IF ( unit == 'illegal'  .AND.  radiation )  THEN
768       CALL radiation_check_data_output( variable, unit, i, ilen, k )
769    ENDIF
[3637]770
[3766]771    IF ( unit == 'illegal' .AND. salsa ) THEN
[3637]772       CALL salsa_check_data_output( variable, unit )
[3766]773    ENDIF
[3637]774
[3766]775    IF ( unit == 'illegal' .AND. indoor_model ) THEN
[3744]776       CALL im_check_data_output( variable, unit )
[3766]777    ENDIF
[3744]778   
[3766]779    IF ( unit == 'illegal'  .AND.  urban_surface                      &
[3637]780        .AND.  variable(1:4) == 'usm_' )  THEN  ! ToDo: remove aditional conditions
781       CALL usm_check_data_output( variable, unit )
[3766]782    ENDIF
[3637]783
[3766]784    IF ( unit == 'illegal'  .AND.  user_module_enabled )  THEN
785       unit = ''
786       CALL user_check_data_output( variable, unit )
787    ENDIF
[3637]788
[3987]789    IF ( debug_output )  CALL debug_message( 'checking module-specific data output 2d/3d', 'end' )
[3637]790
[3987]791
[3766]792 END SUBROUTINE module_interface_check_data_output
[3637]793
794
795!------------------------------------------------------------------------------!
796!
797! Description:
798! ------------
[3687]799!> Interface for init_masks. ToDo: get rid of these redundant calls!
800!------------------------------------------------------------------------------!
[3766]801 SUBROUTINE module_interface_init_masks( variable, unit )
[3687]802
803
[3766]804    CHARACTER (LEN=*), INTENT(IN)    ::  variable !< variable name
805    CHARACTER (LEN=*), INTENT(INOUT) ::  unit     !< physical unit of variable
[3687]806
[3987]807
808    IF ( debug_output )  CALL debug_message( 'initializing module-specific masks', 'start' )
809
[3766]810    IF ( unit == 'illegal'  .AND.  air_chemistry                               &
811         .AND.  (variable(1:3) == 'kc_' .OR. variable(1:3) == 'em_') )  THEN  ! ToDo: remove aditional conditions
812       CALL chem_check_data_output( variable, unit, 0, 0, 0 )
813    ENDIF
[3687]814
[3766]815    IF ( unit == 'illegal'  .AND.  radiation )  THEN
816       CALL radiation_check_data_output( variable, unit, 0, 0, 0 )
817    ENDIF
[3687]818
[3766]819    IF ( unit == 'illegal'  .AND.  salsa )  THEN
820       CALL salsa_check_data_output( variable, unit )
821    ENDIF
[3687]822
[3766]823    IF ( unit == 'illegal'  .AND.  user_module_enabled )  THEN
824       unit = ''
825       CALL user_check_data_output( variable, unit )
826    ENDIF
[3687]827
[3987]828    IF ( debug_output )  CALL debug_message( 'initializing module-specific masks', 'end' )
[3687]829
[3987]830
[3766]831 END SUBROUTINE module_interface_init_masks
[3687]832
833
834!------------------------------------------------------------------------------!
835!
836! Description:
837! ------------
[3637]838!> Define appropriate grid for module-specific netcdf output variables.
839!------------------------------------------------------------------------------!
[3766]840 SUBROUTINE module_interface_define_netcdf_grid( var, found,                   &
841                                                 grid_x, grid_y, grid_z )
[3637]842
843
[3766]844    CHARACTER (LEN=*), INTENT(IN)  ::  var    !< variable name
845    LOGICAL,           INTENT(OUT) ::  found  !< indicates if variable was found
846    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x !< netcdf dimension in x-direction
847    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y !< netcdf dimension in y-direction
848    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z !< netcdf dimension in z-direction
[3987]849
850
851    IF ( debug_output )  CALL debug_message( 'defining module-specific netcdf grids', 'start' )
[3649]852!
[3766]853!-- As long as no action is done in this subroutine, initialize strings with
854!-- intent(out) attribute, in order to avoid compiler warnings.
855    found  = .FALSE.
856    grid_x = 'none'
857    grid_y = 'none'
858    grid_z = 'none'
859!
860!-- Use var to avoid compiler warning about unused variable
861    IF ( var == ' ' )  RETURN
[3637]862
[3987]863    IF ( debug_output )  CALL debug_message( 'defining module-specific netcdf grids', 'end' )
864
865
[3766]866 END SUBROUTINE module_interface_define_netcdf_grid
[3637]867
868
869!------------------------------------------------------------------------------!
870! Description:
871! ------------
872!> Allocate module-specific arrays and pointers
873!------------------------------------------------------------------------------!
[3766]874 SUBROUTINE module_interface_init_arrays
[3637]875
876
[3987]877    IF ( debug_output )  CALL debug_message( 'initializing module-specific arrays', 'start' )
[3885]878
[3766]879    IF ( bulk_cloud_model    )  CALL bcm_init_arrays
880    IF ( air_chemistry       )  CALL chem_init_arrays
881    IF ( gust_module_enabled )  CALL gust_init_arrays
882    IF ( land_surface        )  CALL lsm_init_arrays
883    IF ( ocean_mode          )  CALL ocean_init_arrays
884    IF ( salsa               )  CALL salsa_init_arrays
885    IF ( urban_surface       )  CALL usm_init_arrays
886    IF ( surface_output      )  CALL surface_data_output_init_arrays
887    IF ( wind_turbine        )  CALL wtm_init_arrays
888    IF ( user_module_enabled )  CALL user_init_arrays
[3685]889
[3987]890    IF ( debug_output )  CALL debug_message( 'initializing module-specific arrays', 'end' )
[3685]891
[3885]892
[3766]893 END SUBROUTINE module_interface_init_arrays
[3637]894
895
896!------------------------------------------------------------------------------!
897! Description:
898! ------------
899!> Perform module-specific initialization
900!------------------------------------------------------------------------------!
[3766]901 SUBROUTINE module_interface_init
[3637]902
903
[3987]904    IF ( debug_output )  CALL debug_message( 'module-specific initialization', 'start' )
[3885]905
[3766]906    IF ( biometeorology      )  CALL bio_init
907    IF ( bulk_cloud_model    )  CALL bcm_init
908    IF ( air_chemistry       )  CALL chem_init
909    IF ( virtual_flight      )  CALL flight_init
910    IF ( gust_module_enabled )  CALL gust_init
911    IF ( indoor_model        )  CALL im_init
[4017]912    IF ( particle_advection  )  CALL lpm_init   
[3766]913    IF ( large_scale_forcing )  CALL lsf_init
914    IF ( land_surface        )  CALL lsm_init
915    IF ( nudging             )  CALL nudge_init
916    IF ( ocean_mode          )  CALL ocean_init
917    IF ( plant_canopy        )  CALL pcm_init
918    IF ( salsa               )  CALL salsa_init
919    IF ( urban_surface       )  CALL usm_init
920    IF ( virtual_measurement )  CALL vm_init
921    IF ( wind_turbine        )  CALL wtm_init
922    IF ( radiation           )  CALL radiation_init
923    IF ( user_module_enabled )  CALL user_init
[3685]924
[3987]925    IF ( debug_output )  CALL debug_message( 'module-specific initialization', 'end' )
[3685]926
[3885]927
[3766]928 END SUBROUTINE module_interface_init
[3637]929
930
931!------------------------------------------------------------------------------!
932! Description:
933! ------------
[3711]934!> Perform module-specific post-initialization checks
935!------------------------------------------------------------------------------!
[3766]936 SUBROUTINE module_interface_init_checks
[3711]937
938
[3987]939    IF ( debug_output )  CALL debug_message( 'module-specific post-initialization checks', 'start' )
940
[3766]941    IF ( biometeorology      )  CALL bio_init_checks
[3711]942
[3987]943    IF ( debug_output )  CALL debug_message( 'module-specific post-initialization checks', 'end' )
[3711]944
[3987]945
[3766]946 END SUBROUTINE module_interface_init_checks
[3711]947
948
949!------------------------------------------------------------------------------!
950! Description:
951! ------------
[3637]952!> Gather module-specific header output
953!------------------------------------------------------------------------------!
[3766]954 SUBROUTINE module_interface_header( io )
[3637]955
956
[3766]957    INTEGER(iwp), INTENT(IN) ::  io  !< unit of the output file
[3637]958
959
[3987]960    IF ( debug_output )  CALL debug_message( 'module-specific header output', 'start' )
961
[3766]962    IF ( biometeorology      )  CALL bio_header ( io )
963    IF ( bulk_cloud_model    )  CALL bcm_header( io )
964    IF ( air_chemistry       )  CALL chem_header ( io )
965    IF ( virtual_flight      )  CALL flight_header( io )
966    IF ( gust_module_enabled )  CALL gust_header( io )
[4017]967    IF ( particle_advection  )  CALL lpm_header( io )   
[3766]968    IF ( land_surface        )  CALL lsm_header( io )
969    IF ( large_scale_forcing )  CALL lsf_nudging_header( io )
970    IF ( nesting_offline     )  CALL nesting_offl_header( io )
971    IF ( ocean_mode          )  CALL ocean_header( io )
972    IF ( plant_canopy        )  CALL pcm_header( io )
973    IF ( radiation           )  CALL radiation_header( io )
974    IF ( salsa               )  CALL salsa_header( io )
975    IF ( calculate_spectra   )  CALL spectra_header( io )
976    IF ( syn_turb_gen        )  CALL stg_header( io )
977    IF ( user_module_enabled )  CALL user_header( io )
[3637]978
[3987]979    IF ( debug_output )  CALL debug_message( 'module-specific header output', 'end' )
[3637]980
[3987]981
[3766]982 END SUBROUTINE module_interface_header
[3637]983
984
985!------------------------------------------------------------------------------!
986! Description:
987! ------------
[3874]988!> Perform module-specific actions while in time-integration (vector-optimized)
[3637]989!------------------------------------------------------------------------------!
[3766]990 SUBROUTINE module_interface_actions( location )
[3637]991
992
[3766]993    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
[3637]994
995
[3870]996    IF ( bulk_cloud_model    )  CALL bcm_actions( location )
[3877]997    IF ( air_chemistry       )  CALL chem_actions( location )
[3766]998    IF ( gust_module_enabled )  CALL gust_actions( location )
[4017]999    IF ( particle_advection  )  CALL lpm_actions( location )   
[3873]1000    IF ( ocean_mode          )  CALL ocean_actions( location )
[3871]1001    IF ( salsa               )  CALL salsa_actions( location )
[3875]1002    IF ( wind_turbine        )  CALL wtm_actions( location )
[3766]1003    IF ( user_module_enabled )  CALL user_actions( location )
[3684]1004
1005
[3766]1006 END SUBROUTINE module_interface_actions
[3637]1007
1008
1009!------------------------------------------------------------------------------!
1010! Description:
1011! ------------
[3874]1012!> Perform module-specific actions while in time-integration (cache-optimized)
[3637]1013!------------------------------------------------------------------------------!
[3766]1014 SUBROUTINE module_interface_actions_ij( i, j, location )
[3637]1015
1016
[3766]1017    INTEGER(iwp),      INTENT(IN) ::  i         !< grid index in x-direction
1018    INTEGER(iwp),      INTENT(IN) ::  j         !< grid index in y-direction
1019    CHARACTER (LEN=*), INTENT(IN) ::  location  !< call location string
[3637]1020
1021
[3870]1022    IF ( bulk_cloud_model    )  CALL bcm_actions( i, j, location )
[3877]1023    IF ( air_chemistry       )  CALL chem_actions( i, j, location )
[3766]1024    IF ( gust_module_enabled )  CALL gust_actions( i, j, location )
[3873]1025    IF ( ocean_mode          )  CALL ocean_actions( i, j, location )
[3871]1026    IF ( salsa               )  CALL salsa_actions( i, j, location )
[3875]1027    IF ( wind_turbine        )  CALL wtm_actions( i, j, location )
[3766]1028    IF ( user_module_enabled )  CALL user_actions( i, j, location )
[3684]1029
1030
[3766]1031 END SUBROUTINE module_interface_actions_ij
[3637]1032
1033
1034!------------------------------------------------------------------------------!
1035! Description:
1036! ------------
[3987]1037!> Compute module-specific non_advective_processes (vector-optimized)
[3874]1038!------------------------------------------------------------------------------!
[3931]1039 SUBROUTINE module_interface_non_advective_processes()
[3874]1040
1041
[3931]1042    IF ( bulk_cloud_model    )  CALL bcm_non_advective_processes()
[3930]1043    IF ( air_chemistry       )  CALL chem_non_advective_processes()
[3956]1044    IF ( salsa               )  CALL salsa_non_advective_processes()
[3874]1045
1046
[3931]1047 END SUBROUTINE module_interface_non_advective_processes
[3874]1048
1049
1050!------------------------------------------------------------------------------!
1051! Description:
1052! ------------
[3931]1053!> Compute module-specific non_advective_processes (cache-optimized)
[3837]1054!------------------------------------------------------------------------------!
[3931]1055 SUBROUTINE module_interface_non_advective_processes_ij( i, j )
[3874]1056
1057
1058    INTEGER(iwp), INTENT(IN) ::  i            !< grid index in x-direction
1059    INTEGER(iwp), INTENT(IN) ::  j            !< grid index in y-direction
1060
1061
[3956]1062    IF ( bulk_cloud_model    )  CALL bcm_non_advective_processes( i, j )
[3930]1063    IF ( air_chemistry       )  CALL chem_non_advective_processes( i, j )
[3956]1064    IF ( salsa               )  CALL salsa_non_advective_processes( i, j )
[3874]1065
1066
[3931]1067 END SUBROUTINE module_interface_non_advective_processes_ij
[3887]1068 
1069!------------------------------------------------------------------------------!
1070! Description:
1071! ------------
1072!> Exchange horiz for module-specific quantities
1073!------------------------------------------------------------------------------!
1074 SUBROUTINE module_interface_exchange_horiz()
[3874]1075
1076
[3987]1077    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'start' )
1078
[3887]1079    IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz()
[3929]1080    IF ( air_chemistry       )  CALL chem_exchange_horiz_bounds()
[3956]1081    IF ( salsa               )  CALL salsa_exchange_horiz_bounds()
[3887]1082
[3987]1083    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'end' )
1084
1085
[3887]1086 END SUBROUTINE module_interface_exchange_horiz
1087
1088
[3874]1089!------------------------------------------------------------------------------!
1090! Description:
1091! ------------
1092!> Compute module-specific prognostic_equations (vector-optimized)
1093!------------------------------------------------------------------------------!
[3837]1094 SUBROUTINE module_interface_prognostic_equations()
1095
1096
[3870]1097    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations()
[3880]1098    IF ( air_chemistry       )  CALL chem_prognostic_equations()
[3837]1099    IF ( gust_module_enabled )  CALL gust_prognostic_equations()
[3840]1100    IF ( ocean_mode          )  CALL ocean_prognostic_equations()
[3864]1101    IF ( salsa               )  CALL salsa_prognostic_equations()
[3837]1102
1103
1104 END SUBROUTINE module_interface_prognostic_equations
1105
1106
1107!------------------------------------------------------------------------------!
1108! Description:
1109! ------------
[3874]1110!> Compute module-specific prognostic_equations (cache-optimized)
[3837]1111!------------------------------------------------------------------------------!
1112 SUBROUTINE module_interface_prognostic_equations_ij( i, j, i_omp_start, tn )
1113
1114
1115    INTEGER(iwp), INTENT(IN) ::  i            !< grid index in x-direction
1116    INTEGER(iwp), INTENT(IN) ::  j            !< grid index in y-direction
1117    INTEGER(iwp), INTENT(IN) ::  i_omp_start  !< first loop index of i-loop in prognostic_equations
1118    INTEGER(iwp), INTENT(IN) ::  tn           !< task number of openmp task
1119
1120
[3870]1121    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations( i, j, i_omp_start, tn )
[3880]1122    IF ( air_chemistry       )  CALL chem_prognostic_equations( i, j, i_omp_start, tn )
[3837]1123    IF ( gust_module_enabled )  CALL gust_prognostic_equations( i, j, i_omp_start, tn )
[3840]1124    IF ( ocean_mode          )  CALL ocean_prognostic_equations( i, j, i_omp_start, tn )
[3864]1125    IF ( salsa               )  CALL salsa_prognostic_equations( i, j, i_omp_start, tn )
[3837]1126
1127
1128 END SUBROUTINE module_interface_prognostic_equations_ij
1129
1130
1131!------------------------------------------------------------------------------!
1132! Description:
1133! ------------
[3637]1134!> Swap the timelevel pointers for module-specific arrays
1135!------------------------------------------------------------------------------!
[3766]1136 SUBROUTINE module_interface_swap_timelevel ( swap_mode )
[3637]1137
1138
[3766]1139    INTEGER(iwp), INTENT(IN) :: swap_mode !< determines procedure of pointer swap
[3637]1140
[3987]1141
1142    IF ( debug_output_timestep )  CALL debug_message( 'module-specific swap timelevel', 'start' )
1143
[3766]1144    IF ( bulk_cloud_model    )  CALL bcm_swap_timelevel( swap_mode )
1145    IF ( air_chemistry       )  CALL chem_swap_timelevel( swap_mode )
1146    IF ( gust_module_enabled )  CALL gust_swap_timelevel( swap_mode )
1147    IF ( land_surface        )  CALL lsm_swap_timelevel( swap_mode )
1148    IF ( ocean_mode          )  CALL ocean_swap_timelevel( swap_mode )
1149    IF ( salsa               )  CALL salsa_swap_timelevel( swap_mode )
1150    IF ( urban_surface       )  CALL usm_swap_timelevel( swap_mode )
[3637]1151
[3987]1152    IF ( debug_output_timestep )  CALL debug_message( 'module-specific swap timelevel', 'end' )
[3637]1153
[3987]1154
[3766]1155 END SUBROUTINE module_interface_swap_timelevel
[3637]1156
1157
1158!------------------------------------------------------------------------------!
1159!
1160! Description:
1161! ------------
1162!> Perform module-specific averaging of 3D data
1163!------------------------------------------------------------------------------!
[3766]1164 SUBROUTINE module_interface_3d_data_averaging( mode, variable )
[3637]1165
1166
[3766]1167    CHARACTER (LEN=*), INTENT(IN) ::  mode     !< averaging interface mode
1168    CHARACTER (LEN=*), INTENT(IN) ::  variable !< variable name
[3637]1169
[3987]1170
1171    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data averaging', 'start' )
1172
[3766]1173    IF ( biometeorology      )  CALL bio_3d_data_averaging( mode, variable )
1174    IF ( bulk_cloud_model    )  CALL bcm_3d_data_averaging( mode, variable )
1175    IF ( air_chemistry       )  CALL chem_3d_data_averaging( mode, variable )
1176    IF ( gust_module_enabled )  CALL gust_3d_data_averaging( mode, variable )
1177    IF ( land_surface        )  CALL lsm_3d_data_averaging( mode, variable )
1178    IF ( ocean_mode          )  CALL ocean_3d_data_averaging( mode, variable )
1179    IF ( radiation           )  CALL radiation_3d_data_averaging( mode, variable )
1180    IF ( salsa               )  CALL salsa_3d_data_averaging( mode, variable )
1181    IF ( urban_surface       )  CALL usm_3d_data_averaging( mode, variable )
1182    IF ( user_module_enabled )  CALL user_3d_data_averaging( mode, variable )
[3637]1183
[3987]1184    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data averaging', 'end' )
[3637]1185
[3987]1186
[3766]1187 END SUBROUTINE module_interface_3d_data_averaging
[3637]1188
1189!------------------------------------------------------------------------------!
1190!
1191! Description:
1192! ------------
1193!> Define module-specific 2D output variables
1194!------------------------------------------------------------------------------!
[3766]1195 SUBROUTINE module_interface_data_output_2d( av, variable, found, grid, mode,  &
1196                                             local_pf, two_d, nzb_do, nzt_do,  &
1197                                             fill_value )
[3637]1198
[3766]1199    INTEGER(iwp),      INTENT(IN)    ::  av         !< flag for (non-)average output
1200    CHARACTER (LEN=*), INTENT(IN)    ::  variable   !< variable name
1201    LOGICAL,           INTENT(INOUT) ::  found      !< flag if output variable is found
1202    CHARACTER (LEN=*), INTENT(INOUT) ::  grid       !< name of vertical grid
1203    CHARACTER (LEN=*), INTENT(IN)    ::  mode       !< either 'xy', 'xz' or 'yz'
1204    LOGICAL,           INTENT(OUT)   ::  two_d      !< flag for 2D variables
1205    INTEGER(iwp),      INTENT(IN)    ::  nzb_do     !< vertical output index (bottom) (usually 0)
1206    INTEGER(iwp),      INTENT(IN)    ::  nzt_do     !< vertical output index (top) (usually nz_do3d)
1207    REAL(wp),          INTENT(IN)    ::  fill_value !< to be removed
[3637]1208
[4004]1209    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do), INTENT(INOUT) ::  local_pf !< ToDo: can also be kind=sp
[3637]1210
1211
[3987]1212    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 2d data output', 'start' )
1213
[3766]1214    IF ( .NOT. found  .AND.  biometeorology )  THEN
1215       CALL bio_data_output_2d(                                                &
1216               av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do      &
1217            )
1218    ENDIF
[3637]1219
[3766]1220    IF ( .NOT. found  .AND.  bulk_cloud_model )  THEN
1221       CALL bcm_data_output_2d(                                                &
1222               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do&
1223            )
1224    ENDIF
[3637]1225
[3766]1226    IF ( .NOT. found  .AND.  air_chemistry )  THEN
1227       CALL chem_data_output_2d(                                               &
1228               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, fill_value &
1229            )
1230    ENDIF
[3637]1231
[3766]1232    IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
1233       CALL gust_data_output_2d(                                               &
1234               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, fill_value &
1235            )
1236    ENDIF
[3637]1237
[3766]1238    IF ( .NOT. found  .AND.  land_surface )  THEN
1239       CALL lsm_data_output_2d(                                                &
1240               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do&
1241            )
1242    ENDIF
[3637]1243
[3766]1244    IF ( .NOT. found  .AND.  ocean_mode )  THEN
1245       CALL ocean_data_output_2d(                                              &
1246               av, variable, found, grid, mode, local_pf, nzb_do, nzt_do       &
1247            )
1248    ENDIF
[3637]1249
[4008]1250    IF ( .NOT. found  .AND.  radiation )  THEN
1251       CALL radiation_data_output_2d(                                          &
[3766]1252               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do&
1253            )
1254    ENDIF
[3637]1255
[4008]1256    IF ( .NOT. found  .AND.  salsa )  THEN
1257       CALL salsa_data_output_2d(                                              &
[3766]1258               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do&
1259            )
1260    ENDIF
[3637]1261
[3766]1262    IF ( .NOT. found  .AND.  user_module_enabled )  THEN
1263       CALL user_data_output_2d(                                               &
1264               av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do      &
1265            )
1266    ENDIF
[3637]1267
[3987]1268    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 2d data output', 'end' )
1269
1270
[3766]1271 END SUBROUTINE module_interface_data_output_2d
[3637]1272
1273
1274!------------------------------------------------------------------------------!
1275!
1276! Description:
1277! ------------
1278!> Define module-specific 3D output variables
1279!------------------------------------------------------------------------------!
[3766]1280 SUBROUTINE module_interface_data_output_3d( av, variable, found, local_pf,    &
1281                                             fill_value, resorted, nzb_do, nzt_do )
[3637]1282
1283
[3766]1284    INTEGER(iwp),      INTENT(IN)    ::  av         !< flag for (non-)average output
1285    CHARACTER (LEN=*), INTENT(IN)    ::  variable   !< variable name
1286    LOGICAL,           INTENT(INOUT) ::  found      !< flag if output variable is found
1287    REAL(wp),          INTENT(IN)    ::  fill_value !< ToDo: refactor
1288    LOGICAL,           INTENT(OUT)   ::  resorted   !< flag if output has been resorted
1289    INTEGER(iwp),      INTENT(IN)    ::  nzb_do     !< vertical output index (bottom) (usually 0)
1290    INTEGER(iwp),      INTENT(IN)    ::  nzt_do     !< vertical output index (top) (usually nz_do3d)
[3637]1291
[4004]1292    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do), INTENT(INOUT) ::  local_pf
[3637]1293
1294
[3987]1295    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data output', 'start' )
1296
[3766]1297    IF ( .NOT. found  .AND.  biometeorology )  THEN
1298       CALL bio_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1299       resorted = .FALSE.
1300    ENDIF
[3637]1301
[3766]1302    IF ( .NOT. found  .AND.  bulk_cloud_model )  THEN
1303       CALL bcm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1304       resorted = .TRUE.
1305    ENDIF
[3637]1306
[3766]1307    IF ( .NOT. found  .AND.  air_chemistry )  THEN
1308       CALL chem_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1309       resorted = .TRUE.
1310    ENDIF
[3637]1311
[3766]1312    IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
1313       CALL gust_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1314       resorted = .TRUE.
1315    ENDIF
[3744]1316   
[3766]1317    IF ( .NOT. found  .AND.  indoor_model )  THEN
1318       CALL im_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1319       resorted = .TRUE.
1320    ENDIF
[3637]1321
[3766]1322    IF ( .NOT. found  .AND.  ocean_mode )  THEN
1323       CALL ocean_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1324       resorted = .TRUE.
1325    ENDIF
[3637]1326
[3766]1327    IF ( .NOT. found  .AND.  plant_canopy )  THEN
1328       CALL pcm_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1329       resorted = .TRUE.
1330    ENDIF
[3637]1331
[4008]1332    IF ( .NOT. found  .AND.  radiation )  THEN
1333       CALL radiation_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
[3766]1334       resorted = .TRUE.
1335    ENDIF
[3637]1336
[4008]1337    IF ( .NOT. found  .AND.  salsa )  THEN
1338       CALL salsa_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
[3766]1339       resorted = .TRUE.
1340    ENDIF
[3637]1341
[3766]1342    IF ( .NOT. found  .AND.  user_module_enabled )  THEN
1343       CALL user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1344       resorted = .TRUE.
1345    ENDIF
[3637]1346
[3987]1347    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data output', 'end' )
[3637]1348
[3987]1349
[3766]1350 END SUBROUTINE module_interface_data_output_3d
[3637]1351
1352
1353!------------------------------------------------------------------------------!
1354! Description:
1355! ------------
1356!> Compute module-specific profile and timeseries data
1357!------------------------------------------------------------------------------!
[3766]1358 SUBROUTINE module_interface_statistics( mode, sr, tn, dots_max )
[3637]1359
1360
[3766]1361    CHARACTER (LEN=*), INTENT(IN) ::  mode     !< statistical analysis mode
1362    INTEGER(iwp),      INTENT(IN) ::  sr       !<
1363    INTEGER(iwp),      INTENT(IN) ::  tn       !<
1364    INTEGER(iwp),      INTENT(IN) ::  dots_max !< maximum number of timeseries
[3637]1365
[3987]1366
1367    IF ( debug_output_timestep )  CALL debug_message( 'module-specific statistics', 'start' )
1368
[3766]1369    IF ( gust_module_enabled )  CALL gust_statistics( mode, sr, tn, dots_max )
1370    IF ( air_chemistry       )  CALL chem_statistics( mode, sr, tn )
1371    IF ( user_module_enabled )  CALL user_statistics( mode, sr, tn )
[3637]1372
[3987]1373    IF ( debug_output_timestep )  CALL debug_message( 'module-specific statistics', 'end' )
[3637]1374
[3987]1375
[3766]1376 END SUBROUTINE module_interface_statistics
[3637]1377
1378
1379!------------------------------------------------------------------------------!
1380! Description:
1381! ------------
1382!> Read module-specific restart data globaly shared by all MPI ranks
1383!------------------------------------------------------------------------------!
[3766]1384 SUBROUTINE module_interface_rrd_global( found )
[3637]1385
1386
[3806]1387    LOGICAL, INTENT(INOUT) ::  found    !< flag if variable was found
[3637]1388
[3987]1389
1390    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'start' )
1391
[3766]1392    IF ( .NOT. found )  CALL bio_rrd_global( found ) ! ToDo: change interface to pass variable
1393    IF ( .NOT. found )  CALL bcm_rrd_global( found ) ! ToDo: change interface to pass variable
1394    IF ( .NOT. found )  CALL flight_rrd_global( found ) ! ToDo: change interface to pass variable
1395    IF ( .NOT. found )  CALL gust_rrd_global( found ) ! ToDo: change interface to pass variable
[4017]1396    IF ( .NOT. found )  CALL lpm_rrd_global( found ) ! ToDo: change interface to pass variable       
[3766]1397    IF ( .NOT. found )  CALL ocean_rrd_global( found ) ! ToDo: change interface to pass variable
1398    IF ( .NOT. found )  CALL stg_rrd_global ( found ) ! ToDo: change interface to pass variable
1399    IF ( .NOT. found )  CALL wtm_rrd_global( found ) ! ToDo: change interface to pass variable
1400    IF ( .NOT. found )  CALL surface_data_output_rrd_global( found )
1401    IF ( .NOT. found )  CALL user_rrd_global( found ) ! ToDo: change interface to pass variable
[3637]1402
[3987]1403    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'end' )
[3637]1404
[3987]1405
[3766]1406 END SUBROUTINE module_interface_rrd_global
[3637]1407
1408
1409!------------------------------------------------------------------------------!
1410! Description:
1411! ------------
1412!> Write module-specific restart data globaly shared by all MPI ranks
1413!------------------------------------------------------------------------------!
[3766]1414 SUBROUTINE module_interface_wrd_global
[3637]1415
1416
[3987]1417    IF ( debug_output )  CALL debug_message( 'module-specific write global restart data', 'start' )
1418
[3766]1419    IF ( biometeorology )       CALL bio_wrd_global
1420    IF ( bulk_cloud_model )     CALL bcm_wrd_global
1421    IF ( virtual_flight )       CALL flight_wrd_global
1422    IF ( gust_module_enabled )  CALL gust_wrd_global
1423    IF ( ocean_mode )           CALL ocean_wrd_global
1424    IF ( syn_turb_gen )         CALL stg_wrd_global
1425    IF ( wind_turbine )         CALL wtm_wrd_global
1426    IF ( surface_output )       CALL surface_data_output_wrd_global
1427    IF ( user_module_enabled )  CALL user_wrd_global
[3637]1428
[3987]1429    IF ( debug_output )  CALL debug_message( 'module-specific write global restart data', 'end' )
[3637]1430
[3987]1431
[3766]1432 END SUBROUTINE module_interface_wrd_global
[3637]1433
1434
1435!------------------------------------------------------------------------------!
1436! Description:
1437! ------------
1438!> Read module-specific restart data specific to local MPI ranks
1439!------------------------------------------------------------------------------!
[3767]1440 SUBROUTINE module_interface_rrd_local( map_index,                             &
[3766]1441                                        nxlf, nxlc, nxl_on_file,               &
1442                                        nxrf, nxrc, nxr_on_file,               &
1443                                        nynf, nync, nyn_on_file,               &
1444                                        nysf, nysc, nys_on_file,               &
1445                                        tmp_2d, tmp_3d, found )
[3637]1446
1447
[3806]1448    INTEGER(iwp), INTENT(IN)  ::  map_index    !<
1449    INTEGER(iwp), INTENT(IN)  ::  nxlc         !<
1450    INTEGER(iwp), INTENT(IN)  ::  nxlf         !<
1451    INTEGER(iwp), INTENT(IN)  ::  nxl_on_file  !<
1452    INTEGER(iwp), INTENT(IN)  ::  nxrc         !<
1453    INTEGER(iwp), INTENT(IN)  ::  nxrf         !<
1454    INTEGER(iwp), INTENT(IN)  ::  nxr_on_file  !<
1455    INTEGER(iwp), INTENT(IN)  ::  nync         !<
1456    INTEGER(iwp), INTENT(IN)  ::  nynf         !<
1457    INTEGER(iwp), INTENT(IN)  ::  nyn_on_file  !<
1458    INTEGER(iwp), INTENT(IN)  ::  nysc         !<
1459    INTEGER(iwp), INTENT(IN)  ::  nysf         !<
1460    INTEGER(iwp), INTENT(IN)  ::  nys_on_file  !<
1461    LOGICAL,      INTENT(INOUT) ::  found        !< flag if variable was found
[3637]1462
[3766]1463    REAL(wp), DIMENSION(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp), INTENT(OUT) :: tmp_2d   !<
1464    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp), INTENT(OUT) :: tmp_3d   !<
[3637]1465
1466
[3987]1467    IF ( debug_output )  CALL debug_message( 'module-specific read local restart data', 'start' )
1468
[3766]1469    IF ( .NOT. found ) CALL bio_rrd_local(                                     &
1470                               found                                           &
1471                            )
[3650]1472
[3766]1473    IF ( .NOT. found ) CALL bcm_rrd_local(                                     &
[3767]1474                               map_index,                                      &
[3766]1475                               nxlf, nxlc, nxl_on_file,                        &
1476                               nxrf, nxrc, nxr_on_file,                        &
1477                               nynf, nync, nyn_on_file,                        &
1478                               nysf, nysc, nys_on_file,                        &
1479                               tmp_2d, tmp_3d, found                           &
1480                            ) ! ToDo: change interface to pass variable
[3637]1481
[3766]1482    IF ( .NOT. found ) CALL chem_rrd_local(                                    &
[3767]1483                               map_index,                                      &
[3766]1484                               nxlf, nxlc, nxl_on_file,                        &
1485                               nxrf, nxrc, nxr_on_file,                        &
1486                               nynf, nync, nyn_on_file,                        &
1487                               nysf, nysc, nys_on_file,                        &
1488                               tmp_3d, found                                   &
1489                            ) ! ToDo: change interface to pass variable
[3637]1490
[3766]1491    IF ( .NOT. found ) CALL gust_rrd_local(                                    &
[3767]1492                               map_index,                                      &
[3766]1493                               nxlf, nxlc, nxl_on_file,                        &
1494                               nxrf, nxrc, nxr_on_file,                        &
1495                               nynf, nync, nyn_on_file,                        &
1496                               nysf, nysc, nys_on_file,                        &
1497                               tmp_2d, tmp_3d, found                           &
1498                            ) ! ToDo: change interface to pass variable
[3637]1499
[4017]1500    IF ( .NOT. found ) CALL lpm_rrd_local(                                     &
1501                               map_index,                                      &
1502                               nxlf, nxlc, nxl_on_file,                        &
1503                               nxrf, nxrc, nxr_on_file,                        &
1504                               nynf, nync, nyn_on_file,                        &
1505                               nysf, nysc, nys_on_file,                        &
1506                               tmp_3d, found                                   &
1507                            ) ! ToDo: change interface to pass variable
1508
[3766]1509    IF ( .NOT. found ) CALL lsm_rrd_local(                                     &
[3767]1510                               map_index,                                      &
[3766]1511                               nxlf, nxlc, nxl_on_file,                        &
1512                               nxrf, nxrc, nxr_on_file,                        &
1513                               nynf, nync, nyn_on_file,                        &
1514                               nysf, nysc, nys_on_file,                        &
1515                               tmp_2d, found                                   &
1516                            ) ! ToDo: change interface to pass variable
[3637]1517
[3766]1518    IF ( .NOT. found ) CALL ocean_rrd_local(                                   &
[3767]1519                               map_index,                                      &
[3766]1520                               nxlf, nxlc, nxl_on_file,                        &
1521                               nxrf, nxrc, nxr_on_file,                        &
1522                               nynf, nync, nyn_on_file,                        &
1523                               nysf, nysc, nys_on_file,                        &
[3767]1524                               tmp_3d, found                                   &
[3766]1525                            ) ! ToDo: change interface to pass variable
[3637]1526
[3766]1527    IF ( .NOT. found ) CALL radiation_rrd_local(                               &
[3767]1528                               map_index,                                      &
[3766]1529                               nxlf, nxlc, nxl_on_file,                        &
1530                               nxrf, nxrc, nxr_on_file,                        &
1531                               nynf, nync, nyn_on_file,                        &
1532                               nysf, nysc, nys_on_file,                        &
1533                               tmp_2d, tmp_3d, found                           &
1534                            ) ! ToDo: change interface to pass variable
[3637]1535
[3766]1536    IF ( .NOT. found ) CALL salsa_rrd_local(                                   &
[3767]1537                               map_index,                                      &
[3766]1538                               nxlf, nxlc, nxl_on_file,                        &
1539                               nxrf, nxrc, nxr_on_file,                        &
1540                               nynf, nync, nyn_on_file,                        &
1541                               nysf, nysc, nys_on_file,                        &
1542                               tmp_3d, found                                   &
1543                            ) ! ToDo: change interface to pass variable
[3637]1544
[3766]1545    IF ( .NOT. found ) CALL usm_rrd_local(                                     &
[3767]1546                               map_index,                                      &
[3766]1547                               nxlf, nxlc, nxl_on_file,                        &
[3767]1548                               nxrf, nxr_on_file,                              &
1549                               nynf, nyn_on_file,                              &
[3766]1550                               nysf, nysc, nys_on_file,                        &
1551                               found                                           &
1552                            ) ! ToDo: change interface to pass variable
[3762]1553!
[3766]1554!-- Surface data do not need overlap data, so do not pass these information.
1555    IF ( .NOT. found ) CALL surface_data_output_rrd_local( found )
[3731]1556                           
[3766]1557    IF ( .NOT. found ) CALL user_rrd_local(                                    &
[3767]1558                               map_index,                                      &
[3766]1559                               nxlf, nxlc, nxl_on_file,                        &
1560                               nxrf, nxrc, nxr_on_file,                        &
1561                               nynf, nync, nyn_on_file,                        &
1562                               nysf, nysc, nys_on_file,                        &
1563                               tmp_3d, found                                   &
1564                            ) ! ToDo: change interface to pass variable
[3637]1565
[3987]1566    IF ( debug_output )  CALL debug_message( 'module-specific read local restart data', 'end' )
[3637]1567
[3987]1568
[3766]1569 END SUBROUTINE module_interface_rrd_local
[3637]1570
1571
1572!------------------------------------------------------------------------------!
1573! Description:
1574! ------------
1575!> Write module-specific restart data specific to local MPI ranks
1576!------------------------------------------------------------------------------!
[3766]1577 SUBROUTINE module_interface_wrd_local
[3637]1578
1579
[3987]1580    IF ( debug_output )  CALL debug_message( 'module-specific write local restart data', 'start' )
1581
[3766]1582    IF ( biometeorology )       CALL bio_wrd_local
1583    IF ( bulk_cloud_model )     CALL bcm_wrd_local
1584    IF ( air_chemistry )        CALL chem_wrd_local
1585    IF ( gust_module_enabled )  CALL gust_wrd_local
[4017]1586    IF ( particle_advection )   CALL lpm_wrd_local   
[3766]1587    IF ( land_surface )         CALL lsm_wrd_local
1588    IF ( ocean_mode )           CALL ocean_wrd_local
1589    IF ( radiation )            CALL radiation_wrd_local
1590    IF ( salsa )                CALL salsa_wrd_local
1591    IF ( urban_surface )        CALL usm_wrd_local
1592    IF ( surface_output )       CALL surface_data_output_wrd_local
1593    IF ( user_module_enabled )  CALL user_wrd_local
[3637]1594
[3987]1595    IF ( debug_output )  CALL debug_message( 'module-specific write local restart data', 'end' )
[3637]1596
[3987]1597
[3766]1598 END SUBROUTINE module_interface_wrd_local
[3637]1599
1600
[3687]1601!------------------------------------------------------------------------------!
1602! Description:
1603! ------------
1604!> Perform module-specific last actions before the program terminates
1605!------------------------------------------------------------------------------!
[3766]1606 SUBROUTINE module_interface_last_actions
[3687]1607
1608
[3987]1609    IF ( debug_output )  CALL debug_message( 'module-specific last actions', 'start' )
1610
[3766]1611    IF ( virtual_measurement )  CALL vm_last_actions
1612    IF ( user_module_enabled )  CALL user_last_actions
[3687]1613
[3987]1614    IF ( debug_output )  CALL debug_message( 'module-specific last actions', 'end' )
[3687]1615
[3987]1616
[3766]1617 END SUBROUTINE module_interface_last_actions
[3687]1618
[3766]1619
1620 END MODULE module_interface
Note: See TracBrowser for help on using the repository browser.