Ignore:
Timestamp:
Oct 29, 2013 10:11:53 AM (10 years ago)
Author:
heinze
Message:

routines for nudging and large scale forcing from external file added

File:
1 edited

Legend:

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

    r1116 r1239  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! hyp and rho have to be calculated at each time step if data from external
     23! file LSF_DATA are used
    2324!
    2425! Former revisions:
     
    103104
    104105       USE arrays_3d
    105        USE control_parameters
     106       USE cloud_parameters
     107       USE control_parameters
     108       USE grid_variables
    106109       USE indices
    107110       USE statistics
     
    296299       USE cloud_parameters
    297300       USE control_parameters
     301       USE grid_variables
     302       USE indices
    298303       USE statistics
    299304
    300305       IMPLICIT NONE
    301306
    302        INTEGER ::  i, j
     307       INTEGER ::  i, j, k
     308       REAL    ::  t_surface
     309
     310       IF ( large_scale_forcing .AND. lsf_surf ) THEN
     311!
     312!--       Calculate:
     313!--       pt / t : ratio of potential and actual temperature (pt_d_t)
     314!--       t / pt : ratio of actual and potential temperature (t_d_pt)
     315!--       p_0(z) : vertical profile of the hydrostatic pressure (hyp)
     316          t_surface = pt_surface * ( surface_pressure / 1000.0 )**0.286
     317          DO  k = nzb, nzt+1
     318             hyp(k)    = surface_pressure * 100.0 * &
     319                         ( (t_surface - g/cp * zu(k)) / t_surface )**(1.0/0.286)
     320             pt_d_t(k) = ( 100000.0 / hyp(k) )**0.286
     321             t_d_pt(k) = 1.0 / pt_d_t(k)
     322             hyrho(k)  = hyp(k) / ( r_d * t_d_pt(k) * pt_init(k) )       
     323          ENDDO
     324!
     325!--       Compute reference density
     326          rho_surface = surface_pressure * 100.0 / ( r_d * t_surface )
     327       ENDIF
     328
    303329
    304330       dt_micro = dt_3d * weight_pres(intermediate_timestep_count)
Note: See TracChangeset for help on using the changeset viewer.