Ignore:
Timestamp:
Apr 17, 2018 10:27:57 AM (6 years ago)
Author:
kanani
Message:

Fixes for radiative transfer model

File:
1 edited

Legend:

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

    r2932 r2977  
    1919!
    2020! Current revisions:
    21 ! -----------------
     21! ------------------
    2222!
    2323!
     
    2525! -----------------
    2626! $Id$
     27! Implement changes from branch radiation (r2948-2971) with minor modifications,
     28! plus some formatting.
     29! (moh.hefny):
     30! Add plant canopy type to account for changes in LAD (based on the changes
     31! done by Resler & Pavel) and correct the error message to PALM Standard.
     32!
     33! 2932 2018-03-26 09:39:22Z maronga
    2734! renamed canopy_par to plant_canopy_parameters
    2835!
     
    213220    REAL(wp) ::  lad_vertical_gradient(10) = 0.0_wp              !< lad gradient
    214221    REAL(wp) ::  lad_vertical_gradient_level(10) = -9999999.9_wp !< lad-prof. levels (in m)
     222
     223    REAL(wp) ::  lad_type_coef(0:10) = 1.0_wp   !< multiplicative coeficients for particular types
     224                                                !< of plant canopy (e.g. deciduous tree during winter)
    215225
    216226    REAL(wp), DIMENSION(:), ALLOCATABLE ::  lad            !< leaf area density
     
    962972                                  alpha_lad, beta_lad, canopy_drag_coeff,      &
    963973                                  canopy_mode, cthf,                           &
    964                                   lad_surface,                                 &
     974                                  lad_surface, lad_type_coef,                  &
    965975                                  lad_vertical_gradient,                       &
    966976                                  lad_vertical_gradient_level,                 &
     
    971981       NAMELIST /canopy_par/      alpha_lad, beta_lad, canopy_drag_coeff,      &
    972982                                  canopy_mode, cthf,                           &
    973                                   lad_surface,                                 &
     983                                  lad_surface, lad_type_coef,                  &
    974984                                  lad_vertical_gradient,                       &
    975985                                  lad_vertical_gradient_level,                 &
     
    10341044!>
    10351045!> num_levels
    1036 !> dtype,x,y,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
    1037 !> dtype,x,y,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
    1038 !> dtype,x,y,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
     1046!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
     1047!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
     1048!> dtype,x,y,pctype,value(nzb),value(nzb+1), ... ,value(nzb+num_levels-1)
    10391049!> ...
    10401050!>
     
    10601070
    10611071       INTEGER(iwp)                        ::  dtype     !< type of input data (1=lad)
     1072       INTEGER(iwp)                        ::  pctype    !< type of plant canopy (deciduous,non-deciduous,...)
    10621073       INTEGER(iwp)                        ::  i, j      !< running index
    10631074       INTEGER(iwp)                        ::  nzp       !< number of vertical layers of plant canopy
     
    10731084!
    10741085!--    Open and read plant canopy input data
    1075        OPEN(152, file='PLANT_CANOPY_DATA_3D' // TRIM( coupling_char ),         &
    1076                  access='SEQUENTIAL', action='READ', status='OLD',             &
    1077                  form='FORMATTED', err=515)
    1078        READ(152, *, err=516, end=517) nzp   !< read first line = number of vertical layers
     1086       OPEN(152, FILE='PLANT_CANOPY_DATA_3D' // TRIM( coupling_char ),         &
     1087                 ACCESS='SEQUENTIAL', ACTION='READ', STATUS='OLD',             &
     1088                 FORM='FORMATTED', ERR=515)
     1089       READ(152, *, ERR=516, END=517) nzp   !< read first line = number of vertical layers
    10791090       
    1080        ALLOCATE(col(0:nzp-1))
     1091       ALLOCATE( col(0:nzp-1) )
    10811092
    10821093       DO
    1083           READ(152, *, err=516, end=517) dtype, i, j, col(:)
    1084           IF ( i < nxlg .or. i > nxrg .or. j < nysg .or. j > nyng ) CYCLE
    1085 
    1086              SELECT CASE (dtype)
    1087                 CASE( 1 )   !< leaf area density
    1088 !
    1089 !--                 This is just the pure canopy layer assumed to be grounded to
    1090 !--                 a flat domain surface. At locations where plant canopy sits
    1091 !--                 on top of any kind of topography, the vertical plant column
    1092 !--                 must be "lifted", which is done in SUBROUTINE pcm_tendency.
    1093                     lad_s(0:nzp-1, j, i) = col(0:nzp-1)
    1094                    
    1095                 CASE DEFAULT
    1096                    WRITE(message_string, '(a,i2,a)')   &
    1097                       'Unknown record type in file PLANT_CANOPY_DATA_3D: "', dtype, '"'
    1098                    CALL message( 'pcm_read_plant_canopy_3d', 'PA0530', 1, 2, 0, 6, 0 )
    1099              END SELECT
     1094          READ(152, *, ERR=516, END=517) dtype, i, j, pctype, col(:)
     1095          IF ( i < nxlg  .OR.  i > nxrg  .OR.  j < nysg  .OR.  j > nyng )  CYCLE
     1096         
     1097          SELECT CASE (dtype)
     1098             CASE( 1 )   !< leaf area density
     1099!
     1100!--             This is just the pure canopy layer assumed to be grounded to
     1101!--             a flat domain surface. At locations where plant canopy sits
     1102!--             on top of any kind of topography, the vertical plant column
     1103!--             must be "lifted", which is done in SUBROUTINE pcm_tendency.           
     1104                IF ( pctype < 0  .OR.  pctype > 10 )  THEN   !< incorrect plant canopy type
     1105                   WRITE( message_string, * ) 'Incorrect type of plant canopy. '   //  &
     1106                                              'Allowed values 0 <= pctype <= 10, ' //  &
     1107                                              'but pctype is ', pctype
     1108                   CALL message( 'pcm_read_plant_canopy_3d', 'PA0349', 1, 2, 0, 6, 0 )
     1109                ENDIF
     1110                lad_s(0:nzp-1,j,i) = col(0:nzp-1) * lad_type_coef(pctype)
     1111               
     1112             CASE DEFAULT
     1113                WRITE(message_string, '(a,i2,a)')   &
     1114                     'Unknown record type in file PLANT_CANOPY_DATA_3D: "', dtype, '"'
     1115                CALL message( 'pcm_read_plant_canopy_3d', 'PA0530', 1, 2, 0, 6, 0 )
     1116          END SELECT
    11001117       ENDDO
    11011118
     
    11071124
    11081125517    CLOSE(152)
    1109        DEALLOCATE(col)
     1126       DEALLOCATE( col )
    11101127       
    11111128       CALL exchange_horiz( lad_s, nbgp )
Note: See TracChangeset for help on using the changeset viewer.