Changeset 4102 for palm


Ignore:
Timestamp:
Jul 17, 2019 4:00:03 PM (5 years ago)
Author:
suehring
Message:

Bugfix, set Neumann boundary conditions for the subgrid TKE at vertical walls instead of implicit Dirichlet conditions that always act as a sink term for the subgrid TKE. Therefore, add new data structure for vertical surfaces and revise the setting of the boundary grid point index space. Moreover, slightly revise setting of boundary conditions at upward- and downward facing surfaces. Finally, setting of boundary conditions for subgrid TKE and dissipation (in RANS mode) is now modularized. Update test case results.

Location:
palm/trunk
Files:
16 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r4070 r4102  
    2525# -----------------
    2626# $Id$
     27# Remove dependency on pmc_interface for boundary_conds
     28#
     29# 4070 2019-07-03 13:51:40Z gronemeier
    2730# Add new data output modules
    2831#
     
    802805        radiation_model_mod.o
    803806boundary_conds.o: \
    804         basic_constants_and_equations_mod.o \
    805807        bulk_cloud_model_mod.o \
    806808        chemistry_model_mod.o \
    807809        mod_kinds.o \
    808810        modules.o \
    809         pmc_interface_mod.o \
    810811        salsa_mod.o \
    811812        surface_mod.o \
  • palm/trunk/SOURCE/boundary_conds.f90

    r4087 r4102  
    2525! -----------------
    2626! $Id$
     27! - Revise setting for boundary conditions at horizontal walls, use the offset
     28!   index that belongs to the data structure instead of pre-calculating
     29!   the offset index for each facing.
     30! - Set boundary conditions for bulk-cloud quantities also at downward facing
     31!   surfaces
     32!
     33! 4087 2019-07-11 11:35:23Z gronemeier
    2734! Add comment
    2835!
     
    224231    USE arrays_3d,                                                             &
    225232        ONLY:  c_u, c_u_m, c_u_m_l, c_v, c_v_m, c_v_m_l, c_w, c_w_m, c_w_m_l,  &
    226                diss, diss_p, dzu, e_p, nc_p, nr_p, pt, pt_init, pt_p, q,       &
     233               dzu, nc_p, nr_p, pt, pt_init, pt_p, q,                          &
    227234               q_p, qc_p, qr_p, s, s_p, sa, sa_p, u, u_init, u_m_l, u_m_n,     &
    228235               u_m_r, u_m_s, u_p, v, v_init, v_m_l, v_m_n, v_m_r, v_m_s, v_p,  &
    229236               w, w_p, w_m_l, w_m_n, w_m_r, w_m_s
    230237
    231     USE basic_constants_and_equations_mod,                                     &
    232         ONLY:  kappa
    233 
    234238    USE bulk_cloud_model_mod,                                                  &
    235239        ONLY: bulk_cloud_model, microphysics_morrison, microphysics_seifert
     
    239243
    240244    USE control_parameters,                                                    &
    241         ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,  &
     245        ONLY:  air_chemistry, bc_dirichlet_l,                                  &
    242246               bc_dirichlet_s, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
    243247               bc_radiation_s, bc_pt_t_val, bc_q_t_val, bc_s_t_val,            &
    244                child_domain, constant_diffusion, coupling_mode, dt_3d,         &
     248               child_domain, coupling_mode, dt_3d,                             &
    245249               humidity, ibc_pt_b, ibc_pt_t, ibc_q_b, ibc_q_t, ibc_s_b,        &
    246250               ibc_s_t, ibc_uv_b, ibc_uv_t, intermediate_timestep_count,       &
    247251               nesting_offline, neutral, nudging, ocean_mode, passive_scalar,  &
    248                rans_mode, rans_tke_e, tsc, salsa, use_cmax
     252               tsc, salsa, use_cmax
    249253
    250254    USE grid_variables,                                                        &
     
    262266
    263267    USE pmc_interface,                                                         &
    264         ONLY : nesting_mode, rans_mode_parent
     268        ONLY : nesting_mode
    265269 
    266270    USE salsa_mod,                                                             &
     
    268272
    269273    USE surface_mod,                                                           &
    270         ONLY :  bc_h, surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v,          &
    271                 surf_usm_h, surf_usm_v
     274        ONLY :  bc_h
    272275
    273276    USE turbulence_closure_mod,                                                &
    274         ONLY:  c_0
     277        ONLY:  tcm_boundary_conds
    275278
    276279    IMPLICIT NONE
     
    279282    INTEGER(iwp) ::  j  !< grid index y direction
    280283    INTEGER(iwp) ::  k  !< grid index z direction
    281     INTEGER(iwp) ::  kb !< variable to set respective boundary value, depends on facing.
    282284    INTEGER(iwp) ::  l  !< running index boundary type, for up- and downward-facing walls
    283285    INTEGER(iwp) ::  m  !< running index surface elements
     
    297299!-- of downward-facing surfaces.
    298300    DO  l = 0, 1
    299 !
    300 !--    Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    301 !--    for downward-facing surfaces at topography bottom (k+1).
    302        kb = MERGE( -1, 1, l == 0 )
    303301       !$OMP PARALLEL DO PRIVATE( i, j, k )
    304302       !$ACC PARALLEL LOOP PRIVATE(i, j, k) &
     
    308306          j = bc_h(l)%j(m)
    309307          k = bc_h(l)%k(m)
    310           w_p(k+kb,j,i) = 0.0_wp
     308          w_p(k+bc_h(l)%koff,j,i) = 0.0_wp
    311309       ENDDO
    312310    ENDDO
     
    341339       IF ( ibc_pt_b == 0 )  THEN
    342340          DO  l = 0, 1
    343 !     
    344 !--          Set kb, for upward-facing surfaces value at topography top (k-1)
    345 !--          is set, for downward-facing surfaces at topography bottom (k+1).
    346              kb = MERGE( -1, 1, l == 0 )
    347341             !$OMP PARALLEL DO PRIVATE( i, j, k )
    348342             DO  m = 1, bc_h(l)%ns
     
    350344                j = bc_h(l)%j(m)
    351345                k = bc_h(l)%k(m)
    352                 pt_p(k+kb,j,i) = pt(k+kb,j,i)
     346                pt_p(k+bc_h(l)%koff,j,i) = pt(k+bc_h(l)%koff,j,i)
    353347             ENDDO
    354348          ENDDO
     
    357351       ELSEIF ( ibc_pt_b == 1 )  THEN
    358352          DO  l = 0, 1
    359 !     
    360 !--          Set kb, for upward-facing surfaces value at topography top (k-1)
    361 !--          is set, for downward-facing surfaces at topography bottom (k+1).
    362              kb = MERGE( -1, 1, l == 0 )
    363353             !$OMP PARALLEL DO PRIVATE( i, j, k )
    364354             !$ACC PARALLEL LOOP PRIVATE(i, j, k) &
     
    368358                j = bc_h(l)%j(m)
    369359                k = bc_h(l)%k(m)
    370                 pt_p(k+kb,j,i) = pt_p(k,j,i)
     360                pt_p(k+bc_h(l)%koff,j,i) = pt_p(k,j,i)
    371361             ENDDO
    372362          ENDDO
     
    391381       ENDIF
    392382    ENDIF
    393 
    394 !
    395 !-- Boundary conditions for TKE.
    396 !-- Generally Neumann conditions with de/dz=0 are assumed.
    397     IF ( .NOT. constant_diffusion )  THEN
    398 
    399        IF ( .NOT. rans_mode )  THEN
    400           DO  l = 0, 1
    401 !
    402 !--         Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    403 !--         for downward-facing surfaces at topography bottom (k+1).
    404              kb = MERGE( -1, 1, l == 0 )
    405              !$OMP PARALLEL DO PRIVATE( i, j, k )
    406              !$ACC PARALLEL LOOP PRIVATE(i, j, k) &
    407              !$ACC PRESENT(bc_h, e_p)
    408              DO  m = 1, bc_h(l)%ns
    409                 i = bc_h(l)%i(m)           
    410                 j = bc_h(l)%j(m)
    411                 k = bc_h(l)%k(m)
    412                 e_p(k+kb,j,i) = e_p(k,j,i)
    413              ENDDO
    414           ENDDO
    415        ELSE
    416 !
    417 !--       Use wall function within constant-flux layer
    418 !--       Note, grid points listed in bc_h are not included in any calculations in RANS mode and
    419 !--       are therefore not set here.
    420 !
    421 !--       Upward-facing surfaces
    422 !--       Default surfaces
    423           DO  m = 1, surf_def_h(0)%ns
    424              i = surf_def_h(0)%i(m)
    425              j = surf_def_h(0)%j(m)
    426              k = surf_def_h(0)%k(m)
    427              e_p(k,j,i) = ( surf_def_h(0)%us(m) / c_0 )**2
    428           ENDDO
    429 !
    430 !--       Natural surfaces
    431           DO  m = 1, surf_lsm_h%ns
    432              i = surf_lsm_h%i(m)
    433              j = surf_lsm_h%j(m)
    434              k = surf_lsm_h%k(m)
    435              e_p(k,j,i) = ( surf_lsm_h%us(m) / c_0 )**2
    436           ENDDO
    437 !
    438 !--       Urban surfaces
    439           DO  m = 1, surf_usm_h%ns
    440              i = surf_usm_h%i(m)
    441              j = surf_usm_h%j(m)
    442              k = surf_usm_h%k(m)
    443              e_p(k,j,i) = ( surf_usm_h%us(m) / c_0 )**2
    444           ENDDO
    445 !
    446 !--       Vertical surfaces
    447           DO  l = 0, 3
    448 !
    449 !--          Default surfaces
    450              DO  m = 1, surf_def_v(l)%ns
    451                 i = surf_def_v(l)%i(m)
    452                 j = surf_def_v(l)%j(m)
    453                 k = surf_def_v(l)%k(m)
    454                 e_p(k,j,i) = ( surf_def_v(l)%us(m) / c_0 )**2
    455              ENDDO
    456 !
    457 !--          Natural surfaces
    458              DO  m = 1, surf_lsm_v(l)%ns
    459                 i = surf_lsm_v(l)%i(m)
    460                 j = surf_lsm_v(l)%j(m)
    461                 k = surf_lsm_v(l)%k(m)
    462                 e_p(k,j,i) = ( surf_lsm_v(l)%us(m) / c_0 )**2
    463              ENDDO
    464 !
    465 !--          Urban surfaces
    466              DO  m = 1, surf_usm_v(l)%ns
    467                 i = surf_usm_v(l)%i(m)
    468                 j = surf_usm_v(l)%j(m)
    469                 k = surf_usm_v(l)%k(m)
    470                 e_p(k,j,i) = ( surf_usm_v(l)%us(m) / c_0 )**2
    471              ENDDO
    472           ENDDO
    473        ENDIF
    474 
    475        IF ( .NOT. child_domain )  THEN
    476           !$ACC KERNELS PRESENT(e_p)
    477           e_p(nzt+1,:,:) = e_p(nzt,:,:)
    478           !$ACC END KERNELS
    479 !
    480 !--    Nesting case: if parent operates in RANS mode and child in LES mode,
    481 !--    no TKE is transfered. This case, set Neumann conditions at lateral and
    482 !--    top child boundaries.
    483 !--    If not ( both either in RANS or in LES mode ), TKE boundary condition
    484 !--    is treated in the nesting.
    485        ELSE
    486 
    487           IF ( rans_mode_parent  .AND.  .NOT. rans_mode )  THEN
    488 
    489              e_p(nzt+1,:,:) = e_p(nzt,:,:)
    490              IF ( bc_dirichlet_l )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
    491              IF ( bc_dirichlet_r )  e_p(:,:,nxr+1) = e_p(:,:,nxr)
    492              IF ( bc_dirichlet_s )  e_p(:,nys-1,:) = e_p(:,nys,:)
    493              IF ( bc_dirichlet_n )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
    494 
    495           ENDIF
    496        ENDIF
    497     ENDIF
    498 
    499 !
    500 !-- Boundary conditions for TKE dissipation rate.
    501     IF ( rans_tke_e )  THEN
    502 !
    503 !--    Use wall function within constant-flux layer
    504 !--    Upward-facing surfaces
    505 !--    Default surfaces
    506        DO  m = 1, surf_def_h(0)%ns
    507           i = surf_def_h(0)%i(m)
    508           j = surf_def_h(0)%j(m)
    509           k = surf_def_h(0)%k(m)
    510           diss_p(k,j,i) = surf_def_h(0)%us(m)**3          &
    511                         / ( kappa * surf_def_h(0)%z_mo(m) )
    512        ENDDO
    513 !
    514 !--    Natural surfaces
    515        DO  m = 1, surf_lsm_h%ns
    516           i = surf_lsm_h%i(m)
    517           j = surf_lsm_h%j(m)
    518           k = surf_lsm_h%k(m)
    519           diss_p(k,j,i) = surf_lsm_h%us(m)**3          &
    520                         / ( kappa * surf_lsm_h%z_mo(m) )
    521        ENDDO
    522 !
    523 !--    Urban surfaces
    524        DO  m = 1, surf_usm_h%ns
    525           i = surf_usm_h%i(m)
    526           j = surf_usm_h%j(m)
    527           k = surf_usm_h%k(m)
    528           diss_p(k,j,i) = surf_usm_h%us(m)**3          &
    529                         / ( kappa * surf_usm_h%z_mo(m) )
    530        ENDDO
    531 !
    532 !--    Vertical surfaces
    533        DO  l = 0, 3
    534 !
    535 !--       Default surfaces
    536           DO  m = 1, surf_def_v(l)%ns
    537              i = surf_def_v(l)%i(m)
    538              j = surf_def_v(l)%j(m)
    539              k = surf_def_v(l)%k(m)
    540              diss_p(k,j,i) = surf_def_v(l)%us(m)**3          &
    541                            / ( kappa * surf_def_v(l)%z_mo(m) )
    542           ENDDO
    543 !
    544 !--       Natural surfaces
    545           DO  m = 1, surf_lsm_v(l)%ns
    546              i = surf_lsm_v(l)%i(m)
    547              j = surf_lsm_v(l)%j(m)
    548              k = surf_lsm_v(l)%k(m)
    549              diss_p(k,j,i) = surf_lsm_v(l)%us(m)**3          &
    550                            / ( kappa * surf_lsm_v(l)%z_mo(m) )
    551           ENDDO
    552 !
    553 !--       Urban surfaces
    554           DO  m = 1, surf_usm_v(l)%ns
    555              i = surf_usm_v(l)%i(m)
    556              j = surf_usm_v(l)%j(m)
    557              k = surf_usm_v(l)%k(m)
    558              diss_p(k,j,i) = surf_usm_v(l)%us(m)**3          &
    559                            / ( kappa * surf_usm_v(l)%z_mo(m) )
    560           ENDDO
    561        ENDDO
    562 !
    563 !--    Limit change of diss to be between -90% and +100%. Also, set an absolute
    564 !--    minimum value
    565        DO  i = nxl, nxr
    566           DO  j = nys, nyn
    567              DO  k = nzb, nzt+1
    568                 diss_p(k,j,i) = MAX( MIN( diss_p(k,j,i),          &
    569                                           2.0_wp * diss(k,j,i) ), &
    570                                      0.1_wp * diss(k,j,i),        &
    571                                      0.0001_wp )
    572              ENDDO
    573           ENDDO
    574        ENDDO
    575 
    576        IF ( .NOT. child_domain )  THEN
    577           diss_p(nzt+1,:,:) = diss_p(nzt,:,:)
    578        ENDIF
    579     ENDIF
    580 
    581383!
    582384!-- Boundary conditions for salinity
     
    586388!--    given.
    587389       DO  l = 0, 1
    588 !
    589 !--       Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    590 !--       for downward-facing surfaces at topography bottom (k+1).
    591           kb = MERGE( -1, 1, l == 0 )
    592390          !$OMP PARALLEL DO PRIVATE( i, j, k )
    593391          DO  m = 1, bc_h(l)%ns
     
    595393             j = bc_h(l)%j(m)
    596394             k = bc_h(l)%k(m)
    597              sa_p(k+kb,j,i) = sa_p(k,j,i)
     395             sa_p(k+bc_h(l)%koff,j,i) = sa_p(k,j,i)
    598396          ENDDO
    599397       ENDDO
     
    620418
    621419          DO  l = 0, 1
    622 !
    623 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    624 !--          for downward-facing surfaces at topography bottom (k+1).
    625              kb = MERGE( -1, 1, l == 0 )
    626420             !$OMP PARALLEL DO PRIVATE( i, j, k )
    627421             DO  m = 1, bc_h(l)%ns
     
    629423                j = bc_h(l)%j(m)
    630424                k = bc_h(l)%k(m)
    631                 q_p(k+kb,j,i) = q(k+kb,j,i)
     425                q_p(k+bc_h(l)%koff,j,i) = q(k+bc_h(l)%koff,j,i)
    632426             ENDDO
    633427          ENDDO
     
    636430         
    637431          DO  l = 0, 1
    638 !
    639 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    640 !--          for downward-facing surfaces at topography bottom (k+1).
    641              kb = MERGE( -1, 1, l == 0 )
    642432             !$OMP PARALLEL DO PRIVATE( i, j, k )
    643433             DO  m = 1, bc_h(l)%ns
     
    645435                j = bc_h(l)%j(m)
    646436                k = bc_h(l)%k(m)
    647                 q_p(k+kb,j,i) = q_p(k,j,i)
     437                q_p(k+bc_h(l)%koff,j,i) = q_p(k,j,i)
    648438             ENDDO
    649439          ENDDO
     
    662452!--       Run loop over all non-natural and natural walls. Note, in wall-datatype
    663453!--       the k coordinate belongs to the atmospheric grid point, therefore, set
    664 !--       qr_p and nr_p at k-1
     454!--       qr_p and nr_p at upward (k-1) and downward-facing (k+1) walls
     455          DO  l = 0, 1
    665456          !$OMP PARALLEL DO PRIVATE( i, j, k )
    666           DO  m = 1, bc_h(0)%ns
    667              i = bc_h(0)%i(m)           
    668              j = bc_h(0)%j(m)
    669              k = bc_h(0)%k(m)
    670              qc_p(k-1,j,i) = 0.0_wp
    671              nc_p(k-1,j,i) = 0.0_wp
     457             DO  m = 1, bc_h(l)%ns
     458                i = bc_h(l)%i(m)           
     459                j = bc_h(l)%j(m)
     460                k = bc_h(l)%k(m)
     461                qc_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     462                nc_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     463             ENDDO
    672464          ENDDO
    673465!
     
    683475!--       Run loop over all non-natural and natural walls. Note, in wall-datatype
    684476!--       the k coordinate belongs to the atmospheric grid point, therefore, set
    685 !--       qr_p and nr_p at k-1
     477!--       qr_p and nr_p at upward (k-1) and downward-facing (k+1) walls
     478          DO  l = 0, 1
    686479          !$OMP PARALLEL DO PRIVATE( i, j, k )
    687           DO  m = 1, bc_h(0)%ns
    688              i = bc_h(0)%i(m)           
    689              j = bc_h(0)%j(m)
    690              k = bc_h(0)%k(m)
    691              qr_p(k-1,j,i) = 0.0_wp
    692              nr_p(k-1,j,i) = 0.0_wp
     480             DO  m = 1, bc_h(l)%ns
     481                i = bc_h(l)%i(m)           
     482                j = bc_h(l)%j(m)
     483                k = bc_h(l)%k(m)
     484                qr_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     485                nr_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     486             ENDDO
    693487          ENDDO
    694488!
     
    711505         
    712506          DO  l = 0, 1
    713 !
    714 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    715 !--          for downward-facing surfaces at topography bottom (k+1).
    716              kb = MERGE( -1, 1, l == 0 )
    717507             !$OMP PARALLEL DO PRIVATE( i, j, k )
    718508             DO  m = 1, bc_h(l)%ns
     
    720510                j = bc_h(l)%j(m)
    721511                k = bc_h(l)%k(m)
    722                 s_p(k+kb,j,i) = s(k+kb,j,i)
     512                s_p(k+bc_h(l)%koff,j,i) = s(k+bc_h(l)%koff,j,i)
    723513             ENDDO
    724514          ENDDO
     
    727517         
    728518          DO  l = 0, 1
    729 !
    730 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    731 !--          for downward-facing surfaces at topography bottom (k+1).
    732              kb = MERGE( -1, 1, l == 0 )
    733519             !$OMP PARALLEL DO PRIVATE( i, j, k )
    734520             DO  m = 1, bc_h(l)%ns
     
    736522                j = bc_h(l)%j(m)
    737523                k = bc_h(l)%k(m)
    738                 s_p(k+kb,j,i) = s_p(k,j,i)
     524                s_p(k+bc_h(l)%koff,j,i) = s_p(k,j,i)
    739525             ENDDO
    740526          ENDDO
     
    750536       ENDIF
    751537
    752     ENDIF   
     538    ENDIF 
     539!
     540!-- Set boundary conditions for subgrid TKE and dissipation (RANS mode)
     541    CALL tcm_boundary_conds
    753542!
    754543!-- Top/bottom boundary conditions for chemical species
     
    760549!-- version) these levels are handled as a prognostic level, boundary values
    761550!-- have to be restored here.
    762 !-- For the SGS-TKE, Neumann boundary conditions are used at the inflow.
    763551    IF ( bc_dirichlet_s )  THEN
    764552       v_p(:,nys,:) = v_p(:,nys-1,:)
    765        IF ( .NOT. constant_diffusion ) e_p(:,nys-1,:) = e_p(:,nys,:)
    766     ELSEIF ( bc_dirichlet_n )  THEN
    767        IF ( .NOT. constant_diffusion ) e_p(:,nyn+1,:) = e_p(:,nyn,:)
    768553    ELSEIF ( bc_dirichlet_l ) THEN
    769554       u_p(:,:,nxl) = u_p(:,:,nxl-1)
    770        IF ( .NOT. constant_diffusion ) e_p(:,:,nxl-1) = e_p(:,:,nxl)
    771     ELSEIF ( bc_dirichlet_r )  THEN
    772        IF ( .NOT. constant_diffusion ) e_p(:,:,nxr+1) = e_p(:,:,nxr)
    773555    ENDIF
    774556
     
    777559!-- in case of nest boundaries. This must not be done in case of vertical nesting
    778560!-- mode as in that case the lateral boundaries are actually cyclic.
     561!-- Lateral oundary conditions for TKE and dissipation are set
     562!-- in tcm_boundary_conds.
    779563    IF ( nesting_mode /= 'vertical'  .OR.  nesting_offline )  THEN
    780564       IF ( bc_dirichlet_s )  THEN
     
    787571
    788572!
    789 !-- Lateral boundary conditions for scalar quantities at the outflow
     573!-- Lateral boundary conditions for scalar quantities at the outflow.
     574!-- Lateral oundary conditions for TKE and dissipation are set
     575!-- in tcm_boundary_conds.
    790576    IF ( bc_radiation_s )  THEN
    791577       pt_p(:,nys-1,:)     = pt_p(:,nys,:)
    792        IF ( .NOT. constant_diffusion )  e_p(:,nys-1,:) = e_p(:,nys,:)
    793        IF ( rans_tke_e )  diss_p(:,nys-1,:) = diss_p(:,nys,:)
    794578       IF ( humidity )  THEN
    795579          q_p(:,nys-1,:) = q_p(:,nys,:)
     
    806590    ELSEIF ( bc_radiation_n )  THEN
    807591       pt_p(:,nyn+1,:)     = pt_p(:,nyn,:)
    808        IF ( .NOT. constant_diffusion )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
    809        IF ( rans_tke_e )  diss_p(:,nyn+1,:) = diss_p(:,nyn,:)
    810592       IF ( humidity )  THEN
    811593          q_p(:,nyn+1,:) = q_p(:,nyn,:)
     
    822604    ELSEIF ( bc_radiation_l )  THEN
    823605       pt_p(:,:,nxl-1)     = pt_p(:,:,nxl)
    824        IF ( .NOT. constant_diffusion )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
    825        IF ( rans_tke_e )  diss_p(:,:,nxl-1) = diss_p(:,:,nxl)
    826606       IF ( humidity )  THEN
    827607          q_p(:,:,nxl-1) = q_p(:,:,nxl)
     
    838618    ELSEIF ( bc_radiation_r )  THEN
    839619       pt_p(:,:,nxr+1)     = pt_p(:,:,nxr)
    840        IF ( .NOT. constant_diffusion )  e_p(:,:,nxr+1) = e_p(:,:,nxr)
    841        IF ( rans_tke_e )  diss_p(:,:,nxr+1) = diss_p(:,:,nxr)
    842620       IF ( humidity )  THEN
    843621          q_p(:,:,nxr+1) = q_p(:,:,nxr)
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r4080 r4102  
    2727! -----------------
    2828! $Id$
     29! Slightly revise setting of boundary conditions at horizontal walls, use
     30! data-structure offset index instead of pre-calculate it for each facing
     31!
     32! 4080 2019-07-09 18:17:37Z suehring
    2933! Restore accidantly removed limitation to positive values
    3034!
     
    804808    INTEGER(iwp) ::  j                            !< grid index y direction.
    805809    INTEGER(iwp) ::  k                            !< grid index z direction.
    806     INTEGER(iwp) ::  kb                           !< variable to set respective boundary value, depends on facing.
    807810    INTEGER(iwp) ::  l                            !< running index boundary type, for up- and downward-facing walls.
    808811    INTEGER(iwp) ::  m                            !< running index surface elements.
     
    839842       CASE ( 'set_bc_bottomtop' )                   
    840843!
    841 !--          Bottom boundary condtions for chemical species     
     844!--       Boundary condtions for chemical species at horizontal walls     
    842845          DO  lsp = 1, nspec                                                     
    843              IF ( ibc_cs_b == 0 )  THEN                   
     846             IF ( ibc_cs_b == 0 )  THEN
    844847                DO  l = 0, 1
    845 !
    846 !--                Set index kb: For upward-facing surfaces (l=0), kb=-1, i.e.
    847 !--                the chem_species(nspec)%conc_p value at the topography top (k-1)
    848 !--                is set; for downward-facing surfaces (l=1), kb=1, i.e. the
    849 !--                value at the topography bottom (k+1) is set.
    850 
    851                    kb = MERGE( -1, 1, l == 0 )
    852848                   !$OMP PARALLEL DO PRIVATE( i, j, k )
    853849                   DO  m = 1, bc_h(l)%ns
     
    855851                       j = bc_h(l)%j(m)
    856852                       k = bc_h(l)%k(m)
    857                       chem_species(lsp)%conc_p(k+kb,j,i) = chem_species(lsp)%conc(k+kb,j,i)
     853                      chem_species(lsp)%conc_p(k+bc_h(l)%koff,j,i) =           &
     854                                      chem_species(lsp)%conc(k+bc_h(l)%koff,j,i)
    858855                   ENDDO                                       
    859856                ENDDO                                       
     
    863860!--             in boundary_conds there is som extra loop over m here for passive tracer
    864861                DO  l = 0, 1
    865                    kb = MERGE( -1, 1, l == 0 )
    866862                   !$OMP PARALLEL DO PRIVATE( i, j, k )                                           
    867863                   DO m = 1, bc_h(l)%ns
     
    869865                      j = bc_h(l)%j(m)
    870866                      k = bc_h(l)%k(m)
    871                       chem_species(lsp)%conc_p(k+kb,j,i) = chem_species(lsp)%conc_p(k,j,i)
     867                      chem_species(lsp)%conc_p(k+bc_h(l)%koff,j,i) =           &
     868                                         chem_species(lsp)%conc_p(k,j,i)
    872869
    873870                   ENDDO
  • palm/trunk/SOURCE/salsa_mod.f90

    r4079 r4102  
    2626! -----------------
    2727! $Id$
     28! Slightly revise setting of boundary conditions at horizontal walls, use
     29! data-structure offset index instead of pre-calculate it for each facing
     30!
     31! 4079 2019-07-09 18:04:41Z suehring
    2832! Application of monotonic flux limiter for the vertical scalar advection
    2933! up to the topography top (only for the cache-optimized version at the
     
    80178021    INTEGER(iwp) ::  j    !< grid index y direction
    80188022    INTEGER(iwp) ::  k    !< grid index y direction
    8019     INTEGER(iwp) ::  kb   !< variable to set respective boundary value, depends on facing.
    80208023    INTEGER(iwp) ::  l    !< running index boundary type, for up- and downward-facing walls
    80218024    INTEGER(iwp) ::  m    !< running index surface elements
     
    80308033!--       belongs to the atmospheric grid point, therefore, set s_p at k-1
    80318034          DO  l = 0, 1
    8032 !
    8033 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is
    8034 !--          set, for downward-facing surfaces at topography bottom (k+1)
    8035              kb = MERGE ( -1, 1, l == 0 )
    80368035             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
    80378036             !$OMP DO
     
    80438042
    80448043                DO  ib = 1, nbins_aerosol
    8045                    aerosol_number(ib)%conc_p(k+kb,j,i) = aerosol_number(ib)%conc(k+kb,j,i)
     8044                   aerosol_number(ib)%conc_p(k+bc_h(l)%koff,j,i) =             &
     8045                                    aerosol_number(ib)%conc(k+bc_h(l)%koff,j,i)
    80468046                   DO  ic = 1, ncomponents_mass
    80478047                      icc = ( ic - 1 ) * nbins_aerosol + ib
    8048                       aerosol_mass(icc)%conc_p(k+kb,j,i) = aerosol_mass(icc)%conc(k+kb,j,i)
     8048                      aerosol_mass(icc)%conc_p(k+bc_h(l)%koff,j,i) =           &
     8049                                    aerosol_mass(icc)%conc(k+bc_h(l)%koff,j,i)
    80498050                   ENDDO
    80508051                ENDDO
    80518052                IF ( .NOT. salsa_gases_from_chem )  THEN
    80528053                   DO  ig = 1, ngases_salsa
    8053                       salsa_gas(ig)%conc_p(k+kb,j,i) = salsa_gas(ig)%conc(k+kb,j,i)
     8054                      salsa_gas(ig)%conc_p(k+bc_h(l)%koff,j,i) =               &
     8055                                    salsa_gas(ig)%conc(k+bc_h(l)%koff,j,i)
    80548056                   ENDDO
    80558057                ENDIF
     
    80638065
    80648066          DO l = 0, 1
    8065 !
    8066 !--          Set kb, for upward-facing surfaces value at topography top (k-1) is
    8067 !--          set, for downward-facing surfaces at topography bottom (k+1)
    8068              kb = MERGE( -1, 1, l == 0 )
    80698067             !$OMP PARALLEL PRIVATE( ib, ic, icc, ig, i, j, k )
    80708068             !$OMP DO
     
    80768074
    80778075                DO  ib = 1, nbins_aerosol
    8078                    aerosol_number(ib)%conc_p(k+kb,j,i) = aerosol_number(ib)%conc_p(k,j,i)
     8076                   aerosol_number(ib)%conc_p(k+bc_h(l)%koff,j,i) =             &
     8077                                               aerosol_number(ib)%conc_p(k,j,i)
    80798078                   DO  ic = 1, ncomponents_mass
    80808079                      icc = ( ic - 1 ) * nbins_aerosol + ib
    8081                       aerosol_mass(icc)%conc_p(k+kb,j,i) = aerosol_mass(icc)%conc_p(k,j,i)
     8080                      aerosol_mass(icc)%conc_p(k+bc_h(l)%koff,j,i) =           &
     8081                                               aerosol_mass(icc)%conc_p(k,j,i)
    80828082                   ENDDO
    80838083                ENDDO
    80848084                IF ( .NOT. salsa_gases_from_chem ) THEN
    80858085                   DO  ig = 1, ngases_salsa
    8086                       salsa_gas(ig)%conc_p(k+kb,j,i) = salsa_gas(ig)%conc_p(k,j,i)
     8086                      salsa_gas(ig)%conc_p(k+bc_h(l)%koff,j,i) =               &
     8087                                               salsa_gas(ig)%conc_p(k,j,i)
    80878088                   ENDDO
    80888089                ENDIF
  • palm/trunk/SOURCE/surface_mod.f90

    r3943 r4102  
    2626! -----------------
    2727! $Id$
     28! - Revise initialization of the boundary data structure
     29! - Add new data structure to set boundary conditions at vertical walls
     30!
     31! 3943 2019-05-02 09:50:41Z maronga
    2832! Removed qsws_eb as it is no longer needed.
    2933!
     
    306310!-- are applied
    307311    TYPE bc_type
    308 
    309        INTEGER(iwp) :: ns                                  !< number of surface elements on the PE
    310 
    311        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i       !< x-index linking to the PALM 3D-grid 
    312        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j       !< y-index linking to the PALM 3D-grid   
    313        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k       !< z-index linking to the PALM 3D-grid   
     312       INTEGER(iwp) :: ioff !< offset value in x-direction, used to determine index of surface element
     313       INTEGER(iwp) :: joff !< offset value in y-direction, used to determine index of surface element
     314       INTEGER(iwp) :: koff !< offset value in z-direction, used to determine index of surface element
     315       INTEGER(iwp) :: ns   !< number of surface elements on the PE
     316
     317       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i !< x-index linking to the PALM 3D-grid 
     318       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j !< y-index linking to the PALM 3D-grid   
     319       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k !< z-index linking to the PALM 3D-grid   
    314320
    315321       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE :: start_index !< start index within surface data type for given (j,i)
     
    600606
    601607    TYPE (bc_type), DIMENSION(0:1)           ::  bc_h        !< boundary condition data type, horizontal upward- and downward facing surfaces
     608    TYPE (bc_type), DIMENSION(0:3)           ::  bc_v        !< boundary condition data type, vertical surfaces
    602609
    603610    TYPE (surf_type), DIMENSION(0:2), TARGET ::  surf_def_h  !< horizontal default surfaces (Up, Down, and Top)
     
    668675!
    669676!-- Public variables
    670     PUBLIC bc_h, ind_pav_green, ind_veg_wall, ind_wat_win, ns_h_on_file, ns_v_on_file, surf_def_h, &
    671            surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v, surf_type,                  &
     677    PUBLIC bc_h, bc_v, ind_pav_green, ind_veg_wall, ind_wat_win, ns_h_on_file, ns_v_on_file,      &
     678           surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v, surf_type,      &
    672679           vertical_surfaces_exist, surf_bulk_cloud_model, surf_microphysics_morrison,             &
    673680           surf_microphysics_seifert
     
    687694! Description:
    688695! ------------
    689 !> Initialize data type for setting boundary conditions at horizontal surfaces.
     696!> Initialize data type for setting boundary conditions at horizontal and 
     697!> vertical surfaces.
    690698!------------------------------------------------------------------------------!
    691699    SUBROUTINE init_bc
     
    696704       INTEGER(iwp) ::  j         !< loop index along y-direction
    697705       INTEGER(iwp) ::  k         !< loop index along y-direction
    698 
    699        INTEGER(iwp), DIMENSION(0:1) ::  num_h         !< number of surfaces
    700        INTEGER(iwp), DIMENSION(0:1) ::  num_h_kji     !< number of surfaces for (j,i)-grid point
    701        INTEGER(iwp), DIMENSION(0:1) ::  start_index_h !< local start index
    702 
    703 !
    704 !--    First of all, count the number of upward- and downward-facing surfaces
    705        num_h = 0
    706        DO  i = nxlg, nxrg
    707           DO  j = nysg, nyng
    708              DO  k = nzb+1, nzt
    709 !
    710 !--             Check if current gridpoint belongs to the atmosphere
    711                 IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
    712 !
    713 !--                Upward-facing
    714                    IF ( .NOT. BTEST( wall_flags_0(k-1,j,i), 0 ) )              &
    715                       num_h(0) = num_h(0) + 1
    716 !
    717 !--                Downward-facing
    718                    IF ( .NOT. BTEST( wall_flags_0(k+1,j,i), 0 ) )              &
    719                       num_h(1) = num_h(1) + 1
    720                 ENDIF
     706       INTEGER(iwp) ::  l         !< running index for differently aligned surfaces
     707
     708       INTEGER(iwp), DIMENSION(0:1) ::  num_h         !< number of horizontal surfaces on subdomain
     709       INTEGER(iwp), DIMENSION(0:1) ::  num_h_kji     !< number of horizontal surfaces at (j,i)-grid point
     710       INTEGER(iwp), DIMENSION(0:1) ::  start_index_h !< local start index of horizontal surface elements
     711       
     712       INTEGER(iwp), DIMENSION(0:3) ::  num_v         !< number of vertical surfaces on subdomain
     713       INTEGER(iwp), DIMENSION(0:3) ::  num_v_kji     !< number of vertical surfaces at (j,i)-grid point
     714       INTEGER(iwp), DIMENSION(0:3) ::  start_index_v !< local start index of vertical surface elements
     715!
     716!--    Set offset indices, i.e. index difference between surface element and
     717!--    surface-bounded grid point.
     718!--    Horizontal surfaces - no horizontal offsets
     719       bc_h(:)%ioff = 0
     720       bc_h(:)%joff = 0
     721!
     722!--    Horizontal surfaces, upward facing (0) and downward facing (1)
     723       bc_h(0)%koff   = -1
     724       bc_h(1)%koff   = 1
     725!
     726!--    Vertical surfaces - no vertical offset
     727       bc_v(0:3)%koff = 0
     728!
     729!--    North- and southward facing - no offset in x
     730       bc_v(0:1)%ioff = 0
     731!
     732!--    Northward facing offset in y
     733       bc_v(0)%joff = -1
     734!
     735!--    Southward facing offset in y
     736       bc_v(1)%joff = 1
     737!
     738!--    East- and westward facing - no offset in y
     739       bc_v(2:3)%joff = 0
     740!
     741!--    Eastward facing offset in x
     742       bc_v(2)%ioff = -1
     743!
     744!--    Westward facing offset in y
     745       bc_v(3)%ioff = 1
     746!
     747!--    Initialize data structure for horizontal surfaces, i.e. count the number
     748!--    of surface elements, allocate and initialize the respective index arrays,
     749!--    and set the respective start and end indices at each (j,i)-location.
     750       DO  l = 0, 1
     751!
     752!--       Count the number of upward- and downward-facing surfaces on subdomain
     753          num_h(l) = 0
     754          DO  i = nxlg, nxrg
     755             DO  j = nysg, nyng
     756                DO  k = nzb+1, nzt
     757!         
     758!--                Check if current gridpoint belongs to the atmosphere
     759                   IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
     760                      IF ( .NOT. BTEST( wall_flags_0(k+bc_h(l)%koff,           &
     761                                                     j+bc_h(l)%joff,           &
     762                                                     i+bc_h(l)%ioff), 0 ) )    &
     763                         num_h(l) = num_h(l) + 1
     764                   ENDIF
     765                ENDDO
     766             ENDDO
     767          ENDDO
     768!         
     769!--       Save the number of horizontal surface elements
     770          bc_h(l)%ns = num_h(l)
     771!
     772!--       ALLOCATE arrays for horizontal surfaces
     773          ALLOCATE( bc_h(l)%i(1:bc_h(l)%ns) )
     774          ALLOCATE( bc_h(l)%j(1:bc_h(l)%ns) )
     775          ALLOCATE( bc_h(l)%k(1:bc_h(l)%ns) )
     776          ALLOCATE( bc_h(l)%start_index(nysg:nyng,nxlg:nxrg) )
     777          ALLOCATE( bc_h(l)%end_index(nysg:nyng,nxlg:nxrg)   )
     778          bc_h(l)%start_index = 1
     779          bc_h(l)%end_index   = 0
     780         
     781          num_h(l)         = 1
     782          start_index_h(l) = 1
     783          DO  i = nxlg, nxrg
     784             DO  j = nysg, nyng
     785         
     786                num_h_kji(l) = 0
     787                DO  k = nzb+1, nzt
     788!         
     789!--                Check if current gridpoint belongs to the atmosphere
     790                   IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
     791!         
     792!--                   Upward-facing
     793                      IF ( .NOT. BTEST( wall_flags_0(k+bc_h(l)%koff,           &
     794                                                     j+bc_h(l)%joff,           &
     795                                                     i+bc_h(l)%ioff), 0 )      &
     796                         )  THEN
     797                         bc_h(l)%i(num_h(l)) = i
     798                         bc_h(l)%j(num_h(l)) = j
     799                         bc_h(l)%k(num_h(l)) = k
     800                         num_h_kji(l)        = num_h_kji(l) + 1
     801                         num_h(l)            = num_h(l) + 1
     802                      ENDIF
     803                   ENDIF
     804                ENDDO
     805                bc_h(l)%start_index(j,i) = start_index_h(l)
     806                bc_h(l)%end_index(j,i)   = bc_h(l)%start_index(j,i) +          &
     807                                           num_h_kji(l) - 1
     808                start_index_h(l)         = bc_h(l)%end_index(j,i) + 1
    721809             ENDDO
    722810          ENDDO
    723811       ENDDO
    724 !
    725 !--    Save the number of surface elements
    726        bc_h(0)%ns = num_h(0)
    727        bc_h(1)%ns = num_h(1)
    728 !
    729 !--    ALLOCATE data type variables
    730 !--    Upward facing
    731        ALLOCATE( bc_h(0)%i(1:bc_h(0)%ns) )
    732        ALLOCATE( bc_h(0)%j(1:bc_h(0)%ns) )
    733        ALLOCATE( bc_h(0)%k(1:bc_h(0)%ns) )
    734        ALLOCATE( bc_h(0)%start_index(nysg:nyng,nxlg:nxrg) )
    735        ALLOCATE( bc_h(0)%end_index(nysg:nyng,nxlg:nxrg)   )
    736        bc_h(0)%start_index = 1
    737        bc_h(0)%end_index   = 0
    738 !
    739 !--    Downward facing
    740        ALLOCATE( bc_h(1)%i(1:bc_h(1)%ns) )
    741        ALLOCATE( bc_h(1)%j(1:bc_h(1)%ns) )
    742        ALLOCATE( bc_h(1)%k(1:bc_h(1)%ns) )
    743        ALLOCATE( bc_h(1)%start_index(nysg:nyng,nxlg:nxrg) )
    744        ALLOCATE( bc_h(1)%end_index(nysg:nyng,nxlg:nxrg)   )
    745        bc_h(1)%start_index = 1
    746        bc_h(1)%end_index   = 0
    747 !
    748 !--    Store the respective indices on data type
    749        num_h(0:1)         = 1
    750        start_index_h(0:1) = 1
    751        DO  i = nxlg, nxrg
    752           DO  j = nysg, nyng
    753 
    754              num_h_kji(0:1) = 0
    755              DO  k = nzb+1, nzt
    756 !
    757 !--             Check if current gridpoint belongs to the atmosphere
    758                 IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
    759 !
    760 !--                Upward-facing
    761                    IF ( .NOT. BTEST( wall_flags_0(k-1,j,i), 0 ) )  THEN
    762                       bc_h(0)%i(num_h(0)) = i
    763                       bc_h(0)%j(num_h(0)) = j
    764                       bc_h(0)%k(num_h(0)) = k
    765                       num_h_kji(0)        = num_h_kji(0) + 1
    766                       num_h(0)            = num_h(0) + 1
     812
     813!
     814!--    Initialize data structure for vertical surfaces, i.e. count the number
     815!--    of surface elements, allocate and initialize the respective index arrays,
     816!--    and set the respective start and end indices at each (j,i)-location.
     817       DO  l = 0, 3
     818!
     819!--       Count the number of upward- and downward-facing surfaces on subdomain
     820          num_v(l) = 0
     821          DO  i = nxlg, nxrg
     822             DO  j = nysg, nyng
     823                DO  k = nzb+1, nzt
     824!         
     825!--                Check if current gridpoint belongs to the atmosphere
     826                   IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
     827                      IF ( .NOT. BTEST( wall_flags_0(k+bc_v(l)%koff,           &
     828                                                     j+bc_v(l)%joff,           &
     829                                                     i+bc_v(l)%ioff), 0 ) )    &
     830                         num_v(l) = num_v(l) + 1
    767831                   ENDIF
    768 !
    769 !--                Downward-facing
    770                    IF ( .NOT. BTEST( wall_flags_0(k+1,j,i), 0 ) )  THEN
    771                       bc_h(1)%i(num_h(1)) = i
    772                       bc_h(1)%j(num_h(1)) = j
    773                       bc_h(1)%k(num_h(1)) = k
    774                       num_h_kji(1)        = num_h_kji(1) + 1
    775                       num_h(1)            = num_h(1) + 1
     832                ENDDO
     833             ENDDO
     834          ENDDO
     835!         
     836!--       Save the number of horizontal surface elements
     837          bc_v(l)%ns = num_v(l)
     838!
     839!--       ALLOCATE arrays for horizontal surfaces
     840          ALLOCATE( bc_v(l)%i(1:bc_v(l)%ns) )
     841          ALLOCATE( bc_v(l)%j(1:bc_v(l)%ns) )
     842          ALLOCATE( bc_v(l)%k(1:bc_v(l)%ns) )
     843          ALLOCATE( bc_v(l)%start_index(nysg:nyng,nxlg:nxrg) )
     844          ALLOCATE( bc_v(l)%end_index(nysg:nyng,nxlg:nxrg)   )
     845          bc_v(l)%start_index = 1
     846          bc_v(l)%end_index   = 0
     847         
     848          num_v(l)         = 1
     849          start_index_v(l) = 1
     850          DO  i = nxlg, nxrg
     851             DO  j = nysg, nyng
     852         
     853                num_v_kji(l) = 0
     854                DO  k = nzb+1, nzt
     855!         
     856!--                Check if current gridpoint belongs to the atmosphere
     857                   IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
     858!         
     859!--                   Upward-facing
     860                      IF ( .NOT. BTEST( wall_flags_0(k+bc_v(l)%koff,           &
     861                                                     j+bc_v(l)%joff,           &
     862                                                     i+bc_v(l)%ioff), 0 )      &
     863                         )  THEN
     864                         bc_v(l)%i(num_v(l)) = i
     865                         bc_v(l)%j(num_v(l)) = j
     866                         bc_v(l)%k(num_v(l)) = k
     867                         num_v_kji(l)        = num_v_kji(l) + 1
     868                         num_v(l)            = num_v(l) + 1
     869                      ENDIF
    776870                   ENDIF
    777                 ENDIF
     871                ENDDO
     872                bc_v(l)%start_index(j,i) = start_index_v(l)
     873                bc_v(l)%end_index(j,i)   = bc_v(l)%start_index(j,i) +          &
     874                                           num_v_kji(l) - 1
     875                start_index_v(l)         = bc_v(l)%end_index(j,i) + 1
    778876             ENDDO
    779              bc_h(0)%start_index(j,i) = start_index_h(0)
    780              bc_h(0)%end_index(j,i)   = bc_h(0)%start_index(j,i) + num_h_kji(0) - 1
    781              start_index_h(0)         = bc_h(0)%end_index(j,i) + 1
    782 
    783              bc_h(1)%start_index(j,i) = start_index_h(1)
    784              bc_h(1)%end_index(j,i)   = bc_h(1)%start_index(j,i) + num_h_kji(1) - 1
    785              start_index_h(1)         = bc_h(1)%end_index(j,i) + 1
    786877          ENDDO
    787878       ENDDO
  • palm/trunk/SOURCE/turbulence_closure_mod.f90

    r4048 r4102  
    2525! -----------------
    2626! $Id$
     27! - Modularize setting of boundary conditions for TKE and dissipation
     28! - Neumann boundary condition for TKE at model top is set also in child domain
     29! - Revise setting of Neumann boundary conditions at non-cyclic lateral
     30!   boundaries
     31! - Bugfix, set Neumann boundary condition for TKE at vertical wall instead of
     32!   an implicit Dirichlet boundary condition which implied a sink of TKE
     33!   at vertical walls
     34!
     35! 4048 2019-06-21 21:00:21Z knoop
    2736! write out preprocessor directives; remove tailing whitespaces
    2837!
     
    192201!> @todo Check for random disturbances
    193202!> @note <Enter notes on the module>
    194 !------------------------------------------------------------------------------!
     203!-----------------------------------------------------------------------------!
    195204 MODULE turbulence_closure_mod
    196205
    197206
    198     USE arrays_3d,                                                             &
    199         ONLY:  diss, diss_1, diss_2, diss_3, diss_p, dzu, e, e_1, e_2, e_3,    &
    200                e_p, kh, km, mean_inflow_profiles, prho, pt, tdiss_m,           &
     207    USE arrays_3d,                                                            &
     208        ONLY:  diss, diss_1, diss_2, diss_3, diss_p, dzu, e, e_1, e_2, e_3,   &
     209               e_p, kh, km, mean_inflow_profiles, prho, pt, tdiss_m,          &
    201210               te_m, tend, u, v, vpt, w
    202211
    203     USE basic_constants_and_equations_mod,                                     &
     212    USE basic_constants_and_equations_mod,                                    &
    204213        ONLY:  g, kappa, lv_d_cp, lv_d_rd, rd_d_rv
    205214
    206     USE control_parameters,                                                    &
    207         ONLY:  constant_diffusion, dt_3d, e_init, humidity,                    &
    208                initializing_actions, intermediate_timestep_count,              &
    209                intermediate_timestep_count_max, km_constant,                   &
    210                les_dynamic, les_mw, ocean_mode, plant_canopy, prandtl_number,  &
    211                pt_reference, rans_mode, rans_tke_e, rans_tke_l,                &
    212                timestep_scheme, turbulence_closure,                            &
    213                turbulent_inflow, use_upstream_for_tke, vpt_reference,          &
     215    USE control_parameters,                                                   &
     216        ONLY:  bc_dirichlet_l,                                                &
     217               bc_dirichlet_n,                                                &
     218               bc_dirichlet_r,                                                &
     219               bc_dirichlet_s,                                                &
     220               bc_radiation_l,                                                &
     221               bc_radiation_n,                                                &
     222               bc_radiation_r,                                                &
     223               bc_radiation_s,                                                &
     224               child_domain,                                                  &
     225               constant_diffusion, dt_3d, e_init, humidity,                   &
     226               initializing_actions, intermediate_timestep_count,             &
     227               intermediate_timestep_count_max, km_constant,                  &
     228               les_dynamic, les_mw, ocean_mode, plant_canopy, prandtl_number, &
     229               pt_reference, rans_mode, rans_tke_e, rans_tke_l,               &
     230               timestep_scheme, turbulence_closure,                           &
     231               turbulent_inflow, use_upstream_for_tke, vpt_reference,         &
    214232               ws_scheme_sca, current_timestep_number
    215233
    216     USE advec_ws,                                                              &
     234    USE advec_ws,                                                             &
    217235        ONLY:  advec_s_ws
    218236
    219     USE advec_s_bc_mod,                                                        &
     237    USE advec_s_bc_mod,                                                       &
    220238        ONLY:  advec_s_bc
    221239
    222     USE advec_s_pw_mod,                                                        &
     240    USE advec_s_pw_mod,                                                       &
    223241        ONLY:  advec_s_pw
    224242
    225     USE advec_s_up_mod,                                                        &
     243    USE advec_s_up_mod,                                                       &
    226244        ONLY:  advec_s_up
    227245
    228     USE cpulog,                                                                &
     246    USE cpulog,                                                               &
    229247        ONLY:  cpu_log, log_point_s
    230248
    231     USE indices,                                                               &
    232         ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt,     &
     249    USE indices,                                                              &
     250        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt,    &
    233251               wall_flags_0
    234252
    235253    USE kinds
    236254
    237     USE ocean_mod,                                                             &
     255    USE ocean_mod,                                                            &
    238256        ONLY:  prho_reference
    239257
    240258    USE pegrid
    241259
    242     USE plant_canopy_model_mod,                                                &
     260    USE plant_canopy_model_mod,                                               &
    243261        ONLY:  pcm_tendency
    244262
    245     USE statistics,                                                            &
     263    USE statistics,                                                           &
    246264        ONLY:  hom, hom_sum, statistic_regions
    247 
     265       
     266    USE surface_mod,                                                          &
     267        ONLY:  bc_h,                                                          &
     268               bc_v,                                                          &
     269               get_topography_top_index_ji,                                   &
     270               surf_def_h,                                                    &
     271               surf_def_v,                                                    &
     272               surf_lsm_h,                                                    &
     273               surf_lsm_v,                                                    &
     274               surf_usm_h,                                                    &
     275               surf_usm_v
    248276
    249277    IMPLICIT NONE
     
    271299    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  l_wall !< near-wall mixing length
    272300
    273 
     301!
     302!-- Public variables
    274303    PUBLIC c_0, rans_const_c, rans_const_sigma
    275304
     
    277306
    278307    PRIVATE
    279 
    280 
    281     PUBLIC &
    282        tcm_check_parameters, &
    283        tcm_check_data_output, &
    284        tcm_define_netcdf_grid, &
    285        tcm_init_arrays, &
    286        tcm_init, &
    287        tcm_actions, &
    288        tcm_prognostic_equations, &
    289        tcm_swap_timelevel, &
    290        tcm_3d_data_averaging, &
    291        tcm_data_output_2d, &
    292        tcm_data_output_3d, &
     308!
     309!-- Public subroutines
     310    PUBLIC                                                                     &
     311       tcm_boundary_conds,                                                     &
     312       tcm_check_parameters,                                                   &
     313       tcm_check_data_output,                                                  &
     314       tcm_define_netcdf_grid,                                                 &
     315       tcm_init_arrays,                                                        &
     316       tcm_init,                                                               &
     317       tcm_actions,                                                            &
     318       tcm_prognostic_equations,                                               &
     319       tcm_swap_timelevel,                                                     &
     320       tcm_3d_data_averaging,                                                  &
     321       tcm_data_output_2d,                                                     &
     322       tcm_data_output_3d,                                                     &
    293323       tcm_diffusivities
    294324
    295325!
    296326!-- PALM interfaces:
     327!-- Boundary conditions for subgrid TKE and dissipation
     328    INTERFACE tcm_boundary_conds
     329       MODULE PROCEDURE tcm_boundary_conds
     330    END INTERFACE tcm_boundary_conds
     331!
    297332!-- Input parameter checks to be done in check_parameters
    298333    INTERFACE tcm_check_parameters
     
    371406 CONTAINS
    372407
     408!------------------------------------------------------------------------------!
     409! Description:
     410! ------------
     411!> Check parameters routine for turbulence closure module.
     412!------------------------------------------------------------------------------!
     413 SUBROUTINE tcm_boundary_conds
     414
     415    USE pmc_interface,                                                         &
     416        ONLY : rans_mode_parent
     417 
     418    IMPLICIT NONE
     419
     420    INTEGER(iwp) ::  i  !< grid index x direction
     421    INTEGER(iwp) ::  j  !< grid index y direction
     422    INTEGER(iwp) ::  k  !< grid index z direction
     423    INTEGER(iwp) ::  l  !< running index boundary type, for up- and downward-facing walls
     424    INTEGER(iwp) ::  m  !< running index surface elements
     425!
     426!-- Boundary conditions for TKE.
     427    IF ( .NOT. constant_diffusion )  THEN
     428!
     429!--    In LES mode, Neumann conditions with de/x_i=0 are assumed at solid walls.
     430!--    Note, only TKE is prognostic in this case and dissipation is only
     431!--    a diagnostic quantity.
     432       IF ( .NOT. rans_mode )  THEN
     433!
     434!--       Horizontal walls, upward- and downward-facing
     435          DO  l = 0, 1
     436             !$OMP PARALLEL DO PRIVATE( i, j, k )
     437             !$ACC PARALLEL LOOP PRIVATE(i, j, k) &
     438             !$ACC PRESENT(bc_h, e_p)
     439             DO  m = 1, bc_h(l)%ns
     440                i = bc_h(l)%i(m)           
     441                j = bc_h(l)%j(m)
     442                k = bc_h(l)%k(m)
     443                e_p(k+bc_h(l)%koff,j,i) = e_p(k,j,i)
     444             ENDDO
     445          ENDDO
     446!
     447!--       Vertical walls
     448          DO  l = 0, 3
     449             !$OMP PARALLEL DO PRIVATE( i, j, k )
     450             !$ACC PARALLEL LOOP PRIVATE(i, j, k) &
     451             !$ACC PRESENT(bc_v, e_p)
     452             DO  m = 1, bc_v(l)%ns
     453                i = bc_v(l)%i(m)           
     454                j = bc_v(l)%j(m)
     455                k = bc_v(l)%k(m)
     456                e_p(k,j+bc_v(l)%joff,i+bc_v(l)%ioff) = e_p(k,j,i)
     457             ENDDO
     458          ENDDO
     459!
     460!--    In RANS mode, wall function is used as boundary condition for TKE
     461       ELSE
     462!
     463!--       Use wall function within constant-flux layer
     464!--       Note, grid points listed in bc_h are not included in any calculations in RANS mode and
     465!--       are therefore not set here.
     466!
     467!--       Upward-facing surfaces
     468!--       Default surfaces
     469          DO  m = 1, surf_def_h(0)%ns
     470             i = surf_def_h(0)%i(m)
     471             j = surf_def_h(0)%j(m)
     472             k = surf_def_h(0)%k(m)
     473             e_p(k,j,i) = ( surf_def_h(0)%us(m) / c_0 )**2
     474          ENDDO
     475!
     476!--       Natural surfaces
     477          DO  m = 1, surf_lsm_h%ns
     478             i = surf_lsm_h%i(m)
     479             j = surf_lsm_h%j(m)
     480             k = surf_lsm_h%k(m)
     481             e_p(k,j,i) = ( surf_lsm_h%us(m) / c_0 )**2
     482          ENDDO
     483!
     484!--       Urban surfaces
     485          DO  m = 1, surf_usm_h%ns
     486             i = surf_usm_h%i(m)
     487             j = surf_usm_h%j(m)
     488             k = surf_usm_h%k(m)
     489             e_p(k,j,i) = ( surf_usm_h%us(m) / c_0 )**2
     490          ENDDO
     491!
     492!--       Vertical surfaces
     493          DO  l = 0, 3
     494!
     495!--          Default surfaces
     496             DO  m = 1, surf_def_v(l)%ns
     497                i = surf_def_v(l)%i(m)
     498                j = surf_def_v(l)%j(m)
     499                k = surf_def_v(l)%k(m)
     500                e_p(k,j,i) = ( surf_def_v(l)%us(m) / c_0 )**2
     501             ENDDO
     502!
     503!--          Natural surfaces
     504             DO  m = 1, surf_lsm_v(l)%ns
     505                i = surf_lsm_v(l)%i(m)
     506                j = surf_lsm_v(l)%j(m)
     507                k = surf_lsm_v(l)%k(m)
     508                e_p(k,j,i) = ( surf_lsm_v(l)%us(m) / c_0 )**2
     509             ENDDO
     510!
     511!--          Urban surfaces
     512             DO  m = 1, surf_usm_v(l)%ns
     513                i = surf_usm_v(l)%i(m)
     514                j = surf_usm_v(l)%j(m)
     515                k = surf_usm_v(l)%k(m)
     516                e_p(k,j,i) = ( surf_usm_v(l)%us(m) / c_0 )**2
     517             ENDDO
     518          ENDDO
     519       ENDIF
     520!
     521!--    Set Neumann boundary condition for TKE at model top. Do this also
     522!--    in case of a nested run.
     523       !$ACC KERNELS PRESENT(e_p)
     524       e_p(nzt+1,:,:) = e_p(nzt,:,:)
     525       !$ACC END KERNELS
     526!
     527!--    Nesting case: if parent operates in RANS mode and child in LES mode,
     528!--    no TKE is transfered. This case, set Neumann conditions at lateral and
     529!--    top child boundaries.
     530!--    If not ( both either in RANS or in LES mode ), TKE boundary condition
     531!--    is treated in the nesting.
     532       If ( child_domain )  THEN
     533          IF ( rans_mode_parent  .AND.  .NOT. rans_mode )  THEN
     534
     535             e_p(nzt+1,:,:) = e_p(nzt,:,:)
     536             IF ( bc_dirichlet_l )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
     537             IF ( bc_dirichlet_r )  e_p(:,:,nxr+1) = e_p(:,:,nxr)
     538             IF ( bc_dirichlet_s )  e_p(:,nys-1,:) = e_p(:,nys,:)
     539             IF ( bc_dirichlet_n )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
     540
     541          ENDIF
     542       ENDIF
     543!
     544!--    At in- and outflow boundaries also set Neumann boundary conditions
     545!--    for the SGS-TKE. An exception is made for the child domain if
     546!--    both parent and child operate in RANS mode. This case no
     547!--    lateral Neumann boundary conditions will be set but Dirichlet
     548!--    conditions will be set in the nesting.
     549       IF ( .NOT. child_domain  .AND.  .NOT. rans_mode_parent  .AND.           &
     550            .NOT. rans_mode )  THEN
     551          IF ( bc_dirichlet_s  .OR.  bc_radiation_s )  THEN
     552             e_p(:,nys-1,:) = e_p(:,nys,:)
     553             IF ( rans_tke_e )  diss_p(:,nys-1,:) = diss_p(:,nys,:)
     554          ENDIF
     555          IF ( bc_dirichlet_n  .OR.  bc_radiation_n )  THEN
     556             e_p(:,nyn+1,:) = e_p(:,nyn,:)
     557             IF ( rans_tke_e )  diss_p(:,nyn+1,:) = diss_p(:,nyn,:) 
     558          ENDIF
     559          IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
     560             e_p(:,:,nxl-1) = e_p(:,:,nxl)
     561             IF ( rans_tke_e )  diss_p(:,nyn+1,:) = diss_p(:,nyn,:) 
     562          ENDIF
     563          IF ( bc_dirichlet_r  .OR.  bc_radiation_r )  THEN
     564             e_p(:,:,nxr+1) = e_p(:,:,nxr)
     565             IF ( rans_tke_e )  diss_p(:,nyn+1,:) = diss_p(:,nyn,:)
     566          ENDIF
     567       ENDIF
     568    ENDIF
     569
     570!
     571!-- Boundary conditions for TKE dissipation rate in RANS mode.
     572    IF ( rans_tke_e )  THEN
     573!
     574!--    Use wall function within constant-flux layer
     575!--    Upward-facing surfaces
     576!--    Default surfaces
     577       DO  m = 1, surf_def_h(0)%ns
     578          i = surf_def_h(0)%i(m)
     579          j = surf_def_h(0)%j(m)
     580          k = surf_def_h(0)%k(m)
     581          diss_p(k,j,i) = surf_def_h(0)%us(m)**3          &
     582                        / ( kappa * surf_def_h(0)%z_mo(m) )
     583       ENDDO
     584!
     585!--    Natural surfaces
     586       DO  m = 1, surf_lsm_h%ns
     587          i = surf_lsm_h%i(m)
     588          j = surf_lsm_h%j(m)
     589          k = surf_lsm_h%k(m)
     590          diss_p(k,j,i) = surf_lsm_h%us(m)**3          &
     591                        / ( kappa * surf_lsm_h%z_mo(m) )
     592       ENDDO
     593!
     594!--    Urban surfaces
     595       DO  m = 1, surf_usm_h%ns
     596          i = surf_usm_h%i(m)
     597          j = surf_usm_h%j(m)
     598          k = surf_usm_h%k(m)
     599          diss_p(k,j,i) = surf_usm_h%us(m)**3          &
     600                        / ( kappa * surf_usm_h%z_mo(m) )
     601       ENDDO
     602!
     603!--    Vertical surfaces
     604       DO  l = 0, 3
     605!
     606!--       Default surfaces
     607          DO  m = 1, surf_def_v(l)%ns
     608             i = surf_def_v(l)%i(m)
     609             j = surf_def_v(l)%j(m)
     610             k = surf_def_v(l)%k(m)
     611             diss_p(k,j,i) = surf_def_v(l)%us(m)**3          &
     612                           / ( kappa * surf_def_v(l)%z_mo(m) )
     613          ENDDO
     614!
     615!--       Natural surfaces
     616          DO  m = 1, surf_lsm_v(l)%ns
     617             i = surf_lsm_v(l)%i(m)
     618             j = surf_lsm_v(l)%j(m)
     619             k = surf_lsm_v(l)%k(m)
     620             diss_p(k,j,i) = surf_lsm_v(l)%us(m)**3          &
     621                           / ( kappa * surf_lsm_v(l)%z_mo(m) )
     622          ENDDO
     623!
     624!--       Urban surfaces
     625          DO  m = 1, surf_usm_v(l)%ns
     626             i = surf_usm_v(l)%i(m)
     627             j = surf_usm_v(l)%j(m)
     628             k = surf_usm_v(l)%k(m)
     629             diss_p(k,j,i) = surf_usm_v(l)%us(m)**3          &
     630                           / ( kappa * surf_usm_v(l)%z_mo(m) )
     631          ENDDO
     632       ENDDO
     633!
     634!--    Limit change of diss to be between -90% and +100%. Also, set an absolute
     635!--    minimum value
     636       DO  i = nxl, nxr
     637          DO  j = nys, nyn
     638             DO  k = nzb, nzt+1
     639                diss_p(k,j,i) = MAX( MIN( diss_p(k,j,i),          &
     640                                          2.0_wp * diss(k,j,i) ), &
     641                                     0.1_wp * diss(k,j,i),        &
     642                                     0.0001_wp )
     643             ENDDO
     644          ENDDO
     645       ENDDO
     646
     647       
     648       diss_p(nzt+1,:,:) = diss_p(nzt,:,:)
     649     
     650    ENDIF
     651 END SUBROUTINE tcm_boundary_conds
     652 
    373653!------------------------------------------------------------------------------!
    374654! Description:
     
    9261206    USE model_1d_mod,                                                          &
    9271207        ONLY:  e1d, kh1d, km1d
    928 
    929     USE surface_mod,                                                           &
    930         ONLY:  get_topography_top_index_ji
    9311208
    9321209    IMPLICIT NONE
     
    17131990        ONLY:  phi_m
    17141991
    1715     USE surface_mod,                                                           &
    1716         ONLY :  surf_def_h, surf_lsm_h, surf_usm_h
    1717 
    17181992    IMPLICIT NONE
    17191993
     
    24182692    USE bulk_cloud_model_mod,                                                  &
    24192693        ONLY:  bulk_cloud_model
    2420 
    2421     USE surface_mod,                                                           &
    2422         ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,    &
    2423                 surf_usm_v
    24242694
    24252695    IMPLICIT NONE
     
    31223392        ONLY:  bulk_cloud_model
    31233393
    3124     USE surface_mod,                                                           &
    3125         ONLY :  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,    &
    3126                 surf_usm_v
    3127 
    31283394    IMPLICIT NONE
    31293395
     
    37674033        ONLY:  use_sgs_for_particles, wang_kernel
    37684034
    3769     USE surface_mod,                                                           &
    3770        ONLY :  bc_h
    3771 
    37724035    IMPLICIT NONE
    37734036
     
    39294192
    39304193!
    3931 !-- Neumann boundary condition for dissipation diss(nzb,:,:) = diss(nzb+1,:,:)
     4194!-- Neumann boundary condition for dissipation diss(nzb,:,:) = diss(nzb+1,:,:).
     4195!-- Note, bc cannot be set in tcm_boundary conditions as the dissipation
     4196!-- in LES mode is only a diagnostic quantity.
    39324197    IF ( .NOT. rans_tke_e .AND. ( use_sgs_for_particles  .OR.                  &
    39334198         wang_kernel  .OR.  collision_turbulence  ) )  THEN
     
    39734238    USE particle_attributes,                                                   &
    39744239        ONLY:  use_sgs_for_particles, wang_kernel
    3975 
    3976     USE surface_mod,                                                           &
    3977        ONLY :  bc_h
    39784240
    39794241    IMPLICIT NONE
     
    40624324!--    For each surface type determine start and end index (in case of elevated
    40634325!--    topography several up/downward facing surfaces may exist.
     4326!--    Note, bc cannot be set in tcm_boundary conditions as the dissipation
     4327!--    in LES mode is only a diagnostic quantity.
    40644328       surf_s = bc_h(0)%start_index(j,i)
    40654329       surf_e = bc_h(0)%end_index(j,i)
     
    43224586        ONLY:  phi_m
    43234587
    4324     USE surface_mod,                                                           &
    4325         ONLY :  bc_h, surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v,          &
    4326                 surf_usm_h, surf_usm_v
    4327 
    43284588    INTEGER(iwp) ::  i          !< loop index
    43294589    INTEGER(iwp) ::  j          !< loop index
  • palm/trunk/SOURCE/vertical_nesting_mod.f90

    r4101 r4102  
    2626! -----------------
    2727! $Id$
     28! - Slightly revise setting of boundary conditions at horizontal walls, use
     29!   data-structure offset index instead of pre-calculate it for each facing
     30!
     31! 4101 2019-07-17 15:14:26Z gronemeier
    2832! remove old_dt
    2933!
     
    27112715        INTEGER(iwp)                          ::  i
    27122716        INTEGER(iwp)                          ::  j
    2713         INTEGER(iwp)                          ::  k
    2714         INTEGER(iwp)                          ::  kb !< variable to set respective boundary value, depends on facing.
     2717        INTEGER(iwp)                          ::  k
    27152718        INTEGER(iwp)                          ::  l  !< running index boundary type, for up- and downward-facing walls
    27162719        INTEGER(iwp)                          ::  m  !< running index surface elements
     
    28602863            IF ( ibc_pt_b == 1 )  THEN
    28612864               DO  l = 0, 1
    2862 !
    2863 !--       Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    2864 !--       for downward-facing surfaces at topography bottom (k+1).
    2865                     kb = MERGE( -1, 1, l == 0 )
    2866                     DO  m = 1, bc_h(l)%ns
    2867                        i = bc_h(l)%i(m)     
    2868                        j = bc_h(l)%j(m)
    2869                        k = bc_h(l)%k(m)
    2870                        pt(k+kb,j,i) = pt(k,j,i)
    2871                     ENDDO
    2872                  ENDDO
     2865                  DO  m = 1, bc_h(l)%ns
     2866                     i = bc_h(l)%i(m)     
     2867                     j = bc_h(l)%j(m)
     2868                     k = bc_h(l)%k(m)
     2869                     pt(k+bc_h(l)%koff,j,i) = pt(k,j,i)
     2870                  ENDDO
     2871               ENDDO
    28732872            ENDIF
    28742873   
  • palm/trunk/TESTS/cases/rans_tkee/MONITORING/rans_tkee_rc

    r4101 r4102  
    1111
    1212 ******************************    --------------------------------------------
    13  * PALM 6.0  Rev: 4100M       *    atmosphere - run with 1D - prerun
     13 * PALM 6.0  Rev: 3915M       *    atmosphere - run with 1D - prerun
    1414 ******************************    --------------------------------------------
    1515
    1616 Date:               2019-07-17    Run:       rans_tkee__gfortran_default__4   
    17  Time:                 16:59:43    Run-No.:   00
     17 Time:                 17:23:23    Run-No.:   00
    1818 Run on host:        gfortran_d
    1919 Number of PEs:               4    Processor grid (x,y): (   2,   2) calculated
     
    220220RUN  ITER. HH:MM:SS.SS    DT(E)     UMAX     VMAX     WMAX     U*    W*      THETA*     Z_I     ENERG.   DISTENERG    DIVOLD     DIVNEW     UMAX(KJI)    VMAX(KJI)    WMAX(KJI)   ADVECX   ADVECY   MGCYC
    221221---------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------
    222   0      0 00:00:00.00   2.6700A   3.3592   0.8728   0.0000  0.127  0.00   0.000E+00      0.  0.442E+01  0.442E-02  0.000E+00  0.000E+00   20  29  29    6  29  29    0  29  29    0.000    0.000       0
    223   0      1 00:00:02.67   2.6600A   3.3803   1.5756   1.1290  0.151  0.00  -0.406E-02     10.  0.444E+01  0.437E-02  0.202E-03  0.798E-04   19   7  19    2  14  13    2  13   1    0.000    0.000       2
    224   0      2 00:00:05.33   0.2370D   3.3829   1.4756   1.2399  0.147  0.00  -0.468E-02     10.  0.444E+01  0.432E-02  0.137E-03  0.457E-04   19   6  21    2  14  13    2  13   1    0.000    0.000       2
    225   0      3 00:00:05.56   0.5360D   3.3841   1.5585   1.3626  0.145  0.00  -0.487E-02      0.  0.444E+01  0.422E-02  0.512E-04  0.118E-04   19   6  22    2  17   0    2  13   1    0.000    0.000       2
    226   0      4 00:00:06.10   0.7840D   3.3844   1.5478   1.3603  0.145  0.00  -0.497E-02      0.  0.444E+01  0.408E-02  0.412E-04  0.145E-04   19   5  23    2  17   0    2  13   1    0.000    0.000       2
    227   0      5 00:00:06.88   1.0200D   3.3843   1.5248   1.3393  0.144  0.00  -0.510E-02      0.  0.444E+01  0.401E-02  0.459E-04  0.160E-04   19   5  25    2  17   0    2  13   1    0.000    0.000       2
    228   0      6 00:00:07.90   1.2500D   3.3842   1.5006   1.3115  0.143  0.00  -0.528E-02      0.  0.444E+01  0.397E-02  0.521E-04  0.121E-04   19   3  27    2  17   0    2  13   1    0.000    0.000       2
    229   0      7 00:00:09.15   1.2700D   3.3842   1.4774   1.2804  0.141  0.00  -0.554E-02      0.  0.444E+01  0.393E-02  0.643E-04  0.175E-04   19   0   0    2  17   0    2  13   1    0.000    0.000       2
    230   0      8 00:00:10.42   1.3200D   3.3840   1.4655   1.2613  0.140  0.00  -0.558E-02      0.  0.444E+01  0.387E-02  0.621E-04  0.164E-04   19   2   0    2  17   0    2  13   1    0.000    0.000       2
    231   0      9 00:00:11.74   1.4300D   3.3835   1.4555   1.2678  0.139  0.00  -0.563E-02      0.  0.444E+01  0.380E-02  0.562E-04  0.155E-04   19   1   0    2  17   0    1  12   2    0.000    0.000       2
    232   0     10 00:00:13.17   1.5700D   3.3829   1.4445   1.2852  0.138  0.00  -0.566E-02      0.  0.444E+01  0.376E-02  0.568E-04  0.170E-04   20   2   0    2  17   0    1  12   2    0.000    0.000       2
    233   0     11 00:00:14.74   1.7600D   3.3824   1.4336   1.2960  0.137  0.00  -0.573E-02      0.  0.444E+01  0.371E-02  0.587E-04  0.172E-04   20   2   0    2  17   0    1  12   2    0.000    0.000       2
    234   0     12 00:00:16.50   2.0100D   3.3820   1.4223   1.2996  0.136  0.00  -0.590E-02      0.  0.444E+01  0.367E-02  0.625E-04  0.183E-04   20   2   0    2  17   0    1  12   2    0.000    0.000       2
    235   0     13 00:00:18.51   1.9500D   3.3816   1.4105   1.2953  0.135  0.00  -0.602E-02      0.  0.444E+01  0.362E-02  0.674E-04  0.202E-04   20   2   0    2  17   0    1  12   2    0.000    0.000       2
    236   0     14 00:00:20.46   1.8700D   3.3814   1.4124   1.2963  0.134  0.00  -0.644E-02      0.  0.444E+01  0.359E-02  0.635E-04  0.194E-04   19   6  24    2  17   0    1  12   2    0.000    0.000       2
    237   0     15 00:00:22.33   1.8000D   3.3814   1.4174   1.2972  0.133  0.00  -0.626E-02      0.  0.444E+01  0.356E-02  0.594E-04  0.185E-04   19   6  24    2  17   0    1  12   2    0.000    0.000       2
    238   0     16 00:00:24.13   1.7400D   3.3814   1.4235   1.2974  0.133  0.00  -0.622E-02      0.  0.444E+01  0.353E-02  0.562E-04  0.174E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
    239   0     17 00:00:25.87   1.6900D   3.3815   1.4301   1.2973  0.132  0.00  -0.630E-02      0.  0.444E+01  0.351E-02  0.536E-04  0.165E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
    240   0     18 00:00:27.56   1.6400D   3.3815   1.4371   1.2970  0.131  0.00  -0.639E-02      0.  0.444E+01  0.349E-02  0.513E-04  0.159E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
    241   0     19 00:00:29.20   1.6000D   3.3815   1.4448   1.2972  0.131  0.00  -0.659E-02      0.  0.444E+01  0.347E-02  0.491E-04  0.152E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
    242   0     20 00:00:30.80   1.5500D   3.3816   1.4526   1.2975  0.130  0.00  -0.661E-02      0.  0.444E+01  0.345E-02  0.471E-04  0.147E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
    243   0     21 00:00:32.35   1.4700D   3.3816   1.4611   1.2985  0.129  0.00  -0.654E-02      0.  0.444E+01  0.343E-02  0.451E-04  0.141E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
    244   0     22 00:00:33.82   1.4000D   3.3817   1.4711   1.3011  0.129  0.00  -0.649E-02      0.  0.444E+01  0.342E-02  0.426E-04  0.134E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
    245   0     23 00:00:35.22   1.3400D   3.3817   1.4808   1.3040  0.129  0.00  -0.646E-02      0.  0.444E+01  0.341E-02  0.403E-04  0.126E-04   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    246   0     24 00:00:36.56   1.2800D   3.3818   1.4899   1.3070  0.128  0.00  -0.645E-02      0.  0.444E+01  0.340E-02  0.383E-04  0.120E-04   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    247   0     25 00:00:37.84   1.2400D   3.3818   1.4988   1.3101  0.128  0.00  -0.647E-02      0.  0.444E+01  0.339E-02  0.363E-04  0.115E-04   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    248   0     26 00:00:39.08   1.1900D   3.3819   1.5066   1.3128  0.127  0.00  -0.650E-02      0.  0.444E+01  0.338E-02  0.349E-04  0.110E-04   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    249   0     27 00:00:40.27   1.1500D   3.3819   1.5146   1.3157  0.127  0.00  -0.654E-02      0.  0.444E+01  0.337E-02  0.333E-04  0.106E-04   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    250   0     28 00:00:41.42   1.1100D   3.3820   1.5219   1.3184  0.127  0.00  -0.659E-02      0.  0.444E+01  0.336E-02  0.319E-04  0.102E-04   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    251   0     29 00:00:42.53   1.0800D   3.3820   1.5289   1.3211  0.127  0.00  -0.663E-02      0.  0.444E+01  0.335E-02  0.306E-04  0.979E-05   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    252   0     30 00:00:43.61   1.0500D   3.3821   1.5352   1.3234  0.126  0.00  -0.667E-02      0.  0.444E+01  0.334E-02  0.296E-04  0.949E-05   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    253   0     31 00:00:44.66   1.0200D   3.3822   1.5412   1.3257  0.126  0.00  -0.667E-02      0.  0.444E+01  0.334E-02  0.286E-04  0.921E-05   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    254   0     32 00:00:45.68   0.9930D   3.3822   1.5470   1.3278  0.126  0.00  -0.664E-02      0.  0.444E+01  0.333E-02  0.276E-04  0.893E-05   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    255   0     33 00:00:46.68   0.9680D   3.3823   1.5525   1.3299  0.126  0.00  -0.661E-02      0.  0.444E+01  0.332E-02  0.267E-04  0.868E-05   19   8  23    2  17   0    1  12   2    0.000    0.000       2
    256   0     34 00:00:47.64   0.9450D   3.3823   1.5576   1.3318  0.126  0.00  -0.659E-02      0.  0.444E+01  0.332E-02  0.259E-04  0.844E-05   19   8  24    2  17   0    1  12   2    0.000    0.000       2
    257   0     35 00:00:48.59   0.9240D   3.3824   1.5625   1.3335  0.125  0.00  -0.657E-02      0.  0.444E+01  0.331E-02  0.252E-04  0.823E-05   19   8  24    2  17   0    1  12   2    0.000    0.000       2
    258   0     36 00:00:49.51   0.9040D   3.3825   1.5670   1.3351  0.125  0.00  -0.655E-02      0.  0.444E+01  0.331E-02  0.245E-04  0.803E-05   19   9  24    2  17   0    1  12   2    0.000    0.000       2
    259   0     37 00:00:50.42   0.8850D   3.3826   1.5714   1.3366  0.125  0.00  -0.654E-02      0.  0.444E+01  0.330E-02  0.239E-04  0.785E-05   19   9  24    2  17   0    1  12   2    0.000    0.000       2
     222  0      0 00:00:00.00   0.0200A   3.3592   0.8728   0.0000  0.127  0.00   0.000E+00      0.  0.442E+01  0.442E-02  0.000E+00  0.000E+00   20  29  29    6  29  29    0  29  29    0.000    0.000       0
     223  0      1 00:00:00.02   0.0400A   3.3802   1.7430  -1.2281  0.153  0.00  -0.390E-02     10.  0.444E+01  0.460E-02  0.155E-03  0.701E-04   19   7  19    2  14  13    2  26  29    0.000    0.000       2
     224  0      2 00:00:00.06   0.0800A   3.3832   1.7620  -1.3655  0.151  0.20  -0.421E-02     10.  0.444E+01  0.493E-02  0.874E-04  0.359E-04   19   6  21    2  14  13    2  26  29    0.000    0.000       2
     225  0      3 00:00:00.14   0.1600A   3.3844   1.7515   1.3704  0.150  0.00  -0.428E-02      0.  0.444E+01  0.496E-02  0.977E-04  0.323E-04   19   5  22    2  14  13    2  13   1    0.000    0.000       2
     226  0      4 00:00:00.30   0.3200A   3.3845   1.7361   1.3743  0.150  0.00  -0.429E-02      0.  0.444E+01  0.456E-02  0.521E-04  0.687E-05   19   5  24    2  14  13    2  13   1    0.000    0.000       2
     227  0      5 00:00:00.62   0.6400A   3.3838   1.7102   1.3741  0.149  0.00  -0.432E-02      0.  0.444E+01  0.437E-02  0.385E-04  0.278E-04   19   4  26    2  14  13    2  13   1    0.000    0.000       2
     228  0      6 00:00:01.26   1.2800A   3.3833   1.6639   1.3660  0.148  0.00  -0.437E-02      0.  0.444E+01  0.430E-02  0.704E-04  0.332E-04   19   1   0    2  14  13    2  13   1    0.000    0.000       2
     229  0      7 00:00:02.54   2.5600A   3.3827   1.5852   1.3342  0.147  0.39  -0.449E-02     30.  0.444E+01  0.420E-02  0.618E-04  0.165E-04   19   1   0    2  14  13    2  13   1    0.000    0.000       2
     230  0      8 00:00:05.09   2.6600A   3.3826   1.4669   1.2489  0.145  0.00  -0.484E-02     20.  0.444E+01  0.421E-02  0.144E-03  0.499E-04   20   3  31    2  14  13    2  13   1    0.000    0.000       2
     231  0      9 00:00:07.75   2.6200D   3.3825   1.4248   1.2091  0.142  0.00  -0.540E-02      0.  0.444E+01  0.399E-02  0.137E-03  0.424E-04   20   3   0    2  17   0    2  13   1    0.000    0.000       2
     232  0     10 00:00:10.37   2.6600A   3.3822   1.4058   1.2176  0.140  0.00  -0.536E-02      0.  0.444E+01  0.380E-02  0.971E-04  0.324E-04   20   2   0    2  17   0    1  12   2    0.000    0.000       2
     233  0     11 00:00:13.03   2.6600A   3.3818   1.3920   1.2409  0.138  0.00  -0.554E-02      0.  0.444E+01  0.372E-02  0.912E-04  0.361E-04   20   2   0    2  17   0    1  12   2    0.000    0.000       2
     234  0     12 00:00:15.69   2.6600A   3.3818   1.3841   1.2506  0.137  0.00  -0.573E-02      0.  0.444E+01  0.366E-02  0.867E-04  0.300E-04   19   6  24    2  17   0    1  12   2    0.000    0.000       2
     235  0     13 00:00:18.35   2.6600A   3.3820   1.3790   1.2520  0.135  0.00  -0.581E-02      0.  0.444E+01  0.362E-02  0.864E-04  0.282E-04   19   6  23    2  17   0    1  12   2    0.000    0.000       2
     236  0     14 00:00:21.01   2.6600A   3.3822   1.3757   1.2484  0.134  0.00  -0.617E-02      0.  0.444E+01  0.358E-02  0.862E-04  0.277E-04   19   6  23    2  17   0    1  12   2    0.000    0.000       2
     237  0     15 00:00:23.67   2.6600A   3.3824   1.3733   1.2423  0.133  0.00  -0.644E-02      0.  0.444E+01  0.353E-02  0.800E-04  0.249E-04   19   6  24    2  17   0    1  12   2    0.000    0.000       2
     238  0     16 00:00:26.33   2.6600A   3.3825   1.3716   1.2356  0.132  0.00  -0.633E-02      0.  0.444E+01  0.348E-02  0.755E-04  0.250E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
     239  0     17 00:00:29.00   2.6600A   3.3827   1.3703   1.2296  0.131  0.00  -0.648E-02      0.  0.444E+01  0.345E-02  0.734E-04  0.242E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
     240  0     18 00:00:31.66   2.6600A   3.3829   1.3692   1.2245  0.130  0.00  -0.650E-02      0.  0.444E+01  0.342E-02  0.719E-04  0.232E-04   19   7  23    2  17   0    1  12   2    0.000    0.000       2
     241  0     19 00:00:34.32   2.6600A   3.3830   1.3683   1.2206  0.129  0.00  -0.661E-02      0.  0.444E+01  0.339E-02  0.709E-04  0.228E-04   19   7  24    2  17   0    1  12   2    0.000    0.000       2
     242  0     20 00:00:36.98   2.6600A   3.3832   1.3675   1.2176  0.128  0.00  -0.648E-02      0.  0.444E+01  0.336E-02  0.692E-04  0.224E-04   19   7  24    2  17   0    1  12   2    0.000    0.000       2
     243  0     21 00:00:39.64   2.6600A   3.3834   1.3668   1.2153  0.128  0.00  -0.649E-02      0.  0.444E+01  0.334E-02  0.674E-04  0.221E-04   19   8  24    2  17   0    1  12   2    0.000    0.000       2
     244  0     22 00:00:42.29   2.6600A   3.3836   1.3662   1.2136  0.127  0.00  -0.658E-02      0.  0.444E+01  0.331E-02  0.661E-04  0.218E-04   19   8  24    2  17   0    1  12   2    0.000    0.000       2
     245  0     23 00:00:44.95   2.6600A   3.3837   1.3657   1.2122  0.127  0.00  -0.664E-02      0.  0.444E+01  0.329E-02  0.651E-04  0.215E-04   19   8  24    2  17   0    1  12   2    0.000    0.000       2
     246  0     24 00:00:47.61   2.6600A   3.3839   1.3652   1.2111  0.126  0.00  -0.661E-02      0.  0.444E+01  0.327E-02  0.642E-04  0.212E-04   19   8  24    2  17   0    1  12   2    0.000    0.000       2
     247  0     25 00:00:50.27   2.6600A   3.3841   1.3647   1.2101  0.126  0.00  -0.654E-02      0.  0.444E+01  0.325E-02  0.634E-04  0.210E-04   19   8  25    2  17   0    1  12   2    0.000    0.000       2
  • palm/trunk/TESTS/cases/urban_environment/MONITORING/urban_environment_rc

    r4085 r4102  
    11
    22 ******************************    --------------------------------------------
    3  * PALM 6.0  Rev: 4082M       *    atmosphere - run without 1D - prerun
     3 * PALM 6.0  Rev: 3915M       *    atmosphere - run without 1D - prerun
    44 ******************************    --------------------------------------------
    55
    6  Date:               2019-07-10    Run:       urban_environment__gfortran_defaul
    7  Time:                 17:38:31    Run-No.:   00
     6 Date:               2019-07-17    Run:       urban_environment__gfortran_defaul
     7 Time:                 17:22:42    Run-No.:   00
    88 Run on host:        gfortran_d
    99 Number of PEs:               4    Processor grid (x,y): (   2,   2) calculated
     
    356356  0      9 00:00:06.82   0.7580A  -2.3738  -1.3772   0.8161  0.080  0.25  -0.913E+00     18.  0.137E+01  0.146E-01  0.760E-03  0.196E-03   60  16   9   11  14   0   20  17   0    0.000    0.000       0
    357357  0     10 00:00:07.58   0.7580A  -2.3739  -1.3551   0.8090  0.079  0.25  -0.914E+00     18.  0.137E+01  0.149E-01  0.761E-03  0.196E-03   60  15   8   11  14   0   20  17   0    0.000    0.000       0
    358   0     11 00:00:08.33   0.7580A  -2.3739  -1.3370   0.8029  0.079  0.25  -0.915E+00     18.  0.137E+01  0.153E-01  0.764E-03  0.196E-03   60  15   7   11  14   0   20  17   0    0.000    0.000       0
     358  0     11 00:00:08.33   0.7580A  -2.3739  -1.3371   0.8029  0.079  0.25  -0.915E+00     18.  0.137E+01  0.153E-01  0.764E-03  0.196E-03   60  15   7   11  14   0   20  17   0    0.000    0.000       0
    359359  0     12 00:00:09.09   0.7580A  -2.3740  -1.3232   0.7984  0.078  0.26  -0.916E+00     18.  0.136E+01  0.156E-01  0.768E-03  0.195E-03   60  15   6   16  14   0   20  17   0    0.000    0.000       0
    360360  0     13 00:00:09.85   0.7580A  -2.3741  -1.3182   0.7956  0.078  0.26  -0.917E+00     18.  0.136E+01  0.160E-01  0.773E-03  0.195E-03   60  14   6   16  14   0   20  17   0    0.000    0.000       0
     
    362362  0     15 00:00:11.37   0.7580A  -2.3743  -1.2976   0.7936  0.077  0.26  -0.922E+00     18.  0.136E+01  0.168E-01  0.783E-03  0.194E-03   60  13   4   16  14   0   20  17   0    0.000    0.000       0
    363363  0     16 00:00:12.12   0.7580A  -2.3743  -1.2822   0.8042  0.076  0.27  -0.921E+00     18.  0.136E+01  0.172E-01  0.786E-03  0.193E-03   60  13   3   16  14   0   11  14  18    0.000    0.000       0
    364   0     17 00:00:12.88   0.7580A  -2.3744  -1.2633   0.8294  0.076  0.27  -0.919E+00     18.  0.136E+01  0.176E-01  0.788E-03  0.192E-03   60  12   2   16  14   0   11  14  18    0.000    0.000       0
    365   0     18 00:00:13.64   0.7580A  -2.3745  -1.2574   0.8604  0.076  0.27  -0.917E+00     18.  0.136E+01  0.180E-01  0.792E-03  0.191E-03   60  12   1   11  14   0   10  14  18    0.000    0.000       0
     364  0     17 00:00:12.88   0.7580A  -2.3744  -1.2633   0.8295  0.076  0.27  -0.919E+00     18.  0.136E+01  0.176E-01  0.788E-03  0.192E-03   60  12   2   16  14   0   11  14  18    0.000    0.000       0
     365  0     18 00:00:13.64   0.7580A  -2.3745  -1.2574   0.8605  0.076  0.27  -0.917E+00     18.  0.136E+01  0.180E-01  0.792E-03  0.191E-03   60  12   1   11  14   0   10  14  18    0.000    0.000       0
    366366  0     19 00:00:14.40   0.7580A  -2.3746  -1.2531   0.8936  0.075  0.27  -0.915E+00     18.  0.136E+01  0.184E-01  0.796E-03  0.190E-03   60  12   1   11  14   0   10  14  18    0.000    0.000       0
    367   0     20 00:00:15.16   0.7580A  -2.3746  -1.2498   0.9251  0.075  0.28  -0.914E+00     18.  0.136E+01  0.188E-01  0.799E-03  0.188E-03   60  12   0   11  14   0   10  14  18    0.000    0.000       0
     367  0     20 00:00:15.16   0.7580A  -2.3746  -1.2498   0.9251  0.075  0.28  -0.915E+00     18.  0.136E+01  0.188E-01  0.799E-03  0.188E-03   60  12   0   11  14   0   10  14  18    0.000    0.000       0
    368368  0     21 00:00:15.91   0.7580A  -2.3747  -1.2472   0.9531  0.075  0.28  -0.914E+00     18.  0.136E+01  0.192E-01  0.802E-03  0.187E-03   60  11  19   11  14   0   10  14  18    0.000    0.000       0
    369369  0     22 00:00:16.67   0.7580A  -2.3748  -1.2453   0.9762  0.074  0.40  -0.913E+00     40.  0.136E+01  0.196E-01  0.806E-03  0.185E-03   60  11  18   11  14   0   10  14  18    0.000    0.000       0
    370   0     23 00:00:17.43   0.7580A  -2.3749  -1.2439   0.9937  0.074  0.40  -0.912E+00     40.  0.136E+01  0.200E-01  0.809E-03  0.184E-03   60  10  17   11  14   0   10  14  18    0.000    0.000       0
    371   0     24 00:00:18.19   0.7580A  -2.3749  -1.2430   1.0055  0.074  0.40  -0.911E+00     40.  0.136E+01  0.205E-01  0.812E-03  0.182E-03   60  10  16   11  14   0   10  14  18    0.000    0.000       0
     370  0     23 00:00:17.43   0.7580A  -2.3749  -1.2439   0.9936  0.074  0.40  -0.912E+00     40.  0.136E+01  0.200E-01  0.809E-03  0.184E-03   60  10  17   11  14   0   10  14  18    0.000    0.000       0
     371  0     24 00:00:18.19   0.7580A  -2.3749  -1.2430   1.0055  0.074  0.40  -0.912E+00     40.  0.136E+01  0.205E-01  0.812E-03  0.182E-03   60  10  16   11  14   0   10  14  18    0.000    0.000       0
    372372  0     25 00:00:18.95   0.7580A  -2.3750  -1.2425   1.0123  0.073  0.41  -0.911E+00     40.  0.136E+01  0.209E-01  0.815E-03  0.181E-03   60  10  16   11  14   0   10  14  18    0.000    0.000       0
    373373  0     26 00:00:19.70   0.7580A  -2.3751  -1.2422   1.0163  0.073  0.41  -0.910E+00     40.  0.136E+01  0.213E-01  0.819E-03  0.180E-03   60  10  15   11  14   0   11  14  18    0.000    0.000       0
    374   0     27 00:00:20.46   0.7580A  -2.3752  -1.2420   1.0281  0.073  0.41  -0.910E+00     40.  0.136E+01  0.217E-01  0.823E-03  0.179E-03   60   9  14   11  14   0   11  14  18    0.000    0.000       0
    375   0     28 00:00:21.22   0.7580A  -2.3752  -1.2417   1.0345  0.073  0.42  -0.909E+00     40.  0.136E+01  0.222E-01  0.827E-03  0.178E-03   60   9  13   11  14   0   11  14  18    0.000    0.000       0
    376   0     29 00:00:21.98   0.7580A  -2.3753  -1.2416   1.0356  0.072  0.42  -0.909E+00     40.  0.136E+01  0.226E-01  0.831E-03  0.177E-03   60   9  12   11  14   0   11  14  18    0.000    0.000       0
    377   0     30 00:00:22.74   0.7580A  -2.3754  -1.2414   1.0322  0.072  0.42  -0.908E+00     40.  0.136E+01  0.230E-01  0.835E-03  0.176E-03   60   8  11   11  14   0   11  14  18    0.000    0.000       0
    378   0     31 00:00:23.49   0.7580A  -2.3755  -1.2414   1.0249  0.072  0.42  -0.908E+00     40.  0.136E+01  0.235E-01  0.839E-03  0.175E-03   60   8  10   11  14   0   11  14  18    0.000    0.000       0
    379   0     32 00:00:24.25   0.7580A  -2.3755  -1.2414   1.0153  0.072  0.43  -0.908E+00     40.  0.136E+01  0.239E-01  0.843E-03  0.174E-03   60   8  10   11  14   0   11  14  18    0.000    0.000       0
    380   0     33 00:00:25.01   0.7580A  -2.3756  -1.2413   1.0047  0.071  0.43  -0.908E+00     40.  0.136E+01  0.243E-01  0.848E-03  0.173E-03   60   7   9   11  14   0   11  14  18    0.000    0.000       0
     374  0     27 00:00:20.46   0.7580A  -2.3752  -1.2419   1.0281  0.073  0.41  -0.910E+00     40.  0.136E+01  0.217E-01  0.823E-03  0.179E-03   60   9  14   11  14   0   11  14  18    0.000    0.000       0
     375  0     28 00:00:21.22   0.7580A  -2.3752  -1.2417   1.0344  0.073  0.42  -0.909E+00     40.  0.136E+01  0.222E-01  0.827E-03  0.178E-03   60   9  13   11  14   0   11  14  18    0.000    0.000       0
     376  0     29 00:00:21.98   0.7580A  -2.3753  -1.2415   1.0356  0.072  0.42  -0.909E+00     40.  0.136E+01  0.226E-01  0.831E-03  0.177E-03   60   9  12   11  14   0   11  14  18    0.000    0.000       0
     377  0     30 00:00:22.74   0.7580A  -2.3754  -1.2414   1.0321  0.072  0.42  -0.909E+00     40.  0.136E+01  0.230E-01  0.835E-03  0.176E-03   60   8  11   11  14   0   11  14  18    0.000    0.000       0
     378  0     31 00:00:23.49   0.7580A  -2.3755  -1.2413   1.0248  0.072  0.42  -0.908E+00     40.  0.136E+01  0.234E-01  0.839E-03  0.175E-03   60   8  10   11  14   0   11  14  18    0.000    0.000       0
     379  0     32 00:00:24.25   0.7580A  -2.3755  -1.2413   1.0152  0.072  0.43  -0.908E+00     40.  0.136E+01  0.239E-01  0.843E-03  0.174E-03   60   8  10   11  14   0   11  14  18    0.000    0.000       0
     380  0     33 00:00:25.01   0.7580A  -2.3756  -1.2413   1.0046  0.071  0.43  -0.908E+00     40.  0.136E+01  0.243E-01  0.848E-03  0.173E-03   60   7   9   11  14   0   11  14  18    0.000    0.000       0
    381381  0     34 00:00:25.77   0.7580A  -2.3757  -1.2410   0.9942  0.071  0.43  -0.908E+00     40.  0.136E+01  0.247E-01  0.852E-03  0.173E-03   60   7   8   11  14   0   10  14  18    0.000    0.000       0
    382   0     35 00:00:26.53   0.7580A  -2.3758  -1.2403   1.0107  0.071  0.44  -0.908E+00     40.  0.136E+01  0.252E-01  0.856E-03  0.172E-03   60   7   7   11  14   0   11  14  17    0.000    0.000       0
    383   0     36 00:00:27.28   0.7580A  -2.3759  -1.2388   1.0283  0.071  0.44  -0.908E+00     40.  0.136E+01  0.256E-01  0.860E-03  0.171E-03   60   6   6   11  14   0   11  14  17    0.000    0.000       0
    384   0     37 00:00:28.04   0.7580A  -2.3759  -1.2364   1.0443  0.071  0.44  -0.908E+00     40.  0.136E+01  0.261E-01  0.863E-03  0.171E-03   60   6   5   11  14   0   11  14  17    0.000    0.000       0
    385   0     38 00:00:28.80   0.7580A  -2.3760  -1.2328   1.0568  0.071  0.45  -0.908E+00     40.  0.136E+01  0.265E-01  0.867E-03  0.170E-03   60   6   5   11  14   0   11  14  17    0.000    0.000       0
    386   0     39 00:00:29.56   0.7580A  -2.3761  -1.2280   1.0647  0.070  0.45  -0.908E+00     40.  0.136E+01  0.269E-01  0.871E-03  0.169E-03   60   5   3   11  14   0   11  14  17    0.000    0.000       0
    387   0     40 00:00:30.32   0.7580A  -2.3762  -1.2218   1.0674  0.070  0.45  -0.908E+00     40.  0.136E+01  0.274E-01  0.874E-03  0.169E-03   60   5   3   11  14   0   11  14  17    0.000    0.000       0
    388   0     41 00:00:31.07   0.7580A  -2.3762  -1.2204   1.0649  0.070  0.46  -0.908E+00     40.  0.136E+01  0.278E-01  0.878E-03  0.168E-03   60   5   2   11  13   0   11  14  17    0.000    0.000       0
    389   0     42 00:00:31.83   0.7570A  -2.3763  -1.2190   1.0762  0.070  0.46  -0.908E+00     40.  0.136E+01  0.283E-01  0.882E-03  0.168E-03   60   4   1   11  13   0   12  14  16    0.000    0.000       0
    390   0     43 00:00:32.59   0.7570A  -2.3764  -1.2156   1.0984  0.070  0.46  -0.909E+00     40.  0.136E+01  0.287E-01  0.885E-03  0.168E-03   60   4   0   11  13   0   12  14  16    0.000    0.000       0
    391   0     44 00:00:33.35   0.7570A  -2.3765  -1.2102   1.1184  0.070  0.47  -0.909E+00     40.  0.136E+01  0.292E-01  0.891E-03  0.168E-03   60   4  19   11  13   0   12  14  16    0.000    0.000       0
    392   0     45 00:00:34.10   0.7570A  -2.3765  -1.2026   1.1342  0.070  0.47  -0.910E+00     40.  0.136E+01  0.296E-01  0.896E-03  0.168E-03   60   3  18   11  13   0   12  14  16    0.000    0.000       0
    393   0     46 00:00:34.86   0.7570A  -2.3766  -1.1928   1.1438  0.070  0.47  -0.911E+00     40.  0.136E+01  0.301E-01  0.903E-03  0.168E-03   60   3  17   11  13   0   12  14  16    0.000    0.000       0
    394   0     47 00:00:35.62   0.7570A  -2.3767  -1.1810   1.1535  0.070  0.48  -0.911E+00     40.  0.136E+01  0.305E-01  0.909E-03  0.168E-03   60   3  17   11  13   0   13  14  16    0.000    0.000       0
    395   0     48 00:00:36.37   0.7570A  -2.3768  -1.1670   1.1658  0.070  0.48  -0.912E+00     40.  0.136E+01  0.310E-01  0.917E-03  0.168E-03   60   3  16   11  13   0   13  14  16    0.000    0.000       0
    396   0     49 00:00:37.13   0.7570A  -2.3768  -1.1510   1.1795  0.069  0.48  -0.913E+00     40.  0.136E+01  0.315E-01  0.925E-03  0.169E-03   60   2  15   11  13   0   16  14  17    0.000    0.000       0
    397   0     50 00:00:37.89   0.7570A  -2.3769  -1.1333   1.1993  0.069  0.49  -0.913E+00     40.  0.136E+01  0.320E-01  0.933E-03  0.169E-03   60   2  14   11  13   0   16  14  17    0.000    0.000       0
    398   0     51 00:00:38.64   0.7570A  -2.3770  -1.1139   1.2169  0.069  0.49  -0.912E+00     40.  0.136E+01  0.324E-01  0.942E-03  0.169E-03   60   2  13   11  13   0   17  14  17    0.000    0.000       0
    399   0     52 00:00:39.40   0.7570A  -2.3771  -1.0929   1.2376  0.069  0.49  -0.911E+00     40.  0.136E+01  0.329E-01  0.951E-03  0.170E-03   60   1  12   11  13   0   17  14  17    0.000    0.000       0
    400   0     53 00:00:40.16   0.7570A  -2.3771  -1.0756   1.2530  0.069  0.50  -0.911E+00     40.  0.136E+01  0.334E-01  0.960E-03  0.170E-03   60   1  11   13  14   0   17  14  17    0.000    0.000       0
    401   0     54 00:00:40.92   0.7570A  -2.3772  -1.0760   1.2625  0.069  0.50  -0.910E+00     40.  0.136E+01  0.339E-01  0.970E-03  0.171E-03   60   1  10   13  14   0   17  14  17    0.000    0.000       0
    402   0     55 00:00:41.67   0.7570A  -2.3773  -1.0746   1.2666  0.069  0.50  -0.910E+00     40.  0.136E+01  0.344E-01  0.980E-03  0.172E-03   60   1  10   13  14   0   17  14  17    0.000    0.000       0
    403   0     56 00:00:42.43   0.7570A  -2.3774  -1.0713   1.2691  0.069  0.51  -0.910E+00     40.  0.136E+01  0.349E-01  0.990E-03  0.172E-03   60   0   8   13  14   0   18  14  17    0.000    0.000       0
    404   0     57 00:00:43.19   0.7570A  -2.3774  -1.0664   1.2730  0.069  0.51  -0.909E+00     40.  0.136E+01  0.354E-01  0.100E-02  0.173E-03   60   0   8   13  14   0   18  14  17    0.000    0.000       0
    405   0     58 00:00:43.94   0.7570A  -2.3775  -1.0603   1.2697  0.069  0.55  -0.909E+00     48.  0.136E+01  0.358E-01  0.101E-02  0.173E-03   60   0   7   13  14   0   18  14  17    0.000    0.000       0
    406   0     59 00:00:44.70   0.7570A  -2.3776  -1.0550   1.2800  0.069  0.56  -0.909E+00     48.  0.136E+01  0.363E-01  0.102E-02  0.174E-03   60  19   6   14  14   0   19  14  18    0.000    0.000       0
    407   0     60 00:00:45.46   0.7570A  -2.3777  -1.0550   1.2932  0.069  0.56  -0.909E+00     48.  0.136E+01  0.368E-01  0.103E-02  0.175E-03   60  19   5   14  14   0   19  14  18    0.000    0.000       0
    408   0     61 00:00:46.21   0.7570A  -2.3777  -1.0561   1.2996  0.069  0.56  -0.909E+00     48.  0.136E+01  0.373E-01  0.104E-02  0.175E-03   60  19   5   14  14   0   19  14  18    0.000    0.000       0
    409   0     62 00:00:46.97   0.7570A  -2.3778  -1.0583   1.2988  0.069  0.53  -0.909E+00     40.  0.136E+01  0.378E-01  0.104E-02  0.176E-03   60  18   3   14  14   0   19  14  18    0.000    0.000       0
    410   0     63 00:00:47.73   0.7570A  -2.3779  -1.0611   1.2908  0.069  0.53  -0.910E+00     40.  0.136E+01  0.383E-01  0.105E-02  0.176E-03   60  18   3   14  14   0   19  14  18    0.000    0.000       0
    411   0     64 00:00:48.49   0.7570A  -2.3780  -1.0641   1.2764  0.069  0.53  -0.910E+00     40.  0.136E+01  0.388E-01  0.106E-02  0.177E-03   60  18   2   14  14   0   19  14  18    0.000    0.000       0
    412   0     65 00:00:49.24   0.7570A  -2.3780  -1.0667   1.2565  0.069  0.53  -0.912E+00     40.  0.136E+01  0.393E-01  0.107E-02  0.177E-03   60  18   1   15  14   0   19  14  18    0.000    0.000       0
    413   0     66 00:00:50.00   0.7570A  -2.3781  -1.0750   1.2323  0.069  0.53  -0.913E+00     40.  0.135E+01  0.398E-01  0.108E-02  0.178E-03   60  17   0   15  14   0   19  14  18    0.000    0.000       0
    414   0     67 00:00:50.76   0.7570A  -2.3782  -1.0801   1.2051  0.069  0.53  -0.916E+00     40.  0.135E+01  0.403E-01  0.109E-02  0.178E-03   60  17  19   15  14   0   19  14  18    0.000    0.000       0
    415   0     68 00:00:51.51   0.7570A  -2.3783  -1.0824   1.1761  0.069  0.53  -0.922E+00     40.  0.135E+01  0.408E-01  0.110E-02  0.178E-03   60  17  19   15  13   0   19  14  18    0.000    0.000       0
    416   0     69 00:00:52.27   0.7570A  -2.3783  -1.0899   1.1464  0.069  0.53  -0.933E+00     40.  0.135E+01  0.413E-01  0.110E-02  0.179E-03   60  16  17   15  13   0   19  14  18    0.000    0.000       0
    417   0     70 00:00:53.03   0.7570A  -2.3784  -1.0938   1.1212  0.069  0.53  -0.974E+00     40.  0.135E+01  0.418E-01  0.111E-02  0.179E-03   60  16  16   15  13   0    6  13   2    0.000    0.000       0
    418   0     71 00:00:53.78   0.7570A  -2.3785  -1.0940   1.1570  0.069  0.53  -0.104E+01     40.  0.135E+01  0.423E-01  0.112E-02  0.180E-03   60  16  16   15  13   0    6  13   2    0.000    0.000       0
    419   0     72 00:00:54.54   0.7570A  -2.3786  -1.0909   1.1893  0.069  0.53  -0.947E+00     40.  0.135E+01  0.427E-01  0.113E-02  0.180E-03   60  15  14   15  13   0    6  13   2    0.000    0.000       0
    420   0     73 00:00:55.30   0.7570A  -2.3786  -1.0854   1.2176  0.069  0.53  -0.935E+00     40.  0.135E+01  0.432E-01  0.114E-02  0.180E-03   60  15  14   15  13   0    6  13   2    0.000    0.000       0
    421   0     74 00:00:56.06   0.7570A  -2.3787  -1.0783   1.2412  0.069  0.54  -0.938E+00     40.  0.135E+01  0.437E-01  0.115E-02  0.181E-03   60  15  13   15  13   0    6  13   2    0.000    0.000       0
    422   0     75 00:00:56.81   0.7570A  -2.3788  -1.0704   1.2599  0.069  0.54  -0.949E+00     40.  0.135E+01  0.441E-01  0.115E-02  0.181E-03   60  14  12   15  13   0    6  13   2    0.000    0.000       0
    423   0     76 00:00:57.57   0.7570A  -2.3789  -1.0622   1.2927  0.069  0.54  -0.934E+00     40.  0.135E+01  0.446E-01  0.116E-02  0.182E-03   60  14  11   15  13   0    6  14   3    0.000    0.000       0
    424   0     77 00:00:58.33   0.7570A  -2.3789  -1.0538   1.3263  0.070  0.54  -0.920E+00     40.  0.135E+01  0.450E-01  0.117E-02  0.182E-03   60  14  10   15  13   0    6  14   3    0.000    0.000       0
    425   0     78 00:00:59.08   0.7570A  -2.3790  -1.0455   1.3553  0.070  0.54  -0.913E+00     40.  0.135E+01  0.454E-01  0.118E-02  0.182E-03   60  14  10   15  13   0    6  14   3    0.000    0.000       0
    426   0     79 00:00:59.84   0.7570A  -2.3791  -1.0371   1.3795  0.070  0.54  -0.909E+00     40.  0.135E+01  0.459E-01  0.119E-02  0.183E-03   60  13   8   15  13   0    6  14   3    0.000    0.000       0
    427   0     80 00:01:00.60   0.7570A  -2.3791  -1.0287   1.3988  0.070  0.54  -0.907E+00     40.  0.135E+01  0.463E-01  0.120E-02  0.183E-03   60  13   8   15  13   0    6  14   3    0.000    0.000       0
    428   0     81 00:01:01.35   0.7570A  -2.3792  -1.0357   1.4134  0.070  0.54  -0.906E+00     40.  0.135E+01  0.467E-01  0.121E-02  0.183E-03   60  13   7   18  13   0    6  14   3    0.000    0.000       0
    429   0     82 00:01:02.11   0.7570A  -2.3793  -1.0477   1.4235  0.070  0.54  -0.906E+00     40.  0.135E+01  0.470E-01  0.122E-02  0.183E-03   60  13   6   18  13   0    6  14   3    0.000    0.000       0
    430   0     83 00:01:02.87   0.7570A  -2.3794  -1.0575   1.4295  0.070  0.54  -0.911E+00     40.  0.135E+01  0.474E-01  0.122E-02  0.183E-03   60  12   5   18  13   0    6  14   3    0.000    0.000       0
    431   0     84 00:01:03.63   0.7560A  -2.3794  -1.0640   1.4321  0.070  0.55  -0.919E+00     40.  0.135E+01  0.478E-01  0.123E-02  0.183E-03   60  12   4   18  13   0    7  14   3    0.000    0.000       0
    432   0     85 00:01:04.38   0.7560A  -2.3795  -1.0669   1.4539  0.070  0.55  -0.908E+00     40.  0.135E+01  0.481E-01  0.123E-02  0.183E-03   60  12   4   18  13   0    7  14   3    0.000    0.000       0
    433   0     86 00:01:05.14   0.7560A  -2.3796  -1.0663   1.4705  0.070  0.55  -0.900E+00     40.  0.135E+01  0.485E-01  0.124E-02  0.183E-03   60  11   2   18  13   0    7  14   3    0.000    0.000       0
    434   0     87 00:01:05.89   0.7560A  -2.3797  -1.0652   1.4821  0.070  0.56  -0.895E+00     40.  0.135E+01  0.488E-01  0.125E-02  0.183E-03   60  11   1   17  12   0    7  14   3    0.000    0.000       0
    435   0     88 00:01:06.65   0.7560A  -2.3797  -1.0716   1.4893  0.070  0.56  -0.892E+00     40.  0.135E+01  0.491E-01  0.125E-02  0.183E-03   60  11   1   17  12   0    7  14   3    0.000    0.000       0
    436   0     89 00:01:07.41   0.7560A  -2.3798  -1.0748   1.4927  0.070  0.56  -0.890E+00     40.  0.135E+01  0.495E-01  0.126E-02  0.183E-03   60  10  19   17  12   0    7  14   3    0.000    0.000       0
    437   0     90 00:01:08.16   0.7560A  -2.3799  -1.0747   1.4929  0.070  0.57  -0.889E+00     40.  0.135E+01  0.498E-01  0.126E-02  0.183E-03   60  10  19   17  12   0    7  14   3    0.000    0.000       0
    438   0     91 00:01:08.92   0.7560A  -2.3800   1.0782   1.4907  0.071  0.57  -0.887E+00     40.  0.135E+01  0.500E-01  0.127E-02  0.184E-03   60  10  18    1   2  14    7  14   3    0.000    0.000       0
    439   0     92 00:01:09.67   0.7560A  -2.3800   1.0850   1.4868  0.071  0.60  -0.886E+00     46.  0.135E+01  0.503E-01  0.127E-02  0.184E-03   60   9  16    1   2  14    7  14   3    0.000    0.000       0
    440   0     93 00:01:10.43   0.7560A  -2.3801   1.0912   1.4817  0.071  0.61  -0.885E+00     46.  0.135E+01  0.506E-01  0.128E-02  0.184E-03   60   9  16    1   2  14    7  14   3    0.000    0.000       0
     382  0     35 00:00:26.53   0.7580A  -2.3758  -1.2402   1.0107  0.071  0.44  -0.908E+00     40.  0.136E+01  0.252E-01  0.856E-03  0.172E-03   60   7   7   11  14   0   11  14  17    0.000    0.000       0
     383  0     36 00:00:27.28   0.7580A  -2.3759  -1.2387   1.0283  0.071  0.44  -0.908E+00     40.  0.136E+01  0.256E-01  0.860E-03  0.171E-03   60   6   6   11  14   0   11  14  17    0.000    0.000       0
     384  0     37 00:00:28.04   0.7580A  -2.3759  -1.2363   1.0443  0.071  0.44  -0.908E+00     40.  0.136E+01  0.261E-01  0.863E-03  0.171E-03   60   6   5   11  14   0   11  14  17    0.000    0.000       0
     385  0     38 00:00:28.80   0.7580A  -2.3760  -1.2327   1.0568  0.071  0.45  -0.908E+00     40.  0.136E+01  0.265E-01  0.866E-03  0.170E-03   60   6   5   11  14   0   11  14  17    0.000    0.000       0
     386  0     39 00:00:29.56   0.7580A  -2.3761  -1.2279   1.0647  0.070  0.45  -0.908E+00     40.  0.136E+01  0.269E-01  0.870E-03  0.169E-03   60   5   3   11  14   0   11  14  17    0.000    0.000       0
     387  0     40 00:00:30.32   0.7580A  -2.3762  -1.2217   1.0673  0.070  0.45  -0.908E+00     40.  0.136E+01  0.274E-01  0.874E-03  0.169E-03   60   5   3   11  14   0   11  14  17    0.000    0.000       0
     388  0     41 00:00:31.07   0.7580A  -2.3762  -1.2203   1.0648  0.070  0.46  -0.908E+00     40.  0.136E+01  0.278E-01  0.878E-03  0.168E-03   60   5   2   11  13   0   11  14  17    0.000    0.000       0
     389  0     42 00:00:31.83   0.7570A  -2.3763  -1.2189   1.0761  0.070  0.46  -0.908E+00     40.  0.136E+01  0.283E-01  0.882E-03  0.168E-03   60   4   1   11  13   0   12  14  16    0.000    0.000       0
     390  0     43 00:00:32.59   0.7570A  -2.3764  -1.2156   1.0983  0.070  0.46  -0.909E+00     40.  0.136E+01  0.287E-01  0.885E-03  0.168E-03   60   4   0   11  13   0   12  14  16    0.000    0.000       0
     391  0     44 00:00:33.35   0.7570A  -2.3765  -1.2101   1.1183  0.070  0.47  -0.909E+00     40.  0.136E+01  0.292E-01  0.890E-03  0.168E-03   60   4  19   11  13   0   12  14  16    0.000    0.000       0
     392  0     45 00:00:34.10   0.7570A  -2.3765  -1.2025   1.1340  0.070  0.47  -0.910E+00     40.  0.136E+01  0.296E-01  0.896E-03  0.168E-03   60   3  18   11  13   0   12  14  16    0.000    0.000       0
     393  0     46 00:00:34.86   0.7570A  -2.3766  -1.1928   1.1437  0.070  0.47  -0.911E+00     40.  0.136E+01  0.301E-01  0.902E-03  0.168E-03   60   3  17   11  13   0   12  14  16    0.000    0.000       0
     394  0     47 00:00:35.62   0.7570A  -2.3767  -1.1809   1.1533  0.070  0.48  -0.912E+00     40.  0.136E+01  0.305E-01  0.909E-03  0.168E-03   60   3  17   11  13   0   13  14  16    0.000    0.000       0
     395  0     48 00:00:36.37   0.7570A  -2.3768  -1.1669   1.1656  0.069  0.48  -0.913E+00     40.  0.136E+01  0.310E-01  0.916E-03  0.168E-03   60   3  16   11  13   0   13  14  16    0.000    0.000       0
     396  0     49 00:00:37.13   0.7570A  -2.3768  -1.1509   1.1794  0.069  0.48  -0.913E+00     40.  0.136E+01  0.315E-01  0.924E-03  0.169E-03   60   2  15   11  13   0   16  14  17    0.000    0.000       0
     397  0     50 00:00:37.89   0.7570A  -2.3769  -1.1332   1.1992  0.069  0.49  -0.913E+00     40.  0.136E+01  0.319E-01  0.933E-03  0.169E-03   60   2  14   11  13   0   16  14  17    0.000    0.000       0
     398  0     51 00:00:38.64   0.7570A  -2.3770  -1.1138   1.2167  0.069  0.49  -0.912E+00     40.  0.136E+01  0.324E-01  0.942E-03  0.169E-03   60   2  13   11  13   0   17  14  17    0.000    0.000       0
     399  0     52 00:00:39.40   0.7570A  -2.3771  -1.0927   1.2374  0.069  0.49  -0.911E+00     40.  0.136E+01  0.329E-01  0.951E-03  0.170E-03   60   1  12   11  13   0   17  14  17    0.000    0.000       0
     400  0     53 00:00:40.16   0.7570A  -2.3771  -1.0756   1.2528  0.069  0.50  -0.911E+00     40.  0.136E+01  0.334E-01  0.960E-03  0.170E-03   60   1  11   13  14   0   17  14  17    0.000    0.000       0
     401  0     54 00:00:40.92   0.7570A  -2.3772  -1.0760   1.2624  0.069  0.50  -0.910E+00     40.  0.136E+01  0.339E-01  0.970E-03  0.171E-03   60   1  10   13  14   0   17  14  17    0.000    0.000       0
     402  0     55 00:00:41.67   0.7570A  -2.3773  -1.0746   1.2665  0.069  0.50  -0.910E+00     40.  0.136E+01  0.344E-01  0.980E-03  0.171E-03   60   1  10   13  14   0   17  14  17    0.000    0.000       0
     403  0     56 00:00:42.43   0.7570A  -2.3774  -1.0713   1.2687  0.069  0.51  -0.910E+00     40.  0.136E+01  0.348E-01  0.990E-03  0.172E-03   60   0   8   13  14   0   18  14  17    0.000    0.000       0
     404  0     57 00:00:43.19   0.7570A  -2.3774  -1.0664   1.2727  0.069  0.51  -0.909E+00     40.  0.136E+01  0.353E-01  0.100E-02  0.173E-03   60   0   8   13  14   0   18  14  17    0.000    0.000       0
     405  0     58 00:00:43.94   0.7570A  -2.3775  -1.0603   1.2694  0.069  0.55  -0.909E+00     48.  0.136E+01  0.358E-01  0.101E-02  0.173E-03   60   0   7   13  14   0   18  14  17    0.000    0.000       0
     406  0     59 00:00:44.70   0.7570A  -2.3776  -1.0549   1.2782  0.069  0.56  -0.909E+00     48.  0.136E+01  0.363E-01  0.102E-02  0.174E-03   60  19   6   14  14   0   19  14  18    0.000    0.000       0
     407  0     60 00:00:45.46   0.7570A  -2.3777  -1.0549   1.2915  0.069  0.56  -0.910E+00     48.  0.136E+01  0.368E-01  0.103E-02  0.175E-03   60  19   5   14  14   0   19  14  18    0.000    0.000       0
     408  0     61 00:00:46.21   0.7570A  -2.3777  -1.0560   1.2979  0.069  0.56  -0.909E+00     48.  0.136E+01  0.373E-01  0.104E-02  0.175E-03   60  19   5   14  14   0   19  14  18    0.000    0.000       0
     409  0     62 00:00:46.97   0.7570A  -2.3778  -1.0582   1.2972  0.069  0.53  -0.909E+00     40.  0.136E+01  0.378E-01  0.104E-02  0.176E-03   60  18   3   14  14   0   19  14  18    0.000    0.000       0
     410  0     63 00:00:47.73   0.7570A  -2.3779  -1.0611   1.2893  0.069  0.53  -0.910E+00     40.  0.136E+01  0.383E-01  0.105E-02  0.176E-03   60  18   3   14  14   0   19  14  18    0.000    0.000       0
     411  0     64 00:00:48.49   0.7570A  -2.3780  -1.0641   1.2750  0.069  0.53  -0.910E+00     40.  0.136E+01  0.388E-01  0.106E-02  0.177E-03   60  18   2   14  14   0   19  14  18    0.000    0.000       0
     412  0     65 00:00:49.24   0.7570A  -2.3780  -1.0666   1.2552  0.069  0.53  -0.912E+00     40.  0.136E+01  0.393E-01  0.107E-02  0.177E-03   60  18   1   15  14   0   19  14  18    0.000    0.000       0
     413  0     66 00:00:50.00   0.7570A  -2.3781  -1.0749   1.2310  0.069  0.53  -0.913E+00     40.  0.135E+01  0.398E-01  0.108E-02  0.178E-03   60  17   0   15  14   0   19  14  18    0.000    0.000       0
     414  0     67 00:00:50.76   0.7570A  -2.3782  -1.0801   1.2039  0.069  0.53  -0.916E+00     40.  0.135E+01  0.403E-01  0.109E-02  0.178E-03   60  17  19   15  14   0   19  14  18    0.000    0.000       0
     415  0     68 00:00:51.51   0.7570A  -2.3783  -1.0823   1.1751  0.069  0.53  -0.921E+00     40.  0.135E+01  0.408E-01  0.110E-02  0.178E-03   60  17  19   15  13   0   19  14  18    0.000    0.000       0
     416  0     69 00:00:52.27   0.7570A  -2.3783  -1.0898   1.1455  0.069  0.53  -0.932E+00     40.  0.135E+01  0.413E-01  0.110E-02  0.179E-03   60  16  17   15  13   0   19  14  18    0.000    0.000       0
     417  0     70 00:00:53.03   0.7570A  -2.3784  -1.0937   1.1201  0.069  0.53  -0.969E+00     40.  0.135E+01  0.418E-01  0.111E-02  0.179E-03   60  16  16   15  13   0    6  13   2    0.000    0.000       0
     418  0     71 00:00:53.78   0.7570A  -2.3785  -1.0939   1.1556  0.069  0.53  -0.106E+01     40.  0.135E+01  0.423E-01  0.112E-02  0.180E-03   60  16  16   15  13   0    6  13   2    0.000    0.000       0
     419  0     72 00:00:54.54   0.7570A  -2.3786  -1.0908   1.1876  0.069  0.53  -0.949E+00     40.  0.135E+01  0.427E-01  0.113E-02  0.180E-03   60  15  14   15  13   0    6  13   2    0.000    0.000       0
     420  0     73 00:00:55.30   0.7570A  -2.3786  -1.0853   1.2156  0.069  0.54  -0.935E+00     40.  0.135E+01  0.432E-01  0.114E-02  0.180E-03   60  15  14   15  13   0    6  13   2    0.000    0.000       0
     421  0     74 00:00:56.06   0.7570A  -2.3787  -1.0782   1.2390  0.069  0.54  -0.938E+00     40.  0.135E+01  0.437E-01  0.114E-02  0.181E-03   60  15  13   15  13   0    6  13   2    0.000    0.000       0
     422  0     75 00:00:56.81   0.7570A  -2.3788  -1.0703   1.2575  0.069  0.54  -0.949E+00     40.  0.135E+01  0.441E-01  0.115E-02  0.181E-03   60  14  12   15  13   0    6  13   2    0.000    0.000       0
     423  0     76 00:00:57.57   0.7570A  -2.3789  -1.0620   1.2906  0.069  0.54  -0.934E+00     40.  0.135E+01  0.446E-01  0.116E-02  0.182E-03   60  14  11   15  13   0    6  14   3    0.000    0.000       0
     424  0     77 00:00:58.33   0.7570A  -2.3789  -1.0537   1.3239  0.070  0.54  -0.920E+00     40.  0.135E+01  0.450E-01  0.117E-02  0.182E-03   60  14  10   15  13   0    6  14   3    0.000    0.000       0
     425  0     78 00:00:59.08   0.7570A  -2.3790  -1.0453   1.3527  0.070  0.54  -0.913E+00     40.  0.135E+01  0.454E-01  0.118E-02  0.182E-03   60  14  10   15  13   0    6  14   3    0.000    0.000       0
     426  0     79 00:00:59.84   0.7570A  -2.3791  -1.0370   1.3767  0.070  0.54  -0.909E+00     40.  0.135E+01  0.458E-01  0.119E-02  0.183E-03   60  13   8   15  13   0    6  14   3    0.000    0.000       0
     427  0     80 00:01:00.60   0.7570A  -2.3791  -1.0286   1.3959  0.070  0.54  -0.907E+00     40.  0.135E+01  0.462E-01  0.120E-02  0.183E-03   60  13   8   15  13   0    6  14   3    0.000    0.000       0
     428  0     81 00:01:01.35   0.7570A  -2.3792  -1.0356   1.4104  0.070  0.54  -0.906E+00     40.  0.135E+01  0.466E-01  0.121E-02  0.183E-03   60  13   7   18  13   0    6  14   3    0.000    0.000       0
     429  0     82 00:01:02.11   0.7570A  -2.3793  -1.0476   1.4206  0.070  0.54  -0.906E+00     40.  0.135E+01  0.470E-01  0.121E-02  0.183E-03   60  13   6   18  13   0    6  14   3    0.000    0.000       0
     430  0     83 00:01:02.87   0.7570A  -2.3794  -1.0574   1.4267  0.070  0.55  -0.911E+00     40.  0.135E+01  0.474E-01  0.122E-02  0.183E-03   60  12   5   18  13   0    6  14   3    0.000    0.000       0
     431  0     84 00:01:03.63   0.7560A  -2.3794  -1.0639   1.4300  0.070  0.55  -0.919E+00     40.  0.135E+01  0.478E-01  0.123E-02  0.183E-03   60  12   4   18  13   0    7  14   3    0.000    0.000       0
     432  0     85 00:01:04.38   0.7560A  -2.3795  -1.0669   1.4516  0.070  0.55  -0.909E+00     40.  0.135E+01  0.481E-01  0.123E-02  0.183E-03   60  12   4   18  13   0    7  14   3    0.000    0.000       0
     433  0     86 00:01:05.14   0.7560A  -2.3796  -1.0663   1.4680  0.070  0.55  -0.900E+00     40.  0.135E+01  0.485E-01  0.124E-02  0.183E-03   60  11   2   18  13   0    7  14   3    0.000    0.000       0
     434  0     87 00:01:05.89   0.7560A  -2.3797  -1.0650   1.4796  0.070  0.56  -0.895E+00     40.  0.135E+01  0.488E-01  0.124E-02  0.183E-03   60  11   1   17  12   0    7  14   3    0.000    0.000       0
     435  0     88 00:01:06.65   0.7560A  -2.3797  -1.0715   1.4868  0.070  0.56  -0.892E+00     40.  0.135E+01  0.491E-01  0.125E-02  0.183E-03   60  11   1   17  12   0    7  14   3    0.000    0.000       0
     436  0     89 00:01:07.41   0.7560A  -2.3798  -1.0746   1.4901  0.070  0.56  -0.890E+00     40.  0.135E+01  0.494E-01  0.126E-02  0.183E-03   60  10  19   17  12   0    7  14   3    0.000    0.000       0
     437  0     90 00:01:08.16   0.7560A  -2.3799  -1.0745   1.4904  0.070  0.57  -0.889E+00     40.  0.135E+01  0.497E-01  0.126E-02  0.183E-03   60  10  19   17  12   0    7  14   3    0.000    0.000       0
     438  0     91 00:01:08.92   0.7560A  -2.3800   1.0764   1.4883  0.070  0.57  -0.887E+00     40.  0.135E+01  0.500E-01  0.127E-02  0.184E-03   60  10  18    1   2  14    7  14   3    0.000    0.000       0
     439  0     92 00:01:09.67   0.7560A  -2.3800   1.0833   1.4844  0.071  0.60  -0.886E+00     46.  0.135E+01  0.503E-01  0.127E-02  0.184E-03   60   9  16    1   2  14    7  14   3    0.000    0.000       0
     440  0     93 00:01:10.43   0.7560A  -2.3801   1.0895   1.4794  0.071  0.61  -0.885E+00     46.  0.135E+01  0.506E-01  0.128E-02  0.184E-03   60   9  16    1   2  14    7  14   3    0.000    0.000       0
  • palm/trunk/TESTS/cases/urban_environment_restart/MONITORING/urban_environment_restart_rc

    r4085 r4102  
    77RUN  ITER. HH:MM:SS.SS    DT(E)     UMAX     VMAX     WMAX     U*    W*      THETA*     Z_I     ENERG.   DISTENERG    DIVOLD     DIVNEW     UMAX(KJI)    VMAX(KJI)    WMAX(KJI)   ADVECX   ADVECY   MGCYC
    88---------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------
    9   1     93 00:01:10.43   0.7560A  -2.3801   1.0912   1.4817  0.071  0.11  -0.885E+00     46.  0.135E+01  0.506E-01  0.000E+00  0.000E+00   60   9  16    1   2  14    7  14   3    0.000    0.000       0
    10   1     94 00:01:11.19   0.7560A  -2.3802   1.0968   1.4761  0.071  0.61  -0.884E+00     46.  0.135E+01  0.509E-01  0.128E-02  0.185E-03   60   9  15    1   2  14    7  14   3    0.000    0.000       0
    11   1     95 00:01:11.94   0.7560A  -2.3803   1.1019   1.4704  0.071  0.62  -0.883E+00     46.  0.135E+01  0.511E-01  0.129E-02  0.185E-03   60   8  13    1   2  14    7  14   3    0.000    0.000       0
    12   1     96 00:01:12.70   0.7560A  -2.3803   1.1066   1.4650  0.071  0.62  -0.883E+00     46.  0.135E+01  0.514E-01  0.129E-02  0.185E-03   60   8  13    1   2  14    7  14   3    0.000    0.000       0
    13   1     97 00:01:13.45   0.7560A  -2.3804   1.1108   1.4601  0.071  0.63  -0.882E+00     46.  0.135E+01  0.516E-01  0.130E-02  0.186E-03   60   8  12    1   2  14    7  14   3    0.000    0.000       0
    14   1     98 00:01:14.21   0.7560A  -2.3805   1.1146   1.4557  0.071  0.63  -0.882E+00     46.  0.135E+01  0.519E-01  0.130E-02  0.186E-03   60   8  12    1   2  14    7  14   3    0.000    0.000       0
    15   1     99 00:01:14.97   0.7560A  -2.3806   1.1180   1.4520  0.071  0.63  -0.881E+00     46.  0.135E+01  0.521E-01  0.131E-02  0.187E-03   60   7  10    1   2  14    7  14   3    0.000    0.000       0
    16   1    100 00:01:15.72   0.7560A  -2.3806   1.1209   1.4490  0.071  0.64  -0.881E+00     46.  0.135E+01  0.524E-01  0.131E-02  0.187E-03   60   7  10    1   2  14    7  14   3    0.000    0.000       0
    17   1    101 00:01:16.48   0.7560A  -2.3807   1.1235   1.4468  0.071  0.65  -0.881E+00     48.  0.135E+01  0.526E-01  0.132E-02  0.188E-03   60   7   9    1   2  14    7  14   3    0.000    0.000       0
    18   1    102 00:01:17.23   0.7560A  -2.3808  -1.1326   1.4453  0.071  0.66  -0.881E+00     48.  0.135E+01  0.528E-01  0.132E-02  0.188E-03   60   6   7   13  13   0    7  14   3    0.000    0.000       0
    19   1    103 00:01:17.99   0.7560A  -2.3809  -1.1492   1.4445  0.071  0.66  -0.882E+00     48.  0.135E+01  0.530E-01  0.133E-02  0.189E-03   60   6   7   14  14   0    7  14   3    0.000    0.000       0
    20   1    104 00:01:18.75   0.7560A  -2.3809  -1.1669   1.4444  0.071  0.66  -0.883E+00     48.  0.135E+01  0.532E-01  0.134E-02  0.190E-03   60   6   6   14  14   0    7  14   3    0.000    0.000       0
    21   1    105 00:01:19.50   0.7560A  -2.3810  -1.1848   1.4447  0.071  0.68  -0.885E+00     50.  0.135E+01  0.534E-01  0.134E-02  0.190E-03   60   6   6   14  14   0    7  14   3    0.000    0.000       0
    22   1    106 00:01:20.26   0.7560A  -2.3811  -1.2038   1.4454  0.071  0.68  -0.890E+00     50.  0.135E+01  0.536E-01  0.135E-02  0.191E-03   60   5   4   14  13   0    7  14   3    0.000    0.000       0
    23   1    107 00:01:21.01   0.7560A  -2.3811  -1.2249   1.4465  0.071  0.68  -0.902E+00     50.  0.135E+01  0.538E-01  0.136E-02  0.192E-03   60   5   4   14  13   0    7  14   3    0.000    0.000       0
    24   1    108 00:01:21.77   0.7560A  -2.3812  -1.2464   1.4477  0.071  0.69  -0.890E+00     50.  0.135E+01  0.540E-01  0.136E-02  0.193E-03   60   5   3   14  13   0    7  14   3    0.000    0.000       0
    25   1    109 00:01:22.53   0.7560A  -2.3813  -1.2675   1.4489  0.071  0.69  -0.885E+00     50.  0.135E+01  0.542E-01  0.137E-02  0.193E-03   60   4   1   14  13   0    7  14   3    0.000    0.000       0
    26   1    110 00:01:23.28   0.7560A  -2.3814  -1.2873   1.4501  0.071  0.69  -0.884E+00     50.  0.134E+01  0.543E-01  0.138E-02  0.194E-03   60   4   1   14  13   0    7  14   3    0.000    0.000       0
    27   1    111 00:01:24.04   0.7560A  -2.3814  -1.3050   1.4512  0.071  0.69  -0.883E+00     50.  0.134E+01  0.545E-01  0.139E-02  0.194E-03   60   4   0   14  13   0    7  14   3    0.000    0.000       0
    28   1    112 00:01:24.79   0.7560A  -2.3815  -1.3196   1.4522  0.071  0.70  -0.883E+00     50.  0.134E+01  0.547E-01  0.139E-02  0.194E-03   60   3  19   14  13   0    7  14   3    0.000    0.000       0
    29   1    113 00:01:25.55   0.7560A  -2.3816  -1.3309   1.4530  0.071  0.70  -0.883E+00     50.  0.134E+01  0.548E-01  0.140E-02  0.194E-03   60   3  18   14  13   0    7  14   3    0.000    0.000       0
    30   1    114 00:01:26.31   0.7560A  -2.3817  -1.3388   1.4537  0.071  0.71  -0.884E+00     52.  0.134E+01  0.550E-01  0.141E-02  0.194E-03   60   3  17   14  13   0    7  14   3    0.000    0.000       0
    31   1    115 00:01:27.06   0.7560A  -2.3817  -1.3431   1.4543  0.071  0.71  -0.884E+00     52.  0.134E+01  0.551E-01  0.142E-02  0.194E-03   60   2  16   14  13   0    7  14   3    0.000    0.000       0
    32   1    116 00:01:27.82   0.7560A  -2.3818  -1.3439   1.4564  0.071  0.71  -0.885E+00     52.  0.134E+01  0.552E-01  0.142E-02  0.194E-03   60   2  15   14  13   0    8  14   3    0.000    0.000       0
    33   1    117 00:01:28.57   0.7560A  -2.3819  -1.3412   1.4598  0.071  0.71  -0.886E+00     52.  0.134E+01  0.553E-01  0.143E-02  0.193E-03   60   2  14   14  13   0    8  14   3    0.000    0.000       0
    34   1    118 00:01:29.33   0.7560A  -2.3819  -1.3350   1.4627  0.071  0.71  -0.887E+00     52.  0.134E+01  0.554E-01  0.143E-02  0.192E-03   60   1  13   14  13   0    8  14   3    0.000    0.000       0
    35   1    119 00:01:30.09   0.7560A  -2.3820  -1.3253   1.4650  0.071  0.64  -0.887E+00     40.  0.134E+01  0.555E-01  0.144E-02  0.191E-03   60   1  12   14  13   0    8  14   3    0.000    0.000       0
    36   1    120 00:01:30.84   0.7560A  -2.3821  -1.3125   1.4668  0.071  0.64  -0.887E+00     40.  0.134E+01  0.556E-01  0.145E-02  0.190E-03   60   1  12   14  13   0    8  14   3    0.000    0.000       0
    37   1    121 00:01:31.60   0.7560A  -2.3822  -1.2967   1.4680  0.071  0.64  -0.888E+00     40.  0.134E+01  0.557E-01  0.146E-02  0.189E-03   60   0  10   14  13   0    8  14   3    0.000    0.000       0
    38   1    122 00:01:32.35   0.7560A  -2.3822  -1.2830   1.4685  0.071  0.64  -0.889E+00     40.  0.134E+01  0.558E-01  0.146E-02  0.187E-03   60   0   9   13  13   0    8  14   3    0.000    0.000       0
    39   1    123 00:01:33.11   0.7560A  -2.3823  -1.2692   1.4685  0.071  0.63  -0.890E+00     40.  0.134E+01  0.558E-01  0.147E-02  0.186E-03   60   0   9   13  13   0    8  14   3    0.000    0.000       0
    40   1    124 00:01:33.87   0.7560A  -2.3824  -1.2787   1.4680  0.071  0.63  -0.892E+00     40.  0.134E+01  0.559E-01  0.148E-02  0.184E-03   60   0   8    8  14   5    8  14   3    0.000    0.000       0
    41   1    125 00:01:34.62   0.7560A  -2.3825  -1.2876   1.4669  0.071  0.63  -0.895E+00     40.  0.134E+01  0.559E-01  0.149E-02  0.183E-03   60  19   7    8  14   5    8  14   3    0.000    0.000       0
    42   1    126 00:01:35.38   0.7550A  -2.3825  -1.2951   1.4654  0.071  0.64  -0.897E+00     42.  0.134E+01  0.560E-01  0.149E-02  0.181E-03   60  19   6    8  14   5    8  14   3    0.000    0.000       0
    43   1    127 00:01:36.13   0.7550A  -2.3826  -1.3016   1.4634  0.071  0.63  -0.899E+00     42.  0.134E+01  0.560E-01  0.150E-02  0.179E-03   60  19   6    8  14   5    8  14   3    0.000    0.000       0
    44   1    128 00:01:36.89   0.7550A  -2.3827  -1.3075   1.4613  0.071  0.62  -0.902E+00     40.  0.134E+01  0.560E-01  0.151E-02  0.178E-03   60  18   4    8  14   5    8  14   3    0.000    0.000       0
    45   1    129 00:01:37.64   0.7550A  -2.3828  -1.3132   1.4592  0.070  0.62  -0.911E+00     40.  0.134E+01  0.560E-01  0.152E-02  0.176E-03   60  18   3    8  14   5    8  14   3    0.000    0.000       0
    46   1    130 00:01:38.40   0.7550A  -2.3828  -1.3183   1.4574  0.070  0.61  -0.916E+00     40.  0.134E+01  0.560E-01  0.153E-02  0.174E-03   60  18   3    8  14   5    8  14   3    0.000    0.000       0
    47   1    131 00:01:39.15   0.7550A  -2.3829  -1.3222   1.4560  0.070  0.61  -0.915E+00     40.  0.134E+01  0.559E-01  0.154E-02  0.173E-03   60  18   2    8  14   5    8  14   3    0.000    0.000       0
    48   1    132 00:01:39.91   0.7550A  -2.3830  -1.3240   1.4559  0.070  0.61  -0.915E+00     40.  0.134E+01  0.559E-01  0.156E-02  0.171E-03   60  17   1    8  14   5    7  14   3    0.000    0.000       0
    49   1    133 00:01:40.66   0.7550A  -2.3831  -1.3225   1.4575  0.070  0.60  -0.912E+00     40.  0.133E+01  0.558E-01  0.157E-02  0.170E-03   60  17   0    8  14   5    7  14   3    0.000    0.000       0
    50   1    134 00:01:41.42   0.7550A  -2.3831  -1.3164   1.4593  0.070  0.60  -0.909E+00     40.  0.133E+01  0.557E-01  0.158E-02  0.169E-03   60  17   0    8  14   5    7  14   3    0.000    0.000       0
    51   1    135 00:01:42.17   0.7550A  -2.3832  -1.3049   1.4608  0.070  0.61  -0.908E+00     42.  0.133E+01  0.556E-01  0.159E-02  0.168E-03   60  16  18    8  14   5    7  14   3    0.000    0.000       0
    52   1    136 00:01:42.93   0.7550A  -2.3833  -1.2873   1.4618  0.070  0.61  -0.908E+00     42.  0.133E+01  0.555E-01  0.160E-02  0.167E-03   60  16  17    8  14   5    7  14   3    0.000    0.000       0
    53   1    137 00:01:43.68   0.7550A  -2.3833  -1.2642   1.4638  0.070  0.62  -0.909E+00     44.  0.133E+01  0.554E-01  0.161E-02  0.166E-03   60  16  17    8  14   5    8  13   3    0.000    0.000       0
    54   1    138 00:01:44.44   0.7550A  -2.3834  -1.2366   1.4694  0.070  0.62  -0.910E+00     44.  0.133E+01  0.552E-01  0.162E-02  0.165E-03   60  15  15    8  14   5    8  13   3    0.000    0.000       0
    55   1    139 00:01:45.19   0.7550A  -2.3835  -1.2220   1.4730  0.070  0.61  -0.916E+00     44.  0.133E+01  0.550E-01  0.163E-02  0.164E-03   60  15  14    6  13   5    8  13   3    0.000    0.000       0
    56   1    140 00:01:45.95   0.7550A  -2.3836  -1.2184   1.4743  0.070  0.61  -0.917E+00     44.  0.133E+01  0.549E-01  0.164E-02  0.163E-03   60  15  14    6  13   5    8  13   3    0.000    0.000       0
    57   1    141 00:01:46.70   0.7550A  -2.3836  -1.2098   1.4726  0.069  0.61  -0.912E+00     44.  0.133E+01  0.546E-01  0.165E-02  0.162E-03   60  14  12    6  13   5    8  13   3    0.000    0.000       0
    58   1    142 00:01:47.46   0.7550A  -2.3837  -1.2086   1.4679  0.069  0.61  -0.912E+00     44.  0.133E+01  0.544E-01  0.165E-02  0.161E-03   60  14  11   17   8  19    8  13   3    0.000    0.000       0
    59   1    143 00:01:48.21   0.7550A  -2.3838  -1.2028   1.4643  0.069  0.60  -0.913E+00     44.  0.133E+01  0.542E-01  0.166E-02  0.160E-03   60  14  11   17   8  19    8  14   3    0.000    0.000       0
    60   1    144 00:01:48.97   0.7550A  -2.3839  -1.1926   1.4664  0.069  0.60  -0.915E+00     44.  0.133E+01  0.539E-01  0.167E-02  0.159E-03   60  13   9   17   8  19    8  14   3    0.000    0.000       0
    61   1    145 00:01:49.72   0.7550A  -2.3839  -1.1785   1.4689  0.069  0.60  -0.917E+00     44.  0.133E+01  0.537E-01  0.167E-02  0.158E-03   60  13   8   17   8  19    8  14   3    0.000    0.000       0
    62   1    146 00:01:50.48   0.7550A  -2.3840  -1.1750   1.4719  0.069  0.61  -0.917E+00     46.  0.133E+01  0.534E-01  0.168E-02  0.157E-03   60  13   8   16   8  19    8  14   3    0.000    0.000       0
    63   1    147 00:01:51.23   0.7550A  -2.3841  -1.1698   1.4753  0.069  0.61  -0.917E+00     46.  0.133E+01  0.531E-01  0.168E-02  0.157E-03   60  13   7   16   8  19    8  14   3    0.000    0.000       0
    64   1    148 00:01:51.99   0.7550A  -2.3841  -1.1592   1.4790  0.068  0.60  -0.918E+00     46.  0.133E+01  0.528E-01  0.168E-02  0.156E-03   60  12   6   16   8  19    8  14   3    0.000    0.000       0
    65   1    149 00:01:52.74   0.7550A  -2.3842  -1.1440   1.4830  0.068  0.60  -0.920E+00     46.  0.133E+01  0.525E-01  0.169E-02  0.156E-03   60  12   5   15   8  19    8  14   3    0.000    0.000       0
    66   1    150 00:01:53.50   0.7550A  -2.3843  -1.1376   1.4870  0.068  0.60  -0.922E+00     46.  0.132E+01  0.522E-01  0.169E-02  0.155E-03   60  12   5   17   7  18    8  14   3    0.000    0.000       0
    67   1    151 00:01:54.25   0.7550A  -2.3844  -1.1399   1.4908  0.068  0.60  -0.925E+00     46.  0.132E+01  0.519E-01  0.169E-02  0.155E-03   60  11   3   17   7  18    8  14   3    0.000    0.000       0
    68   1    152 00:01:55.01   0.7550A  -2.3844  -1.1357   1.4942  0.068  0.61  -0.928E+00     48.  0.132E+01  0.515E-01  0.170E-02  0.155E-03   60  11   2   17   7  18    8  14   3    0.000    0.000       0
    69   1    153 00:01:55.76   0.7550A  -2.3845  -1.1241   1.4971  0.067  0.61  -0.929E+00     48.  0.132E+01  0.512E-01  0.170E-02  0.155E-03   60  11   2   17   7  18    8  14   3    0.000    0.000       0
    70   1    154 00:01:56.52   0.7550A  -2.3846  -1.1043   1.4991  0.067  0.61  -0.930E+00     48.  0.132E+01  0.508E-01  0.170E-02  0.155E-03   60  11   1   17   7  18    8  14   3    0.000    0.000       0
    71   1    155 00:01:57.27   0.7550A  -2.3847  -1.1019   1.4997  0.067  0.61  -0.931E+00     48.  0.132E+01  0.505E-01  0.170E-02  0.155E-03   60  10   0   18   7  17    8  14   3    0.000    0.000       0
    72   1    156 00:01:58.03   0.7550A  -2.3847  -1.0973   1.4989  0.067  0.61  -0.933E+00     48.  0.132E+01  0.502E-01  0.169E-02  0.155E-03   60  10  19   18   7  17    8  14   3    0.000    0.000       0
    73   1    157 00:01:58.78   0.7550A  -2.3848  -1.1023   1.4962  0.067  0.61  -0.935E+00     48.  0.132E+01  0.498E-01  0.169E-02  0.155E-03   60  10  19   16   5  18    8  14   3    0.000    0.000       0
    74   1    158 00:01:59.54   0.7550A  -2.3849  -1.1089   1.4915  0.067  0.61  -0.939E+00     48.  0.132E+01  0.495E-01  0.169E-02  0.155E-03   60   9  17   16   5  18    8  14   3    0.000    0.000       0
    75   1    159 00:02:00.29   0.7550A  -2.3849  -1.1068   1.4844  0.066  0.61  -0.942E+00     48.  0.132E+01  0.491E-01  0.169E-02  0.155E-03   60   9  16   16   5  18    8  14   3    0.000    0.000       0
    76   1    160 00:02:01.05   0.7550A  -2.3850  -1.0961   1.4745  0.066  0.62  -0.944E+00     48.  0.132E+01  0.488E-01  0.169E-02  0.155E-03   60   9  16   16   5  18    8  14   3    0.000    0.000       0
    77   1    161 00:02:01.80   0.7550A  -2.3851  -1.0773   1.4617  0.066  0.62  -0.947E+00     48.  0.132E+01  0.484E-01  0.169E-02  0.154E-03   60   8  14   16   5  18    8  14   3    0.000    0.000       0
    78   1    162 00:02:02.56   0.7550A  -2.3852  -1.0860   1.4457  0.066  0.62  -0.948E+00     48.  0.132E+01  0.481E-01  0.169E-02  0.154E-03   60   8  13   16   5  17    8  14   3    0.000    0.000       0
    79   1    163 00:02:03.31   0.7550A  -2.3852  -1.1032   1.4263  0.066  0.62  -0.951E+00     48.  0.132E+01  0.477E-01  0.168E-02  0.153E-03   60   8  13   16   5  17    8  14   3    0.000    0.000       0
    80   1    164 00:02:04.07   0.7550A  -2.3853  -1.1080   1.4101  0.066  0.63  -0.957E+00     48.  0.132E+01  0.474E-01  0.168E-02  0.152E-03   60   7  11   16   5  17    9  14   3    0.000    0.000       0
    81   1    165 00:02:04.82   0.7550A  -2.3854  -1.0998   1.4185  0.066  0.63  -0.962E+00     48.  0.132E+01  0.470E-01  0.167E-02  0.151E-03   60   7  10   16   5  17    8  14   2    0.000    0.000       0
    82   1    166 00:02:05.58   0.7550A  -2.3854  -1.0790   1.4267  0.066  0.63  -0.962E+00     48.  0.131E+01  0.467E-01  0.167E-02  0.150E-03   60   7  10   16   5  17    8  14   2    0.000    0.000       0
    83   1    167 00:02:06.33   0.7550A  -2.3855  -1.0532   1.4328  0.065  0.64  -0.959E+00     48.  0.131E+01  0.463E-01  0.166E-02  0.149E-03   60   6   8   16   5  16    8  14   2    0.000    0.000       0
    84   1    168 00:02:07.09   0.7550A  -2.3856  -1.0680   1.4363  0.065  0.64  -0.958E+00     48.  0.131E+01  0.460E-01  0.166E-02  0.147E-03   60   6   7   16   5  16    8  14   2    0.000    0.000       0
    85   1    169 00:02:07.84   0.7550A  -2.3857  -1.0709   1.4369  0.065  0.64  -0.957E+00     48.  0.131E+01  0.456E-01  0.165E-02  0.144E-03   60   6   7   21  11  18    8  14   2    0.000    0.000       0
    86   1    170 00:02:08.60   0.7540A  -2.3857  -1.0774   1.4344  0.065  0.64  -0.958E+00     48.  0.131E+01  0.453E-01  0.164E-02  0.142E-03   60   6   7   22  11  17    8  14   2    0.000    0.000       0
    87   1    171 00:02:09.35   0.7540A  -2.3858  -1.0936   1.4288  0.065  0.65  -0.960E+00     48.  0.131E+01  0.450E-01  0.163E-02  0.139E-03   60   5   5   22  11  17    8  14   2    0.000    0.000       0
    88   1    172 00:02:10.11   0.7540A  -2.3859  -1.1017   1.4205  0.065  0.65  -0.963E+00     48.  0.131E+01  0.446E-01  0.162E-02  0.136E-03   60   5   4   22  11  17    8  14   2    0.000    0.000       0
    89   1    173 00:02:10.86   0.7540A  -2.3860  -1.1152   1.4096  0.065  0.65  -0.968E+00     48.  0.131E+01  0.443E-01  0.161E-02  0.133E-03   60   5   4   21  10  17    8  14   2    0.000    0.000       0
    90   1    174 00:02:11.61   0.7540A  -2.3860  -1.1221   1.3966  0.064  0.65  -0.975E+00     48.  0.131E+01  0.439E-01  0.160E-02  0.130E-03   60   4   2   21  10  17    8  14   2    0.000    0.000       0
    91   1    175 00:02:12.37   0.7540A  -2.3861  -1.1173   1.3876  0.064  0.67  -0.977E+00     50.  0.131E+01  0.436E-01  0.159E-02  0.127E-03   60   4   1   21  10  17    9  14   2    0.000    0.000       0
    92   1    176 00:02:13.12   0.7540A  -2.3862  -1.1054   1.3955  0.064  0.67  -0.977E+00     50.  0.131E+01  0.433E-01  0.158E-02  0.124E-03   60   4   1   22  10  16    9  14   2    0.000    0.000       0
    93   1    177 00:02:13.88   0.7540A  -2.3862  -1.1083   1.3996  0.064  0.67  -0.983E+00     50.  0.131E+01  0.429E-01  0.157E-02  0.122E-03   60   4   1   22  10  16    9  14   2    0.000    0.000       0
    94   1    178 00:02:14.63   0.7540A  -2.3863  -1.0999   1.4001  0.064  0.67  -0.100E+01     50.  0.131E+01  0.426E-01  0.156E-02  0.119E-03   60   3  19   22  10  16    9  14   2    0.000    0.000       0
    95   1    179 00:02:15.38   0.7540A  -2.3864  -1.0791   1.3975  0.063  0.67  -0.103E+01     50.  0.131E+01  0.423E-01  0.156E-02  0.117E-03   60   3  18   21   9  16    9  14   2    0.000    0.000       0
    96   1    180 00:02:16.14   0.7540A  -2.3865  -1.0799   1.3925  0.063  0.68  -0.993E+00     50.  0.131E+01  0.420E-01  0.155E-02  0.115E-03   60   3  18   21   9  16    9  14   2    0.000    0.000       0
    97   1    181 00:02:16.89   0.7540A  -2.3865  -1.0667   1.3857  0.063  0.68  -0.101E+01     50.  0.131E+01  0.417E-01  0.154E-02  0.113E-03   60   2  16   21   9  16    9  14   2    0.000    0.000       0
    98   1    182 00:02:17.65   0.7540A  -2.3866  -1.0471   1.3775  0.063  0.68  -0.983E+00     50.  0.131E+01  0.414E-01  0.154E-02  0.112E-03   60   2  15   22   9  15    9  14   2    0.000    0.000       0
    99   1    183 00:02:18.40   0.7540A  -2.3867  -1.0440   1.3686  0.063  0.68  -0.964E+00     50.  0.131E+01  0.411E-01  0.153E-02  0.111E-03   60   2  15   22   9  15    9  14   2    0.000    0.000       0
    100   1    184 00:02:19.15   0.7540A  -2.3867  -1.0475   1.3589  0.063  0.69  -0.956E+00     52.  0.130E+01  0.408E-01  0.153E-02  0.110E-03   60   1  13   18   1  12    9  14   2    0.000    0.000       0
    101   1    185 00:02:19.91   0.7540A  -2.3868  -1.0550   1.3488  0.063  0.69  -0.951E+00     52.  0.130E+01  0.406E-01  0.152E-02  0.109E-03   60   1  12   18   1  12    9  14   2    0.000    0.000       0
    102   1    186 00:02:20.66   0.7540A  -2.3869  -1.0554   1.3380  0.063  0.69  -0.946E+00     52.  0.130E+01  0.403E-01  0.152E-02  0.108E-03   60   1  12   18   1  12    9  14   2    0.000    0.000       0
     9  1     93 00:01:10.43   0.7560A  -2.3801   1.0895   1.4794  0.071  0.11  -0.885E+00     46.  0.135E+01  0.506E-01  0.000E+00  0.000E+00   60   9  16    1   2  14    7  14   3    0.000    0.000       0
     10  1     94 00:01:11.19   0.7560A  -2.3802   1.0952   1.4738  0.071  0.61  -0.884E+00     46.  0.135E+01  0.509E-01  0.128E-02  0.185E-03   60   9  15    1   2  14    7  14   3    0.000    0.000       0
     11  1     95 00:01:11.94   0.7560A  -2.3803   1.1004   1.4683  0.071  0.62  -0.883E+00     46.  0.135E+01  0.511E-01  0.129E-02  0.185E-03   60   8  13    1   2  14    7  14   3    0.000    0.000       0
     12  1     96 00:01:12.70   0.7560A  -2.3803   1.1051   1.4629  0.071  0.62  -0.883E+00     46.  0.135E+01  0.514E-01  0.129E-02  0.185E-03   60   8  13    1   2  14    7  14   3    0.000    0.000       0
     13  1     97 00:01:13.45   0.7560A  -2.3804   1.1093   1.4580  0.071  0.63  -0.882E+00     46.  0.135E+01  0.516E-01  0.130E-02  0.186E-03   60   8  12    1   2  14    7  14   3    0.000    0.000       0
     14  1     98 00:01:14.21   0.7560A  -2.3805   1.1132   1.4537  0.071  0.63  -0.882E+00     46.  0.135E+01  0.519E-01  0.130E-02  0.186E-03   60   8  12    1   2  14    7  14   3    0.000    0.000       0
     15  1     99 00:01:14.97   0.7560A  -2.3806   1.1166   1.4501  0.071  0.63  -0.882E+00     46.  0.135E+01  0.521E-01  0.131E-02  0.187E-03   60   7  10    1   2  14    7  14   3    0.000    0.000       0
     16  1    100 00:01:15.72   0.7560A  -2.3806   1.1196   1.4471  0.071  0.64  -0.881E+00     46.  0.135E+01  0.523E-01  0.131E-02  0.187E-03   60   7  10    1   2  14    7  14   3    0.000    0.000       0
     17  1    101 00:01:16.48   0.7560A  -2.3807   1.1223   1.4449  0.071  0.65  -0.881E+00     48.  0.135E+01  0.526E-01  0.132E-02  0.188E-03   60   7   9    1   2  14    7  14   3    0.000    0.000       0
     18  1    102 00:01:17.23   0.7560A  -2.3808  -1.1319   1.4435  0.071  0.66  -0.882E+00     48.  0.135E+01  0.528E-01  0.132E-02  0.188E-03   60   6   7   13  13   0    7  14   3    0.000    0.000       0
     19  1    103 00:01:17.99   0.7560A  -2.3809  -1.1487   1.4427  0.071  0.66  -0.882E+00     48.  0.135E+01  0.530E-01  0.133E-02  0.189E-03   60   6   7   14  14   0    7  14   3    0.000    0.000       0
     20  1    104 00:01:18.75   0.7560A  -2.3809  -1.1665   1.4425  0.071  0.66  -0.883E+00     48.  0.135E+01  0.532E-01  0.134E-02  0.190E-03   60   6   6   14  14   0    7  14   3    0.000    0.000       0
     21  1    105 00:01:19.50   0.7560A  -2.3810  -1.1843   1.4429  0.071  0.67  -0.885E+00     48.  0.135E+01  0.534E-01  0.134E-02  0.190E-03   60   6   6   14  14   0    7  14   3    0.000    0.000       0
     22  1    106 00:01:20.26   0.7560A  -2.3811  -1.2034   1.4436  0.071  0.68  -0.890E+00     50.  0.135E+01  0.536E-01  0.135E-02  0.191E-03   60   5   4   14  13   0    7  14   3    0.000    0.000       0
     23  1    107 00:01:21.01   0.7560A  -2.3811  -1.2245   1.4446  0.071  0.68  -0.900E+00     50.  0.135E+01  0.538E-01  0.136E-02  0.192E-03   60   5   4   14  13   0    7  14   3    0.000    0.000       0
     24  1    108 00:01:21.77   0.7560A  -2.3812  -1.2460   1.4458  0.071  0.69  -0.890E+00     50.  0.135E+01  0.540E-01  0.136E-02  0.193E-03   60   5   3   14  13   0    7  14   3    0.000    0.000       0
     25  1    109 00:01:22.53   0.7560A  -2.3813  -1.2671   1.4471  0.071  0.69  -0.885E+00     50.  0.135E+01  0.541E-01  0.137E-02  0.193E-03   60   4   1   14  13   0    7  14   3    0.000    0.000       0
     26  1    110 00:01:23.28   0.7560A  -2.3814  -1.2870   1.4483  0.071  0.69  -0.884E+00     50.  0.134E+01  0.543E-01  0.138E-02  0.194E-03   60   4   1   14  13   0    7  14   3    0.000    0.000       0
     27  1    111 00:01:24.04   0.7560A  -2.3814  -1.3046   1.4494  0.071  0.69  -0.883E+00     50.  0.134E+01  0.545E-01  0.138E-02  0.194E-03   60   4   0   14  13   0    7  14   3    0.000    0.000       0
     28  1    112 00:01:24.79   0.7560A  -2.3815  -1.3193   1.4504  0.071  0.70  -0.883E+00     50.  0.134E+01  0.546E-01  0.139E-02  0.194E-03   60   3  19   14  13   0    7  14   3    0.000    0.000       0
     29  1    113 00:01:25.55   0.7560A  -2.3816  -1.3307   1.4512  0.071  0.70  -0.883E+00     50.  0.134E+01  0.548E-01  0.140E-02  0.194E-03   60   3  18   14  13   0    7  14   3    0.000    0.000       0
     30  1    114 00:01:26.31   0.7560A  -2.3817  -1.3385   1.4519  0.071  0.71  -0.884E+00     52.  0.134E+01  0.549E-01  0.141E-02  0.194E-03   60   3  17   14  13   0    7  14   3    0.000    0.000       0
     31  1    115 00:01:27.06   0.7560A  -2.3817  -1.3428   1.4525  0.071  0.71  -0.884E+00     52.  0.134E+01  0.550E-01  0.141E-02  0.194E-03   60   2  16   14  13   0    7  14   3    0.000    0.000       0
     32  1    116 00:01:27.82   0.7560A  -2.3818  -1.3436   1.4542  0.071  0.71  -0.885E+00     52.  0.134E+01  0.552E-01  0.142E-02  0.194E-03   60   2  15   14  13   0    8  14   3    0.000    0.000       0
     33  1    117 00:01:28.57   0.7560A  -2.3819  -1.3409   1.4575  0.071  0.71  -0.886E+00     52.  0.134E+01  0.553E-01  0.143E-02  0.193E-03   60   2  14   14  13   0    8  14   3    0.000    0.000       0
     34  1    118 00:01:29.33   0.7560A  -2.3819  -1.3347   1.4604  0.071  0.71  -0.887E+00     52.  0.134E+01  0.554E-01  0.143E-02  0.192E-03   60   1  13   14  13   0    8  14   3    0.000    0.000       0
     35  1    119 00:01:30.09   0.7560A  -2.3820  -1.3251   1.4628  0.071  0.64  -0.887E+00     40.  0.134E+01  0.555E-01  0.144E-02  0.191E-03   60   1  12   14  13   0    8  14   3    0.000    0.000       0
     36  1    120 00:01:30.84   0.7560A  -2.3821  -1.3123   1.4646  0.071  0.64  -0.887E+00     40.  0.134E+01  0.556E-01  0.145E-02  0.190E-03   60   1  12   14  13   0    8  14   3    0.000    0.000       0
     37  1    121 00:01:31.60   0.7560A  -2.3822  -1.2966   1.4658  0.071  0.64  -0.888E+00     40.  0.134E+01  0.557E-01  0.145E-02  0.189E-03   60   0  10   14  13   0    8  14   3    0.000    0.000       0
     38  1    122 00:01:32.35   0.7560A  -2.3822  -1.2829   1.4664  0.071  0.64  -0.889E+00     40.  0.134E+01  0.557E-01  0.146E-02  0.187E-03   60   0   9   13  13   0    8  14   3    0.000    0.000       0
     39  1    123 00:01:33.11   0.7560A  -2.3823  -1.2691   1.4664  0.071  0.63  -0.890E+00     40.  0.134E+01  0.558E-01  0.147E-02  0.186E-03   60   0   9   13  13   0    8  14   3    0.000    0.000       0
     40  1    124 00:01:33.87   0.7560A  -2.3824  -1.2773   1.4659  0.071  0.63  -0.892E+00     40.  0.134E+01  0.558E-01  0.148E-02  0.184E-03   60   0   8    8  14   5    8  14   3    0.000    0.000       0
     41  1    125 00:01:34.62   0.7560A  -2.3825  -1.2862   1.4649  0.071  0.63  -0.895E+00     40.  0.134E+01  0.559E-01  0.148E-02  0.183E-03   60  19   7    8  14   5    8  14   3    0.000    0.000       0
     42  1    126 00:01:35.38   0.7550A  -2.3825  -1.2937   1.4634  0.071  0.64  -0.897E+00     42.  0.134E+01  0.559E-01  0.149E-02  0.181E-03   60  19   6    8  14   5    8  14   3    0.000    0.000       0
     43  1    127 00:01:36.13   0.7550A  -2.3826  -1.3002   1.4615  0.071  0.63  -0.899E+00     42.  0.134E+01  0.559E-01  0.150E-02  0.179E-03   60  19   6    8  14   5    8  14   3    0.000    0.000       0
     44  1    128 00:01:36.89   0.7550A  -2.3827  -1.3062   1.4594  0.071  0.62  -0.902E+00     40.  0.134E+01  0.559E-01  0.151E-02  0.177E-03   60  18   4    8  14   5    8  14   3    0.000    0.000       0
     45  1    129 00:01:37.64   0.7550A  -2.3828  -1.3119   1.4574  0.070  0.62  -0.911E+00     40.  0.134E+01  0.559E-01  0.152E-02  0.176E-03   60  18   3    8  14   5    8  14   3    0.000    0.000       0
     46  1    130 00:01:38.40   0.7550A  -2.3828  -1.3170   1.4556  0.070  0.61  -0.916E+00     40.  0.134E+01  0.559E-01  0.153E-02  0.174E-03   60  18   3    8  14   5    8  14   3    0.000    0.000       0
     47  1    131 00:01:39.15   0.7550A  -2.3829  -1.3209   1.4542  0.070  0.61  -0.915E+00     40.  0.134E+01  0.559E-01  0.154E-02  0.173E-03   60  18   2    8  14   5    8  14   3    0.000    0.000       0
     48  1    132 00:01:39.91   0.7550A  -2.3830  -1.3227   1.4543  0.070  0.61  -0.915E+00     40.  0.134E+01  0.558E-01  0.155E-02  0.171E-03   60  17   1    8  14   5    7  14   3    0.000    0.000       0
     49  1    133 00:01:40.66   0.7550A  -2.3831  -1.3213   1.4559  0.070  0.60  -0.912E+00     40.  0.133E+01  0.558E-01  0.156E-02  0.170E-03   60  17   0    8  14   5    7  14   3    0.000    0.000       0
     50  1    134 00:01:41.42   0.7550A  -2.3831  -1.3153   1.4577  0.070  0.60  -0.910E+00     40.  0.133E+01  0.557E-01  0.158E-02  0.169E-03   60  17   0    8  14   5    7  14   3    0.000    0.000       0
     51  1    135 00:01:42.17   0.7550A  -2.3832  -1.3038   1.4592  0.070  0.61  -0.908E+00     42.  0.133E+01  0.556E-01  0.159E-02  0.168E-03   60  16  18    8  14   5    7  14   3    0.000    0.000       0
     52  1    136 00:01:42.93   0.7550A  -2.3833  -1.2864   1.4601  0.070  0.61  -0.908E+00     42.  0.133E+01  0.554E-01  0.160E-02  0.167E-03   60  16  17    8  14   5    7  14   3    0.000    0.000       0
     53  1    137 00:01:43.68   0.7550A  -2.3833  -1.2634   1.4626  0.070  0.62  -0.909E+00     44.  0.133E+01  0.553E-01  0.161E-02  0.166E-03   60  16  17    8  14   5    8  13   3    0.000    0.000       0
     54  1    138 00:01:44.44   0.7550A  -2.3834  -1.2359   1.4682  0.070  0.62  -0.910E+00     44.  0.133E+01  0.552E-01  0.162E-02  0.165E-03   60  15  15    8  14   5    8  13   3    0.000    0.000       0
     55  1    139 00:01:45.19   0.7550A  -2.3835  -1.2203   1.4717  0.070  0.61  -0.915E+00     44.  0.133E+01  0.550E-01  0.163E-02  0.164E-03   60  15  14    6  13   5    8  13   3    0.000    0.000       0
     56  1    140 00:01:45.95   0.7550A  -2.3836  -1.2167   1.4729  0.070  0.61  -0.917E+00     44.  0.133E+01  0.548E-01  0.164E-02  0.163E-03   60  15  14    6  13   5    8  13   3    0.000    0.000       0
     57  1    141 00:01:46.70   0.7550A  -2.3836  -1.2094   1.4712  0.069  0.61  -0.912E+00     44.  0.133E+01  0.546E-01  0.164E-02  0.162E-03   60  14  12   17   8  19    8  13   3    0.000    0.000       0
     58  1    142 00:01:47.46   0.7550A  -2.3837  -1.2085   1.4664  0.069  0.61  -0.912E+00     44.  0.133E+01  0.544E-01  0.165E-02  0.161E-03   60  14  11   17   8  19    8  13   3    0.000    0.000       0
     59  1    143 00:01:48.21   0.7550A  -2.3838  -1.2026   1.4624  0.069  0.60  -0.913E+00     44.  0.133E+01  0.541E-01  0.166E-02  0.160E-03   60  14  11   17   8  19    8  14   3    0.000    0.000       0
     60  1    144 00:01:48.97   0.7550A  -2.3839  -1.1923   1.4644  0.069  0.60  -0.915E+00     44.  0.133E+01  0.539E-01  0.166E-02  0.159E-03   60  13   9   17   8  19    8  14   3    0.000    0.000       0
     61  1    145 00:01:49.72   0.7550A  -2.3839  -1.1783   1.4669  0.069  0.60  -0.917E+00     44.  0.133E+01  0.536E-01  0.167E-02  0.158E-03   60  13   8   17   8  19    8  14   3    0.000    0.000       0
     62  1    146 00:01:50.48   0.7550A  -2.3840  -1.1749   1.4698  0.069  0.61  -0.917E+00     46.  0.133E+01  0.533E-01  0.167E-02  0.157E-03   60  13   8   16   8  19    8  14   3    0.000    0.000       0
     63  1    147 00:01:51.23   0.7550A  -2.3841  -1.1696   1.4732  0.069  0.61  -0.917E+00     46.  0.133E+01  0.531E-01  0.168E-02  0.157E-03   60  13   7   16   8  19    8  14   3    0.000    0.000       0
     64  1    148 00:01:51.99   0.7550A  -2.3841  -1.1589   1.4768  0.068  0.60  -0.918E+00     46.  0.133E+01  0.528E-01  0.168E-02  0.156E-03   60  12   6   16   8  19    8  14   3    0.000    0.000       0
     65  1    149 00:01:52.74   0.7550A  -2.3842  -1.1438   1.4807  0.068  0.60  -0.920E+00     46.  0.133E+01  0.524E-01  0.168E-02  0.156E-03   60  12   5   15   8  19    8  14   3    0.000    0.000       0
     66  1    150 00:01:53.50   0.7550A  -2.3843  -1.1373   1.4846  0.068  0.60  -0.922E+00     46.  0.132E+01  0.521E-01  0.169E-02  0.155E-03   60  12   5   17   7  18    8  14   3    0.000    0.000       0
     67  1    151 00:01:54.25   0.7550A  -2.3844  -1.1397   1.4884  0.068  0.60  -0.925E+00     46.  0.132E+01  0.518E-01  0.169E-02  0.155E-03   60  11   3   17   7  18    8  14   3    0.000    0.000       0
     68  1    152 00:01:55.01   0.7550A  -2.3844  -1.1355   1.4917  0.068  0.61  -0.928E+00     48.  0.132E+01  0.515E-01  0.169E-02  0.155E-03   60  11   2   17   7  18    8  14   3    0.000    0.000       0
     69  1    153 00:01:55.76   0.7550A  -2.3845  -1.1239   1.4945  0.067  0.61  -0.929E+00     48.  0.132E+01  0.511E-01  0.170E-02  0.155E-03   60  11   2   17   7  18    8  14   3    0.000    0.000       0
     70  1    154 00:01:56.52   0.7550A  -2.3846  -1.1042   1.4964  0.067  0.61  -0.930E+00     48.  0.132E+01  0.508E-01  0.170E-02  0.155E-03   60  11   1   17   7  18    8  14   3    0.000    0.000       0
     71  1    155 00:01:57.27   0.7550A  -2.3847  -1.1017   1.4970  0.067  0.61  -0.931E+00     48.  0.132E+01  0.505E-01  0.169E-02  0.155E-03   60  10   0   18   7  17    8  14   3    0.000    0.000       0
     72  1    156 00:01:58.03   0.7550A  -2.3847  -1.0972   1.4960  0.067  0.61  -0.933E+00     48.  0.132E+01  0.501E-01  0.169E-02  0.155E-03   60  10  19   18   7  17    8  14   3    0.000    0.000       0
     73  1    157 00:01:58.78   0.7550A  -2.3848  -1.1025   1.4933  0.067  0.61  -0.935E+00     48.  0.132E+01  0.498E-01  0.169E-02  0.155E-03   60  10  19   16   5  18    8  14   3    0.000    0.000       0
     74  1    158 00:01:59.54   0.7550A  -2.3849  -1.1090   1.4886  0.067  0.61  -0.939E+00     48.  0.132E+01  0.494E-01  0.169E-02  0.155E-03   60   9  17   16   5  18    8  14   3    0.000    0.000       0
     75  1    159 00:02:00.29   0.7550A  -2.3849  -1.1069   1.4814  0.066  0.61  -0.942E+00     48.  0.132E+01  0.491E-01  0.169E-02  0.155E-03   60   9  16   16   5  18    8  14   3    0.000    0.000       0
     76  1    160 00:02:01.05   0.7550A  -2.3850  -1.0961   1.4715  0.066  0.62  -0.944E+00     48.  0.132E+01  0.487E-01  0.169E-02  0.155E-03   60   9  16   16   5  18    8  14   3    0.000    0.000       0
     77  1    161 00:02:01.80   0.7550A  -2.3851  -1.0772   1.4587  0.066  0.62  -0.947E+00     48.  0.132E+01  0.484E-01  0.169E-02  0.154E-03   60   8  14   16   5  18    8  14   3    0.000    0.000       0
     78  1    162 00:02:02.56   0.7550A  -2.3852  -1.0857   1.4427  0.066  0.62  -0.948E+00     48.  0.132E+01  0.480E-01  0.168E-02  0.154E-03   60   8  13   16   5  17    8  14   3    0.000    0.000       0
     79  1    163 00:02:03.31   0.7550A  -2.3852  -1.1029   1.4233  0.066  0.62  -0.951E+00     48.  0.132E+01  0.477E-01  0.168E-02  0.153E-03   60   8  13   16   5  17    8  14   3    0.000    0.000       0
     80  1    164 00:02:04.07   0.7550A  -2.3853  -1.1078   1.4090  0.066  0.63  -0.957E+00     48.  0.132E+01  0.473E-01  0.168E-02  0.152E-03   60   7  11   16   5  17    8  14   2    0.000    0.000       0
     81  1    165 00:02:04.82   0.7550A  -2.3854  -1.0995   1.4187  0.066  0.63  -0.963E+00     48.  0.132E+01  0.470E-01  0.167E-02  0.151E-03   60   7  10   16   5  17    8  14   2    0.000    0.000       0
     82  1    166 00:02:05.58   0.7550A  -2.3854  -1.0787   1.4268  0.066  0.63  -0.962E+00     48.  0.131E+01  0.466E-01  0.166E-02  0.150E-03   60   7  10   16   5  17    8  14   2    0.000    0.000       0
     83  1    167 00:02:06.33   0.7550A  -2.3855  -1.0526   1.4328  0.065  0.64  -0.959E+00     48.  0.131E+01  0.463E-01  0.166E-02  0.149E-03   60   6   8   16   5  16    8  14   2    0.000    0.000       0
     84  1    168 00:02:07.09   0.7550A  -2.3856  -1.0675   1.4363  0.065  0.64  -0.958E+00     48.  0.131E+01  0.459E-01  0.165E-02  0.147E-03   60   6   7   16   5  16    8  14   2    0.000    0.000       0
     85  1    169 00:02:07.84   0.7550A  -2.3857  -1.0679   1.4368  0.065  0.64  -0.958E+00     48.  0.131E+01  0.456E-01  0.165E-02  0.144E-03   60   6   7   21  11  18    8  14   2    0.000    0.000       0
     86  1    170 00:02:08.60   0.7540A  -2.3857  -1.0746   1.4343  0.065  0.64  -0.958E+00     48.  0.131E+01  0.453E-01  0.164E-02  0.142E-03   60   6   7   22  11  17    8  14   2    0.000    0.000       0
     87  1    171 00:02:09.35   0.7540A  -2.3858  -1.0912   1.4288  0.065  0.65  -0.960E+00     48.  0.131E+01  0.449E-01  0.163E-02  0.139E-03   60   5   5   22  11  17    8  14   2    0.000    0.000       0
     88  1    172 00:02:10.11   0.7540A  -2.3859  -1.0997   1.4204  0.065  0.65  -0.963E+00     48.  0.131E+01  0.446E-01  0.162E-02  0.136E-03   60   5   4   22  11  17    8  14   2    0.000    0.000       0
     89  1    173 00:02:10.86   0.7540A  -2.3860  -1.1130   1.4095  0.064  0.65  -0.968E+00     48.  0.131E+01  0.442E-01  0.160E-02  0.133E-03   60   5   4   21  10  17    8  14   2    0.000    0.000       0
     90  1    174 00:02:11.61   0.7540A  -2.3860  -1.1206   1.3965  0.064  0.65  -0.975E+00     48.  0.131E+01  0.439E-01  0.159E-02  0.130E-03   60   4   2   21  10  17    8  14   2    0.000    0.000       0
     91  1    175 00:02:12.37   0.7540A  -2.3861  -1.1167   1.3873  0.064  0.67  -0.977E+00     50.  0.131E+01  0.436E-01  0.159E-02  0.127E-03   60   4   1   21  10  17    9  14   2    0.000    0.000       0
     92  1    176 00:02:13.12   0.7540A  -2.3862  -1.1043   1.3951  0.064  0.67  -0.977E+00     50.  0.131E+01  0.432E-01  0.158E-02  0.124E-03   60   4   1   22  10  16    9  14   2    0.000    0.000       0
     93  1    177 00:02:13.88   0.7540A  -2.3862  -1.1081   1.3991  0.064  0.67  -0.982E+00     50.  0.131E+01  0.429E-01  0.157E-02  0.122E-03   60   4   1   22  10  16    9  14   2    0.000    0.000       0
     94  1    178 00:02:14.63   0.7540A  -2.3863  -1.1008   1.3996  0.064  0.67  -0.998E+00     50.  0.131E+01  0.426E-01  0.156E-02  0.119E-03   60   3  19   22  10  16    9  14   2    0.000    0.000       0
     95  1    179 00:02:15.38   0.7540A  -2.3864  -1.0795   1.3969  0.063  0.68  -0.106E+01     50.  0.131E+01  0.423E-01  0.155E-02  0.117E-03   60   3  18   22  10  16    9  14   2    0.000    0.000       0
     96  1    180 00:02:16.14   0.7540A  -2.3865  -1.0806   1.3917  0.063  0.68  -0.996E+00     50.  0.131E+01  0.419E-01  0.155E-02  0.115E-03   60   3  18   21   9  16    9  14   2    0.000    0.000       0
     97  1    181 00:02:16.89   0.7540A  -2.3865  -1.0686   1.3847  0.063  0.68  -0.997E+00     50.  0.131E+01  0.416E-01  0.154E-02  0.113E-03   60   2  16   21   9  16    9  14   2    0.000    0.000       0
     98  1    182 00:02:17.65   0.7540A  -2.3866  -1.0480   1.3764  0.063  0.68  -0.982E+00     50.  0.131E+01  0.414E-01  0.153E-02  0.112E-03   60   2  15   22   9  15    9  14   2    0.000    0.000       0
     99  1    183 00:02:18.40   0.7540A  -2.3867  -1.0460   1.3672  0.063  0.68  -0.965E+00     50.  0.131E+01  0.411E-01  0.153E-02  0.111E-03   60   2  15   22   9  15    9  14   2    0.000    0.000       0
     100  1    184 00:02:19.15   0.7540A  -2.3867  -1.0472   1.3574  0.063  0.69  -0.956E+00     52.  0.130E+01  0.408E-01  0.153E-02  0.110E-03   60   1  13   18   1  12    9  14   2    0.000    0.000       0
     101  1    185 00:02:19.91   0.7540A  -2.3868  -1.0554   1.3470  0.063  0.69  -0.951E+00     52.  0.130E+01  0.405E-01  0.152E-02  0.109E-03   60   1  12   18   1  12    9  14   2    0.000    0.000       0
     102  1    186 00:02:20.66   0.7540A  -2.3869  -1.0564   1.3360  0.063  0.69  -0.946E+00     52.  0.130E+01  0.403E-01  0.152E-02  0.108E-03   60   1  12   18   1  12    9  14   2    0.000    0.000       0
Note: See TracChangeset for help on using the changeset viewer.