Ignore:
Timestamp:
Oct 14, 2011 6:39:12 AM (13 years ago)
Author:
raasch
Message:

New:
---

Flow field initialization with given (e.g. measured) profiles. Profile data
for u-,v-velocity components + respective heights are given with new
inipar-parameters u_profile, v_profile, and uv_heights. Final profiles are
calculated from these given profiles by linear interpolation.
(check_parameters, header, init_3d_model, modules, parin)

Changed:


ug,vg replaced by u_init,v_init as the Dirichlet top boundary condition
(boundary_conds)

dirichlet_0 conditions moved from init_3d_model to
check_parameters (check_parameters, init_3d_model)

Errors:


bugfix: dirichlet_0 conditions moved from init_3d_model to
check_parameters (check_parameters, init_3d_model)

File:
1 edited

Legend:

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

    r708 r767  
    44! Current revisions:
    55! -----------------
    6 !
     6! Calculating u,v-profiles from given profiles by linear interpolation.
     7! bugfix: dirichlet_0 conditions for ug/vg moved from init_3d_model to here
    78!
    89! Former revisions:
     
    176177    CHARACTER (LEN=100) ::  action
    177178
    178     INTEGER ::  i, ilen, intervals, iremote = 0, iter, j, k, nnxh, nnyh, &
    179          position, prec
     179    INTEGER ::  i, ilen, intervals, iremote = 0, iter, j, k, kk, nnxh, nnyh, &
     180                position, prec
    180181    LOGICAL ::  found, ldum
    181182    REAL    ::  gradient, maxn, maxp, remote = 0.0, &
     
    771772
    772773!
    773 !--    Initial profiles for 1D and 3D model, respectively
    774        u_init  = ug_surface
    775        v_init  = vg_surface
     774!--    Initial profiles for 1D and 3D model, respectively (u,v further below)
    776775       pt_init = pt_surface
    777776       IF ( humidity )        q_init  = q_surface
     
    838837       ENDIF
    839838
    840        u_init = ug
    841 
    842 !
    843 !--    In case of no given gradients for ug, choose a vanishing gradient
     839!
     840!--    In case of no given gradients for ug, choose a zero gradient
    844841       IF ( ug_vertical_gradient_level(1) == -9999999.9 )  THEN
    845842          ug_vertical_gradient_level(1) = 0.0
     
    904901       ENDIF
    905902
    906        v_init = vg
    907  
    908 !
    909 !--    In case of no given gradients for vg, choose a vanishing gradient
     903!
     904!--    In case of no given gradients for vg, choose a zero gradient
    910905       IF ( vg_vertical_gradient_level(1) == -9999999.9 )  THEN
    911906          vg_vertical_gradient_level(1) = 0.0
     907       ENDIF
     908
     909!
     910!--    Let the initial wind profiles be the calculated ug/vg profiles or
     911!--    interpolate them from wind profile data (if given)
     912       IF ( u_profile(1) == 9999999.9  .AND.  v_profile(1) == 9999999.9 )  THEN
     913
     914          u_init = ug
     915          v_init = vg
     916
     917       ELSEIF ( u_profile(1) == 0.0  .AND.  v_profile(1) == 0.0 )  THEN
     918
     919          IF ( uv_heights(1) /= 0.0 )  THEN
     920             message_string = 'uv_heights(1) must be 0.0'
     921             CALL message( 'check_parameters', 'PA0345', 1, 2, 0, 6, 0 )
     922          ENDIF
     923
     924          use_prescribed_profile_data = .TRUE.
     925
     926          kk = 1
     927          u_init(0) = 0.0
     928          v_init(0) = 0.0
     929
     930          DO  k = 1, nz+1
     931
     932             IF ( kk < 100 )  THEN
     933                DO WHILE ( uv_heights(kk+1) <= zu(k) )
     934                   kk = kk + 1
     935                   IF ( kk == 100 )  EXIT
     936                ENDDO
     937             ENDIF
     938
     939             IF ( kk < 100 )  THEN
     940                u_init(k) = u_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
     941                                       ( uv_heights(kk+1) - uv_heights(kk) ) * &
     942                                       ( u_profile(kk+1) - u_profile(kk) )
     943                v_init(k) = v_profile(kk) + ( zu(k) - uv_heights(kk) ) /       &
     944                                       ( uv_heights(kk+1) - uv_heights(kk) ) * &
     945                                       ( v_profile(kk+1) - v_profile(kk) )
     946             ELSE
     947                u_init(k) = u_profile(kk)
     948                v_init(k) = v_profile(kk)
     949             ENDIF
     950
     951          ENDDO
     952
     953       ELSE
     954
     955          message_string = 'u_profile(1) and v_profile(1) must be 0.0'
     956          CALL message( 'check_parameters', 'PA0346', 1, 2, 0, 6, 0 )
     957
    912958       ENDIF
    913959
     
    15391585       IF ( bc_uv_t == 'dirichlet' .OR. bc_uv_t == 'dirichlet_0' )  THEN
    15401586          ibc_uv_t = 0
     1587          IF ( bc_uv_t == 'dirichlet_0' )  THEN
     1588!
     1589!--          Velocities for the initial u,v-profiles are set zero at the top
     1590!--          in case of dirichlet_0 conditions
     1591             u_init(nzt+1)    = 0.0
     1592             v_init(nzt+1)    = 0.0
     1593          ENDIF
    15411594       ELSEIF ( bc_uv_t == 'neumann' )  THEN
    15421595          ibc_uv_t = 1
Note: See TracChangeset for help on using the changeset viewer.