Ignore:
Timestamp:
Jul 27, 2018 1:36:03 PM (6 years ago)
Author:
suehring
Message:

New Inifor features: grid stretching, improved command-interface, support start dates in different formats in both YYYYMMDD and YYYYMMDDHH, Ability to manually control input file prefixes (--radiation-prefix, --soil-preifx, --flow-prefix, --soilmoisture-prefix) for compatiblity with DWD forcast naming scheme; GNU-style short and long option; Prepared output of large-scale forcing profiles (no computation yet); Added preprocessor flag netcdf4 to switch output format between netCDF 3 and 4; Updated netCDF variable names and attributes to comply with PIDS v1.9; Inifor bugfixes: Improved compatibility with older Intel Intel compilers by avoiding implicit array allocation; Added origin_lon/_lat values and correct reference time in dynamic driver global attributes; corresponding PALM changes: adjustments to revised Inifor; variables names in dynamic driver adjusted; enable geostrophic forcing also in offline nested mode; variable names in LES-LES and COSMO offline nesting changed; lateral boundary flags for nesting, in- and outflow conditions renamed

File:
1 edited

Legend:

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

    r3016 r3182  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! Rename variables for boundary flags and nesting
    2323!
    2424! Former revisions:
     
    161161
    162162    USE control_parameters,                                                    &
    163         ONLY:  bc_lr_cyc, bc_ns_cyc, conserve_volume_flow, coupling_mode,      &
     163        ONLY:  bc_lr_cyc, bc_ns_cyc, bc_radiation_l, bc_radiation_n,           &
     164               bc_radiation_r, bc_radiation_s, child_domain,                   &
     165               conserve_volume_flow, coupling_mode,                            &
    164166               dt_3d, gathered_size, ibc_p_b, ibc_p_t,                         &
    165167               intermediate_timestep_count, intermediate_timestep_count_max,   &
    166                mg_switch_to_pe0_level, nest_domain, outflow_l, outflow_n,      &
    167                outflow_r, outflow_s, psolver, subdomain_size, topography,      &
    168                volume_flow, volume_flow_area, volume_flow_initial
     168               mg_switch_to_pe0_level, psolver, subdomain_size,                &
     169               topography, volume_flow, volume_flow_area, volume_flow_initial
    169170
    170171    USE cpulog,                                                                &
     
    219220    REAL(wp), DIMENSION(1:nzt) ::  w_l_l               !<
    220221
    221     LOGICAL :: nest_domain_nvn      !<
     222    LOGICAL :: child_domain_nvn      !<
    222223
    223224
     
    280281!
    281282!-- Left/right
    282     IF ( conserve_volume_flow  .AND.  ( outflow_l .OR. outflow_r ) )  THEN
     283    IF ( conserve_volume_flow  .AND.  ( bc_radiation_l .OR.                    &
     284                                        bc_radiation_r ) )  THEN
    283285
    284286       volume_flow(1)   = 0.0_wp
    285287       volume_flow_l(1) = 0.0_wp
    286288
    287        IF ( outflow_l )  THEN
     289       IF ( bc_radiation_l )  THEN
    288290          i = 0
    289        ELSEIF ( outflow_r )  THEN
     291       ELSEIF ( bc_radiation_r )  THEN
    290292          i = nx+1
    291293       ENDIF
     
    325327!
    326328!-- South/north
    327     IF ( conserve_volume_flow  .AND.  ( outflow_n .OR. outflow_s ) )  THEN
     329    IF ( conserve_volume_flow  .AND.  ( bc_radiation_n .OR. bc_radiation_s ) )  THEN
    328330
    329331       volume_flow(2)   = 0.0_wp
    330332       volume_flow_l(2) = 0.0_wp
    331333
    332        IF ( outflow_s )  THEN
     334       IF ( bc_radiation_s )  THEN
    333335          j = 0
    334        ELSEIF ( outflow_n )  THEN
     336       ELSEIF ( bc_radiation_n )  THEN
    335337          j = ny+1
    336338       ENDIF
     
    372374!-- used both at bottom and top boundary, and if not a nested domain in a
    373375!-- normal nesting run. In case of vertical nesting, this must be done.
    374 !-- Therefore an auxiliary logical variable nest_domain_nvn is used here, and
     376!-- Therefore an auxiliary logical variable child_domain_nvn is used here, and
    375377!-- nvn stands for non-vertical nesting.
    376378!-- This cannot be done before the first initial time step because ngp_2dh_outer
    377379!-- is not yet known then.
    378     nest_domain_nvn = nest_domain
    379     IF ( nest_domain .AND. nesting_mode == 'vertical' )  THEN
    380        nest_domain_nvn = .FALSE.
     380    child_domain_nvn = child_domain
     381    IF ( child_domain .AND. nesting_mode == 'vertical' )  THEN
     382       child_domain_nvn = .FALSE.
    381383    ENDIF
    382384
    383385    IF ( ibc_p_b == 1  .AND.  ibc_p_t == 1  .AND.                               &
    384          .NOT. nest_domain_nvn  .AND. intermediate_timestep_count /= 0 )        &
     386         .NOT. child_domain_nvn  .AND. intermediate_timestep_count /= 0 )       &
    385387    THEN
    386388       w_l = 0.0_wp;  w_l_l = 0.0_wp
     
    758760!-- height nzt after above modifications. Hint: w level nzt+1 does not impact
    759761!-- results.
    760     IF (nest_domain .OR. coupling_mode == 'vnested_fine') THEN
     762    IF ( child_domain  .OR.  coupling_mode == 'vnested_fine' ) THEN
    761763       w(nzt+1,:,:) = w(nzt,:,:)
    762764    ENDIF
Note: See TracChangeset for help on using the changeset viewer.