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'
File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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              ' ------------------------------'// &
Note: See TracChangeset for help on using the changeset viewer.