Ignore:
Timestamp:
Feb 1, 2008 12:41:46 PM (17 years ago)
Author:
raasch
Message:

further updates for turbulent inflow: reading input data of a precursor run using a smaller total domain is working

File:
1 edited

Legend:

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

    r145 r147  
    177177
    178178
    179  SUBROUTINE user_read_restart_data
     179 SUBROUTINE user_read_restart_data( nxlc, nxlf, nxl_on_file, nxrc, nxrf,  &
     180                                    nxr_on_file, nync, nynf, nyn_on_file, &
     181                                    nysc, nysf, nys_on_file, tmp_2d, tmp_3d )
    180182
    181183!------------------------------------------------------------------------------!
     
    184186! ------------
    185187! Reading restart data from file(s)
     188! Subdomain index limits on file are given by nxl_on_file, etc.
     189! Indices nxlc, etc. indicate the range of gridpoints to be mapped from the
     190! subdomain on file (f) to the subdomain of the current PE (c). They have been
     191! calculated in routine read_3d_binary.
    186192!------------------------------------------------------------------------------!
    187193
     
    194200
    195201    CHARACTER (LEN=20) :: field_char
     202
     203    INTEGER ::  nxlc, nxlf, nxl_on_file, nxrc, nxrf, nxr_on_file, nync, nynf, &
     204                nyn_on_file, nysc, nysf, nys_on_file
     205
     206    REAL, DIMENSION(nys_on_file-1:nyn_on_file+1,nxl_on_file-1:nxr_on_file+1) ::&
     207          tmp_2d
     208
     209    REAL, DIMENSION(nzb:nzt+1,nys_on_file-1:nyn_on_file+1, &
     210                    nxl_on_file-1:nxr_on_file+1) ::        &
     211          tmp_3d
     212
    196213!
    197214!-- Here the reading of user-defined restart data follows:
     
    207224!
    208225!             CASE ( 'u2_av' )
    209 !                ALLOCATE( u2_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
     226!                IF ( .NOT. ALLOCATED( u2_av )  THEN
     227!                   ALLOCATE( u2_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) )
     228!                ENDIF
     229!                READ ( 13 )  tmp_3d
    210230!                READ ( 13 )  u2_av
     231!                u2_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = &
     232!                                          tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1)
    211233!
    212234!             CASE DEFAULT
Note: See TracChangeset for help on using the changeset viewer.