Ignore:
Timestamp:
Sep 12, 2018 3:02:00 PM (6 years ago)
Author:
raasch
Message:

various changes to avoid compiler warnings (mainly removal of unused variables)

File:
1 edited

Legend:

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

    r3065 r3241  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3065 2018-06-12 07:03:02Z Giersch
    2730! dz was replaced by the help of zw to allow for vertical stretching
    2831!
     
    314317 
    315318    USE control_parameters,                                                 &
    316         ONLY:  data_output, message_string, urban_surface
     319        ONLY:  message_string, urban_surface
    317320
    318321    IMPLICIT NONE
     
    671674
    672675       USE control_parameters,                                                 &
    673            ONLY: humidity, io_blocks, io_group, message_string, ocean,         &
    674                  passive_scalar, urban_surface
     676           ONLY: humidity, message_string, ocean, urban_surface
    675677
    676678       USE netcdf_data_input_mod,                                              &
     
    682684       IMPLICIT NONE
    683685
    684        CHARACTER(10) :: pct
    685        
    686686       INTEGER(iwp) ::  i   !< running index
    687        INTEGER(iwp) ::  ii  !< index       
    688687       INTEGER(iwp) ::  j   !< running index
    689688       INTEGER(iwp) ::  k   !< running index
     
    691690
    692691       REAL(wp) ::  int_bpdf        !< vertical integral for lad-profile construction
    693        REAL(wp) ::  dzh             !< vertical grid spacing in units of canopy height
    694692       REAL(wp) ::  gradient        !< gradient for lad-profile construction
    695693       REAL(wp) ::  canopy_height   !< canopy height for lad-profile construction
    696        REAL(wp) ::  pcv(nzb:nzt+1)  !<
    697        
     694
    698695!
    699696!--    Allocate one-dimensional arrays for the computation of the
     
    10991096   
    11001097       USE control_parameters,                                                 &
    1101            ONLY:  coupling_char, message_string, passive_scalar
     1098           ONLY:  coupling_char, message_string
    11021099
    11031100       USE indices,                                                            &
     
    11101107       INTEGER(iwp)                        ::  i, j      !< running index
    11111108       INTEGER(iwp)                        ::  nzp       !< number of vertical layers of plant canopy
    1112        INTEGER(iwp)                        ::  nzpltop   !<
    1113        INTEGER(iwp)                        ::  nzpl      !<
    11141109       
    11151110       REAL(wp), DIMENSION(:), ALLOCATABLE ::  col   !< vertical column of input data
Note: See TracChangeset for help on using the changeset viewer.