Ignore:
Timestamp:
Aug 21, 2019 11:13:06 AM (5 years ago)
Author:
suehring
Message:

Enable external time-dependent radiative forcing with downwelling short- and longwave radiation. Optionally, also downwelling diffuse radiation can be provided. Radiation data will be provided via dynamic input file.

File:
1 edited

Legend:

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

    r4150 r4178  
    2525! -----------------
    2626! $Id$
     27! Implement input of external radiation forcing. Therefore, provide public
     28! subroutines and variables.
     29!
     30! 4150 2019-08-08 20:00:47Z suehring
    2731! Some variables are given the public attribute, in order to call netcdf input
    2832! from single routines
     
    608612       LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used
    609613    END TYPE int_2d_32bit
    610 
     614!
     615!-- Define data type to read 1D real variables
     616    TYPE real_1d
     617       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
     618
     619       REAL(wp) ::  fill = -9999.9_wp                  !< fill value
     620       
     621       REAL(wp), DIMENSION(:), ALLOCATABLE ::  var     !< respective variable
     622    END TYPE real_1d   
    611623!
    612624!-- Define data type to read 2D real variables
     
    834846    CHARACTER(LEN=100) ::  input_file_vm      = 'PIDS_VM'      !< Name of file which comprises virtual measurement data
    835847   
    836     CHARACTER(LEN=25), ALLOCATABLE, DIMENSION(:)    ::  string_values  !< output of string variables read from netcdf input files
     848    CHARACTER(LEN=25), ALLOCATABLE, DIMENSION(:) ::  string_values  !< output of string variables read from netcdf input files
     849    CHARACTER(LEN=50), DIMENSION(:), ALLOCATABLE ::  vars_pids      !< variable in input file
    837850
    838851    INTEGER(iwp)                                     ::  id_emis        !< NetCDF id of input file for chemistry emissions: TBD: It has to be removed
    839852
    840853    INTEGER(iwp) ::  nc_stat         !< return value of nf90 function call
     854    INTEGER(iwp) ::  num_var_pids    !< number of variables in file
     855    INTEGER(iwp) ::  pids_id         !< file id
    841856
    842857    LOGICAL ::  input_pids_static  = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing static information exists
     
    949964!
    950965!-- Public data structures
    951     PUBLIC real_2d
     966    PUBLIC real_1d,                                                            &
     967           real_2d
    952968!
    953969!-- Public variables
     
    956972           chem_emis, chem_emis_att, chem_emis_att_type, chem_emis_val_type,   &
    957973           coord_ref_sys,                                                      &
    958            init_3d, init_model, input_file_atts, input_file_static,            &
     974           init_3d, init_model, input_file_atts,                               &
     975           input_file_dynamic,                                                 &
     976           input_file_static,                                                  &
    959977           input_pids_static,                                                  &
    960978           input_pids_dynamic, input_pids_vm, input_file_vm,                   &
    961979           leaf_area_density_f, nest_offl,                                     &
     980           num_var_pids,                                                       &
    962981           pavement_pars_f, pavement_subsurface_pars_f, pavement_type_f,       &
     982           pids_id,                                                            &
    963983           root_area_density_lad_f, root_area_density_lsm_f, soil_pars_f,      &
    964984           soil_type_f, street_crossing_f, street_type_f, surface_fraction_f,  &
    965985           terrain_height_f, vegetation_pars_f, vegetation_type_f,             &
     986           vars_pids,                                                          &
    966987           water_pars_f, water_type_f
    967988!
Note: See TracChangeset for help on using the changeset viewer.