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

Last change on this file since 3930 was 3930, checked in by forkel, 5 years ago

changed subroutine name from chem_non_transport_physics to chem_non_advective_processes

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