source: palm/trunk/SOURCE/calc_precipitation.f90 @ 154

Last change on this file since 154 was 77, checked in by raasch, 17 years ago

New:
---

particle reflection from vertical walls implemented, particle SGS model adjusted to walls

Wall functions for vertical walls now include diabatic conditions. New subroutines wall_fluxes, wall_fluxes_e. New 4D-array rif_wall.

new d3par-parameter netcdf_64bit_3d to switch on 64bit offset only for 3D files

new d3par-parameter dt_max to define the maximum value for the allowed timestep

new inipar-parameter loop_optimization to control the loop optimization method

new inipar-parameter pt_refrence. If given, this value is used as the reference that in buoyancy terms (otherwise, the instantaneous horizontally averaged temperature is used).

new user interface user_advec_particles

new initializing action "by_user" calls user_init_3d_model and allows the initial setting of all 3d arrays

topography height informations are stored on arrays zu_s_inner and zw_w_inner and output to the 2d/3d NetCDF files

samples added to the user interface which show how to add user-define time series quantities.

calculation/output of precipitation amount, precipitation rate and z0 (by setting "pra*", "prr*", "z0*" with data_output). The time interval on which the precipitation amount is defined is set by new d3par-parameter precipitation_amount_interval

unit 9 opened for debug output (file DEBUG_<pe#>)

Makefile, advec_particles, average_3d_data, buoyancy, calc_precipitation, check_open, check_parameters, data_output_2d, diffusion_e, diffusion_u, diffusion_v, diffusion_w, diffusivities, header, impact_of_latent_heat, init_particles, init_3d_model, modules, netcdf, parin, production_e, read_var_list, read_3d_binary, sum_up_3d_data, user_interface, write_var_list, write_3d_binary

New: wall_fluxes

Changed:


General revision of non-cyclic horizontal boundary conditions: radiation boundary conditions are now used instead of Neumann conditions at the outflow (calculation needs velocity values for t-dt, which are stored on new arrays u_m_l, u_m_r, etc.), calculation of mean outflow is not needed any more, volume flow control is added for the outflow boundary (currently only for the north boundary!!), additional gridpoints along x and y (uxrp, vynp) are not needed any more, routine "boundary_conds" now operates on timelevel t+dt and is not split in two parts (main, uvw_outflow) any more, Neumann boundary conditions at inflow/outflow in case of non-cyclic boundary conditions for all 2d-arrays that are handled by exchange_horiz_2d

The FFT-method for solving the Poisson-equation is now working with Neumann boundary conditions both at the bottom and the top. This requires adjustments of the tridiagonal coefficients and subtracting the horizontally averaged mean from the vertical velocity field.

+age_m in particle_type

Particles-package is now part of the default code ("-p particles" is not needed any more).

Move call of user_actions( 'after_integration' ) below increment of times
and counters. user_actions is now called for each statistic region and has as an argument the number of the respective region (sr)

d3par-parameter data_output_ts removed. Timeseries output for "profil" removed. Timeseries are now switched on by dt_dots. Timeseries data is collected in flow_statistics.

Initial velocities at nzb+1 are regarded for volume flow control in case they have been set zero before (to avoid small timesteps); see new internal parameters u/v_nzb_p1_for_vfc.

q is not allowed to become negative (prognostic_equations).

poisfft_init is only called if fft-solver is switched on (init_pegrid).

d3par-parameter moisture renamed to humidity.

Subversion global revision number is read from mrun and added to the run description header and to the run control (_rc) file.

vtk directives removed from main program.

The uitility routine interpret_config reads PALM environment variables from NAMELIST instead using the system call GETENV.

advec_u_pw, advec_u_up, advec_v_pw, advec_v_up, asselin_filter, check_parameters, coriolis, data_output_dvrp, data_output_ptseries, data_output_ts, data_output_2d, data_output_3d, diffusion_u, diffusion_v, exchange_horiz, exchange_horiz_2d, flow_statistics, header, init_grid, init_particles, init_pegrid, init_rankine, init_pt_anomaly, init_1d_model, init_3d_model, modules, palm, package_parin, parin, poisfft, poismg, prandtl_fluxes, pres, production_e, prognostic_equations, read_var_list, read_3d_binary, sor, swap_timelevel, time_integration, write_var_list, write_3d_binary

Errors:


Bugfix: preset of tendencies te_em, te_um, te_vm in init_1d_model

Bugfix in sample for reading user defined data from restart file (user_init)

Bugfix in setting diffusivities for cases with the outflow damping layer extending over more than one subdomain (init_3d_model)

Check for possible negative humidities in the initial humidity profile.

in Makefile, default suffixes removed from the suffix list to avoid calling of m2c in
# case of .mod files

Makefile
check_parameters, init_1d_model, init_3d_model, user_interface

  • Property svn:keywords set to Id
File size: 4.2 KB
Line 
1 MODULE calc_precipitation_mod
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: calc_precipitation.f90 77 2007-03-29 04:26:56Z letzel $
11!
12! 73 2007-03-20 08:33:14Z raasch
13! Precipitation rate and amount are calculated/stored,
14! + module control_parameters
15!
16! 19 2007-02-23 04:53:48Z raasch
17! Calculation extended for gridpoint nzt
18!
19! RCS Log replace by Id keyword, revision history cleaned up
20!
21! Revision 1.5  2004/01/30 10:15:57  raasch
22! Scalar lower k index nzb replaced by 2d-array nzb_2d
23!
24! Revision 1.1  2000/04/13 14:45:22  schroeter
25! Initial revision
26!
27!
28!
29! Description:
30! ------------
31! Calculate the change of total water content due to precipitation
32! (simplified Kessler scheme)
33!------------------------------------------------------------------------------!
34
35    PRIVATE
36    PUBLIC calc_precipitation
37
38    INTERFACE calc_precipitation
39       MODULE PROCEDURE calc_precipitation
40       MODULE PROCEDURE calc_precipitation_ij
41    END INTERFACE calc_precipitation
42 
43 CONTAINS
44
45
46!------------------------------------------------------------------------------!
47! Call for all grid points
48!------------------------------------------------------------------------------!
49    SUBROUTINE calc_precipitation
50
51       USE arrays_3d
52       USE cloud_parameters
53       USE constants
54       USE control_parameters
55       USE indices
56
57       IMPLICIT NONE
58
59       INTEGER ::  i, j, k
60       REAL    ::  dqdt_precip
61
62
63       precipitation_rate = 0.0
64 
65       DO  i = nxl, nxr
66          DO  j = nys, nyn
67             DO  k = nzb_2d(j,i)+1, nzt
68
69                IF ( ql(k,j,i) > ql_crit )  THEN
70                   dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
71                ELSE
72                   dqdt_precip = 0.0
73                ENDIF
74                tend(k,j,i) = tend(k,j,i) - dqdt_precip
75!
76!--             Precipitation rate in kg / m**2 / s (= mm/s)
77                precipitation_rate(j,i) = precipitation_rate(j,i) + &
78                                          dqdt_precip * dzw(k)
79
80             ENDDO
81!
82!--          Sum up the precipitation amount, unit kg / m**2 (= mm)
83             IF ( intermediate_timestep_count ==         &
84                  intermediate_timestep_count_max  .AND. &
85                  ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
86             THEN
87                precipitation_amount(j,i) = precipitation_amount(j,i) + &
88                                            precipitation_rate(j,i) * dt_3d
89             ENDIF
90          ENDDO
91       ENDDO
92
93    END SUBROUTINE calc_precipitation
94
95
96!------------------------------------------------------------------------------!
97! Call for grid point i,j
98!------------------------------------------------------------------------------!
99    SUBROUTINE calc_precipitation_ij( i, j )
100
101       USE arrays_3d
102       USE cloud_parameters
103       USE constants
104       USE control_parameters
105       USE indices
106   
107       IMPLICIT NONE
108
109       INTEGER ::  i, j, k
110       REAL    ::  dqdt_precip
111
112
113       precipitation_rate(j,i) = 0.0
114 
115!
116!--    Ghostpoints are included (although not needed for tend) to avoid a later
117!--    exchange of these data for the precipitation amount/rate arrays
118       DO  k = nzb_2d(j,i)+1, nzt
119
120          IF ( ql(k,j,i) > ql_crit )  THEN
121             dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
122          ELSE
123             dqdt_precip = 0.0
124          ENDIF
125          tend(k,j,i) = tend(k,j,i) - dqdt_precip
126
127!
128!--       Precipitation rate in (kg * 0.001) / m**2 / s (because 1kg gives 1 mm)
129!          precipitation_rate(j,i) = precipitation_rate(j,i) + dqdt_precip * &
130!                                                              dzw(k) * 0.001
131          precipitation_rate(j,i) = 1.0
132
133       ENDDO
134
135!
136!--    Sum up the precipitation amount (unit kg * 0.001 / m**2)
137       IF ( intermediate_timestep_count == intermediate_timestep_count_max     &
138            .AND. ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
139       THEN
140          precipitation_amount(j,i) = precipitation_amount(j,i) + &
141                                      precipitation_rate(j,i) * dt_3d
142       ENDIF
143
144    END SUBROUTINE calc_precipitation_ij
145
146 END MODULE calc_precipitation_mod
Note: See TracBrowser for help on using the repository browser.