Ignore:
Timestamp:
Sep 11, 2019 1:58:14 PM (5 years ago)
Author:
suehring
Message:

Several bugfixes: profile initialization of chemical species in restart runs; Runge-Kutta tendency array not initialized in chemistry model in restart runs; fixed determination of time indices for chemical emissions (introduced with commit -4227); Update chemistry profiles in offline nesting; initialize canopy resistances for greened building walls (even if green fraction is zero)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/nesting_offl_mod.f90

    r4227 r4230  
    2020! Current revisions:
    2121! ------------------
    22 ! implement new palm_date_time_mod
     22!
    2323!
    2424! Former revisions:
    2525! -----------------
    2626! $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!
    2732! - Data input moved into nesting_offl_mod
    2833! - check rephrased
     
    403408!--    Check if dynamic driver data input is required.
    404409       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.     &
    406411            .NOT.  nest_offl%init )  THEN
    407412          CONTINUE
     
    922927       REAL(wp), DIMENSION(nzb:nzt+1) ::  pt_ref   !< reference profile for potential temperature
    923928       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 subdomain
     929       REAL(wp), DIMENSION(nzb:nzt+1) ::  q_ref    !< reference profile for mixing ratio
    925930       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 subdomain
     931       REAL(wp), DIMENSION(nzb:nzt+1) ::  u_ref    !< reference profile for u-component
    927932       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 subdomain
     933       REAL(wp), DIMENSION(nzb:nzt+1) ::  v_ref    !< reference profile for v-component
    929934       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
    931938
    932939       IF ( debug_output_timestep )  CALL debug_message( 'nesting_offl_bc', 'start' )
     
    934941       CALL  cpu_log( log_point(58), 'offline nesting', 'start' )     
    935942!
    936 !--    Set mean profiles, derived from boundary data, to zero
     943!--    Initialize mean profiles, derived from boundary data, to zero
    937944       pt_ref   = 0.0_wp
    938945       q_ref    = 0.0_wp
     
    944951       u_ref_l  = 0.0_wp
    945952       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
    946961!
    947962!--    Set boundary conditions of u-, v-, w-component, as well as q, and pt.
     
    10241039                                                  fac_dt                   )
    10251040                      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)
    10261043                   ENDDO
    10271044                ENDIF
     
    11001117                                                 fac_dt                       )
    11011118                      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)
    11021121                   ENDDO
    11031122                ENDIF
     
    11791198                                                 fac_dt                    )
    11801199                      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)
    11811202                   ENDDO
    11821203                ENDIF
     
    12571278                                                 fac_dt                       )
    12581279                      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)
    12591282                   ENDDO
    12601283                ENDIF
     
    13371360                   DO  j = nys, nyn
    13381361                      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),     &
    13411364                                              fac_dt                       )
     1365                      ref_chem_l(nzt+1,n) = ref_chem_l(nzt+1,n) +              &
     1366                                            chem_species(n)%conc(nzt+1,j,i)
    13421367                   ENDDO
    13431368                ENDDO
     
    14041429                              comm2d, ierr )
    14051430       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
    14061436#else
    14071437       u_ref  = u_ref_l
    14081438       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
    14111442#endif
    14121443!
     
    14271458                                                          ( ny + 1 + nx + 1 ), &
    14281459                                              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 )
    14291464!
    14301465!--    Derived from top boundary.   
     
    14371472          pt_ref(nzt+1) = pt_ref(nzt+1) / REAL( ( ny + 1 ) * ( nx + 1 ),       &
    14381473                                                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.
    14411481       u_init = u_ref
    14421482       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 )     
    14491504!
    14501505!--    Further, adjust Rayleigh damping height in case of time-changing conditions.
Note: See TracChangeset for help on using the changeset viewer.