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

Last change on this file since 4407 was 4407, checked in by knoop, 4 years ago

Changed program_debug_output_unit to 9 in dom_init call

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