Ignore:
Timestamp:
Sep 23, 2009 9:40:33 AM (15 years ago)
Author:
raasch
Message:

in-situ AND potential density are calculated and used in the ocean version

File:
1 edited

Legend:

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

    r366 r388  
    44! Actual revisions:
    55! -----------------
    6 ! Bugfix: First calculation of hyp(0) changed
     6! Bugfix: Initial profiles of hydrostatic pressure and density are calculated
     7! iteratively. First calculation of hyp(0) changed.
    78!
    89! Former revisions:
     
    3233    INTEGER ::  k, n
    3334
    34     REAL    ::  sa_l, pt_l, rho_l
     35    REAL    ::  sa_l, pt_l
    3536
    3637    REAL, DIMENSION(nzb:nzt+1) ::  rho_init
     
    4546!-- Calculate initial vertical profile of hydrostatic pressure (in Pa)
    4647!-- and the reference density (used later in buoyancy term)
     48!-- First step: Calculate pressure using reference density
    4749    hyp(nzt+1) = surface_pressure * 100.0
    4850
     
    5557    hyp(0) = hyp(1) + rho_surface * g * dzu(1)
    5658
    57     IF ( myid == 0 )  THEN
    58        print*,'hydro pres using rho_surface'
    59        DO  k = nzt+1, 0, -1
    60           print*, 'k = ', k, ' hyp = ', hyp(k)
    61        ENDDO
    62        print*, ' '
    63     ENDIF
    64 
     59!
     60!-- Second step: Iteratively calculate in situ density (based on presssure)
     61!-- and pressure (based on in situ density)
    6562    DO  n = 1, 5
    6663
     
    8582       ENDDO
    8683
    87        IF ( myid == 0 )  THEN
    88           print*,'hydro pres / rho  n = ', n
    89           DO  k = nzt+1, 0, -1
    90              print*, 'k = ', k, ' hyp = ', hyp(k), ' rho = ', rho_init(k)
    91           ENDDO
    92           print*, ' '
    93        ENDIF
    94 
    9584    ENDDO
    9685
     
    111100
    112101!
    113 !-- Calculate the initial potential density, based on the initial
    114 !-- temperature and salinity profile
     102!-- Calculate the 3d array of initial in situ and potential density,
     103!-- based on the initial temperature and salinity profile
    115104    CALL eqn_state_seawater
    116105
Note: See TracChangeset for help on using the changeset viewer.