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

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

updating comments and rc-file

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