Ignore:
Timestamp:
Jan 24, 2018 3:38:29 PM (6 years ago)
Author:
kanani
Message:

Added parameter check, reduced line length, some formatting

File:
1 edited

Legend:

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

    r2766 r2768  
    2525! -----------------
    2626! $Id$
     27! Added check for output quantity pcm_heatrate, some formatting
     28!
     29! 2766 2018-01-22 17:17:47Z kanani
    2730! Increased LEN of canopy mode to 30
    2831!
     
    194197    REAL(wp) ::  leaf_scalar_exch_coeff = 0.0_wp  !< canopy scalar exchange coeff.
    195198    REAL(wp) ::  leaf_surface_conc = 0.0_wp       !< leaf surface concentration
     199    REAL(wp) ::  lsc = 0.0_wp                     !< leaf surface concentration
    196200    REAL(wp) ::  lsec = 0.0_wp                    !< leaf scalar exchange coeff.
    197     REAL(wp) ::  lsc = 0.0_wp                     !< leaf surface concentration
    198201    REAL(wp) ::  prototype_lad                    !< prototype leaf area density for computing effective optical depth
    199202
     
    204207    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pre_lad        !< preliminary lad
    205208   
    206     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::                                 &
    207        pc_heating_rate                                    !< plant canopy heating rate
    208     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf !< cumulative lai for heatflux calc.
    209     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s      !< lad on scalar-grid
    210 
     209    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  cum_lai_hf       !< cumulative lai for heatflux calc.
     210    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  lad_s            !< lad on scalar-grid
     211    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pc_heating_rate  !< plant canopy heating rate
    211212
    212213    SAVE
     
    287288
    288289       CASE ( 'pcm_heatrate' )
     290          IF ( cthf == 0.0_wp )  THEN
     291             message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     292                              'res setting of parameter cthf /= 0.0'
     293             CALL message( 'pcm_check_data_output', 'PA1000', 1, 2, 0, 6, 0 )
     294          ENDIF
    289295          unit = 'K s-1'
    290296   
     
    323329          message_string = 'plant_canopy = .TRUE. requires a non-zero drag '// &
    324330                           'coefficient & given value is canopy_drag_coeff = 0.0'
    325           CALL message( 'check_parameters', 'PA0041', 1, 2, 0, 6, 0 )
     331          CALL message( 'pcm_check_parameters', 'PA0041', 1, 2, 0, 6, 0 )
    326332       ENDIF
    327333   
     
    331337                           'of the leaf area density profile requires '    //  &
    332338                           'both alpha_lad and beta_lad to be /= 9999999.9'
    333           CALL message( 'check_parameters', 'PA0118', 1, 2, 0, 6, 0 )
     339          CALL message( 'pcm_check_parameters', 'PA0118', 1, 2, 0, 6, 0 )
    334340       ENDIF
    335341   
     
    339345                           'a non-zero lai_beta, but given value is '      //  &
    340346                           'lai_beta = 0.0'
    341           CALL message( 'check_parameters', 'PA0119', 1, 2, 0, 6, 0 )
     347          CALL message( 'pcm_check_parameters', 'PA0119', 1, 2, 0, 6, 0 )
    342348       ENDIF
    343349
     
    349355                           'function for the construction of the leaf area '// &
    350356                           'density profile'
    351           CALL message( 'check_parameters', 'PA0120', 1, 2, 0, 6, 0 )
     357          CALL message( 'pcm_check_parameters', 'PA0120', 1, 2, 0, 6, 0 )
    352358       ENDIF
    353359
     
    355361          message_string = 'plant_canopy = .TRUE. requires cloud_scheme /=' // &
    356362                          ' seifert_beheng'
    357           CALL message( 'check_parameters', 'PA0360', 1, 2, 0, 6, 0 )
     363          CALL message( 'pcm_check_parameters', 'PA0360', 1, 2, 0, 6, 0 )
    358364       ENDIF
    359365!
     
    365371                           TRIM( coupling_char ) // ' requires ' //            &
    366372                           'canopy_mode = read_from_file_3d'
    367           CALL message( 'check_parameters', 'PA0999', 1, 2, 0, 6, 0 )
     373          CALL message( 'pcm_check_parameters', 'PA0999', 1, 2, 0, 6, 0 )
    368374       ENDIF
    369375
     
    844850!--    When using the urban surface model (USM), canopy heating (pc_heating_rate)
    845851!--    by radiation is calculated in the USM.
    846        IF ( cthf /= 0.0_wp  .AND. .NOT.  urban_surface)  THEN
     852       IF ( cthf /= 0.0_wp  .AND. .NOT.  urban_surface )  THEN
    847853
    848854          ALLOCATE( cum_lai_hf(nzb:nzt+1,nysg:nyng,nxlg:nxrg),                 &
Note: See TracChangeset for help on using the changeset viewer.