Ignore:
Timestamp:
Jun 21, 2007 8:23:15 AM (17 years ago)
Author:
raasch
Message:

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

File:
1 edited

Legend:

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

    r94 r97  
    1  SUBROUTINE diffusivities( theta )
     1 SUBROUTINE diffusivities( var, var_reference )
    22
    33!------------------------------------------------------------------------------!
     
    77! This is also a bugfix, because the height above the topography is now
    88! used instead of the height above level k=0.
     9! theta renamed var, dpt_dz renamed dvar_dz, +new argument var_reference
     10! use_pt_reference renamed use_reference
    911!
    1012! Former revisions:
     
    4143    INTEGER ::  i, j, k, omp_get_thread_num, sr, tn
    4244
    43     REAL    ::  dpt_dz, l_stable, phi_m = 1.0
     45    REAL    ::  dvar_dz, l_stable, var_reference
    4446
    45     REAL    ::  theta(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
     47    REAL, SAVE ::  phi_m = 1.0
     48
     49    REAL    ::  var(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1)
    4650
    4751    REAL, DIMENSION(1:nzt) ::  l, ll, sqrt_e
     
    5862!
    5963!-- Compute the turbulent diffusion coefficient for momentum
    60     !$OMP PARALLEL PRIVATE (dpt_dz,i,j,k,l,ll,l_stable,phi_m,sqrt_e,sr,tn)
     64    !$OMP PARALLEL PRIVATE (dvar_dz,i,j,k,l,ll,l_stable,phi_m,sqrt_e,sr,tn)
    6165!$  tn = omp_get_thread_num()
    6266
     
    9498!--       Determine the mixing length
    9599          DO  k = nzb_s_inner(j,i)+1, nzt
    96              dpt_dz = ( theta(k+1,j,i) - theta(k-1,j,i) ) * dd2zu(k)
    97              IF ( dpt_dz > 0.0 ) THEN
    98                 IF ( use_pt_reference )  THEN
     100             dvar_dz = atmos_ocean_sign * &  ! inverse effect of pt/rho gradient
     101                       ( var(k+1,j,i) - var(k-1,j,i) ) * dd2zu(k)
     102             IF ( dvar_dz > 0.0 ) THEN
     103                IF ( use_reference )  THEN
    99104                   l_stable = 0.76 * sqrt_e(k) / &
    100                                      SQRT( g / pt_reference * dpt_dz ) + 1E-5
     105                                     SQRT( g / var_reference * dvar_dz ) + 1E-5
    101106                ELSE
    102107                   l_stable = 0.76 * sqrt_e(k) / &
    103                                      SQRT( g / theta(k,j,i) * dpt_dz ) + 1E-5
     108                                     SQRT( g / var(k,j,i) * dvar_dz ) + 1E-5
    104109                ENDIF
    105110             ELSE
Note: See TracChangeset for help on using the changeset viewer.