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

    r3233 r3241  
    2525! -----------------
    2626! $Id$
     27! unused variables removed
     28!
     29! 3233 2018-09-07 13:21:24Z schwenkel
    2730! Adapted for the use of cloud_droplets
    2831!
     
    565568                drho_l_lv,                              & !< (rho_l * l_v)**-1
    566569                exn,                                    & !< value of the Exner function
    567                 e_s = 0.0_wp,                           & !< saturation water vapour pressure
    568570                field_capacity = 9999999.9_wp,          & !< NAMELIST m_fc
    569571                f_shortwave_incoming = 9999999.9_wp,    & !< NAMELIST f_sw_in
     
    12571259    CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    12581260 
    1259     INTEGER(iwp) ::  user_pr_index !<
    12601261    INTEGER(iwp) ::  var_count     !<
    12611262
     
    24802481       INTEGER(iwp) ::  st                      !< soil-type index
    24812482       INTEGER(iwp) ::  n_soil_layers_total     !< temperature variable, stores the total number of soil layers + 4
    2482        INTEGER(iwp) ::  n_surf                  !< number of surface types of given surface element
    24832483
    24842484       REAL(wp), DIMENSION(:), ALLOCATABLE ::  bound, bound_root_fr  !< temporary arrays for storing index bounds
     
    64426442    REAL(wp), DIMENSION(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_2d   !<
    64436443
    6444     REAL(wp), DIMENSION(nzb_soil:nzt_soil+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
    6445 
    6446     REAL(wp), DIMENSION(nzb_soil:nzt_soil,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d2   !<
     6444    REAL(wp), DIMENSION(nzb_soil:nzt_soil,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
    64476445
    64486446    TYPE(surf_type_lsm), SAVE :: tmp_walltype_h_1d   !< temporary 1D array containing the respective surface variable stored on file, horizontal surfaces
     
    65546552                 ALLOCATE( m_soil_av(nzb_soil:nzt_soil,nysg:nyng,nxlg:nxrg) )
    65556553              ENDIF
    6556               IF ( k == 1 )  READ ( 13 )  tmp_3d2(:,:,:)
     6554              IF ( k == 1 )  READ ( 13 )  tmp_3d(:,:,:)
    65576555              m_soil_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
    6558                  tmp_3d2(nzb_soil:nzt_soil,nysf                                &
    6559                          -nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     6556                 tmp_3d(nzb_soil:nzt_soil,nysf                                 &
     6557                        -nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    65606558
    65616559           CASE ( 'qsws_liq_av' )
     
    65866584                 ALLOCATE( t_soil_av(nzb_soil:nzt_soil,nysg:nyng,nxlg:nxrg) )
    65876585              ENDIF
    6588               IF ( k == 1 )  READ ( 13 )  tmp_3d2(:,:,:)
     6586              IF ( k == 1 )  READ ( 13 )  tmp_3d(:,:,:)
    65896587              t_soil_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
    6590                  tmp_3d2(:,nysf-nbgp:nynf+nbgp,                                &
    6591                          nxlf-nbgp:nxrf+nbgp)
     6588                 tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    65926589
    65936590           CASE ( 'lsm_start_index_h', 'lsm_start_index_v'  )   
     
    70147011
    70157012       USE control_parameters,                                                 &
    7016            ONLY: g, kappa, message_string, molecular_viscosity
     7013           ONLY: g, message_string, molecular_viscosity
    70177014
    70187015       IMPLICIT NONE
Note: See TracChangeset for help on using the changeset viewer.