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

Last change on this file since 4143 was 4132, checked in by suehring, 5 years ago

Bugfix in masked data output for prognostic quantities

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