Changeset 3048 for palm


Ignore:
Timestamp:
May 29, 2018 12:59:03 PM (6 years ago)
Author:
gronemeier
Message:

add variable description

File:
1 edited

Legend:

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

    r3046 r3048  
    2020! Current revisions:
    2121! -----------------
    22 ! Error messages revised
     22!
    2323!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! add variable description
     28!
     29! 3046 2018-05-29 08:02:15Z Giersch
    2730! Error messages revised
    2831!
     
    712715    IMPLICIT NONE
    713716
    714     CHARACTER (LEN=1)   ::  sq                       !<
    715     CHARACTER (LEN=varnamelength)  ::  var           !<
    716     CHARACTER (LEN=7)   ::  unit                     !<
    717     CHARACTER (LEN=8)   ::  date                     !<
    718     CHARACTER (LEN=10)  ::  time                     !<
    719     CHARACTER (LEN=20)  ::  ensemble_string          !<
    720     CHARACTER (LEN=15)  ::  nest_string              !<
    721     CHARACTER (LEN=40)  ::  coupling_string          !<
    722     CHARACTER (LEN=100) ::  action                   !<
    723 
    724     INTEGER(iwp) ::  i                               !<
    725     INTEGER(iwp) ::  ilen                            !<
    726     INTEGER(iwp) ::  j                               !<
    727     INTEGER(iwp) ::  k                               !<
    728     INTEGER(iwp) ::  kk                              !<
    729     INTEGER(iwp) ::  netcdf_data_format_save         !<
    730     INTEGER(iwp) ::  position                        !<
     717    CHARACTER (LEN=varnamelength)  ::  var           !< variable name
     718    CHARACTER (LEN=7)   ::  unit                     !< unit of variable
     719    CHARACTER (LEN=8)   ::  date                     !< current date string
     720    CHARACTER (LEN=10)  ::  time                     !< current time string
     721    CHARACTER (LEN=20)  ::  ensemble_string          !< string containing number of ensemble member
     722    CHARACTER (LEN=15)  ::  nest_string              !< string containing id of nested domain
     723    CHARACTER (LEN=40)  ::  coupling_string          !< string containing type of coupling
     724    CHARACTER (LEN=100) ::  action                   !< flag string
     725
     726    INTEGER(iwp) ::  i                               !< loop index
     727    INTEGER(iwp) ::  ilen                            !< string length
     728    INTEGER(iwp) ::  j                               !< loop index
     729    INTEGER(iwp) ::  k                               !< loop index
     730    INTEGER(iwp) ::  kk                              !< loop index
     731    INTEGER(iwp) ::  netcdf_data_format_save         !< initial value of netcdf_data_format
     732    INTEGER(iwp) ::  position                        !< index position of string
    731733    INTEGER(iwp) ::  lsp                             !< running index for chem spcs.
    732734
    733     LOGICAL     ::  found                            !<
     735    LOGICAL     ::  found                            !< flag, true if output variable is already marked for averaging
    734736
    735737    REAL(wp)    ::  dt_spinup_max                    !< maximum spinup timestep in nested domains
    736     REAL(wp)    ::  dum                              !<
    737     REAL(wp)    ::  gradient                         !<
    738     REAL(wp)    ::  remote = 0.0_wp                  !<
     738    REAL(wp)    ::  dum                              !< dummy variable
     739    REAL(wp)    ::  gradient                         !< local gradient
     740    REAL(wp)    ::  remote = 0.0_wp                  !< MPI id of remote processor
    739741    REAL(wp)    ::  spinup_time_max                  !< maximum spinup time in nested domains
    740     REAL(wp)    ::  time_to_be_simulated_from_reference_point  !<
     742    REAL(wp)    ::  time_to_be_simulated_from_reference_point  !< time to be simulated from reference point
    741743
    742744
     
    36283630!--    Generate masks for masked data output
    36293631!--    Parallel netcdf output is not tested so far for masked data, hence
    3630 !--    netcdf_data_format is switched back to non-paralell output.
     3632!--    netcdf_data_format is switched back to non-parallel output.
    36313633       netcdf_data_format_save = netcdf_data_format
    36323634       IF ( netcdf_data_format > 4 )  THEN
     
    43564358       IMPLICIT NONE
    43574359
    4358        CHARACTER (LEN=1)   ::  sq                       !<
    4359        CHARACTER (LEN=*)   ::  bc_b
    4360        CHARACTER (LEN=*)   ::  bc_t
    4361        CHARACTER (LEN=*)   ::  err_nr_b
    4362        CHARACTER (LEN=*)   ::  err_nr_t
    4363 
    4364        INTEGER(iwp)        ::  ibc_b
    4365        INTEGER(iwp)        ::  ibc_t
     4360       CHARACTER (LEN=1)   ::  sq         !< name of scalar quantity
     4361       CHARACTER (LEN=*)   ::  bc_b       !< bottom boundary condition
     4362       CHARACTER (LEN=*)   ::  bc_t       !< top boundary condition
     4363       CHARACTER (LEN=*)   ::  err_nr_b   !< error number if bottom bc is unknown
     4364       CHARACTER (LEN=*)   ::  err_nr_t   !< error number if top bc is unknown
     4365
     4366       INTEGER(iwp)        ::  ibc_b      !< index for bottom boundary condition
     4367       INTEGER(iwp)        ::  ibc_t      !< index for top boundary condition
    43664368
    43674369!
     
    44064408!------------------------------------------------------------------------------!
    44074409
    4408     SUBROUTINE check_bc_scalars( sq, bc_b, ibc_b,                 &
    4409                                  err_nr_1, err_nr_2,       &
     4410    SUBROUTINE check_bc_scalars( sq, bc_b, ibc_b,                      &
     4411                                 err_nr_1, err_nr_2,                   &
    44104412                                 constant_flux, surface_initial_change )
    44114413
     
    44134415       IMPLICIT NONE
    44144416
    4415        CHARACTER (LEN=1)   ::  sq                       !<
    4416        CHARACTER (LEN=*)   ::  bc_b
    4417        CHARACTER (LEN=*)   ::  err_nr_1
    4418        CHARACTER (LEN=*)   ::  err_nr_2
    4419 
    4420        INTEGER(iwp)        ::  ibc_b
    4421 
    4422        LOGICAL             ::  constant_flux
    4423 
    4424        REAL(wp)            ::  surface_initial_change
     4417       CHARACTER (LEN=1)   ::  sq                       !< name of scalar quantity
     4418       CHARACTER (LEN=*)   ::  bc_b                     !< bottom boundary condition
     4419       CHARACTER (LEN=*)   ::  err_nr_1                 !< error number of first error
     4420       CHARACTER (LEN=*)   ::  err_nr_2                 !< error number of second error
     4421
     4422       INTEGER(iwp)        ::  ibc_b                    !< index of bottom boundary condition
     4423
     4424       LOGICAL             ::  constant_flux            !< flag for constant-flux layer
     4425
     4426       REAL(wp)            ::  surface_initial_change   !< value of initial change at the surface
    44254427
    44264428!
     
    44314433       IF ( .NOT. land_surface  .AND.  .NOT. large_scale_forcing )  THEN
    44324434          IF ( ibc_b == 0  .AND.  constant_flux )  THEN
    4433              message_string = 'boundary condition: bc_' // TRIM( sq ) // '_b ' //  &
    4434                               '= "' // TRIM( bc_b ) // '" is not allowed with ' // &
    4435                               'prescribed surface flux'
     4435             message_string = 'boundary condition: bc_' // TRIM( sq ) //       &
     4436                              '_b ' // '= "' // TRIM( bc_b ) //                &
     4437                              '" is not allowed with prescribed surface flux'
    44364438             CALL message( 'check_parameters', err_nr_1, 1, 2, 0, 6, 0 )
    44374439          ENDIF
Note: See TracChangeset for help on using the changeset viewer.