Ignore:
Timestamp:
Jun 2, 2007 4:48:38 PM (17 years ago)
Author:
raasch
Message:

further preliminary uncomplete changes for ocean version

File:
1 edited

Legend:

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

    r94 r95  
    77! +ocean, r, + salinity variables
    88! defaults of .._vertical_gradient_levels changed from -1.0 to -9999999.9
     9! hydro_press renamed hyp
    910!
    1011! Former revisions:
     
    9495
    9596    REAL, DIMENSION(:), ALLOCATABLE ::                                         &
    96           ddzu, dd2zu, dzu, ddzw, dzw, km_damp_x, km_damp_y, l_grid, pt_init,  &
    97           q_init, rdf, sa_init, ug, u_init, u_nzb_p1_for_vfc, vg, v_init,      &
    98           v_nzb_p1_for_vfc, zu, zw
     97          ddzu, dd2zu, dzu, ddzw, dzw, hyp, km_damp_x, km_damp_y, l_grid,      &
     98          pt_init, q_init, rdf, sa_init, ug, u_init, u_nzb_p1_for_vfc, vg,     &
     99          v_init, v_nzb_p1_for_vfc, zu, zw
    99100
    100101    REAL, DIMENSION(:,:), ALLOCATABLE ::                                       &
     
    102103
    103104    REAL, DIMENSION(:,:), ALLOCATABLE, TARGET ::                               &
    104           qsws_1, qsws_2, qswst_1, qswst_2, rif_1, rif_2, saswst_1, shf_1,     &
    105           shf_2, tswst_1, tswst_2, usws_1, usws_2, vsws_1, vsws_2
     105          qsws_1, qsws_2, qswst_1, qswst_2, rif_1, rif_2, saswsb_1, saswst_1,  &
     106          shf_1, shf_2, tswst_1, tswst_2, usws_1, usws_2, vsws_1, vsws_2
    106107
    107108    REAL, DIMENSION(:,:), POINTER ::                                           &
    108           qsws, qsws_m, qswst, qswst_m, rif, rif_m, saswst, shf, shf_m, tswst, &
    109           tswst_m, usws, usws_m, vsws, vsws_m
     109          qsws, qsws_m, qswst, qswst_m, rif, rif_m, saswsb, saswst, shf,      &
     110          shf_m, tswst, tswst_m, usws, usws_m, vsws, vsws_m
    110111
    111112    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
     
    118119    REAL, DIMENSION(:,:,:), ALLOCATABLE, TARGET ::                             &
    119120          e_1, e_2, e_3, kh_1, kh_2, km_1, km_2, p, pt_1, pt_2, pt_3, q_1,     &
    120           q_2, q_3, ql_1, ql_2, r, sa_1, sa_2, sa_3, u_1, u_2, u_3, v_1, v_2,  &
    121           v_3, vpt_1, vpt_2, w_1, w_2, w_3
     121          q_2, q_3, ql_1, ql_2, rho, sa_1, sa_2, sa_3, u_1, u_2, u_3, v_1,     &
     122          v_2, v_3, vpt_1, vpt_2, w_1, w_2, w_3
    122123
    123124    REAL, DIMENSION(:,:,:), POINTER ::                                         &
     
    167168              mass_of_solute, molecular_weight_of_solute,                      &
    168169              prec_time_const = 0.001, ql_crit = 0.0005, rho_l = 1.0E3,        &
    169               r_d = 287.0, r_v = 461.51, rho_surface,                          &
    170               thermal_conductivity_l = 2.43E-2
    171 
    172     REAL, DIMENSION(:), ALLOCATABLE :: hydro_press, pt_d_t, t_d_pt
     170              r_d = 287.0, r_v = 461.51, thermal_conductivity_l = 2.43E-2
     171
     172    REAL, DIMENSION(:), ALLOCATABLE   ::  pt_d_t, t_d_pt
    173173
    174174    REAL, DIMENSION(:,:), ALLOCATABLE ::  precipitation_amount, &
     
    241241                            bc_q_b = 'dirichlet', bc_q_t = 'neumann', &
    242242                            bc_s_b = 'dirichlet', bc_s_t = 'neumann', &
     243                            bc_sa_t = 'neumann', &
    243244                            bc_uv_b = 'dirichlet', bc_uv_t = 'dirichlet', &
    244245                            dissipation_1d = 'as_in_3d_model', &
     
    272273                dvrp_filecount = 0, dz_stretch_level_index, gamma_mg, &
    273274                grid_level, ibc_e_b, ibc_p_b, ibc_p_t, ibc_pt_b, ibc_pt_t, &
    274                 ibc_q_b, ibc_q_t, ibc_uv_b, ibc_uv_t, &
     275                ibc_q_b, ibc_q_t, ibc_sa_t, ibc_uv_b, ibc_uv_t, &
    275276                inflow_disturbance_begin = -1, inflow_disturbance_end = -1, &
    276277                intermediate_timestep_count, intermediate_timestep_count_max, &
     
    302303                conserve_volume_flow = .FALSE., constant_diffusion = .FALSE., &
    303304                constant_heatflux = .TRUE., constant_top_heatflux = .TRUE., &
     305                constant_top_salinityflux = .TRUE., &
    304306                constant_waterflux = .TRUE., create_disturbances = .TRUE., &
    305307                cut_spline_overshoot = .TRUE., &
     
    333335             averaging_interval = 0.0, averaging_interval_pr = 9999999.9, &
    334336             averaging_interval_sp = 9999999.9, bc_pt_t_val, bc_q_t_val, &
     337             bottom_salinityflux = 0.0, &
    335338             building_height = 50.0, building_length_x = 50.0, &
    336339             building_length_y = 50.0, building_wall_left = 9999999.9, &
     
    363366             q_surface_initial_change = 0.0, rayleigh_damping_factor = -1.0, &
    364367             rayleigh_damping_height = -1.0, residual_limit = 1.0E-4, &
    365              restart_time = 9999999.9, rif_max = 1.0, rif_min = -5.0, &
    366              roughness_length = 0.1, sa_surface = 35.0, simulated_time = 0.0, &
    367              simulated_time_at_begin, sin_alpha_surface, &
     368             restart_time = 9999999.9, rho_ref, rho_surface, rif_max = 1.0, &
     369             rif_min = -5.0, roughness_length = 0.1, sa_surface = 35.0, &
     370             simulated_time = 0.0, simulated_time_at_begin, sin_alpha_surface, &
    368371             skip_time_data_output = 0.0, skip_time_data_output_av = 9999999.9,&
    369372             skip_time_dopr = 9999999.9, skip_time_dosp = 9999999.9, &
     
    380383             time_do_sla = 0.0, time_dvrp = 0.0, time_prel = 0.0, &
    381384             time_restart = 9999999.9, time_run_control = 0.0, &
    382              top_heatflux = 9999999.9, top_salinityflux = 0.0, &
     385             top_heatflux = 9999999.9, top_salinityflux = 9999999.9, &
    383386             ug_surface = 0.0, u_gtrans = 0.0, &
    384387             ups_limit_e = 0.0, ups_limit_pt = 0.0, ups_limit_u = 0.0, &
     
    393396             q_vertical_gradient_level(10) = -1.0, &
    394397             s_vertical_gradient(10) = 0.0, &
    395              s_vertical_gradient_level(10) = -1.0,
     398             s_vertical_gradient_level(10) = -1.0, &
    396399             sa_vertical_gradient(10) = 0.0, &
    397              sa_vertical_gradient_level(10) = -1.0, threshold(20) = 0.0, &
     400             sa_vertical_gradient_level(10) = -9999999.9, threshold(20) = 0.0, &
    398401             tsc(10) = (/ 0.0, 1.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /), &
    399402             ug_vertical_gradient(10) = 0.0, &
Note: See TracChangeset for help on using the changeset viewer.