source: palm/trunk/SOURCE/init_ocean.f90 @ 97

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

New:
---
ocean version including prognostic equation for salinity and equation of state for seawater. Routine buoyancy can be used with both temperature and density.
+ inipar-parameters bc_sa_t, bottom_salinityflux, ocean, sa_surface, sa_vertical_gradient, sa_vertical_gradient_level, top_salinityflux

advec_s_bc, average_3d_data, boundary_conds, buoyancy, check_parameters, data_output_2d, data_output_3d, diffusion_e, flow_statistics, header, init_grid, init_3d_model, modules, netcdf, parin, production_e, prognostic_equations, read_var_list, sum_up_3d_data, swap_timelevel, time_integration, user_interface, write_var_list, write_3d_binary

New:
eqn_state_seawater, init_ocean

Changed:


inipar-parameter use_pt_reference renamed use_reference

hydro_press renamed hyp, routine calc_mean_pt_profile renamed calc_mean_profile

format adjustments for the ocean version (run_control)

advec_particles, buoyancy, calc_liquid_water_content, check_parameters, diffusion_e, diffusivities, header, init_cloud_physics, modules, production_e, prognostic_equations, run_control

Errors:


Bugfix: height above topography instead of height above level k=0 is used for calculating the mixing length (diffusion_e and diffusivities).

Bugfix: error in boundary condition for TKE removed (advec_s_bc)

advec_s_bc, diffusion_e, prognostic_equations

  • Property svn:keywords set to Id
File size: 1.8 KB
Line 
1 SUBROUTINE init_ocean
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! hydro_press renamed hyp
7!
8! Former revisions:
9! ------------------
10! $Id: init_ocean.f90 97 2007-06-21 08:23:15Z raasch $
11!
12! Initial revision (raasch 01/06/07)
13!
14! Description:
15! ------------
16! Initialization of quantities needed for the ocean version
17!------------------------------------------------------------------------------!
18
19    USE arrays_3d
20    USE control_parameters
21    USE eqn_state_seawater_mod
22    USE grid_variables
23    USE indices
24
25    IMPLICIT NONE
26
27    INTEGER ::  k
28
29    REAL    ::  sa_l, pt_l, rho_l
30
31    ALLOCATE( hyp(nzb:nzt+1) )
32
33!
34!-- Set water density near the ocean surface
35    rho_surface = 1027.62
36
37!
38!-- Calculate initial vertical profile of hydrostatic pressure (in Pa)
39!-- and the reference density (used later in buoyancy term)
40    hyp(nzt+1) = surface_pressure * 100.0
41
42    hyp(nzt)      = hyp(nzt+1) + rho_surface * g * 0.5 * dzu(nzt+1)
43    rho_reference = rho_surface * 0.5 * dzu(nzt+1)
44
45    DO  k = nzt-1, 0, -1
46
47       sa_l = 0.5 * ( sa_init(k) + sa_init(k+1) )
48       pt_l = 0.5 * ( pt_init(k) + pt_init(k+1) )
49
50       rho_l = eqn_state_seawater_func( hyp(k+1), pt_l, sa_l )
51
52       hyp(k)        = hyp(k+1) + rho_l * g * dzu(k+1)
53       rho_reference = rho_reference + rho_l * dzu(k+1)
54
55    ENDDO
56
57    rho_reference = rho_reference / ( zw(nzt) - zu(nzb) )
58
59!
60!-- Calculate the reference potential density
61    prho_reference = 0.0
62    DO  k = 0, nzt
63
64       sa_l = 0.5 * ( sa_init(k) + sa_init(k+1) )
65       pt_l = 0.5 * ( pt_init(k) + pt_init(k+1) )
66
67       prho_reference = prho_reference + dzu(k+1) * &
68                        eqn_state_seawater_func( hyp(0), pt_l, sa_l )
69
70    ENDDO
71
72    prho_reference = prho_reference / ( zu(nzt) - zu(nzb) )
73
74
75 END SUBROUTINE init_ocean
Note: See TracBrowser for help on using the repository browser.