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

Last change on this file since 4008 was 4008, checked in by moh.hefny, 5 years ago

Bugfix in check radiation related variables

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