Ignore:
Timestamp:
Aug 27, 2019 3:42:37 PM (5 years ago)
Author:
suehring
Message:

Implement external radiation forcing also for level-of-detail = 2 (horizontally 2D radiation)

File:
1 edited

Legend:

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

    r4186 r4190  
    2525! -----------------
    2626! $Id$
     27! type real_1d changed to real_1d_3d
     28!
     29! 4186 2019-08-23 16:06:14Z suehring
    2730! Minor formatting adjustments
    2831!
     
    396399    END TYPE int_2d_32bit
    397400!
    398 !-- Define data type to read 1D real variables
    399     TYPE real_1d
     401!-- Define data type to read 1D or 3D real variables.
     402    TYPE real_1d_3d
    400403       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
    401404
     405       INTEGER(iwp) ::  lod = -1        !< level-of-detail
     406       
    402407       REAL(wp) ::  fill = -9999.9_wp                  !< fill value
    403408       
    404        REAL(wp), DIMENSION(:), ALLOCATABLE ::  var     !< respective variable
    405     END TYPE real_1d   
     409       REAL(wp), DIMENSION(:),     ALLOCATABLE ::  var1d     !< respective 1D variable
     410       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  var3d     !< respective 3D variable
     411    END TYPE real_1d_3d   
    406412!
    407413!-- Define data type to read 2D real variables
     
    409415       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
    410416
     417       INTEGER(iwp) ::  lod             !< level-of-detail
     418       
    411419       REAL(wp) ::  fill = -9999.9_wp                !< fill value
    412420       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var !< respective variable
     
    747755!
    748756!-- Public data structures
    749     PUBLIC real_1d,                                                            &
     757    PUBLIC real_1d_3d,                                                         &
    750758           real_2d
    751759!
    752760!-- Public variables
    753761    PUBLIC albedo_pars_f, albedo_type_f, basal_area_density_f, buildings_f,    &
    754            building_id_f, building_pars_f, building_type_f, char_fill,         &
     762           building_id_f, building_pars_f, building_type_f,                    &
     763           char_fill,                                                          &
     764           char_lod,                                                           &
    755765           chem_emis, chem_emis_att, chem_emis_att_type, chem_emis_val_type,   &
    756766           coord_ref_sys,                                                      &
Note: See TracChangeset for help on using the changeset viewer.