Ignore:
Timestamp:
Aug 24, 2020 4:02:40 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4535 r4646  
    11!> @file gust_mod.f90
    2 !------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
    4 !
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
    9 !
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    13 !
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     2!--------------------------------------------------------------------------------------------------!
     3! This file is part of the PALM model system.
     4!
     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!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4535 2020-05-15 12:07:23Z raasch
    2729! bugfix for restart data format query
    28 ! 
     30!
    2931! 4517 2020-05-03 14:29:30Z raasch
    3032! added restart with MPI-IO for reading local arrays
    31 ! 
     33!
    3234! 4495 2020-04-13 20:11:20Z raasch
    3335! restart data handling with MPI-IO added
    34 ! 
     36!
    3537! 4360 2020-01-07 11:25:50Z suehring
    36 ! CASE statement for dummy variable u2_av in gust_rrd_local changed to avoid
    37 ! unintended interdependencies with user-defined variables
    38 ! 
     38! CASE statement for dummy variable u2_av in gust_rrd_local changed to avoid unintended
     39! interdependencies with user-defined variables
     40!
    3941! 3837 2019-03-28 16:55:58Z knoop
    4042! unused variable for file index removed from rrd-subroutines parameter list
    41 ! 
     43!
    4244! 3725 2019-02-07 10:11:02Z raasch
    4345! dummy statement modified to avoid compiler warnings about unused variables
    44 ! 
     46!
    4547! 3685 2019-01-21 01:02:11Z knoop
    4648! Some interface calls moved to module_interface + cleanup
    47 ! 
     49!
    4850! 3665 2019-01-10 08:28:24Z raasch
    4951! dummy statements added to avoid compiler warnings about unused variables
    50 ! 
     52!
    5153! 3655 2019-01-07 16:51:22Z knoop
    5254! Bugfix: domain bounds of local_pf corrected
    53 ! 
    54 ! 
     55!
     56!
    5557! Interfaces concerning data output updated
    56 ! 
    57 ! 
     58!
     59!
    5860! renamed gust_par to gust_parameters
    59 ! 
    60 ! 
     61!
     62!
    6163! Initial interface definition
    6264!
    63 ! 
     65!
    6466! Description:
    6567! ------------
     
    6769!>
    6870!> @todo This is just a dummy module. The actual module ist not released yet.
    69 !------------------------------------------------------------------------------!
     71!--------------------------------------------------------------------------------------------------!
    7072 MODULE gust_mod
    7173
     
    7375        ONLY:  restart_data_format_output
    7476
    75     USE indices,                                                               &
     77    USE indices,                                                                                   &
    7678        ONLY:  nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt
    7779
     
    9496!
    9597!-- Public functions
    96     PUBLIC &
    97        gust_parin, &
    98        gust_check_parameters, &
    99        gust_check_data_output_pr, &
    100        gust_check_data_output, &
    101        gust_init_arrays, &
    102        gust_init, &
    103        gust_define_netcdf_grid, &
    104        gust_header, &
    105        gust_actions, &
    106        gust_prognostic_equations, &
    107        gust_swap_timelevel, &
    108        gust_3d_data_averaging, &
    109        gust_data_output_2d, &
    110        gust_data_output_3d, &
    111        gust_statistics, &
    112        gust_rrd_global, &
    113        gust_wrd_global, &
    114        gust_rrd_local, &
     98    PUBLIC                                                                                         &
     99       gust_parin,                                                                                 &
     100       gust_check_parameters,                                                                      &
     101       gust_check_data_output_pr,                                                                  &
     102       gust_check_data_output,                                                                     &
     103       gust_init_arrays,                                                                           &
     104       gust_init,                                                                                  &
     105       gust_define_netcdf_grid,                                                                    &
     106       gust_header,                                                                                &
     107       gust_actions,                                                                               &
     108       gust_prognostic_equations,                                                                  &
     109       gust_swap_timelevel,                                                                        &
     110       gust_3d_data_averaging,                                                                     &
     111       gust_data_output_2d,                                                                        &
     112       gust_data_output_3d,                                                                        &
     113       gust_statistics,                                                                            &
     114       gust_rrd_global,                                                                            &
     115       gust_wrd_global,                                                                            &
     116       gust_rrd_local,                                                                             &
    115117       gust_wrd_local
    116118!
    117119!-- Public parameters, constants and initial values
    118     PUBLIC &
     120    PUBLIC                                                                                         &
    119121       gust_module_enabled
    120122
     
    203205
    204206
    205 !------------------------------------------------------------------------------!
     207!--------------------------------------------------------------------------------------------------!
    206208! Description:
    207209! ------------
    208210!> Parin for &gust_parameters for gust module
    209 !------------------------------------------------------------------------------!
     211!--------------------------------------------------------------------------------------------------!
    210212    SUBROUTINE gust_parin
    211213
     
    215217       CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter file
    216218
    217        NAMELIST /gust_parameters/  &
     219       NAMELIST /gust_parameters/                                                                  &
    218220          gust_module_enabled
    219221
     
    240242
    241243
    242 !------------------------------------------------------------------------------!
     244!--------------------------------------------------------------------------------------------------!
    243245! Description:
    244246! ------------
    245247!> Check parameters routine for gust module
    246 !------------------------------------------------------------------------------!
     248!--------------------------------------------------------------------------------------------------!
    247249    SUBROUTINE gust_check_parameters
    248250
     
    254256
    255257
    256 !------------------------------------------------------------------------------!
     258!--------------------------------------------------------------------------------------------------!
    257259! Description:
    258260! ------------
    259261!> Check data output of profiles for gust module
    260 !------------------------------------------------------------------------------!
     262!--------------------------------------------------------------------------------------------------!
    261263    SUBROUTINE gust_check_data_output_pr( variable, var_count, unit, dopr_unit )
    262264
     
    264266       IMPLICIT NONE
    265267
     268       CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    266269       CHARACTER (LEN=*) ::  unit      !<
    267270       CHARACTER (LEN=*) ::  variable  !<
    268        CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    269271
    270272       INTEGER(iwp) ::  var_count      !<
     
    276278    END SUBROUTINE gust_check_data_output_pr
    277279
    278 !------------------------------------------------------------------------------!
     280!--------------------------------------------------------------------------------------------------!
    279281! Description:
    280282! ------------
    281283!> Check data output for gust module
    282 !------------------------------------------------------------------------------!
     284!--------------------------------------------------------------------------------------------------!
    283285    SUBROUTINE gust_check_data_output( var, unit )
    284286
     
    296298
    297299
    298 !------------------------------------------------------------------------------!
     300!--------------------------------------------------------------------------------------------------!
    299301! Description:
    300302! ------------
    301303!> Allocate gust module arrays and define pointers
    302 !------------------------------------------------------------------------------!
     304!--------------------------------------------------------------------------------------------------!
    303305    SUBROUTINE gust_init_arrays
    304306
     
    310312
    311313
    312 !------------------------------------------------------------------------------!
     314!--------------------------------------------------------------------------------------------------!
    313315! Description:
    314316! ------------
    315317!> Initialization of the gust module
    316 !------------------------------------------------------------------------------!
     318!--------------------------------------------------------------------------------------------------!
    317319    SUBROUTINE gust_init
    318320
     
    324326
    325327
    326 !------------------------------------------------------------------------------!
     328!--------------------------------------------------------------------------------------------------!
    327329!
    328330! Description:
     
    330332!> Subroutine defining appropriate grid for netcdf variables.
    331333!> It is called out from subroutine netcdf.
    332 !------------------------------------------------------------------------------!
     334!--------------------------------------------------------------------------------------------------!
    333335    SUBROUTINE gust_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
    334336
     
    336338       IMPLICIT NONE
    337339
    338        CHARACTER (LEN=*), INTENT(IN)  ::  var         !<
    339        LOGICAL, INTENT(IN)           ::  found       !<
    340340       CHARACTER (LEN=*), INTENT(IN) ::  grid_x      !<
    341341       CHARACTER (LEN=*), INTENT(IN) ::  grid_y      !<
    342342       CHARACTER (LEN=*), INTENT(IN) ::  grid_z      !<
     343       CHARACTER (LEN=*), INTENT(IN) ::  var         !<
     344
     345       LOGICAL, INTENT(IN)           ::  found       !<
    343346
    344347!
     
    349352
    350353
    351 !------------------------------------------------------------------------------!
     354!--------------------------------------------------------------------------------------------------!
    352355! Description:
    353356! ------------
    354357!> Header output for gust module
    355 !------------------------------------------------------------------------------!
     358!--------------------------------------------------------------------------------------------------!
    356359    SUBROUTINE gust_header ( io )
    357360
     
    368371
    369372
    370 !------------------------------------------------------------------------------!
     373!--------------------------------------------------------------------------------------------------!
    371374! Description:
    372375! ------------
    373376!> Call for all grid points
    374 !------------------------------------------------------------------------------!
     377!--------------------------------------------------------------------------------------------------!
    375378    SUBROUTINE gust_actions( location )
    376379
     
    387390
    388391
    389 !------------------------------------------------------------------------------!
     392!--------------------------------------------------------------------------------------------------!
    390393! Description:
    391394! ------------
    392395!> Call for grid point i,j
    393 !------------------------------------------------------------------------------!
     396!--------------------------------------------------------------------------------------------------!
    394397    SUBROUTINE gust_actions_ij( i, j, location )
    395398
     
    409412
    410413
    411 !------------------------------------------------------------------------------!
     414!--------------------------------------------------------------------------------------------------!
    412415! Description:
    413416! ------------
    414417!> Call for all grid points
    415 !------------------------------------------------------------------------------!
     418!--------------------------------------------------------------------------------------------------!
    416419    SUBROUTINE gust_prognostic_equations()
    417420
     
    423426
    424427
    425 !------------------------------------------------------------------------------!
     428!--------------------------------------------------------------------------------------------------!
    426429! Description:
    427430! ------------
    428431!> Call for grid point i,j
    429 !------------------------------------------------------------------------------!
     432!--------------------------------------------------------------------------------------------------!
    430433    SUBROUTINE gust_prognostic_equations_ij( i, j, i_omp_start, tn )
    431434
    432435
    433436       INTEGER(iwp), INTENT(IN) ::  i            !< grid index in x-direction
     437       INTEGER(iwp), INTENT(IN) ::  i_omp_start  !< first loop index of i-loop in prognostic_equations
    434438       INTEGER(iwp), INTENT(IN) ::  j            !< grid index in y-direction
    435        INTEGER(iwp), INTENT(IN) ::  i_omp_start  !< first loop index of i-loop in prognostic_equations
    436439       INTEGER(iwp), INTENT(IN) ::  tn           !< task number of openmp task
    437440
     
    443446
    444447
    445 !------------------------------------------------------------------------------!
     448!--------------------------------------------------------------------------------------------------!
    446449! Description:
    447450! ------------
    448451!> Swapping of timelevels
    449 !------------------------------------------------------------------------------!
     452!--------------------------------------------------------------------------------------------------!
    450453    SUBROUTINE gust_swap_timelevel ( mod_count )
    451454
     
    462465
    463466
    464 !------------------------------------------------------------------------------!
     467!--------------------------------------------------------------------------------------------------!
    465468!
    466469! Description:
    467470! ------------
    468471!> Subroutine for averaging 3D data
    469 !------------------------------------------------------------------------------!
     472!--------------------------------------------------------------------------------------------------!
    470473    SUBROUTINE gust_3d_data_averaging( mode, variable )
    471474
     
    474477
    475478       CHARACTER (LEN=*) ::  mode    !<
    476        CHARACTER (LEN=*) :: variable !<
     479       CHARACTER (LEN=*) ::  variable !<
    477480
    478481!
     
    482485    END SUBROUTINE gust_3d_data_averaging
    483486
    484 !------------------------------------------------------------------------------!
     487!--------------------------------------------------------------------------------------------------!
    485488!
    486489! Description:
    487490! ------------
    488491!> Subroutine defining 2D output variables
    489 !------------------------------------------------------------------------------!
    490     SUBROUTINE gust_data_output_2d( av, variable, found, grid, mode, local_pf, &
    491                                     two_d, nzb_do, nzt_do, fill_value )
     492!--------------------------------------------------------------------------------------------------!
     493    SUBROUTINE gust_data_output_2d( av, variable, found, grid, mode, local_pf, two_d, nzb_do,      &
     494                                    nzt_do, fill_value )
    492495
    493496
     
    495498
    496499       CHARACTER (LEN=*), INTENT(INOUT) ::  grid       !< name of vertical grid
    497        CHARACTER (LEN=*), INTENT(IN) ::  mode       !< either 'xy', 'xz' or 'yz'
    498        CHARACTER (LEN=*), INTENT(IN) ::  variable   !< name of variable
     500       CHARACTER (LEN=*), INTENT(IN)    ::  mode       !< either 'xy', 'xz' or 'yz'
     501       CHARACTER (LEN=*), INTENT(IN)    ::  variable   !< name of variable
    499502
    500503       INTEGER(iwp), INTENT(IN) ::  av        !< flag for (non-)average output
     
    508511
    509512       REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do), INTENT(INOUT) ::  local_pf !< local
    510           !< array to which output data is resorted to
     513                                                                                      !< array to which output data is resorted to
    511514
    512515!
     
    519522
    520523
    521 !------------------------------------------------------------------------------!
     524!--------------------------------------------------------------------------------------------------!
    522525!
    523526! Description:
    524527! ------------
    525528!> Subroutine defining 3D output variables
    526 !------------------------------------------------------------------------------!
     529!--------------------------------------------------------------------------------------------------!
    527530    SUBROUTINE gust_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    528531
     
    550553
    551554
    552 !------------------------------------------------------------------------------!
     555!--------------------------------------------------------------------------------------------------!
    553556! Description:
    554557! ------------
    555558!> This routine computes profile and timeseries data for the gust module.
    556 !------------------------------------------------------------------------------!
     559!--------------------------------------------------------------------------------------------------!
    557560    SUBROUTINE gust_statistics( mode, sr, tn, dots_max )
    558561
     
    573576
    574577
    575 !------------------------------------------------------------------------------!
     578!--------------------------------------------------------------------------------------------------!
    576579! Description:
    577580! ------------
    578581!> Read module-specific global restart data (Fortran binary format).
    579 !------------------------------------------------------------------------------!
     582!--------------------------------------------------------------------------------------------------!
    580583    SUBROUTINE gust_rrd_global_ftn( found )
    581584
    582585
    583        USE control_parameters,                                                 &
     586       USE control_parameters,                                                                     &
    584587           ONLY: length, restart_string
    585588
     
    608611
    609612
    610 !------------------------------------------------------------------------------!
     613!--------------------------------------------------------------------------------------------------!
    611614! Description:
    612615! ------------
    613616!> Read module-specific global restart data (MPI-IO).
    614 !------------------------------------------------------------------------------!
     617!--------------------------------------------------------------------------------------------------!
    615618    SUBROUTINE gust_rrd_global_mpi
    616619
     
    622625
    623626
    624 !------------------------------------------------------------------------------!
     627!--------------------------------------------------------------------------------------------------!
    625628! Description:
    626629! ------------
    627630!> Read module-specific local restart data arrays (Fortran binary format).
    628 !------------------------------------------------------------------------------!
    629     SUBROUTINE gust_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,         &
    630                                    nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
    631                                    nysc, nys_on_file, tmp_2d, tmp_3d, found )
     631!--------------------------------------------------------------------------------------------------!
     632    SUBROUTINE gust_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,&
     633                                   nyn_on_file, nysf, nysc, nys_on_file, tmp_2d, tmp_3d, found )
    632634
    633635
     
    696698
    697699
    698 !------------------------------------------------------------------------------!
     700!--------------------------------------------------------------------------------------------------!
    699701! Description:
    700702! ------------
    701703!> Read module-specific local restart data arrays (MPI-IO).
    702 !------------------------------------------------------------------------------!
     704!--------------------------------------------------------------------------------------------------!
    703705    SUBROUTINE gust_rrd_local_mpi
    704706
     
    709711
    710712
    711 !------------------------------------------------------------------------------!
     713!--------------------------------------------------------------------------------------------------!
    712714! Description:
    713715! ------------
    714716!> This routine writes the respective restart data for the gust module.
    715 !------------------------------------------------------------------------------!
     717!--------------------------------------------------------------------------------------------------!
    716718    SUBROUTINE gust_wrd_global
    717719
     
    742744
    743745
    744 !------------------------------------------------------------------------------!
     746!--------------------------------------------------------------------------------------------------!
    745747! Description:
    746748! ------------
    747749!> This routine writes the respective restart data for the gust module.
    748 !------------------------------------------------------------------------------!
     750!--------------------------------------------------------------------------------------------------!
    749751    SUBROUTINE gust_wrd_local
    750752
Note: See TracChangeset for help on using the changeset viewer.