Ignore:
Timestamp:
Feb 23, 2007 4:53:48 AM (17 years ago)
Author:
raasch
Message:

preliminary version of modified boundary conditions at top

File:
1 edited

Legend:

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

    r4 r19  
    44! Actual revisions:
    55! -----------------
    6 !
     6! Temperature and humidity gradients at top are now calculated for nzt+1,
     7! top_heatflux and respective boundary condition bc_pt_t is checked
    78!
    89! Former revisions:
     
    483484!--    Store temperature gradient at the top boundary for possile Neumann
    484485!--    boundary condition
    485        bc_pt_t_val = ( pt_init(nzt) - pt_init(nzt-1) ) / dzu(nzt)
     486       bc_pt_t_val = ( pt_init(nzt+1) - pt_init(nzt) ) / dzu(nzt+1)
    486487
    487488!
     
    539540!--       Store humidity gradient at the top boundary for possile Neumann
    540541!--       boundary condition
    541           bc_q_t_val = ( q_init(nzt) - q_init(nzt-1) ) / dzu(nzt)
     542          bc_q_t_val = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
    542543
    543544       ENDIF
     
    795796    ELSEIF ( bc_pt_t == 'neumann' )  THEN
    796797       ibc_pt_t = 1
     798    ELSEIF ( bc_pt_t == 'initial_gradient' )  THEN
     799       ibc_pt_t = 2
    797800    ELSE
    798801       IF ( myid == 0 )  THEN
     
    804807
    805808    IF ( surface_heatflux == 9999999.9 )  constant_heatflux = .FALSE.
     809    IF ( top_heatflux     == 9999999.9 )  THEN
     810       constant_top_heatflux = .FALSE.
     811    ELSE
     812       use_top_fluxes = .TRUE.    ! because this is currently the only choice
     813    ENDIF
    806814
    807815!
     
    823831          PRINT*, '    allowed with pt_surface_initial_change (/=0) = ', &
    824832                  pt_surface_initial_change
     833       ENDIF
     834       CALL local_stop
     835    ENDIF
     836
     837!
     838!-- A given temperature at the top implies Dirichlet boundary condition for
     839!-- temperature. In this case specification of a constant heat flux is
     840!-- forbidden.
     841    IF ( ibc_pt_t == 0  .AND.   constant_top_heatflux  .AND. &
     842         top_heatflux /= 0.0 )  THEN
     843       IF ( myid == 0 )  THEN
     844          PRINT*, '+++ check_parameters:'
     845          PRINT*, '    boundary_condition: bc_pt_t = ', bc_pt_t
     846          PRINT*, '    is not allowed with constant_top_heatflux = .TRUE.'
    825847       ENDIF
    826848       CALL local_stop
Note: See TracChangeset for help on using the changeset viewer.