Ignore:
Timestamp:
Aug 9, 2012 8:28:32 AM (12 years ago)
Author:
fricke
Message:

merge fricke branch back into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/check_parameters.f90

    r965 r978  
    44! Current revisions:
    55! -----------------
    6 !
     6! setting of bc_lr/ns_dirneu/neudir
     7! outflow damping layer removed
     8! check for z0h*
     9! check for pt_damping_width
    710!
    811! Former revisions:
     
    13791382!-- Lateral boundary conditions
    13801383    IF ( bc_lr /= 'cyclic'  .AND.  bc_lr /= 'dirichlet/radiation'  .AND. &
    1381          bc_lr /= 'radiation/dirichlet' )  THEN
     1384         bc_lr /= 'radiation/dirichlet' .AND. bc_lr /= 'dirichlet/neumann' &
     1385         .AND. bc_lr /= 'neumann/dirichlet' )  THEN
    13821386       message_string = 'unknown boundary condition: bc_lr = "' // &
    13831387                        TRIM( bc_lr ) // '"'
     
    13851389    ENDIF
    13861390    IF ( bc_ns /= 'cyclic'  .AND.  bc_ns /= 'dirichlet/radiation'  .AND. &
    1387          bc_ns /= 'radiation/dirichlet' )  THEN
     1391         bc_ns /= 'radiation/dirichlet' .AND. bc_ns /= 'dirichlet/neumann' &
     1392         .AND. bc_ns /= 'neumann/dirichlet' )  THEN
    13881393       message_string = 'unknown boundary condition: bc_ns = "' // &
    13891394                        TRIM( bc_ns ) // '"'
     
    13961401    IF ( bc_lr == 'dirichlet/radiation' )  bc_lr_dirrad = .TRUE.
    13971402    IF ( bc_lr == 'radiation/dirichlet' )  bc_lr_raddir = .TRUE.
     1403    IF ( bc_lr == 'dirichlet/neumann' )    bc_lr_dirneu = .TRUE.
     1404    IF ( bc_lr == 'neumann/dirichlet' )    bc_lr_neudir = .TRUE.
    13981405    IF ( bc_ns /= 'cyclic' )               bc_ns_cyc    = .FALSE.
    13991406    IF ( bc_ns == 'dirichlet/radiation' )  bc_ns_dirrad = .TRUE.
    14001407    IF ( bc_ns == 'radiation/dirichlet' )  bc_ns_raddir = .TRUE.
     1408    IF ( bc_ns == 'dirichlet/neumann' )    bc_ns_dirneu = .TRUE.
     1409    IF ( bc_ns == 'neumann/dirichlet' )    bc_ns_neudir = .TRUE.
    14011410
    14021411!
     
    26592668             unit = 'psu'
    26602669
    2661           CASE ( 'u*', 't*', 'lwp*', 'pra*', 'prr*', 'qsws*', 'shf*', 'z0*' )
     2670          CASE ( 'u*', 't*', 'lwp*', 'pra*', 'prr*', 'qsws*', 'shf*', 'z0*', 'z0h*' )
    26622671             IF ( k == 0  .OR.  data_output(i)(ilen-2:ilen) /= '_xy' )  THEN
    26632672                message_string = 'illegal value for data_output: "' // &
     
    27002709             IF ( TRIM( var ) == 'u*'     )  unit = 'm/s'
    27012710             IF ( TRIM( var ) == 'z0*'    )  unit = 'm'
     2711             IF ( TRIM( var ) == 'z0h*'    )  unit = 'm'
    27022712
    27032713
     
    29642974
    29652975!
    2966 !-- In case of non-cyclic lateral boundaries, set the default maximum value
    2967 !-- for the horizontal diffusivity used within the outflow damping layer,
    2968 !-- and check/set the width of the damping layer
     2976!-- In case of non-cyclic lateral boundaries and a damping layer for the
     2977!-- potential temperature, check the width of the damping layer
    29692978    IF ( bc_lr /= 'cyclic' ) THEN
    2970        IF ( km_damp_max == -1.0 )  THEN
    2971           km_damp_max = 0.5 * dx
    2972        ENDIF
    2973        IF ( outflow_damping_width == -1.0 )  THEN
    2974           outflow_damping_width = MIN( 20, nx/2 )
    2975        ENDIF
    2976        IF ( outflow_damping_width <= 0  .OR.  outflow_damping_width > nx )  THEN
    2977           message_string = 'outflow_damping width out of range'
     2979       IF ( pt_damping_width < 0.0 .OR. pt_damping_width > REAL( nx * dx ) )  THEN
     2980          message_string = 'pt_damping_width out of range'
    29782981          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
    29792982       ENDIF
     
    29812984
    29822985    IF ( bc_ns /= 'cyclic' )  THEN
    2983        IF ( km_damp_max == -1.0 )  THEN
    2984           km_damp_max = 0.5 * dy
    2985        ENDIF
    2986        IF ( outflow_damping_width == -1.0 )  THEN
    2987           outflow_damping_width = MIN( 20, ny/2 )
    2988        ENDIF
    2989        IF ( outflow_damping_width <= 0  .OR.  outflow_damping_width > ny )  THEN
    2990           message_string = 'outflow_damping width out of range'
     2986       IF ( pt_damping_width < 0.0 .OR. pt_damping_width > REAL( ny * dy ) )  THEN
     2987          message_string = 'pt_damping_width out of range'
    29912988          CALL message( 'check_parameters', 'PA0124', 1, 2, 0, 6, 0 )
    29922989       ENDIF
     
    31083105    ENDIF
    31093106
    3110     IF ( bc_lr == 'radiation/dirichlet' )  THEN
     3107    IF ( bc_lr == 'radiation/dirichlet' .OR. bc_lr == 'neumann/dirichlet' )  THEN
    31113108       dist_nxr    = nx - inflow_disturbance_begin
    31123109       dist_nxl(1) = nx - inflow_disturbance_end
    3113     ELSEIF ( bc_lr == 'dirichlet/radiation' )  THEN
     3110    ELSEIF ( bc_lr == 'dirichlet/radiation' .OR. bc_lr == 'dirichlet/neumann' )  THEN
    31143111       dist_nxl    = inflow_disturbance_begin
    31153112       dist_nxr(1) = inflow_disturbance_end
    31163113    ENDIF
    3117     IF ( bc_ns == 'dirichlet/radiation' )  THEN
     3114    IF ( bc_ns == 'dirichlet/radiation' .OR. bc_ns == 'dirichlet/neumann' )  THEN
    31183115       dist_nyn    = ny - inflow_disturbance_begin
    31193116       dist_nys(1) = ny - inflow_disturbance_end
    3120     ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
     3117    ELSEIF ( bc_ns == 'radiation/dirichlet' .OR. bc_ns == 'neumann/dirichlet' )  THEN
    31213118       dist_nys    = inflow_disturbance_begin
    31223119       dist_nyn(1) = inflow_disturbance_end
     
    31263123!-- A turbulent inflow requires Dirichlet conditions at the respective inflow
    31273124!-- boundary (so far, a turbulent inflow is realized from the left side only)
    3128     IF ( turbulent_inflow  .AND.  bc_lr /= 'dirichlet/radiation' )  THEN
     3125    IF ( turbulent_inflow  .AND.  bc_lr /= 'dirichlet/radiation' .AND.  bc_lr /= 'dirichlet/neumann' )  THEN
    31293126       message_string = 'turbulent_inflow = .T. requires a Dirichlet ' // &
    31303127                        'condition at the inflow boundary'
Note: See TracChangeset for help on using the changeset viewer.