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

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