Ignore:
Timestamp:
Jul 27, 2018 1:36:03 PM (6 years ago)
Author:
suehring
Message:

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File:
1 edited

Legend:

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

    r3065 r3182  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Rename variables and extend error message
     23! Enable geneartor also for stretched grids
    2324!
    2425! Former revisions:
     
    119120!> @bug  Height information from input file is not used. Profiles from input
    120121!>       must match with current PALM grid.
    121 !>       Transformation of length scales to number of gridpoints does not
    122 !>       consider grid stretching.
    123122!>       In case of restart, velocity seeds differ from precursor run if a11,
    124123!>       a22, or a33 are zero.
     
    160159    INCLUDE "mpif.h"
    161160#endif
     161
    162162
    163163    LOGICAL :: velocity_seed_initialized = .FALSE.  !< true after first call of stg_main
     
    317317
    318318    USE control_parameters,                                                    &
    319         ONLY:  bc_lr, bc_ns, forcing, nest_domain, number_stretch_level_start, &
    320                rans_mode, turbulent_inflow
     319        ONLY:  bc_lr, bc_ns, child_domain, nesting_offline,                    &
     320               number_stretch_level_start, rans_mode, turbulent_inflow
    321321
    322322    USE pmc_interface,                                                         &
     
    326326    IMPLICIT NONE
    327327
    328     IF ( .NOT. use_syn_turb_gen  .AND.  .NOT. rans_mode  .AND.  forcing )  THEN
    329        message_string = 'Synthetic turbulence generator has to be applied ' // &
    330                         'when forcing is used and model operates in LES mode.'
    331        CALL message( 'stg_check_parameters', 'PA0000', 1, 2, 0, 6, 0 )
     328    IF ( .NOT. use_syn_turb_gen  .AND.  .NOT. rans_mode  .AND.                 &
     329          nesting_offline )  THEN
     330       message_string = 'No synthetic turbulence generator is applied. ' //    &
     331                        'In case PALM operates in LES mode and lateral ' //    &
     332                        'boundary conditions are provided by COSMO model, ' // &
     333                        'turbulence may require large adjustment lenght at ' //&
     334                        'the lateral inflow boundaries. Please check your ' // &
     335                        'results carefully.'
     336       CALL message( 'stg_check_parameters', 'PA0000', 0, 0, 0, 6, 0 )
    332337    ENDIF
    333338
    334     IF ( .NOT. use_syn_turb_gen  .AND.  nest_domain                            &
     339    IF ( .NOT. use_syn_turb_gen  .AND.  child_domain                           &
    335340         .AND. rans_mode_parent  .AND.  .NOT. rans_mode )  THEN
    336341       message_string = 'Synthetic turbulence generator has to be applied ' // &
     
    342347    IF ( use_syn_turb_gen )  THEN
    343348
    344        IF ( .NOT. forcing  .AND.  .NOT. nest_domain )  THEN
    345 
     349       IF ( .NOT. nesting_offline  .AND.  .NOT. child_domain )  THEN
     350       
    346351          IF ( INDEX( initializing_actions, 'set_constant_profiles' ) == 0     &
    347352        .AND.  INDEX( initializing_actions, 'read_restart_data' ) == 0 )  THEN
     
    371376          CALL message( 'stg_check_parameters', 'PA0039', 1, 2, 0, 6, 0 )
    372377       ENDIF
    373        
    374        IF ( number_stretch_level_start > 0 )  THEN
    375           message_string = 'Using synthetic turbulence generator ' //          &
    376                            'in combination with stretching is not allowed'
    377           CALL message( 'stg_check_parameters', 'PA0420', 1, 2, 0, 6, 0 )
    378        ENDIF
    379378
    380379    ENDIF
     
    424423
    425424    USE control_parameters,                                                    &
    426         ONLY:  coupling_char, dz, e_init, forcing, nest_domain, rans_mode
     425        ONLY:  child_domain, coupling_char, dz, e_init, nesting_offline,       &
     426               rans_mode
    427427
    428428    USE grid_variables,                                                        &
     
    512512!        nzt_x_stg = myidx * nnz + MOD( nz , pdims(1) )
    513513
    514     IF ( forcing  .OR.  ( nest_domain .AND.  rans_mode_parent  .AND.           &
    515                    .NOT.  rans_mode ) )  THEN
     514    IF ( nesting_offline   .OR.  ( child_domain  .AND.  rans_mode_parent       &
     515                            .AND.  .NOT.  rans_mode ) )  THEN
    516516       nnz = nz / pdims(2)
    517517       nzb_y_stg = 1 + myidy * INT( nnz )
     
    558558!-- layer
    559559!-- stg_type_xz: xz-slice with vertical bounds nzb:nzt+1
    560     IF ( forcing  .OR.  ( nest_domain .AND.  rans_mode_parent  .AND.           &
    561                    .NOT.  rans_mode ) )  THEN
     560    IF ( nesting_offline  .OR.  ( child_domain .AND.  rans_mode_parent         &
     561                           .AND.  .NOT.  rans_mode ) )  THEN
    562562       CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt-nzb+2,nxrg-nxlg+1],              &
    563563               [1,nxrg-nxlg+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr )
     
    612612       READ( 90, * )
    613613
    614        DO  k = nzb, nzt+1
     614       DO  k = nzb+1, nzt+1
    615615          READ( 90, * ) zz, luy, luz, tu(k), lvy, lvz, tv(k), lwy, lwz, tw(k), &
    616616                        r11(k), r21(k), r22(k), r31(k), r32(k), r33(k),        &
     
    618618
    619619!
    620 !--       Convert length scales from meter to number of grid points. Attention:
    621 !--       Does not work if grid stretching is used
     620!--       Convert length scales from meter to number of grid points.
    622621          nuy(k) = INT( luy * ddy )
    623           nuz(k) = INT( luz / dz(1) )
     622          nuz(k) = INT( luz * ddzw(k) )
    624623          nvy(k) = INT( lvy * ddy )
    625           nvz(k) = INT( lvz / dz(1) )
     624          nvz(k) = INT( lvz * ddzw(k) )
    626625          nwy(k) = INT( lwy * ddy )
    627           nwz(k) = INT( lwz / dz(1) )
     626          nwz(k) = INT( lwz * ddzw(k) )
    628627!
    629628!--       Workaround, assume isotropic turbulence
     
    640639          ENDIF
    641640       ENDDO
    642 
     641!
     642!--    Set lenght scales at surface grid point
     643       nuy(nzb) = nuy(nzb+1)
     644       nuz(nzb) = nuz(nzb+1)
     645       nvy(nzb) = nvy(nzb+1)
     646       nvz(nzb) = nvz(nzb+1)
     647       nwy(nzb) = nwy(nzb+1)
     648       nwz(nzb) = nwz(nzb+1)
     649       
    643650       CLOSE( 90 )
    644651
     
    710717!
    711718!-- Assign initial profiles
    712     IF ( .NOT. forcing  .AND.  .NOT.  nest_domain )  THEN
     719    IF ( .NOT. nesting_offline  .AND.  .NOT.  child_domain )  THEN
    713720       u_init = mean_inflow_profiles(:,1)
    714721       v_init = mean_inflow_profiles(:,2)
     
    10421049
    10431050    USE control_parameters,                                                    &
    1044         ONLY:  dt_3d, forcing, intermediate_timestep_count,  nest_domain,      &
    1045                rans_mode, simulated_time, volume_flow_initial
     1051        ONLY:  child_domain, dt_3d, intermediate_timestep_count,               &
     1052               nesting_offline, rans_mode, simulated_time, volume_flow_initial
    10461053
    10471054    USE grid_variables,                                                        &
     
    10861093       CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fw_yz, id_stg_left )
    10871094
    1088        IF ( forcing  .OR.  ( nest_domain .AND.  rans_mode_parent  .AND.        &
    1089                       .NOT.  rans_mode ) )  THEN
     1095       IF ( nesting_offline  .OR.  ( child_domain .AND.  rans_mode_parent      &
     1096                                .AND.  .NOT.  rans_mode ) )  THEN
    10901097!
    10911098!--       Generate turbulence at right boundary
     
    11121119    CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fwo_yz, id_stg_left )
    11131120
    1114     IF ( forcing  .OR.  ( nest_domain .AND.  rans_mode_parent  .AND.           &
    1115                    .NOT.  rans_mode ) )  THEN
     1121    IF ( nesting_offline  .OR.  ( child_domain .AND.  rans_mode_parent         &
     1122                             .AND.  .NOT.  rans_mode ) )  THEN
    11161123!
    11171124!--       Generate turbulence at right boundary
     
    11911198!--    This correction factor insures that the mass flux is preserved at the
    11921199!--    inflow boundary
    1193        IF ( .NOT. forcing  .AND.  .NOT. nest_domain )  THEN
     1200       IF ( .NOT. nesting_offline  .AND.  .NOT. child_domain )  THEN
    11941201          mc_factor_l = 0.0_wp
    11951202          mc_factor   = 0.0_wp
Note: See TracChangeset for help on using the changeset viewer.