Changeset 4768 for palm/trunk/SOURCE/data_output_3d.f90
- Timestamp:
- Nov 2, 2020 7:11:23 PM (4 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/data_output_3d.f90
r4559 r4768 19 19 ! Current revisions: 20 20 ! ------------------ 21 ! 22 ! 21 ! 22 ! 23 23 ! Former revisions: 24 24 ! ----------------- 25 25 ! $Id$ 26 ! Enable 3D data output also with 64-bit precision 27 ! 28 ! 4559 2020-06-11 08:51:48Z raasch 26 29 ! file re-formatted to follow the PALM coding standard 27 30 ! … … 170 173 REAL(wp) :: s_r3 !< sum( particle-radius**3 ) 171 174 172 REAL( sp), DIMENSION(:,:,:), ALLOCATABLE :: local_pf !< output array175 REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: local_pf !< output array 173 176 174 177 REAL(wp), DIMENSION(:,:,:), POINTER :: to_be_resorted !< pointer to array which shall be … … 261 264 ! 262 265 !-- Before each output, set array local_pf to fill value 263 local_pf = fill_value266 local_pf = REAL( fill_value, KIND=wp ) 264 267 ! 265 268 !-- Set masking flag for topography for not resorted arrays … … 674 677 ! count = (/ nxr-nxl+2, nyn-nys+2, nzt_do-nzb_do+1, 1 /) ) 675 678 ! ELSE 676 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,ivar), & 677 local_pf(nxl:nxr,nys:nyn,nzb_do:nzt_do), & 678 start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /), & 679 count = (/ nxr-nxl+1, nyn-nys+1, nzt_do-nzb_do+1, 1 /) & 680 ) 679 ! 680 !-- Call for parallel runs 681 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,ivar), & 682 local_pf(nxl:nxr,nys:nyn,nzb_do:nzt_do), & 683 start = (/ nxl+1, nys+1, nzb_do+1, do3d_time_count(av) /), & 684 count = (/ nxr-nxl+1, nyn-nys+1, nzt_do-nzb_do+1, 1 /) & 685 ) 681 686 ! ENDIF 682 687 CALL netcdf_handle_error( 'data_output_3d', 386 ) … … 685 690 #else 686 691 #if defined( __netcdf ) 692 ! 693 !-- Call for non-parallel runs 687 694 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_do3d(av,ivar), & 688 695 local_pf(nxl:nxr,nys:nyn,nzb_do:nzt_do), &
Note: See TracChangeset
for help on using the changeset viewer.