Changeset 2945
- Timestamp:
- Apr 4, 2018 4:27:14 PM (7 years ago)
- Location:
- palm/trunk/SOURCE
- Files:
-
- 2 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/netcdf_data_input_mod.f90
r2938 r2945 25 25 ! ----------------- 26 26 ! $Id$ 27 ! - Mimic for topography input slightly revised, in order to enable consistency 28 ! checks 29 ! - Add checks for dimensions in dynamic input file and move already existing 30 ! checks 31 ! 32 ! 2938 2018-03-27 15:52:42Z suehring 27 33 ! Initial read of geostrophic wind components from dynamic driver. 28 34 ! … … 104 110 INTEGER(iwp) :: nx !< dimension length in x 105 111 INTEGER(iwp) :: ny !< dimension length in y 112 INTEGER(iwp) :: nz !< dimension length in z 106 113 REAL(wp), DIMENSION(:), ALLOCATABLE :: x !< dimension array in x 107 114 REAL(wp), DIMENSION(:), ALLOCATABLE :: y !< dimension array in y 115 REAL(wp), DIMENSION(:), ALLOCATABLE :: z !< dimension array in z 108 116 END TYPE dims_xy 109 117 ! … … 316 324 ! 317 325 !-- Define variables 318 TYPE(dims_xy) :: dim_static !< data structure for x, y-dimension in static input file326 TYPE(dims_xy) :: dim_static !< data structure for x, y-dimension in static input file 319 327 320 328 TYPE(force_type) :: force !< data structure for data input at lateral and top boundaries (provided by Inifor) … … 1672 1680 REAL(wp) :: dum !< dummy variable to skip columns while reading topography file 1673 1681 1674 IF ( TRIM( topography ) /= 'read_from_file' ) RETURN1675 1682 1676 1683 DO ii = 0, io_blocks-1 … … 1695 1702 CALL inquire_variable_names( id_topo, var_names ) 1696 1703 ! 1697 !-- Read x, y - dimensions 1704 !-- Read x, y - dimensions. Only required for consistency checks. 1698 1705 CALL get_dimension_length( id_topo, dim_static%nx, 'x' ) 1699 1706 CALL get_dimension_length( id_topo, dim_static%ny, 'y' ) … … 1830 1837 ! 1831 1838 !-- ASCII input 1832 ELSE 1839 ELSEIF ( TRIM( topography ) == 'read_from_file' ) THEN 1833 1840 1834 1841 OPEN( 90, FILE='TOPOGRAPHY_DATA'//TRIM( coupling_char ), & … … 2013 2020 CALL get_dimension_length( id_dynamic, init_3d%ny, 'y' ) 2014 2021 CALL get_dimension_length( id_dynamic, init_3d%nyv, 'yv' ) 2015 !2016 !-- Check for correct horizontal dimension. Please note, u- and v-grid2017 !-- hase 1 grid point less on Inifor grid.2018 IF ( init_3d%nx-1 /= nx .OR. init_3d%nxu-1 /= nx - 1 .OR. &2019 init_3d%ny-1 /= ny .OR. init_3d%nyv-1 /= ny - 1 ) THEN2020 message_string = 'Number of inifor grid points does not ' // &2021 'match the number of numeric grid points.'2022 CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 )2023 ENDIF2024 2022 ! 2025 2023 !-- Read vertical dimensions. Later, these are required for eventual … … 2376 2374 2377 2375 USE indices, & 2378 ONLY: nx , nxl, nxlu, nxr, ny, nyn, nys, nysv, nzb, nzt2376 ONLY: nxl, nxlu, nxr, nyn, nys, nysv, nzb, nzt 2379 2377 2380 2378 IMPLICIT NONE … … 2780 2778 ONLY: initializing_actions, forcing, message_string 2781 2779 2780 USE indices, & 2781 ONLY: nx, ny, nz 2782 2782 2783 IMPLICIT NONE 2783 2784 … … 2798 2799 TRIM( coupling_char ) 2799 2800 CALL message( 'netcdf_data_input_mod', 'NDI010', 1, 2, 0, 6, 0 ) 2801 ENDIF 2802 ! 2803 !-- Check for correct horizontal and vertical dimension. 2804 !-- Please note, u- and v-grid has 1 grid point less on Inifor grid. 2805 IF ( init_3d%nx-1 /= nx .OR. init_3d%nxu-1 /= nx - 1 .OR. & 2806 init_3d%ny-1 /= ny .OR. init_3d%nyv-1 /= ny - 1 ) THEN 2807 message_string = 'Number of inifor horizontal grid points does ' // & 2808 'not match the number of numeric grid points.' 2809 CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 ) 2810 ENDIF 2811 2812 IF ( init_3d%nzu /= nz ) THEN 2813 message_string = 'Number of inifor vertical grid points does ' // & 2814 'not match the number of numeric grid points.' 2815 CALL message( 'netcdf_data_input_mod', 'NDI003', 1, 2, 0, 6, 0 ) 2800 2816 ENDIF 2801 2817 -
palm/trunk/SOURCE/synthetic_turbulence_generator_mod.f90
r2938 r2945 25 25 ! ----------------- 26 26 ! $Id$ 27 ! - Bugfix in parallelization of synthetic turbulence generator in case the 28 ! z-dimension is not an integral divisor of the number of processors along 29 ! the x- and y-dimension 30 ! - Revision in control mimic in case of RAN-LES nesting 31 ! 32 ! 2938 2018-03-27 15:52:42Z suehring 27 33 ! Apply turbulence generator at all non-cyclic lateral boundaries in case of 28 34 ! realistic Inifor large-scale forcing or RANS-LES nesting … … 87 93 !> enable cyclic_fill 88 94 !> implement turbulence generation for e and pt 95 !> @todo Input of height-constant length scales via namelist 89 96 !> @note <Enter notes on the module> 90 97 !> @bug Height information from input file is not used. Profiles from input … … 388 395 389 396 USE control_parameters, & 390 ONLY: coupling_char, dz, e_init, forcing, nest_domain 397 ONLY: coupling_char, dz, e_init, forcing, nest_domain, rans_mode 391 398 392 399 USE grid_variables, & … … 395 402 USE indices, & 396 403 ONLY: nz 404 405 USE pmc_interface, & 406 ONLY : rans_mode_parent 397 407 398 408 … … 411 421 INTEGER(iwp) :: newtype !< dummy MPI type 412 422 INTEGER(iwp) :: realsize !< size of REAL variables 413 INTEGER(iwp) :: nnz !< increment used to determine processor decomposition of z-axis along x and y direction414 423 INTEGER(iwp) :: nseed !< dimension of random number seed 415 424 INTEGER(iwp) :: startseed = 1234567890 !< start seed for random number generator … … 431 440 REAL(wp) :: lwy !< length scale for w in y direction 432 441 REAL(wp) :: lwz !< length scale for w in z direction 442 REAL(wp) :: nnz !< increment used to determine processor decomposition of z-axis along x and y direction 433 443 REAL(wp) :: zz !< height 434 444 … … 463 473 !-- Determine processor decomposition of z-axis along x- and y-direction 464 474 nnz = nz / pdims(1) 465 nzb_x_stg = 1 + myidx * nnz466 nzt_x_stg = ( myidx + 1 ) * nnz475 nzb_x_stg = 1 + myidx * INT( nnz ) 476 nzt_x_stg = ( myidx + 1 ) * INT( nnz ) 467 477 468 478 IF ( MOD( nz , pdims(1) ) /= 0 .AND. myidx == id_stg_right ) & 469 nzt_x_stg = myidx * nnz + MOD( nz , pdims(1) ) 470 471 IF ( forcing .OR. nest_domain ) THEN 479 nzt_x_stg = nzt_x_stg + myidx * ( nnz - INT( nnz ) ) 480 ! nzt_x_stg = myidx * nnz + MOD( nz , pdims(1) ) 481 482 IF ( forcing .OR. ( nest_domain .AND. rans_mode_parent .AND. & 483 .NOT. rans_mode ) ) THEN 472 484 nnz = nz / pdims(2) 473 nzb_y_stg = 1 + myidy * nnz 474 nzt_y_stg = ( myidy + 1 ) * nnz 475 476 IF ( MOD( nz , pdims(2) ) /= 0 .AND. myidy == id_stg_north ) & 477 nzt_y_stg = myidy * nnz + MOD( nz , pdims(2) ) 485 nzb_y_stg = 1 + myidy * INT( nnz ) 486 nzt_y_stg = ( myidy + 1 ) * INT( nnz ) 487 488 IF ( MOD( nz , pdims(2) ) /= 0 .AND. myidy == id_stg_north ) & 489 nzt_y_stg = nzt_y_stg + myidy * ( nnz - INT( nnz ) ) 490 ! nzt_y_stg = myidy * nnz + MOD( nz , pdims(2) ) 478 491 ENDIF 479 492 … … 494 507 495 508 ! stg_type_yz_small: yz-slice with vertical bounds nzb_x_stg:nzt_x_stg+1 496 CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt_x_stg-nzb_x_stg+2,nyng-nysg+1], 509 CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt_x_stg-nzb_x_stg+2,nyng-nysg+1], & 497 510 [1,nyng-nysg+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr ) 498 511 CALL MPI_TYPE_CREATE_RESIZED( newtype, tob, extent, stg_type_yz_small, ierr ) … … 513 526 !-- layer 514 527 !-- stg_type_xz: xz-slice with vertical bounds nzb:nzt+1 515 IF ( forcing .OR. nest_domain) THEN 516 CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt-nzb+2,nxrg-nxlg+1], & 528 IF ( forcing .OR. ( nest_domain .AND. rans_mode_parent .AND. & 529 .NOT. rans_mode ) ) THEN 530 CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt-nzb+2,nxrg-nxlg+1], & 517 531 [1,nxrg-nxlg+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr ) 518 532 CALL MPI_TYPE_CREATE_RESIZED( newtype, tob, extent, stg_type_xz, ierr ) … … 521 535 522 536 ! stg_type_yz_small: xz-slice with vertical bounds nzb_x_stg:nzt_x_stg+1 523 CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt_y_stg-nzb_y_stg+2,nxrg-nxlg+1], 537 CALL MPI_TYPE_CREATE_SUBARRAY( 2, [nzt_y_stg-nzb_y_stg+2,nxrg-nxlg+1], & 524 538 [1,nxrg-nxlg+1], [0,0], MPI_ORDER_FORTRAN, MPI_REAL, newtype, ierr ) 525 539 CALL MPI_TYPE_CREATE_RESIZED( newtype, tob, extent, stg_type_xz_small, ierr ) … … 600 614 !-- Set-up defaul length scales. Assume exponentially decreasing length 601 615 !-- scales and isotropic turbulence. 602 !-- Typical length (time) scales of 100 m (s) should be a goo gcompromise616 !-- Typical length (time) scales of 100 m (s) should be a good compromise 603 617 !-- between all stratrifications. Near-surface variances are fixed to 604 618 !-- 0.1 m2/s2, vertical fluxes are one order of magnitude smaller. … … 998 1012 USE control_parameters, & 999 1013 ONLY: dt_3d, forcing, intermediate_timestep_count, nest_domain, & 1000 simulated_time, volume_flow_initial1014 rans_mode, simulated_time, volume_flow_initial 1001 1015 1002 1016 USE grid_variables, & … … 1008 1022 USE statistics, & 1009 1023 ONLY: weight_substep 1024 1025 USE pmc_interface, & 1026 ONLY : rans_mode_parent 1010 1027 1011 1028 … … 1038 1055 CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fw_yz, id_stg_left ) 1039 1056 1040 IF ( forcing .OR. nest_domain ) THEN 1057 IF ( forcing .OR. ( nest_domain .AND. rans_mode_parent .AND. & 1058 .NOT. rans_mode ) ) THEN 1041 1059 ! 1042 1060 !-- Generate turbulence at right boundary … … 1063 1081 CALL stg_generate_seed_yz( nwy, nwz, bwy, bwz, fwo_yz, id_stg_left ) 1064 1082 1065 IF ( forcing .OR. nest_domain ) THEN 1083 IF ( forcing .OR. ( nest_domain .AND. rans_mode_parent .AND. & 1084 .NOT. rans_mode ) ) THEN 1066 1085 ! 1067 1086 !-- Generate turbulence at right boundary … … 1120 1139 dist_yz(k,j,1) = a11(k) * fu_yz(k,j) 1121 1140 !experimental test of 1.2 1122 dist_yz(k,j,2) = ( SQRT( a22(k) / MAXVAL(a22) ) 1141 dist_yz(k,j,2) = ( SQRT( a22(k) / MAXVAL(a22) ) & 1123 1142 * 1.2_wp ) & 1124 * ( a21(k) * fu_yz(k,j) 1143 * ( a21(k) * fu_yz(k,j) & 1125 1144 + a22(k) * fv_yz(k,j) ) 1126 dist_yz(k,j,3) = ( SQRT(a33(k) / MAXVAL(a33) ) 1145 dist_yz(k,j,3) = ( SQRT(a33(k) / MAXVAL(a33) ) & 1127 1146 * 1.3_wp ) & 1128 * ( a31(k) * fu_yz(k,j) 1129 + a32(k) * fv_yz(k,j) 1147 * ( a31(k) * fu_yz(k,j) & 1148 + a32(k) * fv_yz(k,j) & 1130 1149 + a33(k) * fw_yz(k,j) ) 1131 1150 ! Calculation for pt and e not yet implemented … … 1303 1322 DO i = nxl, nxr 1304 1323 DO k = nzb+1, nzt 1305 volume_flow_l = volume_flow_l + v(k,j,i) * dzw(k) * dx &1306 * MERGE( 1.0_wp, 0.0_wp, &1324 volume_flow_l = volume_flow_l + v(k,j,i) * dzw(k) * dx & 1325 * MERGE( 1.0_wp, 0.0_wp, & 1307 1326 BTEST( wall_flags_0(k,j,i), 2 ) ) 1308 1327 1309 mc_factor_l = mc_factor_l + ( v(k,j,i) + dist_xz(k,i,2) ) &1310 * dzw(k) * dx &1311 * MERGE( 1.0_wp, 0.0_wp, &1328 mc_factor_l = mc_factor_l + ( v(k,j,i) + dist_xz(k,i,2) ) & 1329 * dzw(k) * dx & 1330 * MERGE( 1.0_wp, 0.0_wp, & 1312 1331 BTEST( wall_flags_0(k,j,i), 2 ) ) 1313 1332 ENDDO 1314 1333 ENDDO 1315 1334 #if defined( __parallel ) 1316 CALL MPI_ALLREDUCE( volume_flow_l, volume_flow, &1335 CALL MPI_ALLREDUCE( volume_flow_l, volume_flow, & 1317 1336 1, MPI_REAL, MPI_SUM, comm1dx, ierr ) 1318 CALL MPI_ALLREDUCE( mc_factor_l, mc_factor, &1337 CALL MPI_ALLREDUCE( mc_factor_l, mc_factor, & 1319 1338 1, MPI_REAL, MPI_SUM, comm1dx, ierr ) 1320 1339 #else … … 1374 1393 ONLY: ny 1375 1394 1395 USE pegrid 1376 1396 1377 1397 IMPLICIT NONE … … 1467 1487 1468 1488 DEALLOCATE( rand_it ) 1469 1470 1489 ! 1471 1490 !-- Gather velocity seeds of full subdomain … … 1474 1493 1475 1494 #if defined( __parallel ) 1476 CALL MPI_GATHERV( f_n_l(nzb_x_stg,nysg), send_count, stg_type_yz_small, 1477 f_n(nzb+1,nysg), recv_count_yz, displs_yz, stg_type_yz, 1495 CALL MPI_GATHERV( f_n_l(nzb_x_stg,nysg), send_count, stg_type_yz_small, & 1496 f_n(nzb+1,nysg), recv_count_yz, displs_yz, stg_type_yz, & 1478 1497 id, comm1dx, ierr ) 1479 1498 #else … … 1603 1622 1604 1623 #if defined( __parallel ) 1605 CALL MPI_GATHERV( f_n_l(nzb_y_stg,nxlg), send_count, stg_type_xz_small, 1624 CALL MPI_GATHERV( f_n_l(nzb_y_stg,nxlg), send_count, stg_type_xz_small, & 1606 1625 f_n(nzb+1,nxlg), recv_count_xz, displs_xz, stg_type_xz, & 1607 1626 id, comm1dy, ierr )
Note: See TracChangeset
for help on using the changeset viewer.