Ignore:
Timestamp:
Apr 30, 2020 4:29:59 PM (4 years ago)
Author:
suehring
Message:

Bugfix in plant-canopy model for output of averaged transpiration rate after a restart; Revise check for output for plant heating rate and rename error message number; Surface-data output: enable output of mixing ratio and passive scalar concentration at the surface; Surface-data input: Add possibility to prescribe surface sensible and latent heat fluxes via static input file

File:
1 edited

Legend:

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

    r4495 r4514  
    2727! -----------------
    2828! $Id$
     29! - Bugfix in output of pcm_heatrate_av in a restart run. In order to fix this,
     30!   pch_index is now output for a restart run. Therefore, define global restart
     31!   routines.
     32! - Error message number renamed and check for PA0505 revised in order to also
     33!   consider natural surfaces with plant-canopy.
     34!
     35! 4495 2020-04-13 20:11:20Z raasch
    2936! restart data handling with MPI-IO added
    3037!
     
    168175! @todo - precalculate constant terms in pcm_calc_transpiration_rate
    169176! @todo - unify variable names (pcm_, pc_, ...)
     177! @todo - get rid-off dependency on radiation model
    170178!------------------------------------------------------------------------------!
    171179 MODULE plant_canopy_model_mod
     
    187195              dz,                                                              &
    188196              humidity,                                                        &
     197              land_surface,                                                    &
    189198              length,                                                          &
    190199              message_string,                                                  &
     
    225234
    226235    USE restart_data_mpi_io_mod,                                                                   &
    227         ONLY:  wrd_mpi_io
     236        ONLY:  rrd_mpi_io,                                                                         &
     237               wrd_mpi_io
    228238
    229239    USE surface_mod,                                                           &
     
    294304           pcm_init,                                                          &
    295305           pcm_parin,                                                         &
     306           pcm_rrd_global,                                                    &
    296307           pcm_rrd_local,                                                     &
    297308           pcm_tendency,                                                      &
     309           pcm_wrd_global,                                                    &
    298310           pcm_wrd_local
    299311
     
    349361    END INTERFACE pcm_rrd_local
    350362
     363    INTERFACE pcm_rrd_global
     364       MODULE PROCEDURE pcm_rrd_global_ftn
     365       MODULE PROCEDURE pcm_rrd_global_mpi
     366    END INTERFACE pcm_rrd_global
     367
    351368    INTERFACE pcm_tendency
    352369       MODULE PROCEDURE pcm_tendency
     
    357374       MODULE PROCEDURE pcm_wrd_local
    358375    END INTERFACE pcm_wrd_local
     376
     377    INTERFACE pcm_wrd_global
     378       MODULE PROCEDURE pcm_wrd_global
     379    END INTERFACE pcm_wrd_global
    359380
    360381
     
    483504
    484505       CASE ( 'pcm_heatrate' )
    485           IF ( cthf == 0.0_wp  .AND. .NOT.  urban_surface )  THEN
    486              message_string = 'output of "' // TRIM( var ) // '" requi' //  &
     506!
     507!--       Output of heatrate can be only done if it is explicitely set by cthf,
     508!--       or parametrized by absorption of radiation. The latter, however, is
     509!--       only available if radiation_interactions are on. Note, these are
     510!--       enabled if land-surface or urban-surface is switched-on. Using
     511!--       radiation_interactions_on directly is not possible since it belongs
     512!--       to the radition_model, which in turn depends on the plant-canopy model,
     513!--       creating circular dependencies.
     514          IF ( cthf == 0.0_wp  .AND. (  .NOT.  urban_surface  .AND.             &
     515                                        .NOT.  land_surface ) )  THEN
     516             message_string = 'output of "' // TRIM( var ) // '" requi' //      &
    487517                              'res setting of parameter cthf /= 0.0'
    488              CALL message( 'pcm_check_data_output', 'PA1000', 1, 2, 0, 6, 0 )
     518             CALL message( 'pcm_check_data_output', 'PA0505', 1, 2, 0, 6, 0 )
    489519          ENDIF
    490520          unit = 'K s-1'
     
    16201650! Description:
    16211651! ------------
     1652!> Read module-specific global restart data (Fortran binary format).
     1653!------------------------------------------------------------------------------!
     1654    SUBROUTINE pcm_rrd_global_ftn( found )
     1655
     1656       LOGICAL, INTENT(OUT)  ::  found
     1657
     1658       found = .TRUE.
     1659
     1660       SELECT CASE ( restart_string(1:length) )
     1661
     1662          CASE ( 'pch_index' )
     1663             READ ( 13 )  pch_index
     1664
     1665          CASE DEFAULT
     1666
     1667             found = .FALSE.
     1668
     1669       END SELECT
     1670
     1671    END SUBROUTINE pcm_rrd_global_ftn
     1672
     1673!------------------------------------------------------------------------------!
     1674! Description:
     1675! ------------
     1676!> Read module-specific global restart data (MPI-IO).
     1677!------------------------------------------------------------------------------!
     1678    SUBROUTINE pcm_rrd_global_mpi
     1679
     1680       CALL rrd_mpi_io( 'pch_index', pch_index )
     1681
     1682    END SUBROUTINE pcm_rrd_global_mpi
     1683
     1684!------------------------------------------------------------------------------!
     1685! Description:
     1686! ------------
    16221687!> Subroutine reads local (subdomain) restart data
    16231688!------------------------------------------------------------------------------!
     
    24372502! Description:
    24382503! ------------
     2504!> Subroutine writes global restart data
     2505!------------------------------------------------------------------------------!
     2506    SUBROUTINE pcm_wrd_global
     2507
     2508       IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     2509
     2510          CALL wrd_write_string( 'pch_index' )
     2511          WRITE ( 14 )  pch_index
     2512
     2513       ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     2514
     2515          CALL wrd_mpi_io( 'pch_index', pch_index )
     2516
     2517       ENDIF
     2518
     2519    END SUBROUTINE pcm_wrd_global
     2520
     2521!------------------------------------------------------------------------------!
     2522! Description:
     2523! ------------
    24392524!> Subroutine writes local (subdomain) restart data
    24402525!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.