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

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

Merge with branch resler: biomet- output of bio_mrt added; plant_canopy - separate vertical dimension for 3D output (to save disk space); radiation - remove unused plant canopy variables; urban-surface model - do not add anthropogenic heat during wall spin-up

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