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

Last change on this file since 3987 was 3987, checked in by kanani, 5 years ago

clean up location, debug and error messages

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