Ignore:
Timestamp:
Oct 15, 2018 2:21:08 PM (5 years ago)
Author:
suehring
Message:

Offline nesting revised and separated from large_scale_forcing_mod; Time-dependent synthetic turbulence generator; bugfixes in USM/LSM radiation model and init_pegrid

File:
1 edited

Legend:

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

    r3337 r3347  
    2828! -----------------
    2929! $Id$
     30! Enable USM initialization with default building parameters in case no static
     31! input file exist.
     32!
     33! 3343 2018-10-15 10:38:52Z suehring
    3034! Add output variables usm_rad_pc_inlw, usm_rad_pc_insw*
    3135!
     
    69026906        INTEGER(iwp)                                          :: wtc
    69036907        REAL(wp), DIMENSION(n_surface_params)                 :: wtp
     6908       
     6909        LOGICAL                                               :: ascii_file = .FALSE.
    69046910   
    69056911        INTEGER(iwp), DIMENSION(0:17, nysg:nyng, nxlg:nxrg)   :: usm_par
     
    69226928        IF ( building_type_f%from_file  .OR.  building_pars_f%from_file )      &
    69236929           RETURN
     6930!
     6931!--     Check if ASCII input file exists. If not, return and initialize USM
     6932!--     with default settings.
     6933        INQUIRE( FILE = 'SURFACE_PARAMETERS' // coupling_char,                 &
     6934                 EXIST = ascii_file )
     6935                 
     6936        IF ( .NOT. ascii_file )  RETURN
    69246937
    69256938!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Note: See TracChangeset for help on using the changeset viewer.