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

Last change on this file since 3887 was 3887, checked in by schwenkel, 5 years ago

bugfix for chemistry_model_mod via introducing module_interface_exchange_horiz

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