Changeset 557 for palm/trunk/SOURCE
- Timestamp:
- Sep 7, 2010 2:50:07 PM (14 years ago)
- Location:
- palm/trunk/SOURCE
- Files:
-
- 11 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/advec_particles.f90
r520 r557 3794 3794 3795 3795 IMPLICIT NONE 3796 3797 INTEGER :: rbs 3796 3798 3797 3799 CHARACTER (LEN=10) :: particle_binary_version … … 3814 3816 ENDIF 3815 3817 3816 ! 3817 !-- Write the version number of the binary format. 3818 !-- Attention: After changes to the following output commands the version 3819 !-- --------- number of the variable particle_binary_version must be changed! 3818 DO rbs = 0, numprocs/binary_io_blocksize-1 3819 IF ( mod_numprocs_size == rbs ) THEN 3820 ! 3821 !-- Write the version number of the binary format. 3822 !-- Attention: After changes to the following output commands the version 3823 !-- --- number of the variable particle_binary_version must be changed! 3820 3824 !-- Also, the version number and the list of arrays to be read in 3821 3825 !-- init_particles must be adjusted accordingly. 3822 particle_binary_version = '3.0'3823 WRITE ( 90 ) particle_binary_version3824 3825 ! 3826 !-- Write some particle parameters, the size of the particle arrays as well as3827 !-- other dvrp-plot variables.3828 WRITE ( 90 ) bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,&3826 particle_binary_version = '3.0' 3827 WRITE ( 90 ) particle_binary_version 3828 3829 ! 3830 !-- Write some particle parameters, the size of the particle arrays 3831 !-- as well as other dvrp-plot variables. 3832 WRITE ( 90 ) bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, & 3829 3833 maximum_number_of_particles, maximum_number_of_tailpoints, & 3830 3834 maximum_number_of_tails, number_of_initial_particles, & … … 3833 3837 time_write_particle_data, uniform_particles 3834 3838 3835 IF ( number_of_initial_particles /= 0 ) WRITE ( 90 ) initial_particles 3836 3837 WRITE ( 90 ) prt_count, prt_start_index 3838 WRITE ( 90 ) particles 3839 3840 IF ( use_particle_tails ) THEN 3841 WRITE ( 90 ) particle_tail_coordinates 3842 ENDIF 3839 IF ( number_of_initial_particles /= 0 ) & 3840 WRITE ( 90 ) initial_particles 3841 3842 WRITE ( 90 ) prt_count, prt_start_index 3843 WRITE ( 90 ) particles 3844 3845 IF ( use_particle_tails ) THEN 3846 WRITE ( 90 ) particle_tail_coordinates 3847 ENDIF 3848 3849 ENDIF 3850 CALL MPI_BARRIER(comm2d, ierr ) 3851 ENDDO 3843 3852 3844 3853 CLOSE ( 90 ) -
palm/trunk/SOURCE/data_output_2d.f90
r494 r557 77 77 CHARACTER (LEN=50) :: rtext 78 78 INTEGER :: av, ngp, file_id, i, if, is, iis, j, k, l, layer_xy, n, psi, & 79 s, sender, &79 rbs, s, sender, & 80 80 ind(4) 81 81 LOGICAL :: found, resorted, two_d … … 720 720 ENDIF 721 721 #endif 722 WRITE ( 21 ) nxl-1, nxr+1, nys-1, nyn+1 723 WRITE ( 21 ) local_2d 724 722 DO rbs = 0, numprocs/binary_io_blocksize-1 723 IF ( mod_numprocs_size == rbs ) THEN 724 WRITE ( 21 ) nxl-1, nxr+1, nys-1, nyn+1 725 WRITE ( 21 ) local_2d 726 ENDIF 727 CALL MPI_BARRIER(comm2d, ierr ) 728 ENDDO 729 725 730 ELSE 726 731 ! … … 1013 1018 ENDIF 1014 1019 #endif 1015 IF ( ( section(is,s) >= nys .AND. & 1016 section(is,s) <= nyn ) .OR. & 1017 ( section(is,s) == -1 .AND. nys-1 == -1 ) ) & 1018 THEN 1019 WRITE (22) nxl-1, nxr+1, nzb, nzt+1 1020 WRITE (22) local_2d 1021 ELSE 1022 WRITE (22) -1, -1, -1, -1 1023 ENDIF 1020 DO rbs = 0, numprocs/binary_io_blocksize-1 1021 IF ( mod_numprocs_size == rbs ) THEN 1022 IF ( ( section(is,s) >= nys .AND. & 1023 section(is,s) <= nyn ) .OR. & 1024 ( section(is,s) == -1 .AND. & 1025 nys-1 == -1 ) ) & 1026 THEN 1027 WRITE (22) nxl-1, nxr+1, nzb, nzt+1 1028 WRITE (22) local_2d 1029 ELSE 1030 WRITE (22) -1, -1, -1, -1 1031 ENDIF 1032 ENDIF 1033 CALL MPI_BARRIER(comm2d, ierr ) 1034 ENDDO 1024 1035 1025 1036 ELSE … … 1312 1323 ENDIF 1313 1324 #endif 1314 IF ( ( section(is,s) >= nxl .AND. & 1315 section(is,s) <= nxr ) .OR. & 1316 ( section(is,s) == -1 .AND. nxl-1 == -1 ) ) & 1317 THEN 1318 WRITE (23) nys-1, nyn+1, nzb, nzt+1 1319 WRITE (23) local_2d 1320 ELSE 1321 WRITE (23) -1, -1, -1, -1 1322 ENDIF 1325 DO rbs = 0, numprocs/binary_io_blocksize-1 1326 IF ( mod_numprocs_size == rbs ) THEN 1327 IF ( ( section(is,s) >= nxl .AND. & 1328 section(is,s) <= nxr ) .OR. & 1329 ( section(is,s) == -1 .AND. & 1330 nxl-1 == -1 ) ) & 1331 THEN 1332 WRITE (23) nys-1, nyn+1, nzb, nzt+1 1333 WRITE (23) local_2d 1334 ELSE 1335 WRITE (23) -1, -1, -1, -1 1336 ENDIF 1337 ENDIF 1338 CALL MPI_BARRIER(comm2d, ierr ) 1339 ENDDO 1323 1340 1324 1341 ELSE -
palm/trunk/SOURCE/data_output_3d.f90
r494 r557 60 60 CHARACTER (LEN=9) :: simulated_time_mod 61 61 62 INTEGER :: av, i, if, j, k, n, pos, prec, psi 62 INTEGER :: av, i, if, j, k, n, pos, prec, psi, rbs 63 63 64 64 LOGICAL :: found, resorted … … 382 382 !-- Compression, output of compression information on FLD-file and output 383 383 !-- of compressed data. 384 CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, nyn, nys, & 385 nzb, nz_do3d, prec ) 384 DO rbs = 0, numprocs/binary_io_blocksize-1 385 IF ( mod_numprocs_size == rbs ) THEN 386 CALL write_compressed( local_pf, 30, 33, myid, nxl, nxr, & 387 nyn, nys, nzb, nz_do3d, prec ) 388 ENDIF 389 CALL MPI_BARRIER(comm2d, ierr ) 390 ENDDO 391 386 392 ELSE 387 393 ! … … 397 403 WRITE ( 30 ) simulated_time, do3d_time_count(av), av 398 404 ENDIF 399 WRITE ( 30 ) nxl-1, nxr+1, nys-1, nyn+1, nzb, nz_do3d 400 WRITE ( 30 ) local_pf 401 405 DO rbs = 0, numprocs/binary_io_blocksize-1 406 IF ( mod_numprocs_size == rbs ) THEN 407 WRITE ( 30 ) nxl-1, nxr+1, nys-1, nyn+1, nzb, nz_do3d 408 WRITE ( 30 ) local_pf 409 ENDIF 410 CALL MPI_BARRIER(comm2d, ierr ) 411 ENDDO 412 402 413 ELSE 403 414 ! -
palm/trunk/SOURCE/init_3d_model.f90
r486 r557 113 113 IMPLICIT NONE 114 114 115 INTEGER :: i, ind_array(1), j, k, sr115 INTEGER :: i, ind_array(1), j, k, rbs, sr 116 116 117 117 INTEGER, DIMENSION(:), ALLOCATABLE :: ngp_2dh_l … … 969 969 !-- some of the global variables from restart file 970 970 IF ( TRIM( initializing_actions ) == 'cyclic_fill' ) THEN 971 972 971 WRITE (9,*) 'before read_parts_of_var_list' 973 972 CALL local_flush( 9 ) 974 CALL read_parts_of_var_list 973 DO rbs = 0, numprocs/binary_io_blocksize-1 974 IF ( mod_numprocs_size == rbs ) THEN 975 CALL read_parts_of_var_list 976 ENDIF 977 CALL MPI_BARRIER(comm2d, ierr ) 978 ENDDO 975 979 WRITE (9,*) 'after read_parts_of_var_list' 976 980 CALL local_flush( 9 ) … … 1056 1060 ! 1057 1061 !-- Read binary data from restart file 1058 WRITE (9,*) 'before read_3d_binary' 1059 CALL local_flush( 9 ) 1060 CALL read_3d_binary 1061 WRITE (9,*) 'after read_3d_binary' 1062 CALL local_flush( 9 ) 1062 WRITE (9,*) 'before read_3d_binary' 1063 CALL local_flush( 9 ) 1064 DO rbs = 0, numprocs/binary_io_blocksize-1 1065 IF ( mod_numprocs_size == rbs ) THEN 1066 CALL read_3d_binary 1067 ENDIF 1068 CALL MPI_BARRIER(comm2d, ierr ) 1069 ENDDO 1070 WRITE (9,*) 'after read_3d_binary' 1071 CALL local_flush( 9 ) 1063 1072 1064 1073 ! … … 1573 1582 #endif 1574 1583 1575 ngp_3d = INT( ngp_2dh * ( nz + 2 ), KIND = SELECTED_INT_KIND( 18 ) ) 1584 ngp_3d = INT ( ngp_2dh, KIND = SELECTED_INT_KIND( 18 ) ) * & 1585 INT ( (nz + 2 ), KIND = SELECTED_INT_KIND( 18 ) ) 1576 1586 1577 1587 ! -
palm/trunk/SOURCE/init_grid.f90
r556 r557 63 63 INTEGER :: bh, blx, bly, bxl, bxr, byn, bys, ch, cwx, cwy, cxl, cxr, cyn, & 64 64 cys, gls, i, inc, i_center, j, j_center, k, l, nxl_l, nxr_l, & 65 nyn_l, nys_l, nzb_si, nzt_l, vi65 nyn_l, nys_l, nzb_si, nzt_l, rbs, vi 66 66 67 67 INTEGER, DIMENSION(:), ALLOCATABLE :: vertical_influence … … 460 460 OPEN( 90, FILE='TOPOGRAPHY_DATA', STATUS='OLD', FORM='FORMATTED', & 461 461 ERR=10 ) 462 DO j = ny, 0, -1 463 READ( 90, *, ERR=11, END=11 ) ( topo_height(j,i), i = 0, nx ) 464 ENDDO 462 DO rbs = 0, numprocs/binary_io_blocksize-1 463 IF ( mod_numprocs_size == rbs ) THEN 464 DO j = ny, 0, -1 465 READ( 90, *, ERR=11, END=11 ) ( topo_height(j,i), i = 0, nx ) 466 ENDDO 467 ENDIF 468 CALL MPI_BARRIER(comm2d, ierr ) 469 ENDDO 465 470 ! 466 471 !-- Calculate the index height of the topography -
palm/trunk/SOURCE/init_masks.f90
r554 r557 4 4 ! Current revisions: 5 5 ! ----------------- 6 ! 6 ! bugfix message string for PA9998 7 7 ! 8 8 ! Former revisions: … … 521 521 IF ( mask_loop(mid,dim,2) * mask_scale(dim) > dz_stretch_level ) & 522 522 THEN 523 WRITE ( message_string, '(A,I3,A,I1,A,F9.3,A,F8.2,3A)' ) 524 'mask_loop(',mid, dim,',2)=', mask_loop(mid,dim,2),&523 WRITE ( message_string, '(A,I3,A,I1,A,F9.3,A,F8.2,3A)' ) & 524 'mask_loop(',mid,',',dim,',2)=', mask_loop(mid,dim,2),& 525 525 ' exceeds dz_stretch_level=',dz_stretch_level, & 526 526 '.&Vertical mask locations will not ', & -
palm/trunk/SOURCE/modules.f90
r554 r557 398 398 vg_vertical_gradient_level_ind(10) = -9999, & 399 399 ws_vertical_gradient_level_ind(10) = -9999 400 401 INTEGER :: binary_io_blocksize = -9999, mod_numprocs_size 400 402 401 403 INTEGER, DIMENSION(:), ALLOCATABLE :: grid_level_count -
palm/trunk/SOURCE/palm.f90
r496 r557 74 74 CHARACTER (LEN=9) :: time_to_string 75 75 CHARACTER (LEN=1) :: cdum 76 INTEGER :: i, r un_description_header_i(80)76 INTEGER :: i, rbs, run_description_header_i(80) 77 77 78 78 version = 'PALM 3.7a' … … 174 174 !-- If required, write binary data for restart runs 175 175 IF ( write_binary(1:4) == 'true' ) THEN 176 ! 177 !-- Write flow field data 178 CALL write_3d_binary 176 DO rbs = 0, numprocs/binary_io_blocksize-1 177 IF ( mod_numprocs_size == rbs ) THEN 178 ! 179 !-- Write flow field data 180 CALL write_3d_binary 181 ENDIF 182 CALL MPI_BARRIER(comm2d, ierr ) 183 ENDDO 179 184 ! 180 185 !-- If required, write particle data -
palm/trunk/SOURCE/parin.f90
r554 r557 98 98 IMPLICIT NONE 99 99 100 INTEGER :: idum 100 INTEGER :: idum, mod_blocksize, rbs 101 101 102 102 … … 104 104 bc_ns, bc_p_b, bc_p_t, bc_pt_b, bc_pt_t, bc_q_b, & 105 105 bc_q_t,bc_s_b, bc_s_t, bc_sa_t, bc_uv_b, bc_uv_t, & 106 binary_io_blocksize, & 106 107 bottom_salinityflux, building_height, building_length_x, & 107 108 building_length_y, building_wall_left, building_wall_south, & … … 208 209 11 message_string = 'no \$inipar-namelist found' 209 210 CALL message( 'parin', 'PA0272', 1, 2, 0, 6, 0 ) 210 211 212 ! 213 !-- Check blocksize of binary IO 214 12 mod_blocksize = MODULO(numprocs,binary_io_blocksize) 215 IF ( mod_blocksize /= 0 ) THEN 216 WRITE( message_string, * ) 'illegal value for binary_io_blocksize: & 217 ', binary_io_blocksize, & 218 ' - no binary IO block by block' 219 CALL message( 'check_parameters', 'PA0325', 0, 1, 0, 6, 0) 220 binary_io_blocksize = numprocs 221 ENDIF 222 mod_numprocs_size = MOD(myid,numprocs/binary_io_blocksize) 223 211 224 ! 212 225 !-- If required, read control parameters from restart file (produced by 213 226 !-- a prior run). All PEs are reading from file created by PE0 (see check_open) 214 12 IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN 215 216 CALL read_var_list 227 IF ( TRIM( initializing_actions ) == 'read_restart_data' ) THEN 228 229 DO rbs = 0, numprocs/binary_io_blocksize-1 230 IF ( mod_numprocs_size == rbs ) THEN 231 CALL read_var_list 232 ENDIF 233 CALL MPI_BARRIER(comm2d, ierr ) 234 ENDDO 235 217 236 ! 218 237 !-- The restart file will be reopened when reading the subdomain data -
palm/trunk/SOURCE/user_check_data_output_pr.f90
r484 r557 55 55 ! ! defined (use zu or zw) 56 56 57 CASE ( 'u*v*' ) ! quantity string as given in 58 ! data_output_pr_user 59 index = pr_palm + 1 60 dopr_index(var_count) = index ! quantities' user-profile-number 61 dopr_unit(var_count) = 'm2/s2' ! quantity unit 62 hom(:,2,index,:) = SPREAD( zu, 2, statistic_regions+1 ) 63 ! grid on which the quantity is 64 ! defined (use zu or zw) 65 57 66 CASE DEFAULT 58 67 unit = 'illegal' -
palm/trunk/SOURCE/user_last_actions.f90
r484 r557 22 22 23 23 USE control_parameters 24 USE pegrid 24 25 USE user 25 26 26 27 IMPLICIT NONE 28 29 INTEGER :: rbs 27 30 28 31 ! … … 30 33 !-- Sample for user-defined output: 31 34 IF ( write_binary(1:4) == 'true' ) THEN 32 ! IF ( ALLOCATED( u2_av ) ) THEN 33 ! WRITE ( 14 ) 'u2_av '; WRITE ( 14 ) u2_av 34 ! ENDIF 35 DO rbs = 0, numprocs/binary_io_blocksize-1 36 IF ( mod_numprocs_size == rbs ) THEN 37 38 ! IF ( ALLOCATED( u2_av ) ) THEN 39 ! WRITE ( 14 ) 'u2_av '; WRITE ( 14 ) u2_av 40 ! ENDIF 35 41 36 WRITE ( 14 ) '*** end user *** ' 42 WRITE ( 14 ) '*** end user *** ' 43 44 ENDIF 45 CALL MPI_BARRIER(comm2d, ierr ) 46 ENDDO 37 47 38 48 ENDIF
Note: See TracChangeset
for help on using the changeset viewer.