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

Last change on this file since 4178 was 4173, checked in by gronemeier, 5 years ago

add vdi_internal_controls

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