Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (6 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/data_output_2d.f90

    r2512 r2696  
    11!> @file data_output_2d.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2525! -----------------
    2626! $Id$
     27! Implementation of uv exposure model (FK)
     28! Implementation of turbulence_closure_mod (TG)
     29! Set fill values at topography grid points or e.g. non-natural-type surface
     30! in case of LSM output (MS)
     31!
     32! 2512 2017-10-04 08:26:59Z raasch
    2733! upper bounds of cross section output changed from nx+1,ny+1 to nx,ny
    2834! no output of ghost layer data
     
    196202               ntdim_2d_xy, ntdim_2d_xz, ntdim_2d_yz,                          &
    197203               psolver, section, simulated_time, simulated_time_chr,           &
    198                time_since_reference_point
     204               time_since_reference_point, uv_exposure
    199205       
    200206    USE cpulog,                                                                &
     
    205211       
    206212    USE indices,                                                               &
    207         ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nz, nzb, nzt
     213        ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nz, nzb, nzt, wall_flags_0
    208214               
    209215    USE kinds
     
    217223
    218224    USE netcdf_interface,                                                      &
    219         ONLY:  id_set_xy, id_set_xz, id_set_yz, id_var_do2d, id_var_time_xy,   &
    220                id_var_time_xz, id_var_time_yz, nc_stat, netcdf_data_format,    &
    221                netcdf_handle_error
     225        ONLY:  fill_value, id_set_xy, id_set_xz, id_set_yz, id_var_do2d,       &
     226               id_var_time_xy, id_var_time_xz, id_var_time_yz, nc_stat,        &
     227               netcdf_data_format, netcdf_handle_error
    222228
    223229    USE particle_attributes,                                                   &
     
    232238    USE surface_mod,                                                           &
    233239        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
     240
     241    USE turbulence_closure_mod,                                                &
     242        ONLY:  tcm_data_output_2d
     243
     244    USE uv_exposure_model_mod,                                                 &
     245        ONLY:  uvem_data_output_2d
     246
    234247
    235248    IMPLICIT NONE
     
    244257    INTEGER(iwp) ::  ngp       !<
    245258    INTEGER(iwp) ::  file_id   !<
     259    INTEGER(iwp) ::  flag_nr   !< number of masking flag
    246260    INTEGER(iwp) ::  i         !<
    247261    INTEGER(iwp) ::  if        !<
     
    457471          nzt_do = nzt+1
    458472!
     473!--       Before each output, set array local_pf to fill value
     474          local_pf = fill_value
     475!
     476!--       Set masking flag for topography for not resorted arrays
     477          flag_nr = 0
     478         
     479!
    459480!--       Store the array chosen on the temporary array.
    460481          resorted = .FALSE.
    461482          SELECT CASE ( TRIM( do2d(av,if) ) )
    462 
    463483             CASE ( 'e_xy', 'e_xz', 'e_yz' )
    464484                IF ( av == 0 )  THEN
     
    928948
    929949             CASE ( 'u_xy', 'u_xz', 'u_yz' )
     950                flag_nr = 1
    930951                IF ( av == 0 )  THEN
    931952                   to_be_resorted => u
     
    970991
    971992             CASE ( 'v_xy', 'v_xz', 'v_yz' )
     993                flag_nr = 2
    972994                IF ( av == 0 )  THEN
    973995                   to_be_resorted => v
     
    9921014
    9931015             CASE ( 'w_xy', 'w_xz', 'w_yz' )
     1016                flag_nr = 3
    9941017                IF ( av == 0 )  THEN
    9951018                   to_be_resorted => w
     
    10931116
    10941117!
     1118!--             Turbulence closure variables
     1119                IF ( .NOT. found )  THEN
     1120                   CALL tcm_data_output_2d( av, do2d(av,if), found, grid, mode,&
     1121                                             local_pf, two_d, nzb_do, nzt_do )
     1122                ENDIF
     1123
     1124!
    10951125!--             Radiation quantity
    10961126                IF ( .NOT. found  .AND.  radiation )  THEN
    10971127                   CALL radiation_data_output_2d( av, do2d(av,if), found, grid,&
    10981128                                                  mode, local_pf, two_d  )
     1129                ENDIF
     1130
     1131!
     1132!--             UV exposure model quantity
     1133                IF ( uv_exposure )  THEN
     1134                   CALL uvem_data_output_2d( av, do2d(av,if), found, grid, mode,&
     1135                                             local_pf, two_d, nzb_do, nzt_do )
    10991136                ENDIF
    11001137
     
    11271164
    11281165!
    1129 !--       Resort the array to be output, if not done above
     1166!--       Resort the array to be output, if not done above. Flag topography
     1167!--       grid points with fill values, using the corresponding maksing flag.
    11301168          IF ( .NOT. resorted )  THEN
    11311169             DO  i = nxl, nxr
    11321170                DO  j = nys, nyn
    11331171                   DO  k = nzb_do, nzt_do
    1134                       local_pf(i,j,k) = to_be_resorted(k,j,i)
     1172                      local_pf(i,j,k) = MERGE( to_be_resorted(k,j,i),          &
     1173                                               REAL( fill_value, KIND = wp ),  &
     1174                                               BTEST( wall_flags_0(k,j,i),     &
     1175                                                      flag_nr ) )
    11351176                   ENDDO
    11361177                ENDDO
Note: See TracChangeset for help on using the changeset viewer.