Ignore:
Timestamp:
Jun 4, 2007 8:07:41 AM (17 years ago)
Author:
raasch
Message:

more preliminary uncomplete changes for ocean version

File:
1 edited

Legend:

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

    r95 r96  
    88! Former revisions:
    99! ------------------
    10 ! $Id:$
     10! $Id$
    1111!
    1212! Initial revision (raasch 01/06/07)
     
    3737!
    3838!-- Calculate initial vertical profile of hydrostatic pressure (in Pa)
     39!-- and the reference density (used later in buoyancy term)
    3940    hyp(nzt+1) = surface_pressure * 100.0
    4041
    4142    hyp(nzt)   = hyp(nzt+1) + rho_surface * g * 0.5 * dzu(nzt+1)
     43    rho_ref    = rho_surface * 0.5 * dzu(nzt+1)
    4244
    4345    DO  k = nzt-1, 0, -1
     
    4648       pt_l = 0.5 * ( pt_init(k) + pt_init(k+1) )
    4749
    48        rho_l = eqn_state_seawater_func( hyp(k+1), pt_l, sa_l )
     50       rho_l   = eqn_state_seawater_func( hyp(k+1), pt_l, sa_l )
    4951
    50        hyp(k) = hyp(k+1) + rho_l * g * dzu(k+1)
     52       hyp(k)  = hyp(k+1) + rho_l * g * dzu(k+1)
     53       rho_ref = rho_ref + rho_l * dzu(k+1)
    5154
    5255    ENDDO
    5356
     57    rho_ref = rho_ref / ( zw(nzt) - zu(nzb) )
     58    print*, '*** rho_ref = ', rho_ref
     59
    5460
    5561 END SUBROUTINE init_ocean
Note: See TracChangeset for help on using the changeset viewer.