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

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

diagnostic output: Modularize diagnostic output, rename subroutines; formatting adjustments; allocate arrays only when required; add output of uu, vv, ww to enable variance calculation via temporal EC method; radiation: bugfix in masked data output; flow_statistics: Correct conversion to kinematic vertical scalar fluxes in case of pw-scheme and statistic regions

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