Ignore:
Timestamp:
Apr 28, 2014 12:40:45 PM (10 years ago)
Author:
heinze
Message:

Upper boundary conditions for pt and q in case of nudging adjusted

File:
1 edited

Legend:

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

    r1366 r1380  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Subroutine nudge_ref added to account for proper upper scalar boundary
     23! conditions in case of nudging
    2324!
    2425! Former revisions:
     
    7273
    7374    PRIVATE
    74     PUBLIC init_nudge, calc_tnudge, nudge 
     75    PUBLIC init_nudge, calc_tnudge, nudge, nudge_ref
    7576    SAVE
    7677
     
    515516    END SUBROUTINE nudge_ij
    516517
     518
     519    SUBROUTINE nudge_ref ( time )
     520
     521       USE arrays_3d,                                                          &
     522           ONLY:  time_vert, ptnudge, pt_init, qnudge, q_init
     523
     524       USE kinds
     525
     526
     527       IMPLICIT NONE
     528
     529       INTEGER(iwp) ::  nt                    !:
     530
     531       REAL(wp)             ::  fac           !:
     532       REAL(wp), INTENT(in) ::  time          !:
     533
     534!
     535!--    Interpolation in time of NUDGING_DATA for pt_init and q_init. This is
     536!--    needed for correct upper boundary conditions for pt and q and in case that
     537!      large scale subsidence as well as scalar Rayleigh-damping are used
     538       nt = 1
     539       DO WHILE ( time > time_vert(nt) )
     540          nt = nt + 1
     541       ENDDO
     542       IF ( time /= time_vert(nt) )  THEN
     543        nt = nt - 1
     544       ENDIF
     545
     546       fac = ( time-time_vert(nt) ) / ( time_vert(nt+1)-time_vert(nt) )
     547
     548       pt_init = ptnudge(:,nt) + fac * ( ptnudge(:,nt+1) - ptnudge(:,nt) )
     549       q_init  = qnudge(:,nt) + fac * ( qnudge(:,nt+1) - qnudge(:,nt) )
     550
     551    END SUBROUTINE nudge_ref
     552
     553
    517554 END MODULE nudge_mod
Note: See TracChangeset for help on using the changeset viewer.