Ignore:
Timestamp:
May 30, 2017 5:47:52 PM (7 years ago)
Author:
suehring
Message:

Adjustments according new topography and surface-modelling concept implemented

File:
1 edited

Legend:

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

    r2201 r2232  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Adjustments to new topography and surface concept
     23! Generic tunnel setup added
    2324!
    2425! Former revisions:
     
    293294
    294295    USE arrays_3d,                                                             &
    295         ONLY:  pt_init, qsws, q_init, s_init, sa_init, shf, ug, vg, w_subs, zu,&
    296                zw
     296        ONLY:  pt_init, q_init, s_init, sa_init, ug, vg, w_subs, zu, zw
    297297       
    298298    USE control_parameters
     
    320320 
    321321    USE land_surface_model_mod,                                                &
    322         ONLY: land_surface, lsm_header
     322        ONLY: lsm_header
    323323
    324324    USE microphysics_mod,                                                      &
     
    362362    USE spectra_mod,                                                           &
    363363        ONLY:  calculate_spectra, spectra_header
     364
     365    USE surface_mod,                                                           &
     366        ONLY:  surf_def_h
    364367
    365368    IMPLICIT NONE
     
    933936          ENDIF
    934937
     938       CASE ( 'tunnel' )
     939          IF ( tunnel_width_x /= 9999999.9_wp )  THEN
     940!
     941!--          Tunnel axis in y direction
     942             IF ( tunnel_length == 9999999.9_wp  .OR.                          &
     943                  tunnel_length >= ( nx + 1 ) * dx )  THEN
     944                WRITE ( io, 273 )  'y', tunnel_height, tunnel_wall_depth,      &
     945                                        tunnel_width_x
     946             ELSE
     947                WRITE ( io, 274 )  'y', tunnel_height, tunnel_wall_depth,      &
     948                                        tunnel_width_x, tunnel_length
     949             ENDIF
     950
     951          ELSEIF ( tunnel_width_y /= 9999999.9_wp )  THEN
     952!
     953!--          Tunnel axis in x direction
     954             IF ( tunnel_length == 9999999.9_wp  .OR.                          &
     955                  tunnel_length >= ( ny + 1 ) * dy )  THEN
     956                WRITE ( io, 273 )  'x', tunnel_height, tunnel_wall_depth,      &
     957                                        tunnel_width_y
     958             ELSE
     959                WRITE ( io, 274 )  'x', tunnel_height, tunnel_wall_depth,      &
     960                                        tunnel_width_y, tunnel_length
     961             ENDIF
     962          ENDIF
     963
    935964    END SELECT
    936965
     
    10651094       IF ( constant_heatflux )  THEN
    10661095          IF ( large_scale_forcing .AND. lsf_surf )  THEN
    1067              WRITE ( io, 306 )  shf(0,0)
     1096             IF ( surf_def_h(0)%ns >= 1 )  WRITE ( io, 306 )  surf_def_h(0)%shf(1)
    10681097          ELSE
    10691098             WRITE ( io, 306 )  surface_heatflux
     
    10731102       IF ( humidity  .AND.  constant_waterflux )  THEN
    10741103          IF ( large_scale_forcing .AND. lsf_surf )  THEN
    1075              WRITE ( io, 311 ) qsws(0,0)
     1104             WRITE ( io, 311 ) surf_def_h(0)%qsws(1)
    10761105          ELSE
    10771106             WRITE ( io, 311 ) surface_waterflux
     
    20242053              ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
    20252054              ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
     2055273 FORMAT (  ' Tunnel of infinite length in ',A, &
     2056              ' direction' / &
     2057              ' Tunnel height: ', F6.2, / &
     2058              ' Tunnel-wall depth: ', F6.2      / &
     2059              ' Tunnel width: ', F6.2 )
     2060274 FORMAT (  ' Tunnel in ', A, ' direction.' / &
     2061              ' Tunnel height: ', F6.2, / &   
     2062              ' Tunnel-wall depth: ', F6.2      / &
     2063              ' Tunnel width: ', F6.2, / &
     2064              ' Tunnel length: ', F6.2 )
    20262065278 FORMAT (' Topography grid definition convention:'/ &
    20272066            ' cell edge (staggered grid points'/  &
Note: See TracChangeset for help on using the changeset viewer.