Ignore:
Timestamp:
May 10, 2020 5:05:07 PM (4 years ago)
Author:
raasch
Message:

salsa: added reading/writing of global restart data + reading/writing restart data with MPI-IO, bugfix for MPI-IO in plant_canopy_model_mod, tutorial user-interface dispersion_eularian_and_lpm_extended updated

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/TUTORIALS/cases/dispersion_eulerian_and_lpm_extended/USER_CODE/user_module.f90

    r4370 r4525  
    11!> @file user_module.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
     
    2424! Former revisions:
    2525! -----------------
    26 ! $Id: user_module.f90 3986 2019-05-20 14:08:14Z Giersch $
     26! $Id: user_module.f90 4517 2020-05-03 14:29:30Z raasch $
     27! Modified user-interface has been adapted to r4521
     28!
     29! 4517 2020-05-03 14:29:30Z raasch
     30! added restart with MPI-IO for reading local arrays
     31!
     32! 4504 2020-04-20 12:11:24Z raasch
     33! hint for setting rmask arrays added
     34!
     35! 4497 2020-04-15 10:20:51Z raasch
     36! file re-formatted to follow the PALM coding standard
     37!
     38! 4495 2020-04-13 20:11:20Z raasch
     39! restart data handling with MPI-IO added
     40!
     41! 4360 2020-01-07 11:25:50Z suehring
     42! Introduction of wall_flags_total_0, which currently sets bits based on static topography
     43! information used in wall_flags_static_0
     44!
     45! 4329 2019-12-10 15:46:36Z motisi
     46! Renamed wall_flags_0 to wall_flags_static_0
     47!
     48! 4287 2019-11-01 14:50:20Z raasch
     49! reading of namelist file and actions in case of namelist errors revised so that statement labels
     50! and goto statements are not required any more; this revision also removes a previous bug which
     51! appeared when the namelist has been commented out in the namelist file
     52!
     53! 4182 2019-08-22 15:20:23Z scharf
     54! Corrected "Former revisions" section
     55!
     56! 3986 2019-05-20 14:08:14Z Giersch
    2757! Redundant integration of control parameters in user_rrd_global removed
    28 ! 
     58!
    2959! 3911 2019-04-17 12:26:19Z knoop
    3060! Bugfix: added before_prognostic_equations case in user_actions
    31 ! 
     61!
    3262! 3768 2019-02-27 14:35:58Z raasch
    3363! variables commented + statements added to avoid compiler warnings about unused variables
     
    3565! 3767 2019-02-27 08:18:02Z raasch
    3666! unused variable for file index removed from rrd-subroutines parameter list
    37 ! 
     67!
    3868! 3747 2019-02-16 15:15:23Z gronemeier
    3969! Add routine user_init_arrays
    40 ! 
     70!
    4171! 3703 2019-01-29 16:43:53Z knoop
    4272! An example for a user defined global variable has been added (Giersch)
    43 !
    44 ! 2718 2018-01-02 08:49:38Z suehring
    45 ! Corrected "Former revisions" section
    46 !
    47 ! 2696 2017-12-14 17:12:51Z kanani
    48 ! Change in file header (GPL part)
    49 !
    50 ! 2101 2017-01-05 16:42:31Z suehring
    51 !
    52 ! 2000 2016-08-20 18:09:15Z knoop
    53 ! Forced header and separation lines into 80 columns
    54 !
    55 ! 1873 2016-04-18 14:50:06Z maronga
    56 ! Module renamed (removed _mod)
    57 !
    58 !
    59 ! 1850 2016-04-08 13:29:27Z maronga
    60 ! Module renamed
    61 !
    62 !
    63 ! 1682 2015-10-07 23:56:08Z knoop
    64 ! Code annotations made doxygen readable
    65 !
    66 ! 1320 2014-03-20 08:40:49Z raasch
    67 ! kind-parameters added to all INTEGER and REAL declaration statements,
    68 ! kinds are defined in new module kinds,
    69 ! old module precision_kind is removed,
    70 ! revision history before 2012 removed,
    71 ! comment fields (!:) to be used for variable explanations added to
    72 ! all variable declaration statements
    73 !
    74 ! 1036 2012-10-22 13:43:42Z raasch
    75 ! code put under GPL (PALM 3.9)
    7673!
    7774! Revision 1.1  1998/03/24 15:29:04  raasch
     
    8178! Description:
    8279! ------------
    83 !> Declaration of user-defined variables. This module may only be used
    84 !> in the user-defined routines (contained in user_interface.f90).
    85 !------------------------------------------------------------------------------!
     80!> Declaration of user-defined variables. This module may only be used in the user-defined routines
     81!> (contained in user_interface.f90).
     82!--------------------------------------------------------------------------------------------------!
    8683 MODULE user
    8784
    88 
    8985    USE arrays_3d
    9086
     
    105101    IMPLICIT NONE
    106102
    107     INTEGER(iwp) ::  dots_num_palm   !<
    108     INTEGER(iwp) ::  dots_num_user = 0  !< 
    109     INTEGER(iwp) ::  user_idummy     !<
    110    
    111     LOGICAL ::  user_module_enabled = .FALSE.   !<
    112    
    113     REAL(wp) ::  user_rdummy   !<
     103    INTEGER(iwp) ::  dots_num_palm      !<
     104    INTEGER(iwp) ::  dots_num_user = 0  !<
     105    INTEGER(iwp) ::  user_idummy        !<
     106
     107    LOGICAL ::  user_module_enabled = .FALSE.  !<
     108
     109    REAL(wp) ::  user_rdummy  !<
    114110
    115111!
    116112!-- Sample for user-defined output
    117 !    REAL(wp) :: global_parameter !< user defined global parameter
    118 !
    119 !    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2       !< user defined array
    120 !    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2_av    !< user defined array
    121 !    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ustvst   !< user defined array
    122 
     113!    REAL(wp) :: global_parameter  !< user defined global parameter
     114!
     115!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2      !< user defined array
     116!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2_av   !< user defined array
     117!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ustvst  !< user defined array
     118
     119!
    123120!-- User-defined parameters
    124121    INTEGER(iwp), DIMENSION(1:3) ::  s_ts_pos_x_ind = 0
     
    130127    REAL(wp), DIMENSION(1:3) ::  s_ts_pos_x = 0.0
    131128    REAL(wp), DIMENSION(1:3) ::  s_ts_pos_y = 0.0
    132 
    133129    SAVE
    134130
     
    137133!
    138134!- Public functions
    139     PUBLIC &
    140        user_parin, &
    141        user_check_parameters, &
    142        user_check_data_output_ts, &
    143        user_check_data_output_pr, &
    144        user_check_data_output, &
    145        user_define_netcdf_grid, &
    146        user_init, &
    147        user_init_arrays, &
    148        user_header, &
    149        user_actions, &
    150        user_3d_data_averaging, &
    151        user_data_output_2d, &
    152        user_data_output_3d, &
    153        user_statistics, &
    154        user_rrd_global, &
    155        user_rrd_local, &
    156        user_wrd_global, &
    157        user_wrd_local, &
    158        user_last_actions
     135    PUBLIC                                                                                         &
     136       user_actions,                                                                               &
     137       user_check_data_output,                                                                     &
     138       user_check_data_output_pr,                                                                  &
     139       user_check_data_output_ts,                                                                  &
     140       user_check_parameters,                                                                      &
     141       user_data_output_2d,                                                                        &
     142       user_data_output_3d,                                                                        &
     143       user_define_netcdf_grid,                                                                    &
     144       user_header,                                                                                &
     145       user_init,                                                                                  &
     146       user_init_arrays,                                                                           &
     147       user_last_actions,                                                                          &
     148       user_parin,                                                                                 &
     149       user_rrd_global,                                                                            &
     150       user_rrd_local,                                                                             &
     151       user_statistics,                                                                            &
     152       user_3d_data_averaging,                                                                     &
     153       user_wrd_global,                                                                            &
     154       user_wrd_local
     155
    159156
    160157!
    161158!- Public parameters, constants and initial values
    162    PUBLIC &
     159   PUBLIC                                                                                          &
    163160      user_module_enabled
    164161
     
    221218
    222219    INTERFACE user_rrd_global
    223        MODULE PROCEDURE user_rrd_global
     220       MODULE PROCEDURE user_rrd_global_ftn
     221       MODULE PROCEDURE user_rrd_global_mpi
    224222    END INTERFACE user_rrd_global
    225223
    226224    INTERFACE user_rrd_local
    227        MODULE PROCEDURE user_rrd_local
     225       MODULE PROCEDURE user_rrd_local_ftn
     226       MODULE PROCEDURE user_rrd_local_mpi
    228227    END INTERFACE user_rrd_local
    229228
     
    244243
    245244
    246 !------------------------------------------------------------------------------!
     245!--------------------------------------------------------------------------------------------------!
    247246! Description:
    248247! ------------
    249248!> Parin for &user_parameters for user module
    250 !------------------------------------------------------------------------------!
     249!--------------------------------------------------------------------------------------------------!
    251250 SUBROUTINE user_parin
    252251
    253 
    254     CHARACTER (LEN=80) ::  line   !<
    255 
    256     INTEGER(iwp) ::  i                 !<
    257     INTEGER(iwp) ::  j                 !<
    258 
    259 
    260     NAMELIST /user_parameters/  &
    261        user_module_enabled, &
    262        data_output_pr_user, &
    263        data_output_user, &
    264        region, &
    265        data_output_masks_user, &
    266        emission_stripe_orig_y, emission_stripe_width_y,       &
    267        s_ts_pos_x, s_ts_pos_y
     252    CHARACTER (LEN=80) ::  line  !< string containing the last line read from namelist file
     253
     254    INTEGER(iwp) ::  i          !<
     255    INTEGER(iwp) ::  io_status  !< status after reading the namelist file
     256    INTEGER(iwp) ::  j          !<
     257
     258
     259    NAMELIST /user_parameters/                                                                     &
     260       data_output_masks_user,                                                                     &
     261       data_output_pr_user,                                                                        &
     262       data_output_user,                                                                           &
     263       region,                                                                                     &
     264       emission_stripe_orig_y,                                                                     &
     265       emission_stripe_width_y,                                                                    &
     266       s_ts_pos_x,                                                                                 &
     267       s_ts_pos_y
     268
    268269
    269270!
     
    274275
    275276!
    276 !-- Set revision number of this default interface version. It will be checked within
    277 !-- the main program (palm). Please change the revision number in case that the
    278 !-- current revision does not match with previous revisions (e.g. if routines
    279 !-- have been added/deleted or if parameter lists in subroutines have been changed).
    280     user_interface_current_revision = 'r3703'
    281 
    282 !
    283 !-- Position the namelist-file at the beginning (it was already opened in
    284 !-- parin), search for user-defined namelist-group ("userpar", but any other
    285 !-- name can be choosed) and position the file at this line.
     277!-- Set revision number of this default interface version. It will be checked within the main
     278!-- program (palm). Please change the revision number in case that the current revision does not
     279!-- match with previous revisions (e.g. if routines have been added/deleted or if parameter lists
     280!-- in subroutines have been changed).
     281    user_interface_current_revision = 'r4495'
     282
     283!
     284!-- Position the namelist-file at the beginning (it has already been opened in parin), and try to
     285!-- read (find) a namelist named "user_parameters".
    286286    REWIND ( 11 )
    287 
    288     line = ' '
    289     DO WHILE ( INDEX( line, '&user_parameters' ) == 0 )
    290        READ ( 11, '(A)', END=12 )  line
    291     ENDDO
    292     BACKSPACE ( 11 )
    293 
    294 !-- Set default module switch to true
    295     user_module_enabled = .TRUE.
    296 
    297 !-- Read user-defined namelist
    298     READ ( 11, user_parameters, ERR = 10 )
    299 
    300     GOTO 12
    301 
    302 10  BACKSPACE( 11 )
    303     READ( 11 , '(A)') line
    304     CALL parin_fail_message( 'user_parameters', line )
    305 
    306 12  CONTINUE
    307 
    308 !
    309 !-- Determine the number of user-defined profiles and append them to the
    310 !-- standard data output (data_output_pr)
     287    READ( 11, user_parameters, IOSTAT=io_status )
     288
     289!
     290!-- Actions depending on the READ status
     291    IF ( io_status == 0 )  THEN
     292!
     293!--    User namelist found and correctly read. Set default module switch to true. This activates
     294!--    calls of the user-interface subroutines.
     295       user_module_enabled = .TRUE.
     296
     297    ELSEIF ( io_status > 0 )  THEN
     298!
     299!--    User namelist was found, but contained errors. Print an error message containing the line
     300!--    that caused the problem
     301       BACKSPACE( 11 )
     302       READ( 11 , '(A)') line
     303       CALL parin_fail_message( 'user_parameters', line )
     304
     305    ENDIF
     306
     307!
     308!-- Determine the number of user-defined profiles and append them to the standard data output
     309!-- (data_output_pr)
    311310    IF ( user_module_enabled )  THEN
    312311       IF ( data_output_pr_user(1) /= ' ' )  THEN
     
    329328
    330329
    331 !------------------------------------------------------------------------------!
     330!--------------------------------------------------------------------------------------------------!
    332331! Description:
    333332! ------------
    334333!> Check &userpar control parameters and deduce further quantities.
    335 !------------------------------------------------------------------------------!
     334!--------------------------------------------------------------------------------------------------!
    336335 SUBROUTINE user_check_parameters
    337336
    338 
    339 !-- Here the user may add code to check the validity of further &userpar
    340 !-- control parameters or deduce further quantities.
     337!
     338!-- Here the user may add code to check the validity of further &userpar control parameters or
     339!-- deduce further quantities.
    341340
    342341
     
    344343
    345344
    346 !------------------------------------------------------------------------------!
     345!--------------------------------------------------------------------------------------------------!
    347346! Description:
    348347! ------------
    349348!> Set module-specific timeseries units and labels
    350 !------------------------------------------------------------------------------!
     349!--------------------------------------------------------------------------------------------------!
    351350 SUBROUTINE user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
    352351
     352    INTEGER(iwp),      INTENT(IN)     ::  dots_max  !<
     353    INTEGER(iwp),      INTENT(INOUT)  ::  dots_num  !<
     354
     355    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_label  !<
     356    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_unit   !<
    353357
    354358    INTEGER(iwp)  ::  i
    355  
    356     INTEGER(iwp),      INTENT(IN)     ::  dots_max
    357     INTEGER(iwp),      INTENT(INOUT)  ::  dots_num
    358    
    359359    CHARACTER(LEN=7)   ::  i_char = ''
    360     CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_label
    361     CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_unit
    362 
    363360
    364361!
     
    367364
    368365!
    369 !-- Sample for user-defined time series
    370 !-- For each time series quantity you have to give a label and a unit,
    371 !-- which will be used for the NetCDF file. They must not contain more than
    372 !-- seven characters. The value of dots_num has to be increased by the
    373 !-- number of new time series quantities. Its old value has to be store in
    374 !-- dots_num_palm. See routine user_statistics on how to output calculate
    375 !-- and output these quantities.
     366!-- Sample for user-defined time series:
     367!-- For each time series quantity you have to give a label and a unit, which will be used for the
     368!-- NetCDF file. They must not contain more than seven characters. The value of dots_num has to be
     369!-- increased by the number of new time series quantities. Its old value has to be stored in
     370!-- dots_num_palm. See routine user_statistics on how to calculate and output these quantities.
    376371
    377372!    dots_num_palm = dots_num
     
    387382!    dots_unit(dots_num)  = 'm/s'
    388383
     384!
    389385!-- Additional timeseries output
    390386    size_of_pos_array = SIZE(s_ts_pos_x)
     
    399395    dots_num = dots_num + size_of_pos_array
    400396
    401 
    402397 END SUBROUTINE user_check_data_output_ts
    403398
    404399
    405 !------------------------------------------------------------------------------!
    406 ! Description:
    407 ! ------------
    408 !> Set the unit of user defined profile output quantities. For those variables
    409 !> not recognized by the user, the parameter unit is set to "illegal", which
    410 !> tells the calling routine that the output variable is not defined and leads
    411 !> to a program abort.
    412 !------------------------------------------------------------------------------!
     400!--------------------------------------------------------------------------------------------------!
     401! Description:
     402! ------------
     403!> Set the unit of user defined profile output quantities. For those variables not recognized by the
     404!> user, the parameter unit is set to "illegal", which tells the calling routine that the
     405!> output variable is not defined and leads to a program abort.
     406!--------------------------------------------------------------------------------------------------!
    413407 SUBROUTINE user_check_data_output_pr( variable, var_count, unit, dopr_unit )
    414408
     
    417411
    418412
    419     CHARACTER (LEN=*) ::  unit     !<
    420     CHARACTER (LEN=*) ::  variable !<
     413    CHARACTER (LEN=*) ::  unit      !<
     414    CHARACTER (LEN=*) ::  variable  !<
    421415    CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    422416
    423 !    INTEGER(iwp) ::  user_pr_index !<
    424     INTEGER(iwp) ::  var_count     !<
     417!    INTEGER(iwp) ::  user_pr_index  !<
     418    INTEGER(iwp) ::  var_count      !<
    425419
    426420!
     
    432426!
    433427!--    Uncomment and extend the following lines, if necessary.
    434 !--    Add additional CASE statements depending on the number of quantities
    435 !--    for which profiles are to be calculated. The respective calculations
    436 !--    to be performed have to be added in routine user_statistics.
    437 !--    The quantities are (internally) identified by a user-profile-number
    438 !--    (see variable "user_pr_index" below). The first user-profile must be assigned
    439 !--    the number "pr_palm+1", the second one "pr_palm+2", etc. The respective
    440 !--    user-profile-numbers have also to be used in routine user_statistics!
    441 !       CASE ( 'u*v*' )                      ! quantity string as given in
    442 !                                            ! data_output_pr_user
     428!--    Add additional CASE statements depending on the number of quantities for which profiles are
     429!--    to be calculated. The respective calculations to be performed have to be added in routine
     430!--    user_statistics. The quantities are (internally) identified by a user-profile-number
     431!--    (see variable "user_pr_index" below). The first user-profile must be assigned the number
     432!--    "pr_palm+1", the second one "pr_palm+2", etc. The respective user-profile-numbers have also
     433!--    to be used in routine user_statistics!
     434!       CASE ( 'u*v*' )                      ! quantity string as given in data_output_pr_user
    443435!          user_pr_index = pr_palm + 1
    444436!          dopr_index(var_count)  = user_pr_index    ! quantities' user-profile-number
    445437!          dopr_unit = 'm2/s2'  ! quantity unit
    446438!          unit = dopr_unit
    447 !          hom(:,2,user_pr_index,:)       = SPREAD( zu, 2, statistic_regions+1 )
    448 !                                            ! grid on which the quantity is
    449 !                                            ! defined (use zu or zw)
     439!          hom(:,2,user_pr_index,:) = SPREAD( zu, 2, statistic_regions+1 )
     440!                                            ! grid on which the quantity is defined (use zu or zw)
     441!
    450442
    451443       CASE DEFAULT
     
    458450
    459451
    460 !------------------------------------------------------------------------------!
    461 ! Description:
    462 ! ------------
    463 !> Set the unit of user defined output quantities. For those variables
    464 !> not recognized by the user, the parameter unit is set to "illegal", which
    465 !> tells the calling routine that the output variable is not defined and leads
    466 !> to a program abort.
    467 !------------------------------------------------------------------------------!
     452!--------------------------------------------------------------------------------------------------!
     453! Description:
     454! ------------
     455!> Set the unit of user defined output quantities. For those variables not recognized by the user,
     456!> the parameter unit is set to "illegal", which tells the calling routine that the output variable
     457!> is not defined and leads to a program abort.
     458!--------------------------------------------------------------------------------------------------!
    468459 SUBROUTINE user_check_data_output( variable, unit )
    469460
    470461
    471     CHARACTER (LEN=*) ::  unit     !<
    472     CHARACTER (LEN=*) ::  variable !<
     462    CHARACTER (LEN=*) ::  unit      !<
     463    CHARACTER (LEN=*) ::  variable  !<
    473464
    474465
     
    492483
    493484
    494 !------------------------------------------------------------------------------!
     485!--------------------------------------------------------------------------------------------------!
    495486! Description:
    496487! ------------
    497488!> Initialize user-defined arrays
    498 !------------------------------------------------------------------------------!
     489!--------------------------------------------------------------------------------------------------!
    499490 SUBROUTINE user_init_arrays
    500491
     
    512503!
    513504!-- Example for defining a statistic region:
     505!-- ATTENTION: rmask = 0 is required at the ghost boundaries to guarantee correct statistic
     506!--            evaluations (otherwise ghost points would be counted twice). This setting has
     507!--            already been cared for in routine init_3d_model. Please don't set the ghost points
     508!--            /= 0. i.e. run the following loop only over nxl,nxr and nys,nyn.
    514509!     IF ( statistic_regions >= 1 )  THEN
    515510!        region = 1
    516 ! 
     511!
    517512!        rmask(:,:,region) = 0.0_wp
    518513!        DO  i = nxl, nxr
     
    525520!           ENDIF
    526521!        ENDDO
    527 ! 
     522!
    528523!     ENDIF
    529524
     
    531526
    532527
    533 !------------------------------------------------------------------------------!
     528!--------------------------------------------------------------------------------------------------!
    534529! Description:
    535530! ------------
    536531!> Execution of user-defined initializing actions
    537 !------------------------------------------------------------------------------!
     532!--------------------------------------------------------------------------------------------------!
    538533 SUBROUTINE user_init
    539534
    540  
    541535    USE grid_variables
    542536
    543 !    CHARACTER (LEN=20) :: field_char   !<
    544 
    545     INTEGER(iwp), DIMENSION(1:2) ::  eso_ind      !< index values of emission_stripe_orig
     537!    CHARACTER(LEN=20) :: field_char  !<
     538
     539INTEGER(iwp), DIMENSION(1:2) ::  eso_ind      !< index values of emission_stripe_orig
    546540    INTEGER(iwp)                 ::  esw_ind      !< index value of emission_stripe_width
    547541    INTEGER(iwp)                 ::  i, j, m      !< running index
     
    578572       ENDDO
    579573    ENDDO   
    580    
    581574
    582575 END SUBROUTINE user_init
    583576
    584577
    585 !------------------------------------------------------------------------------!
    586 ! Description:
    587 ! ------------
    588 !> Set the grids on which user-defined output quantities are defined.
    589 !> Allowed values for grid_x are "x" and "xu", for grid_y "y" and "yv", and
    590 !> for grid_z "zu" and "zw".
    591 !------------------------------------------------------------------------------!
     578!--------------------------------------------------------------------------------------------------!
     579! Description:
     580! ------------
     581!> Set the grids on which user-defined output quantities are defined. Allowed values for grid_x are
     582!> "x" and "xu", for grid_y "y" and "yv", and for grid_z "zu" and "zw".
     583!--------------------------------------------------------------------------------------------------!
    592584 SUBROUTINE user_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
    593585
     
    631623
    632624
    633 !------------------------------------------------------------------------------!
     625!--------------------------------------------------------------------------------------------------!
    634626! Description:
    635627! ------------
    636628!> Print a header with user-defined information.
    637 !------------------------------------------------------------------------------!
     629!--------------------------------------------------------------------------------------------------!
    638630 SUBROUTINE user_header( io )
    639631
    640632
    641     INTEGER(iwp) ::  i    !<
    642     INTEGER(iwp) ::  io   !<
    643 
    644 !
    645 !-- If no user-defined variables are read from the namelist-file, no
    646 !-- information will be printed.
     633    INTEGER(iwp) ::  i   !<
     634    INTEGER(iwp) ::  io  !<
     635
     636!
     637!-- If no user-defined variables are read from the namelist-file, no information will be printed.
    647638    IF ( .NOT. user_module_enabled )  THEN
    648639       WRITE ( io, 100 )
     
    663654    WRITE ( io, 122 )
    664655    WRITE ( io, 123 ) s_ts_pos_x, s_ts_pos_y
    665    
    666656   
    667657    IF ( statistic_regions /= 0 )  THEN
     
    675665!-- Format-descriptors
    676666100 FORMAT (//' *** no user-defined variables found'/)
    677 110 FORMAT (//1X,78('#')                                                       &
    678             //' User-defined variables and actions:'/                          &
    679               ' -----------------------------------'//)
     667110 FORMAT (//1X,78('#') // ' User-defined variables and actions:' /                               &
     668            ' -----------------------------------'//)
    680669120 FORMAT (' Parameters for traffic emission:' /)
    681670121 FORMAT ('stripe origin(s) in y-direction (in m): ',F5.1,', ',F5.1,' , stripe width in y-direction (in m): ',F5.1)
     
    689678
    690679
    691 !------------------------------------------------------------------------------!
     680!--------------------------------------------------------------------------------------------------!
    692681! Description:
    693682! ------------
    694683!> Call for all grid points
    695 !------------------------------------------------------------------------------!
     684!--------------------------------------------------------------------------------------------------!
    696685 SUBROUTINE user_actions( location )
    697686
    698687
    699     CHARACTER (LEN=*) ::  location !<
    700 
    701 !    INTEGER(iwp) ::  i !<
    702 !    INTEGER(iwp) ::  j !<
    703 !    INTEGER(iwp) ::  k !<
     688    CHARACTER(LEN=*) ::  location  !<
     689
     690!    INTEGER(iwp) ::  i  !<
     691!    INTEGER(iwp) ::  j  !<
     692!    INTEGER(iwp) ::  k  !<
    704693
    705694    CALL cpu_log( log_point(24), 'user_actions', 'start' )
    706695
    707696!
    708 !-- Here the user-defined actions follow
    709 !-- No calls for single grid points are allowed at locations before and
    710 !-- after the timestep, since these calls are not within an i,j-loop
     697!-- Here the user-defined actions follow. No calls for single grid points are allowed at locations
     698!-- before and after the timestep, since these calls are not within an i,j-loop
    711699    SELECT CASE ( location )
    712700
     
    721709       CASE ( 'after_integration' )
    722710!
    723 !--       Enter actions to be done after every time integration (before
    724 !--       data output)
     711!--       Enter actions to be done after every time integration (before data output)
    725712!--       Sample for user-defined output:
    726713!          DO  i = nxlg, nxrg
     
    735722!                DO  k = nzb, nzt+1
    736723!                   ustvst(k,j,i) =  &
    737 !                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) * &
     724!                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) *                      &
    738725!                      ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) )
    739726!                ENDDO
     
    783770
    784771
    785 !------------------------------------------------------------------------------!
     772!--------------------------------------------------------------------------------------------------!
    786773! Description:
    787774! ------------
    788775!> Call for grid point i,j
    789 !------------------------------------------------------------------------------!
     776!--------------------------------------------------------------------------------------------------!
    790777 SUBROUTINE user_actions_ij( i, j, location )
    791778
    792779
    793     CHARACTER (LEN=*) ::  location
    794 
    795     INTEGER(iwp) ::  i
    796     INTEGER(iwp) ::  j
     780    CHARACTER(LEN=*) ::  location  !<
     781
     782    INTEGER(iwp) ::  i  !<
     783    INTEGER(iwp) ::  j  !<
    797784
    798785!
     
    839826
    840827
    841 !------------------------------------------------------------------------------!
    842 ! Description:
    843 ! ------------
    844 !> Sum up and time-average user-defined output quantities as well as allocate
    845 !> the array necessary for storing the average.
    846 !------------------------------------------------------------------------------!
     828!--------------------------------------------------------------------------------------------------!
     829! Description:
     830! ------------
     831!> Sum up and time-average user-defined output quantities as well as allocate the array necessary
     832!> for storing the average.
     833!--------------------------------------------------------------------------------------------------!
    847834 SUBROUTINE user_3d_data_averaging( mode, variable )
    848835
    849836
    850     CHARACTER (LEN=*) ::  mode    !<
    851     CHARACTER (LEN=*) :: variable !<
    852 
    853 !    INTEGER(iwp) ::  i !<
    854 !    INTEGER(iwp) ::  j !<
    855 !    INTEGER(iwp) ::  k !<
     837    CHARACTER(LEN=*) ::  mode      !<
     838    CHARACTER(LEN=*) ::  variable  !<
     839
     840!    INTEGER(iwp) ::  i  !<
     841!    INTEGER(iwp) ::  j  !<
     842!    INTEGER(iwp) ::  k  !<
    856843
    857844    IF ( mode == 'allocate' )  THEN
     
    861848!
    862849!--       Uncomment and extend the following lines, if necessary.
    863 !--       The arrays for storing the user defined quantities (here u2_av) have
    864 !--       to be declared and defined by the user!
     850!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
     851!--       defined by the user!
    865852!--       Sample for user-defined output:
    866853!          CASE ( 'u2' )
     
    881868!
    882869!--       Uncomment and extend the following lines, if necessary.
    883 !--       The arrays for storing the user defined quantities (here u2 and
    884 !--       u2_av) have to be declared and defined by the user!
     870!--       The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     871!--       and defined by the user!
    885872!--       Sample for user-defined output:
    886873!          CASE ( 'u2' )
    887 !             IF ( ALLOCATED( u2_av ) ) THEN
     874!             IF ( ALLOCATED( u2_av ) )  THEN
    888875!                DO  i = nxlg, nxrg
    889876!                   DO  j = nysg, nyng
     
    906893!
    907894!--       Uncomment and extend the following lines, if necessary.
    908 !--       The arrays for storing the user defined quantities (here u2_av) have
    909 !--       to be declared and defined by the user!
     895!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
     896!--       defined by the user!
    910897!--       Sample for user-defined output:
    911898!          CASE ( 'u2' )
    912 !             IF ( ALLOCATED( u2_av ) ) THEN
     899!             IF ( ALLOCATED( u2_av ) )  THEN
    913900!                DO  i = nxlg, nxrg
    914901!                   DO  j = nysg, nyng
     
    928915
    929916
    930 !------------------------------------------------------------------------------!
    931 ! Description:
    932 ! ------------
    933 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    934 !> temporary array with indices (i,j,k) and sets the grid on which it is defined.
    935 !> Allowed values for grid are "zu" and "zw".
    936 !------------------------------------------------------------------------------!
     917!--------------------------------------------------------------------------------------------------!
     918! Description:
     919! ------------
     920!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
     921!> (i,j,k) and sets the grid on which it is defined. Allowed values for grid are "zu" and "zw".
     922!--------------------------------------------------------------------------------------------------!
    937923 SUBROUTINE user_data_output_2d( av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do )
    938924
    939925
    940     CHARACTER (LEN=*) ::  grid     !<
    941     CHARACTER (LEN=*) ::  variable !<
    942 
    943     INTEGER(iwp) ::  av     !< flag to control data output of instantaneous or time-averaged data
    944 !    INTEGER(iwp) ::  i      !< grid index along x-direction
    945 !    INTEGER(iwp) ::  j      !< grid index along y-direction
    946 !    INTEGER(iwp) ::  k      !< grid index along z-direction
    947 !    INTEGER(iwp) ::  m      !< running index surface elements
    948     INTEGER(iwp) ::  nzb_do !< lower limit of the domain (usually nzb)
    949     INTEGER(iwp) ::  nzt_do !< upper limit of the domain (usually nzt+1)
    950 
    951     LOGICAL      ::  found !<
    952     LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
     926    CHARACTER(LEN=*) ::  grid      !<
     927    CHARACTER(LEN=*) ::  variable  !<
     928
     929    INTEGER(iwp) ::  av      !< flag to control data output of instantaneous or time-averaged data
     930!    INTEGER(iwp) ::  i       !< grid index along x-direction
     931!    INTEGER(iwp) ::  j       !< grid index along y-direction
     932!    INTEGER(iwp) ::  k       !< grid index along z-direction
     933!    INTEGER(iwp) ::  m       !< running index surface elements
     934    INTEGER(iwp) ::  nzb_do  !< lower limit of the domain (usually nzb)
     935    INTEGER(iwp) ::  nzt_do  !< upper limit of the domain (usually nzt+1)
     936
     937    LOGICAL      ::  found  !<
     938    LOGICAL      ::  two_d  !< flag parameter that indicates 2D variables (horizontal cross sections)
    953939
    954940!    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    955941
    956     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     942    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
    957943
    958944!
     
    967953!
    968954!--    Uncomment and extend the following lines, if necessary.
    969 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    970 !--    have to be declared and defined by the user!
     955!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     956!--    and defined by the user!
    971957!--    Sample for user-defined output:
    972958!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
     
    980966!             ENDDO
    981967!          ELSE
    982 !             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     968!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    983969!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    984970!                u2_av = REAL( fill_value, KIND = wp )
     
    995981!          grid = 'zu'
    996982!
    997 !--    In case two-dimensional surface variables are output, the user
    998 !--    has to access related surface-type. Uncomment and extend following lines
    999 !--    appropriately (example output of vertical surface momentum flux of u-
    1000 !--    component). Please note, surface elements can be distributed over
    1001 !--    several data type, depending on their respective surface properties.
     983!--    In case two-dimensional surface variables are output, the user has to access related
     984!--    surface-type. Uncomment and extend following lines appropriately (example output of vertical
     985!--    surface momentum flux of u-component). Please note, surface elements can be distributed over
     986!--    several data types, depending on their respective surface properties.
    1002987!       CASE ( 'usws_xy' )
    1003988!          IF ( av == 0 )  THEN
     
    10261011!
    10271012!          grid = 'zu'
    1028 !--       
     1013!--
    10291014
    10301015
     
    10391024
    10401025
    1041 !------------------------------------------------------------------------------!
    1042 ! Description:
    1043 ! ------------
    1044 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    1045 !> temporary array with indices (i,j,k).
    1046 !------------------------------------------------------------------------------!
     1026!--------------------------------------------------------------------------------------------------!
     1027! Description:
     1028! ------------
     1029!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
     1030!> (i,j,k).
     1031!--------------------------------------------------------------------------------------------------!
    10471032 SUBROUTINE user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
    10481033
    10491034
    1050     CHARACTER (LEN=*) ::  variable !<
    1051 
    1052     INTEGER(iwp) ::  av    !<
    1053 !    INTEGER(iwp) ::  i     !<
    1054 !    INTEGER(iwp) ::  j     !<
    1055 !    INTEGER(iwp) ::  k     !<
     1035    CHARACTER(LEN=*) ::  variable  !<
     1036
     1037    INTEGER(iwp) ::  av     !<
     1038!    INTEGER(iwp) ::  i      !<
     1039!    INTEGER(iwp) ::  j      !<
     1040!    INTEGER(iwp) ::  k      !<
    10561041    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
    10571042    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    10581043
    1059     LOGICAL      ::  found !<
    1060 
    1061 !    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    1062 
    1063     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     1044    LOGICAL      ::  found  !<
     1045
     1046!    REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
     1047
     1048    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
    10641049
    10651050!
     
    10741059!
    10751060!--    Uncomment and extend the following lines, if necessary.
    1076 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    1077 !--    have to be declared and defined by the user!
     1061!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     1062!--    and defined by the user!
    10781063!--    Sample for user-defined output:
    10791064!       CASE ( 'u2' )
     
    10871072!             ENDDO
    10881073!          ELSE
    1089 !             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     1074!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    10901075!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    10911076!                u2_av = REAL( fill_value, KIND = wp )
     
    11101095
    11111096
    1112 !------------------------------------------------------------------------------!
    1113 ! Description:
    1114 ! ------------
    1115 !> Calculation of user-defined statistics, i.e. horizontally averaged profiles
    1116 !> and time series.
    1117 !> This routine is called for every statistic region sr defined by the user,
    1118 !> but at least for the region "total domain" (sr=0).
    1119 !> See section 3.5.4 on how to define, calculate, and output user defined
    1120 !> quantities.
    1121 !------------------------------------------------------------------------------!
     1097!--------------------------------------------------------------------------------------------------!
     1098! Description:
     1099! ------------
     1100!> Calculation of user-defined statistics, i.e. horizontally averaged profiles and time series.
     1101!> This routine is called for every statistic region sr defined by the user, but at least for the
     1102!> region "total domain" (sr=0). See section 3.5.4 on how to define, calculate, and output user
     1103!> defined quantities.
     1104!--------------------------------------------------------------------------------------------------!
    11221105 SUBROUTINE user_statistics( mode, sr, tn )
    1123 
    11241106
    11251107    USE netcdf_interface,                                                      &
    11261108       ONLY:  dots_max
    1127        
    1128     CHARACTER (LEN=*) ::  mode   !<
    1129     INTEGER(iwp) ::  i    !<
    1130 !    INTEGER(iwp) ::  j    !<
    1131 !    INTEGER(iwp) ::  k    !<
    1132     INTEGER(iwp) ::  sr   !<
    1133     INTEGER(iwp) ::  tn   !<
    1134 
    1135 !    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l   !<
     1109
     1110    CHARACTER(LEN=*) ::  mode  !<
     1111    INTEGER(iwp) ::  i   !<
     1112!    INTEGER(iwp) ::  j   !<
     1113!    INTEGER(iwp) ::  k   !<
     1114    INTEGER(iwp) ::  sr  !<
     1115    INTEGER(iwp) ::  tn  !<
     1116
     1117!    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l  !<
    11361118    REAL(wp), DIMENSION(dots_num_palm+1:dots_max) ::  ts_value_l   !<
    11371119
     
    11431125
    11441126!
    1145 !--    Sample on how to calculate horizontally averaged profiles of user-
    1146 !--    defined quantities. Each quantity is identified by the index
    1147 !--    "pr_palm+#" where "#" is an integer starting from 1. These
    1148 !--    user-profile-numbers must also be assigned to the respective strings
    1149 !--    given by data_output_pr_user in routine user_check_data_output_pr.
     1127!--    Sample on how to calculate horizontally averaged profiles of user-defined quantities. Each
     1128!--    quantity is identified by the index "pr_palm+#" where "#" is an integer starting from 1.
     1129!--    These user-profile-numbers must also be assigned to the respective strings given by
     1130!--    data_output_pr_user in routine user_check_data_output_pr.
    11501131!       !$OMP DO
    11511132!       DO  i = nxl, nxr
     
    11531134!             DO  k = nzb+1, nzt
    11541135!!
    1155 !!--             Sample on how to calculate the profile of the resolved-scale
    1156 !!--             horizontal momentum flux u*v*
    1157 !                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +             &
    1158 !                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *&
    1159 !                      ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )  &
    1160 !                                     * rmask(j,i,sr)                          &
    1161 !                                     * MERGE( 1.0_wp, 0.0_wp,                 &
    1162 !                                              BTEST( wall_flags_0(k,j,i), 0 ) )
     1136!!--             Sample on how to calculate the profile of the resolved-scale horizontal momentum
     1137!!--             flux u*v*
     1138!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +                                  &
     1139!                                         ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *  &
     1140!                                         ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) ) *  &
     1141!                                         rmask(j,i,sr) * MERGE( 1.0_wp, 0.0_wp,                    &
     1142!                                         BTEST( wall_flags_total_0(k,j,i), 0 ) )
    11631143!!
    1164 !!--             Further profiles can be defined and calculated by increasing
    1165 !!--             the second index of array sums_l (replace ... appropriately)
    1166 !                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...           &
    1167 !                                         * rmask(j,i,sr)
     1144!!--             Further profiles can be defined and calculated by increasing the second index of
     1145!!--             array sums_l (replace ... appropriately)
     1146!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...   * rmask(j,i,sr)
    11681147!             ENDDO
    11691148!          ENDDO
     
    11761155!
    11771156!--    Sample on how to add values for the user-defined time series quantities.
    1178 !--    These have to be defined before in routine user_init. This sample
    1179 !--    creates two time series for the absolut values of the horizontal
    1180 !--    velocities u and v.
     1157!--    These have to be defined before in routine user_init. This sample creates two time series for
     1158!--    the absolut values of the horizontal velocities u and v.
    11811159!       ts_value_l = 0.0_wp
    11821160!       ts_value_l(1) = ABS( u_max )
     
    11841162!
    11851163!--     Collect / send values to PE0, because only PE0 outputs the time series.
    1186 !--     CAUTION: Collection is done by taking the sum over all processors.
    1187 !--              You may have to normalize this sum, depending on the quantity
    1188 !--              that you like to calculate. For serial runs, nothing has to be
    1189 !--              done.
    1190 !--     HINT: If the time series value that you are calculating has the same
    1191 !--           value on all PEs, you can omit the MPI_ALLREDUCE call and
    1192 !--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
     1164!--     CAUTION: Collection is done by taking the sum over all processors. You may have to normalize
     1165!--              this sum, depending on the quantity that you like to calculate. For serial runs,
     1166!--              nothing has to be done.
     1167!--     HINT: If the time series value that you are calculating has the same value on all PEs, you
     1168!--           can omit the MPI_ALLREDUCE call and assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
    11931169!#if defined( __parallel )
    11941170!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1195 !       CALL MPI_ALLREDUCE( ts_value_l(1),                         &
    1196 !                           ts_value(dots_num_palm+1,sr),                        &
    1197 !                           dots_num_user, MPI_REAL, MPI_MAX, comm2d,   &
    1198 !                           ierr )
     1171!       CALL MPI_ALLREDUCE( ts_value_l(1), ts_value(dots_num_palm+1,sr), dots_num_user, MPI_REAL,   &
     1172!                           MPI_MAX, comm2d, ierr )
    11991173!#else
    12001174!       ts_value(dots_num_palm+1:dots_num_palm+dots_num_user,sr) = ts_value_l
    12011175!#endif
    1202 
    12031176
    12041177       ts_value_l = 0.0_wp
     
    12391212
    12401213
    1241 !------------------------------------------------------------------------------!
    1242 ! Description:
    1243 ! ------------
    1244 !> Reading global restart data that has been defined by the user.
    1245 !------------------------------------------------------------------------------!
    1246  SUBROUTINE user_rrd_global( found )
    1247 
    1248 
    1249     LOGICAL, INTENT(OUT)  ::  found
     1214!--------------------------------------------------------------------------------------------------!
     1215! Description:
     1216! ------------
     1217!> Read module-specific global restart data (Fortran binary format).
     1218!--------------------------------------------------------------------------------------------------!
     1219 SUBROUTINE user_rrd_global_ftn( found )
     1220
     1221
     1222    LOGICAL, INTENT(OUT)  ::  found  !<
    12501223
    12511224
     
    12591232
    12601233       CASE DEFAULT
    1261  
     1234
    12621235          found = .FALSE.
    12631236
     
    12651238
    12661239
    1267  END SUBROUTINE user_rrd_global
    1268 
    1269 
    1270 !------------------------------------------------------------------------------!
    1271 ! Description:
    1272 ! ------------
    1273 !> Reading processor specific restart data from file(s) that has been defined
    1274 !> by the user.
    1275 !> Subdomain index limits on file are given by nxl_on_file, etc.
    1276 !> Indices nxlc, etc. indicate the range of gridpoints to be mapped from the
    1277 !> subdomain on file (f) to the subdomain of the current PE (c). They have been
    1278 !> calculated in routine rrd_local.
    1279 !------------------------------------------------------------------------------!
    1280  SUBROUTINE user_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,         &
    1281                             nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
    1282                             nysc, nys_on_file, tmp_3d, found )
     1240 END SUBROUTINE user_rrd_global_ftn
     1241
     1242
     1243!--------------------------------------------------------------------------------------------------!
     1244! Description:
     1245! ------------
     1246!> Read module-specific global restart data (MPI-IO).
     1247!--------------------------------------------------------------------------------------------------!
     1248 SUBROUTINE user_rrd_global_mpi
     1249
     1250!    USE restart_data_mpi_io_mod,                                                                   &
     1251!        ONLY:  rrd_mpi_io
     1252
     1253!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
     1254    CONTINUE
     1255
     1256 END SUBROUTINE user_rrd_global_mpi
     1257
     1258
     1259!--------------------------------------------------------------------------------------------------!
     1260! Description:
     1261! ------------
     1262!> Read module-specific local restart data arrays (Fortran binary format).
     1263!> Subdomain
     1264!> index limits on file are given by nxl_on_file, etc. Indices nxlc, etc. indicate the range of
     1265!> gridpoints to be mapped from the subdomain on file (f) to the subdomain of the current PE (c).
     1266!> They have been calculated in routine rrd_local.
     1267!--------------------------------------------------------------------------------------------------!
     1268 SUBROUTINE user_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,   &
     1269                                nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
    12831270
    12841271
     
    12981285    INTEGER(iwp) ::  nys_on_file     !<
    12991286
    1300     LOGICAL, INTENT(OUT)  ::  found
    1301 
    1302     REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
     1287    LOGICAL, INTENT(OUT)  ::  found  !<
     1288
     1289    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d  !<
    13031290
    13041291!
     
    13161303
    13171304       CASE ( 'u2_av' )
    1318 !          IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     1305!          IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    13191306!               ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    13201307!          ENDIF
    13211308!          IF ( k == 1 )  READ ( 13 )  tmp_3d
    1322 !             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
    1323 !                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     1309!             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                    &
     1310!             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    13241311!
    13251312       CASE DEFAULT
     
    13291316    END SELECT
    13301317
    1331  END SUBROUTINE user_rrd_local
    1332 
    1333 
    1334 !------------------------------------------------------------------------------!
    1335 ! Description:
    1336 ! ------------
    1337 !> Writes global and user-defined restart data into binary file(s) for restart
    1338 !> runs.
    1339 !------------------------------------------------------------------------------!
     1318 END SUBROUTINE user_rrd_local_ftn
     1319
     1320
     1321!--------------------------------------------------------------------------------------------------!
     1322! Description:
     1323! ------------
     1324!> Read module-specific local restart data arrays (MPI-IO).
     1325!--------------------------------------------------------------------------------------------------!
     1326 SUBROUTINE user_rrd_local_mpi
     1327
     1328!    USE restart_data_mpi_io_mod,                                                                   &
     1329!        ONLY:  rd_mpi_io_check_array, rrd_mpi_io
     1330
     1331!    CALL rd_mpi_io_check_array( 'u2_av' , found = array_found )
     1332!    IF ( array_found )  THEN
     1333!       IF ( .NOT. ALLOCATED( u2_av ) )  ALLOCATE( u2_av(nysg:nyng,nxlg:nxrg) )
     1334!       CALL rrd_mpi_io( 'rad_u2_av', rad_u2_av )
     1335!    ENDIF
     1336
     1337    CONTINUE
     1338
     1339 END SUBROUTINE user_rrd_local_mpi
     1340
     1341
     1342!--------------------------------------------------------------------------------------------------!
     1343! Description:
     1344! ------------
     1345!> Writes global and user-defined restart data into binary file(s) for restart runs.
     1346!--------------------------------------------------------------------------------------------------!
    13401347 SUBROUTINE user_wrd_global
    13411348
    1342 !    CALL wrd_write_string( 'global_parameter' )
    1343 !    WRITE ( 14 )  global_parameter
     1349!    USE restart_data_mpi_io_mod,                                                                   &
     1350!        ONLY:  wrd_mpi_io
     1351
     1352    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     1353
     1354!       CALL wrd_write_string( 'global_parameter' )
     1355!       WRITE ( 14 )  global_parameter
     1356
     1357    ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     1358
     1359!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
     1360
     1361    ENDIF
    13441362
    13451363 END SUBROUTINE user_wrd_global
    13461364
    13471365
    1348 !------------------------------------------------------------------------------!
    1349 ! Description:
    1350 ! ------------
    1351 !> Writes processor specific and user-defined restart data into binary file(s)
    1352 !> for restart runs.
    1353 !------------------------------------------------------------------------------!
     1366!--------------------------------------------------------------------------------------------------!
     1367! Description:
     1368! ------------
     1369!> Writes processor specific and user-defined restart data into binary file(s) for restart runs.
     1370!--------------------------------------------------------------------------------------------------!
    13541371 SUBROUTINE user_wrd_local
     1372
     1373!    USE restart_data_mpi_io_mod,                                                                   &
     1374!        ONLY:  wrd_mpi_io
    13551375
    13561376!
    13571377!-- Here the user-defined actions at the end of a job follow.
    13581378!-- Sample for user-defined output:
    1359 !    IF ( ALLOCATED( u2_av ) )  THEN
    1360 !       CALL wrd_write_string( 'u2_av' )
    1361 !       WRITE ( 14 )  u2_av
    1362 !    ENDIF
     1379    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     1380
     1381!       IF ( ALLOCATED( u2_av ) )  THEN
     1382!          CALL wrd_write_string( 'u2_av' )
     1383!          WRITE ( 14 )  u2_av
     1384!       ENDIF
     1385
     1386    ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     1387
     1388!       IF ( ALLOCATED( u2_av ) )  CALL wrd_mpi_io( 'u2_av', u2_av )
     1389
     1390    ENDIF
    13631391
    13641392 END SUBROUTINE user_wrd_local
    13651393
    13661394
    1367 !------------------------------------------------------------------------------!
     1395!--------------------------------------------------------------------------------------------------!
    13681396! Description:
    13691397! ------------
    13701398!> Execution of user-defined actions at the end of a job.
    1371 !------------------------------------------------------------------------------!
     1399!--------------------------------------------------------------------------------------------------!
    13721400 SUBROUTINE user_last_actions
    13731401
Note: See TracChangeset for help on using the changeset viewer.