Changeset 240 for palm/trunk/SOURCE


Ignore:
Timestamp:
Feb 18, 2009 5:50:38 PM (15 years ago)
Author:
letzel
Message:
  • External pressure gradient (check_parameters, init_3d_model, header, modules, parin, prognostic_equations)
  • New topography case 'single_street_canyon'
Location:
palm/trunk/SOURCE
Files:
13 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/CURRENT_MODIFICATIONS

    r239 r240  
    55for buildings can be chosen with parameter cluster_size. (init_dvrp)
    66
    7 init_dvrp, header, modules, package_parin
     7External pressure gradient (check_parameters, header, init_3d_model, modules,
     8parin, prognostic_equations, read_var_list, write_var_list)
     9
     10New topography case 'single_street_canyon' (header, init_grid, modules, parin,
     11read_var_list, user_check_parameters, user_header, user_init_grid, write_var_list)
     12
     13check_parameters, init_dvrp, init_grid, init_3d_model, header, modules, package_parin, parin, prognostic_equations, read_var_list, user_check_parameters, user_header, user_init_grid, write_var_list
    814
    915
  • palm/trunk/SOURCE/check_parameters.f90

    r232 r240  
    55! -----------------
    66! Bugfix: pressure included for profile output
     7! Check pressure gradient conditions
    78!
    89! Former revisions:
     
    28162817
    28172818!
     2819!-- Check pressure gradient conditions
     2820    IF ( dp_external .AND. conserve_volume_flow )  THEN
     2821       WRITE( message_string, * )  'Both dp_external and conserve_volume_flow', &
     2822            ' are .TRUE. but one of them must be .FALSE.'
     2823       CALL message( 'check_parameters', 'PA0150', 1, 2, 0, 6, 0 )
     2824    ENDIF
     2825    IF ( dp_external )  THEN
     2826       IF ( dp_level_b < zu(nzb) .OR. dp_level_b > zu(nzt) )  THEN
     2827          WRITE( message_string, * )  'dp_level_b = ', dp_level_b, ' is out ', &
     2828               ' of range'
     2829          CALL message( 'check_parameters', 'PA0151', 1, 2, 0, 6, 0 )
     2830       ENDIF
     2831       IF ( .NOT. ANY( dpdxy /= 0.0 ) )  THEN
     2832          WRITE( message_string, * )  'dp_external is .TRUE. but dpdxy is zero',&
     2833               ', i.e. the external pressure gradient & will not be applied'
     2834          CALL message( 'check_parameters', 'PA0152', 0, 1, 0, 6, 0 )
     2835       ENDIF
     2836    ENDIF
     2837    IF ( ANY( dpdxy /= 0.0 ) .AND. .NOT. dp_external )  THEN
     2838       WRITE( message_string, * )  'dpdxy is nonzero but dp_external is ', &
     2839            '.FALSE., i.e. the external pressure gradient & will not be applied'
     2840       CALL message( 'check_parameters', 'PA0153', 0, 1, 0, 6, 0 )
     2841    ENDIF
     2842
     2843!
    28182844!-- Check &userpar parameters
    28192845    CALL user_check_parameters
  • palm/trunk/SOURCE/header.f90

    r237 r240  
    55! -----------------
    66! Output of cluster_size
     7! +dp_external, dp_level_b, dp_smooth, dpdxy
     8! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
     9! canyon_wall_south
    710!
    811! Former revisions:
     
    99102    CHARACTER (LEN=85) ::  roben, runten
    100103
    101     INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, i, ihost, io, j, l, ll
     104    INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, cwx, cwy, cxl, cxr, &
     105         cyn, cys, i, ihost, io, j, l, ll
    102106    REAL    ::  cpuseconds_per_simulated_second
    103107
     
    285289    ENDIF
    286290    IF ( passive_scalar )  WRITE ( io, 134 )
    287     IF ( conserve_volume_flow )  WRITE ( io, 150 )
     291    IF ( conserve_volume_flow )  THEN
     292       WRITE ( io, 150 )
     293    ELSEIF ( dp_external )  THEN
     294       IF ( dp_smooth )  THEN
     295          WRITE ( io, 151 ) dpdxy, dp_level_b, ', vertically smoothed.'
     296       ELSE
     297          WRITE ( io, 151 ) dpdxy, dp_level_b, '.'
     298       ENDIF
     299    ENDIF
    288300    WRITE ( io, 99 )
    289301
     
    381393          WRITE ( io, 271 )  building_length_x, building_length_y, &
    382394                             building_height, bxl, bxr, bys, byn
     395
     396       CASE ( 'single_street_canyon' )
     397          ch  = NINT( canyon_height / dz )
     398          IF ( canyon_width_x /= 9999999.9 )  THEN
     399!
     400!--          Street canyon in y direction
     401             cwx = NINT( canyon_width_x / dx )
     402             IF ( canyon_wall_left == 9999999.9 )  THEN
     403                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
     404             ENDIF
     405             cxl = NINT( canyon_wall_left / dx )
     406             cxr = cxl + cwx
     407             WRITE ( io, 272 )  'y', canyon_height, ch, 'u', cxl, cxr
     408
     409          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
     410!
     411!--          Street canyon in x direction
     412             cwy = NINT( canyon_width_y / dy )
     413             IF ( canyon_wall_south == 9999999.9 )  THEN
     414                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
     415             ENDIF
     416             cys = NINT( canyon_wall_south / dy )
     417             cyn = cys + cwy
     418             WRITE ( io, 272 )  'x', canyon_height, ch, 'v', cys, cyn
     419          ENDIF
    383420
    384421    END SELECT
     
    13701407150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
    13711408                  'conserved')
     1409151 FORMAT (' --> External pressure gradient directly prescribed by the user:'/, &
     1410              2(1X,E12.5),'Pa/m', &
     1411             ' in x/y direction starting from dp_level_b =', F6.3, 'm', &
     1412             A /)
    13721413200 FORMAT (//' Run time and time step information:'/ &
    13731414             ' ----------------------------------'/)
     
    14071448              ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
    14081449                ' / ',I4)
     1450272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
     1451              ' direction' / &
     1452              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
     1453              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
    14091454280 FORMAT (//' Vegetation canopy (drag) model:'/ &
    14101455              ' ------------------------------'// &
  • palm/trunk/SOURCE/init_3d_model.f90

    r198 r240  
    77! Actual revisions:
    88! -----------------
    9 !
     9! Set the starting level and the vertical smoothing factor used for
     10! the external pressure gradient
    1011!
    1112! Former revisions:
     
    9192    IMPLICIT NONE
    9293
    93     INTEGER ::  i, j, k, sr
     94    INTEGER ::  i, ind_array(1), j, k, sr
    9495
    9596    INTEGER, DIMENSION(:), ALLOCATABLE ::  ngp_2dh_l, ngp_3d_inner_l
     
    111112              sums_divnew_l(0:statistic_regions),                           &
    112113              sums_divold_l(0:statistic_regions) )
    113     ALLOCATE( rdf(nzb+1:nzt) )
     114    ALLOCATE( dp_smooth_factor(nzb:nzt), rdf(nzb+1:nzt) )
    114115    ALLOCATE( ngp_2dh_outer(nzb:nzt+1,0:statistic_regions),                 &
    115116              ngp_2dh_outer_l(nzb:nzt+1,0:statistic_regions),               &
     
    12641265
    12651266!
     1267!-- Initialize the starting level and the vertical smoothing factor used for
     1268!-- the external pressure gradient
     1269    dp_smooth_factor = 1.0
     1270    IF ( dp_external )  THEN
     1271!
     1272!--    Set the starting level dp_level_ind_b only if it has not been set before
     1273!--    (e.g. in init_grid).
     1274       IF ( dp_level_ind_b == 0 )  THEN
     1275          ind_array = MINLOC( ABS( dp_level_b - zu ) )
     1276          dp_level_ind_b = ind_array(1) - 1 + nzb
     1277                                        ! MINLOC uses lower array bound 1
     1278       ENDIF
     1279       IF ( dp_smooth )  THEN
     1280          dp_smooth_factor(:dp_level_ind_b) = 0.0
     1281          DO  k = dp_level_ind_b+1, nzt
     1282             dp_smooth_factor(k) = 0.5 * ( 1.0 + SIN( pi * &
     1283                  ( REAL( k - dp_level_ind_b ) /  &
     1284                    REAL( nzt - dp_level_ind_b ) - 0.5 ) ) )
     1285          ENDDO
     1286       ENDIF
     1287    ENDIF
     1288
     1289!
    12661290!-- Initialize diffusivities used within the outflow damping layer in case of
    12671291!-- non-cyclic lateral boundaries. A linear increase is assumed over the first
  • palm/trunk/SOURCE/init_grid.f90

    r226 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! new topography case 'single_street_canyon'
    77!
    88! Former revisions:
     
    5454    IMPLICIT NONE
    5555
    56     INTEGER ::  bh, blx, bly, bxl, bxr, byn, bys, gls, i, inc, i_center, j, &
    57                 j_center, k, l, nxl_l, nxr_l, nyn_l, nys_l, nzb_si, nzt_l, vi
     56    INTEGER ::  bh, blx, bly, bxl, bxr, byn, bys, ch, cwx, cwy, cxl, cxr, cyn, &
     57                cys, gls, i, inc, i_center, j, j_center, k, l, nxl_l, nxr_l, &
     58                nyn_l, nys_l, nzb_si, nzt_l, vi
    5859
    5960    INTEGER, DIMENSION(:), ALLOCATABLE   ::  vertical_influence
     
    379380          nzb_local(bys:byn,bxl:bxr) = bh
    380381
     382       CASE ( 'single_street_canyon' )
     383!
     384!--       Single quasi-2D street canyon of infinite length in x or y direction.
     385!--       The canyon is centered in the other direction by default.
     386          IF ( canyon_width_x /= 9999999.9 )  THEN
     387!
     388!--          Street canyon in y direction
     389             cwx = NINT( canyon_width_x / dx )
     390             IF ( canyon_wall_left == 9999999.9 )  THEN
     391                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
     392             ENDIF
     393             cxl = NINT( canyon_wall_left / dx )
     394             cxr = cxl + cwx
     395
     396          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
     397!
     398!--          Street canyon in x direction
     399             cwy = NINT( canyon_width_y / dy )
     400             IF ( canyon_wall_south == 9999999.9 )  THEN
     401                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
     402             ENDIF
     403             cys = NINT( canyon_wall_south / dy )
     404             cyn = cys + cwy
     405
     406          ELSE
     407             IF ( myid == 0 )  THEN
     408                PRINT*, '+++ user_init_grid: no street canyon width given'
     409             ENDIF
     410             CALL local_stop
     411          ENDIF
     412
     413          ch             = NINT( canyon_height / dz )
     414          dp_level_ind_b = ch
     415!
     416!--       Street canyon size has to meet some requirements
     417          IF ( canyon_width_x /= 9999999.9 )  THEN
     418             IF ( ( cxl < 1 ) .OR. ( cxr > nx-1 ) .OR. ( cwx < 3 ) .OR.  &
     419               ( ch < 3 ) )  THEN
     420                IF ( myid == 0 )  THEN
     421                   PRINT*, '+++ user_init_grid: inconsistent canyon parameters:'
     422                   PRINT*, '                    cxl=', cxl, 'cxr=', cxr,  &
     423                                              'cwx=', cwx,  &
     424                                              'ch=', ch, 'nx=', nx, 'ny=', ny
     425                ENDIF
     426                CALL local_stop
     427             ENDIF
     428          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
     429             IF ( ( cys < 1 ) .OR. ( cyn > ny-1 ) .OR. ( cwy < 3 ) .OR.  &
     430               ( ch < 3 ) )  THEN
     431                IF ( myid == 0 )  THEN
     432                   PRINT*, '+++ user_init_grid: inconsistent canyon parameters:'
     433                   PRINT*, '                    cys=', cys, 'cyn=', cyn,  &
     434                                              'cwy=', cwy,  &
     435                                              'ch=', ch, 'nx=', nx, 'ny=', ny
     436                ENDIF
     437                CALL local_stop
     438             ENDIF
     439          ENDIF
     440          IF ( canyon_width_x /= 9999999.9 .AND. canyon_width_y /= 9999999.9 )  &
     441               THEN
     442             IF ( myid == 0 )  THEN
     443                PRINT*, '+++ user_init_grid: inconsistent canyon parameters:'
     444                PRINT*, '                    street canyon can only be oriented'
     445                PRINT*, '                    either in x- or in y-direction'
     446             ENDIF
     447             CALL local_stop
     448          ENDIF
     449
     450          nzb_local = ch
     451          IF ( canyon_width_x /= 9999999.9 )  THEN
     452             nzb_local(:,cxl+1:cxr-1) = 0
     453          ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
     454             nzb_local(cys+1:cyn-1,:) = 0
     455          ENDIF
     456
    381457       CASE ( 'read_from_file' )
    382458!
  • palm/trunk/SOURCE/modules.f90

    r237 r240  
    66! -----------------
    77! +cluster_size in dvrp_variables
     8! +dp_external, dp_level_b, dp_level_ind_b, dp_smooth, dp_smooth_factor, dpdxy,
     9! in control_parameters
     10! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
     11! canyon_wall_south in control_parameters
    812!
    913! Former revisions:
     
    313317                dosp_time_count = 0, dots_time_count = 0, &
    314318                do2d_xy_n = 0, do2d_xz_n = 0, do2d_yz_n = 0, do3d_avs_n = 0, &
     319                dp_level_ind_b = 0, &
    315320                dvrp_filecount = 0, dz_stretch_level_index, gamma_mg, &
    316321                grid_level, ibc_e_b, ibc_p_b, ibc_p_t, ibc_pt_b, ibc_pt_t, &
     
    323328                nsor_ini = 100, n_sor, normalizing_region = 0, &
    324329                nz_do1d, nz_do3d = -9999, outflow_damping_width = -1, &
    325                 prt_time_count = 0, recycling_plane, runnr = 0, &
     330                pch_index = 0, prt_time_count = 0, recycling_plane, runnr = 0, &
    326331                skip_do_avs = 0, terminate_coupled = 0, &
    327332                terminate_coupled_remote = 0, timestep_count = 0
     
    332337                do3d_no(0:1) = 0, do3d_time_count(0:1), &
    333338                lad_vertical_gradient_level_ind(10) = -9999, &
    334                 pch_index = 0, &
    335339                pt_vertical_gradient_level_ind(10) = -9999, &
    336340                q_vertical_gradient_level_ind(10) = -9999, &
     
    354358                data_output_2d_on_each_pe = .TRUE., do2d_at_begin = .FALSE., &
    355359                do3d_at_begin = .FALSE., do3d_compress = .FALSE., &
    356                 do_sum = .FALSE., dt_changed = .FALSE., dt_fixed = .FALSE., &
     360                do_sum = .FALSE., dp_external = .FALSE., dp_smooth = .FALSE., &
     361                dt_changed = .FALSE., dt_fixed = .FALSE., &
    357362                disturbance_created = .FALSE., &
    358363                first_call_advec_particles = .TRUE., &
     
    388393             building_height = 50.0, building_length_x = 50.0, &
    389394             building_length_y = 50.0, building_wall_left = 9999999.9, &
    390              building_wall_south = 9999999.9, cthf = 0.0, cfl_factor = -1.0, &
     395             building_wall_south = 9999999.9, canyon_height = 50.0, &
     396             canyon_width_x = 9999999.9, canyon_width_y = 9999999.9, &
     397             canyon_wall_left = 9999999.9, canyon_wall_south = 9999999.9, &
     398             cthf = 0.0, cfl_factor = -1.0, &
    391399             cos_alpha_surface, disturbance_amplitude = 0.25, &
    392400             disturbance_energy_limit = 0.01, &
    393401             disturbance_level_b = -9999999.9, &
    394402             disturbance_level_t = -9999999.9, &
    395              drag_coefficient = 0.0, &
     403             dp_level_b = 0.0, drag_coefficient = 0.0, &
    396404             dt = -1.0, dt_averaging_input = 0.0, &
    397405             dt_averaging_input_pr = 9999999.9, dt_coupling = 9999999.9, &
     
    452460
    453461    REAL ::  do2d_xy_last_time(0:1) = -1.0, do2d_xz_last_time(0:1) = -1.0, &
    454              do2d_yz_last_time(0:1) = -1.0, &
     462             do2d_yz_last_time(0:1) = -1.0, dpdxy(1:2) = 0.0, &
    455463             lad_vertical_gradient(10) = 0.0, &
    456464             lad_vertical_gradient_level(10) = -9999999.9, &
     
    472480             wall_humidityflux(0:4) = 0.0, wall_qflux(0:4) = 0.0, &
    473481             wall_salinityflux(0:4) = 0.0, wall_scalarflux(0:4) = 0.0
     482
     483    REAL, DIMENSION(:), ALLOCATABLE ::  dp_smooth_factor
    474484
    475485
  • palm/trunk/SOURCE/parin.f90

    r199 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
     7! canyon_wall_south, dp_external, dp_level_b, dp_smooth, dpdxy in inipar
    78!
    89! Former revisions:
     
    8485             bc_q_t,bc_s_b, bc_s_t, bc_sa_t, bc_uv_b, bc_uv_t, &
    8586             bottom_salinityflux, building_height, building_length_x, &
    86              building_length_y, building_wall_left, &
    87              building_wall_south, canopy_mode, cloud_droplets, cloud_physics, &
    88              conserve_volume_flow, cthf, cut_spline_overshoot, damp_level_1d, &
    89              dissipation_1d, drag_coefficient, dt, dt_pr_1d, &
     87             building_length_y, building_wall_left, building_wall_south, &
     88             canopy_mode, canyon_height, canyon_width_x, canyon_width_y, &
     89             canyon_wall_left, canyon_wall_south, cloud_droplets, &
     90             cloud_physics, conserve_volume_flow, cthf, cut_spline_overshoot, &
     91             damp_level_1d, dissipation_1d, dp_external, dp_level_b, &
     92             dp_smooth, dpdxy, drag_coefficient, dt, dt_pr_1d, &
    9093             dt_run_control_1d, dx, dy, dz, dz_max, dz_stretch_factor, &
    9194             dz_stretch_level, e_init, e_min, end_time_1d, fft_method, &
  • palm/trunk/SOURCE/prognostic_equations.f90

    r198 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! external pressure gradient
    77!
    88! Former revisions:
     
    173173!--       Drag by plant canopy
    174174          IF ( plant_canopy )  CALL plant_canopy_model( i, j, 1 )
     175
     176!
     177!--       External pressure gradient
     178          IF ( dp_external )  THEN
     179             DO  k = dp_level_ind_b+1, nzt
     180                tend(k,j,i) = tend(k,j,i) - dpdxy(1) * dp_smooth_factor(k)
     181             ENDDO
     182          ENDIF
     183
    175184          CALL user_actions( i, j, 'u-tendency' )
    176185
     
    244253!--       Drag by plant canopy
    245254          IF ( plant_canopy )  CALL plant_canopy_model( i, j, 2 )     
     255
     256!
     257!--       External pressure gradient
     258          IF ( dp_external )  THEN
     259             DO  k = dp_level_ind_b+1, nzt
     260                tend(k,j,i) = tend(k,j,i) - dpdxy(2) * dp_smooth_factor(k)
     261             ENDDO
     262          ENDIF
    246263
    247264          CALL user_actions( i, j, 'v-tendency' )
     
    878895             IF ( plant_canopy )  CALL plant_canopy_model( i, j, 1 )
    879896
     897!
     898!--          External pressure gradient
     899             IF ( dp_external )  THEN
     900                DO  k = dp_level_ind_b+1, nzt
     901                   tend(k,j,i) = tend(k,j,i) - dpdxy(1) * dp_smooth_factor(k)
     902                ENDDO
     903             ENDIF
     904
    880905             CALL user_actions( i, j, 'u-tendency' )
    881906
     
    931956!--          Drag by plant canopy
    932957             IF ( plant_canopy )  CALL plant_canopy_model( i, j, 2 )       
     958
     959!
     960!--          External pressure gradient
     961             IF ( dp_external )  THEN
     962                DO  k = dp_level_ind_b+1, nzt
     963                   tend(k,j,i) = tend(k,j,i) - dpdxy(2) * dp_smooth_factor(k)
     964                ENDDO
     965             ENDIF
    933966
    934967             CALL user_actions( i, j, 'v-tendency' )
     
    13471380    IF ( plant_canopy )  CALL plant_canopy_model( 1 )
    13481381
     1382!
     1383!-- External pressure gradient
     1384    IF ( dp_external )  THEN
     1385       DO  i = nxlu, nxr
     1386          DO  j = nys, nyn
     1387             DO  k = dp_level_ind_b+1, nzt
     1388                tend(k,j,i) = tend(k,j,i) - dpdxy(1) * dp_smooth_factor(k)
     1389             ENDDO
     1390          ENDDO
     1391       ENDDO
     1392    ENDIF
     1393
    13491394    CALL user_actions( 'u-tendency' )
    13501395
     
    14221467!-- Drag by plant canopy
    14231468    IF ( plant_canopy )  CALL plant_canopy_model( 2 )
     1469
     1470!
     1471!-- External pressure gradient
     1472    IF ( dp_external )  THEN
     1473       DO  i = nxl, nxr
     1474          DO  j = nysv, nyn
     1475             DO  k = dp_level_ind_b+1, nzt
     1476                tend(k,j,i) = tend(k,j,i) - dpdxy(2) * dp_smooth_factor(k)
     1477             ENDDO
     1478          ENDDO
     1479       ENDDO
     1480    ENDIF
     1481
    14241482    CALL user_actions( 'v-tendency' )
    14251483
  • palm/trunk/SOURCE/read_var_list.f90

    r226 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
     7! canyon_wall_south, dp_external, dp_level_b, dp_smooth, dpdxy
    78!
    89! Former revisions:
     
    8081!-- Make version number check first
    8182    READ ( 13 )  version_on_file
    82     binary_version = '3.2'
     83    binary_version = '3.3'
    8384    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
    8485       IF ( myid == 0 )  THEN
     
    223224          CASE ( 'canopy_mode' )
    224225             READ ( 13 )  canopy_mode
     226          CASE ( 'canyon_height' )
     227             READ ( 13 )  canyon_height
     228          CASE ( 'canyon_width_x' )
     229             READ ( 13 )  canyon_width_x
     230          CASE ( 'canyon_width_y' )
     231             READ ( 13 )  canyon_width_y
     232          CASE ( 'canyon_wall_left' )
     233             READ ( 13 )  canyon_wall_left
     234          CASE ( 'canyon_wall_south' )
     235             READ ( 13 )  canyon_wall_south
    225236          CASE ( 'cloud_droplets' )
    226237             READ ( 13 )  cloud_droplets
     
    239250          CASE ( 'dissipation_1d' )
    240251             READ ( 13 )  dissipation_1d
     252          CASE ( 'dp_external' )
     253             READ ( 13 )  dp_external
     254          CASE ( 'dp_level_b' )
     255             READ ( 13 )  dp_level_b
     256          CASE ( 'dp_smooth' )
     257             READ ( 13 )  dp_smooth
     258          CASE ( 'dpdxy' )
     259             READ ( 13 )  dpdxy
    241260          CASE ( 'drag_coefficient' )
    242261             READ ( 13 )  drag_coefficient
  • palm/trunk/SOURCE/user_check_parameters.f90

    r226 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! add default topography_grid_convention for the new topography case
     7! 'single_street_canyon'
    78!
    89! Former revisions:
     
    3031       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
    3132          IF ( TRIM( topography ) /= 'single_building' .AND.  &
     33               TRIM( topography ) /= 'single_street_canyon' .AND.  &
    3234               TRIM( topography ) /= 'read_from_file' )  THEN
    3335!--          The default value is not applicable here, because it is only valid
    3436!--          for the two standard cases 'single_building' and 'read_from_file'
    3537!--          defined in init_grid.
    36              message_string = 'The value for "topography_grid_convention" '//  &
    37                   'is not set. Its default value is & only valid for '//  &
    38                   '"topography" = ''single_building'' or ''read_from_file''.'//&
     38             WRITE( message_string, * )  &
     39                  'The value for "topography_grid_convention" ',  &
     40                  'is not set. Its default value is & only valid for ',  &
     41                  '"topography" = ''single_building'', ',  &
     42                  '''single_street_canyon'' & or ''read_from_file''.',  &
    3943                  ' & Choose ''cell_edge'' or ''cell_center''.'
    4044             CALL message( 'user_check_parameters', 'UI0001', 1, 2, 0, 6, 0 )
     
    4246!--          The default value is applicable here.
    4347!--          Set convention according to topography.
    44              IF ( TRIM( topography ) == 'single_building' )  THEN
     48             IF ( TRIM( topography ) == 'single_building' .OR.  &
     49                  TRIM( topography ) == 'single_street_canyon' )  THEN
    4550                topography_grid_convention = 'cell_edge'
    4651             ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
     
    5055       ELSEIF ( TRIM( topography_grid_convention ) /= 'cell_edge' .AND.  &
    5156                TRIM( topography_grid_convention ) /= 'cell_center' )  THEN
    52           message_string = 'The value for "topography_grid_convention" is '// &
     57          WRITE( message_string, * )  &
     58               'The value for "topography_grid_convention" is ', &
    5359               'not recognized. & Choose ''cell_edge'' or ''cell_center''.'
    5460          CALL message( 'user_check_parameters', 'UI0002', 1, 2, 0, 6, 0 )
  • palm/trunk/SOURCE/user_header.f90

    r226 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! new topography case 'single_street_canyon'
    77!
    88! Former revisions:
     
    4949       WRITE ( io, 300 )
    5050       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
    51           IF ( TRIM( topography ) == 'single_building' )  THEN
     51          IF ( TRIM( topography ) == 'single_building' .OR.  &
     52               TRIM( topography ) == 'single_street_canyon' )  THEN
    5253             WRITE ( io, 301 )
    5354          ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
  • palm/trunk/SOURCE/user_init_grid.f90

    r226 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! add 'single_street_canyon' as standard topography case
    77!
    88! Former revisions:
     
    3939    SELECT CASE ( TRIM( topography ) )
    4040
    41        CASE ( 'flat', 'single_building' )
     41       CASE ( 'flat', 'single_building', 'single_street_canyon' )
    4242!
    4343!--       Not allowed here since these are the standard cases used in init_grid.
  • palm/trunk/SOURCE/write_var_list.f90

    r198 r240  
    44! Actual revisions:
    55! -----------------
    6 !
     6! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
     7! canyon_wall_south, dp_external, dp_level_b, dp_smooth, dpdxy
    78!
    89! Former revisions:
     
    7071
    7172
    72     binary_version = '3.2'
     73    binary_version = '3.3'
    7374
    7475    WRITE ( 14 )  binary_version
     
    151152    WRITE ( 14 )  'canopy_mode                   '
    152153    WRITE ( 14 )  canopy_mode
     154    WRITE ( 14 )  'canyon_height                 '
     155    WRITE ( 14 )  canyon_height
     156    WRITE ( 14 )  'canyon_width_x                '
     157    WRITE ( 14 )  canyon_width_x
     158    WRITE ( 14 )  'canyon_width_y                '
     159    WRITE ( 14 )  canyon_width_y
     160    WRITE ( 14 )  'canyon_wall_left              '
     161    WRITE ( 14 )  canyon_wall_left
     162    WRITE ( 14 )  'canyon_wall_south             '
     163    WRITE ( 14 )  canyon_wall_south
    153164    WRITE ( 14 )  'cloud_droplets                '
    154165    WRITE ( 14 )  cloud_droplets
     
    167178    WRITE ( 14 )  'dissipation_1d                '
    168179    WRITE ( 14 )  dissipation_1d
     180    WRITE ( 14 )  'dp_external                   '
     181    WRITE ( 14 )  dp_external
     182    WRITE ( 14 )  'dp_level_b                    '
     183    WRITE ( 14 )  dp_level_b
     184    WRITE ( 14 )  'dp_smooth                     '
     185    WRITE ( 14 )  dp_smooth
     186    WRITE ( 14 )  'dpdxy                         '
     187    WRITE ( 14 )  dpdxy
    169188    WRITE ( 14 )  'drag_coefficient              '
    170189    WRITE ( 14 )  drag_coefficient
Note: See TracChangeset for help on using the changeset viewer.