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

Last change on this file since 4048 was 4048, checked in by knoop, 5 years ago

Moved turbulence_closure_mod calls into module_interface

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