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

Last change on this file since 4401 was 4400, checked in by suehring, 4 years ago

Revision of the virtual-measurement module: data input from NetCDF file; removed binary output - instead parallel NetCDF output using the new data-output module; variable attributes added; further variables added that can be sampled, file connections added; Functions for coordinate transformation moved to basic_constants_and_equations; netcdf_data_input_mod: unused routines netcdf_data_input_att and netcdf_data_input_var removed; new routines to inquire fill values added; Preprocessing script (palm_cvd) to setup virtual-measurement input files provided; postprocessor combine_virtual_measurements deleted

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