Ignore:
Timestamp:
Dec 10, 2018 7:05:46 AM (5 years ago)
Author:
raasch
Message:

unused variables removed, abort renamed inifor_abort to avoid intrinsic problem in Fortran

File:
1 edited

Legend:

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

    r3593 r3614  
    2727! -----------------
    2828! $Id$
     29! unused variables removed
     30!
     31! 3593 2018-12-03 13:51:13Z kanani
    2932! Bugfix: additional tmrt_grid allocation in case bio_mrt not selected as ouput,
    3033! replace degree symbol by degree_C
     
    157160    LOGICAL ::  aver_v     = .FALSE.  !< switch: do v  averaging in this module?
    158161    LOGICAL ::  aver_w     = .FALSE.  !< switch: do w  averaging in this module?
    159     LOGICAL ::  aver_mrt   = .FALSE.  !< switch: do mrt averaging in this module?
    160162    LOGICAL ::  average_trigger_perct = .FALSE.  !< update averaged input on call to bio_perct?
    161163    LOGICAL ::  average_trigger_utci  = .FALSE.  !< update averaged input on call to bio_utci?
     
    10761078        ONLY: message_string
    10771079
    1078     USE netcdf_data_input_mod,                                                &
    1079         ONLY:  netcdf_data_input_uvem, uvem_projarea_f, uvem_radiance_f,      &
    1080                uvem_irradiance_f, uvem_integration_f, building_obstruction_f
     1080    USE netcdf_data_input_mod,                                                 &
     1081        ONLY:  netcdf_data_input_uvem
    10811082
    10821083    IMPLICIT NONE
     
    39303931
    39313932    USE indices,                                                                                                      &
    3932         ONLY:  nxlg, nxrg, nyng, nysg, nys, nyn, nxl, nxr
     3933        ONLY:  nys, nyn, nxl, nxr
    39333934   
    39343935   
     
    40344035!                                               
    40354036!                                               
    4036        DO  i = nxl, nxr    !nxlg, nxrg
    4037           DO  j = nys, nyn    !nysg, nyng
     4037       DO  i = nxl, nxr
     4038          DO  j = nys, nyn
    40384039!                   
    40394040! !--        extract obstruction from IBSET-Integer_Array ------------------'
Note: See TracChangeset for help on using the changeset viewer.