Ignore:
Timestamp:
Mar 6, 2014 1:15:21 PM (10 years ago)
Author:
heinze
Message:

enable usage of large_scale subsidence in combination with large_scale_forcing

File:
1 edited

Legend:

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

    r1277 r1299  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Ensure a zero large scale vertical velocity at the surface
     23! Bugfix: typo in case of boundary condition in if-clause
    2324!
    2425! Former revisions:
     
    3940! ------------
    4041! Calculates large scale forcings (geostrophic wind and subsidence velocity) as
    41 ! well as surfaces fluxes dependend on time given in an external file (LSF_DATA).
     42! well as surfaces fluxes dependent on time given in an external file (LSF_DATA).
    4243! Code is based in parts on DALES and UCLA-LES.
    4344!--------------------------------------------------------------------------------!
     
    110111
    111112          IF ( ierrn < 0 )  THEN
    112             WRITE ( message_string, * ) 'No time dependend surface variables ',&
     113            WRITE ( message_string, * ) 'No time dependent surface variables ',&
    113114                              'in&LSF_DATA for end of run found'
    114115
     
    119120
    120121       IF ( time_surf(1) > end_time )  THEN
    121           WRITE ( message_string, * ) 'No time dependend surface variables in ',&
     122          WRITE ( message_string, * ) 'No time dependent surface variables in ',&
    122123                                     '&LSF_DATA for end of run found - ',  &
    123124                                     'lsf_surf is set to FALSE'
     
    146147             READ ( finput, *, IOSTAT=ierrn ) hash, time_vert(t)
    147148             IF ( ierrn < 0 )  THEN
    148                 WRITE( message_string, * ) 'No time dependend vertical profiles',&
     149                WRITE( message_string, * ) 'No time dependent vertical profiles',&
    149150                                 ' in&LSF_DATA for end of run found'
    150151                CALL message( 'ls_forcing', 'PA0372', 1, 2, 0, 6, 0 )
     
    158159          IF ( ierrn /= 0 )  THEN
    159160             message_string = 'errors in file LSF_DATA'
    160              CALL message( 'nudging', 'PA0369', 1, 2, 0, 6, 0 )
     161             CALL message( 'ls_forcing', 'PA0369', 1, 2, 0, 6, 0 )
    161162          ENDIF
    162163
     
    166167          IF ( ierrn /= 0 )  THEN
    167168             message_string = 'errors in file LSF_DATA'
    168              CALL message( 'nudging', 'PA0369', 1, 2, 0, 6, 0 )
     169             CALL message( 'ls_forcing', 'PA0369', 1, 2, 0, 6, 0 )
    169170          ENDIF
    170171
     
    183184                IF ( ierrn /= 0 )  THEN
    184185                   message_string = 'errors in file LSF_DATA'
    185                    CALL message( 'nudging', 'PA0369', 1, 2, 0, 6, 0 )
     186                   CALL message( 'ls_forcing', 'PA0369', 1, 2, 0, 6, 0 )
    186187                ENDIF
    187188
     
    200201       ENDDO
    201202
     203!
     204!--    Large scale vertical velocity has to be zero at the surface
     205       wsubs_vert(nzb,:) = 0.0
     206 
    202207       IF ( time_vert(1) > end_time )  THEN
    203208          WRITE ( message_string, * ) 'Time dependent large scale profile ',&
     
    262267          q_surface = q_surf(t) + fac * ( q_surf(t+1) - q_surf(t) )
    263268
    264        ELSEIF ( ibc_pt_b == 1 )  THEN
     269       ELSEIF ( ibc_q_b == 1 )  THEN
    265270
    266271          qsws = qsws_surf(t) + fac * ( qsws_surf(t+1) - qsws_surf(t) )
Note: See TracChangeset for help on using the changeset viewer.