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

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

more preliminary uncomplete changes for ocean version

  • Property svn:keywords set to Id
File size: 1.4 KB
RevLine 
[95]1 SUBROUTINE init_ocean
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! hydro_press renamed hyp
7!
8! Former revisions:
9! ------------------
[96]10! $Id: init_ocean.f90 96 2007-06-04 08:07:41Z raasch $
[95]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)
[96]39!-- and the reference density (used later in buoyancy term)
[95]40    hyp(nzt+1) = surface_pressure * 100.0
41
42    hyp(nzt)   = hyp(nzt+1) + rho_surface * g * 0.5 * dzu(nzt+1)
[96]43    rho_ref    = rho_surface * 0.5 * dzu(nzt+1)
[95]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
[96]50       rho_l   = eqn_state_seawater_func( hyp(k+1), pt_l, sa_l )
[95]51
[96]52       hyp(k)  = hyp(k+1) + rho_l * g * dzu(k+1)
53       rho_ref = rho_ref + rho_l * dzu(k+1)
[95]54
55    ENDDO
56
[96]57    rho_ref = rho_ref / ( zw(nzt) - zu(nzb) )
58    print*, '*** rho_ref = ', rho_ref
[95]59
[96]60
[95]61 END SUBROUTINE init_ocean
Note: See TracBrowser for help on using the repository browser.