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/flow_statistics.f90

    r96 r97  
    55! -----------------
    66! Statistics for ocean version (salinity, density) added,
    7 ! calculation of Deardorff velocity scale adjusted to be used with the ocean
    8 ! version (HAS STILL TO BE COMPLETED!!!)
     7! calculation of z_i and Deardorff velocity scale adjusted to be used with
     8! the ocean version
    99!
    1010! Former revisions:
     
    558558!
    559559!--             Salinity flux and density (density does not belong to here,
    560 !--             but so far there is no suitable place to calculate)
     560!--             but so far there is no other suitable place to calculate)
    561561                IF ( ocean )  THEN
    562562                   pts = 0.5 * ( sa(k,j,i)   - hom(k,1,23,sr) + &
     
    611611
    612612!
     613!--    Density at top follows Neumann condition
     614       IF ( ocean )  sums_l(nzt+1,64,tn) = sums_l(nzt,64,tn)
     615
     616!
    613617!--    Divergence of vertical flux of resolved scale energy and pressure
    614618!--    fluctuations. First calculate the products, then the divergence.
     
    709713!
    710714!--       Fluxes at the surface must be zero (e.g. due to the Prandtl-layer)
    711           sums(nzb,58) = 0.0
    712           sums(nzb,59) = 0.0
    713           sums(nzb,60) = 0.0
    714           sums(nzb,61) = 0.0
    715           sums(nzb,62) = 0.0
    716           sums(nzb,63) = 0.0
     715          sums_l(nzb,58,tn) = 0.0
     716          sums_l(nzb,59,tn) = 0.0
     717          sums_l(nzb,60,tn) = 0.0
     718          sums_l(nzb,61,tn) = 0.0
     719          sums_l(nzb,62,tn) = 0.0
     720          sums_l(nzb,63,tn) = 0.0
    717721
    718722       ENDIF
     
    857861       z_i(1) = 0.0
    858862       first = .TRUE.
    859 !       IF ( .NOT. ocean )  THEN
     863       IF ( ocean )  THEN
     864          DO  k = nzt, nzb+1, -1
     865             IF ( first .AND. hom(k,1,18,sr) < 0.0 )  THEN
     866                first = .FALSE.
     867                height = zw(k)
     868             ENDIF
     869             IF ( hom(k,1,18,sr) < 0.0  .AND. &
     870                  hom(k-1,1,18,sr) > hom(k,1,18,sr) )  THEN
     871                IF ( zw(k) < 1.5 * height )  THEN
     872                   z_i(1) = zw(k)
     873                ELSE
     874                   z_i(1) = height
     875                ENDIF
     876                EXIT
     877             ENDIF
     878          ENDDO
     879       ELSE
    860880          DO  k = nzb, nzt-1
    861881             IF ( first .AND. hom(k,1,18,sr) < 0.0 )  THEN
     
    873893             ENDIF
    874894          ENDDO
    875 !       ELSE
    876 !       ENDIF
    877 
    878 !
    879 !--    Second scheme: Starting from the top model boundary, look for the first
    880 !--    characteristic kink in the temperature profile, where the originally
    881 !--    stable stratification notably weakens.
     895       ENDIF
     896
     897!
     898!--    Second scheme: Starting from the top/bottom model boundary, look for
     899!--    the first characteristic kink in the temperature profile, where the
     900!--    originally stable stratification notably weakens.
    882901       z_i(2) = 0.0
    883        DO  k = nzt-1, nzb+1, -1
    884           IF ( ( hom(k+1,1,4,sr) - hom(k,1,4,sr) ) > &
    885                2.0 * ( hom(k,1,4,sr) - hom(k-1,1,4,sr) ) )  THEN
    886              z_i(2) = zu(k)
    887              EXIT
    888           ENDIF
    889        ENDDO
     902       IF ( ocean )  THEN
     903          DO  k = nzb+1, nzt-1
     904             IF ( ( hom(k,1,4,sr) - hom(k-1,1,4,sr) ) > &
     905                  2.0 * ( hom(k+1,1,4,sr) - hom(k,1,4,sr) ) )  THEN
     906                z_i(2) = zu(k)
     907                EXIT
     908             ENDIF
     909          ENDDO
     910       ELSE
     911          DO  k = nzt-1, nzb+1, -1
     912             IF ( ( hom(k+1,1,4,sr) - hom(k,1,4,sr) ) > &
     913                  2.0 * ( hom(k,1,4,sr) - hom(k-1,1,4,sr) ) )  THEN
     914                z_i(2) = zu(k)
     915                EXIT
     916             ENDIF
     917          ENDDO
     918       ENDIF
    890919
    891920       hom(nzb+6,1,pr_palm,sr) = z_i(1)
Note: See TracChangeset for help on using the changeset viewer.