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

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

restart data handling with MPI-IO added, first part

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