Ignore:
Timestamp:
Mar 22, 2007 9:54:05 AM (17 years ago)
Author:
raasch
Message:

preliminary update for changes concerning non-cyclic boundary conditions

File:
1 edited

Legend:

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

    r73 r75  
    77! and counters,
    88! calls of prognostic_equations_.. changed to .._noopt, .._cache, and
    9 ! .._vector, these calls are now controlled by switch loop_optimization
     9! .._vector, these calls are now controlled by switch loop_optimization,
     10! uxrp, vynp eliminated, 2nd+3rd argument removed from exchange horiz,
     11! moisture renamed humidity
    1012!
    1113! Former revisions:
     
    136138!--       Exchange of ghost points (lateral boundary conditions)
    137139          CALL cpu_log( log_point(26), 'exchange-horiz-progn', 'start' )
    138           CALL exchange_horiz( u_p, uxrp,    0 )
    139           CALL exchange_horiz( v_p,    0, vynp )
    140           CALL exchange_horiz( w_p,    0,    0 )
    141           CALL exchange_horiz( pt_p,   0,    0 )
    142           IF ( .NOT. constant_diffusion       )  CALL exchange_horiz( e_p, 0, 0)
    143           IF ( moisture  .OR.  passive_scalar )  CALL exchange_horiz( q_p, 0, 0)
     140          CALL exchange_horiz( u_p )
     141          CALL exchange_horiz( v_p )
     142          CALL exchange_horiz( w_p )
     143          CALL exchange_horiz( pt_p )
     144          IF ( .NOT. constant_diffusion       )  CALL exchange_horiz( e_p )
     145          IF ( humidity  .OR.  passive_scalar )  CALL exchange_horiz( q_p )
    144146          IF ( cloud_droplets )  THEN
    145              CALL exchange_horiz( ql,    0, 0 )
    146              CALL exchange_horiz( ql_c,  0, 0 )
    147              CALL exchange_horiz( ql_v,  0, 0 )
    148              CALL exchange_horiz( ql_vp, 0, 0 )
     147             CALL exchange_horiz( ql )
     148             CALL exchange_horiz( ql_c )
     149             CALL exchange_horiz( ql_v )
     150             CALL exchange_horiz( ql_vp )
    149151          ENDIF
    150152
     
    182184             IF ( time_disturb >= dt_disturb )  THEN
    183185                IF ( hom(nzb+5,1,var_hom,0) < disturbance_energy_limit )  THEN
    184                    CALL disturb_field( nzb_u_inner, tend, u, uxrp, 0    )
    185                    CALL disturb_field( nzb_v_inner, tend, v ,   0, vynp )
     186                   CALL disturb_field( nzb_u_inner, tend, u )
     187                   CALL disturb_field( nzb_v_inner, tend, v )
    186188                ELSEIF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
    187189!
     
    189191!--                near the inflow throughout the whole simulation
    190192                   dist_range = 1
    191                    CALL disturb_field( nzb_u_inner, tend, u, uxrp, 0    )
    192                    CALL disturb_field( nzb_v_inner, tend, v ,   0, vynp )
     193                   CALL disturb_field( nzb_u_inner, tend, u )
     194                   CALL disturb_field( nzb_v_inner, tend, v )
    193195                   dist_range = 0
    194196                ENDIF
     
    208210!--       In case of a non-cyclic lateral wall, set the boundary conditions for
    209211!--       the velocities at the outflow
    210           IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
    211              CALL boundary_conds( 'outflow_uvw' )
    212           ENDIF
     212!          IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
     213!             CALL boundary_conds( 'outflow_uvw' )
     214!          ENDIF
    213215
    214216!
    215217!--       If required, compute virtuell potential temperature
    216           IF ( moisture ) CALL compute_vpt
     218          IF ( humidity ) CALL compute_vpt
    217219
    218220!
     
    235237!--          Compute the diffusion coefficients
    236238             CALL cpu_log( log_point(17), 'diffusivities', 'start' )
    237              IF ( .NOT. moisture ) THEN
     239             IF ( .NOT. humidity ) THEN
    238240                CALL diffusivities( pt )
    239241             ELSE
Note: See TracChangeset for help on using the changeset viewer.