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

Last change on this file since 4517 was 4517, checked in by raasch, 4 years ago

added restart with MPI-IO for reading local arrays

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