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

Last change on this file since 4313 was 4281, checked in by schwenkel, 4 years ago

Moved boundary_conds to dynamics module

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