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

Last change on this file since 4411 was 4411, checked in by maronga, 4 years ago

Added NetCDf output for wind turbine model. Added new features to palmrungui

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