Ignore:
Timestamp:
Mar 7, 2008 1:42:18 PM (17 years ago)
Author:
raasch
Message:

preliminary update for the turbulence recycling method

File:
1 edited

Legend:

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

    r147 r151  
    44! Actual revisions:
    55! -----------------
    6 ! +numprocs_previous_run, hor_index_bounds_previous_run,
     6! +numprocs_previous_run, hor_index_bounds_previous_run, inflow_damping_factor,
     7! inflow_damping_height, inflow_damping_width, mean_inflow_profiles,
     8! recycling_width, turbulent_inflow,
    79! -cross_ts_*, npex, npey,
    810! hom_sum, volume_flow_area, volume_flow_initial moved from
     
    279281          CASE ( 'hom_sum' )
    280282             READ ( 13 )  hom_sum
     283          CASE ( 'humidity' )
     284             READ ( 13 )  humidity
     285          CASE ( 'inflow_damping_factor' )
     286             IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
     287                ALLOCATE( inflow_damping_factor(0:nz+1) )
     288             ENDIF
     289             READ ( 13 )  inflow_damping_factor
     290          CASE ( 'inflow_damping_height' )
     291             READ ( 13 )  inflow_damping_height
     292          CASE ( 'inflow_damping_width' )
     293             READ ( 13 )  inflow_damping_width
    281294          CASE ( 'inflow_disturbance_begin' )
    282295             READ ( 13 )  inflow_disturbance_begin
     
    303316          CASE ( 'loop_optimization' )
    304317             READ ( 13 )  loop_optimization
     318          CASE ( 'mean_inflow_profiles' )
     319             IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
     320                ALLOCATE( mean_inflow_profiles(0:nz+1,5) )
     321             ENDIF
     322             READ ( 13 )  mean_inflow_profiles
    305323          CASE ( 'mixing_length_1d' )
    306324             READ ( 13 )  mixing_length_1d
    307           CASE ( 'humidity' )
    308              READ ( 13 )  humidity
    309325          CASE ( 'momentum_advec' )
    310326             READ ( 13 )  momentum_advec
     
    381397          CASE ( 'random_heatflux' )
    382398             READ ( 13 )  random_heatflux
     399          CASE ( 'recycling_width' )
     400             READ ( 13 )  recycling_width
    383401          CASE ( 'rif_max' )
    384402             READ ( 13 )  rif_max
     
    467485          CASE ( 'tsc' )
    468486             READ ( 13 )  tsc
     487          CASE ( 'turbulent_inflow' )
     488             READ ( 13 )  turbulent_inflow
    469489          CASE ( 'u_init' )
    470490             READ ( 13 )  u_init
     
    552572! Skipping the global control variables from restart-file (binary format)
    553573! except some informations needed when reading restart data from a previous
    554 ! run which used a smaller total domain.
     574! run which used a smaller total domain or/and a different domain decomposition.
    555575!------------------------------------------------------------------------------!
    556576
     577    USE arrays_3d
    557578    USE control_parameters
    558579    USE indices
     
    568589                statistic_regions_on_file
    569590
     591    REAL, DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
    570592    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
    571593
     
    672694       SELECT CASE ( TRIM( variable_chr ) )
    673695
     696          CASE ( 'average_count_pr' )
     697             READ ( 13 )  average_count_pr
     698             IF ( average_count_pr /= 0  .AND.  myid == 0 )  THEN
     699                PRINT*, '+++ read_parts_of_var_list:'
     700                PRINT*, '    WARNING: inflow profiles not temporally averaged.'
     701                PRINT*, '    Averaging will be done now using ', &
     702                        average_count_pr, ' samples.'
     703             ENDIF
     704
    674705          CASE ( 'hom' )
    675706             ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file, &
     
    678709             hom = hom_on_file(:,:,1:pr_palm+max_pr_user,0:statistic_regions)
    679710             DEALLOCATE( hom_on_file )
     711
     712          CASE ( 'hom_sum' )
     713             ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file, &
     714                       0:statistic_regions_on_file) )
     715             READ ( 13 )  hom_sum_on_file
     716             hom_sum = hom_sum_on_file(:,1:pr_palm+max_pr_user, &
     717                                       0:statistic_regions)
     718             DEALLOCATE( hom_sum_on_file )
    680719
    681720          CASE ( 'nx' )
     
    710749    ENDDO
    711750
     751!
     752!-- Calculate the temporal average of vertical profiles, if neccessary
     753    IF ( average_count_pr /= 0 )  THEN
     754       hom_sum = hom_sum / REAL( average_count_pr )
     755    ENDIF
     756
    712757
    713758 END SUBROUTINE read_parts_of_var_list
Note: See TracChangeset for help on using the changeset viewer.