Ignore:
Timestamp:
Oct 21, 2014 10:53:05 AM (9 years ago)
Author:
kanani
Message:

New:
---
Subroutine init_plant_canopy added to module plant_canopy_model_mod. (plant_canopy_model)
Alternative method for lad-profile construction added, also, new parameters added.
(header, package_parin, plant_canopy_model, read_var_list, write_var_list)
plant_canopy_model-dependency added to several subroutines. (Makefile)
New package/namelist canopy_par for canopy-related parameters added. (package_parin)

Changed:
---
Code structure of the plant canopy model changed, all canopy-model related code
combined to module plant_canopy_model_mod. (check_parameters, init_3d_model,
modules, timestep)
Module plant_canopy_model_mod added in USE-lists of some subroutines. (check_parameters,
header, init_3d_model, package_parin, read_var_list, user_init_plant_canopy, write_var_list)
Canopy initialization moved to new subroutine init_plant_canopy. (check_parameters,
init_3d_model, plant_canopy_model)
Calculation of canopy timestep-criterion removed, instead, the canopy
drag is now directly limited in the calculation of the canopy tendency terms.
(plant_canopy_model, timestep)
Some parameters renamed. (check_parameters, header, init_plant_canopy,
plant_canopy_model, read_var_list, write_var_list)
Unnecessary 3d-arrays removed. (init_plant_canopy, plant_canopy_model, user_init_plant_canopy)
Parameter checks regarding canopy initialization added. (check_parameters)
All canopy steering parameters moved from namelist inipar to canopy_par. (package_parin, parin)
Some redundant MPI communication removed. (init_plant_canopy)

Bugfix:
---
Missing KIND-attribute for REAL constant added. (check_parameters)
DO-WHILE-loop for lad-profile output restricted. (header)
Removed double-listing of use_upstream_for_tke in ONLY-list of module
control_parameters. (prognostic_equations)

File:
1 edited

