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

Last change on this file since 4420 was 4414, checked in by suehring, 4 years ago

Remove deprecated topography arrays; Move basic initialization of numerics into an extra module interface

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