Ignore:
Timestamp:
Mar 19, 2007 8:20:46 AM (17 years ago)
Author:
raasch
Message:

preliminary changes for precipitation output

File:
1 edited

Legend:

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

    r63 r72  
    55! Actual revisions:
    66! -----------------
    7 ! +array rif_wall
     7! +arrays precipitation_amount, precipitation_rate, precipitation_rate_av,
     8! rif_wall, z0_av
    89! +loop_optimization, netcdf_64bit_3d, zu_s_inner, zw_w_inner, id_var_zusi_*,
    910! id_var_zwwi_*, ts_value, u_nzb_p1_for_vfc, v_nzb_p1_for_vfc, pt_reference,
    10 ! use_pt_reference,
     11! use_pt_reference, precipitation_amount_interval
    1112! +age_m in particle_type
    1213! -data_output_ts, dots_n
     
    128129!------------------------------------------------------------------------------!
    129130
    130     REAL, DIMENSION(:,:), ALLOCATABLE ::  lwp_av, ts_av, us_av
     131    REAL, DIMENSION(:,:), ALLOCATABLE ::  lwp_av, precipitation_rate_av, &
     132                                          ts_av, us_av, z0_av
    131133
    132134    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET :: &
     
    156158    REAL, DIMENSION(:), ALLOCATABLE :: hydro_press, pt_d_t, t_d_pt
    157159
     160    REAL, DIMENSION(:,:), ALLOCATABLE ::  precipitation_amount, &
     161                                          precipitation_rate
     162
    158163    SAVE
    159164
     
    211216    CHARACTER (LEN=8)   ::  run_date, run_time
    212217    CHARACTER (LEN=9)   ::  simulated_time_chr
    213     CHARACTER (LEN=12)  ::  version = 'PALM   3.1c'
     218    CHARACTER (LEN=12)  ::  version = 'PALM   3.2'
    214219    CHARACTER (LEN=16)  ::  loop_optimization = 'default', &
    215220                            momentum_advec = 'pw-scheme', &
     
    333338             overshoot_limit_u = 0.0, overshoot_limit_v = 0.0, &
    334339             overshoot_limit_w = 0.0, particle_maximum_age = 9999999.9, &
    335              phi = 55.0, prandtl_number = 1.0, pt_reference = 9999999.9, &
     340             phi = 55.0, prandtl_number = 1.0, &
     341             precipitation_amount_interval = 9999999.9, &
     342             pt_reference = 9999999.9, &
    336343             pt_slope_offset = 0.0, pt_surface = 300.0, &
    337344             pt_surface_initial_change = 0.0, q_surface = 0.0, &
Note: See TracChangeset for help on using the changeset viewer.