Ignore:
Timestamp:
Sep 14, 2012 2:35:53 PM (12 years ago)
Author:
raasch
Message:

subdomains must have identical size, i.e. grid_matching = "match" not allowed any more
parameter grid_matching removed
some obsolete variables removed

File:
1 edited

Legend:

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

    r708 r1003  
    44! Current revisions:
    55! -----------------
    6 !
     6! adjustment of array tend for cases with unequal subdomain sizes removed
    77!
    88! Former revisions:
     
    7373    IF ( psolver == 'multigrid' )  THEN
    7474       DEALLOCATE( d )
    75        ALLOCATE( d(nzb+1:nzta,nys:nyna,nxl:nxra) )
    76     ENDIF
    77 
    78 !
    79 !-- Enlarge the size of tend, used as a working array for the transpositions
    80     IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
    81        DEALLOCATE( tend )
    82        ALLOCATE( tend(1:nza,nys:nyna,nxl:nxra) )
     75       ALLOCATE( d(nzb+1:nzt,nys:nyn,nxl:nxr) )
    8376    ENDIF
    8477
     
    154147!-- Increase counter for averaging process in routine plot_spectra
    155148    average_count_sp = average_count_sp + 1
    156 
    157 !
    158 !-- Resize tend to its normal size
    159     IF ( nxra > nxr  .OR.  nyna > nyn  .OR.  nza > nz )  THEN
    160        DEALLOCATE( tend )
    161        ALLOCATE( tend(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    162     ENDIF
    163149
    164150    CALL cpu_log( log_point(30), 'calc_spectra', 'stop' )
     
    249235    REAL, DIMENSION(0:nx/2,100)::  sums_spectra
    250236
    251     REAL, DIMENSION(0:nxa,nys_x:nyn_xa,nzb_x:nzt_xa) ::  ddd
     237    REAL, DIMENSION(0:nx,nys_x:nyn_x,nzb_x:nzt_x) ::  ddd
    252238
    253239!
     
    359345    REAL, DIMENSION(0:ny/2,100)::  sums_spectra
    360346
    361     REAL, DIMENSION(0:nya,nxl_yd:nxr_yda,nzb_yd:nzt_yda) :: ddd
     347    REAL, DIMENSION(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd) :: ddd
    362348
    363349
Note: See TracChangeset for help on using the changeset viewer.