Changeset 3768 for palm/trunk/SOURCE


Ignore:
Timestamp:
Feb 27, 2019 2:35:58 PM (5 years ago)
Author:
raasch
Message:

variables commented out + statement added to avoid compiler warnings about unused variables

Location:
palm/trunk/SOURCE
Files:
16 edited

Legend:

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

    r3761 r3768  
    2525! -----------------
    2626! $Id$
     27! further variables moved to serial branch to avoid compiler warnings about unused variables
     28!
     29! 3761 2019-02-25 15:31:42Z raasch
    2730! variables moved to serial branch to avoid compiler warnings about unused variables
    2831!
     
    235238
    236239    USE control_parameters,                                                    &
    237         ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,                 &
    238                bc_dirichlet_s, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
    239                bc_radiation_s, bc_lr_cyc, bc_ns_cyc, bc_radiation_l,           &
    240                bc_radiation_n, bc_radiation_r, bc_radiation_s
     240        ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, bc_dirichlet_s, &
     241               bc_radiation_l, bc_radiation_n, bc_radiation_r, bc_radiation_s, &
     242               bc_radiation_l, bc_radiation_n, bc_radiation_r, bc_radiation_s
    241243       
    242244    USE cpulog,                                                                &
     
    247249    USE pegrid
    248250
     251#if ! defined( __parallel )
     252    USE control_parameters,                                                    &
     253        ONLY:  bc_lr_cyc, bc_ns_cyc
     254#endif
     255
    249256    IMPLICIT NONE
    250257
     
    371378
    372379    USE control_parameters,                                                    &
    373         ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,                 &
    374                bc_dirichlet_s, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
    375                bc_radiation_s, bc_lr_cyc, bc_ns_cyc, bc_radiation_l,          &
    376                bc_radiation_n, bc_radiation_r, bc_radiation_s, grid_level
     380        ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r, bc_dirichlet_s, &
     381               bc_radiation_l, bc_radiation_n, bc_radiation_r, bc_radiation_s, &
     382               bc_radiation_l, bc_radiation_n, bc_radiation_r, bc_radiation_s, &
     383               grid_level
    377384       
    378385    USE cpulog,                                                                &
     
    383390    USE pegrid
    384391
     392#if ! defined( __parallel )
     393    USE control_parameters,                                                    &
     394        ONLY:  bc_lr_cyc, bc_ns_cyc
     395#endif
     396
    385397    IMPLICIT NONE
    386398
  • palm/trunk/SOURCE/user_data_output_dvrp.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! variables commented + statement added to avoid compiler warnings about unused variables
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Error messages revised
    2831!
     
    7780    CHARACTER (LEN=*) ::  output_variable !<
    7881
    79     INTEGER(iwp) ::  i !<
    80     INTEGER(iwp) ::  j !<
    81     INTEGER(iwp) ::  k !<
     82!    INTEGER(iwp) ::  i !<
     83!    INTEGER(iwp) ::  j !<
     84!    INTEGER(iwp) ::  k !<
    8285
    8386    REAL(wp), DIMENSION(nxl_dvrp:nxr_dvrp+1,nys_dvrp:nyn_dvrp+1,nzb:nz_do3d) :: &
    8487              local_pf !<
     88
     89!
     90!-- Next line is to avoid compiler warning about unused variables. Please remove.
     91    IF ( local_pf(nxl_dvrp,nys_dvrp,nzb) == 0.0_wp )  CONTINUE
    8592
    8693!
  • palm/trunk/SOURCE/user_data_output_mask.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! variables commented + statement added to avoid compiler warnings about unused variables
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Add terrain-following output
    2831!
     
    7679
    7780    INTEGER(iwp) ::  av             !<
    78     INTEGER(iwp) ::  i              !<
    79     INTEGER(iwp) ::  j              !<
    80     INTEGER(iwp) ::  k              !<
    81     INTEGER(iwp) ::  topo_top_ind   !< k index of highest horizontal surface
     81!    INTEGER(iwp) ::  i              !<
     82!    INTEGER(iwp) ::  j              !<
     83!    INTEGER(iwp) ::  k              !<
     84!    INTEGER(iwp) ::  topo_top_ind   !< k index of highest horizontal surface
    8285
    8386    LOGICAL ::  found               !<
     
    8689       DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  &
    8790          local_pf   !<
     91
     92!
     93!-- Next line is to avoid compiler warning about unused variables. Please remove.
     94    IF ( av == 0  .OR.                                                                             &
     95         local_pf(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) == 0.0_wp )  CONTINUE
    8896
    8997
  • palm/trunk/SOURCE/user_dvrp_coltab.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! statement added to avoid compiler warning about unused variable
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    7174    CHARACTER (LEN=*) ::  variable   !<
    7275
     76!
     77!-- Next line is to avoid compiler warning about unused variables. Please remove.
     78    IF ( variable(1:1) == ' ' )  CONTINUE
     79
    7380
    7481!
  • palm/trunk/SOURCE/user_flight.f90

    r3684 r3768  
    2525! -----------------
    2626! $Id$
     27! unused variables commented out + statement added to avoid compiler warnings
     28!
     29! 3684 2019-01-20 20:20:58Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    5962    IMPLICIT NONE
    6063
    61     INTEGER(iwp) ::  i  !< index along x
    62     INTEGER(iwp) ::  j  !< index along y
    63     INTEGER(iwp) ::  k  !< index along z
     64!    INTEGER(iwp) ::  i  !< index along x
     65!    INTEGER(iwp) ::  j  !< index along y
     66!    INTEGER(iwp) ::  k  !< index along z
    6467    INTEGER(iwp) ::  id !< variable identifyer, according to the settings in user_init_flight
    6568       
    6669    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !< treated variable
     70
     71!
     72!-- Next line is to avoid compiler warning about unused variables. Please remove.
     73    IF ( id == 0  .OR.  var(nzb,nysg,nxlg) == 0.0_wp )  CONTINUE
    6774
    6875!
  • palm/trunk/SOURCE/user_init_3d_model.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! variables commented out to avoid compiler warnings about unused variables
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    7780    IMPLICIT NONE
    7881
    79     INTEGER(iwp) ::  l !< running index surface orientation
    80     INTEGER(iwp) ::  m !< running index surface elements
     82!    INTEGER(iwp) ::  l !< running index surface orientation
     83!    INTEGER(iwp) ::  m !< running index surface elements
    8184
    8285!
  • palm/trunk/SOURCE/user_init_flight.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! statements commented or added to avoid compiler warnings about unused variables
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    5154    USE kinds
    5255   
    53     USE netcdf_interface,                                                      &
    54         ONLY: dofl_label, dofl_unit
     56!    USE netcdf_interface,                                                      &
     57!        ONLY: dofl_label, dofl_unit
    5558   
    5659    USE user
     
    6467   
    6568    LOGICAL ::  init  !< variable to recognize initial call
     69
     70!
     71!-- Following statements are added to avoid compiler warnings about unused variables. Please remove.
     72    IF ( PRESENT( id )        )  CONTINUE
     73    IF ( PRESENT( k )         )  CONTINUE
     74    IF ( PRESENT( label_leg ) )  CONTINUE
     75
    6676!
    6777!-- Sample for user-defined flight-time series.
  • palm/trunk/SOURCE/user_init_grid.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! variables commented + statement added to avoid compiler warnings about unused variables
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! dz was replaced by dz(1)
    2831!
     
    8285    IMPLICIT NONE
    8386
    84     INTEGER(iwp)                                           ::  k_topo      !< topography top index
     87!    INTEGER(iwp)                                           ::  k_topo      !< topography top index
    8588    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d     !< 3D topography field
    8689
    87     REAL(wp) ::  h_topo !< user-defined topography height
     90!    REAL(wp) ::  h_topo !< user-defined topography height
     91
     92!
     93!-- Next line is to avoid compiler warning about unused variables. Please remove.
     94    IF ( topo_3d(nzb,nysg,nxlg) == 0 )  CONTINUE
     95
    8896
    8997!
  • palm/trunk/SOURCE/user_init_plant_canopy.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! unused variables commented out to avoid compiler warnings
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    8790    IMPLICIT NONE
    8891
    89     INTEGER(iwp) :: i   !< running index
    90     INTEGER(iwp) :: j   !< running index
     92!    INTEGER(iwp) :: i   !< running index
     93!    INTEGER(iwp) :: j   !< running index
    9194
    9295!
  • palm/trunk/SOURCE/user_init_radiation.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! unused variables commented out to avoid compiler warnings
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    6265    IMPLICIT NONE
    6366
    64     INTEGER(iwp) :: i   !< running index
    65     INTEGER(iwp) :: j   !< running index
     67!    INTEGER(iwp) :: i   !< running index
     68!    INTEGER(iwp) :: j   !< running index
    6669
    6770!
  • palm/trunk/SOURCE/user_init_urban_surface.f90

    r3655 r3768  
    2626! -----------------
    2727! $Id$
     28! unused variables commented out to avoid compiler warnings
     29!
     30! 3655 2019-01-07 16:51:22Z knoop
    2831! Corrected "Former revisions" section
    2932!
     
    5255    USE arrays_3d
    5356   
    54     USE control_parameters,                                                    &
    55         ONLY:  urban_surface
     57!    USE control_parameters,                                                    &
     58!        ONLY:  urban_surface
    5659   
    5760    USE indices
     
    6770    IMPLICIT NONE
    6871
    69     INTEGER(iwp) ::  i  !< grid index
    70     INTEGER(iwp) ::  j  !< grid index
    71     INTEGER(iwp) ::  m  !< running index on 1D wall-type grid
     72!    INTEGER(iwp) ::  i  !< grid index
     73!    INTEGER(iwp) ::  j  !< grid index
     74!    INTEGER(iwp) ::  m  !< running index on 1D wall-type grid
    7275
    7376!
  • palm/trunk/SOURCE/user_lpm_advec.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! variables commented + statement added to avoid compiler warnings about unused variables
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    8487    INTEGER(iwp) ::  jp   !< index of particle grid box, y-direction
    8588    INTEGER(iwp) ::  kp   !< index of particle grid box, z-direction
    86     INTEGER(iwp) ::  n    !< particle index
    87     INTEGER(iwp) ::  nb   !< index of sub-box particles are sorted in
     89!    INTEGER(iwp) ::  n    !< particle index
     90!    INTEGER(iwp) ::  nb   !< index of sub-box particles are sorted in
    8891
    89     INTEGER(iwp), DIMENSION(0:7)  ::  start_index !< start particle index for current sub-box
    90     INTEGER(iwp), DIMENSION(0:7)  ::  end_index   !< start particle index for current sub-box
     92!    INTEGER(iwp), DIMENSION(0:7)  ::  start_index !< start particle index for current sub-box
     93!    INTEGER(iwp), DIMENSION(0:7)  ::  end_index   !< start particle index for current sub-box
     94
     95!
     96!-- Next line is to avoid compiler warning about unused variables. Please remove.
     97    IF ( ip == 0  .OR.  jp == 0  .OR.  kp == 0 )  CONTINUE
    9198
    9299!
  • palm/trunk/SOURCE/user_lpm_init.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! unused variables commented out to avoid compiler warnings
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    7679    IMPLICIT NONE
    7780
    78     INTEGER(iwp) ::  ip   !<
    79     INTEGER(iwp) ::  jp   !<
    80     INTEGER(iwp) ::  kp   !<
    81     INTEGER(iwp) ::  n    !<
     81!    INTEGER(iwp) ::  ip   !<
     82!    INTEGER(iwp) ::  jp   !<
     83!    INTEGER(iwp) ::  kp   !<
     84!    INTEGER(iwp) ::  n    !<
    8285
    8386!
  • palm/trunk/SOURCE/user_lpm_set_attributes.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! unused variables commented out to avoid compiler warnings
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Corrected "Former revisions" section
    2831!
     
    6467 
    6568
    66     USE indices,                                                               &
    67         ONLY:  nxl, nxr, nys, nyn, nzb, nzt
     69!    USE indices,                                                               &
     70!        ONLY:  nxl, nxr, nys, nyn, nzb, nzt
    6871
    6972    USE kinds
     
    7578    IMPLICIT NONE
    7679
    77     INTEGER(iwp) ::  ip   !<
    78     INTEGER(iwp) ::  jp   !<
    79     INTEGER(iwp) ::  kp   !<
    80     INTEGER(iwp) ::  n    !<
     80!    INTEGER(iwp) ::  ip   !<
     81!    INTEGER(iwp) ::  jp   !<
     82!    INTEGER(iwp) ::  kp   !<
     83!    INTEGER(iwp) ::  n    !<
    8184
    8285!
  • palm/trunk/SOURCE/user_module.f90

    r3767 r3768  
    2525! -----------------
    2626! $Id$
     27! variables commented + statements added to avoid compiler warnings about unused variables
     28!
     29! 3767 2019-02-27 08:18:02Z raasch
    2730! unused variable for file index removed from rrd-subroutines parameter list
    2831!
     
    247250
    248251!
     252!-- Next statement is to avoid compiler warnings about unused variables. Please remove in case
     253!-- that you are using them.
     254    IF ( dots_num_palm == 0  .OR.  dots_num_user == 0  .OR.  user_idummy == 0  .OR.                &
     255         user_rdummy == 0.0_wp )  CONTINUE
     256
     257!
    249258!-- Set revision number of this default interface version. It will be checked within
    250259!-- the main program (palm). Please change the revision number in case that the
     
    325334
    326335
    327    INTEGER(iwp),      INTENT(IN)     ::  dots_max
    328    INTEGER(iwp),      INTENT(INOUT)  ::  dots_num
    329    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_label
    330    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_unit
    331 
    332 
     336    INTEGER(iwp),      INTENT(IN)     ::  dots_max
     337    INTEGER(iwp),      INTENT(INOUT)  ::  dots_num
     338    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_label
     339    CHARACTER (LEN=*), DIMENSION(dots_max), INTENT(INOUT)  :: dots_unit
     340
     341!
     342!-- Next line is to avoid compiler warning about unused variables. Please remove.
     343    IF ( dots_num == 0  .OR.  dots_label(1)(1:1) == ' '  .OR.  dots_unit(1)(1:1) == ' ' )  CONTINUE
     344
     345!
    333346!-- Sample for user-defined time series
    334347!-- For each time series quantity you have to give a label and a unit,
     
    373386    CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    374387
    375     INTEGER(iwp) ::  user_pr_index !<
    376     INTEGER(iwp) ::  var_count     !<
     388!    INTEGER(iwp) ::  user_pr_index !<
     389    INTEGER(iwp) ::  var_count     !<
     390
     391!
     392!-- Next line is to avoid compiler warning about unused variables. Please remove.
     393    IF ( unit(1:1) == ' '  .OR.  dopr_unit(1:1) == ' '  .OR.  var_count == 0 )  CONTINUE
    377394
    378395    SELECT CASE ( TRIM( variable ) )
     
    448465
    449466
    450     INTEGER(iwp) :: i       !< loop index
    451     INTEGER(iwp) :: j       !< loop index
    452     INTEGER(iwp) :: region  !< index for loop over statistic regions
     467!    INTEGER(iwp) :: i       !< loop index
     468!    INTEGER(iwp) :: j       !< loop index
     469!    INTEGER(iwp) :: region  !< index for loop over statistic regions
    453470
    454471!
     
    487504
    488505
    489     CHARACTER (LEN=20) :: field_char   !<
     506!    CHARACTER (LEN=20) :: field_char   !<
    490507!
    491508!-- Here the user-defined initializing actions follow:
     
    598615    CHARACTER (LEN=*) ::  location !<
    599616
    600     INTEGER(iwp) ::  i !<
    601     INTEGER(iwp) ::  j !<
    602     INTEGER(iwp) ::  k !<
     617!    INTEGER(iwp) ::  i !<
     618!    INTEGER(iwp) ::  j !<
     619!    INTEGER(iwp) ::  k !<
    603620
    604621    CALL cpu_log( log_point(24), 'user_actions', 'start' )
     
    688705
    689706
    690        CHARACTER (LEN=*) ::  location
    691 
    692        INTEGER(iwp) ::  i
    693        INTEGER(iwp) ::  idum
    694        INTEGER(iwp) ::  j
     707    CHARACTER (LEN=*) ::  location
     708
     709    INTEGER(iwp) ::  i
     710    INTEGER(iwp) ::  j
    695711
    696712!
     
    699715
    700716       CASE ( 'u-tendency' )
     717
     718!
     719!--       Next line is to avoid compiler warning about unused variables. Please remove.
     720          IF ( i == 0  .OR.  j == 0 )  CONTINUE
     721
    701722!
    702723!--       Enter actions to be done in the u-tendency term here
     
    752773    CHARACTER (LEN=*) :: variable !<
    753774
    754     INTEGER(iwp) ::  i !<
    755     INTEGER(iwp) ::  j !<
    756     INTEGER(iwp) ::  k !<
     775!    INTEGER(iwp) ::  i !<
     776!    INTEGER(iwp) ::  j !<
     777!    INTEGER(iwp) ::  k !<
    757778
    758779    IF ( mode == 'allocate' )  THEN
     
    843864
    844865    INTEGER(iwp) ::  av     !< flag to control data output of instantaneous or time-averaged data
    845     INTEGER(iwp) ::  i      !< grid index along x-direction
    846     INTEGER(iwp) ::  j      !< grid index along y-direction
    847     INTEGER(iwp) ::  k      !< grid index along z-direction
    848     INTEGER(iwp) ::  m      !< running index surface elements
     866!    INTEGER(iwp) ::  i      !< grid index along x-direction
     867!    INTEGER(iwp) ::  j      !< grid index along y-direction
     868!    INTEGER(iwp) ::  k      !< grid index along z-direction
     869!    INTEGER(iwp) ::  m      !< running index surface elements
    849870    INTEGER(iwp) ::  nzb_do !< lower limit of the domain (usually nzb)
    850871    INTEGER(iwp) ::  nzt_do !< upper limit of the domain (usually nzt+1)
     
    853874    LOGICAL      ::  two_d !< flag parameter that indicates 2D variables (horizontal cross sections)
    854875
    855     REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
     876!    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    856877
    857878    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     879
     880!
     881!-- Next line is to avoid compiler warning about unused variables. Please remove.
     882    IF ( av == 0  .OR.  local_pf(nxl,nys,nzb_do) == 0.0_wp  .OR.  two_d )  CONTINUE
    858883
    859884
     
    948973
    949974    INTEGER(iwp) ::  av    !<
    950     INTEGER(iwp) ::  i     !<
    951     INTEGER(iwp) ::  j     !<
    952     INTEGER(iwp) ::  k     !<
     975!    INTEGER(iwp) ::  i     !<
     976!    INTEGER(iwp) ::  j     !<
     977!    INTEGER(iwp) ::  k     !<
    953978    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
    954979    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
     
    956981    LOGICAL      ::  found !<
    957982
    958     REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
     983!    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    959984
    960985    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     986
     987!
     988!-- Next line is to avoid compiler warning about unused variables. Please remove.
     989    IF ( av == 0  .OR.  local_pf(nxl,nys,nzb_do) == 0.0_wp )  CONTINUE
    961990
    962991
     
    10171046
    10181047    CHARACTER (LEN=*) ::  mode   !<
    1019     INTEGER(iwp) ::  i    !<
    1020     INTEGER(iwp) ::  j    !<
    1021     INTEGER(iwp) ::  k    !<
     1048!    INTEGER(iwp) ::  i    !<
     1049!    INTEGER(iwp) ::  j    !<
     1050!    INTEGER(iwp) ::  k    !<
    10221051    INTEGER(iwp) ::  sr   !<
    10231052    INTEGER(iwp) ::  tn   !<
    10241053
    1025     REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l   !<
     1054!    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts_value_l   !<
     1055
     1056!
     1057!-- Next line is to avoid compiler warning about unused variables. Please remove.
     1058    IF ( sr == 0  .OR.  tn == 0 )  CONTINUE
    10261059
    10271060    IF ( mode == 'profiles' )  THEN
     
    10961129!> Reading global restart data that has been defined by the user.
    10971130!------------------------------------------------------------------------------!
    1098     SUBROUTINE user_rrd_global( found )
    1099 
    1100 
    1101        USE control_parameters,                                                 &
    1102            ONLY: length, restart_string
    1103 
    1104 
    1105        LOGICAL, INTENT(OUT)  ::  found
    1106 
    1107 
    1108        found = .TRUE.
    1109 
    1110 
    1111        SELECT CASE ( restart_string(1:length) )
    1112 
    1113           CASE ( 'global_paramter' )
    1114 !             READ ( 13 )  global_parameter
    1115 
    1116           CASE DEFAULT
     1131 SUBROUTINE user_rrd_global( found )
     1132
     1133
     1134    USE control_parameters,                                                 &
     1135        ONLY: length, restart_string
     1136
     1137
     1138    LOGICAL, INTENT(OUT)  ::  found
     1139
     1140
     1141    found = .TRUE.
     1142
     1143
     1144    SELECT CASE ( restart_string(1:length) )
     1145
     1146       CASE ( 'global_paramter' )
     1147!          READ ( 13 )  global_parameter
     1148
     1149       CASE DEFAULT
    11171150 
    1118              found = .FALSE.
    1119 
    1120        END SELECT
    1121 
    1122 
    1123     END SUBROUTINE user_rrd_global
     1151          found = .FALSE.
     1152
     1153    END SELECT
     1154
     1155
     1156 END SUBROUTINE user_rrd_global
    11241157
    11251158
     
    11341167!> calculated in routine rrd_local.
    11351168!------------------------------------------------------------------------------!
    1136     SUBROUTINE user_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,         &
    1137                                nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
    1138                                nysc, nys_on_file, tmp_3d, found )
    1139 
    1140 
    1141        INTEGER(iwp) ::  k               !<
    1142        INTEGER(iwp) ::  nxlc            !<
    1143        INTEGER(iwp) ::  nxlf            !<
    1144        INTEGER(iwp) ::  nxl_on_file     !<
    1145        INTEGER(iwp) ::  nxrc            !<
    1146        INTEGER(iwp) ::  nxrf            !<
    1147        INTEGER(iwp) ::  nxr_on_file     !<
    1148        INTEGER(iwp) ::  nync            !<
    1149        INTEGER(iwp) ::  nynf            !<
    1150        INTEGER(iwp) ::  nyn_on_file     !<
    1151        INTEGER(iwp) ::  nysc            !<
    1152        INTEGER(iwp) ::  nysf            !<
    1153        INTEGER(iwp) ::  nys_on_file     !<
    1154 
    1155        LOGICAL, INTENT(OUT)  ::  found
    1156 
    1157        REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
     1169 SUBROUTINE user_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,         &
     1170                            nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
     1171                            nysc, nys_on_file, tmp_3d, found )
     1172
     1173
     1174    INTEGER(iwp) ::  idum            !<
     1175    INTEGER(iwp) ::  k               !<
     1176    INTEGER(iwp) ::  nxlc            !<
     1177    INTEGER(iwp) ::  nxlf            !<
     1178    INTEGER(iwp) ::  nxl_on_file     !<
     1179    INTEGER(iwp) ::  nxrc            !<
     1180    INTEGER(iwp) ::  nxrf            !<
     1181    INTEGER(iwp) ::  nxr_on_file     !<
     1182    INTEGER(iwp) ::  nync            !<
     1183    INTEGER(iwp) ::  nynf            !<
     1184    INTEGER(iwp) ::  nyn_on_file     !<
     1185    INTEGER(iwp) ::  nysc            !<
     1186    INTEGER(iwp) ::  nysf            !<
     1187    INTEGER(iwp) ::  nys_on_file     !<
     1188
     1189    LOGICAL, INTENT(OUT)  ::  found
     1190
     1191    REAL(wp), DIMENSION(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp) :: tmp_3d   !<
     1192
     1193!
     1194!-- Next line is to avoid compiler warning about unused variables. Please remove.
     1195    idum = k + nxlc + nxlf + nxrc + nxrf + nync + nynf + nysc + nysf +                             &
     1196           INT( tmp_3d(nzb,nys_on_file,nxl_on_file) )
    11581197
    11591198!
     
    11611200!-- Sample for user-defined output
    11621201
    1163 
    1164        found = .TRUE.
    1165 
    1166 
    1167           SELECT CASE ( restart_string(1:length) )
    1168 
    1169              CASE ( 'u2_av' )
    1170 !                IF ( .NOT. ALLOCATED( u2_av ) ) THEN
    1171 !                     ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    1172 !                ENDIF
    1173 !                IF ( k == 1 )  READ ( 13 )  tmp_3d
    1174 !                   u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
    1175 !                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
    1176 !
    1177              CASE DEFAULT
    1178 
    1179                 found = .FALSE.
    1180 
    1181              END SELECT
    1182 
    1183 
    1184     END SUBROUTINE user_rrd_local
     1202    found = .TRUE.
     1203
     1204    SELECT CASE ( restart_string(1:length) )
     1205
     1206       CASE ( 'u2_av' )
     1207!          IF ( .NOT. ALLOCATED( u2_av ) ) THEN
     1208!               ALLOCATE( u2_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     1209!          ENDIF
     1210!          IF ( k == 1 )  READ ( 13 )  tmp_3d
     1211!             u2_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
     1212!                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
     1213!
     1214       CASE DEFAULT
     1215
     1216          found = .FALSE.
     1217
     1218    END SELECT
     1219
     1220 END SUBROUTINE user_rrd_local
    11851221
    11861222
     
    11911227!> runs.
    11921228!------------------------------------------------------------------------------!
    1193     SUBROUTINE user_wrd_global
    1194 
    1195 
    1196 !       CALL wrd_write_string( 'global_parameter' )
    1197 !       WRITE ( 14 )  global_parameter
    1198 
    1199 
    1200     END SUBROUTINE user_wrd_global   
     1229 SUBROUTINE user_wrd_global
     1230
     1231!    CALL wrd_write_string( 'global_parameter' )
     1232!    WRITE ( 14 )  global_parameter
     1233
     1234 END SUBROUTINE user_wrd_global
    12011235
    12021236
     
    12071241!> for restart runs.
    12081242!------------------------------------------------------------------------------!
    1209     SUBROUTINE user_wrd_local
    1210 
     1243 SUBROUTINE user_wrd_local
    12111244
    12121245!
    12131246!-- Here the user-defined actions at the end of a job follow.
    12141247!-- Sample for user-defined output:
    1215 !          IF ( ALLOCATED( u2_av ) )  THEN
    1216 !             CALL wrd_write_string( 'u2_av' ) 
    1217 !             WRITE ( 14 )  u2_av
    1218 !          ENDIF
    1219 
    1220 
    1221 
    1222     END SUBROUTINE user_wrd_local
     1248!    IF ( ALLOCATED( u2_av ) )  THEN
     1249!       CALL wrd_write_string( 'u2_av' )
     1250!       WRITE ( 14 )  u2_av
     1251!    ENDIF
     1252
     1253 END SUBROUTINE user_wrd_local
    12231254
    12241255
     
    12361267 END SUBROUTINE user_last_actions
    12371268
    1238 
    12391269 END MODULE user
  • palm/trunk/SOURCE/user_spectra.f90

    r3655 r3768  
    2525! -----------------
    2626! $Id$
     27! variables removed + statement added to avoid compiler warnings about unused variables
     28!
     29! 3655 2019-01-07 16:51:22Z knoop
    2730! Renamed output variables
    2831!
     
    9194    CHARACTER (LEN=*) ::  mode
    9295
    93     INTEGER(iwp) ::  i    !<
    94     INTEGER(iwp) ::  j    !<
    95     INTEGER(iwp) ::  k    !<
    9696    INTEGER(iwp) ::  m    !<
    9797    INTEGER(iwp) ::  pr   !<
    9898
     99
     100!
     101!-- Next line is to avoid compiler warning about unused variable. Please remove.
     102    IF ( pr == 0 )  CONTINUE
    99103
    100104!
Note: See TracChangeset for help on using the changeset viewer.