Ignore:
Timestamp:
Nov 2, 2020 10:31:45 AM (3 years ago)
Author:
Giersch
Message:

Tutorials updated for r4761

File:
1 edited

Legend:

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

    r4397 r4765  
    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 4535 2020-05-15 12:07:23Z raasch $
     27! bugfix for restart data format query
     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
     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
    122118     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_h, v_h_av       !< user defined array
    123119
     
    128124!
    129125!- Public functions
    130     PUBLIC &
    131        user_parin, &
    132        user_check_parameters, &
    133        user_check_data_output_ts, &
    134        user_check_data_output_pr, &
    135        user_check_data_output, &
    136        user_define_netcdf_grid, &
    137        user_init, &
    138        user_init_arrays, &
    139        user_header, &
    140        user_actions, &
    141        user_3d_data_averaging, &
    142        user_data_output_2d, &
    143        user_data_output_3d, &
    144        user_statistics, &
    145        user_rrd_global, &
    146        user_rrd_local, &
    147        user_wrd_global, &
    148        user_wrd_local, &
    149        user_last_actions
     126    PUBLIC                                                                                         &
     127       user_actions,                                                                               &
     128       user_check_data_output,                                                                     &
     129       user_check_data_output_pr,                                                                  &
     130       user_check_data_output_ts,                                                                  &
     131       user_check_parameters,                                                                      &
     132       user_data_output_2d,                                                                        &
     133       user_data_output_3d,                                                                        &
     134       user_define_netcdf_grid,                                                                    &
     135       user_header,                                                                                &
     136       user_init,                                                                                  &
     137       user_init_arrays,                                                                           &
     138       user_last_actions,                                                                          &
     139       user_parin,                                                                                 &
     140       user_rrd_global,                                                                            &
     141       user_rrd_local,                                                                             &
     142       user_statistics,                                                                            &
     143       user_3d_data_averaging,                                                                     &
     144       user_wrd_global,                                                                            &
     145       user_wrd_local
     146
    150147
    151148!
    152149!- Public parameters, constants and initial values
    153    PUBLIC &
     150   PUBLIC                                                                                          &
    154151      user_module_enabled
    155152
     
    212209
    213210    INTERFACE user_rrd_global
    214        MODULE PROCEDURE user_rrd_global
     211       MODULE PROCEDURE user_rrd_global_ftn
     212       MODULE PROCEDURE user_rrd_global_mpi
    215213    END INTERFACE user_rrd_global
    216214
    217215    INTERFACE user_rrd_local
    218        MODULE PROCEDURE user_rrd_local
     216       MODULE PROCEDURE user_rrd_local_ftn
     217       MODULE PROCEDURE user_rrd_local_mpi
    219218    END INTERFACE user_rrd_local
    220219
     
    235234
    236235
    237 !------------------------------------------------------------------------------!
     236!--------------------------------------------------------------------------------------------------!
    238237! Description:
    239238! ------------
    240239!> Parin for &user_parameters for user module
    241 !------------------------------------------------------------------------------!
     240!--------------------------------------------------------------------------------------------------!
    242241 SUBROUTINE user_parin
    243242
    244 
    245     CHARACTER (LEN=80) ::  line   !<
    246 
    247     INTEGER(iwp) ::  i                 !<
    248     INTEGER(iwp) ::  j                 !<
    249 
    250 
    251     NAMELIST /user_parameters/  &
    252        user_module_enabled, &
    253        data_output_pr_user, &
    254        data_output_user, &
    255        region, &
    256        data_output_masks_user
     243    CHARACTER (LEN=80) ::  line  !< string containing the last line read from namelist file
     244
     245    INTEGER(iwp) ::  i          !<
     246    INTEGER(iwp) ::  io_status  !< status after reading the namelist file
     247    INTEGER(iwp) ::  j          !<
     248
     249
     250    NAMELIST /user_parameters/                                                                     &
     251       data_output_masks_user,                                                                     &
     252       data_output_pr_user,                                                                        &
     253       data_output_user,                                                                           &
     254       region
    257255
    258256!
     
    263261
    264262!
    265 !-- Set revision number of this default interface version. It will be checked within
    266 !-- the main program (palm). Please change the revision number in case that the
    267 !-- current revision does not match with previous revisions (e.g. if routines
    268 !-- have been added/deleted or if parameter lists in subroutines have been changed).
    269     user_interface_current_revision = 'r3703'
    270 
    271 !
    272 !-- Position the namelist-file at the beginning (it was already opened in
    273 !-- parin), search for user-defined namelist-group ("userpar", but any other
    274 !-- name can be choosed) and position the file at this line.
     263!-- Set revision number of this default interface version. It will be checked within the main
     264!-- program (palm). Please change the revision number in case that the current revision does not
     265!-- match with previous revisions (e.g. if routines have been added/deleted or if parameter lists
     266!-- in subroutines have been changed).
     267    user_interface_current_revision = 'r4495'
     268
     269!
     270!-- Position the namelist-file at the beginning (it has already been opened in parin), and try to
     271!-- read (find) a namelist named "user_parameters".
    275272    REWIND ( 11 )
    276 
    277     line = ' '
    278     DO WHILE ( INDEX( line, '&user_parameters' ) == 0 )
    279        READ ( 11, '(A)', END=12 )  line
    280     ENDDO
    281     BACKSPACE ( 11 )
    282 
    283 !-- Set default module switch to true
    284     user_module_enabled = .TRUE.
    285 
    286 !-- Read user-defined namelist
    287     READ ( 11, user_parameters, ERR = 10 )
    288 
    289     GOTO 12
    290 
    291 10  BACKSPACE( 11 )
    292     READ( 11 , '(A)') line
    293     CALL parin_fail_message( 'user_parameters', line )
    294 
    295 12  CONTINUE
    296 
    297 !
    298 !-- Determine the number of user-defined profiles and append them to the
    299 !-- standard data output (data_output_pr)
     273    READ( 11, user_parameters, IOSTAT=io_status )
     274
     275!
     276!-- Actions depending on the READ status
     277    IF ( io_status == 0 )  THEN
     278!
     279!--    User namelist found and correctly read. Set default module switch to true. This activates
     280!--    calls of the user-interface subroutines.
     281       user_module_enabled = .TRUE.
     282
     283    ELSEIF ( io_status > 0 )  THEN
     284!
     285!--    User namelist was found, but contained errors. Print an error message containing the line
     286!--    that caused the problem
     287       BACKSPACE( 11 )
     288       READ( 11 , '(A)') line
     289       CALL parin_fail_message( 'user_parameters', line )
     290
     291    ENDIF
     292
     293!
     294!-- Determine the number of user-defined profiles and append them to the standard data output
     295!-- (data_output_pr)
    300296    IF ( user_module_enabled )  THEN
    301297       IF ( data_output_pr_user(1) /= ' ' )  THEN
     
    318314
    319315
    320 !------------------------------------------------------------------------------!
     316!--------------------------------------------------------------------------------------------------!
    321317! Description:
    322318! ------------
    323319!> Check &userpar control parameters and deduce further quantities.
    324 !------------------------------------------------------------------------------!
     320!--------------------------------------------------------------------------------------------------!
    325321 SUBROUTINE user_check_parameters
    326322
    327 
    328 !-- Here the user may add code to check the validity of further &userpar
    329 !-- control parameters or deduce further quantities.
     323!
     324!-- Here the user may add code to check the validity of further &userpar control parameters or
     325!-- deduce further quantities.
    330326
    331327
     
    333329
    334330
    335 !------------------------------------------------------------------------------!
     331!--------------------------------------------------------------------------------------------------!
    336332! Description:
    337333! ------------
    338334!> Set module-specific timeseries units and labels
    339 !------------------------------------------------------------------------------!
     335!--------------------------------------------------------------------------------------------------!
    340336 SUBROUTINE user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
    341337
    342 
    343     INTEGER(iwp),      INTENT(IN)     ::  dots_max
    344     INTEGER(iwp),      INTENT(INOUT)  ::  dots_num
    345     CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_label
    346     CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_unit
     338    INTEGER(iwp),      INTENT(IN)     ::  dots_max  !<
     339    INTEGER(iwp),      INTENT(INOUT)  ::  dots_num  !<
     340
     341    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_label  !<
     342    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_unit   !<
    347343
    348344!
     
    351347
    352348!
    353 !-- Sample for user-defined time series
    354 !-- For each time series quantity you have to give a label and a unit,
    355 !-- which will be used for the NetCDF file. They must not contain more than
    356 !-- seven characters. The value of dots_num has to be increased by the
    357 !-- number of new time series quantities. Its old value has to be store in
    358 !-- dots_num_palm. See routine user_statistics on how to output calculate
    359 !-- and output these quantities.
     349!-- Sample for user-defined time series:
     350!-- For each time series quantity you have to give a label and a unit, which will be used for the
     351!-- NetCDF file. They must not contain more than seven characters. The value of dots_num has to be
     352!-- increased by the number of new time series quantities. Its old value has to be stored in
     353!-- dots_num_palm. See routine user_statistics on how to calculate and output these quantities.
    360354
    361355!    dots_num_palm = dots_num
     
    375369
    376370
    377 !------------------------------------------------------------------------------!
    378 ! Description:
    379 ! ------------
    380 !> Set the unit of user defined profile output quantities. For those variables
    381 !> not recognized by the user, the parameter unit is set to "illegal", which
    382 !> tells the calling routine that the output variable is not defined and leads
    383 !> to a program abort.
    384 !------------------------------------------------------------------------------!
     371!--------------------------------------------------------------------------------------------------!
     372! Description:
     373! ------------
     374!> Set the unit of user defined profile output quantities. For those variables not recognized by the
     375!> user, the parameter unit is set to "illegal", which tells the calling routine that the
     376!> output variable is not defined and leads to a program abort.
     377!--------------------------------------------------------------------------------------------------!
    385378 SUBROUTINE user_check_data_output_pr( variable, var_count, unit, dopr_unit )
    386379
     
    389382
    390383
    391     CHARACTER (LEN=*) ::  unit     !<
    392     CHARACTER (LEN=*) ::  variable !<
     384    CHARACTER (LEN=*) ::  unit      !<
     385    CHARACTER (LEN=*) ::  variable  !<
    393386    CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    394387
    395 !    INTEGER(iwp) ::  user_pr_index !<
    396     INTEGER(iwp) ::  var_count     !<
     388!    INTEGER(iwp) ::  user_pr_index  !<
     389    INTEGER(iwp) ::  var_count      !<
    397390
    398391!
     
    404397!
    405398!--    Uncomment and extend the following lines, if necessary.
    406 !--    Add additional CASE statements depending on the number of quantities
    407 !--    for which profiles are to be calculated. The respective calculations
    408 !--    to be performed have to be added in routine user_statistics.
    409 !--    The quantities are (internally) identified by a user-profile-number
    410 !--    (see variable "user_pr_index" below). The first user-profile must be assigned
    411 !--    the number "pr_palm+1", the second one "pr_palm+2", etc. The respective
    412 !--    user-profile-numbers have also to be used in routine user_statistics!
    413 !       CASE ( 'u*v*' )                      ! quantity string as given in
    414 !                                            ! data_output_pr_user
     399!--    Add additional CASE statements depending on the number of quantities for which profiles are
     400!--    to be calculated. The respective calculations to be performed have to be added in routine
     401!--    user_statistics. The quantities are (internally) identified by a user-profile-number
     402!--    (see variable "user_pr_index" below). The first user-profile must be assigned the number
     403!--    "pr_palm+1", the second one "pr_palm+2", etc. The respective user-profile-numbers have also
     404!--    to be used in routine user_statistics!
     405!       CASE ( 'u*v*' )                      ! quantity string as given in data_output_pr_user
    415406!          user_pr_index = pr_palm + 1
    416407!          dopr_index(var_count)  = user_pr_index    ! quantities' user-profile-number
    417408!          dopr_unit = 'm2/s2'  ! quantity unit
    418409!          unit = dopr_unit
    419 !          hom(:,2,user_pr_index,:)       = SPREAD( zu, 2, statistic_regions+1 )
    420 !                                            ! grid on which the quantity is
    421 !                                            ! defined (use zu or zw)
     410!          hom(:,2,user_pr_index,:) = SPREAD( zu, 2, statistic_regions+1 )
     411!                                            ! grid on which the quantity is defined (use zu or zw)
     412!
    422413
    423414       CASE DEFAULT
     
    430421
    431422
    432 !------------------------------------------------------------------------------!
    433 ! Description:
    434 ! ------------
    435 !> Set the unit of user defined output quantities. For those variables
    436 !> not recognized by the user, the parameter unit is set to "illegal", which
    437 !> tells the calling routine that the output variable is not defined and leads
    438 !> to a program abort.
    439 !------------------------------------------------------------------------------!
     423!--------------------------------------------------------------------------------------------------!
     424! Description:
     425! ------------
     426!> Set the unit of user defined output quantities. For those variables not recognized by the user,
     427!> the parameter unit is set to "illegal", which tells the calling routine that the output variable
     428!> is not defined and leads to a program abort.
     429!--------------------------------------------------------------------------------------------------!
    440430 SUBROUTINE user_check_data_output( variable, unit )
    441431
    442432
    443     CHARACTER (LEN=*) ::  unit     !<
    444     CHARACTER (LEN=*) ::  variable !<
     433    CHARACTER (LEN=*) ::  unit      !<
     434    CHARACTER (LEN=*) ::  variable  !<
    445435
    446436
     
    451441!       CASE ( 'u2' )
    452442!          unit = 'm2/s2'
    453 
     443!
     444!       CASE ( 'u*v*' )
     445!          unit = 'm2/s2'
     446!
    454447      CASE ( 'v_h' )
    455448         unit = 'm/s'
    456 !
    457 !       CASE ( 'u*v*' )
    458 !          unit = 'm2/s2'
    459 !
     449
    460450       CASE DEFAULT
    461451          unit = 'illegal'
     
    467457
    468458
    469 !------------------------------------------------------------------------------!
     459!--------------------------------------------------------------------------------------------------!
    470460! Description:
    471461! ------------
    472462!> Initialize user-defined arrays
    473 !------------------------------------------------------------------------------!
     463!--------------------------------------------------------------------------------------------------!
    474464 SUBROUTINE user_init_arrays
    475465
     
    486476    ALLOCATE( v_h(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    487477
     478
    488479!
    489480!-- Example for defining a statistic region:
     481!-- ATTENTION: rmask = 0 is required at the ghost boundaries to guarantee correct statistic
     482!--            evaluations (otherwise ghost points would be counted twice). This setting has
     483!--            already been cared for in routine init_3d_model. Please don't set the ghost points
     484!--            /= 0. i.e. run the following loop only over nxl,nxr and nys,nyn.
    490485!     IF ( statistic_regions >= 1 )  THEN
    491486!        region = 1
    492 ! 
     487!
    493488!        rmask(:,:,region) = 0.0_wp
    494489!        DO  i = nxl, nxr
     
    501496!           ENDIF
    502497!        ENDDO
    503 ! 
     498!
    504499!     ENDIF
    505500
     
    507502
    508503
    509 !------------------------------------------------------------------------------!
     504!--------------------------------------------------------------------------------------------------!
    510505! Description:
    511506! ------------
    512507!> Execution of user-defined initializing actions
    513 !------------------------------------------------------------------------------!
     508!--------------------------------------------------------------------------------------------------!
    514509 SUBROUTINE user_init
    515510
    516511
    517 !    CHARACTER (LEN=20) :: field_char   !<
     512!    CHARACTER(LEN=20) :: field_char  !<
    518513!
    519514!-- Here the user-defined initializing actions follow:
     
    526521
    527522
    528 !------------------------------------------------------------------------------!
    529 ! Description:
    530 ! ------------
    531 !> Set the grids on which user-defined output quantities are defined.
    532 !> Allowed values for grid_x are "x" and "xu", for grid_y "y" and "yv", and
    533 !> for grid_z "zu" and "zw".
    534 !------------------------------------------------------------------------------!
     523!--------------------------------------------------------------------------------------------------!
     524! Description:
     525! ------------
     526!> Set the grids on which user-defined output quantities are defined. Allowed values for grid_x are
     527!> "x" and "xu", for grid_y "y" and "yv", and for grid_z "zu" and "zw".
     528!--------------------------------------------------------------------------------------------------!
    535529 SUBROUTINE user_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
    536530
     
    560554!          grid_z = 'zu'
    561555
    562 
    563556      CASE ( 'v_h', 'v_h_av' )
    564557         found  = .TRUE.
     
    581574
    582575
    583 !------------------------------------------------------------------------------!
     576!--------------------------------------------------------------------------------------------------!
    584577! Description:
    585578! ------------
    586579!> Print a header with user-defined information.
    587 !------------------------------------------------------------------------------!
     580!--------------------------------------------------------------------------------------------------!
    588581 SUBROUTINE user_header( io )
    589582
    590583
    591     INTEGER(iwp) ::  i    !<
    592     INTEGER(iwp) ::  io   !<
    593 
    594 !
    595 !-- If no user-defined variables are read from the namelist-file, no
    596 !-- information will be printed.
     584    INTEGER(iwp) ::  i   !<
     585    INTEGER(iwp) ::  io  !<
     586
     587!
     588!-- If no user-defined variables are read from the namelist-file, no information will be printed.
    597589    IF ( .NOT. user_module_enabled )  THEN
    598590       WRITE ( io, 100 )
     
    614606!-- Format-descriptors
    615607100 FORMAT (//' *** no user-defined variables found'/)
    616 110 FORMAT (//1X,78('#')                                                       &
    617             //' User-defined variables and actions:'/                          &
    618               ' -----------------------------------'//)
     608110 FORMAT (//1X,78('#') // ' User-defined variables and actions:' /                               &
     609            ' -----------------------------------'//)
    619610200 FORMAT (' Output of profiles and time series for following regions:' /)
    620611201 FORMAT (4X,'Region ',I1,':   ',A)
     
    624615
    625616
    626 !------------------------------------------------------------------------------!
     617!--------------------------------------------------------------------------------------------------!
    627618! Description:
    628619! ------------
    629620!> Call for all grid points
    630 !------------------------------------------------------------------------------!
     621!--------------------------------------------------------------------------------------------------!
    631622 SUBROUTINE user_actions( location )
    632623
    633624
    634     CHARACTER (LEN=*) ::  location !<
    635 
    636     INTEGER(iwp) ::  i !<
    637     INTEGER(iwp) ::  j !<
    638     INTEGER(iwp) ::  k !<
     625    CHARACTER(LEN=*) ::  location  !<
     626
     627    INTEGER(iwp) ::  i  !<
     628    INTEGER(iwp) ::  j  !<
     629    INTEGER(iwp) ::  k  !<
    639630
    640631    CALL cpu_log( log_point(24), 'user_actions', 'start' )
    641632
    642633!
    643 !-- Here the user-defined actions follow
    644 !-- No calls for single grid points are allowed at locations before and
    645 !-- after the timestep, since these calls are not within an i,j-loop
     634!-- Here the user-defined actions follow. No calls for single grid points are allowed at locations
     635!-- before and after the timestep, since these calls are not within an i,j-loop
    646636    SELECT CASE ( location )
    647637
     
    656646       CASE ( 'after_integration' )
    657647!
    658 !--       Enter actions to be done after every time integration (before
    659 !--       data output)
     648!--       Enter actions to be done after every time integration (before data output)
    660649!--       Sample for user-defined output:
    661650!          DO  i = nxlg, nxrg
     
    670659!                DO  k = nzb, nzt+1
    671660!                   ustvst(k,j,i) =  &
    672 !                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) * &
     661!                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) *                      &
    673662!                      ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) )
    674663!                ENDDO
     
    679668             DO  j = nysg, nyng
    680669                DO  k = nzb, nzt
    681                    v_h(k,j,i) = SQRT(u(k,j,i)**2.+v(k,j,i)**2.)
     670                   v_h(k,j,i) = SQRT( u(k,j,i)**2.0_wp + v(k,j,i)**2.0_wp )
    682671                ENDDO
    683672             ENDDO
    684673          ENDDO
    685674
    686 
    687675       CASE ( 'after_timestep' )
    688676!
     
    726714
    727715
    728 !------------------------------------------------------------------------------!
     716!--------------------------------------------------------------------------------------------------!
    729717! Description:
    730718! ------------
    731719!> Call for grid point i,j
    732 !------------------------------------------------------------------------------!
     720!--------------------------------------------------------------------------------------------------!
    733721 SUBROUTINE user_actions_ij( i, j, location )
    734722
    735723
    736     CHARACTER (LEN=*) ::  location
    737 
    738     INTEGER(iwp) ::  i
    739     INTEGER(iwp) ::  j
     724    CHARACTER(LEN=*) ::  location  !<
     725
     726    INTEGER(iwp) ::  i  !<
     727    INTEGER(iwp) ::  j  !<
    740728
    741729!
     
    782770
    783771
    784 !------------------------------------------------------------------------------!
    785 ! Description:
    786 ! ------------
    787 !> Sum up and time-average user-defined output quantities as well as allocate
    788 !> the array necessary for storing the average.
    789 !------------------------------------------------------------------------------!
     772!--------------------------------------------------------------------------------------------------!
     773! Description:
     774! ------------
     775!> Sum up and time-average user-defined output quantities as well as allocate the array necessary
     776!> for storing the average.
     777!--------------------------------------------------------------------------------------------------!
    790778 SUBROUTINE user_3d_data_averaging( mode, variable )
    791779
    792780
    793     CHARACTER (LEN=*) ::  mode    !<
    794     CHARACTER (LEN=*) :: variable !<
    795 
    796     INTEGER(iwp) ::  i !<
    797     INTEGER(iwp) ::  j !<
    798     INTEGER(iwp) ::  k !<
     781    CHARACTER(LEN=*) ::  mode      !<
     782    CHARACTER(LEN=*) ::  variable  !<
     783
     784    INTEGER(iwp) ::  i  !<
     785    INTEGER(iwp) ::  j  !<
     786    INTEGER(iwp) ::  k  !<
    799787
    800788    IF ( mode == 'allocate' )  THEN
     
    804792!
    805793!--       Uncomment and extend the following lines, if necessary.
    806 !--       The arrays for storing the user defined quantities (here u2_av) have
    807 !--       to be declared and defined by the user!
     794!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
     795!--       defined by the user!
    808796!--       Sample for user-defined output:
    809797!          CASE ( 'u2' )
     
    830818!
    831819!--       Uncomment and extend the following lines, if necessary.
    832 !--       The arrays for storing the user defined quantities (here u2 and
    833 !--       u2_av) have to be declared and defined by the user!
     820!--       The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     821!--       and defined by the user!
    834822!--       Sample for user-defined output:
    835823!          CASE ( 'u2' )
    836 !             IF ( ALLOCATED( u2_av ) ) THEN
     824!             IF ( ALLOCATED( u2_av ) )  THEN
    837825!                DO  i = nxlg, nxrg
    838826!                   DO  j = nysg, nyng
     
    845833
    846834          CASE ( 'v_h' )
     835
    847836             IF ( ALLOCATED( v_h_av ) ) THEN
    848837                DO  i = nxlg, nxrg
     
    855844             ENDIF
    856845
     846
    857847          CASE DEFAULT
    858848             CONTINUE
     
    866856!
    867857!--       Uncomment and extend the following lines, if necessary.
    868 !--       The arrays for storing the user defined quantities (here u2_av) have
    869 !--       to be declared and defined by the user!
     858!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
     859!--       defined by the user!
    870860!--       Sample for user-defined output:
    871861!          CASE ( 'u2' )
    872 !             IF ( ALLOCATED( u2_av ) ) THEN
     862!             IF ( ALLOCATED( u2_av ) )  THEN
    873863!                DO  i = nxlg, nxrg
    874864!                   DO  j = nysg, nyng
     
    881871
    882872          CASE ( 'v_h' )
     873
    883874             IF ( ALLOCATED( v_h_av ) ) THEN
    884875                DO  i = nxlg, nxrg
     
    891882             ENDIF
    892883
     884
    893885       END SELECT
    894886
     
    899891
    900892
    901 !------------------------------------------------------------------------------!
    902 ! Description:
    903 ! ------------
    904 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    905 !> temporary array with indices (i,j,k) and sets the grid on which it is defined.
    906 !> Allowed values for grid are "zu" and "zw".
    907 !------------------------------------------------------------------------------!
     893!--------------------------------------------------------------------------------------------------!
     894! Description:
     895! ------------
     896!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
     897!> (i,j,k) and sets the grid on which it is defined. Allowed values for grid are "zu" and "zw".
     898!--------------------------------------------------------------------------------------------------!
    908899 SUBROUTINE user_data_output_2d( av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do )
    909900
    910901
    911     CHARACTER (LEN=*) ::  grid     !<
    912     CHARACTER (LEN=*) ::  variable !<
    913 
    914     INTEGER(iwp) ::  av     !< flag to control data output of instantaneous or time-averaged data
    915     INTEGER(iwp) ::  i      !< grid index along x-direction
    916     INTEGER(iwp) ::  j      !< grid index along y-direction
    917     INTEGER(iwp) ::  k      !< grid index along z-direction
    918 !    INTEGER(iwp) ::  m      !< running index surface elements
    919     INTEGER(iwp) ::  nzb_do !< lower limit of the domain (usually nzb)
    920     INTEGER(iwp) ::  nzt_do !< upper limit of the domain (usually nzt+1)
    921 
    922     LOGICAL      ::  found !<
    923     LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
    924 
    925     REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    926 
    927     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     902    CHARACTER(LEN=*) ::  grid      !<
     903    CHARACTER(LEN=*) ::  variable  !<
     904
     905    INTEGER(iwp) ::  av      !< flag to control data output of instantaneous or time-averaged data
     906    INTEGER(iwp) ::  i       !< grid index along x-direction
     907    INTEGER(iwp) ::  j       !< grid index along y-direction
     908    INTEGER(iwp) ::  k       !< grid index along z-direction
     909!    INTEGER(iwp) ::  m       !< running index surface elements
     910    INTEGER(iwp) ::  nzb_do  !< lower limit of the domain (usually nzb)
     911    INTEGER(iwp) ::  nzt_do  !< upper limit of the domain (usually nzt+1)
     912
     913    LOGICAL      ::  found  !<
     914    LOGICAL      ::  two_d  !< flag parameter that indicates 2D variables (horizontal cross sections)
     915
     916   REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
     917
     918    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
    928919
    929920!
     
    931922    IF ( av == 0  .OR.  local_pf(nxl,nys,nzb_do) == 0.0_wp  .OR.  two_d )  CONTINUE
    932923
     924
    933925    found = .TRUE.
    934926
     
    937929!
    938930!--    Uncomment and extend the following lines, if necessary.
    939 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    940 !--    have to be declared and defined by the user!
     931!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     932!--    and defined by the user!
    941933!--    Sample for user-defined output:
    942934!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
     
    950942!             ENDDO
    951943!          ELSE
    952 !             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     944!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    953945!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    954946!                u2_av = REAL( fill_value, KIND = wp )
     
    989981
    990982          grid = 'zu'
    991 !
    992 !--    In case two-dimensional surface variables are output, the user
    993 !--    has to access related surface-type. Uncomment and extend following lines
    994 !--    appropriately (example output of vertical surface momentum flux of u-
    995 !--    component). Please note, surface elements can be distributed over
    996 !--    several data type, depending on their respective surface properties.
     983
     984!
     985!--    In case two-dimensional surface variables are output, the user has to access related
     986!--    surface-type. Uncomment and extend following lines appropriately (example output of vertical
     987!--    surface momentum flux of u-component). Please note, surface elements can be distributed over
     988!--    several data types, depending on their respective surface properties.
    997989!       CASE ( 'usws_xy' )
    998990!          IF ( av == 0 )  THEN
     
    10211013!
    10221014!          grid = 'zu'
    1023 !--       
     1015!--
    10241016
    10251017
     
    10341026
    10351027
    1036 !------------------------------------------------------------------------------!
    1037 ! Description:
    1038 ! ------------
    1039 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    1040 !> temporary array with indices (i,j,k).
    1041 !------------------------------------------------------------------------------!
     1028!--------------------------------------------------------------------------------------------------!
     1029! Description:
     1030! ------------
     1031!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
     1032!> (i,j,k).
     1033!--------------------------------------------------------------------------------------------------!
    10421034 SUBROUTINE user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
    10431035
    10441036
    1045     CHARACTER (LEN=*) ::  variable !<
    1046 
    1047     INTEGER(iwp) ::  av    !<
    1048     INTEGER(iwp) ::  i     !<
    1049     INTEGER(iwp) ::  j     !<
    1050     INTEGER(iwp) ::  k     !<
     1037    CHARACTER(LEN=*) ::  variable  !<
     1038
     1039    INTEGER(iwp) ::  av     !<
     1040    INTEGER(iwp) ::  i      !<
     1041    INTEGER(iwp) ::  j      !<
     1042    INTEGER(iwp) ::  k      !<
    10511043    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
    10521044    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    10531045
    1054     LOGICAL      ::  found !<
    1055 
    1056     REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    1057 
    1058     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     1046    LOGICAL      ::  found  !<
     1047
     1048   REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
     1049
     1050    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
     1051
     1052!
     1053!-- Next line is to avoid compiler warning about unused variables. Please remove.
     1054    IF ( av == 0  .OR.  local_pf(nxl,nys,nzb_do) == 0.0_wp )  CONTINUE
    10591055
    10601056
     
    10651061!
    10661062!--    Uncomment and extend the following lines, if necessary.
    1067 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    1068 !--    have to be declared and defined by the user!
     1063!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     1064!--    and defined by the user!
    10691065!--    Sample for user-defined output:
    10701066!       CASE ( 'u2' )
     
    10781074!             ENDDO
    10791075!          ELSE
    1080 !             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     1076!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    10811077!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    10821078!                u2_av = REAL( fill_value, KIND = wp )
     
    10901086!             ENDDO
    10911087!          ENDIF
    1092 
    10931088
    10941089       CASE ( 'v_h' )
     
    11141109             ENDDO
    11151110          ENDIF
    1116 !
     1111
    11171112
    11181113       CASE DEFAULT
     
    11251120
    11261121
    1127 !------------------------------------------------------------------------------!
    1128 ! Description:
    1129 ! ------------
    1130 !> Calculation of user-defined statistics, i.e. horizontally averaged profiles
    1131 !> and time series.
    1132 !> This routine is called for every statistic region sr defined by the user,
    1133 !> but at least for the region "total domain" (sr=0).
    1134 !> See section 3.5.4 on how to define, calculate, and output user defined
    1135 !> quantities.
    1136 !------------------------------------------------------------------------------!
     1122!--------------------------------------------------------------------------------------------------!
     1123! Description:
     1124! ------------
     1125!> Calculation of user-defined statistics, i.e. horizontally averaged profiles and time series.
     1126!> This routine is called for every statistic region sr defined by the user, but at least for the
     1127!> region "total domain" (sr=0). See section 3.5.4 on how to define, calculate, and output user
     1128!> defined quantities.
     1129!--------------------------------------------------------------------------------------------------!
    11371130 SUBROUTINE user_statistics( mode, sr, tn )
    11381131
    11391132
    1140     CHARACTER (LEN=*) ::  mode   !<
    1141 !    INTEGER(iwp) ::  i    !<
    1142 !    INTEGER(iwp) ::  j    !<
    1143 !    INTEGER(iwp) ::  k    !<
    1144     INTEGER(iwp) ::  sr   !<
    1145     INTEGER(iwp) ::  tn   !<
    1146 
    1147 !    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l   !<
     1133    CHARACTER(LEN=*) ::  mode  !<
     1134!    INTEGER(iwp) ::  i   !<
     1135!    INTEGER(iwp) ::  j   !<
     1136!    INTEGER(iwp) ::  k   !<
     1137    INTEGER(iwp) ::  sr  !<
     1138    INTEGER(iwp) ::  tn  !<
     1139
     1140!    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l  !<
    11481141
    11491142!
     
    11541147
    11551148!
    1156 !--    Sample on how to calculate horizontally averaged profiles of user-
    1157 !--    defined quantities. Each quantity is identified by the index
    1158 !--    "pr_palm+#" where "#" is an integer starting from 1. These
    1159 !--    user-profile-numbers must also be assigned to the respective strings
    1160 !--    given by data_output_pr_user in routine user_check_data_output_pr.
     1149!--    Sample on how to calculate horizontally averaged profiles of user-defined quantities. Each
     1150!--    quantity is identified by the index "pr_palm+#" where "#" is an integer starting from 1.
     1151!--    These user-profile-numbers must also be assigned to the respective strings given by
     1152!--    data_output_pr_user in routine user_check_data_output_pr.
    11611153!       !$OMP DO
    11621154!       DO  i = nxl, nxr
     
    11641156!             DO  k = nzb+1, nzt
    11651157!!
    1166 !!--             Sample on how to calculate the profile of the resolved-scale
    1167 !!--             horizontal momentum flux u*v*
    1168 !                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +             &
    1169 !                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *&
    1170 !                      ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )  &
    1171 !                                     * rmask(j,i,sr)                          &
    1172 !                                     * MERGE( 1.0_wp, 0.0_wp,                 &
    1173 !                                              BTEST( wall_flags_0(k,j,i), 0 ) )
     1158!!--             Sample on how to calculate the profile of the resolved-scale horizontal momentum
     1159!!--             flux u*v*
     1160!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +                                  &
     1161!                                         ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *  &
     1162!                                         ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) ) *  &
     1163!                                         rmask(j,i,sr) * MERGE( 1.0_wp, 0.0_wp,                    &
     1164!                                         BTEST( wall_flags_total_0(k,j,i), 0 ) )
    11741165!!
    1175 !!--             Further profiles can be defined and calculated by increasing
    1176 !!--             the second index of array sums_l (replace ... appropriately)
    1177 !                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...           &
    1178 !                                         * rmask(j,i,sr)
     1166!!--             Further profiles can be defined and calculated by increasing the second index of
     1167!!--             array sums_l (replace ... appropriately)
     1168!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...   * rmask(j,i,sr)
    11791169!             ENDDO
    11801170!          ENDDO
     
    11871177!
    11881178!--    Sample on how to add values for the user-defined time series quantities.
    1189 !--    These have to be defined before in routine user_init. This sample
    1190 !--    creates two time series for the absolut values of the horizontal
    1191 !--    velocities u and v.
     1179!--    These have to be defined before in routine user_init. This sample creates two time series for
     1180!--    the absolut values of the horizontal velocities u and v.
    11921181!       ts_value_l = 0.0_wp
    11931182!       ts_value_l(1) = ABS( u_max )
     
    11951184!
    11961185!--     Collect / send values to PE0, because only PE0 outputs the time series.
    1197 !--     CAUTION: Collection is done by taking the sum over all processors.
    1198 !--              You may have to normalize this sum, depending on the quantity
    1199 !--              that you like to calculate. For serial runs, nothing has to be
    1200 !--              done.
    1201 !--     HINT: If the time series value that you are calculating has the same
    1202 !--           value on all PEs, you can omit the MPI_ALLREDUCE call and
    1203 !--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
     1186!--     CAUTION: Collection is done by taking the sum over all processors. You may have to normalize
     1187!--              this sum, depending on the quantity that you like to calculate. For serial runs,
     1188!--              nothing has to be done.
     1189!--     HINT: If the time series value that you are calculating has the same value on all PEs, you
     1190!--           can omit the MPI_ALLREDUCE call and assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
    12041191!#if defined( __parallel )
    12051192!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1206 !       CALL MPI_ALLREDUCE( ts_value_l(1),                         &
    1207 !                           ts_value(dots_num_palm+1,sr),                        &
    1208 !                           dots_num_user, MPI_REAL, MPI_MAX, comm2d,   &
    1209 !                           ierr )
     1193!       CALL MPI_ALLREDUCE( ts_value_l(1), ts_value(dots_num_palm+1,sr), dots_num_user, MPI_REAL,   &
     1194!                           MPI_MAX, comm2d, ierr )
    12101195!#else
    12111196!       ts_value(dots_num_palm+1:dots_num_palm+dots_num_user,sr) = ts_value_l
     
    12171202
    12181203
    1219 !------------------------------------------------------------------------------!
    1220 ! Description:
    1221 ! ------------
    1222 !> Reading global restart data that has been defined by the user.
    1223 !------------------------------------------------------------------------------!
    1224  SUBROUTINE user_rrd_global( found )
    1225 
    1226 
    1227     LOGICAL, INTENT(OUT)  ::  found
     1204!--------------------------------------------------------------------------------------------------!
     1205! Description:
     1206! ------------
     1207!> Read module-specific global restart data (Fortran binary format).
     1208!--------------------------------------------------------------------------------------------------!
     1209 SUBROUTINE user_rrd_global_ftn( found )
     1210
     1211
     1212    LOGICAL, INTENT(OUT)  ::  found  !<
    12281213
    12291214
     
    12371222
    12381223       CASE DEFAULT
    1239  
     1224
    12401225          found = .FALSE.
    12411226
     
    12431228
    12441229
    1245  END SUBROUTINE user_rrd_global
    1246 
    1247 
    1248 !------------------------------------------------------------------------------!
    1249 ! Description:
    1250 ! ------------
    1251 !> Reading processor specific restart data from file(s) that has been defined
    1252 !> by the user.
    1253 !> Subdomain index limits on file are given by nxl_on_file, etc.
    1254 !> Indices nxlc, etc. indicate the range of gridpoints to be mapped from the
    1255 !> subdomain on file (f) to the subdomain of the current PE (c). They have been
    1256 !> calculated in routine rrd_local.
    1257 !------------------------------------------------------------------------------!
    1258  SUBROUTINE user_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,         &
    1259                             nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
    1260                             nysc, nys_on_file, tmp_3d, found )
     1230 END SUBROUTINE user_rrd_global_ftn
     1231
     1232
     1233!--------------------------------------------------------------------------------------------------!
     1234! Description:
     1235! ------------
     1236!> Read module-specific global restart data (MPI-IO).
     1237!--------------------------------------------------------------------------------------------------!
     1238 SUBROUTINE user_rrd_global_mpi
     1239
     1240!    USE restart_data_mpi_io_mod,                                                                   &
     1241!        ONLY:  rrd_mpi_io
     1242
     1243!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
     1244    CONTINUE
     1245
     1246 END SUBROUTINE user_rrd_global_mpi
     1247
     1248
     1249!--------------------------------------------------------------------------------------------------!
     1250! Description:
     1251! ------------
     1252!> Read module-specific local restart data arrays (Fortran binary format).
     1253!> Subdomain
     1254!> index limits on file are given by nxl_on_file, etc. Indices nxlc, etc. indicate the range of
     1255!> gridpoints to be mapped from the subdomain on file (f) to the subdomain of the current PE (c).
     1256!> They have been calculated in routine rrd_local.
     1257!--------------------------------------------------------------------------------------------------!
     1258 SUBROUTINE user_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,   &
     1259                                nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
    12611260
    12621261
     
    12761275    INTEGER(iwp) ::  nys_on_file     !<
    12771276
    1278     LOGICAL, INTENT(OUT)  ::  found
    1279 
    1280     REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
     1277    LOGICAL, INTENT(OUT)  ::  found  !<
     1278
     1279    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d  !<
    12811280
    12821281!
     
    12941293
    12951294       CASE ( 'u2_av' )
    1296 !          IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     1295!          IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    12971296!               ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    12981297!          ENDIF
    12991298!          IF ( k == 1 )  READ ( 13 )  tmp_3d
    1300 !             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
    1301 !                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     1299!             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                    &
     1300!             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    13021301!
    13031302       CASE DEFAULT
     
    13071306    END SELECT
    13081307
    1309  END SUBROUTINE user_rrd_local
    1310 
    1311 
    1312 !------------------------------------------------------------------------------!
    1313 ! Description:
    1314 ! ------------
    1315 !> Writes global and user-defined restart data into binary file(s) for restart
    1316 !> runs.
    1317 !------------------------------------------------------------------------------!
     1308 END SUBROUTINE user_rrd_local_ftn
     1309
     1310
     1311!--------------------------------------------------------------------------------------------------!
     1312! Description:
     1313! ------------
     1314!> Read module-specific local restart data arrays (MPI-IO).
     1315!--------------------------------------------------------------------------------------------------!
     1316 SUBROUTINE user_rrd_local_mpi
     1317
     1318!    USE restart_data_mpi_io_mod,                                                                   &
     1319!        ONLY:  rd_mpi_io_check_array, rrd_mpi_io
     1320
     1321!    CALL rd_mpi_io_check_array( 'u2_av' , found = array_found )
     1322!    IF ( array_found )  THEN
     1323!       IF ( .NOT. ALLOCATED( u2_av ) )  ALLOCATE( u2_av(nysg:nyng,nxlg:nxrg) )
     1324!       CALL rrd_mpi_io( 'rad_u2_av', rad_u2_av )
     1325!    ENDIF
     1326
     1327    CONTINUE
     1328
     1329 END SUBROUTINE user_rrd_local_mpi
     1330
     1331
     1332!--------------------------------------------------------------------------------------------------!
     1333! Description:
     1334! ------------
     1335!> Writes global and user-defined restart data into binary file(s) for restart runs.
     1336!--------------------------------------------------------------------------------------------------!
    13181337 SUBROUTINE user_wrd_global
    13191338
    1320 !    CALL wrd_write_string( 'global_parameter' )
    1321 !    WRITE ( 14 )  global_parameter
     1339!    USE restart_data_mpi_io_mod,                                                                   &
     1340!        ONLY:  wrd_mpi_io
     1341
     1342    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     1343
     1344!       CALL wrd_write_string( 'global_parameter' )
     1345!       WRITE ( 14 )  global_parameter
     1346
     1347    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
     1348
     1349!    CALL rrd_mpi_io( 'global_parameter', global_parameter )
     1350
     1351    ENDIF
    13221352
    13231353 END SUBROUTINE user_wrd_global
    13241354
    13251355
    1326 !------------------------------------------------------------------------------!
    1327 ! Description:
    1328 ! ------------
    1329 !> Writes processor specific and user-defined restart data into binary file(s)
    1330 !> for restart runs.
    1331 !------------------------------------------------------------------------------!
     1356!--------------------------------------------------------------------------------------------------!
     1357! Description:
     1358! ------------
     1359!> Writes processor specific and user-defined restart data into binary file(s) for restart runs.
     1360!--------------------------------------------------------------------------------------------------!
    13321361 SUBROUTINE user_wrd_local
     1362
     1363!    USE restart_data_mpi_io_mod,                                                                   &
     1364!        ONLY:  wrd_mpi_io
    13331365
    13341366!
    13351367!-- Here the user-defined actions at the end of a job follow.
    13361368!-- Sample for user-defined output:
    1337 !    IF ( ALLOCATED( u2_av ) )  THEN
    1338 !       CALL wrd_write_string( 'u2_av' )
    1339 !       WRITE ( 14 )  u2_av
    1340 !    ENDIF
     1369    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     1370
     1371!       IF ( ALLOCATED( u2_av ) )  THEN
     1372!          CALL wrd_write_string( 'u2_av' )
     1373!          WRITE ( 14 )  u2_av
     1374!       ENDIF
     1375
     1376    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
     1377
     1378!       IF ( ALLOCATED( u2_av ) )  CALL wrd_mpi_io( 'u2_av', u2_av )
     1379
     1380    ENDIF
    13411381
    13421382 END SUBROUTINE user_wrd_local
    13431383
    13441384
    1345 !------------------------------------------------------------------------------!
     1385!--------------------------------------------------------------------------------------------------!
    13461386! Description:
    13471387! ------------
    13481388!> Execution of user-defined actions at the end of a job.
    1349 !------------------------------------------------------------------------------!
     1389!--------------------------------------------------------------------------------------------------!
    13501390 SUBROUTINE user_last_actions
    13511391
Note: See TracChangeset for help on using the changeset viewer.