Ignore:
Timestamp:
Oct 26, 2018 6:25:44 PM (5 years ago)
Author:
gronemeier
Message:

new: terrain-following masked output; bugfixes: increase vertical dimension of gamma_w_green_sat by 1, add checks for masked output for chemistry_model and radiation_model, reordered calls to xxx_define_netcdf_grid in masked output part

File:
1 edited

Legend:

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

    r3422 r3435  
    2525! -----------------
    2626! $Id$
     27! +mask_k_over_surface, mask_surface
     28!
     29! 3422 2018-10-24 19:01:57Z gronemeier
    2730! bugfix: increase number of blanks in output string
    2831!
     
    12831286    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_j_global  !< global grid index of masked output point on y-dimension
    12841287    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mask_k_global  !< global grid index of masked output point on z-dimension
     1288
     1289    INTEGER(iwp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_k_over_surface = -1  !< namelist parameter, k index of height over surface
    12851290
    12861291    LOGICAL ::  agent_time_unlimited = .FALSE.                   !< namelist parameter
     
    13931398    LOGICAL ::  data_output_xz(0:1) = .FALSE.                !< output of xz cross-section data?
    13941399    LOGICAL ::  data_output_yz(0:1) = .FALSE.                !< output of yz cross-section data?
     1400
     1401    LOGICAL, DIMENSION(max_masks) ::  mask_surface = .FALSE.      !< flag for surface-following masked output
    13951402
    13961403    REAL(wp) ::  advected_distance_x = 0.0_wp                  !< advected distance of model domain along x
Note: See TracChangeset for help on using the changeset viewer.