Ignore:
Timestamp:
Jun 21, 2019 6:58:09 PM (5 years ago)
Author:
knoop
Message:

Initial introduction of the dynamics module with only dynamics_swap_timelevel implemented

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/module_interface.f90

    r4039 r4047  
    2525! -----------------
    2626! $Id$
     27! Introduction of the dynamics module
     28!
     29! 4039 2019-06-18 10:32:41Z suehring
    2730! Introduce diagnostic output
    28 ! 
     31!
    2932! 4028 2019-06-13 12:21:37Z schwenkel
    3033! Further modularization of particle code components
    31 ! 
     34!
    3235! 4017 2019-06-06 12:16:46Z schwenkel
    33 ! local_pf need INTENT(INOUT) attribute rather than INTENT(OUT). This is 
     36! local_pf need INTENT(INOUT) attribute rather than INTENT(OUT). This is
    3437! because INTENT(OUT) sets the array to not-defined. Especially for outputs that
    35 ! are not defined everywhere, e.g. land-surface outputs, this will be 
    36 ! problematic as NaN will be output.   
    37 ! 
     38! are not defined everywhere, e.g. land-surface outputs, this will be
     39! problematic as NaN will be output.
     40!
    3841! 3987 2019-05-22 09:52:13Z kanani
    3942! Introduce switchable DEBUG file output via debug_message routine
    40 ! 
     43!
    4144! 3956 2019-05-07 12:32:52Z monakurppa
    42 ! - Added calls for salsa_non_advective_processes and 
     45! - Added calls for salsa_non_advective_processes and
    4346!   salsa_exchange_horiz_bounds
    4447! - Moved the call for salsa_data_output_2d/3d before that of
     
    4649!   salsa output variable and encounters a segmentation fault for "Ntot" due
    4750!   to the shortoutput name
    48 ! 
     51!
    4952! 3931 2019-04-24 16:34:28Z schwenkel
    5053! Changed non_transport_physics to non_advective_processes
    51 ! 
     54!
    5255! 3930 2019-04-24 14:57:18Z forkel
    5356! Correct/complete module_interface introduction for chemistry model
    5457!
    5558! 3887 2019 -04-12 08:47:41Z schwenkel
    56 ! Changes related to global restructuring of location messages and introduction 
     59! Changes related to global restructuring of location messages and introduction
    5760! of additional debug messages
    58 ! 
     61!
    5962! 3880 2019 -04-08 21:43:02Z knoop
    6063! Add a call for salsa_prognostic_equations
    61 ! 
     64!
    6265! 3840 2019-03-29 10:35:52Z knoop
    6366! bugfix: intent of dummy arguments changed to inout
    64 ! 
     67!
    6568! 3770 2019-02-28 11:22:32Z moh.hefny
    6669! removed unused variables in module_interface_check_data_output_ts
     
    6871! 3767 08:18:02Z raasch
    6972! unused variable file_index removed from subroutine parameter list
    70 ! 
     73!
    7174! 3766 2019-02-26 16:23:41Z raasch
    7275! first argument removed from module_interface_rrd_*, statement added to avoid
    7376! compiler warning about unused variable, file reformatted with respect to coding
    7477! standards
    75 ! 
     78!
    7679! 3762 2019-02-25 16:54:16Z suehring
    7780! only pass required arguments to surface_data_output_rrd_local
    78 ! 
     81!
    7982! 3747 2019-02-16 15:15:23Z gronemeier
    8083! Call user_init_arrays
    81 ! 
     84!
    8285! 3745 2019-02-15 18:57:56Z suehring
    8386! Add indoor model
    84 ! 
     87!
    8588! 3744 2019-02-15 18:38:58Z suehring
    8689! Removed bio_check_parameters as the method is empty.
    87 ! 
     90!
    8891! 3735 2019-02-12 09:52:40Z dom_dwd_user
    89 ! Accepting variable j from check_parameters and passing it to 
     92! Accepting variable j from check_parameters and passing it to
    9093! bio_check_data_output
    9194! Add required restart data for surface output module
    92 ! 
     95!
    9396! 3731 2019-02-11 13:06:27Z suehring
    9497! Add check_parameters routine for virtual measurements
    95 ! 
     98!
    9699! 3711 2019-01-31 13:44:26Z knoop
    97100! Introduced module_interface_init_checks for post-init checks
    98 ! 
     101!
    99102! 3705 2019-01-29 19:56:39Z suehring
    100103! Add last_actions for virtual measurements
    101 ! 
     104!
    102105! 3704 2019-01-29 19:51:41Z suehring
    103106! Some interface calls moved to module_interface + cleanup
    104 ! 
     107!
    105108! 3684 2019-01-20 20:20:58Z knoop
    106109! Bugfix: made unit intend INOUT
    107 ! 
     110!
    108111! 3650 2019-01-04 13:01:33Z kanani
    109112! Add restart routines for biometeorology
    110 ! 
     113!
    111114! 3649 2019-01-02 16:52:21Z suehring
    112115! Initialize strings, in order to avoid compiler warnings for non-initialized
    113116! characters with intent(out) attribute
    114 ! 
     117!
    115118! 3648 2019-01-02 16:35:46Z suehring
    116119! Rename subroutines for surface-data output
    117 ! 
     120!
    118121! 3641 2018-12-23 22:10:01Z knoop
    119122! Initial implementation of the PALM module interface
    120123!
    121 ! 
     124!
    122125! Description:
    123126! ------------
     
    136139!-- load module-specific control parameters.
    137140!-- ToDo: move all of them to respective module or a dedicated central module
     141
     142    USE dynamics_mod, &
     143        ONLY:  dynamics_parin, &
     144               dynamics_check_parameters, &
     145               dynamics_check_data_output_ts, &
     146               dynamics_check_data_output_pr, &
     147               dynamics_check_data_output, &
     148               dynamics_init_masks, &
     149               dynamics_define_netcdf_grid, &
     150               dynamics_init_arrays, &
     151               dynamics_init, &
     152               dynamics_init_checks, &
     153               dynamics_header, &
     154               dynamics_actions, &
     155               dynamics_non_advective_processes, &
     156               dynamics_exchange_horiz, &
     157               dynamics_prognostic_equations, &
     158               dynamics_swap_timelevel, &
     159               dynamics_3d_data_averaging, &
     160               dynamics_data_output_2d, &
     161               dynamics_data_output_3d, &
     162               dynamics_statistics, &
     163               dynamics_rrd_global, &
     164               dynamics_rrd_local, &
     165               dynamics_wrd_global, &
     166               dynamics_wrd_local, &
     167               dynamics_last_actions
     168
     169    USE turbulence_closure_mod, &
     170        ONLY:  tcm_swap_timelevel
     171
    138172    USE control_parameters,                                                    &
    139173        ONLY:  air_chemistry,                                                  &
     
    213247              chem_rrd_local,                                                  &
    214248              chem_wrd_local
    215      
    216     USE diagnostic_output_quantities_mod,                                      & 
     249
     250    USE diagnostic_output_quantities_mod,                                      &
    217251        ONLY:  doq_3d_data_averaging,                                          &
    218252               doq_check_data_output,                                          &
     
    257291               im_data_output_3d,                                              &
    258292               im_init
    259                
     293
    260294    USE lagrangian_particle_model_mod,                                         &
    261295        ONLY:  lpm_parin,                                                      &
    262296               lpm_header,                                                     &
    263297               lpm_check_parameters,                                           &
    264                lpm_init_arrays,                                                &                             
     298               lpm_init_arrays,                                                &
    265299               lpm_init,                                                       &
    266300               lpm_actions,                                                    &
     
    269303               lpm_wrd_local,                                                  &
    270304               lpm_wrd_global
    271                
     305
    272306    USE land_surface_model_mod,                                                &
    273307        ONLY:  lsm_parin,                                                      &
     
    317351               ocean_rrd_local,                                                &
    318352               ocean_wrd_local
    319                
     353
    320354    USE particle_attributes,                                                   &
    321         ONLY:  particle_advection               
     355        ONLY:  particle_advection
    322356
    323357    USE plant_canopy_model_mod,                                                &
     
    394428               usm_rrd_local,                                                  &
    395429               usm_wrd_local
     430
     431    USE virtual_measurement_mod,                                               &
     432        ONLY:  vm_check_parameters,                                            &
     433               vm_init,                                                        &
     434               vm_last_actions,                                                &
     435               vm_parin
     436
     437    USE wind_turbine_model_mod,                                                &
     438        ONLY:  wtm_parin,                                                      &
     439               wtm_check_parameters,                                           &
     440               wtm_init_arrays,                                                &
     441               wtm_init,                                                       &
     442               wtm_actions,                                                    &
     443               wtm_rrd_global,                                                 &
     444               wtm_wrd_global
    396445
    397446    USE user,                                                                  &
     
    415464               user_wrd_local,                                                 &
    416465               user_last_actions
    417 
    418     USE virtual_measurement_mod,                                               &
    419         ONLY:  vm_check_parameters,                                            &
    420                vm_init,                                                        &
    421                vm_last_actions,                                                &
    422                vm_parin
    423 
    424     USE wind_turbine_model_mod,                                                &
    425         ONLY:  wtm_parin,                                                      &
    426                wtm_check_parameters,                                           &
    427                wtm_init_arrays,                                                &
    428                wtm_init,                                                       &
    429                wtm_actions,                                                    &
    430                wtm_rrd_global,                                                 &
    431                wtm_wrd_global
    432466
    433467    IMPLICIT NONE
     
    518552       MODULE PROCEDURE module_interface_non_advective_processes_ij
    519553    END INTERFACE module_interface_non_advective_processes
    520    
     554
    521555    INTERFACE module_interface_exchange_horiz
    522556       MODULE PROCEDURE module_interface_exchange_horiz
    523557    END INTERFACE module_interface_exchange_horiz
    524    
     558
    525559    INTERFACE module_interface_prognostic_equations
    526560       MODULE PROCEDURE module_interface_prognostic_equations
     
    581615
    582616    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'start' )
     617
     618    CALL dynamics_parin
    583619
    584620    CALL bio_parin
     
    588624    CALL gust_parin
    589625    CALL im_parin
    590     CALL lpm_parin     
     626    CALL lpm_parin
    591627    CALL lsm_parin
    592628    ! ToDo: create parin routine for large_scale_forcing and nudging (should be seperate modules or new module switch)
     
    600636    CALL surface_data_output_parin
    601637    CALL stg_parin
    602     CALL user_parin ! ToDo: make user code a single Fortran module
    603638    CALL usm_parin
    604639    CALL vm_parin
    605640    CALL wtm_parin
    606641
     642    CALL user_parin
     643
    607644    IF ( debug_output )  CALL debug_message( 'reading module-specific parameters', 'end' )
    608645
     
    620657
    621658    IF ( debug_output )  CALL debug_message( 'checking module-specific parameters', 'start' )
     659
     660    CALL dynamics_check_parameters
    622661
    623662    IF ( bulk_cloud_model )     CALL bcm_check_parameters
     
    625664    IF ( gust_module_enabled )  CALL gust_check_parameters
    626665    IF ( indoor_model )         CALL im_check_parameters
    627     IF ( particle_advection )   CALL lpm_check_parameters       
     666    IF ( particle_advection )   CALL lpm_check_parameters
    628667    IF ( land_surface )         CALL lsm_check_parameters
    629668    IF ( large_scale_forcing  .OR.  nudging )  CALL lsf_nudging_check_parameters ! ToDo: create single module switch
     
    639678    IF ( virtual_measurement )  CALL vm_check_parameters
    640679    IF ( wind_turbine )         CALL wtm_check_parameters
     680
    641681    IF ( user_module_enabled )  CALL user_check_parameters
    642682
     
    663703    IF ( debug_output )  CALL debug_message( 'checking module-specific data output ts', 'start' )
    664704
     705    CALL dynamics_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
     706
    665707    IF ( radiation )  THEN
    666708       CALL radiation_check_data_output_ts( dots_max, dots_num )
     
    694736    IF ( debug_output )  CALL debug_message( 'checking module-specific data output pr', 'start' )
    695737
     738    CALL dynamics_check_data_output_pr( variable, var_count, unit, dopr_unit )
     739
    696740    IF ( unit == 'illegal' .AND.  bulk_cloud_model )  THEN
    697741       CALL bcm_check_data_output_pr( variable, var_count, unit, dopr_unit )
     
    751795    IF ( debug_output )  CALL debug_message( 'checking module-specific data output 2d/3d', 'start' )
    752796
     797    CALL dynamics_check_data_output( variable, unit )
     798
    753799    IF ( unit == 'illegal'  .AND.  biometeorology )  THEN
    754800       CALL bio_check_data_output( variable, unit, i, j, ilen, k )
     
    763809       CALL chem_check_data_output( variable, unit, i, ilen, k )
    764810    ENDIF
    765    
     811
    766812    IF ( unit == 'illegal' )  THEN
    767813       CALL doq_check_data_output( variable, unit )
     
    796842       CALL im_check_data_output( variable, unit )
    797843    ENDIF
    798    
     844
    799845    IF ( unit == 'illegal'  .AND.  urban_surface                      &
    800846        .AND.  variable(1:4) == 'usm_' )  THEN  ! ToDo: remove aditional conditions
     
    827873
    828874    IF ( debug_output )  CALL debug_message( 'initializing module-specific masks', 'start' )
     875
     876    CALL dynamics_init_masks( variable, unit )
    829877
    830878    IF ( unit == 'illegal'  .AND.  air_chemistry                               &
     
    897945    IF ( debug_output )  CALL debug_message( 'initializing module-specific arrays', 'start' )
    898946
     947    CALL dynamics_init_arrays
     948
    899949    IF ( bulk_cloud_model    )  CALL bcm_init_arrays
    900950    IF ( air_chemistry       )  CALL chem_init_arrays
    901951    IF ( gust_module_enabled )  CALL gust_init_arrays
    902     IF ( particle_advection  )  CALL lpm_init_arrays       
     952    IF ( particle_advection  )  CALL lpm_init_arrays
    903953    IF ( land_surface        )  CALL lsm_init_arrays
    904954    IF ( ocean_mode          )  CALL ocean_init_arrays
     
    907957    IF ( surface_output      )  CALL surface_data_output_init_arrays
    908958    IF ( wind_turbine        )  CALL wtm_init_arrays
     959
    909960    IF ( user_module_enabled )  CALL user_init_arrays
    910961
     
    924975
    925976    IF ( debug_output )  CALL debug_message( 'module-specific initialization', 'start' )
     977
     978    CALL dynamics_init
    926979
    927980    IF ( biometeorology      )  CALL bio_init
     
    931984    IF ( gust_module_enabled )  CALL gust_init
    932985    IF ( indoor_model        )  CALL im_init
    933     IF ( particle_advection  )  CALL lpm_init   
     986    IF ( particle_advection  )  CALL lpm_init
    934987    IF ( large_scale_forcing )  CALL lsf_init
    935988    IF ( land_surface        )  CALL lsm_init
     
    942995    IF ( wind_turbine        )  CALL wtm_init
    943996    IF ( radiation           )  CALL radiation_init
     997
    944998    IF ( user_module_enabled )  CALL user_init
    945999
     
    9601014    IF ( debug_output )  CALL debug_message( 'module-specific post-initialization checks', 'start' )
    9611015
     1016    CALL dynamics_init_checks
     1017
    9621018    IF ( biometeorology      )  CALL bio_init_checks
    9631019
     
    9801036
    9811037    IF ( debug_output )  CALL debug_message( 'module-specific header output', 'start' )
     1038
     1039    CALL dynamics_header( io )
    9821040
    9831041    IF ( biometeorology      )  CALL bio_header ( io )
     
    9861044    IF ( virtual_flight      )  CALL flight_header( io )
    9871045    IF ( gust_module_enabled )  CALL gust_header( io )
    988     IF ( particle_advection  )  CALL lpm_header( io )   
     1046    IF ( particle_advection  )  CALL lpm_header( io )
    9891047    IF ( land_surface        )  CALL lsm_header( io )
    9901048    IF ( large_scale_forcing )  CALL lsf_nudging_header( io )
     
    9961054    IF ( calculate_spectra   )  CALL spectra_header( io )
    9971055    IF ( syn_turb_gen        )  CALL stg_header( io )
     1056
    9981057    IF ( user_module_enabled )  CALL user_header( io )
    9991058
     
    10141073    CHARACTER (LEN=*), INTENT(IN) ::  location !< call location string
    10151074
     1075    CALL dynamics_actions( location )
    10161076
    10171077    IF ( bulk_cloud_model    )  CALL bcm_actions( location )
    10181078    IF ( air_chemistry       )  CALL chem_actions( location )
    10191079    IF ( gust_module_enabled )  CALL gust_actions( location )
    1020     IF ( particle_advection  )  CALL lpm_actions( location )   
     1080    IF ( particle_advection  )  CALL lpm_actions( location )
    10211081    IF ( ocean_mode          )  CALL ocean_actions( location )
    10221082    IF ( salsa               )  CALL salsa_actions( location )
    10231083    IF ( wind_turbine        )  CALL wtm_actions( location )
     1084
    10241085    IF ( user_module_enabled )  CALL user_actions( location )
    10251086
     
    10401101    CHARACTER (LEN=*), INTENT(IN) ::  location  !< call location string
    10411102
     1103    CALL dynamics_actions( i, j, location )
    10421104
    10431105    IF ( bulk_cloud_model    )  CALL bcm_actions( i, j, location )
     
    10471109    IF ( salsa               )  CALL salsa_actions( i, j, location )
    10481110    IF ( wind_turbine        )  CALL wtm_actions( i, j, location )
     1111
    10491112    IF ( user_module_enabled )  CALL user_actions( i, j, location )
    10501113
     
    10581121!> Compute module-specific non_advective_processes (vector-optimized)
    10591122!------------------------------------------------------------------------------!
    1060  SUBROUTINE module_interface_non_advective_processes()
    1061 
    1062 
    1063     IF ( bulk_cloud_model    )  CALL bcm_non_advective_processes()
    1064     IF ( air_chemistry       )  CALL chem_non_advective_processes()
    1065     IF ( salsa               )  CALL salsa_non_advective_processes()
     1123 SUBROUTINE module_interface_non_advective_processes
     1124
     1125
     1126    CALL dynamics_non_advective_processes
     1127
     1128    IF ( bulk_cloud_model    )  CALL bcm_non_advective_processes
     1129    IF ( air_chemistry       )  CALL chem_non_advective_processes
     1130    IF ( salsa               )  CALL salsa_non_advective_processes
    10661131
    10671132
     
    10801145    INTEGER(iwp), INTENT(IN) ::  j            !< grid index in y-direction
    10811146
     1147    CALL dynamics_non_advective_processes( i, j )
    10821148
    10831149    IF ( bulk_cloud_model    )  CALL bcm_non_advective_processes( i, j )
     
    10871153
    10881154 END SUBROUTINE module_interface_non_advective_processes_ij
    1089  
    1090 !------------------------------------------------------------------------------!
    1091 ! Description:
    1092 ! ------------
    1093 !> Exchange horiz for module-specific quantities 
    1094 !------------------------------------------------------------------------------!
    1095  SUBROUTINE module_interface_exchange_horiz()
     1155
     1156!------------------------------------------------------------------------------!
     1157! Description:
     1158! ------------
     1159!> Exchange horiz for module-specific quantities
     1160!------------------------------------------------------------------------------!
     1161 SUBROUTINE module_interface_exchange_horiz
    10961162
    10971163
    10981164    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'start' )
    10991165
    1100     IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz()
    1101     IF ( air_chemistry       )  CALL chem_exchange_horiz_bounds()
    1102     IF ( salsa               )  CALL salsa_exchange_horiz_bounds()
     1166    CALL dynamics_exchange_horiz
     1167
     1168    IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz
     1169    IF ( air_chemistry       )  CALL chem_exchange_horiz_bounds
     1170    IF ( salsa               )  CALL salsa_exchange_horiz_bounds
    11031171
    11041172    IF ( debug_output_timestep )  CALL debug_message( 'module-specific exchange_horiz', 'end' )
     
    11131181!> Compute module-specific prognostic_equations (vector-optimized)
    11141182!------------------------------------------------------------------------------!
    1115  SUBROUTINE module_interface_prognostic_equations()
    1116 
    1117 
    1118     IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations()
    1119     IF ( air_chemistry       )  CALL chem_prognostic_equations()
    1120     IF ( gust_module_enabled )  CALL gust_prognostic_equations()
    1121     IF ( ocean_mode          )  CALL ocean_prognostic_equations()
    1122     IF ( salsa               )  CALL salsa_prognostic_equations()
     1183 SUBROUTINE module_interface_prognostic_equations
     1184
     1185
     1186    CALL dynamics_prognostic_equations
     1187
     1188    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations
     1189    IF ( air_chemistry       )  CALL chem_prognostic_equations
     1190    IF ( gust_module_enabled )  CALL gust_prognostic_equations
     1191    IF ( ocean_mode          )  CALL ocean_prognostic_equations
     1192    IF ( salsa               )  CALL salsa_prognostic_equations
    11231193
    11241194
     
    11391209    INTEGER(iwp), INTENT(IN) ::  tn           !< task number of openmp task
    11401210
     1211    CALL dynamics_prognostic_equations( i, j, i_omp_start, tn )
    11411212
    11421213    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations( i, j, i_omp_start, tn )
     
    11621233
    11631234    IF ( debug_output_timestep )  CALL debug_message( 'module-specific swap timelevel', 'start' )
     1235
     1236    CALL dynamics_swap_timelevel( swap_mode )
     1237    CALL tcm_swap_timelevel( swap_mode )
    11641238
    11651239    IF ( bulk_cloud_model    )  CALL bcm_swap_timelevel( swap_mode )
     
    11921266    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data averaging', 'start' )
    11931267
     1268    CALL dynamics_3d_data_averaging( mode, variable )
     1269
    11941270    IF ( biometeorology      )  CALL bio_3d_data_averaging( mode, variable )
    11951271    IF ( bulk_cloud_model    )  CALL bcm_3d_data_averaging( mode, variable )
    11961272    IF ( air_chemistry       )  CALL chem_3d_data_averaging( mode, variable )
    1197     CALL doq_3d_data_averaging( mode, variable )
     1273    CALL doq_3d_data_averaging( mode, variable )  ! ToDo: this seems to be not according to the design
    11981274    IF ( gust_module_enabled )  CALL gust_3d_data_averaging( mode, variable )
    11991275    IF ( land_surface        )  CALL lsm_3d_data_averaging( mode, variable )
     
    12021278    IF ( salsa               )  CALL salsa_3d_data_averaging( mode, variable )
    12031279    IF ( urban_surface       )  CALL usm_3d_data_averaging( mode, variable )
     1280
    12041281    IF ( user_module_enabled )  CALL user_3d_data_averaging( mode, variable )
    12051282
     
    12341311    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 2d data output', 'start' )
    12351312
     1313    CALL dynamics_data_output_2d(                                                  &
     1314               av, variable, found, grid, mode, local_pf, two_d, nzb_do, nzt_do, fill_value &
     1315            )
     1316
    12361317    IF ( .NOT. found  .AND.  biometeorology )  THEN
    12371318       CALL bio_data_output_2d(                                                &
     
    12511332            )
    12521333    ENDIF
    1253    
     1334
    12541335    IF ( .NOT. found )  THEN
    12551336       CALL doq_output_2d(                                                     &
     
    13231404    IF ( debug_output_timestep )  CALL debug_message( 'module-specific 3d data output', 'start' )
    13241405
     1406    CALL dynamics_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
     1407    resorted = .FALSE.
     1408
    13251409    IF ( .NOT. found  .AND.  biometeorology )  THEN
    13261410       CALL bio_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
     
    13371421       resorted = .TRUE.
    13381422    ENDIF
    1339    
     1423
    13401424    IF ( .NOT. found )  THEN
    13411425       CALL doq_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    13421426       resorted = .TRUE.
    13431427    ENDIF
    1344    
     1428
    13451429    IF ( .NOT. found  .AND.  gust_module_enabled )  THEN
    13461430       CALL gust_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    13471431       resorted = .TRUE.
    13481432    ENDIF
    1349    
     1433
    13501434    IF ( .NOT. found  .AND.  indoor_model )  THEN
    13511435       CALL im_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
     
    14001484    IF ( debug_output_timestep )  CALL debug_message( 'module-specific statistics', 'start' )
    14011485
     1486    CALL dynamics_statistics( mode, sr, tn )
     1487
    14021488    IF ( gust_module_enabled )  CALL gust_statistics( mode, sr, tn, dots_max )
    14031489    IF ( air_chemistry       )  CALL chem_statistics( mode, sr, tn )
     1490
    14041491    IF ( user_module_enabled )  CALL user_statistics( mode, sr, tn )
    14051492
     
    14221509
    14231510    IF ( debug_output )  CALL debug_message( 'module-specific read global restart data', 'start' )
     1511
     1512    CALL dynamics_rrd_global( found ) ! ToDo: change interface to pass variable
    14241513
    14251514    IF ( .NOT. found )  CALL bio_rrd_global( found ) ! ToDo: change interface to pass variable
     
    14271516    IF ( .NOT. found )  CALL flight_rrd_global( found ) ! ToDo: change interface to pass variable
    14281517    IF ( .NOT. found )  CALL gust_rrd_global( found ) ! ToDo: change interface to pass variable
    1429     IF ( .NOT. found )  CALL lpm_rrd_global( found ) ! ToDo: change interface to pass variable       
     1518    IF ( .NOT. found )  CALL lpm_rrd_global( found ) ! ToDo: change interface to pass variable
    14301519    IF ( .NOT. found )  CALL ocean_rrd_global( found ) ! ToDo: change interface to pass variable
    14311520    IF ( .NOT. found )  CALL stg_rrd_global ( found ) ! ToDo: change interface to pass variable
    14321521    IF ( .NOT. found )  CALL wtm_rrd_global( found ) ! ToDo: change interface to pass variable
    14331522    IF ( .NOT. found )  CALL surface_data_output_rrd_global( found )
     1523
    14341524    IF ( .NOT. found )  CALL user_rrd_global( found ) ! ToDo: change interface to pass variable
    14351525
     
    14491539
    14501540    IF ( debug_output )  CALL debug_message( 'module-specific write global restart data', 'start' )
     1541
     1542    CALL dynamics_wrd_global
    14511543
    14521544    IF ( biometeorology )       CALL bio_wrd_global
     
    14581550    IF ( wind_turbine )         CALL wtm_wrd_global
    14591551    IF ( surface_output )       CALL surface_data_output_wrd_global
     1552
    14601553    IF ( user_module_enabled )  CALL user_wrd_global
    14611554
     
    15041597    IF ( debug_output )  CALL debug_message( 'module-specific read local restart data', 'start' )
    15051598
     1599    CALL dynamics_rrd_local(                                                   &
     1600           map_index,                                                          &
     1601           nxlf, nxlc, nxl_on_file,                                            &
     1602           nxrf, nxrc, nxr_on_file,                                            &
     1603           nynf, nync, nyn_on_file,                                            &
     1604           nysf, nysc, nys_on_file,                                            &
     1605           tmp_2d, tmp_3d, found                                               &
     1606        ) ! ToDo: change interface to pass variable
     1607
    15061608    IF ( .NOT. found )  CALL bio_rrd_local(                                    &
    15071609                               found                                           &
     
    15251627                               tmp_3d, found                                   &
    15261628                            ) ! ToDo: change interface to pass variable
    1527                            
     1629
    15281630!     IF ( .NOT. found )  CALL doq_rrd_local(                                    &
    15291631!                                map_index,                                      &
     
    16001702!-- Surface data do not need overlap data, so do not pass these information.
    16011703    IF ( .NOT. found )  CALL surface_data_output_rrd_local( found )
    1602                            
     1704
    16031705    IF ( .NOT. found )  CALL user_rrd_local(                                   &
    16041706                               map_index,                                      &
     
    16261728    IF ( debug_output )  CALL debug_message( 'module-specific write local restart data', 'start' )
    16271729
     1730    CALL dynamics_wrd_local
     1731
    16281732    IF ( biometeorology )       CALL bio_wrd_local
    16291733    IF ( bulk_cloud_model )     CALL bcm_wrd_local
     
    16311735    CALL doq_wrd_local
    16321736    IF ( gust_module_enabled )  CALL gust_wrd_local
    1633     IF ( particle_advection )   CALL lpm_wrd_local   
     1737    IF ( particle_advection )   CALL lpm_wrd_local
    16341738    IF ( land_surface )         CALL lsm_wrd_local
    16351739    IF ( ocean_mode )           CALL ocean_wrd_local
     
    16381742    IF ( urban_surface )        CALL usm_wrd_local
    16391743    IF ( surface_output )       CALL surface_data_output_wrd_local
     1744
    16401745    IF ( user_module_enabled )  CALL user_wrd_local
    16411746
     
    16561761    IF ( debug_output )  CALL debug_message( 'module-specific last actions', 'start' )
    16571762
     1763    CALL dynamics_last_actions
     1764
    16581765    IF ( virtual_measurement )  CALL vm_last_actions
     1766
    16591767    IF ( user_module_enabled )  CALL user_last_actions
    16601768
Note: See TracChangeset for help on using the changeset viewer.