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/read_var_list.f90

    r146 r147  
    88! hom_sum, volume_flow_area, volume_flow_initial moved from
    99! read_3d_binary to here,
    10 ! routine skip_var_list added at the end
     10! routines read_parts_of_var_list and skip_var_list added at the end
    1111!
    1212! Former revisions:
     
    148148    READ ( 13 )  statistic_regions
    149149    IF ( .NOT. ALLOCATED( ug ) )  THEN
    150        ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1), v_init(0:nz+1), &
    151                  pt_init(0:nz+1), q_init(0:nz+1), sa_init(0:nz+1),       &
     150       ALLOCATE( lad(0:nz+1), ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),    &
     151                 v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),        &
     152                 sa_init(0:nz+1),                                        &
    152153                 hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),  &
    153154                 hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
     
    314315          CASE ( 'nx' )
    315316             READ ( 13 )  nx
     317             nx_on_file = nx
    316318          CASE ( 'ny' )
    317319             READ ( 13 )  ny
     320             ny_on_file = ny
    318321          CASE ( 'ocean' )
    319322             READ ( 13 )  ocean
     
    542545
    543546
     547 SUBROUTINE read_parts_of_var_list
     548
     549!------------------------------------------------------------------------------!
     550! Description:
     551! ------------
     552! Skipping the global control variables from restart-file (binary format)
     553! except some informations needed when reading restart data from a previous
     554! run which used a smaller total domain.
     555!------------------------------------------------------------------------------!
     556
     557    USE control_parameters
     558    USE indices
     559    USE pegrid
     560    USE statistics
     561
     562    IMPLICIT NONE
     563
     564    CHARACTER (LEN=10) ::  version_on_file
     565    CHARACTER (LEN=30) ::  variable_chr
     566
     567    INTEGER ::  idum, max_pr_user_on_file, nz_on_file, &
     568                statistic_regions_on_file
     569
     570    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
     571
     572
     573    CALL check_open( 13 )
     574
     575    WRITE (9,*) 'rpovl: after check open 13'
     576    CALL local_flush( 9 )
     577    READ ( 13 )  version_on_file
     578
     579!
     580!-- Read number of PEs and horizontal index bounds of all PEs used in previous
     581!-- run
     582    READ ( 13 )  variable_chr
     583    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
     584       PRINT*, '+++ read_parts_of_var_list: numprocs not found in data from ', &
     585                    'prior run on PE ', myid
     586       CALL local_stop
     587    ENDIF
     588    READ ( 13 )  numprocs_previous_run
     589
     590    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
     591       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
     592    ENDIF
     593
     594    READ ( 13 )  variable_chr
     595    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
     596       PRINT*, '+++ read_parts_of_var_list: hor_index_bounds not found in da', &
     597                    'ta from prior run on PE ', myid
     598       CALL local_stop
     599    ENDIF
     600    READ ( 13 )  hor_index_bounds_previous_run
     601
     602!
     603!-- Read vertical number of gridpoints and number of different areas used
     604!-- for computing statistics. Allocate arrays depending on these values,
     605!-- which are needed for the following read instructions.
     606    READ ( 13 )  variable_chr
     607    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
     608       PRINT*, '+++ read_parts_of_var_list: nz not found in restart data file'
     609       CALL local_stop
     610    ENDIF
     611    READ ( 13 )  nz_on_file
     612    IF ( nz_on_file /= nz )  THEN
     613       IF ( myid == 0 )  THEN
     614          PRINT*, '+++ read_parts_of_var_list: mismatch concerning number of', &
     615                       ' gridpoints along z'
     616          PRINT*, '                   nz on file    = "', nz_on_file, '"'
     617          PRINT*, '                   nz from run   = "', nz, '"'
     618       ENDIF
     619       CALL local_stop
     620    ENDIF
     621
     622    READ ( 13 )  variable_chr
     623    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
     624       PRINT*, '+++ read_parts_of_var_list: max_pr_user not found in restart', &
     625                    ' data file'
     626       CALL local_stop
     627    ENDIF
     628    READ ( 13 )  max_pr_user_on_file
     629    IF ( max_pr_user_on_file > max_pr_user )  THEN
     630       IF ( myid == 0 )  THEN
     631          PRINT*, '+++ read_parts_of_var_list: too many user profiles on res', &
     632                       'tart data file'
     633          PRINT*, '                   max_pr_user on file    = "', &
     634                  max_pr_user_on_file, '"'
     635          PRINT*, '                   max_pr_user from run   = "', &
     636                  max_pr_user, '"'
     637       ENDIF
     638       CALL local_stop
     639    ENDIF
     640
     641    READ ( 13 )  variable_chr
     642    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
     643       PRINT*, '+++ read_var_list: statistic_regions not found in restart da', &
     644                    'ta file'
     645       CALL local_stop
     646    ENDIF
     647    READ ( 13 )  statistic_regions_on_file
     648    IF ( statistic_regions_on_file > statistic_regions )  THEN
     649       IF ( myid == 0 )  THEN
     650          PRINT*, '+++ read_parts_of_var_list: too many statistic regions on', &
     651                       ' restart data file'
     652          PRINT*, '                   statistic regions on file    = "', &
     653                  max_pr_user_on_file, '"'
     654          PRINT*, '                   statistic regions from run   = "', &
     655                  max_pr_user, '"'
     656       ENDIF
     657       CALL local_stop
     658    ENDIF
     659
     660
     661!
     662!-- Now read and check some control parameters and skip the rest
     663!-- The total domain of the pre-run must not be smaller than the subdomain
     664!-- of the current run, because the mapping of data from the pre-run does
     665!-- not work for this case.
     666    WRITE (9,*) 'wpovl: begin reading variables'
     667    CALL local_flush( 9 )
     668    READ ( 13 )  variable_chr
     669
     670    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
     671
     672       SELECT CASE ( TRIM( variable_chr ) )
     673
     674          CASE ( 'hom' )
     675             ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file, &
     676                       0:statistic_regions_on_file) )
     677             READ ( 13 )  hom_on_file
     678             hom = hom_on_file(:,:,1:pr_palm+max_pr_user,0:statistic_regions)
     679             DEALLOCATE( hom_on_file )
     680
     681          CASE ( 'nx' )
     682             READ ( 13 )  nx_on_file
     683             IF ( nx_on_file < ( nxr - nxl ) )  THEN
     684                PRINT*, '+++ read_parts_of_var_list: total domain along x on', &
     685                             ' restart file is smaller than current subdomain'
     686                PRINT*, '                            nx on file = ', nx_on_file
     687                PRINT*, '                            nxr - nxl  = ', nxr - nxl
     688                CALL local_stop
     689             ENDIF
     690
     691          CASE ( 'ny' )
     692             READ ( 13 )  ny_on_file
     693             IF ( ny_on_file < ( nyn - nys ) )  THEN
     694                PRINT*, '+++ read_parts_of_var_list: total domain along y on', &
     695                             ' restart file is smaller than current subdomain'
     696                PRINT*, '                            ny on file = ', ny_on_file
     697                PRINT*, '                            nyn - nys  = ', nyn - nys
     698                CALL local_stop
     699             ENDIF
     700
     701
     702          CASE DEFAULT
     703
     704             READ ( 13 )  idum
     705
     706       END SELECT
     707
     708       READ ( 13 )  variable_chr
     709
     710    ENDDO
     711
     712
     713 END SUBROUTINE read_parts_of_var_list
     714
     715
     716
    544717 SUBROUTINE skip_var_list
    545718
     
    550723!------------------------------------------------------------------------------!
    551724
     725    IMPLICIT NONE
     726
    552727    CHARACTER (LEN=10) ::  version_on_file
    553728    CHARACTER (LEN=30) ::  variable_chr
     
    556731
    557732
     733    WRITE (9,*) 'skipvl #1'
     734    CALL local_flush( 9 )
    558735    READ ( 13 )  version_on_file
    559736
    560     READ ( 13 )  variable_chr
     737    WRITE (9,*) 'skipvl before variable_chr'
     738    CALL local_flush( 9 )
     739    READ ( 13 )  variable_chr
     740    WRITE (9,*) 'skipvl after variable_chr'
     741    CALL local_flush( 9 )
    561742
    562743    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
    563744
     745    WRITE (9,*) 'skipvl chr = ', variable_chr
     746    CALL local_flush( 9 )
    564747       READ ( 13 )  idum
    565748       READ ( 13 )  variable_chr
    566749
    567750    ENDDO
     751    WRITE (9,*) 'skipvl last'
     752    CALL local_flush( 9 )
    568753
    569754
Note: See TracChangeset for help on using the changeset viewer.