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

Last change on this file since 3929 was 3929, checked in by banzhafs, 5 years ago

Correct/complete module_interface introduction for chemistry model and bug fix in chem_depo subroutine

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