Ignore:
Timestamp:
Jun 25, 2020 9:53:58 AM (4 years ago)
Author:
raasch
Message:

further re-formatting to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4542 r4577  
    2424! -----------------
    2525! $Id$
     26! further re-formatting concerning Fortran parameter variables
     27!
     28! 4542 2020-05-19 15:45:12Z raasch
    2629! file re-formatted to follow the PALM coding standard
    2730!
     
    28842887    IMPLICIT NONE
    28852888
     2889    REAL(wp), PARAMETER ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
     2890
    28862891    CHARACTER (LEN=*), INTENT(INOUT) ::  grid       !< name of vertical grid
    28872892    CHARACTER (LEN=*), INTENT(IN)    ::  mode       !< either 'xy', 'xz' or 'yz'
     
    29022907    LOGICAL, INTENT(INOUT) ::  two_d   !< flag parameter that indicates 2D variables
    29032908                                       !<  (horizontal cross sections)
    2904 
    2905 
    2906     REAL(wp), PARAMETER ::  fill_value = -999.0_wp  !< value for the _FillValue attribute
    29072909
    29082910    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do), INTENT(INOUT) ::  local_pf !< local
     
    65316533       INTEGER(iwp) ::  j            !<
    65326534
    6533        REAL(wp)     ::  gamm         !<
    6534        REAL(wp)     ::  ser          !<
    6535        REAL(wp)     ::  tmp          !<
    6536        REAL(wp)     ::  x_gamm       !<
    6537        REAL(wp)     ::  xx           !<
    6538        REAL(wp)     ::  y_gamm       !<
    6539 
    6540 
    65416535       REAL(wp), PARAMETER  ::  stp = 2.5066282746310005_wp               !<
    65426536       REAL(wp), PARAMETER  ::  cof(6) = (/ 76.18009172947146_wp,                                  &
     
    65476541                                            -0.5395239384953E-5_wp /)     !<
    65486542
     6543       REAL(wp)     ::  gamm         !<
     6544       REAL(wp)     ::  ser          !<
     6545       REAL(wp)     ::  tmp          !<
     6546       REAL(wp)     ::  x_gamm       !<
     6547       REAL(wp)     ::  xx           !<
     6548       REAL(wp)     ::  y_gamm       !<
     6549
     6550
    65496551       x_gamm = xx
    65506552       y_gamm = x_gamm
Note: See TracChangeset for help on using the changeset viewer.