Ignore:
Timestamp:
Mar 26, 2018 9:39:22 AM (6 years ago)
Author:
maronga
Message:

renamed all Fortran NAMELISTS

File:
1 edited

Legend:

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

    r2920 r2932  
    2525! -----------------
    2626! $Id$
     27! renamed canopy_par to plant_canopy_parameters
     28!
     29! 2920 2018-03-22 11:22:01Z kanani
    2730! Move usm_lad_rma and prototype_lad to radiation_model (moh.hefny)
    2831!
     
    945948! Description:
    946949! ------------
    947 !> Parin for &canopy_par for plant canopy model
     950!> Parin for &plant_canopy_parameters for plant canopy model
    948951!------------------------------------------------------------------------------!
    949952    SUBROUTINE pcm_parin
    950953
    951954       USE control_parameters,                                                 &
    952            ONLY:  plant_canopy
     955           ONLY:  message_string, plant_canopy
    953956
    954957       IMPLICIT NONE
     
    956959       CHARACTER (LEN=80) ::  line  !< dummy string that contains the current line of the parameter file
    957960       
     961       NAMELIST /plant_canopy_parameters/                                      &
     962                                  alpha_lad, beta_lad, canopy_drag_coeff,      &
     963                                  canopy_mode, cthf,                           &
     964                                  lad_surface,                                 &
     965                                  lad_vertical_gradient,                       &
     966                                  lad_vertical_gradient_level,                 &
     967                                  lai_beta,                                    &
     968                                  leaf_scalar_exch_coeff,                      &
     969                                  leaf_surface_conc, pch_index
     970
    958971       NAMELIST /canopy_par/      alpha_lad, beta_lad, canopy_drag_coeff,      &
    959972                                  canopy_mode, cthf,                           &
     
    964977                                  leaf_scalar_exch_coeff,                      &
    965978                                  leaf_surface_conc, pch_index
    966        
     979                                  
    967980       line = ' '
    968981       
     
    971984       REWIND ( 11 )
    972985       line = ' '
    973        DO   WHILE ( INDEX( line, '&canopy_par' ) == 0 )
     986       DO   WHILE ( INDEX( line, '&plant_canopy_parameters' ) == 0 )
    974987          READ ( 11, '(A)', END=10 )  line
    975988       ENDDO
     
    978991!
    979992!--    Read user-defined namelist
    980        READ ( 11, canopy_par )
     993       READ ( 11, plant_canopy_parameters )
    981994
    982995!
    983996!--    Set flag that indicates that the radiation model is switched on
    984997       plant_canopy = .TRUE.
    985 
    986  10    CONTINUE
     998       
     999       GOTO 12
     1000!
     1001!--    Try to find old namelist
     1002 10    REWIND ( 11 )
     1003       line = ' '
     1004       DO   WHILE ( INDEX( line, '&canopy_par' ) == 0 )
     1005          READ ( 11, '(A)', END=12 )  line
     1006       ENDDO
     1007       BACKSPACE ( 11 )
     1008
     1009!
     1010!--    Read user-defined namelist
     1011       READ ( 11, canopy_par )
     1012
     1013       message_string = 'namelist canopy_par is deprecated and will be ' // &
     1014                     'removed in near future. Please &use namelist ' //     &
     1015                     'plant_canopy_parameters instead'
     1016       CALL message( 'pcm_parin', 'PA0487', 0, 1, 0, 6, 0 )
     1017       
     1018!
     1019!--    Set flag that indicates that the radiation model is switched on
     1020       plant_canopy = .TRUE.
     1021
     1022 12    CONTINUE
    9871023       
    9881024
Note: See TracChangeset for help on using the changeset viewer.