SUBROUTINE read_3d_binary !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: read_3d_binary.f90 198 2008-09-17 08:55:28Z heinze $ ! ! 150 2008-02-29 08:19:58Z raasch ! Files from which restart data are to be read are determined and subsequently ! opened. The total domain on the restart file is allowed to be smaller than ! the current total domain. In this case it will be periodically mapped on the ! current domain (needed for recycling method). ! +call of user_read_restart_data, -dopr_time_count, ! hom_sum, volume_flow_area, volume_flow_initial moved to read_var_list, ! reading of old profil parameters (cross_..., dopr_crossindex, profile_***) ! removed, initialization of spectrum_x|y removed ! ! 102 2007-07-27 09:09:17Z raasch ! +uswst, uswst_m, vswst, vswst_m ! ! 96 2007-06-04 08:07:41Z raasch ! +rho_av, sa, sa_av, saswsb, saswst ! ! 73 2007-03-20 08:33:14Z raasch ! +precipitation_amount, precipitation_rate_av, rif_wall, u_m_l, u_m_r, etc., ! z0_av ! ! 19 2007-02-23 04:53:48Z raasch ! +qswst, qswst_m, tswst, tswst_m ! ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.4 2006/08/04 15:02:32 raasch ! +iran, iran_part ! ! Revision 1.1 2004/04/30 12:47:27 raasch ! Initial revision ! ! ! Description: ! ------------ ! Binary input of variables and arrays from restart file !------------------------------------------------------------------------------! USE arrays_3d USE averaging USE cloud_parameters USE control_parameters USE cpulog USE indices USE interfaces USE particle_attributes USE pegrid USE profil_parameter USE random_function_mod USE statistics IMPLICIT NONE CHARACTER (LEN=5) :: myid_char_save CHARACTER (LEN=10) :: binary_version, version_on_file CHARACTER (LEN=20) :: field_chr INTEGER :: files_to_be_opened, i, j, myid_on_file, & numprocs_on_file, nxlc, nxlf, nxlpr, nxl_on_file, nxrc, nxrf, & nxrpr, nxr_on_file, nync, nynf, nynpr, nyn_on_file, nysc, & nysf, nyspr, nys_on_file, nzb_on_file, nzt_on_file, offset_x, & offset_y INTEGER, DIMENSION(numprocs_previous_run*4) :: file_list, nxlfa, nxrfa, & nynfa, nysfa, offset_xa, offset_ya REAL, DIMENSION(:,:), ALLOCATABLE :: tmp_2d REAL, DIMENSION(:,:,:), ALLOCATABLE :: tmp_3d, tmp_3dw REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: tmp_4d ! !-- Read data from previous model run. CALL cpu_log( log_point_s(14), 'read_3d_binary', 'start' ) ! !-- Check which of the restart files contain data needed for the subdomain !-- of this PE files_to_be_opened = 0 DO i = 1, numprocs_previous_run nxlpr = hor_index_bounds_previous_run(1,i-1) nxrpr = hor_index_bounds_previous_run(2,i-1) nyspr = hor_index_bounds_previous_run(3,i-1) nynpr = hor_index_bounds_previous_run(4,i-1) ! !-- Determine the offsets. They may be non-zero in case that the total domain !-- on file is smaller than the current total domain. offset_x = ( nxl / ( nx_on_file + 1 ) ) * ( nx_on_file + 1 ) offset_y = ( nys / ( ny_on_file + 1 ) ) * ( ny_on_file + 1 ) ! !-- Only data which overlap with the current subdomain have to be read IF ( nxlpr <= nxr-offset_x .AND. nxrpr >= nxl-offset_x .AND. & nyspr <= nyn-offset_y .AND. nynpr >= nys-offset_y ) THEN files_to_be_opened = files_to_be_opened + 1 file_list(files_to_be_opened) = i-1 ! !-- Index bounds of overlapping data nxlfa(files_to_be_opened) = MAX( nxl-offset_x, nxlpr ) nxrfa(files_to_be_opened) = MIN( nxr-offset_x, nxrpr ) nysfa(files_to_be_opened) = MAX( nys-offset_y, nyspr ) nynfa(files_to_be_opened) = MIN( nyn-offset_y, nynpr ) WRITE (9,*) '*** reading from file: ', i WRITE (9,*) ' index bounds on file:' WRITE (9,*) ' nxlpr=', nxlpr, ' nxrpr=', nxrpr WRITE (9,*) ' nyspr=', nyspr, ' nynpr=', nynpr WRITE (9,*) ' index bounds of current subdmain:' WRITE (9,*) ' nxl =', nxl, ' nxr =', nxr WRITE (9,*) ' nys =', nys, ' nyn =', nyn WRITE (9,*) ' offset used:' WRITE (9,*) ' offset_x=', offset_x, ' offset_y=', offset_y WRITE (9,*) ' bounds of overlapping data:' WRITE (9,*) ' nxlfa=', nxlfa(files_to_be_opened), ' nxrfa=', nxrfa(files_to_be_opened) WRITE (9,*) ' nysfa=', nysfa(files_to_be_opened), ' nynfa=', nynfa(files_to_be_opened) CALL local_flush( 9 ) offset_xa(files_to_be_opened) = offset_x offset_ya(files_to_be_opened) = offset_y ENDIF ! !-- If the total domain on file is smaller than the current total domain, !-- and if the current subdomain extends beyond the limits of the total !-- domain of file, the respective file may be opened again (three times !-- maximum) to read the still missing parts, which are then added !-- "cyclically". !-- Overlap along x: IF ( ( nxr - offset_x ) > nx_on_file ) THEN offset_x = offset_x + ( nx_on_file + 1 ) IF ( nxlpr <= nxr-offset_x .AND. nxrpr >= nxl-offset_x .AND. & nyspr <= nyn-offset_y .AND. nynpr >= nys-offset_y ) THEN files_to_be_opened = files_to_be_opened + 1 file_list(files_to_be_opened) = i-1 ! !-- Index bounds of overlapping data nxlfa(files_to_be_opened) = MAX( nxl-offset_x, nxlpr ) nxrfa(files_to_be_opened) = MIN( nxr-offset_x, nxrpr ) nysfa(files_to_be_opened) = MAX( nys-offset_y, nyspr ) nynfa(files_to_be_opened) = MIN( nyn-offset_y, nynpr ) WRITE (9,*) '*** reading from file: ', i WRITE (9,*) ' index bounds on file:' WRITE (9,*) ' nxlpr=', nxlpr, ' nxrpr=', nxrpr WRITE (9,*) ' nyspr=', nyspr, ' nynpr=', nynpr WRITE (9,*) ' index bounds of current subdmain:' WRITE (9,*) ' nxl =', nxl, ' nxr =', nxr WRITE (9,*) ' nys =', nys, ' nyn =', nyn WRITE (9,*) ' offset used:' WRITE (9,*) ' offset_x=', offset_x, ' offset_y=', offset_y WRITE (9,*) ' bounds of overlapping data:' WRITE (9,*) ' nxlfa=', nxlfa(files_to_be_opened), ' nxrfa=', nxrfa(files_to_be_opened) WRITE (9,*) ' nysfa=', nysfa(files_to_be_opened), ' nynfa=', nynfa(files_to_be_opened) CALL local_flush( 9 ) offset_xa(files_to_be_opened) = offset_x offset_ya(files_to_be_opened) = offset_y ENDIF offset_x = offset_x - ( nx_on_file + 1 ) ENDIF ! !-- Overlap along y: IF ( ( nyn - offset_y ) > ny_on_file ) THEN offset_y = offset_y + ( ny_on_file + 1 ) IF ( nxlpr <= nxr-offset_x .AND. nxrpr >= nxl-offset_x .AND. & nyspr <= nyn-offset_y .AND. nynpr >= nys-offset_y ) THEN files_to_be_opened = files_to_be_opened + 1 file_list(files_to_be_opened) = i-1 ! !-- Index bounds of overlapping data nxlfa(files_to_be_opened) = MAX( nxl-offset_x, nxlpr ) nxrfa(files_to_be_opened) = MIN( nxr-offset_x, nxrpr ) nysfa(files_to_be_opened) = MAX( nys-offset_y, nyspr ) nynfa(files_to_be_opened) = MIN( nyn-offset_y, nynpr ) WRITE (9,*) '*** reading from file: ', i WRITE (9,*) ' index bounds on file:' WRITE (9,*) ' nxlpr=', nxlpr, ' nxrpr=', nxrpr WRITE (9,*) ' nyspr=', nyspr, ' nynpr=', nynpr WRITE (9,*) ' index bounds of current subdmain:' WRITE (9,*) ' nxl =', nxl, ' nxr =', nxr WRITE (9,*) ' nys =', nys, ' nyn =', nyn WRITE (9,*) ' offset used:' WRITE (9,*) ' offset_x=', offset_x, ' offset_y=', offset_y WRITE (9,*) ' bounds of overlapping data:' WRITE (9,*) ' nxlfa=', nxlfa(files_to_be_opened), ' nxrfa=', nxrfa(files_to_be_opened) WRITE (9,*) ' nysfa=', nysfa(files_to_be_opened), ' nynfa=', nynfa(files_to_be_opened) CALL local_flush( 9 ) offset_xa(files_to_be_opened) = offset_x offset_ya(files_to_be_opened) = offset_y ENDIF offset_y = offset_y - ( ny_on_file + 1 ) ENDIF !-- Overlap along x and y: IF ( ( nxr - offset_x ) > nx_on_file .AND. & ( nyn - offset_y ) > ny_on_file ) THEN offset_x = offset_x + ( nx_on_file + 1 ) offset_y = offset_y + ( ny_on_file + 1 ) IF ( nxlpr <= nxr-offset_x .AND. nxrpr >= nxl-offset_x .AND. & nyspr <= nyn-offset_y .AND. nynpr >= nys-offset_y ) THEN files_to_be_opened = files_to_be_opened + 1 file_list(files_to_be_opened) = i-1 ! !-- Index bounds of overlapping data nxlfa(files_to_be_opened) = MAX( nxl-offset_x, nxlpr ) nxrfa(files_to_be_opened) = MIN( nxr-offset_x, nxrpr ) nysfa(files_to_be_opened) = MAX( nys-offset_y, nyspr ) nynfa(files_to_be_opened) = MIN( nyn-offset_y, nynpr ) WRITE (9,*) '*** reading from file: ', i WRITE (9,*) ' index bounds on file:' WRITE (9,*) ' nxlpr=', nxlpr, ' nxrpr=', nxrpr WRITE (9,*) ' nyspr=', nyspr, ' nynpr=', nynpr WRITE (9,*) ' index bounds of current subdmain:' WRITE (9,*) ' nxl =', nxl, ' nxr =', nxr WRITE (9,*) ' nys =', nys, ' nyn =', nyn WRITE (9,*) ' offset used:' WRITE (9,*) ' offset_x=', offset_x, ' offset_y=', offset_y WRITE (9,*) ' bounds of overlapping data:' WRITE (9,*) ' nxlfa=', nxlfa(files_to_be_opened), ' nxrfa=', nxrfa(files_to_be_opened) WRITE (9,*) ' nysfa=', nysfa(files_to_be_opened), ' nynfa=', nynfa(files_to_be_opened) CALL local_flush( 9 ) offset_xa(files_to_be_opened) = offset_x offset_ya(files_to_be_opened) = offset_y ENDIF offset_x = offset_x - ( nx_on_file + 1 ) offset_y = offset_y - ( ny_on_file + 1 ) ENDIF ENDDO ! !-- Save the id-string of the current process, since myid_char may now be used !-- to open files created by PEs with other id. myid_char_save = myid_char ! !-- Test output (remove later) DO i = 1, numprocs_previous_run WRITE (9,*) 'i=',i-1, ' ibs= ',hor_index_bounds_previous_run(1:4,i-1) ENDDO CALL local_flush( 9 ) IF ( files_to_be_opened /= 1 .OR. numprocs /= numprocs_previous_run ) & THEN PRINT*, '*** number of PEs or virtual PE-grid changed in restart run' PRINT*, ' PE', myid, ' will read from files ', & file_list(1:files_to_be_opened) ENDIF ! !-- Read data from all restart files determined above DO i = 1, files_to_be_opened j = file_list(i) ! !-- Set the filename (underscore followed by four digit processor id) WRITE (myid_char,'(''_'',I4.4)') j WRITE (9,*) 'myid=',myid,' opening file "',myid_char,'"' CALL local_flush( 9 ) ! !-- Open the restart file. If this file has been created by PE0 (_0000), !-- the global variables at the beginning of the file have to be skipped !-- first. CALL check_open( 13 ) WRITE (9,*) 'before skipping' CALL local_flush( 9 ) IF ( j == 0 ) CALL skip_var_list WRITE (9,*) 'skipping done' CALL local_flush( 9 ) ! !-- First compare the version numbers READ ( 13 ) version_on_file binary_version = '3.1' IF ( TRIM( version_on_file ) /= TRIM( binary_version ) ) THEN IF ( myid == 0 ) THEN PRINT*, '+++ init_3d_model: version mismatch concerning data ', & 'from prior run' PRINT*, ' version on file = "', TRIM( version_on_file ),& '"' PRINT*, ' version in program = "', TRIM( binary_version ), & '"' ENDIF CALL local_stop ENDIF ! !-- Read number of processors, processor-id, and array ranges. !-- Compare the array ranges with those stored in the index bound array. READ ( 13 ) numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file, & nys_on_file, nyn_on_file, nzb_on_file, nzt_on_file IF ( nxl_on_file /= hor_index_bounds_previous_run(1,j) ) THEN PRINT*, '+++ read_3d_binary: problem with index bound nxl on ', & ' restart file "', myid_char, '"' PRINT*, ' nxl = ', nxl_on_file, ' but it should be' PRINT*, ' = ', hor_index_bounds_previous_run(1,j) PRINT*, ' from the index bound information array' #if defined( __parallel ) CALL MPI_ABORT( comm2d, 9999, ierr ) #else CALL local_stop #endif ENDIF IF ( nxr_on_file /= hor_index_bounds_previous_run(2,j) ) THEN PRINT*, '+++ read_3d_binary: problem with index bound nxr on ', & ' restart file "', myid_char, '"' PRINT*, ' nxr = ', nxr_on_file, ' but it should be' PRINT*, ' = ', hor_index_bounds_previous_run(2,j) PRINT*, ' from the index bound information array' #if defined( __parallel ) CALL MPI_ABORT( comm2d, 9999, ierr ) #else CALL local_stop #endif ENDIF IF ( nys_on_file /= hor_index_bounds_previous_run(3,j) ) THEN PRINT*, '+++ read_3d_binary: problem with index bound nys on ', & ' restart file "', myid_char, '"' PRINT*, ' nys = ', nys_on_file, ' but it should be' PRINT*, ' = ', hor_index_bounds_previous_run(3,j) PRINT*, ' from the index bound information array' #if defined( __parallel ) CALL MPI_ABORT( comm2d, 9999, ierr ) #else CALL local_stop #endif ENDIF IF ( nyn_on_file /= hor_index_bounds_previous_run(4,j) ) THEN PRINT*, '+++ read_3d_binary: problem with index bound nyn on ', & ' restart file "', myid_char, '"' PRINT*, ' nyn = ', nyn_on_file, ' but it should be' PRINT*, ' = ', hor_index_bounds_previous_run(4,j) PRINT*, ' from the index bound information array' #if defined( __parallel ) CALL MPI_ABORT( comm2d, 9999, ierr ) #else CALL local_stop #endif ENDIF IF ( nzb_on_file /= nzb ) THEN PRINT*, '+++ read_3d_binary: mismatch between actual data and data ' PRINT*, ' from prior run on PE ', myid PRINT*, ' nzb on file = ', nzb_on_file PRINT*, ' nzb = ', nzb CALL local_stop ENDIF IF ( nzt_on_file /= nzt ) THEN PRINT*, '+++ read_3d_binary: mismatch between actual data and data ' PRINT*, ' from prior run on PE ', myid PRINT*, ' nzt on file = ', nzt_on_file PRINT*, ' nzt = ', nzt CALL local_stop ENDIF ! !-- Allocate temporary arrays sized as the arrays on the restart file ALLOCATE( tmp_2d(nys_on_file-1:nyn_on_file+1, & nxl_on_file-1:nxr_on_file+1), & tmp_3d(nzb:nzt+1,nys_on_file-1:nyn_on_file+1, & nxl_on_file-1:nxr_on_file+1) ) ! !-- Get the index range of the subdomain on file which overlap with the !-- current subdomain nxlf = nxlfa(i) nxlc = nxlfa(i) + offset_xa(i) nxrf = nxrfa(i) nxrc = nxrfa(i) + offset_xa(i) nysf = nysfa(i) nysc = nysfa(i) + offset_ya(i) nynf = nynfa(i) nync = nynfa(i) + offset_ya(i) ! !-- Read arrays !-- ATTENTION: If the following read commands have been altered, the !-- ---------- version number of the variable binary_version must be altered, !-- too. Furthermore, the output list of arrays in write_3d_binary !-- must also be altered accordingly. READ ( 13 ) field_chr DO WHILE ( TRIM( field_chr ) /= '*** end ***' ) WRITE (9,*) 'var = ', field_chr CALL local_flush( 9 ) SELECT CASE ( TRIM( field_chr ) ) CASE ( 'e' ) READ ( 13 ) tmp_3d e(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'e_av' ) IF ( .NOT. ALLOCATED( e_av ) ) THEN ALLOCATE( e_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d e_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'e_m' ) READ ( 13 ) tmp_3d e_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'iran' ) ! matching random numbers is still unresolved issue READ ( 13 ) iran, iran_part CASE ( 'kh' ) READ ( 13 ) tmp_3d kh(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'kh_m' ) READ ( 13 ) tmp_3d kh_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'km' ) READ ( 13 ) tmp_3d km(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'km_m' ) READ ( 13 ) tmp_3d km_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'lwp_av' ) IF ( .NOT. ALLOCATED( lwp_av ) ) THEN ALLOCATE( lwp_av(nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_2d lwp_av(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'p' ) READ ( 13 ) tmp_3d p(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'p_av' ) IF ( .NOT. ALLOCATED( p_av ) ) THEN ALLOCATE( p_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d p_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'pc_av' ) IF ( .NOT. ALLOCATED( pc_av ) ) THEN ALLOCATE( pc_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d pc_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'pr_av' ) IF ( .NOT. ALLOCATED( pr_av ) ) THEN ALLOCATE( pr_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d pr_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'precipitation_amount' ) READ ( 13 ) tmp_2d precipitation_amount(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'precipitation_rate_a' ) IF ( .NOT. ALLOCATED( precipitation_rate_av ) ) THEN ALLOCATE( precipitation_rate_av(nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_2d precipitation_rate_av(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'pt' ) READ ( 13 ) tmp_3d pt(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'pt_av' ) IF ( .NOT. ALLOCATED( pt_av ) ) THEN ALLOCATE( pt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d pt_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'pt_m' ) READ ( 13 ) tmp_3d pt_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'q' ) READ ( 13 ) tmp_3d q(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'q_av' ) IF ( .NOT. ALLOCATED( q_av ) ) THEN ALLOCATE( q_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d q_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'q_m' ) READ ( 13 ) tmp_3d q_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'ql' ) READ ( 13 ) tmp_3d ql(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'ql_av' ) IF ( .NOT. ALLOCATED( ql_av ) ) THEN ALLOCATE( ql_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d ql_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'ql_c_av' ) IF ( .NOT. ALLOCATED( ql_c_av ) ) THEN ALLOCATE( ql_c_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d ql_c_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'ql_v_av' ) IF ( .NOT. ALLOCATED( ql_v_av ) ) THEN ALLOCATE( ql_v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d ql_v_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'ql_vp_av' ) IF ( .NOT. ALLOCATED( ql_vp_av ) ) THEN ALLOCATE( ql_vp_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d ql_vp_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'qs' ) READ ( 13 ) tmp_2d qs(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'qsws' ) READ ( 13 ) tmp_2d qsws(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'qsws_m' ) READ ( 13 ) tmp_2d qsws_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'qswst' ) READ ( 13 ) tmp_2d qswst(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'qswst_m' ) READ ( 13 ) tmp_2d qswst_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'qv_av' ) IF ( .NOT. ALLOCATED( qv_av ) ) THEN ALLOCATE( qv_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d qv_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'random_iv' ) ! still unresolved issue READ ( 13 ) random_iv READ ( 13 ) random_iy CASE ( 'rho_av' ) IF ( .NOT. ALLOCATED( rho_av ) ) THEN ALLOCATE( rho_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d rho_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'rif' ) READ ( 13 ) tmp_2d rif(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'rif_m' ) READ ( 13 ) tmp_2d rif_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'rif_wall' ) ALLOCATE( tmp_4d(nzb:nzt+1,nys_on_file-1:nyn_on_file+1, & nxl_on_file-1:nxr_on_file+1,1:4) ) READ ( 13 ) tmp_4d rif_wall(:,nysc-1:nync+1,nxlc-1:nxrc+1,:) = & tmp_4d(:,nysf-1:nynf+1,nxlf-1:nxrf+1,:) DEALLOCATE( tmp_4d ) CASE ( 's_av' ) IF ( .NOT. ALLOCATED( s_av ) ) THEN ALLOCATE( s_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d s_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'sa' ) READ ( 13 ) tmp_3d sa(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'sa_av' ) IF ( .NOT. ALLOCATED( sa_av ) ) THEN ALLOCATE( sa_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d sa_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'saswsb' ) READ ( 13 ) tmp_2d saswsb(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'saswst' ) READ ( 13 ) tmp_2d saswst(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'shf' ) READ ( 13 ) tmp_2d shf(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'shf_m' ) READ ( 13 ) tmp_2d shf_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'spectrum_x' ) READ ( 13 ) spectrum_x CASE ( 'spectrum_y' ) READ ( 13 ) spectrum_y CASE ( 'ts' ) READ ( 13 ) tmp_2d ts(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'ts_av' ) IF ( .NOT. ALLOCATED( ts_av ) ) THEN ALLOCATE( ts_av(nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_2d ts_av(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'tswst' ) READ ( 13 ) tmp_2d tswst(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'tswst_m' ) READ ( 13 ) tmp_2d tswst_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'u' ) READ ( 13 ) tmp_3d u(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'u_av' ) IF ( .NOT. ALLOCATED( u_av ) ) THEN ALLOCATE( u_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d u_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'u_m' ) READ ( 13 ) tmp_3d u_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'u_m_l' ) ALLOCATE( tmp_3dw(nzb:nzt+1,nys_on_file-1:nyn_on_file+1,1:2) ) READ ( 13 ) tmp_3dw IF ( outflow_l ) THEN u_m_l(:,nysc-1:nync+1,:) = tmp_3dw(:,nysf-1:nynf+1,:) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'u_m_n' ) ALLOCATE( tmp_3dw(nzb:nzt+1,ny-1:ny, & nxl_on_file-1:nxr_on_file+1) ) READ ( 13 ) tmp_3dw IF ( outflow_n ) THEN u_m_n(:,:,nxlc-1:nxrc+1) = tmp_3dw(:,:,nxlf-1:nxrf+1) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'u_m_r' ) ALLOCATE( tmp_3dw(nzb:nzt+1,nys_on_file-1:nyn_on_file+1, & nx-1:nx) ) READ ( 13 ) tmp_3dw IF ( outflow_r ) THEN u_m_r(:,nysc-1:nync+1,:) = tmp_3dw(:,nysf-1:nynf+1,:) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'u_m_s' ) ALLOCATE( tmp_3dw(nzb:nzt+1,0:1, & nxl_on_file-1:nxr_on_file+1) ) READ ( 13 ) tmp_3dw IF ( outflow_s ) THEN u_m_s(:,:,nxlc-1:nxrc+1) = tmp_3dw(:,:,nxlf-1:nxrf+1) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'us' ) READ ( 13 ) tmp_2d us(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'usws' ) READ ( 13 ) tmp_2d usws(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'uswst' ) READ ( 13 ) tmp_2d uswst(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'usws_m' ) READ ( 13 ) tmp_2d usws_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'uswst_m' ) READ ( 13 ) tmp_2d uswst_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'us_av' ) IF ( .NOT. ALLOCATED( us_av ) ) THEN ALLOCATE( us_av(nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_2d us_av(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'v' ) READ ( 13 ) tmp_3d v(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'v_av' ) IF ( .NOT. ALLOCATED( v_av ) ) THEN ALLOCATE( v_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d v_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'v_m' ) READ ( 13 ) tmp_3d v_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'v_m_l' ) ALLOCATE( tmp_3dw(nzb:nzt+1,nys_on_file-1:nyn_on_file+1,0:1) ) READ ( 13 ) tmp_3dw IF ( outflow_l ) THEN v_m_l(:,nysc-1:nync+1,:) = tmp_3dw(:,nysf-1:nynf+1,:) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'v_m_n' ) ALLOCATE( tmp_3dw(nzb:nzt+1,ny-1:ny, & nxl_on_file-1:nxr_on_file+1) ) READ ( 13 ) tmp_3dw IF ( outflow_n ) THEN v_m_n(:,:,nxlc-1:nxrc+1) = tmp_3dw(:,:,nxlf-1:nxrf+1) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'v_m_r' ) ALLOCATE( tmp_3dw(nzb:nzt+1,nys_on_file-1:nyn_on_file+1, & nx-1:nx) ) READ ( 13 ) tmp_3dw IF ( outflow_r ) THEN v_m_r(:,nysc-1:nync+1,:) = tmp_3dw(:,nysf-1:nynf+1,:) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'v_m_s' ) ALLOCATE( tmp_3dw(nzb:nzt+1,1:2, & nxl_on_file-1:nxr_on_file+1) ) READ ( 13 ) tmp_3dw IF ( outflow_s ) THEN v_m_s(:,:,nxlc-1:nxrc+1) = tmp_3dw(:,:,nxlf-1:nxrf+1) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'vpt' ) READ ( 13 ) tmp_3d vpt(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'vpt_av' ) IF ( .NOT. ALLOCATED( vpt_av ) ) THEN ALLOCATE( vpt_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d vpt_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'vpt_m' ) READ ( 13 ) tmp_3d vpt_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'vsws' ) READ ( 13 ) tmp_2d vsws(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'vswst' ) READ ( 13 ) tmp_2d vswst(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'vsws_m' ) READ ( 13 ) tmp_2d vsws_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'vswst_m' ) READ ( 13 ) tmp_2d vswst_m(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'w' ) READ ( 13 ) tmp_3d w(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'w_av' ) IF ( .NOT. ALLOCATED( w_av ) ) THEN ALLOCATE( w_av(nzb:nzt+1,nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_3d w_av(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'w_m' ) READ ( 13 ) tmp_3d w_m(:,nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_3d(:,nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'w_m_l' ) ALLOCATE( tmp_3dw(nzb:nzt+1,nys_on_file-1:nyn_on_file+1,0:1) ) READ ( 13 ) tmp_3dw IF ( outflow_l ) THEN w_m_l(:,nysc-1:nync+1,:) = tmp_3dw(:,nysf-1:nynf+1,:) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'w_m_n' ) ALLOCATE( tmp_3dw(nzb:nzt+1,ny-1:ny, & nxl_on_file-1:nxr_on_file+1) ) READ ( 13 ) tmp_3dw IF ( outflow_n ) THEN w_m_n(:,:,nxlc-1:nxrc+1) = tmp_3dw(:,:,nxlf-1:nxrf+1) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'w_m_r' ) ALLOCATE( tmp_3dw(nzb:nzt+1,nys_on_file-1:nyn_on_file+1, & nx-1:nx) ) READ ( 13 ) tmp_3dw IF ( outflow_r ) THEN w_m_r(:,nysc-1:nync+1,:) = tmp_3dw(:,nysf-1:nynf+1,:) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'w_m_s' ) ALLOCATE( tmp_3dw(nzb:nzt+1,0:1, & nxl_on_file-1:nxr_on_file+1) ) READ ( 13 ) tmp_3dw IF ( outflow_s ) THEN w_m_s(:,:,nxlc-1:nxrc+1) = tmp_3dw(:,:,nxlf-1:nxrf+1) ENDIF DEALLOCATE( tmp_3dw ) CASE ( 'z0' ) READ ( 13 ) tmp_2d z0(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE ( 'z0_av' ) IF ( .NOT. ALLOCATED( z0_av ) ) THEN ALLOCATE( z0_av(nys-1:nyn+1,nxl-1:nxr+1) ) ENDIF READ ( 13 ) tmp_2d z0_av(nysc-1:nync+1,nxlc-1:nxrc+1) = & tmp_2d(nysf-1:nynf+1,nxlf-1:nxrf+1) CASE DEFAULT PRINT*, '+++ read_3d_binary: unknown field named "', & TRIM( field_chr ), '" found in' PRINT*, ' data from prior run on PE ', myid CALL local_stop END SELECT ! !-- Read next character string READ ( 13 ) field_chr ENDDO ! loop over variables ! !-- Read user-defined restart data CALL user_read_restart_data( nxlc, nxlf, nxl_on_file, nxrc, nxrf, & nxr_on_file, nync, nynf, nyn_on_file, & nysc, nysf, nys_on_file, tmp_2d, tmp_3d ) ! !-- Close the restart file CALL close_file( 13 ) DEALLOCATE( tmp_2d, tmp_3d ) ENDDO ! loop over restart files ! !-- Restore the original filename for the restart file to be written myid_char = myid_char_save ! !-- End of time measuring for reading binary data CALL cpu_log( log_point_s(14), 'read_3d_binary', 'stop' ) END SUBROUTINE read_3d_binary