Changeset 2746


Ignore:
Timestamp:
Jan 15, 2018 12:06:04 PM (6 years ago)
Author:
suehring
Message:

Read information from statitic driver for resolved vegetation independently from land- or urban-surface model

Location:
palm/trunk/SOURCE
Files:
12 edited

Legend:

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

    r2743 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2743 2018-01-12 16:03:39Z suehring
    2730! In case of natural- and urban-type surfaces output surfaces fluxes in W/m2.
    2831!
     
    608611    USE pegrid
    609612    USE plant_canopy_model_mod,                                                &
    610         ONLY:  pcm_check_data_output, pcm_check_parameters, plant_canopy
     613        ONLY:  pcm_check_data_output, pcm_check_parameters
    611614
    612615    USE pmc_interface,                                                         &
  • palm/trunk/SOURCE/data_output_3d.f90

    r2718 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    190193        ONLY:  air_chemistry, cloud_physics, do3d, do3d_no, do3d_time_count,   &
    191194               io_blocks, io_group, land_surface, message_string,              &
    192                ntdim_3d, nz_do3d,                                              &
     195               ntdim_3d, nz_do3d,  plant_canopy,                               &
    193196               psolver, simulated_time, time_since_reference_point,            &
    194197               urban_surface, varnamelength
     
    220223
    221224    USE plant_canopy_model_mod,                                                &
    222         ONLY:  pcm_data_output_3d, plant_canopy
     225        ONLY:  pcm_data_output_3d
    223226       
    224227    USE radiation_model_mod,                                                   &
  • palm/trunk/SOURCE/header.f90

    r2718 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    405408
    406409    USE plant_canopy_model_mod,                                                &
    407         ONLY:  pcm_header, plant_canopy
     410        ONLY:  pcm_header
    408411
    409412    USE pmc_handle_communicator,                                               &
  • palm/trunk/SOURCE/init_3d_model.f90

    r2718 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    455458   
    456459    USE plant_canopy_model_mod,                                                &
    457         ONLY:  pcm_init, plant_canopy
     460        ONLY:  pcm_init
    458461
    459462    USE radiation_model_mod,                                                   &
  • palm/trunk/SOURCE/modules.f90

    r2742 r2746  
    2525! -----------------
    2626! $Id$
     27! +plant_canopy
     28!
     29! 2742 2018-01-12 14:59:47Z suehring
    2730! +tsurf_av
    2831!
     
    12681271    LOGICAL ::  outflow_s = .FALSE.                          !< south domain boundary has non-cyclic outflow?
    12691272    LOGICAL ::  passive_scalar = .FALSE.                     !< namelist parameter
     1273    LOGICAL ::  plant_canopy = .FALSE.                       !< switch for use of plant canopy model
    12701274    LOGICAL ::  precipitation = .FALSE.                      !< namelist parameter
    12711275    LOGICAL ::  random_heatflux = .FALSE.                    !< namelist parameter
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r2718 r2746  
    2525! -----------------
    2626! $Id$
     27! Read plant-canopy variables independently on land-surface model usage
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    497500       USE control_parameters,                                                 &
    498501           ONLY:  bc_lr_cyc, bc_ns_cyc, land_surface, message_string,          &
    499                   urban_surface
     502                  plant_canopy, urban_surface
    500503
    501504       USE indices,                                                            &
    502505           ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg
     506
    503507
    504508       IMPLICIT NONE
     
    525529!
    526530!--    If not static input file is available, skip this routine
    527        IF ( .NOT. input_pids_static )  RETURN 
    528 !
    529 !--    Moreover, skip routine if no land-surface or urban-surface module are
    530 !--    applied as no variable is used anyway. 
     531       IF ( .NOT. input_pids_static )  RETURN
     532!
     533!--    Read plant canopy variables.
     534       IF ( plant_canopy )  THEN
     535          DO  ii = 0, io_blocks-1
     536             IF ( ii == io_group )  THEN
     537#if defined ( __netcdf )
     538!
     539!--             Open file in read-only mode
     540                CALL open_read_file( TRIM( input_file_static ) //              &
     541                                     TRIM( coupling_char ) , id_surf )
     542!
     543!--             At first, inquire all variable names.
     544!--             This will be used to check whether an optional input variable
     545!--             exist or not.
     546                CALL inquire_num_variables( id_surf, num_vars )
     547
     548                ALLOCATE( var_names(1:num_vars) )
     549                CALL inquire_variable_names( id_surf, var_names )
     550
     551
     552!
     553!--             Read leaf area density - resolved vegetation
     554                IF ( check_existence( var_names, 'leaf_area_density' ) )  THEN
     555                   leaf_area_density_f%from_file = .TRUE.
     556                   CALL get_attribute( id_surf, char_fill,                     &
     557                                       leaf_area_density_f%fill,               &
     558                                       .FALSE., 'leaf_area_density' ) 
     559!
     560!--                Inquire number of vertical vegetation layer
     561                   CALL get_dimension_length( id_surf, leaf_area_density_f%nz, &
     562                                              'zlad' )
     563!           
     564!--                Allocate variable for leaf-area density
     565                   ALLOCATE( leaf_area_density_f%var(                          &
     566                                                   0:leaf_area_density_f%nz-1, &
     567                                                   nys:nyn,nxl:nxr) )
     568
     569                      DO  i = nxl, nxr
     570                         DO  j = nys, nyn
     571                            CALL get_variable( id_surf, 'leaf_area_density',   &
     572                                               i, j,                           &
     573                                               leaf_area_density_f%var(:,j,i) )
     574                         ENDDO
     575                      ENDDO
     576                ELSE
     577                   leaf_area_density_f%from_file = .FALSE.
     578                ENDIF
     579
     580!
     581!--             Read basal area density - resolved vegetation
     582                IF ( check_existence( var_names, 'basal_area_density' ) )  THEN
     583                   basal_area_density_f%from_file = .TRUE.
     584                   CALL get_attribute( id_surf, char_fill,                     &
     585                                       basal_area_density_f%fill,              &
     586                                       .FALSE., 'basal_area_density' ) 
     587!
     588!--                Inquire number of vertical vegetation layer
     589                   CALL get_dimension_length( id_surf,                         &
     590                                              basal_area_density_f%nz,         &
     591                                              'zlad' )
     592!           
     593!--                Allocate variable
     594                   ALLOCATE( basal_area_density_f%var(                         &
     595                                                  0:basal_area_density_f%nz-1, &
     596                                                  nys:nyn,nxl:nxr) )
     597
     598                   DO  i = nxl, nxr
     599                      DO  j = nys, nyn
     600                         CALL get_variable( id_surf, 'basal_area_density',     &
     601                                            i, j,                              &
     602                                            basal_area_density_f%var(:,j,i) )
     603                      ENDDO
     604                   ENDDO
     605                ELSE
     606                   basal_area_density_f%from_file = .FALSE.
     607                ENDIF
     608
     609!
     610!--             Read root area density - resolved vegetation
     611                IF ( check_existence( var_names, 'root_area_density_lad' ) )  THEN
     612                   root_area_density_lad_f%from_file = .TRUE.
     613                   CALL get_attribute( id_surf, char_fill,                     &
     614                                       root_area_density_lad_f%fill,           &
     615                                       .FALSE., 'root_area_density_lad' ) 
     616!
     617!--                Inquire number of vertical soil layers
     618                   CALL get_dimension_length( id_surf,                         &
     619                                              root_area_density_lad_f%nz,      &
     620                                              'zsoil' )
     621!           
     622!--                Allocate variable
     623                   ALLOCATE( root_area_density_lad_f%var                       &
     624                                               (0:root_area_density_lad_f%nz-1,&
     625                                                nys:nyn,nxl:nxr) )
     626
     627                   DO  i = nxl, nxr
     628                      DO  j = nys, nyn
     629                         CALL get_variable( id_surf, 'root_area_density_lad',  &
     630                                            i, j,                              &
     631                                            root_area_density_lad_f%var(:,j,i) )
     632                      ENDDO
     633                   ENDDO
     634                ELSE
     635                   root_area_density_lad_f%from_file = .FALSE.
     636                ENDIF
     637!
     638!--             Finally, close input file
     639                CALL close_input_file( id_surf )
     640#endif
     641             ENDIF
     642#if defined( __parallel )
     643             CALL MPI_BARRIER( comm2d, ierr )
     644#endif
     645          ENDDO
     646!
     647!--       Deallocate variable list. Will be re-allocated in case further
     648!--       variables are read from file.         
     649          IF ( ALLOCATED( var_names ) )  DEALLOCATE( var_names )
     650
     651       ENDIF
     652!
     653!--    Skip the following if no land-surface or urban-surface module are
     654!--    applied. This case, no one of the following variables is used anyway. 
    531655       IF (  .NOT. land_surface  .OR.  .NOT. urban_surface )  RETURN
    532656!
     
    544668
    545669!
    546 !--          At first, inquire all variable names.
     670!--          Inquire all variable names.
    547671!--          This will be used to check whether an optional input variable exist
    548672!--          or not.
     
    9531077                water_pars_f%from_file = .FALSE.
    9541078             ENDIF
    955 
    956 !
    957 !--          Read leaf area density - resolved vegetation
    958              IF ( check_existence( var_names, 'leaf_area_density' ) )  THEN
    959                 leaf_area_density_f%from_file = .TRUE.
    960                 CALL get_attribute( id_surf, char_fill,                        &
    961                                     leaf_area_density_f%fill,                  &
    962                                     .FALSE., 'leaf_area_density' ) 
    963 !
    964 !--             Inquire number of vertical vegetation layer
    965                 CALL get_dimension_length( id_surf, leaf_area_density_f%nz,    &
    966                                            'zlad' )
    967 !           
    968 !--             Allocate variable for leaf-area density
    969                 ALLOCATE( leaf_area_density_f%var(0:leaf_area_density_f%nz-1,  &
    970                                                   nys:nyn,nxl:nxr) )
    971 
    972                 DO  i = nxl, nxr
    973                    DO  j = nys, nyn
    974                       CALL get_variable( id_surf, 'leaf_area_density', i, j,   &
    975                                          leaf_area_density_f%var(:,j,i) )
    976                    ENDDO
    977                 ENDDO
    978              ELSE
    979                 leaf_area_density_f%from_file = .FALSE.
    980              ENDIF
    981 
    982 !
    983 !--          Read basal area density - resolved vegetation
    984              IF ( check_existence( var_names, 'basal_area_density' ) )  THEN
    985                 basal_area_density_f%from_file = .TRUE.
    986                 CALL get_attribute( id_surf, char_fill,                        &
    987                                     basal_area_density_f%fill,                 &
    988                                     .FALSE., 'basal_area_density' ) 
    989 !
    990 !--             Inquire number of vertical vegetation layer
    991                 CALL get_dimension_length( id_surf, basal_area_density_f%nz,   &
    992                                            'zlad' )
    993 !           
    994 !--             Allocate variable
    995                 ALLOCATE( basal_area_density_f%var(0:basal_area_density_f%nz-1,&
    996                                                    nys:nyn,nxl:nxr) )
    997 
    998                 DO  i = nxl, nxr
    999                    DO  j = nys, nyn
    1000                       CALL get_variable( id_surf, 'basal_area_density', i, j,  &
    1001                                          basal_area_density_f%var(:,j,i) )
    1002                    ENDDO
    1003                 ENDDO
    1004              ELSE
    1005                 basal_area_density_f%from_file = .FALSE.
    1006              ENDIF
    1007 
    1008 !
    1009 !--          Read root area density - resolved vegetation
    1010              IF ( check_existence( var_names, 'root_area_density_lad' ) )  THEN
    1011                 root_area_density_lad_f%from_file = .TRUE.
    1012                 CALL get_attribute( id_surf, char_fill,                        &
    1013                                     root_area_density_lad_f%fill,              &
    1014                                     .FALSE., 'root_area_density_lad' ) 
    1015 !
    1016 !--             Inquire number of vertical soil layers
    1017                 CALL get_dimension_length( id_surf, root_area_density_lad_f%nz,&
    1018                                            'zsoil' )
    1019 !           
    1020 !--             Allocate variable
    1021                 ALLOCATE( root_area_density_lad_f%var                          &
    1022                                             (0:root_area_density_lad_f%nz-1,   &
    1023                                              nys:nyn,nxl:nxr) )
    1024 
    1025                 DO  i = nxl, nxr
    1026                    DO  j = nys, nyn
    1027                       CALL get_variable( id_surf, 'root_area_density_lad', i, j,&
    1028                                          root_area_density_lad_f%var(:,j,i) )
    1029                    ENDDO
    1030                 ENDDO
    1031              ELSE
    1032                 root_area_density_lad_f%from_file = .FALSE.
    1033              ENDIF
    1034 
    10351079!
    10361080!--          Read root area density - parametrized vegetation
  • palm/trunk/SOURCE/netcdf_interface_mod.f90

    r2718 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    496499               mask_size_l, mask_i, mask_i_global, mask_j, mask_j_global,      &
    497500               mask_k_global, message_string, mid, ntdim_2d_xy,                &
    498                ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, prt_time_count,    &
    499                run_description_header, section, simulated_time,                &
     501               ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, plant_canopy,      &
     502               prt_time_count, run_description_header, section, simulated_time,&
    500503               simulated_time_at_begin, skip_time_data_output_av,              &
    501504               skip_time_do2d_xy, skip_time_do2d_xz, skip_time_do2d_yz,        &
     
    520523
    521524    USE plant_canopy_model_mod,                                                &
    522         ONLY:  pcm_define_netcdf_grid, plant_canopy
     525        ONLY:  pcm_define_netcdf_grid
    523526
    524527    USE profil_parameter,                                                      &
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r2718 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    175178
    176179    LOGICAL ::  calc_beta_lad_profile = .FALSE. !< switch for calc. of lad from beta func.
    177     LOGICAL ::  plant_canopy = .FALSE.          !< switch for use of canopy model
    178180    LOGICAL ::  usm_lad_rma = .TRUE.            !< use MPI RMA to access LAD for raytracing (instead of global array)
    179181
     
    218220!-- Public variables and constants
    219221    PUBLIC pc_heating_rate, canopy_mode, cthf, dt_plant_canopy, lad, lad_s,   &
    220            pch_index, plant_canopy, prototype_lad, usm_lad_rma
     222           pch_index, prototype_lad, usm_lad_rma
    221223           
    222224
     
    931933    SUBROUTINE pcm_parin
    932934
     935       USE control_parameters,                                                 &
     936           ONLY:  plant_canopy
    933937
    934938       IMPLICIT NONE
  • palm/trunk/SOURCE/prognostic_equations.f90

    r2719 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2719 2018-01-02 09:02:06Z maronga
    2730! Bugfix for last change.
    2831!
     
    282285               inflow_l, intermediate_timestep_count,                          &
    283286               intermediate_timestep_count_max, large_scale_forcing,           &
    284                large_scale_subsidence, microphysics_morrison, microphysics_seifert, &
    285                microphysics_sat_adjust, neutral, nudging, ocean, outflow_l,    &
    286                outflow_s, passive_scalar, prho_reference, prho_reference,      &
     287               large_scale_subsidence, microphysics_morrison,                  &
     288               microphysics_seifert, microphysics_sat_adjust, neutral, nudging,&
     289               ocean, outflow_l, outflow_s, passive_scalar, plant_canopy,      &
     290               prho_reference, prho_reference,                                 &
    287291               prho_reference, pt_reference, pt_reference, pt_reference,       &
    288292               scalar_advec, scalar_advec, simulated_time, sloping_surface,    &
     
    362366
    363367    USE plant_canopy_model_mod,                                                &
    364         ONLY:  cthf, plant_canopy, pcm_tendency
     368        ONLY:  cthf, pcm_tendency
    365369
    366370    USE radiation_model_mod,                                                   &
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r2724 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2724 2018-01-05 12:12:38Z maronga
    2730! Set default of average_radiation to .FALSE.
    2831!
     
    235238               initializing_actions, io_blocks, io_group,                      &
    236239               latitude, longitude, large_scale_forcing, lsf_surf,             &
    237                message_string, microphysics_morrison, pt_surface,              &
     240               message_string, microphysics_morrison, plant_canopy, pt_surface,&
    238241               rho_surface, surface_pressure, time_since_reference_point
    239242
     
    268271
    269272    USE plant_canopy_model_mod,                                                &
    270         ONLY:  plant_canopy, pc_heating_rate, lad_s, usm_lad_rma
     273        ONLY:  pc_heating_rate, lad_s, usm_lad_rma
    271274
    272275    USE pegrid
     
    44234426
    44244427       USE plant_canopy_model_mod,                                             &     
    4425            ONLY:  plant_canopy, pch_index,                                     &
    4426                   pc_heating_rate, lad_s, prototype_lad, usm_lad_rma       
     4428           ONLY:  pch_index, pc_heating_rate, lad_s, prototype_lad, usm_lad_rma       
    44274429       
    44284430       IMPLICIT NONE
  • palm/trunk/SOURCE/turbulence_closure_mod.f90

    r2718 r2746  
    2525! -----------------
    2626! $Id$
     27! Move flag plant canopy to modules
     28!
     29! 2718 2018-01-02 08:49:38Z maronga
    2730! Corrected "Former revisions" section
    2831!
     
    7376               initializing_actions, intermediate_timestep_count,              &
    7477               intermediate_timestep_count_max, kappa, km_constant, les_mw,    &
    75                ocean, prandtl_number, prho_reference, pt_reference, rans_mode, &
    76                rans_tke_e, rans_tke_l, simulated_time, timestep_scheme,        &
    77                turbulence_closure, turbulent_inflow, use_upstream_for_tke,     &
    78                vpt_reference, ws_scheme_sca
     78               ocean, plant_canopy, prandtl_number, prho_reference,            &
     79               pt_reference, rans_mode, rans_tke_e, rans_tke_l, simulated_time,&
     80               timestep_scheme, turbulence_closure, turbulent_inflow,          &
     81               use_upstream_for_tke, vpt_reference, ws_scheme_sca
    7982
    8083    USE advec_ws,                                                              &
     
    103106
    104107    USE plant_canopy_model_mod,                                                &
    105         ONLY:  pcm_tendency, plant_canopy
     108        ONLY:  pcm_tendency
    106109
    107110    USE statistics,                                                            &
  • palm/trunk/SOURCE/urban_surface_mod.f90

    r2737 r2746  
    2626! -----------------
    2727! $Id$
     28! Move flag plant canopy to modules
     29!
     30! 2737 2018-01-11 14:58:11Z kanani
    2831! Removed unused variables t_surf_whole...
    2932!
     
    231234               g, pt_surface, large_scale_forcing, lsf_surf, spinup,           &
    232235               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
    233                average_count_3d, varnamelength, urban_surface, kappa
     236               average_count_3d, varnamelength, urban_surface, kappa,          &
     237               plant_canopy
    234238
    235239    USE cpulog,                                                                &
     
    253257   
    254258    USE plant_canopy_model_mod,                                                &
    255         ONLY:  pc_heating_rate, plant_canopy, usm_lad_rma
     259        ONLY:  pc_heating_rate, usm_lad_rma
    256260   
    257261    USE radiation_model_mod,                                                   &
Note: See TracChangeset for help on using the changeset viewer.