Changeset 197 for palm/trunk/SOURCE


Ignore:
Timestamp:
Sep 16, 2008 3:29:03 PM (16 years ago)
Author:
raasch
Message:

further adjustments for SGI and other small changes

Location:
palm/trunk/SOURCE
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/CURRENT_MODIFICATIONS

    r192 r197  
    2828Particle advection adjusted for ocean runs.
    2929
     30Multigrid levels are limited by subdomains if mg_switch_to_pe0_level = -1.
     31
    3032User-defined spectra.
     33
     34Output of q*2 profile added.
    3135
    3236Argument -c introduced to most of the subjob calls, which allows the user to
     
    9195(combine_plot_fields)
    9296
    93 advec_s_ups, advec_u_ups, advec_v_ups, advec_w_ups, calc_spectra, check_open, check_parameters, cpu_statistics, data_output_spectra, header, init_1d_model, init_3d_model, modules, netcdf, palm, parin, poisfft, production_e, read_var_list, read_3d_binary, transpose, wall_fluxes, write_var_list, write_3d_binary
     97Time coordinate t=0 stored on netcdf-file only if an output is required for
     98this time for at least one of the profiles
     99
     100Spline timeseries splptx etc. removed, timeseries w'u', w'v', w'q' (k=0) added
     101(flow_statistics)
     102
     103advec_s_ups, advec_u_ups, advec_v_ups, advec_w_ups, calc_spectra, check_open, check_parameters, cpu_statistics, data_output_profiles, data_output_spectra, flow_statistics, header, init_1d_model, init_3d_model, modules, netcdf, palm, parin, poisfft, production_e, read_var_list, read_3d_binary, transpose, wall_fluxes, write_var_list, write_3d_binary
    94104
    95105
     
    148158Bugfix: misplaced #endif directives (combine_plot_fields)
    149159
    150 calc_spectra, check_parameters, diffusion_s, flow_statistics, init_dvrp, init_3d_model, local_stop, plant_canopy_model, poismg, prandtl_fluxes, pres, read_3d_binary, user_interface, wall_fluxes, write_3d_binary
     160data are collected from PE0 in an ordered sequence which seems to avoid hanging of processes on SGI-ICE (cpu_statistics)
    151161
     162calc_spectra, check_parameters, cpu_statistics, diffusion_s, flow_statistics, init_dvrp, init_3d_model, local_stop, plant_canopy_model, poismg, prandtl_fluxes, pres, read_3d_binary, user_interface, wall_fluxes, write_3d_binary
     163
  • palm/trunk/SOURCE/check_parameters.f90

    r181 r197  
    1010! Leaf area density (LAD) explicitly set to its surface value at k=0
    1111! Case of reading data for recycling included in initializing_actions,
    12 ! check of turbulent_inflow and calculation of recycling_plane
     12! check of turbulent_inflow and calculation of recycling_plane.
     13! q*2 profile added
    1314!
    1415! Former revisions:
     
    22562257             hom(:,2,69,:) = SPREAD( zu, 2, statistic_regions+1 )
    22572258
     2259          CASE ( 'q*2' )
     2260             IF ( .NOT. humidity )  THEN
     2261                IF ( myid == 0 )  THEN
     2262                   PRINT*, '+++ check_parameters:  data_output_pr = ', &
     2263                           data_output_pr(i),                          &
     2264                           '    is not implemented for humidity = FALSE'
     2265                ENDIF
     2266                CALL local_stop
     2267             ELSE
     2268                dopr_index(i) = 70
     2269                dopr_unit(i)  = 'kg2/kg2'
     2270                hom(:,2,70,:) = SPREAD( zu, 2, statistic_regions+1 )
     2271             ENDIF
    22582272
    22592273          CASE DEFAULT
  • palm/trunk/SOURCE/cpu_statistics.f90

    r181 r197  
    44! Actual revisions:
    55! -----------------
    6 ! Format adjustments in order to allow CPU# > 999
     6! Format adjustments in order to allow CPU# > 999,
     7! data are collected from PE0 in an ordered sequence which seems to avoid
     8! hanging of processes on SGI-ICE
    79!
    810! Former revisions:
     
    6971       DO  i = 1, numprocs-1
    7072          CALL MPI_RECV( pe_max(1), SIZE( log_point ), MPI_REAL, &
    71                          MPI_ANY_SOURCE, MPI_ANY_TAG, comm2d, status, ierr )
     73                         i, i, comm2d, status, ierr )
    7274          sender = status(MPI_SOURCE)
    7375          pe_log_points(:,sender) = pe_max
     
    8789!--       Calculate rms
    8890          DO  i = 0, numprocs-1
    89 !             IF ( log_point(iii)%place == 'run_control' )  THEN
    90 !                PRINT*, 'pe_rms=',pe_rms(iii),' plp=',pe_log_points(iii,i), &
    91 !                        ' lps=',log_point(iii)%sum
    92 !             ENDIF
    9391             pe_rms(iii) = pe_rms(iii) + ( &
    9492                                 pe_log_points(iii,i) - log_point(iii)%sum &
     
    103101       ALLOCATE( pe_max( SIZE( log_point ) ) )
    104102       pe_max = log_point%sum
    105        CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, 0, comm2d, &
     103       CALL MPI_SEND( pe_max(1), SIZE( log_point ), MPI_REAL, 0, myid, comm2d, &
    106104                      ierr )
    107105#endif
  • palm/trunk/SOURCE/data_output_profiles.f90

    r90 r197  
    44! Actual revisions:
    55! -----------------
    6 !
     6! Time coordinate t=0 stored on netcdf-file only if an output is required for
     7! this time for at least one of the profiles
    78!
    89! Former revisions:
     
    3940
    4041    INTEGER ::  i, id, ilc, ils, j, k, sr
     42    LOGICAL ::  output_for_t0
    4143    REAL    ::  uxma, uxmi
    4244
     
    101103#if defined( __netcdf )
    102104!
    103 !--          Store initial time (t=0) to time axis         
    104              nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr, (/ 0.0 /), &
    105                                      start = (/ 1 /), count = (/ 1 /) )
    106              IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 329 )
     105!--          Store initial time (t=0) to time axis, but only if an output
     106!--          is required for at least one of the profiles
     107             output_for_t0 = .FALSE.
     108             DO  i = 1, dopr_n
     109                IF ( dopr_initial_index(i) /= 0 )  THEN
     110                   nc_stat = NF90_PUT_VAR( id_set_pr, id_var_time_pr,  &
     111                                           (/ 0.0 /), start = (/ 1 /), &
     112                                           count = (/ 1 /) )
     113                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 329 )
     114                   output_for_t0 = .TRUE.
     115                   EXIT
     116                ENDIF
     117             ENDDO
    107118
    108119!
     
    331342          ENDDO   ! Loop over dopr_n for initial profiles
    332343
    333           IF ( netcdf_output )  dopr_time_count = dopr_time_count + 1
     344          IF ( netcdf_output  .AND.  output_for_t0 )  THEN
     345             dopr_time_count = dopr_time_count + 1
     346          ENDIF
    334347
    335348       ENDIF   ! Initial profiles
  • palm/trunk/SOURCE/flow_statistics.f90

    r142 r197  
    44! Actual revisions:
    55! -----------------
     6! Spline timeseries splptx etc. removed, timeseries w'u', w'v', w'q' (k=0)
     7! added
    68! Bugfix: divide sums(k,8) (e) and sums(k,34) (e*) by ngp_2dh_s_inner(k,sr)
    79! (like other scalars)
     
    109111       sums_l(nzb+9,pr_palm,0)  = sums_divold_l(sr)  ! old divergence from pres
    110112       sums_l(nzb+10,pr_palm,0) = sums_divnew_l(sr)  ! new divergence from pres
    111 !--    WARNING: next four lines still may have to be adjusted for OpenMP
    112        sums_l(nzb:nzb+2,pr_palm-1,0)    = sums_up_fraction_l(1,1:3,sr)! upstream
    113        sums_l(nzb+3:nzb+5,pr_palm-1,0)  = sums_up_fraction_l(2,1:3,sr)! parts
    114        sums_l(nzb+6:nzb+8,pr_palm-1,0)  = sums_up_fraction_l(3,1:3,sr)! from
    115        sums_l(nzb+9:nzb+11,pr_palm-1,0) = sums_up_fraction_l(4,1:3,sr)! spline
    116113
    117114!
     
    380377             sums_l(nzb+3,pr_palm,tn) = sums_l(nzb+3,pr_palm,tn) + &
    381378                                        ts(j,i)   * rmask(j,i,sr)
     379             IF ( humidity )  THEN
     380                sums_l(nzb+12,pr_palm,tn) = sums_l(nzb+12,pr_palm,tn) + &
     381                                            qs(j,i)   * rmask(j,i,sr)
     382             ENDIF
    382383          ENDDO
    383384       ENDDO
     
    807808!--    above the topography, they are being divided by ngp_2dh(sr)
    808809       sums(nzb:nzb+3,pr_palm)    = sums(nzb:nzb+3,pr_palm)    / &
     810                                    ngp_2dh(sr)
     811       sums(nzb+12,pr_palm)       = sums(nzb+12,pr_palm)       / &    ! qs
    809812                                    ngp_2dh(sr)
    810813!--    eges, e*
     
    882885       hom(:,1,68,sr) = sums(:,68)     ! w*p*
    883886       hom(:,1,69,sr) = sums(:,69)     ! w"e + w"p"/rho
     887       hom(:,1,70,sr) = sums(:,70)     ! q*2
    884888
    885889       hom(:,1,pr_palm-1,sr) = sums(:,pr_palm-1)
     
    9991003       ts_value(17,sr) = hom(nzb,1,4,sr)            ! pt(0)
    10001004       ts_value(18,sr) = hom(nzb+1,1,4,sr)          ! pt(zp)
    1001        ts_value(19,sr) = hom(nzb+9,1,pr_palm-1,sr)  ! splptx
    1002        ts_value(20,sr) = hom(nzb+10,1,pr_palm-1,sr) ! splpty
    1003        ts_value(21,sr) = hom(nzb+11,1,pr_palm-1,sr) ! splptz
     1005       ts_value(19,sr) = hom(nzb+1,1,pr_palm,sr)    ! u'w'    at k=0
     1006       ts_value(20,sr) = hom(nzb+2,1,pr_palm,sr)    ! v'w'    at k=0
     1007       ts_value(21,sr) = hom(nzb+12,1,pr_palm,sr)   ! w'q'    at k=0
     1008
    10041009       IF ( ts_value(5,sr) /= 0.0 )  THEN
    10051010          ts_value(22,sr) = ts_value(4,sr)**2 / &
  • palm/trunk/SOURCE/header.f90

    r189 r197  
    44! Actual revisions:
    55! -----------------
     6! TEST: mg_switch_to_pe0_level = -1!!!!!!!!!
    67! allow 100 spectra levels instead of 10 for consistency with
    78! define_netcdf_header
     
    117118    ELSEIF ( INDEX( initializing_actions, 'set_constant_profiles' ) /= 0 )  THEN
    118119       run_classification = '3D - run without 1D - prerun'
    119     ELSEIF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 ) THEN
     120    ELSEIF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 ) THEN
    120121       run_classification = '3D - run with 1D - prerun'
     122    ELSEIF ( INDEX( initializing_actions, 'by_user' ) /=0 )  THEN
     123       run_classification = '3D - run initialized by user'
    121124    ELSE
    122125       PRINT*,'+++ header:  unknown action(s): ',initializing_actions
     
    184187          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
    185188                             nzt_mg(1)
    186        ELSE
     189       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
    187190          WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
    188191                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
  • palm/trunk/SOURCE/init_pegrid.f90

    r181 r197  
    55! -----------------
    66! ATTENTION: nnz_x undefined problem still has to be solved!!!!!!!!
     7! multigrid levels are limited by subdomains if mg_switch_to_pe0_level = -1,
    78! nz is used instead nnz for calculating mg-levels
    89! Collect on PE0 horizontal index bounds from all other PEs,
     
    719720!--    Find out, if the total domain allows more levels. These additional
    720721!--    levels are processed on PE0 only.
    721        IF ( numprocs > 1 )  THEN
     722       IF ( numprocs > 1  .AND.  mg_switch_to_pe0_level /= -1 )  THEN
    722723          IF ( mg_levels_z > MIN( mg_levels_x, mg_levels_y ) )  THEN
    723724             mg_switch_to_pe0_level_l = maximum_grid_level
  • palm/trunk/SOURCE/modules.f90

    r189 r197  
    788788             'vmax   ', 'wmax   ', 'div_new', 'div_old', 'z_i_wpt', 'z_i_pt ', &
    789789             'w*     ', 'w"pt"0 ', 'w"pt"  ', 'wpt    ', 'pt(0)  ', 'pt(zp) ', &
    790              'splptx ', 'splpty ', 'splptz ', 'mo_L   ',                       &
     790             'w"u"0  ', 'w"v"0  ', 'w"q"0 ', 'mo_L   ',                       &
    791791             ( 'unknown', i9 = 1, 78) /)
    792792
     
    795795             'm/s    ', 'm/s    ', 's-1    ', 's-1    ', 'm      ', 'm      ', &
    796796             'm/s    ', 'K m/s  ', 'K m/s  ', 'k m/s  ', 'K      ', 'K      ', &
    797              '%      ', '%      ', '%      ', 'm      ',                       &
     797             'm2/s2  ', 'm2/s2  ', 'kg m/s ', 'm      ',                       &
    798798             ( 'unknown', i9 = 1, 78 ) /)
    799799
  • palm/trunk/SOURCE/palm.f90

    r164 r197  
    6666    INTEGER           ::  i, run_description_header_i(80)
    6767
    68     version = 'PALM 3.4a'
     68    version = 'PALM 3.5'
    6969
    7070#if defined( __parallel )
  • palm/trunk/SOURCE/parin.f90

    r153 r197  
    88! +inflow_damping_height, inflow_damping_width, recycling_width,
    99! turbulent_inflow in inipar
     10! -skip_time_dosp in d3par,
    1011! Allocation of hom_sum moved from init_3d_model to here,
    1112! npex, npey moved from inipar to d3par, setting of myid_char_14 removed,
     
    109110             surface_heatflux, surface_pressure, surface_scalarflux, &
    110111             surface_waterflux, s_surface, s_surface_initial_change, &
    111              s_vertical_gradient, s_vertical_gradient_level, top_heatflux, &
    112              top_momentumflux_u, top_momentumflux_v, top_salinityflux, &
    113              timestep_scheme, topography, turbulent_inflow, ug_surface, &
     112             s_vertical_gradient, s_vertical_gradient_level, timestep_scheme,
     113             topography, top_heatflux, top_momentumflux_u, top_momentumflux_v, &
     114             top_salinityflux, turbulent_inflow, ug_surface, &
    114115             ug_vertical_gradient, ug_vertical_gradient_level, ups_limit_e, &
    115116             ups_limit_pt, ups_limit_u, ups_limit_v, ups_limit_w, &
     
    143144                       section_yz, skip_time_data_output, &
    144145                       skip_time_data_output_av, skip_time_dopr, &
    145                        skip_time_dosp, skip_time_do2d_xy, skip_time_do2d_xz, &
     146                       skip_time_do2d_xy, skip_time_do2d_xz, &
    146147                       skip_time_do2d_yz, skip_time_do3d, &
    147148                       termination_time_needed, use_prior_plot1d_parameters, &
Note: See TracChangeset for help on using the changeset viewer.