Ignore:
Timestamp:
Jan 15, 2020 11:10:51 AM (4 years ago)
Author:
gronemeier
Message:

bugfix: set fill value for output according to wall_flags_total_0 for non-terrain following output

File:
1 edited

Legend:

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

    r4360 r4377  
    2020! Current revisions:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! bugfix: set fill value for output according to wall_flags_total_0 for
     28!         non-terrain following output
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Introduction of wall_flags_total_0, which currently sets bits based on static
    2832! topography information used in wall_flags_static_0
    29 ! 
     33!
    3034! 4331 2019-12-10 18:25:02Z suehring
    3135! Formatting adjustment
    32 ! 
     36!
    3337! 4329 2019-12-10 15:46:36Z motisi
    3438! Renamed wall_flags_0 to wall_flags_static_0
    35 ! 
     39!
    3640! 4246 2019-09-30 09:27:52Z pavelkrc
    3741! Corrected "Former revisions" section
    38 ! 
     42!
    3943! 4168 2019-08-16 13:50:17Z suehring
    4044! Remove variable grid
    41 ! 
     45!
    4246! 4167 2019-08-16 11:01:48Z suehring
    43 ! Changed behaviour of masked output over surface to follow terrain and ignore 
     47! Changed behaviour of masked output over surface to follow terrain and ignore
    4448! buildings (J.Resler, T.Gronemeier)
    45 ! 
     49!
    4650! 4069 2019-07-01 14:05:51Z Giersch
    47 ! Masked output running index mid has been introduced as a local variable to 
    48 ! avoid runtime error (Loop variable has been modified) in time_integration 
    49 ! 
     51! Masked output running index mid has been introduced as a local variable to
     52! avoid runtime error (Loop variable has been modified) in time_integration
     53!
    5054! 4039 2019-06-18 10:32:41Z suehring
    5155! Modularize diagnostic output
    52 ! 
     56!
    5357! 3994 2019-05-22 18:08:09Z suehring
    5458! output of turbulence intensity added
    55 ! 
     59!
    5660! 3665 2019-01-10 08:28:24Z raasch
    5761! unused variables removed
    58 ! 
     62!
    5963! 3655 2019-01-07 16:51:22Z knoop
    6064! Fix output time levels (use time_since_reference_point)
     
    6973 SUBROUTINE data_output_mask( av, mid )
    7074
    71  
     75
    7276
    7377#if defined( __netcdf )
     
    7983        ONLY:  e_av, lpt_av, nc_av, nr_av, p_av, pc_av, pr_av, pt_av, q_av,    &
    8084               qc_av, ql_av, ql_c_av, ql_v_av, ql_vp_av, qv_av, qr_av,         &
    81                rho_ocean_av, s_av, sa_av, u_av, v_av, vpt_av, w_av 
     85               rho_ocean_av, s_av, sa_av, u_av, v_av, vpt_av, w_av
    8286
    8387    USE basic_constants_and_equations_mod,                                     &
     
    9498               time_since_reference_point
    9599
    96     USE diagnostic_output_quantities_mod,                                      & 
     100    USE diagnostic_output_quantities_mod,                                      &
    97101        ONLY:  doq_output_mask
    98                
     102
    99103    USE cpulog,                                                                &
    100104        ONLY:  cpu_log, log_point
     
    107111    USE bulk_cloud_model_mod,                                                  &
    108112        ONLY:  bulk_cloud_model
    109    
     113
    110114    USE NETCDF
    111    
     115
    112116    USE netcdf_interface,                                                      &
    113117        ONLY:  fill_value, id_set_mask, id_var_domask, id_var_time_mask,       &
    114118               nc_stat, netcdf_data_format, netcdf_handle_error
    115    
     119
    116120    USE particle_attributes,                                                   &
    117121        ONLY:  grid_particles, number_of_particles, particles,                 &
    118122               particle_advection_start, prt_count
    119    
     123
    120124    USE pegrid
    121125
     
    124128
    125129    USE salsa_mod,                                                             &
    126         ONLY:  salsa_data_output_mask     
     130        ONLY:  salsa_data_output_mask
    127131
    128132
     
    131135    INTEGER(iwp) ::  av                      !< flag for (non-)average output
    132136    INTEGER(iwp) ::  ngp                     !< number of grid points of an output slice
     137    INTEGER(iwp) ::  flag_nr                 !< number of masking flag
    133138    INTEGER(iwp) ::  i                       !< loop index
    134139    INTEGER(iwp) ::  ivar                    !< variable index
     
    151156    REAL(wp) ::  s_r2      !< sum( particle-radius**2 )
    152157    REAL(wp) ::  s_r3      !< sum( particle-radius**3 )
    153    
     158
    154159    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf    !< output array
    155160#if defined( __parallel )
     
    175180    IF ( myid == 0  .OR.  netcdf_data_format > 4 )  THEN
    176181       CALL check_open( 200+mid+av*max_masks )
    177     ENDIF 
     182    ENDIF
    178183
    179184!
     
    210215                             mask_size_l(mid,3)) )
    211216       ENDIF
     217!
     218!--    Set masking flag for topography for not resorted arrays
     219       flag_nr = 0
    212220!
    213221!--    Store the variable chosen.
     
    397405                         ENDDO
    398406                      ENDDO
    399                    ENDIF                   
     407                   ENDIF
    400408                   resorted = .TRUE.
    401409                ENDIF
     
    567575
    568576          CASE ( 'u' )
     577             flag_nr = 1
    569578             IF ( av == 0 )  THEN
    570579                to_be_resorted => u
     
    574583
    575584          CASE ( 'v' )
     585             flag_nr = 2
    576586             IF ( av == 0 )  THEN
    577587                to_be_resorted => v
     
    588598
    589599          CASE ( 'w' )
     600             flag_nr = 3
    590601             IF ( av == 0 )  THEN
    591602                to_be_resorted => w
     
    621632                CALL salsa_data_output_mask( av, domask(mid,av,ivar), found,   &
    622633                                             local_pf, mid )
    623              ENDIF         
     634             ENDIF
    624635!
    625636!--          User defined quantity
     
    648659                DO  j = 1, mask_size_l(mid,2)
    649660                   DO  k = 1, mask_size_l(mid,3)
    650                       local_pf(i,j,k) =  to_be_resorted(mask_k(mid,k), &
    651                                          mask_j(mid,j),mask_i(mid,i))
     661                      local_pf(i,j,k) = MERGE( to_be_resorted(mask_k(mid,k),  &
     662                                                              mask_j(mid,j),  &
     663                                                              mask_i(mid,i)), &
     664                                               REAL( fill_value, KIND = wp ), &
     665                                               BTEST( wall_flags_total_0(     &
     666                                                              mask_k(mid,k),  &
     667                                                              mask_j(mid,j),  &
     668                                                              mask_i(mid,i)), &
     669                                                      flag_nr ) )
    652670                   ENDDO
    653671                ENDDO
     
    705723!--       (1) b. Conventional I/O only through PE0
    706724!--       PE0 receives partial arrays from all processors of the respective mask
    707 !--       and outputs them. Here a barrier has to be set, because otherwise 
     725!--       and outputs them. Here a barrier has to be set, because otherwise
    708726!--       "-MPI- FATAL: Remote protocol queue full" may occur.
    709727          CALL MPI_BARRIER( comm2d, ierr )
Note: See TracChangeset for help on using the changeset viewer.