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

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

Further modularization of particle code components

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