Ignore:
Timestamp:
Oct 30, 2018 9:07:39 PM (5 years ago)
Author:
kanani
Message:

Add netcdf input for uv exposure model (netcdf_data_input_mod, Makefile, .palm.iofiles), plus bugfixes (uv_exposure_model_mod)

File:
1 edited

Legend:

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

    r3472 r3474  
    2525! -----------------
    2626! $Id$
     27! Add UV exposure model input (Schrempf)
     28!
     29! 3472 2018-10-30 20:43:50Z suehring
    2730! Salsa implemented
    2831!
     
    446449    END TYPE int_2d_8bit
    447450!
     451!-- 8-bit Integer 3D
     452    TYPE int_3d_8bit
     453       INTEGER(KIND=1) ::  fill = -127                           !< fill value
     454       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d !< respective variable
     455
     456       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
     457    END TYPE int_3d_8bit
     458!
    448459!-- 32-bit Integer 2D
    449460    TYPE int_2d_32bit
     
    464475
    465476!
    466 !-- Define data type to read 2D real variables
     477!-- Define data type to read 3D real variables
    467478    TYPE real_3d
    468479       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
     
    629640    TYPE(int_2d_8bit)  ::  vegetation_type_f !< input variable for vegetation type
    630641    TYPE(int_2d_8bit)  ::  water_type_f      !< input variable for water type
    631 
     642!
     643!-- Define 3D variables of type NC_BYTE
     644    TYPE(int_3d_8bit)  ::  building_obstruction_f    !< input variable for building obstruction
     645    TYPE(int_3d_8bit)  ::  building_obstruction_full !< input variable for building obstruction
    632646!
    633647!-- Define 2D variables of type NC_INT
     
    636650!-- Define 2D variables of type NC_FLOAT
    637651    TYPE(real_2d) ::  terrain_height_f       !< input variable for terrain height
     652    TYPE(real_2d) ::  uvem_irradiance_f      !< input variable for uvem irradiance lookup table
     653    TYPE(real_2d) ::  uvem_integration_f     !< input variable for uvem integration
    638654!
    639655!-- Define 3D variables of type NC_FLOAT
     
    642658    TYPE(real_3d) ::  root_area_density_lad_f !< input variable for root area density - resolved vegetation
    643659    TYPE(real_3d) ::  root_area_density_lsm_f !< input variable for root area density - parametrized vegetation
    644 
     660    TYPE(real_3d) ::  uvem_radiance_f         !< input variable for uvem radiance lookup table
     661    TYPE(real_3d) ::  uvem_projarea_f         !< input variable for uvem projection area lookup table
    645662!
    646663!-- Define input variable for buildings
     
    670687    CHARACTER(LEN=100) ::  input_file_dynamic = 'PIDS_DYNAMIC' !< Name of file which comprises dynamic input data
    671688    CHARACTER(LEN=100) ::  input_file_chem    = 'PIDS_CHEM'    !< Name of file which comprises chemistry input data
     689    CHARACTER(LEN=100) ::  input_file_uvem    = 'PIDS_UVEM'    !< Name of file which comprises static uv_exposure model input data
    672690    CHARACTER(LEN=100) ::  input_file_vm      = 'PIDS_VM'      !< Name of file which comprises virtual measurement data
    673691
    674692    CHARACTER (LEN=25), ALLOCATABLE, DIMENSION(:)    ::  string_values  !< output of string variables read from netcdf input files
    675  
     693
    676694    INTEGER(iwp)                                     ::  id_emis        !< NetCDF id of input file for chemistry emissions: TBD: It has to be removed
    677695
     
    681699    LOGICAL ::  input_pids_dynamic = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing dynamic information exists
    682700    LOGICAL ::  input_pids_chem    = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing chemistry information exists
     701    LOGICAL ::  input_pids_uvem    = .FALSE.   !< Flag indicating whether uv-expoure-model input file containing static information exists
    683702    LOGICAL ::  input_pids_vm      = .FALSE.   !< Flag indicating whether input file for virtual measurements exist
    684    
     703
    685704    LOGICAL ::  collective_read = .FALSE.      !< Enable NetCDF collective read
    686705
     
    749768       MODULE PROCEDURE netcdf_data_input_var_real_2d
    750769    END INTERFACE netcdf_data_input_var
     770
     771    INTERFACE netcdf_data_input_uvem
     772       MODULE PROCEDURE netcdf_data_input_uvem
     773    END INTERFACE netcdf_data_input_uvem
    751774
    752775    INTERFACE get_variable
     
    791814           terrain_height_f, vegetation_pars_f, vegetation_type_f,             &
    792815           water_pars_f, water_type_f
     816!
     817!-- Public uv exposure variables
     818    PUBLIC building_obstruction_f, input_file_uvem, input_pids_uvem,           &
     819           netcdf_data_input_uvem,                                             &
     820           uvem_integration_f, uvem_irradiance_f,                              &
     821           uvem_projarea_f, uvem_radiance_f
    793822
    794823!
     
    804833           netcdf_data_input_var, get_attribute, get_variable, open_read_file
    805834
     835
    806836 CONTAINS
    807837
     
    826856       INQUIRE( FILE = TRIM( input_file_chem )    // TRIM( coupling_char ),    &
    827857                EXIST = input_pids_chem )
     858       INQUIRE( FILE = TRIM( input_file_uvem ) // TRIM( coupling_char ),       &
     859                EXIST = input_pids_uvem  )
    828860       INQUIRE( FILE = TRIM( input_file_vm )      // TRIM( coupling_char ),    &
    829861                EXIST = input_pids_vm )
     
    24972529! Description:
    24982530! ------------
     2531!> Reads uvem lookup table information.
     2532!------------------------------------------------------------------------------!
     2533    SUBROUTINE netcdf_data_input_uvem
     2534       
     2535       USE indices,                                                            &
     2536           ONLY:  nxl, nxr, nyn, nys
     2537
     2538       IMPLICIT NONE
     2539
     2540       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names in static input file
     2541
     2542
     2543       INTEGER(iwp) ::  id_uvem       !< NetCDF id of uvem lookup table input file
     2544       INTEGER(iwp) ::  nli = 35      !< dimension length of lookup table in x
     2545       INTEGER(iwp) ::  nlj =  9      !< dimension length of lookup table in y
     2546       INTEGER(iwp) ::  nlk = 90      !< dimension length of lookup table in z
     2547       INTEGER(iwp) ::  num_vars      !< number of variables in netcdf input file
     2548!
     2549!--    Input via uv exposure model lookup table input
     2550       IF ( input_pids_uvem )  THEN
     2551
     2552#if defined ( __netcdf )
     2553!
     2554!--       Open file in read-only mode
     2555          CALL open_read_file( TRIM( input_file_uvem ) //                    &
     2556                               TRIM( coupling_char ), id_uvem )
     2557!
     2558!--       At first, inquire all variable names.
     2559!--       This will be used to check whether an input variable exist or not.
     2560          CALL inquire_num_variables( id_uvem, num_vars )
     2561!
     2562!--       Allocate memory to store variable names and inquire them.
     2563          ALLOCATE( var_names(1:num_vars) )
     2564          CALL inquire_variable_names( id_uvem, var_names )
     2565!
     2566!
     2567!--       uvem integration
     2568          IF ( check_existence( var_names, 'int_factors' ) )  THEN
     2569             uvem_integration_f%from_file = .TRUE.
     2570!
     2571!--          Input 2D uvem integration.
     2572             ALLOCATE ( uvem_integration_f%var(0:nlj,0:nli)  )
     2573             
     2574             CALL get_variable( id_uvem, 'int_factors', uvem_integration_f%var, 0, nli, 0, nlj )
     2575          ELSE
     2576             uvem_integration_f%from_file = .FALSE.
     2577          ENDIF
     2578!
     2579!
     2580!
     2581!--       uvem irradiance
     2582          IF ( check_existence( var_names, 'irradiance' ) )  THEN
     2583             uvem_irradiance_f%from_file = .TRUE.
     2584!
     2585!--          Input 2D uvem irradiance.
     2586             ALLOCATE ( uvem_irradiance_f%var(0:nlk, 0:2)  )
     2587             
     2588             CALL get_variable( id_uvem, 'irradiance', uvem_irradiance_f%var, 0, 2, 0, nlk )
     2589          ELSE
     2590             uvem_irradiance_f%from_file = .FALSE.
     2591          ENDIF
     2592!
     2593!
     2594!
     2595!--       uvem porjection areas
     2596          IF ( check_existence( var_names, 'projarea' ) )  THEN
     2597             uvem_projarea_f%from_file = .TRUE.
     2598!
     2599!--          Input 3D uvem projection area (human geometgry)
     2600             ALLOCATE ( uvem_projarea_f%var(0:2,0:nlj,0:nli)  )
     2601           
     2602             CALL get_variable( id_uvem, 'projarea', uvem_projarea_f%var, 0, nli, 0, nlj, 0, 2 )
     2603          ELSE
     2604             uvem_projarea_f%from_file = .FALSE.
     2605          ENDIF
     2606!
     2607!
     2608!
     2609!--       uvem radiance
     2610          IF ( check_existence( var_names, 'radiance' ) )  THEN
     2611             uvem_radiance_f%from_file = .TRUE.
     2612!
     2613!--          Input 3D uvem radiance
     2614             ALLOCATE ( uvem_radiance_f%var(0:nlk,0:nlj,0:nli)  )
     2615             
     2616             CALL get_variable( id_uvem, 'radiance', uvem_radiance_f%var, 0, nli, 0, nlj, 0, nlk )
     2617          ELSE
     2618             uvem_radiance_f%from_file = .FALSE.
     2619          ENDIF
     2620!
     2621!
     2622!
     2623!--       Read building obstruction
     2624          IF ( check_existence( var_names, 'obstruction' ) )  THEN
     2625             building_obstruction_full%from_file = .TRUE.
     2626!--          Input 3D uvem building obstruction
     2627              ALLOCATE ( building_obstruction_full%var_3d(0:44,0:2,0:2) )
     2628              CALL get_variable( id_uvem, 'obstruction', building_obstruction_full%var_3d,0, 2, 0, 2, 0, 44 )       
     2629          ELSE
     2630             building_obstruction_full%from_file = .FALSE.
     2631          ENDIF
     2632!
     2633          IF ( check_existence( var_names, 'obstruction' ) )  THEN
     2634             building_obstruction_f%from_file = .TRUE.
     2635!
     2636!--          Input 3D uvem building obstruction
     2637             ALLOCATE ( building_obstruction_f%var_3d(0:44,nys:nyn,nxl:nxr) )
     2638!
     2639             CALL get_variable( id_uvem, 'obstruction', building_obstruction_f%var_3d,      &
     2640                                nxl, nxr, nys, nyn, 0, 44 )       
     2641          ELSE
     2642             building_obstruction_f%from_file = .FALSE.
     2643          ENDIF
     2644!
     2645!
     2646!
     2647!
     2648!--       Close uvem lookup table input file
     2649          CALL close_input_file( id_uvem )
     2650#else
     2651          CONTINUE
     2652#endif
     2653       ENDIF
     2654    END SUBROUTINE netcdf_data_input_uvem
     2655
     2656!------------------------------------------------------------------------------!
     2657! Description:
     2658! ------------
    24992659!> Reads orography and building information.
    25002660!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.