Changeset 4230 for palm/trunk/SOURCE/nesting_offl_mod.f90
- Timestamp:
- Sep 11, 2019 1:58:14 PM (3 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/nesting_offl_mod.f90
r4227 r4230 20 20 ! Current revisions: 21 21 ! ------------------ 22 ! implement new palm_date_time_mod22 ! 23 23 ! 24 24 ! Former revisions: 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Update mean chemistry profiles. These are also used for rayleigh damping. 28 ! 29 ! 4227 2019-09-10 18:04:34Z gronemeier 30 ! implement new palm_date_time_mod 31 ! 27 32 ! - Data input moved into nesting_offl_mod 28 33 ! - check rephrased … … 403 408 !-- Check if dynamic driver data input is required. 404 409 IF ( nest_offl%time(nest_offl%tind_p) <= & 405 MAX( time_since_reference_point, 0.0_wp) + time_utc_init .OR. 410 MAX( time_since_reference_point, 0.0_wp) + time_utc_init .OR. & 406 411 .NOT. nest_offl%init ) THEN 407 412 CONTINUE … … 922 927 REAL(wp), DIMENSION(nzb:nzt+1) :: pt_ref !< reference profile for potential temperature 923 928 REAL(wp), DIMENSION(nzb:nzt+1) :: pt_ref_l !< reference profile for potential temperature on subdomain 924 REAL(wp), DIMENSION(nzb:nzt+1) :: q_ref !< reference profile for mixing ratio on subdomain929 REAL(wp), DIMENSION(nzb:nzt+1) :: q_ref !< reference profile for mixing ratio 925 930 REAL(wp), DIMENSION(nzb:nzt+1) :: q_ref_l !< reference profile for mixing ratio on subdomain 926 REAL(wp), DIMENSION(nzb:nzt+1) :: u_ref !< reference profile for u-component on subdomain931 REAL(wp), DIMENSION(nzb:nzt+1) :: u_ref !< reference profile for u-component 927 932 REAL(wp), DIMENSION(nzb:nzt+1) :: u_ref_l !< reference profile for u-component on subdomain 928 REAL(wp), DIMENSION(nzb:nzt+1) :: v_ref !< reference profile for v-component on subdomain933 REAL(wp), DIMENSION(nzb:nzt+1) :: v_ref !< reference profile for v-component 929 934 REAL(wp), DIMENSION(nzb:nzt+1) :: v_ref_l !< reference profile for v-component on subdomain 930 935 936 REAL(wp), DIMENSION(:,:), ALLOCATABLE :: ref_chem !< reference profile for chemical species 937 REAL(wp), DIMENSION(:,:), ALLOCATABLE :: ref_chem_l !< reference profile for chemical species on subdomain 931 938 932 939 IF ( debug_output_timestep ) CALL debug_message( 'nesting_offl_bc', 'start' ) … … 934 941 CALL cpu_log( log_point(58), 'offline nesting', 'start' ) 935 942 ! 936 !-- Setmean profiles, derived from boundary data, to zero943 !-- Initialize mean profiles, derived from boundary data, to zero 937 944 pt_ref = 0.0_wp 938 945 q_ref = 0.0_wp … … 944 951 u_ref_l = 0.0_wp 945 952 v_ref_l = 0.0_wp 953 ! 954 !-- If required, allocate temporary arrays to compute chemistry mean profiles 955 IF ( air_chemistry ) THEN 956 ALLOCATE( ref_chem(nzb:nzt+1,1:UBOUND( chem_species, 1 ) ) ) 957 ALLOCATE( ref_chem_l(nzb:nzt+1,1:UBOUND( chem_species, 1 ) ) ) 958 ref_chem = 0.0_wp 959 ref_chem_l = 0.0_wp 960 ENDIF 946 961 ! 947 962 !-- Set boundary conditions of u-, v-, w-component, as well as q, and pt. … … 1024 1039 fac_dt ) 1025 1040 ENDDO 1041 ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n) & 1042 + chem_species(n)%conc(nzb+1:nzt,j,-1) 1026 1043 ENDDO 1027 1044 ENDIF … … 1100 1117 fac_dt ) 1101 1118 ENDDO 1119 ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n) & 1120 + chem_species(n)%conc(nzb+1:nzt,j,nxr+1) 1102 1121 ENDDO 1103 1122 ENDIF … … 1179 1198 fac_dt ) 1180 1199 ENDDO 1200 ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n) & 1201 + chem_species(n)%conc(nzb+1:nzt,-1,i) 1181 1202 ENDDO 1182 1203 ENDIF … … 1257 1278 fac_dt ) 1258 1279 ENDDO 1280 ref_chem_l(nzb+1:nzt,n) = ref_chem_l(nzb+1:nzt,n) & 1281 + chem_species(n)%conc(nzb+1:nzt,nyn+1,i) 1259 1282 ENDDO 1260 1283 ENDIF … … 1337 1360 DO j = nys, nyn 1338 1361 chem_species(n)%conc(nzt+1,j,i) = interpolate_in_time( & 1339 nest_offl%chem_top(0,j,i,n), &1340 nest_offl%chem_top(1,j,i,n), &1362 nest_offl%chem_top(0,j,i,n), & 1363 nest_offl%chem_top(1,j,i,n), & 1341 1364 fac_dt ) 1365 ref_chem_l(nzt+1,n) = ref_chem_l(nzt+1,n) + & 1366 chem_species(n)%conc(nzt+1,j,i) 1342 1367 ENDDO 1343 1368 ENDDO … … 1404 1429 comm2d, ierr ) 1405 1430 ENDIF 1431 IF ( air_chemistry ) THEN 1432 CALL MPI_ALLREDUCE( ref_chem_l, ref_chem, & 1433 ( nzt+1-nzb+1 ) * SIZE( ref_chem(nzb,:) ), & 1434 MPI_REAL, MPI_SUM, comm2d, ierr ) 1435 ENDIF 1406 1436 #else 1407 1437 u_ref = u_ref_l 1408 1438 v_ref = v_ref_l 1409 IF ( humidity ) q_ref = q_ref_l 1410 IF ( .NOT. neutral ) pt_ref = pt_ref_l 1439 IF ( humidity ) q_ref = q_ref_l 1440 IF ( .NOT. neutral ) pt_ref = pt_ref_l 1441 IF ( air_chemistry ) ref_chem = ref_chem_l 1411 1442 #endif 1412 1443 ! … … 1427 1458 ( ny + 1 + nx + 1 ), & 1428 1459 KIND = wp ) 1460 IF ( air_chemistry ) & 1461 ref_chem(nzb:nzt,:) = ref_chem(nzb:nzt,:) / REAL( 2.0_wp * & 1462 ( ny + 1 + nx + 1 ), & 1463 KIND = wp ) 1429 1464 ! 1430 1465 !-- Derived from top boundary. … … 1437 1472 pt_ref(nzt+1) = pt_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx + 1 ), & 1438 1473 KIND = wp ) 1439 ! 1440 !-- Write onto init profiles, which are used for damping 1474 IF ( air_chemistry ) & 1475 ref_chem(nzt+1,:) = ref_chem(nzt+1,:) / & 1476 REAL( ( ny + 1 ) * ( nx + 1 ),KIND = wp ) 1477 ! 1478 !-- Write onto init profiles, which are used for damping. Also set lower 1479 !-- boundary condition for scalars (not required for u and v as these are 1480 !-- zero at k=nzb. 1441 1481 u_init = u_ref 1442 1482 v_init = v_ref 1443 IF ( humidity ) q_init = q_ref 1444 IF ( .NOT. neutral ) pt_init = pt_ref 1445 ! 1446 !-- Set bottom boundary condition 1447 IF ( humidity ) q_init(nzb) = q_init(nzb+1) 1448 IF ( .NOT. neutral ) pt_init(nzb) = pt_init(nzb+1) 1483 IF ( humidity ) THEN 1484 q_init = q_ref 1485 q_init(nzb) = q_init(nzb+1) 1486 ENDIF 1487 IF ( .NOT. neutral ) THEN 1488 pt_init = pt_ref 1489 pt_init(nzb) = pt_init(nzb+1) 1490 ENDIF 1491 1492 IF ( air_chemistry ) THEN 1493 DO n = 1, UBOUND( chem_species, 1 ) 1494 IF ( nest_offl%chem_from_file_t(n) ) THEN 1495 chem_species(n)%conc_pr_init(:) = ref_chem(:,n) 1496 chem_species(n)%conc_pr_init(nzb) = & 1497 chem_species(n)%conc_pr_init(nzb+1) 1498 ENDIF 1499 ENDDO 1500 ENDIF 1501 1502 DEALLOCATE( ref_chem ) 1503 DEALLOCATE( ref_chem_l ) 1449 1504 ! 1450 1505 !-- Further, adjust Rayleigh damping height in case of time-changing conditions.
Note: See TracChangeset
for help on using the changeset viewer.