Legend:

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

    r1483 r1484  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Changes due to new module structure of the plant canopy model:
     23!   module plant_canopy_model_mod and output for new canopy model parameters
     24!   (alpha_lad, beta_lad, lai_beta,...) added,
     25!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
     26!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff,
     27!   learde renamed leaf_area_density.
     28! Bugfix: DO-WHILE-loop for lad header information additionally restricted
     29! by maximum number of gradient levels (currently 10)
    2330!
    2431! Former revisions:
     
    165172
    166173    USE arrays_3d,                                                             &
    167         ONLY:  lad, pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
     174        ONLY:  pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
    168175       
    169176    USE control_parameters
     
    205212       
    206213    USE pegrid
     214
     215    USE plant_canopy_model_mod,                                                &
     216        ONLY:  alpha_lad, beta_lad, calc_beta_lad_profile, canopy_drag_coeff,  &
     217               canopy_mode, cthf, lad, lad_surface, lad_vertical_gradient,     &
     218               lad_vertical_gradient_level, lad_vertical_gradient_level_ind,   &
     219               lai_beta, leaf_scalar_exch_coeff, leaf_surface_conc, pch_index, &
     220               plant_canopy
    207221   
    208222    USE spectrum,                                                              &
     
    242256    CHARACTER (LEN=86) ::  coordinates         !:
    243257    CHARACTER (LEN=86) ::  gradients           !:
    244     CHARACTER (LEN=86) ::  learde              !:
     258    CHARACTER (LEN=86) ::  leaf_area_density   !:
    245259    CHARACTER (LEN=86) ::  slices              !:
    246260    CHARACTER (LEN=86) ::  temperatures        !:
     
    270284    INTEGER(iwp) ::  io        !:
    271285    INTEGER(iwp) ::  j         !:
     286    INTEGER(iwp) ::  k         !:
    272287    INTEGER(iwp) ::  l         !:
    273288    INTEGER(iwp) ::  ll        !:
    274289    INTEGER(iwp) ::  mpi_type  !:
    275290   
     291    REAL(wp) ::  canopy_height                    !: canopy height (in m)
    276292    REAL(wp) ::  cpuseconds_per_simulated_second  !:
    277293
     
    760776
    761777    IF ( plant_canopy )  THEN
    762 
    763        WRITE ( io, 280 ) canopy_mode, pch_index, drag_coefficient
     778   
     779       canopy_height = pch_index * dz
     780
     781       WRITE ( io, 280 )  canopy_mode, canopy_height, pch_index,               &
     782                          canopy_drag_coeff
    764783       IF ( passive_scalar )  THEN
    765           WRITE ( io, 281 ) scalar_exchange_coefficient,   &
    766                             leaf_surface_concentration
     784          WRITE ( io, 281 )  leaf_scalar_exch_coeff,                           &
     785                             leaf_surface_conc
    767786       ENDIF
    768787
    769788!
    770789!--    Heat flux at the top of vegetation
    771        WRITE ( io, 282 ) cthf
    772 
    773 !
    774 !--    Leaf area density profile
    775 !--    Building output strings, starting with surface value
    776        WRITE ( learde, '(F6.4)' )  lad_surface
    777        gradients = '------'
    778        slices = '     0'
    779        coordinates = '   0.0'
    780        i = 1
    781        DO  WHILE ( lad_vertical_gradient_level_ind(i) /= -9999 )
    782 
    783           WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
    784           learde = TRIM( learde ) // ' ' // TRIM( coor_chr )
    785 
    786           WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
    787           gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
    788 
    789           WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
    790           slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
    791 
    792           WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
    793           coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
    794 
    795           i = i + 1
    796        ENDDO
    797 
    798        WRITE ( io, 283 )  TRIM( coordinates ), TRIM( learde ), &
    799                           TRIM( gradients ), TRIM( slices )
    800 
    801     ENDIF
     790       WRITE ( io, 282 )  cthf
     791
     792!
     793!--    Leaf area density profile, calculated either from given vertical
     794!--    gradients or from beta probability density function.
     795       IF (  .NOT.  calc_beta_lad_profile )  THEN
     796
     797!--       Building output strings, starting with surface value
     798          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
     799          gradients = '------'
     800          slices = '     0'
     801          coordinates = '   0.0'
     802          i = 1
     803          DO  WHILE ( i < 11  .AND.  lad_vertical_gradient_level_ind(i) /= -9999 )
     804
     805             WRITE (coor_chr,'(F7.2)')  lad(lad_vertical_gradient_level_ind(i))
     806             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
     807 
     808             WRITE (coor_chr,'(F7.2)')  lad_vertical_gradient(i)
     809             gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
     810
     811             WRITE (coor_chr,'(I7)')  lad_vertical_gradient_level_ind(i)
     812             slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
     813
     814             WRITE (coor_chr,'(F7.1)')  lad_vertical_gradient_level(i)
     815             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
     816
     817             i = i + 1
     818          ENDDO
     819
     820          WRITE ( io, 283 )  TRIM( coordinates ), TRIM( leaf_area_density ),              &
     821                             TRIM( gradients ), TRIM( slices )
     822
     823       ELSE
     824       
     825          WRITE ( leaf_area_density, '(F6.4)' )  lad_surface
     826          coordinates = '   0.0'
     827         
     828          DO  k = 1, pch_index
     829
     830             WRITE (coor_chr,'(F7.2)')  lad(k)
     831             leaf_area_density = TRIM( leaf_area_density ) // ' ' // TRIM( coor_chr )
     832 
     833             WRITE (coor_chr,'(F7.1)')  zu(k)
     834             coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
     835
     836          ENDDO       
     837
     838          WRITE ( io, 284 ) TRIM( coordinates ), TRIM( leaf_area_density ), alpha_lad,    &
     839                            beta_lad, lai_beta
     840
     841       ENDIF 
     842
     843    ENDIF
     844
    802845
    803846!
     
    18361879              ' ------------------------------'// &
    18371880              ' Canopy mode: ', A / &
    1838               ' Canopy top: ',I4 / &
     1881              ' Canopy height: ',F6.2,'m (',I4,' grid points)' / &
    18391882              ' Leaf drag coefficient: ',F6.2 /)
    1840 281 FORMAT (/ ' Scalar_exchange_coefficient: ',F6.2 / &
     1883281 FORMAT (/ ' Scalar exchange coefficient: ',F6.2 / &
    18411884              ' Scalar concentration at leaf surfaces in kg/m**3: ',F6.2 /)
    18421885282 FORMAT (' Predefined constant heatflux at the top of the vegetation: ',F6.2,' K m/s')
     
    18461889              ' Gradient:            ',A,'  m**2/m**4'/ &
    18471890              ' Gridpoint:           ',A)
     1891284 FORMAT (//' Characteristic levels of the leaf area density and coefficients:'// &
     1892              ' Height:              ',A,'  m'/ &
     1893              ' Leaf area density:   ',A,'  m**2/m**3'/ &
     1894              ' Coefficient alpha: ',F6.2 / &
     1895              ' Coefficient beta: ',F6.2 / &
     1896              ' Leaf area index: ',F6.2,'  m**2/m**2' /)
    18481897               
    18491898300 FORMAT (//' Boundary conditions:'/ &
Note: See TracChangeset for help on using the changeset viewer.