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/urban_surface_mod.f90

    r3223 r3241  
    2828! -----------------
    2929! $Id$
     30! unused variables removed
     31!
     32! 3223 2018-08-30 13:48:17Z suehring
    3033! Bugfix for commit 3222
    3134!
     
    406409    INTEGER(iwp) ::  pedestrian_category = 2         !< default category for wall surface in pedestrian zone
    407410    INTEGER(iwp) ::  roof_category = 2               !< default category for root surface
    408     REAL(wp)     ::  roughness_concrete = 0.001_wp   !< roughness length of average concrete surface
    409411!
    410412!-- Indices of input attributes for (above) ground floor level
     
    587589!-- arrays for time averages
    588590!-- Attention: the variable rad_net_av is also used in the 3d field variable in radiation_model_mod.f90. It may be better to rename it
    589     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  rad_net_av       !< average of rad_net_l
    590591    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  surfinsw_av      !< average of sw radiation falling to local surface including radiation from reflections
    591592    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  surfinlw_av      !< average of lw radiation falling to local surface including radiation from reflections
     
    599600    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  surfins_av       !< average of array of residua of sw radiation absorbed in surface after last reflection
    600601    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  surfinl_av       !< average of array of residua of lw radiation absorbed in surface after last reflection
    601     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  surfhf_av        !< average of total radiation flux incoming to minus outgoing from local surface 
    602     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_av       !< average of wghf_eb
    603     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wshf_eb_av       !< average of wshf_eb
    604     REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_wall_av        !< Average of t_wall
    605     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_green_av !< average of wghf_eb_green
    606     REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_green_av       !< Average of t_green
    607     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  wghf_eb_window_av !< average of wghf_eb_window
    608     REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  t_window_av      !< Average of t_window   
    609602   
    610603
     
    704697   
    705698#endif
    706     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_av          !< average of wall surface temperature (K)
    707     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_window_av   !< average of window surface temperature (K)
    708     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_green_av    !< average of green wall surface temperature (K)
    709     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET    :: t_surf_10cm_av    !< average of whole wall surface temperature (K)
    710 
    711 !-- Temporal tendencies for time stepping           
    712     REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_m       !< surface temperature tendency of wall (K)
    713     REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_window_m !< surface temperature tendency of window (K)
    714     REAL(wp), DIMENSION(:), ALLOCATABLE            :: tt_surface_green_m !< surface temperature tendency of green wall (K)
    715699
    716700!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    721705#if defined( __nopointer )
    722706    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h             !< Wall temperature (K)
    723     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_av          !< Average of t_wall
    724707    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_p           !< Prog. wall temperature (K)
    725708    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h           !< Window temperature (K)
    726     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_av        !< Average of t_window
    727709    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_p         !< Prog. window temperature (K)
    728710    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h            !< Green temperature (K)
    729     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_av         !< Average of t_green
    730711    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_p          !< Prog. green temperature (K)
    731712
    732713    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v             !< Wall temperature (K)
    733     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_av          !< Average of t_wall
    734714    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_p           !< Prog. wall temperature (K)
    735715    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v           !< Window temperature (K)
    736     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_av        !< Average of t_window
    737716    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_p         !< Prog. window temperature (K)
    738717    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v            !< Green temperature (K)
    739     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_av         !< Average of t_green
    740718    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_p          !< Prog. green temperature (K)
    741719#else
    742720    REAL(wp), DIMENSION(:,:), POINTER                :: t_wall_h, t_wall_h_p
    743     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_av, t_wall_h_1, t_wall_h_2
     721    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_wall_h_1, t_wall_h_2
    744722    REAL(wp), DIMENSION(:,:), POINTER                :: t_window_h, t_window_h_p
    745     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_av, t_window_h_1, t_window_h_2
     723    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_window_h_1, t_window_h_2
    746724    REAL(wp), DIMENSION(:,:), POINTER                :: t_green_h, t_green_h_p
    747     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_av, t_green_h_1, t_green_h_2
     725    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET    :: t_green_h_1, t_green_h_2
    748726
    749727    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_wall_v, t_wall_v_p
    750     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_av, t_wall_v_1, t_wall_v_2
     728    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_wall_v_1, t_wall_v_2
    751729    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_window_v, t_window_v_p
    752     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_av, t_window_v_1, t_window_v_2
     730    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_window_v_1, t_window_v_2
    753731    TYPE(t_wall_vertical), DIMENSION(:), POINTER   :: t_green_v, t_green_v_p
    754     TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_av, t_green_v_1, t_green_v_2
     732    TYPE(t_wall_vertical), DIMENSION(0:3), TARGET  :: t_green_v_1, t_green_v_2
    755733#endif
    756734
    757 !-- Wall temporal tendencies for time stepping
    758     REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_wall_m          !< t_wall prognostic array
    759     REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_window_m        !< t_window prognostic array
    760     REAL(wp), DIMENSION(:,:), ALLOCATABLE          :: tt_green_m         !< t_green prognostic array
    761 
     735!
    762736!-- Surface and material parameters classes (surface_type)
    763737!-- albedo, emissivity, lambda_surf, roughness, thickness, volumetric heat capacity, thermal conductivity
     
    12701244        IMPLICIT NONE
    12711245
    1272         CHARACTER (len=*), INTENT(IN) ::  mode
    1273         CHARACTER (len=*), INTENT(IN) :: variable
     1246        CHARACTER(LEN=*), INTENT(IN) ::  mode
     1247        CHARACTER(LEN=*), INTENT(IN) :: variable
    12741248 
    12751249        INTEGER(iwp)                                       :: i, j, k, l, m, ids, idsint, iwl, istat
    1276         CHARACTER (len=varnamelength)                      :: var, surfid
     1250        CHARACTER(LEN=varnamelength)                       :: var
    12771251        INTEGER(iwp), PARAMETER                            :: nd = 5
    1278         CHARACTER(len=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
     1252        CHARACTER(LEN=6), DIMENSION(0:nd-1), PARAMETER     :: dirname = (/ '_roof ', '_south', '_north', '_west ', '_east ' /)
    12791253        INTEGER(iwp), DIMENSION(0:nd-1), PARAMETER         :: dirint = (/ iup_u, isouth_u, inorth_u, iwest_u, ieast_u /)
    12801254
     
    24402414        INTEGER(iwp)                                           :: ids,idsint,idsidx,isurf,isvf,isurfs,isurflt
    24412415        INTEGER(iwp)                                           :: is,js,ks,i,j,k,iwl,istat, l, m
    2442         INTEGER(iwp)                                           :: k_topo    !< topography top index
    24432416
    24442417        dirstart = (/ startland, startwall, startwall, startwall, startwall /)
     
    36213594        INTEGER(iwp) ::  st                  !< dummy 
    36223595
    3623         REAL(wp)     ::  c, d, tin, twin
     3596        REAL(wp)     ::  c, tin, twin
    36243597        REAL(wp)     ::  ground_floor_level_l         !< local height of ground floor level
    36253598        REAL(wp)     ::  z_agl                        !< height above ground
     
    53485321                           naheatlayers,                                       &
    53495322                           pedestrian_category,                                &
    5350                            roughness_concrete,                                 &
    53515323                           read_wall_temp_3d,                                  &
    53525324                           roof_category,                                      &
     
    53665338                           naheatlayers,                                       &
    53675339                           pedestrian_category,                                &
    5368                            roughness_concrete,                                 &
    53695340                           read_wall_temp_3d,                                  &
    53705341                           roof_category,                                      &
     
    55745545           
    55755546       IMPLICIT NONE
    5576 
    5577        CHARACTER (LEN=1)  ::  dum              !< dummy to create correct string for reading input variable
    55785547
    55795548       INTEGER(iwp)       ::  l                !< index variable for surface type
     
    67586727        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
    67596728        REAL(wp), DIMENSION(1:14, nysg:nyng, nxlg:nxrg)       :: usm_val
    6760         INTEGER(iwp)                                          :: k, l, d, iw, jw, kw, it, ip, ii, ij, m
     6729        INTEGER(iwp)                                          :: k, l, iw, jw, kw, it, ip, ii, ij, m
    67616730        INTEGER(iwp)                                          :: i, j
    67626731        INTEGER(iwp)                                          :: nz, roof, dirwe, dirsn
     
    67696738        REAL(wp)                                              :: wealbedo2, wethick2, snalbedo2, snthick2
    67706739        REAL(wp)                                              :: wealbedo3, wethick3, snalbedo3, snthick3
    6771        
    6772         LOGICAL                                               ::  surfpar
    6773         LOGICAL                                               ::  urbsurf
    67746740
    67756741!
     
    73327298        IMPLICIT NONE
    73337299
    7334         INTEGER(iwp)                          :: i, j, k, l, d, m   !< running indices
     7300        INTEGER(iwp)                          :: i, j, k, l, m      !< running indices
    73357301       
    73367302        REAL(wp)                              :: stend              !< surface tendency
     
    78397805!> called out from subroutine swap_timelevel
    78407806!------------------------------------------------------------------------------!
    7841     SUBROUTINE usm_swap_timelevel ( mod_count )
     7807    SUBROUTINE usm_swap_timelevel( mod_count )
    78427808
    78437809       IMPLICIT NONE
    78447810
    7845        INTEGER(iwp), INTENT(IN) :: mod_count
    7846        INTEGER(iwp)             :: i
     7811       INTEGER(iwp), INTENT(IN) ::  mod_count
    78477812     
    78487813#if defined( __nopointer )
Note: See TracChangeset for help on using the changeset viewer.