Ignore:
Timestamp:
Apr 15, 2020 10:20:51 AM (4 years ago)
Author:
raasch
Message:

last bugfix deactivated because of compile problems, files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4495 r4497  
    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:
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4495 2020-04-13 20:11:20Z raasch
    2731! restart data handling with MPI-IO added
    28 ! 
     32!
    2933! 4360 2020-01-07 11:25:50Z suehring
    30 ! Introduction of wall_flags_total_0, which currently sets bits based on static
    31 ! topography information used in wall_flags_static_0
    32 ! 
     34! Introduction of wall_flags_total_0, which currently sets bits based on static topography
     35! information used in wall_flags_static_0
     36!
    3337! 4329 2019-12-10 15:46:36Z motisi
    3438! Renamed wall_flags_0 to wall_flags_static_0
    35 ! 
     39!
    3640! 4287 2019-11-01 14:50:20Z raasch
    3741! reading of namelist file and actions in case of namelist errors revised so that statement labels
    38 ! and goto statements are not required any more; this revision also removes a previous bug
    39 ! which appeared when the namelist has been commented out in the namelist file
    40 ! 
     42! and goto statements are not required any more; this revision also removes a previous bug which
     43! appeared when the namelist has been commented out in the namelist file
     44!
    4145! 4182 2019-08-22 15:20:23Z scharf
    4246! Corrected "Former revisions" section
    43 ! 
     47!
    4448! 3986 2019-05-20 14:08:14Z Giersch
    4549! Redundant integration of control parameters in user_rrd_global removed
    46 ! 
     50!
    4751! 3911 2019-04-17 12:26:19Z knoop
    4852! Bugfix: added before_prognostic_equations case in user_actions
    49 ! 
     53!
    5054! 3768 2019-02-27 14:35:58Z raasch
    5155! variables commented + statements added to avoid compiler warnings about unused variables
     
    5357! 3767 2019-02-27 08:18:02Z raasch
    5458! unused variable for file index removed from rrd-subroutines parameter list
    55 ! 
     59!
    5660! 3747 2019-02-16 15:15:23Z gronemeier
    5761! Add routine user_init_arrays
    58 ! 
     62!
    5963! 3703 2019-01-29 16:43:53Z knoop
    6064! An example for a user defined global variable has been added (Giersch)
     
    6670! Description:
    6771! ------------
    68 !> Declaration of user-defined variables. This module may only be used
    69 !> in the user-defined routines (contained in user_interface.f90).
    70 !------------------------------------------------------------------------------!
     72!> Declaration of user-defined variables. This module may only be used in the user-defined routines
     73!> (contained in user_interface.f90).
     74!--------------------------------------------------------------------------------------------------!
    7175 MODULE user
    7276
    73 
    7477    USE arrays_3d
    7578
     
    9093    IMPLICIT NONE
    9194
    92     INTEGER(iwp) ::  dots_num_palm   !<
    93     INTEGER(iwp) ::  dots_num_user = 0  !< 
    94     INTEGER(iwp) ::  user_idummy     !<
    95    
    96     LOGICAL ::  user_module_enabled = .FALSE.   !<
    97    
    98     REAL(wp) ::  user_rdummy   !<
     95    INTEGER(iwp) ::  dots_num_palm      !<
     96    INTEGER(iwp) ::  dots_num_user = 0  !<
     97    INTEGER(iwp) ::  user_idummy        !<
     98
     99    LOGICAL ::  user_module_enabled = .FALSE.  !<
     100
     101    REAL(wp) ::  user_rdummy  !<
    99102
    100103!
    101104!-- Sample for user-defined output
    102 !    REAL(wp) :: global_parameter !< user defined global parameter
    103 !
    104 !    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2       !< user defined array
    105 !    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2_av    !< user defined array
    106 !    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ustvst   !< user defined array
     105!    REAL(wp) :: global_parameter  !< user defined global parameter
     106!
     107!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2      !< user defined array
     108!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u2_av   !< user defined array
     109!    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  ustvst  !< user defined array
    107110
    108111    SAVE
     
    112115!
    113116!- Public functions
    114     PUBLIC &
    115        user_parin, &
    116        user_check_parameters, &
    117        user_check_data_output_ts, &
    118        user_check_data_output_pr, &
    119        user_check_data_output, &
    120        user_define_netcdf_grid, &
    121        user_init, &
    122        user_init_arrays, &
    123        user_header, &
    124        user_actions, &
    125        user_3d_data_averaging, &
    126        user_data_output_2d, &
    127        user_data_output_3d, &
    128        user_statistics, &
    129        user_rrd_global, &
    130        user_rrd_local, &
    131        user_wrd_global, &
    132        user_wrd_local, &
    133        user_last_actions
     117    PUBLIC                                                                                         &
     118       user_actions,                                                                               &
     119       user_check_data_output,                                                                     &
     120       user_check_data_output_pr,                                                                  &
     121       user_check_data_output_ts,                                                                  &
     122       user_check_parameters,                                                                      &
     123       user_data_output_2d,                                                                        &
     124       user_data_output_3d,                                                                        &
     125       user_define_netcdf_grid,                                                                    &
     126       user_header,                                                                                &
     127       user_init,                                                                                  &
     128       user_init_arrays,                                                                           &
     129       user_last_actions,                                                                          &
     130       user_parin,                                                                                 &
     131       user_rrd_global,                                                                            &
     132       user_rrd_local,                                                                             &
     133       user_statistics,                                                                            &
     134       user_3d_data_averaging,                                                                     &
     135       user_wrd_global,                                                                            &
     136       user_wrd_local
     137
    134138
    135139!
    136140!- Public parameters, constants and initial values
    137    PUBLIC &
     141   PUBLIC                                                                                          &
    138142      user_module_enabled
    139143
     
    220224
    221225
    222 !------------------------------------------------------------------------------!
     226!--------------------------------------------------------------------------------------------------!
    223227! Description:
    224228! ------------
    225229!> Parin for &user_parameters for user module
    226 !------------------------------------------------------------------------------!
     230!--------------------------------------------------------------------------------------------------!
    227231 SUBROUTINE user_parin
    228232
    229     CHARACTER (LEN=80) ::  line        !< string containing the last line read from namelist file
    230 
    231     INTEGER(iwp) ::  i                 !<
    232     INTEGER(iwp) ::  io_status         !< status after reading the namelist file
    233     INTEGER(iwp) ::  j                 !<
     233    CHARACTER (LEN=80) ::  line  !< string containing the last line read from namelist file
     234
     235    INTEGER(iwp) ::  i          !<
     236    INTEGER(iwp) ::  io_status  !< status after reading the namelist file
     237    INTEGER(iwp) ::  j          !<
    234238
    235239
     
    247251
    248252!
    249 !-- Set revision number of this default interface version. It will be checked within
    250 !-- the main program (palm). Please change the revision number in case that the
    251 !-- current revision does not match with previous revisions (e.g. if routines
    252 !-- have been added/deleted or if parameter lists in subroutines have been changed).
     253!-- Set revision number of this default interface version. It will be checked within the main
     254!-- program (palm). Please change the revision number in case that the current revision does not
     255!-- match with previous revisions (e.g. if routines have been added/deleted or if parameter lists
     256!-- in subroutines have been changed).
    253257    user_interface_current_revision = 'r4495'
    254258
    255259!
    256 !-- Position the namelist-file at the beginning (it was already opened in
    257 !-- parin), and try to read (find) a namelist named "user_parameters".
     260!-- Position the namelist-file at the beginning (it has already been opened in parin), and try to
     261!-- read (find) a namelist named "user_parameters".
    258262    REWIND ( 11 )
    259263    READ( 11, user_parameters, IOSTAT=io_status )
     
    278282
    279283!
    280 !-- Determine the number of user-defined profiles and append them to the
    281 !-- standard data output (data_output_pr)
     284!-- Determine the number of user-defined profiles and append them to the standard data output
     285!-- (data_output_pr)
    282286    IF ( user_module_enabled )  THEN
    283287       IF ( data_output_pr_user(1) /= ' ' )  THEN
     
    300304
    301305
    302 !------------------------------------------------------------------------------!
     306!--------------------------------------------------------------------------------------------------!
    303307! Description:
    304308! ------------
    305309!> Check &userpar control parameters and deduce further quantities.
    306 !------------------------------------------------------------------------------!
     310!--------------------------------------------------------------------------------------------------!
    307311 SUBROUTINE user_check_parameters
    308312
    309 
    310 !-- Here the user may add code to check the validity of further &userpar
    311 !-- control parameters or deduce further quantities.
     313!
     314!-- Here the user may add code to check the validity of further &userpar control parameters or
     315!-- deduce further quantities.
    312316
    313317
     
    315319
    316320
    317 !------------------------------------------------------------------------------!
     321!--------------------------------------------------------------------------------------------------!
    318322! Description:
    319323! ------------
    320324!> Set module-specific timeseries units and labels
    321 !------------------------------------------------------------------------------!
     325!--------------------------------------------------------------------------------------------------!
    322326 SUBROUTINE user_check_data_output_ts( dots_max, dots_num, dots_label, dots_unit )
    323327
    324 
    325     INTEGER(iwp),      INTENT(IN)     ::  dots_max
    326     INTEGER(iwp),      INTENT(INOUT)  ::  dots_num
    327     CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_label
    328     CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_unit
     328    INTEGER(iwp),      INTENT(IN)     ::  dots_max  !<
     329    INTEGER(iwp),      INTENT(INOUT)  ::  dots_num  !<
     330
     331    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_label  !<
     332    CHARACTER(LEN=*), DIMENSION(dots_max), INTENT(INOUT)  ::  dots_unit   !<
    329333
    330334!
     
    333337
    334338!
    335 !-- Sample for user-defined time series
    336 !-- For each time series quantity you have to give a label and a unit,
    337 !-- which will be used for the NetCDF file. They must not contain more than
    338 !-- seven characters. The value of dots_num has to be increased by the
    339 !-- number of new time series quantities. Its old value has to be store in
    340 !-- dots_num_palm. See routine user_statistics on how to output calculate
    341 !-- and output these quantities.
     339!-- Sample for user-defined time series:
     340!-- For each time series quantity you have to give a label and a unit, which will be used for the
     341!-- NetCDF file. They must not contain more than seven characters. The value of dots_num has to be
     342!-- increased by the number of new time series quantities. Its old value has to be stored in
     343!-- dots_num_palm. See routine user_statistics on how to calculate and output these quantities.
    342344
    343345!    dots_num_palm = dots_num
     
    357359
    358360
    359 !------------------------------------------------------------------------------!
    360 ! Description:
    361 ! ------------
    362 !> Set the unit of user defined profile output quantities. For those variables
    363 !> not recognized by the user, the parameter unit is set to "illegal", which
    364 !> tells the calling routine that the output variable is not defined and leads
    365 !> to a program abort.
    366 !------------------------------------------------------------------------------!
     361!--------------------------------------------------------------------------------------------------!
     362! Description:
     363! ------------
     364!> Set the unit of user defined profile output quantities. For those variables not recognized by the
     365!> user, the parameter unit is set to "illegal", which tells the calling routine that the
     366!> output variable is not defined and leads to a program abort.
     367!--------------------------------------------------------------------------------------------------!
    367368 SUBROUTINE user_check_data_output_pr( variable, var_count, unit, dopr_unit )
    368369
     
    371372
    372373
    373     CHARACTER (LEN=*) ::  unit     !<
    374     CHARACTER (LEN=*) ::  variable !<
     374    CHARACTER (LEN=*) ::  unit      !<
     375    CHARACTER (LEN=*) ::  variable  !<
    375376    CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    376377
    377 !    INTEGER(iwp) ::  user_pr_index !<
    378     INTEGER(iwp) ::  var_count     !<
     378!    INTEGER(iwp) ::  user_pr_index  !<
     379    INTEGER(iwp) ::  var_count      !<
    379380
    380381!
     
    386387!
    387388!--    Uncomment and extend the following lines, if necessary.
    388 !--    Add additional CASE statements depending on the number of quantities
    389 !--    for which profiles are to be calculated. The respective calculations
    390 !--    to be performed have to be added in routine user_statistics.
    391 !--    The quantities are (internally) identified by a user-profile-number
    392 !--    (see variable "user_pr_index" below). The first user-profile must be assigned
    393 !--    the number "pr_palm+1", the second one "pr_palm+2", etc. The respective
    394 !--    user-profile-numbers have also to be used in routine user_statistics!
    395 !       CASE ( 'u*v*' )                      ! quantity string as given in
    396 !                                            ! data_output_pr_user
     389!--    Add additional CASE statements depending on the number of quantities for which profiles are
     390!--    to be calculated. The respective calculations to be performed have to be added in routine
     391!--    user_statistics. The quantities are (internally) identified by a user-profile-number
     392!--    (see variable "user_pr_index" below). The first user-profile must be assigned the number
     393!--    "pr_palm+1", the second one "pr_palm+2", etc. The respective user-profile-numbers have also
     394!--    to be used in routine user_statistics!
     395!       CASE ( 'u*v*' )                      ! quantity string as given in data_output_pr_user
    397396!          user_pr_index = pr_palm + 1
    398397!          dopr_index(var_count)  = user_pr_index    ! quantities' user-profile-number
    399398!          dopr_unit = 'm2/s2'  ! quantity unit
    400399!          unit = dopr_unit
    401 !          hom(:,2,user_pr_index,:)       = SPREAD( zu, 2, statistic_regions+1 )
    402 !                                            ! grid on which the quantity is
    403 !                                            ! defined (use zu or zw)
     400!          hom(:,2,user_pr_index,:) = SPREAD( zu, 2, statistic_regions+1 )
     401!                                            ! grid on which the quantity is defined (use zu or zw)
     402!
    404403
    405404       CASE DEFAULT
     
    412411
    413412
    414 !------------------------------------------------------------------------------!
    415 ! Description:
    416 ! ------------
    417 !> Set the unit of user defined output quantities. For those variables
    418 !> not recognized by the user, the parameter unit is set to "illegal", which
    419 !> tells the calling routine that the output variable is not defined and leads
    420 !> to a program abort.
    421 !------------------------------------------------------------------------------!
     413!--------------------------------------------------------------------------------------------------!
     414! Description:
     415! ------------
     416!> Set the unit of user defined output quantities. For those variables not recognized by the user,
     417!> the parameter unit is set to "illegal", which tells the calling routine that the output variable
     418!> is not defined and leads to a program abort.
     419!--------------------------------------------------------------------------------------------------!
    422420 SUBROUTINE user_check_data_output( variable, unit )
    423421
    424422
    425     CHARACTER (LEN=*) ::  unit     !<
    426     CHARACTER (LEN=*) ::  variable !<
     423    CHARACTER (LEN=*) ::  unit      !<
     424    CHARACTER (LEN=*) ::  variable  !<
    427425
    428426
     
    446444
    447445
    448 !------------------------------------------------------------------------------!
     446!--------------------------------------------------------------------------------------------------!
    449447! Description:
    450448! ------------
    451449!> Initialize user-defined arrays
    452 !------------------------------------------------------------------------------!
     450!--------------------------------------------------------------------------------------------------!
    453451 SUBROUTINE user_init_arrays
    454452
     
    468466!     IF ( statistic_regions >= 1 )  THEN
    469467!        region = 1
    470 ! 
     468!
    471469!        rmask(:,:,region) = 0.0_wp
    472470!        DO  i = nxl, nxr
     
    479477!           ENDIF
    480478!        ENDDO
    481 ! 
     479!
    482480!     ENDIF
    483481
     
    485483
    486484
    487 !------------------------------------------------------------------------------!
     485!--------------------------------------------------------------------------------------------------!
    488486! Description:
    489487! ------------
    490488!> Execution of user-defined initializing actions
    491 !------------------------------------------------------------------------------!
     489!--------------------------------------------------------------------------------------------------!
    492490 SUBROUTINE user_init
    493491
    494492
    495 !    CHARACTER (LEN=20) :: field_char   !<
     493!    CHARACTER(LEN=20) :: field_char  !<
    496494!
    497495!-- Here the user-defined initializing actions follow:
     
    503501
    504502
    505 !------------------------------------------------------------------------------!
    506 ! Description:
    507 ! ------------
    508 !> Set the grids on which user-defined output quantities are defined.
    509 !> Allowed values for grid_x are "x" and "xu", for grid_y "y" and "yv", and
    510 !> for grid_z "zu" and "zw".
    511 !------------------------------------------------------------------------------!
     503!--------------------------------------------------------------------------------------------------!
     504! Description:
     505! ------------
     506!> Set the grids on which user-defined output quantities are defined. Allowed values for grid_x are
     507!> "x" and "xu", for grid_y "y" and "yv", and for grid_z "zu" and "zw".
     508!--------------------------------------------------------------------------------------------------!
    512509 SUBROUTINE user_define_netcdf_grid( variable, found, grid_x, grid_y, grid_z )
    513510
     
    551548
    552549
    553 !------------------------------------------------------------------------------!
     550!--------------------------------------------------------------------------------------------------!
    554551! Description:
    555552! ------------
    556553!> Print a header with user-defined information.
    557 !------------------------------------------------------------------------------!
     554!--------------------------------------------------------------------------------------------------!
    558555 SUBROUTINE user_header( io )
    559556
    560557
    561     INTEGER(iwp) ::  i    !<
    562     INTEGER(iwp) ::  io   !<
    563 
    564 !
    565 !-- If no user-defined variables are read from the namelist-file, no
    566 !-- information will be printed.
     558    INTEGER(iwp) ::  i   !<
     559    INTEGER(iwp) ::  io  !<
     560
     561!
     562!-- If no user-defined variables are read from the namelist-file, no information will be printed.
    567563    IF ( .NOT. user_module_enabled )  THEN
    568564       WRITE ( io, 100 )
     
    584580!-- Format-descriptors
    585581100 FORMAT (//' *** no user-defined variables found'/)
    586 110 FORMAT (//1X,78('#')                                                       &
    587             //' User-defined variables and actions:'/                          &
    588               ' -----------------------------------'//)
     582110 FORMAT (//1X,78('#') // ' User-defined variables and actions:' /                               &
     583            ' -----------------------------------'//)
    589584200 FORMAT (' Output of profiles and time series for following regions:' /)
    590585201 FORMAT (4X,'Region ',I1,':   ',A)
     
    594589
    595590
    596 !------------------------------------------------------------------------------!
     591!--------------------------------------------------------------------------------------------------!
    597592! Description:
    598593! ------------
    599594!> Call for all grid points
    600 !------------------------------------------------------------------------------!
     595!--------------------------------------------------------------------------------------------------!
    601596 SUBROUTINE user_actions( location )
    602597
    603598
    604     CHARACTER (LEN=*) ::  location !<
    605 
    606 !    INTEGER(iwp) ::  i !<
    607 !    INTEGER(iwp) ::  j !<
    608 !    INTEGER(iwp) ::  k !<
     599    CHARACTER(LEN=*) ::  location  !<
     600
     601!    INTEGER(iwp) ::  i  !<
     602!    INTEGER(iwp) ::  j  !<
     603!    INTEGER(iwp) ::  k  !<
    609604
    610605    CALL cpu_log( log_point(24), 'user_actions', 'start' )
    611606
    612607!
    613 !-- Here the user-defined actions follow
    614 !-- No calls for single grid points are allowed at locations before and
    615 !-- after the timestep, since these calls are not within an i,j-loop
     608!-- Here the user-defined actions follow. No calls for single grid points are allowed at locations
     609!-- before and after the timestep, since these calls are not within an i,j-loop
    616610    SELECT CASE ( location )
    617611
     
    626620       CASE ( 'after_integration' )
    627621!
    628 !--       Enter actions to be done after every time integration (before
    629 !--       data output)
     622!--       Enter actions to be done after every time integration (before data output)
    630623!--       Sample for user-defined output:
    631624!          DO  i = nxlg, nxrg
     
    640633!                DO  k = nzb, nzt+1
    641634!                   ustvst(k,j,i) =  &
    642 !                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) * &
     635!                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,0) ) *                      &
    643636!                      ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,0) )
    644637!                ENDDO
     
    688681
    689682
    690 !------------------------------------------------------------------------------!
     683!--------------------------------------------------------------------------------------------------!
    691684! Description:
    692685! ------------
    693686!> Call for grid point i,j
    694 !------------------------------------------------------------------------------!
     687!--------------------------------------------------------------------------------------------------!
    695688 SUBROUTINE user_actions_ij( i, j, location )
    696689
    697690
    698     CHARACTER (LEN=*) ::  location
    699 
    700     INTEGER(iwp) ::  i
    701     INTEGER(iwp) ::  j
     691    CHARACTER(LEN=*) ::  location  !<
     692
     693    INTEGER(iwp) ::  i  !<
     694    INTEGER(iwp) ::  j  !<
    702695
    703696!
     
    744737
    745738
    746 !------------------------------------------------------------------------------!
    747 ! Description:
    748 ! ------------
    749 !> Sum up and time-average user-defined output quantities as well as allocate
    750 !> the array necessary for storing the average.
    751 !------------------------------------------------------------------------------!
     739!--------------------------------------------------------------------------------------------------!
     740! Description:
     741! ------------
     742!> Sum up and time-average user-defined output quantities as well as allocate the array necessary
     743!> for storing the average.
     744!--------------------------------------------------------------------------------------------------!
    752745 SUBROUTINE user_3d_data_averaging( mode, variable )
    753746
    754747
    755     CHARACTER (LEN=*) ::  mode    !<
    756     CHARACTER (LEN=*) :: variable !<
    757 
    758 !    INTEGER(iwp) ::  i !<
    759 !    INTEGER(iwp) ::  j !<
    760 !    INTEGER(iwp) ::  k !<
     748    CHARACTER(LEN=*) ::  mode      !<
     749    CHARACTER(LEN=*) ::  variable  !<
     750
     751!    INTEGER(iwp) ::  i  !<
     752!    INTEGER(iwp) ::  j  !<
     753!    INTEGER(iwp) ::  k  !<
    761754
    762755    IF ( mode == 'allocate' )  THEN
     
    766759!
    767760!--       Uncomment and extend the following lines, if necessary.
    768 !--       The arrays for storing the user defined quantities (here u2_av) have
    769 !--       to be declared and defined by the user!
     761!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
     762!--       defined by the user!
    770763!--       Sample for user-defined output:
    771764!          CASE ( 'u2' )
     
    786779!
    787780!--       Uncomment and extend the following lines, if necessary.
    788 !--       The arrays for storing the user defined quantities (here u2 and
    789 !--       u2_av) have to be declared and defined by the user!
     781!--       The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     782!--       and defined by the user!
    790783!--       Sample for user-defined output:
    791784!          CASE ( 'u2' )
    792 !             IF ( ALLOCATED( u2_av ) ) THEN
     785!             IF ( ALLOCATED( u2_av ) )  THEN
    793786!                DO  i = nxlg, nxrg
    794787!                   DO  j = nysg, nyng
     
    811804!
    812805!--       Uncomment and extend the following lines, if necessary.
    813 !--       The arrays for storing the user defined quantities (here u2_av) have
    814 !--       to be declared and defined by the user!
     806!--       The arrays for storing the user defined quantities (here u2_av) have to be declared and
     807!--       defined by the user!
    815808!--       Sample for user-defined output:
    816809!          CASE ( 'u2' )
    817 !             IF ( ALLOCATED( u2_av ) ) THEN
     810!             IF ( ALLOCATED( u2_av ) )  THEN
    818811!                DO  i = nxlg, nxrg
    819812!                   DO  j = nysg, nyng
     
    833826
    834827
    835 !------------------------------------------------------------------------------!
    836 ! Description:
    837 ! ------------
    838 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    839 !> temporary array with indices (i,j,k) and sets the grid on which it is defined.
    840 !> Allowed values for grid are "zu" and "zw".
    841 !------------------------------------------------------------------------------!
     828!--------------------------------------------------------------------------------------------------!
     829! Description:
     830! ------------
     831!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
     832!> (i,j,k) and sets the grid on which it is defined. Allowed values for grid are "zu" and "zw".
     833!--------------------------------------------------------------------------------------------------!
    842834 SUBROUTINE user_data_output_2d( av, variable, found, grid, local_pf, two_d, nzb_do, nzt_do )
    843835
    844836
    845     CHARACTER (LEN=*) ::  grid     !<
    846     CHARACTER (LEN=*) ::  variable !<
    847 
    848     INTEGER(iwp) ::  av     !< flag to control data output of instantaneous or time-averaged data
    849 !    INTEGER(iwp) ::  i      !< grid index along x-direction
    850 !    INTEGER(iwp) ::  j      !< grid index along y-direction
    851 !    INTEGER(iwp) ::  k      !< grid index along z-direction
    852 !    INTEGER(iwp) ::  m      !< running index surface elements
    853     INTEGER(iwp) ::  nzb_do !< lower limit of the domain (usually nzb)
    854     INTEGER(iwp) ::  nzt_do !< upper limit of the domain (usually nzt+1)
    855 
    856     LOGICAL      ::  found !<
    857     LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
     837    CHARACTER(LEN=*) ::  grid      !<
     838    CHARACTER(LEN=*) ::  variable  !<
     839
     840    INTEGER(iwp) ::  av      !< flag to control data output of instantaneous or time-averaged data
     841!    INTEGER(iwp) ::  i       !< grid index along x-direction
     842!    INTEGER(iwp) ::  j       !< grid index along y-direction
     843!    INTEGER(iwp) ::  k       !< grid index along z-direction
     844!    INTEGER(iwp) ::  m       !< running index surface elements
     845    INTEGER(iwp) ::  nzb_do  !< lower limit of the domain (usually nzb)
     846    INTEGER(iwp) ::  nzt_do  !< upper limit of the domain (usually nzt+1)
     847
     848    LOGICAL      ::  found  !<
     849    LOGICAL      ::  two_d  !< flag parameter that indicates 2D variables (horizontal cross sections)
    858850
    859851!    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    860852
    861     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     853    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
    862854
    863855!
     
    872864!
    873865!--    Uncomment and extend the following lines, if necessary.
    874 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    875 !--    have to be declared and defined by the user!
     866!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     867!--    and defined by the user!
    876868!--    Sample for user-defined output:
    877869!       CASE ( 'u2_xy', 'u2_xz', 'u2_yz' )
     
    885877!             ENDDO
    886878!          ELSE
    887 !             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     879!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    888880!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    889881!                u2_av = REAL( fill_value, KIND = wp )
     
    900892!          grid = 'zu'
    901893!
    902 !--    In case two-dimensional surface variables are output, the user
    903 !--    has to access related surface-type. Uncomment and extend following lines
    904 !--    appropriately (example output of vertical surface momentum flux of u-
    905 !--    component). Please note, surface elements can be distributed over
    906 !--    several data type, depending on their respective surface properties.
     894!--    In case two-dimensional surface variables are output, the user has to access related
     895!--    surface-type. Uncomment and extend following lines appropriately (example output of vertical
     896!--    surface momentum flux of u-component). Please note, surface elements can be distributed over
     897!--    several data types, depending on their respective surface properties.
    907898!       CASE ( 'usws_xy' )
    908899!          IF ( av == 0 )  THEN
     
    931922!
    932923!          grid = 'zu'
    933 !--       
     924!--
    934925
    935926
     
    944935
    945936
    946 !------------------------------------------------------------------------------!
    947 ! Description:
    948 ! ------------
    949 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    950 !> temporary array with indices (i,j,k).
    951 !------------------------------------------------------------------------------!
     937!--------------------------------------------------------------------------------------------------!
     938! Description:
     939! ------------
     940!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with indices
     941!> (i,j,k).
     942!--------------------------------------------------------------------------------------------------!
    952943 SUBROUTINE user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
    953944
    954945
    955     CHARACTER (LEN=*) ::  variable !<
    956 
    957     INTEGER(iwp) ::  av    !<
    958 !    INTEGER(iwp) ::  i     !<
    959 !    INTEGER(iwp) ::  j     !<
    960 !    INTEGER(iwp) ::  k     !<
     946    CHARACTER(LEN=*) ::  variable  !<
     947
     948    INTEGER(iwp) ::  av     !<
     949!    INTEGER(iwp) ::  i      !<
     950!    INTEGER(iwp) ::  j      !<
     951!    INTEGER(iwp) ::  k      !<
    961952    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
    962953    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    963954
    964     LOGICAL      ::  found !<
    965 
    966 !    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    967 
    968     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     955    LOGICAL      ::  found  !<
     956
     957!    REAL(wp) ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
     958
     959    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf  !<
    969960
    970961!
     
    979970!
    980971!--    Uncomment and extend the following lines, if necessary.
    981 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    982 !--    have to be declared and defined by the user!
     972!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     973!--    and defined by the user!
    983974!--    Sample for user-defined output:
    984975!       CASE ( 'u2' )
     
    992983!             ENDDO
    993984!          ELSE
    994 !             IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     985!             IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    995986!                ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    996987!                u2_av = REAL( fill_value, KIND = wp )
     
    10151006
    10161007
    1017 !------------------------------------------------------------------------------!
    1018 ! Description:
    1019 ! ------------
    1020 !> Calculation of user-defined statistics, i.e. horizontally averaged profiles
    1021 !> and time series.
    1022 !> This routine is called for every statistic region sr defined by the user,
    1023 !> but at least for the region "total domain" (sr=0).
    1024 !> See section 3.5.4 on how to define, calculate, and output user defined
    1025 !> quantities.
    1026 !------------------------------------------------------------------------------!
     1008!--------------------------------------------------------------------------------------------------!
     1009! Description:
     1010! ------------
     1011!> Calculation of user-defined statistics, i.e. horizontally averaged profiles and time series.
     1012!> This routine is called for every statistic region sr defined by the user, but at least for the
     1013!> region "total domain" (sr=0). See section 3.5.4 on how to define, calculate, and output user
     1014!> defined quantities.
     1015!--------------------------------------------------------------------------------------------------!
    10271016 SUBROUTINE user_statistics( mode, sr, tn )
    10281017
    10291018
    1030     CHARACTER (LEN=*) ::  mode   !<
    1031 !    INTEGER(iwp) ::  i    !<
    1032 !    INTEGER(iwp) ::  j    !<
    1033 !    INTEGER(iwp) ::  k    !<
    1034     INTEGER(iwp) ::  sr   !<
    1035     INTEGER(iwp) ::  tn   !<
    1036 
    1037 !    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l   !<
     1019    CHARACTER(LEN=*) ::  mode  !<
     1020!    INTEGER(iwp) ::  i   !<
     1021!    INTEGER(iwp) ::  j   !<
     1022!    INTEGER(iwp) ::  k   !<
     1023    INTEGER(iwp) ::  sr  !<
     1024    INTEGER(iwp) ::  tn  !<
     1025
     1026!    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l  !<
    10381027
    10391028!
     
    10441033
    10451034!
    1046 !--    Sample on how to calculate horizontally averaged profiles of user-
    1047 !--    defined quantities. Each quantity is identified by the index
    1048 !--    "pr_palm+#" where "#" is an integer starting from 1. These
    1049 !--    user-profile-numbers must also be assigned to the respective strings
    1050 !--    given by data_output_pr_user in routine user_check_data_output_pr.
     1035!--    Sample on how to calculate horizontally averaged profiles of user-defined quantities. Each
     1036!--    quantity is identified by the index "pr_palm+#" where "#" is an integer starting from 1.
     1037!--    These user-profile-numbers must also be assigned to the respective strings given by
     1038!--    data_output_pr_user in routine user_check_data_output_pr.
    10511039!       !$OMP DO
    10521040!       DO  i = nxl, nxr
     
    10541042!             DO  k = nzb+1, nzt
    10551043!!
    1056 !!--             Sample on how to calculate the profile of the resolved-scale
    1057 !!--             horizontal momentum flux u*v*
    1058 !                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +             &
    1059 !                      ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *&
    1060 !                      ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) )  &
    1061 !                                     * rmask(j,i,sr)                          &
    1062 !                                     * MERGE( 1.0_wp, 0.0_wp,                 &
    1063 !                                              BTEST( wall_flags_total_0(k,j,i), 0 ) )
     1044!!--             Sample on how to calculate the profile of the resolved-scale horizontal momentum
     1045!!--             flux u*v*
     1046!                sums_l(k,pr_palm+1,tn) = sums_l(k,pr_palm+1,tn) +                                  &
     1047!                                         ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) - hom(k,1,1,sr) ) *  &
     1048!                                         ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) - hom(k,1,2,sr) ) *  &
     1049!                                         rmask(j,i,sr) * MERGE( 1.0_wp, 0.0_wp,                    &
     1050!                                         BTEST( wall_flags_total_0(k,j,i), 0 ) )
    10641051!!
    1065 !!--             Further profiles can be defined and calculated by increasing
    1066 !!--             the second index of array sums_l (replace ... appropriately)
    1067 !                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...           &
    1068 !                                         * rmask(j,i,sr)
     1052!!--             Further profiles can be defined and calculated by increasing the second index of
     1053!!--             array sums_l (replace ... appropriately)
     1054!                sums_l(k,pr_palm+2,tn) = sums_l(k,pr_palm+2,tn) + ...   * rmask(j,i,sr)
    10691055!             ENDDO
    10701056!          ENDDO
     
    10771063!
    10781064!--    Sample on how to add values for the user-defined time series quantities.
    1079 !--    These have to be defined before in routine user_init. This sample
    1080 !--    creates two time series for the absolut values of the horizontal
    1081 !--    velocities u and v.
     1065!--    These have to be defined before in routine user_init. This sample creates two time series for
     1066!--    the absolut values of the horizontal velocities u and v.
    10821067!       ts_value_l = 0.0_wp
    10831068!       ts_value_l(1) = ABS( u_max )
     
    10851070!
    10861071!--     Collect / send values to PE0, because only PE0 outputs the time series.
    1087 !--     CAUTION: Collection is done by taking the sum over all processors.
    1088 !--              You may have to normalize this sum, depending on the quantity
    1089 !--              that you like to calculate. For serial runs, nothing has to be
    1090 !--              done.
    1091 !--     HINT: If the time series value that you are calculating has the same
    1092 !--           value on all PEs, you can omit the MPI_ALLREDUCE call and
    1093 !--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
     1072!--     CAUTION: Collection is done by taking the sum over all processors. You may have to normalize
     1073!--              this sum, depending on the quantity that you like to calculate. For serial runs,
     1074!--              nothing has to be done.
     1075!--     HINT: If the time series value that you are calculating has the same value on all PEs, you
     1076!--           can omit the MPI_ALLREDUCE call and assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
    10941077!#if defined( __parallel )
    10951078!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1096 !       CALL MPI_ALLREDUCE( ts_value_l(1),                         &
    1097 !                           ts_value(dots_num_palm+1,sr),                        &
    1098 !                           dots_num_user, MPI_REAL, MPI_MAX, comm2d,   &
    1099 !                           ierr )
     1079!       CALL MPI_ALLREDUCE( ts_value_l(1), ts_value(dots_num_palm+1,sr), dots_num_user, MPI_REAL,   &
     1080!                           MPI_MAX, comm2d, ierr )
    11001081!#else
    11011082!       ts_value(dots_num_palm+1:dots_num_palm+dots_num_user,sr) = ts_value_l
     
    11071088
    11081089
    1109 !------------------------------------------------------------------------------!
     1090!--------------------------------------------------------------------------------------------------!
    11101091! Description:
    11111092! ------------
    11121093!> Read module-specific global restart data (Fortran binary format).
    1113 !------------------------------------------------------------------------------!
     1094!--------------------------------------------------------------------------------------------------!
    11141095 SUBROUTINE user_rrd_global_ftn( found )
    11151096
    11161097
    1117     LOGICAL, INTENT(OUT)  ::  found
     1098    LOGICAL, INTENT(OUT)  ::  found  !<
    11181099
    11191100
     
    11271108
    11281109       CASE DEFAULT
    1129  
     1110
    11301111          found = .FALSE.
    11311112
     
    11361117
    11371118
    1138 !------------------------------------------------------------------------------!
     1119!--------------------------------------------------------------------------------------------------!
    11391120! Description:
    11401121! ------------
    11411122!> Read module-specific global restart data (MPI-IO).
    1142 !------------------------------------------------------------------------------!
     1123!--------------------------------------------------------------------------------------------------!
    11431124 SUBROUTINE user_rrd_global_mpi
    11441125
     
    11491130
    11501131
    1151 !------------------------------------------------------------------------------!
    1152 ! Description:
    1153 ! ------------
    1154 !> Reading processor specific restart data from file(s) that has been defined
    1155 !> by the user.
    1156 !> Subdomain index limits on file are given by nxl_on_file, etc.
    1157 !> Indices nxlc, etc. indicate the range of gridpoints to be mapped from the
    1158 !> subdomain on file (f) to the subdomain of the current PE (c). They have been
    1159 !> calculated in routine rrd_local.
    1160 !------------------------------------------------------------------------------!
    1161  SUBROUTINE user_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,         &
    1162                             nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
    1163                             nysc, nys_on_file, tmp_3d, found )
     1132!--------------------------------------------------------------------------------------------------!
     1133! Description:
     1134! ------------
     1135!> Reading processor specific restart data from file(s) that has been defined by the user. Subdomain
     1136!> index limits on file are given by nxl_on_file, etc. Indices nxlc, etc. indicate the range of
     1137!> gridpoints to be mapped from the subdomain on file (f) to the subdomain of the current PE (c).
     1138!> They have been calculated in routine rrd_local.
     1139!--------------------------------------------------------------------------------------------------!
     1140 SUBROUTINE user_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,       &
     1141                            nyn_on_file, nysf, nysc, nys_on_file, tmp_3d, found )
    11641142
    11651143
     
    11791157    INTEGER(iwp) ::  nys_on_file     !<
    11801158
    1181     LOGICAL, INTENT(OUT)  ::  found
    1182 
    1183     REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
     1159    LOGICAL, INTENT(OUT)  ::  found  !<
     1160
     1161    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d  !<
    11841162
    11851163!
     
    11971175
    11981176       CASE ( 'u2_av' )
    1199 !          IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     1177!          IF ( .NOT. ALLOCATED( u2_av ) )  THEN
    12001178!               ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    12011179!          ENDIF
    12021180!          IF ( k == 1 )  READ ( 13 )  tmp_3d
    1203 !             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
    1204 !                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     1181!             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                    &
     1182!             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    12051183!
    12061184       CASE DEFAULT
     
    12131191
    12141192
    1215 !------------------------------------------------------------------------------!
    1216 ! Description:
    1217 ! ------------
    1218 !> Writes global and user-defined restart data into binary file(s) for restart
    1219 !> runs.
    1220 !------------------------------------------------------------------------------!
     1193!--------------------------------------------------------------------------------------------------!
     1194! Description:
     1195! ------------
     1196!> Writes global and user-defined restart data into binary file(s) for restart runs.
     1197!--------------------------------------------------------------------------------------------------!
    12211198 SUBROUTINE user_wrd_global
    12221199
     
    12351212
    12361213
    1237 !------------------------------------------------------------------------------!
    1238 ! Description:
    1239 ! ------------
    1240 !> Writes processor specific and user-defined restart data into binary file(s)
    1241 !> for restart runs.
    1242 !------------------------------------------------------------------------------!
     1214!--------------------------------------------------------------------------------------------------!
     1215! Description:
     1216! ------------
     1217!> Writes processor specific and user-defined restart data into binary file(s) for restart runs.
     1218!--------------------------------------------------------------------------------------------------!
    12431219 SUBROUTINE user_wrd_local
    12441220
     
    12621238
    12631239
    1264 !------------------------------------------------------------------------------!
     1240!--------------------------------------------------------------------------------------------------!
    12651241! Description:
    12661242! ------------
    12671243!> Execution of user-defined actions at the end of a job.
    1268 !------------------------------------------------------------------------------!
     1244!--------------------------------------------------------------------------------------------------!
    12691245 SUBROUTINE user_last_actions
    12701246
Note: See TracChangeset for help on using the changeset viewer.