Ignore:
Timestamp:
Jan 21, 2019 1:02:11 AM (5 years ago)
Author:
knoop
Message:

Some interface calls moved to module_interface + cleanup

File:
1 edited

Legend:

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

    r3667 r3685  
    2828! -----------------
    2929! $Id$
     30! Some interface calls moved to module_interface + cleanup
     31!
     32! 3667 2019-01-10 14:26:24Z schwenkel
    3033! Modified check for rrtmg input files
    3134!
     
    567570               message_string, plant_canopy, pt_surface,                       &
    568571               rho_surface, simulated_time, spinup_time, surface_pressure,     &
     572               read_svf, write_svf,                                            &
    569573               time_since_reference_point, urban_surface, varnamelength
    570574
     
    630634        ONLY:  get_topography_top_index, get_topography_top_index_ji,          &
    631635               ind_pav_green, ind_veg_wall, ind_wat_win,                       &
    632                surf_lsm_h, surf_lsm_v, surf_type, surf_usm_h, surf_usm_v
     636               surf_lsm_h, surf_lsm_v, surf_type, surf_usm_h, surf_usm_v,      &
     637               vertical_surfaces_exist
    633638
    634639    IMPLICIT NONE
     
    17391744       INTEGER(iwp) ::  ind_type  !< running index for subgrid-surface tiles
    17401745#endif
     1746
     1747!
     1748!--    Activate radiation_interactions according to the existence of vertical surfaces and/or trees.
     1749!--    The namelist parameter radiation_interactions_on can override this behavior.
     1750!--    (This check cannot be performed in check_parameters, because vertical_surfaces_exist is first set in
     1751!--    init_surface_arrays.)
     1752       IF ( radiation_interactions_on )  THEN
     1753          IF ( vertical_surfaces_exist  .OR.  plant_canopy )  THEN
     1754             radiation_interactions    = .TRUE.
     1755             average_radiation         = .TRUE.
     1756          ELSE
     1757             radiation_interactions_on = .FALSE.   !< reset namelist parameter: no interactions
     1758                                                   !< calculations necessary in case of flat surface
     1759          ENDIF
     1760       ELSEIF ( vertical_surfaces_exist  .OR.  plant_canopy )  THEN
     1761          message_string = 'radiation_interactions_on is set to .FALSE. although '     // &
     1762                           'vertical surfaces and/or trees exist. The model will run ' // &
     1763                           'without RTM (no shadows, no radiation reflections)'
     1764          CALL message( 'init_3d_model', 'PA0348', 0, 1, 0, 6, 0 )
     1765       ENDIF
     1766!
     1767!--    If required, initialize radiation interactions between surfaces
     1768!--    via sky-view factors. This must be done before radiation is initialized.
     1769       IF ( radiation_interactions )  CALL radiation_interaction_init
     1770
     1771!
     1772!--    Initialize radiation model
     1773       CALL location_message( 'initializing radiation model', .FALSE. )
    17411774
    17421775!
     
    26712704       CALL init_date_and_time
    26722705
     2706       CALL location_message( 'finished', .TRUE. )
     2707
     2708!
     2709!--    Find all discretized apparent solar positions for radiation interaction.
     2710       IF ( radiation_interactions )  CALL radiation_presimulate_solar_pos
     2711
     2712!
     2713!--    If required, read or calculate and write out the SVF
     2714       IF ( radiation_interactions .AND. read_svf)  THEN
     2715!
     2716!--       Read sky-view factors and further required data from file
     2717          CALL location_message( '    Start reading SVF from file', .FALSE. )
     2718          CALL radiation_read_svf()
     2719          CALL location_message( '    Reading SVF from file has finished', .TRUE. )
     2720
     2721       ELSEIF ( radiation_interactions .AND. .NOT. read_svf)  THEN
     2722!
     2723!--       calculate SFV and CSF
     2724          CALL location_message( '    Start calculation of SVF', .FALSE. )
     2725          CALL radiation_calc_svf()
     2726          CALL location_message( '    Calculation of SVF has finished', .TRUE. )
     2727       ENDIF
     2728
     2729       IF ( radiation_interactions .AND. write_svf)  THEN
     2730!
     2731!--       Write svf, csf svfsurf and csfsurf data to file
     2732          CALL location_message( '    Start writing SVF in file', .FALSE. )
     2733          CALL radiation_write_svf()
     2734          CALL location_message( '    Writing SVF in file has finished', .TRUE. )
     2735       ENDIF
     2736
     2737!
     2738!--    Adjust radiative fluxes. In case of urban and land surfaces, also
     2739!--    call an initial interaction.
     2740       IF ( radiation_interactions )  THEN
     2741          CALL radiation_interaction
     2742       ENDIF
     2743
    26732744       RETURN
    26742745
     
    58385909           !WRITE(message_string, '(a,f6.3)') 'Precomputing effective box optical ' &
    58395910           !    // 'depth using prototype leaf area density = ', prototype_lad
    5840            !CALL message('usm_init_urban_surface', 'PA0520', 0, 0, -1, 6, 0)
     5911           !CALL message('radiation_interaction_init', 'PA0520', 0, 0, -1, 6, 0)
    58415912       ENDIF
    58425913
Note: See TracChangeset for help on using the changeset viewer.