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

Last change on this file since 4725 was 4708, checked in by suehring, 4 years ago

Bugfix, correct mapping of RRTMG heating rates, as well as incoming/outgoing radiation onto the topography-following grid; add fill values to the radiation output

  • Property svn:keywords set to Id
File size: 92.6 KB
Line 
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!
17! Copyright 1997-2020 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: module_interface.f90 4708 2020-09-28 17:42:58Z suehring $
27! pass fillvalue attribute to radiation output
28!
29! 4590 2020-07-06 14:34:59Z suehring
30! Enable mpi-io for biomet
31!
32! 4525 2020-05-10 17:05:07Z raasch
33! added restart I/O for global salsa data,
34! added restart with MPI-IO for salsa
35!
36! 4518 2020-05-04 15:44:28Z suehring
37! Call of doq_rrd_local enabled
38!
39! 4517 2020-05-03 14:29:30Z raasch
40! added restart with MPI-IO for reading local arrays
41!
42! 4514 2020-04-30 16:29:59Z suehring
43! Added global restart routines for plant-canopy model
44!
45! 4495 2020-04-13 20:11:20Z raasch
46! restart data handling with MPI-IO added
47!
48! 4414 2020-02-19 20:16:04Z suehring
49! Add module interface for basic initialization of numerics.
50!
51! 4411 2020-02-18 14:28:02Z maronga
52! Added output routines for WTM
53!
54! 4407 2020-02-13 20:31:44Z knoop
55! Changed program_debug_output_unit to 9 in dom_init call
56!
57! 4400 2020-02-10 20:32:41Z suehring
58! - Use data-output module for virtual measurement output
59! - Remove deprecated routines for virtual measurement module
60!
61! 4361 2020-01-07 12:22:38Z suehring
62! Remove unused arrays in pmc_rrd_local
63!
64! 4360 2020-01-07 11:25:50Z suehring
65! Add pcm_rrd_local and pcm_wrd_local
66!
67! 4331 2019-12-10 18:25:02Z suehring
68! Change interface for doq_check_data_output, in order to perform further
69! output checks.
70!
71! 4281 2019-10-29 15:15:39Z schwenkel
72! Added dynamics boundary conditions
73!
74! 4272 2019-10-23 15:18:57Z schwenkel
75! Further modularization of boundary conditions: moved boundary conditions to
76! respective modules
77!
78! 4268 2019-10-17 11:29:38Z schwenkel
79! Introduction of module_interface_boundary_conditions
80!
81! 4182 2019-08-22 15:20:23Z scharf
82! Corrected "Former revisions" section
83!
84! 4173 2019-08-20 12:04:06Z gronemeier
85! add vdi_internal_controls
86!
87! 4157 2019-08-14 09:19:12Z suehring
88! Call doq_init from module interface
89!
90! 4132 2019-08-02 12:34:17Z suehring
91! Bugfix in masked data output for diagnostic quantities
92!
93! 4131 2019-08-02 11:06:18Z monakurppa
94! Add output of 3D plant-canopy outputs (merge from branch resler)
95!
96! 4048 2019-06-21 21:00:21Z knoop
97! Moved turbulence_closure_mod calls into this module_interface
98!
99! 4047 2019-06-21 18:58:09Z knoop
100! Introduction of the dynamics module
101!
102! 4039 2019-06-18 10:32:41Z suehring
103! Introduce diagnostic output
104!
105! 4028 2019-06-13 12:21:37Z schwenkel
106! Further modularization of particle code components
107!
108! 4017 2019-06-06 12:16:46Z schwenkel
109! local_pf need INTENT(INOUT) attribute rather than INTENT(OUT). This is
110! because INTENT(OUT) sets the array to not-defined. Especially for outputs that
111! are not defined everywhere, e.g. land-surface outputs, this will be
112! problematic as NaN will be output.
113!
114! 3987 2019-05-22 09:52:13Z kanani
115! Introduce switchable DEBUG file output via debug_message routine
116!
117! 3956 2019-05-07 12:32:52Z monakurppa
118! - Added calls for salsa_non_advective_processes and
119!   salsa_exchange_horiz_bounds
120! - Moved the call for salsa_data_output_2d/3d before that of
121!   radiation_data_output_2d/3d. radiation_data_output_2d/3d tries to read a
122!   salsa output variable and encounters a segmentation fault for "Ntot" due
123!   to the shortoutput name
124!
125! 3931 2019-04-24 16:34:28Z schwenkel
126! Changed non_transport_physics to non_advective_processes
127!
128! 3930 2019-04-24 14:57:18Z forkel
129! Correct/complete module_interface introduction for chemistry model
130!
131! 3887 2019 -04-12 08:47:41Z schwenkel
132! Changes related to global restructuring of location messages and introduction
133! of additional debug messages
134!
135! 3880 2019 -04-08 21:43:02Z knoop
136! Add a call for salsa_prognostic_equations
137!
138! 3840 2019-03-29 10:35:52Z knoop
139! bugfix: intent of dummy arguments changed to inout
140!
141! 3770 2019-02-28 11:22:32Z moh.hefny
142! removed unused variables in module_interface_check_data_output_ts
143!
144! 3767 08:18:02Z raasch
145! unused variable file_index removed from subroutine parameter list
146!
147! 3766 2019-02-26 16:23:41Z raasch
148! first argument removed from module_interface_rrd_*, statement added to avoid
149! compiler warning about unused variable, file reformatted with respect to coding
150! standards
151!
152! 3762 2019-02-25 16:54:16Z suehring
153! only pass required arguments to surface_data_output_rrd_local
154!
155! 3747 2019-02-16 15:15:23Z gronemeier
156! Call user_init_arrays
157!
158! 3745 2019-02-15 18:57:56Z suehring
159! Add indoor model
160!
161! 3744 2019-02-15 18:38:58Z suehring
162! Removed bio_check_parameters as the method is empty.
163!
164! 3735 2019-02-12 09:52:40Z dom_dwd_user
165! Accepting variable j from check_parameters and passing it to
166! bio_check_data_output
167! Add required restart data for surface output module
168!
169! 3731 2019-02-11 13:06:27Z suehring
170! Add check_parameters routine for virtual measurements
171!
172! 3711 2019-01-31 13:44:26Z knoop
173! Introduced module_interface_init_checks for post-init checks
174!
175! 3705 2019-01-29 19:56:39Z suehring
176! Add last_actions for virtual measurements
177!
178! 3704 2019-01-29 19:51:41Z suehring
179! Some interface calls moved to module_interface + cleanup
180!
181! 3684 2019-01-20 20:20:58Z knoop
182! Bugfix: made unit intend INOUT
183!
184! 3650 2019-01-04 13:01:33Z kanani
185! Add restart routines for biometeorology
186!
187! 3649 2019-01-02 16:52:21Z suehring
188! Initialize strings, in order to avoid compiler warnings for non-initialized
189! characters with intent(out) attribute
190!
191! 3648 2019-01-02 16:35:46Z suehring
192! 3641 2018-12-23 22:10:01Z knoop
193! Initial implementation of the PALM module interface
194!
195!
196! Description:
197! ------------
198!> This is the interface between the PALM model core and all its modules.
199!>
200!> @todo Re-format module to be consistent with coding standard
201!------------------------------------------------------------------------------!
202 MODULE module_interface
203
204    USE indices,                                                               &
205        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt
206
207    USE kinds
208
209    USE pegrid,                                                                &
210        ONLY:  comm2d
211
212!
213!-- load module-specific control parameters.
214!-- ToDo: move all of them to respective module or a dedicated central module
215    USE data_output_module,                                                    &
216        ONLY:  dom_def_end,                                                    &
217               dom_finalize_output,                                            &
218               dom_init
219
220    USE dynamics_mod, &
221        ONLY:  dynamics_parin, &
222               dynamics_check_parameters, &
223               dynamics_check_data_output_ts, &
224               dynamics_check_data_output_pr, &
225               dynamics_check_data_output, &
226               dynamics_init_masks, &
227               dynamics_define_netcdf_grid, &
228               dynamics_init_arrays, &
229               dynamics_init, &
230               dynamics_init_checks, &
231               dynamics_header, &
232               dynamics_actions, &
233               dynamics_non_advective_processes, &
234               dynamics_exchange_horiz, &
235               dynamics_prognostic_equations, &
236               dynamics_boundary_conditions, &
237               dynamics_swap_timelevel, &
238               dynamics_3d_data_averaging, &
239               dynamics_data_output_2d, &
240               dynamics_data_output_3d, &
241               dynamics_statistics, &
242               dynamics_rrd_global, &
243               dynamics_rrd_local, &
244               dynamics_wrd_global, &
245               dynamics_wrd_local, &
246               dynamics_last_actions
247
248    USE turbulence_closure_mod, &
249        ONLY:  tcm_check_parameters, &
250               tcm_check_data_output, &
251               tcm_init_arrays, &
252               tcm_init, &
253               tcm_actions, &
254               tcm_prognostic_equations, &
255               tcm_boundary_conds, &
256               tcm_swap_timelevel, &
257               tcm_3d_data_averaging, &
258               tcm_data_output_2d, &
259               tcm_data_output_3d
260
261    USE control_parameters,                                                    &
262        ONLY:  air_chemistry,                                                  &
263               biometeorology,                                                 &
264               coupling_char,                                                  &
265               debug_output,                                                   &
266               debug_output_timestep,                                          &
267               indoor_model,                                                   &
268               land_surface,                                                   &
269               large_scale_forcing,                                            &
270               nesting_offline,                                                &
271               nudging,                                                        &
272               ocean_mode,                                                     &
273               plant_canopy,                                                   &
274               salsa,                                                          &
275               surface_output,                                                 &
276               syn_turb_gen,                                                   &
277               urban_surface,                                                  &
278               vdi_checks,                                                     &
279               virtual_flight,                                                 &
280               virtual_measurement,                                            &
281               wind_turbine
282
283!
284!-- load interface routines of all PALM modules
285    USE biometeorology_mod,                                                    &
286        ONLY:  bio_parin,                                                      &
287               bio_check_data_output,                                          &
288               bio_init,                                                       &
289               bio_init_checks,                                                &
290               bio_header,                                                     &
291               bio_3d_data_averaging,                                          &
292               bio_data_output_2d,                                             &
293               bio_data_output_3d,                                             &
294               bio_rrd_global,                                                 &
295               bio_rrd_local,                                                  &
296               bio_wrd_global,                                                 &
297               bio_wrd_local
298
299    USE bulk_cloud_model_mod,                                                  &
300        ONLY:  bulk_cloud_model,                                               &
301               bcm_parin,                                                      &
302               bcm_check_parameters,                                           &
303               bcm_check_data_output_pr,                                       &
304               bcm_check_data_output,                                          &
305               bcm_init_arrays,                                                &
306               bcm_init,                                                       &
307               bcm_header,                                                     &
308               bcm_actions,                                                    &
309               bcm_non_advective_processes,                                    &
310               bcm_exchange_horiz,                                             &
311               bcm_prognostic_equations,                                       &
312               bcm_boundary_conditions,                                        &
313               bcm_swap_timelevel,                                             &
314               bcm_3d_data_averaging,                                          &
315               bcm_data_output_2d,                                             &
316               bcm_data_output_3d,                                             &
317               bcm_rrd_global,                                                 &
318               bcm_wrd_global,                                                 &
319               bcm_rrd_local,                                                  &
320               bcm_wrd_local
321
322   USE chemistry_model_mod,                                                    &
323       ONLY:  chem_parin,                                                      &
324              chem_check_parameters,                                           &
325              chem_check_data_output_pr,                                       &
326              chem_check_data_output,                                          &
327              chem_exchange_horiz_bounds,                                      &
328              chem_init_arrays,                                                &
329              chem_init,                                                       &
330              chem_header,                                                     &
331              chem_actions,                                                    &
332              chem_non_advective_processes,                                    &
333              chem_prognostic_equations,                                       &
334              chem_boundary_conditions,                                        &
335              chem_swap_timelevel,                                             &
336              chem_3d_data_averaging,                                          &
337              chem_data_output_2d,                                             &
338              chem_data_output_3d,                                             &
339              chem_statistics,                                                 &
340              chem_rrd_local,                                                  &
341              chem_wrd_local
342
343    USE diagnostic_output_quantities_mod,                                      &
344        ONLY:  doq_3d_data_averaging,                                          &
345               doq_check_data_output,                                          &
346               doq_define_netcdf_grid,                                         &
347               doq_init,                                                       &
348               doq_output_2d,                                                  &
349               doq_output_3d,                                                  &
350               doq_rrd_local,                                                  &
351               doq_wrd_local
352
353    USE flight_mod,                                                            &
354        ONLY:  flight_parin,                                                   &
355               flight_header,                                                  &
356               flight_init,                                                    &
357               flight_rrd_global,                                              &
358               flight_wrd_global
359
360    USE gust_mod,                                                              &
361        ONLY:  gust_module_enabled,                                            &
362               gust_parin,                                                     &
363               gust_check_parameters,                                          &
364               gust_check_data_output_pr,                                      &
365               gust_check_data_output,                                         &
366               gust_init_arrays,                                               &
367               gust_init,                                                      &
368               gust_header,                                                    &
369               gust_actions,                                                   &
370               gust_prognostic_equations,                                      &
371               gust_swap_timelevel,                                            &
372               gust_3d_data_averaging,                                         &
373               gust_data_output_2d,                                            &
374               gust_data_output_3d,                                            &
375               gust_statistics,                                                &
376               gust_rrd_global,                                                &
377               gust_wrd_global,                                                &
378               gust_rrd_local,                                                 &
379               gust_wrd_local
380
381    USE indoor_model_mod,                                                      &
382        ONLY:  im_parin,                                                       &
383               im_check_data_output,                                           &
384               im_check_parameters,                                            &
385               im_data_output_3d,                                              &
386               im_init
387
388    USE lagrangian_particle_model_mod,                                         &
389        ONLY:  lpm_parin,                                                      &
390               lpm_header,                                                     &
391               lpm_check_parameters,                                           &
392               lpm_init_arrays,                                                &
393               lpm_init,                                                       &
394               lpm_actions,                                                    &
395               lpm_rrd_global,                                                 &
396               lpm_rrd_local,                                                  &
397               lpm_wrd_local,                                                  &
398               lpm_wrd_global
399
400    USE land_surface_model_mod,                                                &
401        ONLY:  lsm_parin,                                                      &
402               lsm_check_parameters,                                           &
403               lsm_check_data_output_pr,                                       &
404               lsm_check_data_output,                                          &
405               lsm_init_arrays,                                                &
406               lsm_init,                                                       &
407               lsm_header,                                                     &
408               lsm_swap_timelevel,                                             &
409               lsm_3d_data_averaging,                                          &
410               lsm_data_output_2d,                                             &
411               lsm_rrd_local,                                                  &
412               lsm_wrd_local
413
414    USE lsf_nudging_mod,                                                       &
415        ONLY:  lsf_nudging_check_parameters,                                   &
416               lsf_nudging_check_data_output_pr,                               &
417               lsf_init,                                                       &
418               nudge_init,                                                     &
419               lsf_nudging_header
420
421    USE multi_agent_system_mod,                                                &
422        ONLY:  mas_parin
423
424    USE nesting_offl_mod,                                                      &
425        ONLY:  nesting_offl_parin,                                             &
426               nesting_offl_check_parameters,                                  &
427               nesting_offl_header
428
429    USE ocean_mod,                                                             &
430        ONLY:  ocean_parin,                                                    &
431               ocean_check_parameters,                                         &
432               ocean_check_data_output_pr,                                     &
433               ocean_check_data_output,                                        &
434               ocean_init_arrays,                                              &
435               ocean_init,                                                     &
436               ocean_header,                                                   &
437               ocean_actions,                                                  &
438               ocean_prognostic_equations,                                     &
439               ocean_boundary_conditions,                                      &
440               ocean_swap_timelevel,                                           &
441               ocean_3d_data_averaging,                                        &
442               ocean_data_output_2d,                                           &
443               ocean_data_output_3d,                                           &
444               ocean_rrd_global,                                               &
445               ocean_wrd_global,                                               &
446               ocean_rrd_local,                                                &
447               ocean_wrd_local
448
449    USE particle_attributes,                                                   &
450        ONLY:  particle_advection
451
452    USE poismg_noopt_mod,                                                      &
453        ONLY:  poismg_noopt_init
454
455    USE plant_canopy_model_mod,                                                &
456         ONLY: pcm_parin,                                                      &
457               pcm_check_parameters,                                           &
458               pcm_check_data_output,                                          &
459               pcm_init,                                                       &
460               pcm_header,                                                     &
461               pcm_3d_data_averaging,                                          &
462               pcm_data_output_3d,                                             &
463               pcm_rrd_global,                                                 &
464               pcm_rrd_local,                                                  &
465               pcm_wrd_global,                                                 &
466               pcm_wrd_local
467
468    USE radiation_model_mod,                                                   &
469        ONLY:  radiation,                                                      &
470               radiation_parin,                                                &
471               radiation_check_parameters,                                     &
472               radiation_check_data_output_ts,                                 &
473               radiation_check_data_output_pr,                                 &
474               radiation_check_data_output,                                    &
475               radiation_init,                                                 &
476               radiation_header,                                               &
477               radiation_3d_data_averaging,                                    &
478               radiation_data_output_2d,                                       &
479               radiation_data_output_3d,                                       &
480               radiation_rrd_local,                                            &
481               radiation_wrd_local
482
483    USE salsa_mod,                                                             &
484        ONLY:  salsa_parin,                                                    &
485               salsa_check_parameters,                                         &
486               salsa_check_data_output_pr,                                     &
487               salsa_check_data_output,                                        &
488               salsa_init_arrays,                                              &
489               salsa_init,                                                     &
490               salsa_header,                                                   &
491               salsa_actions,                                                  &
492               salsa_non_advective_processes,                                  &
493               salsa_exchange_horiz_bounds,                                    &
494               salsa_prognostic_equations,                                     &
495               salsa_boundary_conditions,                                      &
496               salsa_swap_timelevel,                                           &
497               salsa_3d_data_averaging,                                        &
498               salsa_data_output_2d,                                           &
499               salsa_data_output_3d,                                           &
500               salsa_statistics,                                               &
501               salsa_rrd_global,                                               &
502               salsa_rrd_local,                                                &
503               salsa_wrd_global,                                               &
504               salsa_wrd_local
505
506    USE spectra_mod,                                                           &
507        ONLY:  calculate_spectra,                                              &
508               spectra_parin,                                                  &
509               spectra_check_parameters,                                       &
510               spectra_header
511
512    USE surface_data_output_mod,                                               &
513        ONLY:  surface_data_output_parin,                                      &
514               surface_data_output_check_parameters,                           &
515               surface_data_output_init_arrays,                                &
516               surface_data_output_rrd_local,                                  &
517               surface_data_output_rrd_global,                                 &
518               surface_data_output_wrd_local,                                  &
519               surface_data_output_wrd_global
520
521    USE surface_mod,                                                           &
522        ONLY:  init_bc
523
524    USE synthetic_turbulence_generator_mod,                                    &
525        ONLY:  stg_parin,                                                      &
526               stg_check_parameters,                                           &
527               stg_header,                                                     &
528               stg_rrd_global,                                                 &
529               stg_wrd_global
530
531    USE urban_surface_mod,                                                     &
532        ONLY:  usm_parin,                                                      &
533               usm_check_parameters,                                           &
534               usm_check_data_output,                                          &
535               usm_init_arrays,                                                &
536               usm_init,                                                       &
537               usm_swap_timelevel,                                             &
538               usm_3d_data_averaging,                                          &
539               usm_rrd_local,                                                  &
540               usm_wrd_local
541
542    USE vdi_internal_controls,                                                 &
543        ONLY:  vdi_actions
544               
545    USE virtual_measurement_mod,                                               &
546        ONLY:  vm_check_parameters,                                            &
547               vm_init,                                                        &
548               vm_init_output,                                                 &
549               vm_parin
550
551    USE wind_turbine_model_mod,                                                &
552        ONLY:  wtm_parin,                                                      &
553               wtm_check_parameters,                                           &
554               wtm_init,                                                       &
555               wtm_init_arrays,                                                &
556               wtm_init_output,                                                &
557               wtm_actions,                                                    &
558               wtm_rrd_global,                                                 &
559               wtm_wrd_global
560
561    USE user,                                                                  &
562        ONLY:  user_module_enabled,                                            &
563               user_parin,                                                     &
564               user_check_parameters,                                          &
565               user_check_data_output_ts,                                      &
566               user_check_data_output_pr,                                      &
567               user_check_data_output,                                         &
568               user_init,                                                      &
569               user_init_arrays,                                               &
570               user_header,                                                    &
571               user_actions,                                                   &
572               user_3d_data_averaging,                                         &
573               user_data_output_2d,                                            &
574               user_data_output_3d,                                            &
575               user_statistics,                                                &
576               user_rrd_global,                                                &
577               user_rrd_local,                                                 &
578               user_wrd_global,                                                &
579               user_wrd_local,                                                 &
580               user_last_actions
581
582    IMPLICIT NONE
583
584    PRIVATE
585
586!
587!-- Public functions
588    PUBLIC                                                                     &
589       module_interface_parin,                                                 &
590       module_interface_check_parameters,                                      &
591       module_interface_check_data_output_ts,                                  &
592       module_interface_check_data_output_pr,                                  &
593       module_interface_check_data_output,                                     &
594       module_interface_init_masks,                                            &
595       module_interface_define_netcdf_grid,                                    &
596       module_interface_init_arrays,                                           &
597       module_interface_init,                                                  &
598       module_interface_init_checks,                                           &
599       module_interface_init_numerics,                                         &
600       module_interface_init_output,                                           &
601       module_interface_header,                                                &
602       module_interface_actions,                                               &
603       module_interface_non_advective_processes,                               &
604       module_interface_exchange_horiz,                                        &
605       module_interface_prognostic_equations,                                  &
606       module_interface_boundary_conditions,                                   &
607       module_interface_swap_timelevel,                                        &
608       module_interface_3d_data_averaging,                                     &
609       module_interface_data_output_2d,                                        &
610       module_interface_data_output_3d,                                        &
611       module_interface_statistics,                                            &
612       module_interface_rrd_global,                                            &
613       module_interface_wrd_global,                                            &
614       module_interface_rrd_local,                                             &
615       module_interface_wrd_local,                                             &
616       module_interface_last_actions
617
618
619    INTERFACE module_interface_parin
620       MODULE PROCEDURE module_interface_parin
621    END INTERFACE module_interface_parin
622
623    INTERFACE module_interface_check_parameters
624       MODULE PROCEDURE module_interface_check_parameters
625    END INTERFACE module_interface_check_parameters
626
627    INTERFACE module_interface_check_data_output_ts
628       MODULE PROCEDURE module_interface_check_data_output_ts
629    END INTERFACE module_interface_check_data_output_ts
630
631    INTERFACE module_interface_check_data_output_pr
632       MODULE PROCEDURE module_interface_check_data_output_pr
633    END INTERFACE module_interface_check_data_output_pr
634
635    INTERFACE module_interface_check_data_output
636       MODULE PROCEDURE module_interface_check_data_output
637    END INTERFACE module_interface_check_data_output
638
639    INTERFACE module_interface_init_masks
640       MODULE PROCEDURE module_interface_init_masks
641    END INTERFACE module_interface_init_masks
642
643    INTERFACE module_interface_define_netcdf_grid
644       MODULE PROCEDURE module_interface_define_netcdf_grid
645    END INTERFACE module_interface_define_netcdf_grid
646
647    INTERFACE module_interface_init_arrays
648       MODULE PROCEDURE module_interface_init_arrays
649    END INTERFACE module_interface_init_arrays
650
651    INTERFACE module_interface_init
652       MODULE PROCEDURE module_interface_init
653    END INTERFACE module_interface_init
654
655    INTERFACE module_interface_init_checks
656       MODULE PROCEDURE module_interface_init_checks
657    END INTERFACE module_interface_init_checks
658
659    INTERFACE module_interface_init_numerics
660       MODULE PROCEDURE module_interface_init_numerics
661    END INTERFACE module_interface_init_numerics
662
663    INTERFACE module_interface_init_output
664       MODULE PROCEDURE module_interface_init_output
665    END INTERFACE module_interface_init_output
666
667    INTERFACE module_interface_header
668       MODULE PROCEDURE module_interface_header
669    END INTERFACE module_interface_header
670
671    INTERFACE module_interface_actions
672       MODULE PROCEDURE module_interface_actions
673       MODULE PROCEDURE module_interface_actions_ij
674    END INTERFACE module_interface_actions
675
676    INTERFACE module_interface_non_advective_processes
677       MODULE PROCEDURE module_interface_non_advective_processes
678       MODULE PROCEDURE module_interface_non_advective_processes_ij
679    END INTERFACE module_interface_non_advective_processes
680
681    INTERFACE module_interface_exchange_horiz
682       MODULE PROCEDURE module_interface_exchange_horiz
683    END INTERFACE module_interface_exchange_horiz
684
685    INTERFACE module_interface_prognostic_equations
686       MODULE PROCEDURE module_interface_prognostic_equations
687       MODULE PROCEDURE module_interface_prognostic_equations_ij
688    END INTERFACE module_interface_prognostic_equations
689
690    INTERFACE module_interface_swap_timelevel
691       MODULE PROCEDURE module_interface_swap_timelevel
692    END INTERFACE module_interface_swap_timelevel
693
694    INTERFACE module_interface_boundary_conditions
695       MODULE PROCEDURE module_interface_boundary_conditions
696    END INTERFACE module_interface_boundary_conditions
697
698    INTERFACE module_interface_3d_data_averaging
699       MODULE PROCEDURE module_interface_3d_data_averaging
700    END INTERFACE module_interface_3d_data_averaging
701
702    INTERFACE module_interface_data_output_2d
703       MODULE PROCEDURE module_interface_data_output_2d
704    END INTERFACE module_interface_data_output_2d
705
706    INTERFACE module_interface_data_output_3d
707       MODULE PROCEDURE module_interface_data_output_3d
708    END INTERFACE module_interface_data_output_3d
709
710    INTERFACE module_interface_statistics
711       MODULE PROCEDURE module_interface_statistics
712    END INTERFACE module_interface_statistics
713
714    INTERFACE module_interface_rrd_global
715       MODULE PROCEDURE module_interface_rrd_global_ftn
716       MODULE PROCEDURE module_interface_rrd_global_mpi
717    END INTERFACE module_interface_rrd_global
718
719    INTERFACE module_interface_wrd_global
720       MODULE PROCEDURE module_interface_wrd_global
721    END INTERFACE module_interface_wrd_global
722
723    INTERFACE module_interface_rrd_local
724       MODULE PROCEDURE module_interface_rrd_local_ftn
725       MODULE PROCEDURE module_interface_rrd_local_mpi
726    END INTERFACE module_interface_rrd_local
727
728    INTERFACE module_interface_wrd_local
729       MODULE PROCEDURE module_interface_wrd_local
730    END INTERFACE module_interface_wrd_local
731
732    INTERFACE module_interface_last_actions
733       MODULE PROCEDURE module_interface_last_actions
734    END INTERFACE module_interface_last_actions
735
736
737 CONTAINS
738
739
740!------------------------------------------------------------------------------!
741! Description:
742! ------------
743!> Read module-specific parameter namelists
744!------------------------------------------------------------------------------!
745 SUBROUTINE module_interface_parin
746
747
748    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'start' )
749
750    CALL dynamics_parin
751
752    CALL bio_parin
753    CALL bcm_parin
754    CALL chem_parin
755    CALL flight_parin ! ToDo: rename module to match filename
756    CALL gust_parin
757    CALL im_parin
758    CALL lpm_parin
759    CALL lsm_parin
760    ! ToDo: create parin routine for large_scale_forcing and nudging (should be seperate modules or new module switch)
761    CALL mas_parin
762    CALL nesting_offl_parin
763    CALL ocean_parin
764    CALL pcm_parin
765    CALL radiation_parin
766    CALL salsa_parin
767    CALL spectra_parin
768    CALL surface_data_output_parin
769    CALL stg_parin
770    CALL usm_parin
771    CALL vm_parin
772    CALL wtm_parin
773
774    CALL user_parin
775
776    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'end' )
777
778
779 END SUBROUTINE module_interface_parin
780
781
782!------------------------------------------------------------------------------!
783! Description:
784! ------------
785!> Perform module-specific initialization checks
786!------------------------------------------------------------------------------!
787 SUBROUTINE module_interface_check_parameters
788
789
790    IF ( debug_output )  CALL debug_message( 'checking module-specific parameters', 'start' )
791
792    CALL dynamics_check_parameters
793    CALL tcm_check_parameters
794
795    IF ( bulk_cloud_model )     CALL bcm_check_parameters
796    IF ( air_chemistry )        CALL chem_check_parameters
797    IF ( gust_module_enabled )  CALL gust_check_parameters
798    IF ( indoor_model )         CALL im_check_parameters
799    IF ( particle_advection )   CALL lpm_check_parameters
800    IF ( land_surface )         CALL lsm_check_parameters
801    IF ( large_scale_forcing  .OR.  nudging )  CALL lsf_nudging_check_parameters ! ToDo: create single module switch
802    IF ( nesting_offline )      CALL nesting_offl_check_parameters
803    IF ( ocean_mode )           CALL ocean_check_parameters
804    IF ( plant_canopy )         CALL pcm_check_parameters
805    IF ( radiation )            CALL radiation_check_parameters
806    IF ( salsa )                CALL salsa_check_parameters
807    IF ( calculate_spectra )    CALL spectra_check_parameters
808    IF ( surface_output )       CALL surface_data_output_check_parameters
809    IF ( syn_turb_gen )         CALL stg_check_parameters
810    IF ( urban_surface )        CALL usm_check_parameters
811    IF ( virtual_measurement )  CALL vm_check_parameters
812    IF ( wind_turbine )         CALL wtm_check_parameters
813
814    IF ( user_module_enabled )  CALL user_check_parameters
815
816    IF ( debug_output )  CALL debug_message( 'checking module-specific parameters', 'end' )
817
818
819 END SUBROUTINE module_interface_check_parameters
820
821
822!------------------------------------------------------------------------------!
823! Description:
824! ------------
825!> Check module-specific data output of timeseries
826!------------------------------------------------------------------------------!
827 SUBROUTINE module_interface_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
828
829
830    INTEGER(iwp),      INTENT(IN)    ::  dots_max !< variable output array index
831    INTEGER(iwp),      INTENT(INOUT)    ::  dots_num !< variable output array index
832    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT) :: dots_label
833    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT) :: dots_unit
834
835
836    IF ( debug_output )  CALL debug_message( 'checking module-specific data output ts', 'start' )
837
838    CALL dynamics_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
839
840    IF ( radiation )  THEN
841       CALL radiation_check_data_output_ts( dots_max, dots_num )
842    ENDIF
843
844    IF ( user_module_enabled )  THEN
845       CALL user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
846    ENDIF
847
848    IF ( debug_output )  CALL debug_message( 'checking module-specific data output ts', 'end' )
849
850
851 END SUBROUTINE module_interface_check_data_output_ts
852
853
854!------------------------------------------------------------------------------!
855! Description:
856! ------------
857!> Check module-specific data output of profiles
858!------------------------------------------------------------------------------!
859 SUBROUTINE module_interface_check_data_output_pr( variable, var_count, unit,  &
860                                                   dopr_unit )
861
862
863    CHARACTER (LEN=*), INTENT(IN)    ::  variable  !< variable name
864    INTEGER(iwp),      INTENT(IN)    ::  var_count !< variable output array index
865    CHARACTER (LEN=*), INTENT(INOUT) ::  unit      !< physical unit of variable
866    CHARACTER (LEN=*), INTENT(OUT)   ::  dopr_unit !< local value of dopr_unit
867
868
869    IF ( debug_output )  CALL debug_message( 'checking module-specific data output pr', 'start' )
870
871    CALL dynamics_check_data_output_pr( variable, var_count, unit, dopr_unit )
872
873    IF ( unit == 'illegal' .AND.  bulk_cloud_model )  THEN
874       CALL bcm_check_data_output_pr( variable, var_count, unit, dopr_unit )
875    ENDIF
876
877    IF ( unit == 'illegal' .AND.  air_chemistry )  THEN
878       CALL chem_check_data_output_pr( variable, var_count, unit, dopr_unit )
879    ENDIF
880
881    IF ( unit == 'illegal'  .AND.  gust_module_enabled  )  THEN
882       CALL gust_check_data_output_pr( variable, var_count, unit, dopr_unit )
883    ENDIF
884
885    IF ( unit == 'illegal' )  THEN ! ToDo: add module switch if possible
886       CALL lsm_check_data_output_pr( variable, var_count, unit, dopr_unit )
887    ENDIF
888
889    IF ( unit == 'illegal' )  THEN ! ToDo: add module switch if possible
890       CALL lsf_nudging_check_data_output_pr( variable, var_count, unit, dopr_unit )
891    ENDIF
892
893    IF ( unit == 'illegal'  .AND.  ocean_mode )  THEN
894       CALL ocean_check_data_output_pr( variable, var_count, unit, dopr_unit )
895    ENDIF
896
897    IF ( unit == 'illegal'  .AND.  radiation )  THEN
898       CALL radiation_check_data_output_pr( variable, var_count, unit, dopr_unit )
899    ENDIF
900
901    IF ( unit == 'illegal'  .AND.  salsa )  THEN
902       CALL salsa_check_data_output_pr( variable, var_count, unit, dopr_unit )
903    ENDIF
904
905    IF ( unit == 'illegal'  .AND.  user_module_enabled )  THEN
906       unit = '' ! ToDo: Seems like a hack. Find a general soultion!
907       CALL user_check_data_output_pr( variable, var_count, unit, dopr_unit )
908    ENDIF
909
910    IF ( debug_output )  CALL debug_message( 'checking module-specific data output pr', 'end' )
911
912
913 END SUBROUTINE module_interface_check_data_output_pr
914
915!------------------------------------------------------------------------------!
916! Description:
917! ------------
918!> Check module-specific 2D and 3D data output
919!------------------------------------------------------------------------------!
920 SUBROUTINE module_interface_check_data_output( variable, unit, i, j, ilen, k )
921
922
923    CHARACTER (LEN=*), INTENT(IN)    ::  variable !< variable name
924    CHARACTER (LEN=*), INTENT(INOUT) ::  unit     !< physical unit of variable
925
926    INTEGER(iwp),      INTENT(IN)    :: i         !< ToDo: remove dummy argument, instead pass string from data_output
927    INTEGER(iwp),      INTENT(IN)    :: j         !< average quantity? 0 = no, 1 = yes
928    INTEGER(iwp),      INTENT(IN)    :: ilen      !< ToDo: remove dummy argument, instead pass string from data_output
929    INTEGER(iwp),      INTENT(IN)    :: k         !< ToDo: remove dummy argument, instead pass string from data_output
930
931
932    IF ( debug_output )  CALL debug_message( 'checking module-specific data output 2d/3d', 'start' )
933
934    CALL dynamics_check_data_output( variable, unit )
935
936    CALL tcm_check_data_output( variable, unit )
937
938    IF ( unit == 'illegal'  .AND.  biometeorology )  THEN
939       CALL bio_check_data_output( variable, unit, i, j, ilen, k )
940    ENDIF
941
942    IF ( unit == 'illegal'  .AND.  bulk_cloud_model  )  THEN
943       CALL bcm_check_data_output( variable, unit )
944    ENDIF
945
946    IF ( unit == 'illegal'  .AND.  air_chemistry                               &
947         .AND.  (variable(1:3) == 'kc_' .OR. variable(1:3) == 'em_') )  THEN  ! ToDo: remove aditional conditions
948       CALL chem_check_data_output( variable, unit, i, ilen, k )
949    ENDIF
950
951    IF ( unit == 'illegal' )  THEN
952       CALL doq_check_data_output( variable, unit, i, ilen, k )
953    ENDIF
954
955    IF ( unit == 'illegal'  .AND.  gust_module_enabled  )  THEN
956       CALL gust_check_data_output( variable, unit )
957    ENDIF
958
959    IF ( unit == 'illegal' )  THEN  ! ToDo: add module switch if possible
960       CALL lsm_check_data_output( variable, unit, i, ilen, k )
961    ENDIF
962
963    IF ( unit == 'illegal'  .AND.  ocean_mode )  THEN
964       CALL ocean_check_data_output( variable, unit )
965    ENDIF
966
967    IF ( unit == 'illegal'  .AND.  plant_canopy                                &
968         .AND.  variable(1:4) == 'pcm_' )  THEN  ! ToDo: remove aditional conditions
969       CALL pcm_check_data_output( variable, unit )
970    ENDIF
971
972    IF ( unit == 'illegal'  .AND.  radiation )  THEN
973       CALL radiation_check_data_output( variable, unit, i, ilen, k )
974    ENDIF
975
976    IF ( unit == 'illegal' .AND. salsa ) THEN
977       CALL salsa_check_data_output( variable, unit )
978    ENDIF
979
980    IF ( unit == 'illegal' .AND. indoor_model ) THEN
981       CALL im_check_data_output( variable, unit )
982    ENDIF
983
984    IF ( unit == 'illegal'  .AND.  urban_surface                      &
985        .AND.  variable(1:4) == 'usm_' )  THEN  ! ToDo: remove aditional conditions
986       CALL usm_check_data_output( variable, unit )
987    ENDIF
988
989    IF ( unit == 'illegal'  .AND.  user_module_enabled )  THEN
990       unit = ''
991       CALL user_check_data_output( variable, unit )
992    ENDIF
993
994    IF ( debug_output )  CALL debug_message( 'checking module-specific data output 2d/3d', 'end' )
995
996
997 END SUBROUTINE module_interface_check_data_output
998
999
1000!------------------------------------------------------------------------------!
1001!
1002! Description:
1003! ------------
1004!> Interface for init_masks. ToDo: get rid of these redundant calls!
1005!------------------------------------------------------------------------------!
1006 SUBROUTINE module_interface_init_masks( variable, unit )
1007
1008
1009    CHARACTER (LEN=*), INTENT(IN)    ::  variable !< variable name
1010    CHARACTER (LEN=*), INTENT(INOUT) ::  unit     !< physical unit of variable
1011
1012
1013    IF ( debug_output )  CALL debug_message( 'initializing module-specific masks', 'start' )
1014
1015    CALL dynamics_init_masks( variable, unit )
1016
1017    IF ( unit == 'illegal'  .AND.  air_chemistry                               &
1018         .AND.  (variable(1:3) == 'kc_' .OR. variable(1:3) == 'em_') )  THEN  ! ToDo: remove aditional conditions
1019       CALL chem_check_data_output( variable, unit, 0, 0, 0 )
1020    ENDIF
1021   
1022    IF ( unit == 'illegal' )  THEN
1023       CALL doq_check_data_output( variable, unit )
1024    ENDIF
1025
1026    IF ( unit == 'illegal'  .AND.  radiation )  THEN
1027       CALL radiation_check_data_output( variable, unit, 0, 0, 0 )
1028    ENDIF
1029
1030    IF ( unit == 'illegal'  .AND.  salsa )  THEN
1031       CALL salsa_check_data_output( variable, unit )
1032    ENDIF
1033
1034    IF ( unit == 'illegal'  .AND.  user_module_enabled )  THEN
1035       unit = ''
1036       CALL user_check_data_output( variable, unit )
1037    ENDIF
1038
1039    IF ( debug_output )  CALL debug_message( 'initializing module-specific masks', 'end' )
1040
1041
1042 END SUBROUTINE module_interface_init_masks
1043
1044
1045!------------------------------------------------------------------------------!
1046!
1047! Description:
1048! ------------
1049!> Define appropriate grid for module-specific netcdf output variables.
1050!------------------------------------------------------------------------------!
1051 SUBROUTINE module_interface_define_netcdf_grid( var, found,                   &
1052                                                 grid_x, grid_y, grid_z )
1053
1054
1055    CHARACTER (LEN=*), INTENT(IN)  ::  var    !< variable name
1056    LOGICAL,           INTENT(OUT) ::  found  !< indicates if variable was found
1057    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x !< netcdf dimension in x-direction
1058    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y !< netcdf dimension in y-direction
1059    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z !< netcdf dimension in z-direction
1060
1061
1062    IF ( debug_output )  CALL debug_message( 'defining module-specific netcdf grids', 'start' )
1063!
1064!-- As long as no action is done in this subroutine, initialize strings with
1065!-- intent(out) attribute, in order to avoid compiler warnings.
1066    found  = .FALSE.
1067    grid_x = 'none'
1068    grid_y = 'none'
1069    grid_z = 'none'
1070!
1071!-- Use var to avoid compiler warning about unused variable
1072    IF ( var == ' ' )  RETURN
1073
1074    IF ( debug_output )  CALL debug_message( 'defining module-specific netcdf grids', 'end' )
1075
1076
1077 END SUBROUTINE module_interface_define_netcdf_grid
1078
1079
1080!------------------------------------------------------------------------------!
1081! Description:
1082! ------------
1083!> Allocate module-specific arrays and pointers
1084!------------------------------------------------------------------------------!
1085 SUBROUTINE module_interface_init_arrays
1086
1087
1088    IF ( debug_output )  CALL debug_message( 'initializing module-specific arrays', 'start' )
1089
1090    CALL dynamics_init_arrays
1091    CALL tcm_init_arrays
1092
1093    IF ( bulk_cloud_model    )  CALL bcm_init_arrays
1094    IF ( air_chemistry       )  CALL chem_init_arrays
1095    IF ( gust_module_enabled )  CALL gust_init_arrays
1096    IF ( particle_advection  )  CALL lpm_init_arrays
1097    IF ( land_surface        )  CALL lsm_init_arrays
1098    IF ( ocean_mode          )  CALL ocean_init_arrays
1099    IF ( salsa               )  CALL salsa_init_arrays
1100    IF ( urban_surface       )  CALL usm_init_arrays
1101    IF ( surface_output      )  CALL surface_data_output_init_arrays
1102    IF ( wind_turbine        )  CALL wtm_init_arrays
1103
1104    IF ( user_module_enabled )  CALL user_init_arrays
1105
1106    IF ( debug_output )  CALL debug_message( 'initializing module-specific arrays', 'end' )
1107
1108
1109 END SUBROUTINE module_interface_init_arrays
1110
1111
1112!------------------------------------------------------------------------------!
1113! Description:
1114! ------------
1115!> Perform module-specific initialization
1116!------------------------------------------------------------------------------!
1117 SUBROUTINE module_interface_init
1118
1119
1120    IF ( debug_output )  CALL debug_message( 'module-specific initialization', 'start' )
1121
1122    CALL dynamics_init
1123    CALL tcm_init
1124
1125    IF ( biometeorology      )  CALL bio_init
1126    IF ( bulk_cloud_model    )  CALL bcm_init
1127    IF ( air_chemistry       )  CALL chem_init
1128    IF ( virtual_flight      )  CALL flight_init
1129    IF ( gust_module_enabled )  CALL gust_init
1130    IF ( indoor_model        )  CALL im_init
1131    IF ( particle_advection  )  CALL lpm_init
1132    IF ( large_scale_forcing )  CALL lsf_init
1133    IF ( land_surface        )  CALL lsm_init
1134    IF ( nudging             )  CALL nudge_init
1135    IF ( ocean_mode          )  CALL ocean_init
1136    IF ( plant_canopy        )  CALL pcm_init
1137    IF ( salsa               )  CALL salsa_init
1138    IF ( urban_surface       )  CALL usm_init
1139    IF ( virtual_measurement )  CALL vm_init
1140    IF ( wind_turbine        )  CALL wtm_init
1141    IF ( radiation           )  CALL radiation_init
1142
1143    CALL doq_init
1144
1145    IF ( user_module_enabled )  CALL user_init
1146
1147    IF ( debug_output )  CALL debug_message( 'module-specific initialization', 'end' )
1148
1149 END SUBROUTINE module_interface_init
1150
1151!------------------------------------------------------------------------------!
1152! Description:
1153! ------------
1154!> Initialize boundary conditions and numerical schemes.
1155!------------------------------------------------------------------------------!
1156 SUBROUTINE module_interface_init_numerics
1157
1158!
1159!-- Initialize boundary conditions via surface type
1160    CALL init_bc
1161!
1162!-- Calculate wall flag arrays for the multigrid method.
1163!-- Please note, wall flags are only applied in the non-optimized version.
1164    CALL poismg_noopt_init
1165 
1166 END SUBROUTINE module_interface_init_numerics
1167
1168 
1169!------------------------------------------------------------------------------!
1170! Description:
1171! ------------
1172!> Initialize data output
1173!------------------------------------------------------------------------------!
1174 SUBROUTINE module_interface_init_output
1175
1176    INTEGER(iwp) ::  return_value  !< returned status value of called function
1177
1178!
1179!-- Initialize data-output module
1180    CALL dom_init( file_suffix_of_output_group=coupling_char,                  &
1181                   mpi_comm_of_output_group=comm2d,                            &
1182                   program_debug_output_unit=9,                                &
1183                   debug_output=debug_output )
1184!
1185!-- Define module-specific output quantities
1186    IF ( virtual_measurement )  CALL vm_init_output
1187    IF ( wind_turbine )         CALL wtm_init_output
1188!
1189!-- Leave output-definition state
1190    return_value = dom_def_end()
1191
1192 END SUBROUTINE module_interface_init_output
1193
1194!------------------------------------------------------------------------------!
1195! Description:
1196! ------------
1197!> Perform module-specific post-initialization checks
1198!------------------------------------------------------------------------------!
1199 SUBROUTINE module_interface_init_checks
1200
1201
1202    IF ( debug_output )  CALL debug_message( 'module-specific post-initialization checks', 'start' )
1203
1204    CALL dynamics_init_checks
1205
1206    IF ( biometeorology      )  CALL bio_init_checks
1207
1208    IF ( debug_output )  CALL debug_message( 'module-specific post-initialization checks', 'end' )
1209
1210
1211 END SUBROUTINE module_interface_init_checks
1212
1213
1214!------------------------------------------------------------------------------!
1215! Description:
1216! ------------
1217!> Gather module-specific header output
1218!------------------------------------------------------------------------------!
1219 SUBROUTINE module_interface_header( io )
1220
1221
1222    INTEGER(iwp), INTENT(IN) ::  io  !< unit of the output file
1223
1224
1225    IF ( debug_output )  CALL debug_message( 'module-specific header output', 'start' )
1226
1227    CALL dynamics_header( io )
1228
1229    IF ( biometeorology      )  CALL bio_header ( io )
1230    IF ( bulk_cloud_model    )  CALL bcm_header( io )
1231    IF ( air_chemistry       )  CALL chem_header ( io )
1232    IF ( virtual_flight      )  CALL flight_header( io )
1233    IF ( gust_module_enabled )  CALL gust_header( io )
1234    IF ( particle_advection  )  CALL lpm_header( io )
1235    IF ( land_surface        )  CALL lsm_header( io )
1236    IF ( large_scale_forcing )  CALL lsf_nudging_header( io )
1237    IF ( nesting_offline     )  CALL nesting_offl_header( io )
1238    IF ( ocean_mode          )  CALL ocean_header( io )
1239    IF ( plant_canopy        )  CALL pcm_header( io )
1240    IF ( radiation           )  CALL radiation_header( io )
1241    IF ( salsa               )  CALL salsa_header( io )
1242    IF ( calculate_spectra   )  CALL spectra_header( io )
1243    IF ( syn_turb_gen        )  CALL stg_header( io )
1244
1245    IF ( user_module_enabled )  CALL user_header( io )
1246
1247    IF ( debug_output )  CALL debug_message( 'module-specific header output', 'end' )
1248
1249
1250 END SUBROUTINE module_interface_header
1251
1252
1253!------------------------------------------------------------------------------!
1254! Description:
1255! ------------
1256!> Perform module-specific actions while in time-integration (vector-optimized)
1257!------------------------------------------------------------------------------!
1258 SUBROUTINE module_interface_actions( location )
1259
1260
1261    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
1262
1263    CALL dynamics_actions( location )
1264    CALL tcm_actions( location )
1265
1266    IF ( bulk_cloud_model    )  CALL bcm_actions( location )
1267    IF ( air_chemistry       )  CALL chem_actions( location )
1268    IF ( gust_module_enabled )  CALL gust_actions( location )
1269    IF ( particle_advection  )  CALL lpm_actions( location )
1270    IF ( ocean_mode          )  CALL ocean_actions( location )
1271    IF ( salsa               )  CALL salsa_actions( location )
1272    IF ( wind_turbine        )  CALL wtm_actions( location )
1273
1274    IF ( user_module_enabled )  CALL user_actions( location )
1275    IF ( vdi_checks          )  CALL vdi_actions( location )
1276
1277
1278 END SUBROUTINE module_interface_actions
1279
1280
1281!------------------------------------------------------------------------------!
1282! Description:
1283! ------------
1284!> Perform module-specific actions while in time-integration (cache-optimized)
1285!------------------------------------------------------------------------------!
1286 SUBROUTINE module_interface_actions_ij( i, j, location )
1287
1288
1289    INTEGER(iwp),      INTENT(IN) ::  i         !< grid index in x-direction
1290    INTEGER(iwp),      INTENT(IN) ::  j         !< grid index in y-direction
1291    CHARACTER (LEN=*), INTENT(IN) ::  location  !< call location string
1292
1293    CALL dynamics_actions( i, j, location )
1294    CALL tcm_actions( i, j, location )
1295
1296    IF ( bulk_cloud_model    )  CALL bcm_actions( i, j, location )
1297    IF ( air_chemistry       )  CALL chem_actions( i, j, location )
1298    IF ( gust_module_enabled )  CALL gust_actions( i, j, location )
1299    IF ( ocean_mode          )  CALL ocean_actions( i, j, location )
1300    IF ( salsa               )  CALL salsa_actions( i, j, location )
1301    IF ( wind_turbine        )  CALL wtm_actions( i, j, location )
1302
1303    IF ( user_module_enabled )  CALL user_actions( i, j, location )
1304
1305
1306 END SUBROUTINE module_interface_actions_ij
1307
1308
1309!------------------------------------------------------------------------------!
1310! Description:
1311! ------------
1312!> Compute module-specific non_advective_processes (vector-optimized)
1313!------------------------------------------------------------------------------!
1314 SUBROUTINE module_interface_non_advective_processes
1315
1316
1317    CALL dynamics_non_advective_processes
1318
1319    IF ( bulk_cloud_model    )  CALL bcm_non_advective_processes
1320    IF ( air_chemistry       )  CALL chem_non_advective_processes
1321    IF ( salsa               )  CALL salsa_non_advective_processes
1322
1323
1324 END SUBROUTINE module_interface_non_advective_processes
1325
1326
1327!------------------------------------------------------------------------------!
1328! Description:
1329! ------------
1330!> Compute module-specific non_advective_processes (cache-optimized)
1331!------------------------------------------------------------------------------!
1332 SUBROUTINE module_interface_non_advective_processes_ij( i, j )
1333
1334
1335    INTEGER(iwp), INTENT(IN) ::  i            !< grid index in x-direction
1336    INTEGER(iwp), INTENT(IN) ::  j            !< grid index in y-direction
1337
1338    CALL dynamics_non_advective_processes( i, j )
1339
1340    IF ( bulk_cloud_model    )  CALL bcm_non_advective_processes( i, j )
1341    IF ( air_chemistry       )  CALL chem_non_advective_processes( i, j )
1342    IF ( salsa               )  CALL salsa_non_advective_processes( i, j )
1343
1344
1345 END SUBROUTINE module_interface_non_advective_processes_ij
1346
1347!------------------------------------------------------------------------------!
1348! Description:
1349! ------------
1350!> Exchange horiz for module-specific quantities
1351!------------------------------------------------------------------------------!
1352 SUBROUTINE module_interface_exchange_horiz
1353
1354
1355    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'start' )
1356
1357    CALL dynamics_exchange_horiz
1358
1359    IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz
1360    IF ( air_chemistry       )  CALL chem_exchange_horiz_bounds
1361    IF ( salsa               )  CALL salsa_exchange_horiz_bounds
1362
1363    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'end' )
1364
1365
1366 END SUBROUTINE module_interface_exchange_horiz
1367
1368
1369!------------------------------------------------------------------------------!
1370! Description:
1371! ------------
1372!> Compute module-specific prognostic_equations (vector-optimized)
1373!------------------------------------------------------------------------------!
1374 SUBROUTINE module_interface_prognostic_equations
1375
1376
1377    CALL dynamics_prognostic_equations
1378    CALL tcm_prognostic_equations
1379
1380    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations
1381    IF ( air_chemistry       )  CALL chem_prognostic_equations
1382    IF ( gust_module_enabled )  CALL gust_prognostic_equations
1383    IF ( ocean_mode          )  CALL ocean_prognostic_equations
1384    IF ( salsa               )  CALL salsa_prognostic_equations
1385
1386
1387 END SUBROUTINE module_interface_prognostic_equations
1388
1389
1390!------------------------------------------------------------------------------!
1391! Description:
1392! ------------
1393!> Compute module-specific prognostic_equations (cache-optimized)
1394!------------------------------------------------------------------------------!
1395 SUBROUTINE module_interface_prognostic_equations_ij( i, j, i_omp_start, tn )
1396
1397
1398    INTEGER(iwp), INTENT(IN) ::  i            !< grid index in x-direction
1399    INTEGER(iwp), INTENT(IN) ::  j            !< grid index in y-direction
1400    INTEGER(iwp), INTENT(IN) ::  i_omp_start  !< first loop index of i-loop in prognostic_equations
1401    INTEGER(iwp), INTENT(IN) ::  tn           !< task number of openmp task
1402
1403    CALL dynamics_prognostic_equations( i, j, i_omp_start, tn )
1404    CALL tcm_prognostic_equations( i, j, i_omp_start, tn )
1405
1406    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations( i, j, i_omp_start, tn )
1407    IF ( air_chemistry       )  CALL chem_prognostic_equations( i, j, i_omp_start, tn )
1408    IF ( gust_module_enabled )  CALL gust_prognostic_equations( i, j, i_omp_start, tn )
1409    IF ( ocean_mode          )  CALL ocean_prognostic_equations( i, j, i_omp_start, tn )
1410    IF ( salsa               )  CALL salsa_prognostic_equations( i, j, i_omp_start, tn )
1411
1412
1413 END SUBROUTINE module_interface_prognostic_equations_ij
1414
1415!------------------------------------------------------------------------------!
1416! Description:
1417! ------------
1418!> Compute module-specific boundary conditions
1419!------------------------------------------------------------------------------!
1420 SUBROUTINE module_interface_boundary_conditions
1421
1422
1423    IF ( debug_output_timestep )  CALL debug_message( 'module-specific boundary_conditions', 'start' )
1424
1425    CALL dynamics_boundary_conditions
1426    CALL tcm_boundary_conds
1427
1428    IF ( bulk_cloud_model    )  CALL bcm_boundary_conditions
1429    IF ( air_chemistry       )  CALL chem_boundary_conditions
1430    IF ( ocean_mode          )  CALL ocean_boundary_conditions
1431    IF ( salsa               )  CALL salsa_boundary_conditions
1432
1433    IF ( debug_output_timestep )  CALL debug_message( 'module-specific boundary_conditions', 'end' )
1434
1435
1436 END SUBROUTINE module_interface_boundary_conditions
1437
1438!------------------------------------------------------------------------------!
1439! Description:
1440! ------------
1441!> Swap the timelevel pointers for module-specific arrays
1442!------------------------------------------------------------------------------!
1443 SUBROUTINE module_interface_swap_timelevel ( swap_mode )
1444
1445
1446    INTEGER(iwp), INTENT(IN) :: swap_mode !< determines procedure of pointer swap
1447
1448
1449    IF ( debug_output_timestep )  CALL debug_message( 'module-specific swap timelevel', 'start' )
1450
1451    CALL dynamics_swap_timelevel( swap_mode )
1452    CALL tcm_swap_timelevel( swap_mode )
1453
1454    IF ( bulk_cloud_model    )  CALL bcm_swap_timelevel( swap_mode )
1455    IF ( air_chemistry       )  CALL chem_swap_timelevel( swap_mode )
1456    IF ( gust_module_enabled )  CALL gust_swap_timelevel( swap_mode )
1457    IF ( land_surface        )  CALL lsm_swap_timelevel( swap_mode )
1458    IF ( ocean_mode          )  CALL ocean_swap_timelevel( swap_mode )
1459    IF ( salsa               )  CALL salsa_swap_timelevel( swap_mode )
1460    IF ( urban_surface       )  CALL usm_swap_timelevel( swap_mode )
1461
1462    IF ( debug_output_timestep )  CALL debug_message( 'module-specific swap timelevel', 'end' )
1463
1464
1465 END SUBROUTINE module_interface_swap_timelevel
1466
1467
1468!------------------------------------------------------------------------------!
1469!
1470! Description:
1471! ------------
1472!> Perform module-specific averaging of 3D data
1473!------------------------------------------------------------------------------!
1474 SUBROUTINE module_interface_3d_data_averaging( mode, variable )
1475
1476
1477    CHARACTER (LEN=*), INTENT(IN) ::  mode     !< averaging interface mode
1478    CHARACTER (LEN=*), INTENT(IN) ::  variable !< variable name
1479
1480
1481    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data averaging', 'start' )
1482
1483    CALL dynamics_3d_data_averaging( mode, variable )
1484    CALL tcm_3d_data_averaging( mode, variable )
1485
1486    IF ( biometeorology      )  CALL bio_3d_data_averaging( mode, variable )
1487    IF ( bulk_cloud_model    )  CALL bcm_3d_data_averaging( mode, variable )
1488    IF ( air_chemistry       )  CALL chem_3d_data_averaging( mode, variable )
1489    CALL doq_3d_data_averaging( mode, variable )  ! ToDo: this seems to be not according to the design
1490    IF ( gust_module_enabled )  CALL gust_3d_data_averaging( mode, variable )
1491    IF ( land_surface        )  CALL lsm_3d_data_averaging( mode, variable )
1492    IF ( ocean_mode          )  CALL ocean_3d_data_averaging( mode, variable )
1493    IF ( plant_canopy        )  CALL pcm_3d_data_averaging( mode, variable )
1494    IF ( radiation           )  CALL radiation_3d_data_averaging( mode, variable )
1495    IF ( salsa               )  CALL salsa_3d_data_averaging( mode, variable )
1496    IF ( urban_surface       )  CALL usm_3d_data_averaging( mode, variable )
1497
1498    IF ( user_module_enabled )  CALL user_3d_data_averaging( mode, variable )
1499
1500    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data averaging', 'end' )
1501
1502
1503 END SUBROUTINE module_interface_3d_data_averaging
1504
1505!------------------------------------------------------------------------------!
1506!
1507! Description:
1508! ------------
1509!> Define module-specific 2D output variables
1510!------------------------------------------------------------------------------!
1511 SUBROUTINE module_interface_data_output_2d( av, variable, found, grid, mode,  &
1512                                             local_pf, two_d, nzb_do, nzt_do,  &
1513                                             fill_value )
1514
1515    INTEGER(iwp),      INTENT(IN)    ::  av         !< flag for (non-)average output
1516    CHARACTER (LEN=*), INTENT(IN)    ::  variable   !< variable name
1517    LOGICAL,           INTENT(INOUT) ::  found      !< flag if output variable is found
1518    CHARACTER (LEN=*), INTENT(INOUT) ::  grid       !< name of vertical grid
1519    CHARACTER (LEN=*), INTENT(IN)    ::  mode       !< either 'xy', 'xz' or 'yz'
1520    LOGICAL,           INTENT(OUT)   ::  two_d      !< flag for 2D variables
1521    INTEGER(iwp),      INTENT(IN)    ::  nzb_do     !< vertical output index (bottom) (usually 0)
1522    INTEGER(iwp),      INTENT(IN)    ::  nzt_do     !< vertical output index (top) (usually nz_do3d)
1523    REAL(wp),          INTENT(IN)    ::  fill_value !< to be removed
1524
1525    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do), INTENT(INOUT) ::  local_pf !< ToDo: can also be kind=sp
1526
1527
1528    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 2d data output', 'start' )
1529
1530    CALL dynamics_data_output_2d(                                                  &
1531               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, fill_value &
1532            )
1533
1534    IF ( .NOT. found )  THEN
1535       CALL tcm_data_output_2d(                                                  &
1536               av, variable, found, grid, mode, local_pf, nzb_do, nzt_do &
1537            )
1538    ENDIF
1539
1540    IF ( .NOT. found  .AND.  biometeorology )  THEN
1541       CALL bio_data_output_2d(                                                &
1542               av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do      &
1543            )
1544    ENDIF
1545
1546    IF ( .NOT. found  .AND.  bulk_cloud_model )  THEN
1547       CALL bcm_data_output_2d(                                                &
1548               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do&
1549            )
1550    ENDIF
1551
1552    IF ( .NOT. found  .AND.  air_chemistry )  THEN
1553       CALL chem_data_output_2d(                                               &
1554               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, fill_value &
1555            )
1556    ENDIF
1557
1558    IF ( .NOT. found )  THEN
1559       CALL doq_output_2d(                                                     &
1560               av, variable, found, grid, mode, local_pf, two_d,               &
1561               nzb_do, nzt_do, fill_value )
1562    ENDIF
1563
1564    IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
1565       CALL gust_data_output_2d(                                               &
1566               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, fill_value &
1567            )
1568    ENDIF
1569
1570    IF ( .NOT. found  .AND.  land_surface )  THEN
1571       CALL lsm_data_output_2d(                                                &
1572               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do&
1573            )
1574    ENDIF
1575
1576    IF ( .NOT. found  .AND.  ocean_mode )  THEN
1577       CALL ocean_data_output_2d(                                              &
1578               av, variable, found, grid, mode, local_pf, nzb_do, nzt_do       &
1579            )
1580    ENDIF
1581
1582    IF ( .NOT. found  .AND.  radiation )  THEN
1583       CALL radiation_data_output_2d(                                                       &
1584               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, fill_value &
1585            )
1586    ENDIF
1587
1588    IF ( .NOT. found  .AND.  salsa )  THEN
1589       CALL salsa_data_output_2d(                                              &
1590               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do&
1591            )
1592    ENDIF
1593
1594    IF ( .NOT. found  .AND.  user_module_enabled )  THEN
1595       CALL user_data_output_2d(                                               &
1596               av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do      &
1597            )
1598    ENDIF
1599
1600    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 2d data output', 'end' )
1601
1602
1603 END SUBROUTINE module_interface_data_output_2d
1604
1605
1606!------------------------------------------------------------------------------!
1607!
1608! Description:
1609! ------------
1610!> Define module-specific 3D output variables
1611!------------------------------------------------------------------------------!
1612 SUBROUTINE module_interface_data_output_3d( av, variable, found, local_pf,    &
1613                                             fill_value, resorted, nzb_do, nzt_do )
1614
1615
1616    INTEGER(iwp),      INTENT(IN)    ::  av         !< flag for (non-)average output
1617    CHARACTER (LEN=*), INTENT(IN)    ::  variable   !< variable name
1618    LOGICAL,           INTENT(INOUT) ::  found      !< flag if output variable is found
1619    REAL(wp),          INTENT(IN)    ::  fill_value !< ToDo: refactor
1620    LOGICAL,           INTENT(OUT)   ::  resorted   !< flag if output has been resorted
1621    INTEGER(iwp),      INTENT(IN)    ::  nzb_do     !< vertical output index (bottom) (usually 0)
1622    INTEGER(iwp),      INTENT(IN)    ::  nzt_do     !< vertical output index (top) (usually nz_do3d)
1623
1624    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do), INTENT(INOUT) ::  local_pf
1625
1626
1627    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data output', 'start' )
1628
1629    CALL dynamics_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1630    resorted = .FALSE.
1631
1632    IF ( .NOT. found )  THEN
1633       CALL tcm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1634       resorted = .TRUE.
1635    ENDIF
1636
1637    IF ( .NOT. found  .AND.  biometeorology )  THEN
1638       CALL bio_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1639       resorted = .FALSE.
1640    ENDIF
1641
1642    IF ( .NOT. found  .AND.  bulk_cloud_model )  THEN
1643       CALL bcm_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1644       resorted = .TRUE.
1645    ENDIF
1646
1647    IF ( .NOT. found  .AND.  air_chemistry )  THEN
1648       CALL chem_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1649       resorted = .TRUE.
1650    ENDIF
1651
1652    IF ( .NOT. found )  THEN
1653       CALL doq_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1654       resorted = .TRUE.
1655    ENDIF
1656
1657    IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
1658       CALL gust_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1659       resorted = .TRUE.
1660    ENDIF
1661
1662    IF ( .NOT. found  .AND.  indoor_model )  THEN
1663       CALL im_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1664       resorted = .TRUE.
1665    ENDIF
1666
1667    IF ( .NOT. found  .AND.  ocean_mode )  THEN
1668       CALL ocean_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1669       resorted = .TRUE.
1670    ENDIF
1671
1672    IF ( .NOT. found  .AND.  plant_canopy )  THEN
1673       CALL pcm_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1674       resorted = .TRUE.
1675    ENDIF
1676
1677    IF ( .NOT. found  .AND.  radiation )  THEN
1678       CALL radiation_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
1679       resorted = .TRUE.
1680    ENDIF
1681
1682    IF ( .NOT. found  .AND.  salsa )  THEN
1683       CALL salsa_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1684       resorted = .TRUE.
1685    ENDIF
1686
1687    IF ( .NOT. found  .AND.  user_module_enabled )  THEN
1688       CALL user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
1689       resorted = .TRUE.
1690    ENDIF
1691
1692    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data output', 'end' )
1693
1694
1695 END SUBROUTINE module_interface_data_output_3d
1696
1697
1698!------------------------------------------------------------------------------!
1699! Description:
1700! ------------
1701!> Compute module-specific profile and timeseries data
1702!------------------------------------------------------------------------------!
1703 SUBROUTINE module_interface_statistics( mode, sr, tn, dots_max )
1704
1705
1706    CHARACTER (LEN=*), INTENT(IN) ::  mode     !< statistical analysis mode
1707    INTEGER(iwp),      INTENT(IN) ::  sr       !<
1708    INTEGER(iwp),      INTENT(IN) ::  tn       !<
1709    INTEGER(iwp),      INTENT(IN) ::  dots_max !< maximum number of timeseries
1710
1711
1712    IF ( debug_output_timestep )  CALL debug_message( 'module-specific statistics', 'start' )
1713
1714    CALL dynamics_statistics( mode, sr, tn )
1715
1716    IF ( gust_module_enabled )  CALL gust_statistics( mode, sr, tn, dots_max )
1717    IF ( air_chemistry       )  CALL chem_statistics( mode, sr, tn )
1718    IF ( salsa               )  CALL salsa_statistics( mode, sr, tn )
1719
1720    IF ( user_module_enabled )  CALL user_statistics( mode, sr, tn )
1721
1722    IF ( debug_output_timestep )  CALL debug_message( 'module-specific statistics', 'end' )
1723
1724
1725 END SUBROUTINE module_interface_statistics
1726
1727
1728!--------------------------------------------------------------------------------------------------!
1729! Description:
1730! ------------
1731!> Read module-specific restart data in Fortran binary format globaly shared by all MPI ranks
1732!--------------------------------------------------------------------------------------------------!
1733 SUBROUTINE module_interface_rrd_global_ftn( found )
1734
1735
1736    LOGICAL, INTENT(INOUT) ::  found    !< flag if variable was found
1737
1738
1739    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'start' )
1740
1741    CALL dynamics_rrd_global( found ) ! ToDo: change interface to pass variable
1742
1743    IF ( .NOT. found )  CALL bio_rrd_global( found ) ! ToDo: change interface to pass variable
1744    IF ( .NOT. found )  CALL bcm_rrd_global( found ) ! ToDo: change interface to pass variable
1745    IF ( .NOT. found )  CALL flight_rrd_global( found ) ! ToDo: change interface to pass variable
1746    IF ( .NOT. found )  CALL gust_rrd_global( found ) ! ToDo: change interface to pass variable
1747    IF ( .NOT. found )  CALL lpm_rrd_global( found ) ! ToDo: change interface to pass variable
1748    IF ( .NOT. found )  CALL pcm_rrd_global( found )
1749    IF ( .NOT. found )  CALL ocean_rrd_global( found ) ! ToDo: change interface to pass variable
1750    IF ( .NOT. found )  CALL salsa_rrd_global( found )
1751    IF ( .NOT. found )  CALL stg_rrd_global ( found ) ! ToDo: change interface to pass variable
1752    IF ( .NOT. found )  CALL wtm_rrd_global( found ) ! ToDo: change interface to pass variable
1753    IF ( .NOT. found )  CALL surface_data_output_rrd_global( found )
1754
1755    IF ( .NOT. found )  CALL user_rrd_global( found ) ! ToDo: change interface to pass variable
1756
1757    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'end' )
1758
1759
1760 END SUBROUTINE module_interface_rrd_global_ftn
1761
1762
1763!--------------------------------------------------------------------------------------------------!
1764! Description:
1765! ------------
1766!> Read module-specific restart data in MPI format globaly shared by all MPI ranks
1767!--------------------------------------------------------------------------------------------------!
1768 SUBROUTINE module_interface_rrd_global_mpi
1769
1770
1771    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'start' )
1772
1773    CALL dynamics_rrd_global
1774
1775    IF ( biometeorology )       CALL bio_rrd_global
1776    IF ( bulk_cloud_model )     CALL bcm_rrd_global
1777    IF ( virtual_flight )       CALL flight_rrd_global
1778    IF ( gust_module_enabled )  CALL gust_rrd_global
1779    IF ( particle_advection )   CALL lpm_rrd_global
1780    IF ( plant_canopy )         CALL pcm_rrd_global
1781    IF ( ocean_mode )           CALL ocean_rrd_global
1782    IF ( salsa )                CALL salsa_rrd_global
1783    IF ( syn_turb_gen )         CALL stg_rrd_global
1784    IF ( wind_turbine )         CALL wtm_rrd_global
1785    IF ( surface_output )       CALL surface_data_output_rrd_global
1786
1787    IF ( user_module_enabled )  CALL user_rrd_global
1788
1789    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'end' )
1790
1791
1792 END SUBROUTINE module_interface_rrd_global_mpi
1793
1794
1795!------------------------------------------------------------------------------!
1796! Description:
1797! ------------
1798!> Write module-specific restart data globaly shared by all MPI ranks
1799!------------------------------------------------------------------------------!
1800 SUBROUTINE module_interface_wrd_global
1801
1802
1803    IF ( debug_output )  CALL debug_message( 'module-specific write global restart data', 'start' )
1804
1805    CALL dynamics_wrd_global
1806
1807    IF ( biometeorology )       CALL bio_wrd_global
1808    IF ( bulk_cloud_model )     CALL bcm_wrd_global
1809    IF ( virtual_flight )       CALL flight_wrd_global
1810    IF ( gust_module_enabled )  CALL gust_wrd_global
1811    IF ( particle_advection )   CALL lpm_wrd_global
1812    IF ( plant_canopy )         CALL pcm_wrd_global
1813    IF ( ocean_mode )           CALL ocean_wrd_global
1814    IF ( salsa )                CALL salsa_wrd_global
1815    IF ( syn_turb_gen )         CALL stg_wrd_global
1816    IF ( wind_turbine )         CALL wtm_wrd_global
1817    IF ( surface_output )       CALL surface_data_output_wrd_global
1818
1819    IF ( user_module_enabled )  CALL user_wrd_global
1820
1821    IF ( debug_output )  CALL debug_message( 'module-specific write global restart data', 'end' )
1822
1823
1824 END SUBROUTINE module_interface_wrd_global
1825
1826
1827!------------------------------------------------------------------------------!
1828! Description:
1829! ------------
1830!> Read module-specific local restart data arrays (Fortran binary format).
1831!------------------------------------------------------------------------------!
1832 SUBROUTINE module_interface_rrd_local_ftn( map_index,                             &
1833                                           nxlf, nxlc, nxl_on_file,               &
1834                                           nxrf, nxrc, nxr_on_file,               &
1835                                           nynf, nync, nyn_on_file,               &
1836                                           nysf, nysc, nys_on_file,               &
1837                                           tmp_2d, tmp_3d, found )
1838
1839
1840    INTEGER(iwp), INTENT(IN)  ::  map_index    !<
1841    INTEGER(iwp), INTENT(IN)  ::  nxlc         !<
1842    INTEGER(iwp), INTENT(IN)  ::  nxlf         !<
1843    INTEGER(iwp), INTENT(IN)  ::  nxl_on_file  !<
1844    INTEGER(iwp), INTENT(IN)  ::  nxrc         !<
1845    INTEGER(iwp), INTENT(IN)  ::  nxrf         !<
1846    INTEGER(iwp), INTENT(IN)  ::  nxr_on_file  !<
1847    INTEGER(iwp), INTENT(IN)  ::  nync         !<
1848    INTEGER(iwp), INTENT(IN)  ::  nynf         !<
1849    INTEGER(iwp), INTENT(IN)  ::  nyn_on_file  !<
1850    INTEGER(iwp), INTENT(IN)  ::  nysc         !<
1851    INTEGER(iwp), INTENT(IN)  ::  nysf         !<
1852    INTEGER(iwp), INTENT(IN)  ::  nys_on_file  !<
1853    LOGICAL,      INTENT(INOUT) ::  found        !< flag if variable was found
1854
1855    REAL(wp), &
1856       DIMENSION(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp), &
1857       INTENT(OUT) :: tmp_2d   !<
1858    REAL(wp), &
1859       DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp), &
1860       INTENT(OUT) :: tmp_3d   !<
1861
1862
1863    IF ( debug_output )  THEN
1864       CALL debug_message( 'module-specific read local restart data (Fortran binary)', 'start' )
1865    ENDIF
1866
1867    CALL dynamics_rrd_local(                                                   &
1868           map_index,                                                          &
1869           nxlf, nxlc, nxl_on_file,                                            &
1870           nxrf, nxrc, nxr_on_file,                                            &
1871           nynf, nync, nyn_on_file,                                            &
1872           nysf, nysc, nys_on_file,                                            &
1873           tmp_2d, tmp_3d, found                                               &
1874        ) ! ToDo: change interface to pass variable
1875
1876    IF ( .NOT. found )  CALL bio_rrd_local(                                    &
1877                               found                                           &
1878                            )
1879
1880    IF ( .NOT. found )  CALL bcm_rrd_local(                                    &
1881                               map_index,                                      &
1882                               nxlf, nxlc, nxl_on_file,                        &
1883                               nxrf, nxrc, nxr_on_file,                        &
1884                               nynf, nync, nyn_on_file,                        &
1885                               nysf, nysc, nys_on_file,                        &
1886                               tmp_2d, tmp_3d, found                           &
1887                            ) ! ToDo: change interface to pass variable
1888
1889    IF ( .NOT. found )  CALL chem_rrd_local(                                   &
1890                               map_index,                                      &
1891                               nxlf, nxlc, nxl_on_file,                        &
1892                               nxrf, nxrc, nxr_on_file,                        &
1893                               nynf, nync, nyn_on_file,                        &
1894                               nysf, nysc, nys_on_file,                        &
1895                               tmp_3d, found                                   &
1896                            ) ! ToDo: change interface to pass variable
1897
1898    IF ( .NOT. found )  CALL doq_rrd_local(                                    &
1899                               map_index,                                      &
1900                               nxlf, nxlc, nxl_on_file,                        &
1901                               nxrf, nxrc, nxr_on_file,                        &
1902                               nynf, nync, nyn_on_file,                        &
1903                               nysf, nysc, nys_on_file,                        &
1904                               tmp_2d, tmp_3d, found                           &
1905                            ) ! ToDo: change interface to pass variable
1906
1907    IF ( .NOT. found )  CALL gust_rrd_local(                                   &
1908                               map_index,                                      &
1909                               nxlf, nxlc, nxl_on_file,                        &
1910                               nxrf, nxrc, nxr_on_file,                        &
1911                               nynf, nync, nyn_on_file,                        &
1912                               nysf, nysc, nys_on_file,                        &
1913                               tmp_2d, tmp_3d, found                           &
1914                            ) ! ToDo: change interface to pass variable
1915
1916    IF ( .NOT. found )  CALL lpm_rrd_local(                                    &
1917                               map_index,                                      &
1918                               nxlf, nxlc, nxl_on_file,                        &
1919                               nxrf, nxrc, nxr_on_file,                        &
1920                               nynf, nync, nyn_on_file,                        &
1921                               nysf, nysc, nys_on_file,                        &
1922                               tmp_3d, found                                   &
1923                            ) ! ToDo: change interface to pass variable
1924
1925    IF ( .NOT. found )  CALL lsm_rrd_local(                                    &
1926                               map_index,                                      &
1927                               nxlf, nxlc, nxl_on_file,                        &
1928                               nxrf, nxrc, nxr_on_file,                        &
1929                               nynf, nync, nyn_on_file,                        &
1930                               nysf, nysc, nys_on_file,                        &
1931                               tmp_2d, found                                   &
1932                            ) ! ToDo: change interface to pass variable
1933
1934     IF ( .NOT. found )  CALL pcm_rrd_local(                                   &
1935                               map_index,                                      &
1936                               nxlf, nxlc, nxl_on_file,                        &
1937                               nxrf, nxrc, nxr_on_file,                        &
1938                               nynf, nync, nyn_on_file,                        &
1939                               nysf, nysc, nys_on_file,                        &
1940                               found                                           &
1941                                           )
1942
1943    IF ( .NOT. found )  CALL ocean_rrd_local(                                  &
1944                               map_index,                                      &
1945                               nxlf, nxlc, nxl_on_file,                        &
1946                               nxrf, nxrc, nxr_on_file,                        &
1947                               nynf, nync, nyn_on_file,                        &
1948                               nysf, nysc, nys_on_file,                        &
1949                               tmp_3d, found                                   &
1950                            ) ! ToDo: change interface to pass variable
1951
1952    IF ( .NOT. found )  CALL radiation_rrd_local(                              &
1953                               map_index,                                      &
1954                               nxlf, nxlc, nxl_on_file,                        &
1955                               nxrf, nxrc, nxr_on_file,                        &
1956                               nynf, nync, nyn_on_file,                        &
1957                               nysf, nysc, nys_on_file,                        &
1958                               tmp_2d, tmp_3d, found                           &
1959                            ) ! ToDo: change interface to pass variable
1960
1961    IF ( .NOT. found )  CALL salsa_rrd_local(                                  &
1962                               map_index,                                      &
1963                               nxlf, nxlc, nxl_on_file,                        &
1964                               nxrf, nxrc, nxr_on_file,                        &
1965                               nynf, nync, nyn_on_file,                        &
1966                               nysf, nysc, nys_on_file,                        &
1967                               tmp_3d, found                                   &
1968                            ) ! ToDo: change interface to pass variable
1969
1970    IF ( .NOT. found )  CALL usm_rrd_local(                                    &
1971                               map_index,                                      &
1972                               nxlf, nxlc, nxl_on_file,                        &
1973                               nxrf, nxr_on_file,                              &
1974                               nynf, nyn_on_file,                              &
1975                               nysf, nysc, nys_on_file,                        &
1976                               found                                           &
1977                            ) ! ToDo: change interface to pass variable
1978!
1979!-- Surface data do not need overlap data, so do not pass these information.
1980    IF ( .NOT. found )  CALL surface_data_output_rrd_local( found )
1981
1982    IF ( .NOT. found )  CALL user_rrd_local(                                   &
1983                               map_index,                                      &
1984                               nxlf, nxlc, nxl_on_file,                        &
1985                               nxrf, nxrc, nxr_on_file,                        &
1986                               nynf, nync, nyn_on_file,                        &
1987                               nysf, nysc, nys_on_file,                        &
1988                               tmp_3d, found                                   &
1989                            ) ! ToDo: change interface to pass variable
1990
1991    IF ( debug_output )  THEN
1992       CALL debug_message( 'module-specific read local restart data (Fortran binary)', 'end' )
1993    ENDIF
1994
1995 END SUBROUTINE module_interface_rrd_local_ftn
1996
1997
1998!------------------------------------------------------------------------------!
1999! Description:
2000! ------------
2001!> Read module-specific local restart data arrays (MPI-IO).
2002!------------------------------------------------------------------------------!
2003 SUBROUTINE module_interface_rrd_local_mpi
2004
2005    IF ( debug_output )  THEN
2006       CALL debug_message( 'module-specific read local restart data (MPI-IO)', 'start' )
2007    ENDIF
2008
2009    CALL dynamics_rrd_local
2010
2011    IF ( biometeorology )       CALL bio_rrd_local
2012    IF ( bulk_cloud_model )     CALL bcm_rrd_local
2013    IF ( air_chemistry )        CALL chem_rrd_local
2014    CALL doq_rrd_local
2015    IF ( gust_module_enabled )  CALL gust_rrd_local
2016    IF ( particle_advection )   CALL lpm_rrd_local
2017    IF ( land_surface )         CALL lsm_rrd_local
2018    IF ( plant_canopy )         CALL pcm_rrd_local
2019    IF ( ocean_mode )           CALL ocean_rrd_local
2020    IF ( radiation )            CALL radiation_rrd_local
2021    IF ( salsa )                CALL salsa_rrd_local
2022    IF ( urban_surface )        CALL usm_rrd_local
2023    IF ( surface_output )       CALL surface_data_output_rrd_local
2024
2025    IF ( user_module_enabled )  CALL user_rrd_local
2026
2027    IF ( debug_output )  THEN
2028       CALL debug_message( 'module-specific read local restart data (Fortran binary)', 'end' )
2029    ENDIF
2030
2031 END SUBROUTINE module_interface_rrd_local_mpi
2032
2033
2034!------------------------------------------------------------------------------!
2035! Description:
2036! ------------
2037!> Write module-specific restart data specific to local MPI ranks
2038!------------------------------------------------------------------------------!
2039 SUBROUTINE module_interface_wrd_local
2040
2041
2042    IF ( debug_output )  CALL debug_message( 'module-specific write local restart data', 'start' )
2043
2044    CALL dynamics_wrd_local
2045
2046    IF ( biometeorology )       CALL bio_wrd_local
2047    IF ( bulk_cloud_model )     CALL bcm_wrd_local
2048    IF ( air_chemistry )        CALL chem_wrd_local
2049    CALL doq_wrd_local
2050    IF ( gust_module_enabled )  CALL gust_wrd_local
2051    IF ( particle_advection )   CALL lpm_wrd_local
2052    IF ( land_surface )         CALL lsm_wrd_local
2053    IF ( plant_canopy )         CALL pcm_wrd_local
2054    IF ( ocean_mode )           CALL ocean_wrd_local
2055    IF ( radiation )            CALL radiation_wrd_local
2056    IF ( salsa )                CALL salsa_wrd_local
2057    IF ( urban_surface )        CALL usm_wrd_local
2058    IF ( surface_output )       CALL surface_data_output_wrd_local
2059
2060    IF ( user_module_enabled )  CALL user_wrd_local
2061
2062    IF ( debug_output )  CALL debug_message( 'module-specific write local restart data', 'end' )
2063
2064
2065 END SUBROUTINE module_interface_wrd_local
2066
2067
2068!------------------------------------------------------------------------------!
2069! Description:
2070! ------------
2071!> Perform module-specific last actions before the program terminates
2072!------------------------------------------------------------------------------!
2073 SUBROUTINE module_interface_last_actions
2074
2075    INTEGER ::  return_value  !< returned status value of a called function
2076
2077
2078    IF ( debug_output )  CALL debug_message( 'module-specific last actions', 'start' )
2079
2080    return_value = dom_finalize_output()
2081
2082    CALL dynamics_last_actions
2083
2084    IF ( user_module_enabled )  CALL user_last_actions
2085
2086    IF ( debug_output )  CALL debug_message( 'module-specific last actions', 'end' )
2087
2088
2089 END SUBROUTINE module_interface_last_actions
2090
2091
2092 END MODULE module_interface
Note: See TracBrowser for help on using the repository browser.