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

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

chem_emissions: Replace global arrays also in mode_emis branch; diagnostic output: restructure initialization in order to work also when data output during spin-up is enabled; radiation: give informative message on raytracing distance only by core zero not by all cores

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