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/poismg_noopt_mod.f90

    r2939 r3182  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Rename variables in mesoscale-offline nesting mode
    2323!
    2424! Former revisions:
     
    165165 
    166166    USE control_parameters,                                                    &
    167         ONLY:  grid_level, force_bound_l, force_bound_n, force_bound_r,        &
    168                force_bound_s, forcing, inflow_l, inflow_n, inflow_r, inflow_s, &
    169                nest_bound_l, nest_bound_n, nest_bound_r, nest_bound_s,         &
    170                outflow_l, outflow_n, outflow_r, outflow_s
     167        ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,                 &
     168               bc_dirichlet_s, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
     169               bc_radiation_s, child_domain, grid_level, nesting_offline
    171170
    172171    USE cpulog,                                                                &
     
    261260!--    Set lateral boundary conditions in non-cyclic case
    262261       IF ( .NOT. bc_lr_cyc )  THEN
    263           IF ( inflow_l .OR. outflow_l .OR. nest_bound_l .OR. force_bound_l )  &
     262          IF ( bc_dirichlet_l   .OR.  bc_radiation_l )                         &
    264263             d(:,:,nxl-1) = d(:,:,nxl)
    265           IF ( inflow_r .OR. outflow_r .OR. nest_bound_r .OR. force_bound_r )  &
     264          IF ( bc_dirichlet_r   .OR.  bc_radiation_r )                         &
    266265             d(:,:,nxr+1) = d(:,:,nxr)
    267266       ENDIF
    268267       IF ( .NOT. bc_ns_cyc )  THEN
    269           IF ( inflow_n .OR. outflow_n .OR. nest_bound_n .OR. force_bound_n )  &
     268          IF ( bc_dirichlet_n   .OR.  bc_radiation_n )                         &
    270269             d(:,nyn+1,:) = d(:,nyn,:)
    271           IF ( inflow_s .OR. outflow_s .OR. nest_bound_s .OR. force_bound_s )  &
     270          IF ( bc_dirichlet_s   .OR.  bc_radiation_s )                         &
    272271             d(:,nys-1,:) = d(:,nys,:)
    273272       ENDIF
     
    442441
    443442       IF ( .NOT. bc_lr_cyc )  THEN
    444           IF ( inflow_l .OR. outflow_l .OR. nest_bound_l .OR. force_bound_l )  THEN
     443          IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
    445444             r(:,:,nxl_mg(l)-1) = r(:,:,nxl_mg(l))
    446445          ENDIF
    447           IF ( inflow_r .OR. outflow_r .OR. nest_bound_r .OR. force_bound_r )  THEN
     446          IF ( bc_dirichlet_r  .OR.  bc_radiation_r )  THEN
    448447             r(:,:,nxr_mg(l)+1) = r(:,:,nxr_mg(l))
    449448          ENDIF
     
    451450
    452451       IF ( .NOT. bc_ns_cyc )  THEN
    453           IF ( inflow_n .OR. outflow_n .OR. nest_bound_n .OR. force_bound_n )  THEN
     452          IF ( bc_dirichlet_n  .OR.  bc_radiation_n )  THEN
    454453             r(:,nyn_mg(l)+1,:) = r(:,nyn_mg(l),:)
    455454          ENDIF
    456           IF ( inflow_s .OR. outflow_s .OR. nest_bound_s .OR. force_bound_s )  THEN
     455          IF ( bc_dirichlet_s  .OR.  bc_radiation_s )  THEN
    457456             r(:,nys_mg(l)-1,:) = r(:,nys_mg(l),:)
    458457          ENDIF
     
    657656
    658657       IF ( .NOT. bc_lr_cyc )  THEN
    659           IF ( inflow_l .OR. outflow_l .OR. nest_bound_l .OR. force_bound_l )  THEN
     658          IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
    660659             f_mg(:,:,nxl_mg(l)-1) = f_mg(:,:,nxl_mg(l))
    661660          ENDIF
    662           IF ( inflow_r .OR. outflow_r .OR. nest_bound_r .OR. force_bound_r )  THEN
     661          IF ( bc_dirichlet_r  .OR.  bc_radiation_r )  THEN
    663662             f_mg(:,:,nxr_mg(l)+1) = f_mg(:,:,nxr_mg(l))
    664663          ENDIF
     
    666665
    667666       IF ( .NOT. bc_ns_cyc )  THEN
    668           IF ( inflow_n .OR. outflow_n .OR. nest_bound_n .OR. force_bound_n )  THEN
     667          IF ( bc_dirichlet_n  .OR.  bc_radiation_n )  THEN
    669668             f_mg(:,nyn_mg(l)+1,:) = f_mg(:,nyn_mg(l),:)
    670669          ENDIF
    671           IF ( inflow_s .OR. outflow_s .OR. nest_bound_s .OR. force_bound_s )  THEN
     670          IF ( bc_dirichlet_s  .OR.  bc_radiation_s )  THEN
    672671             f_mg(:,nys_mg(l)-1,:) = f_mg(:,nys_mg(l),:)
    673672          ENDIF
     
    770769
    771770    IF ( .NOT. bc_lr_cyc )  THEN
    772        IF ( inflow_l .OR. outflow_l .OR. nest_bound_l .OR. force_bound_l )  THEN
     771       IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
    773772          temp(:,:,nxl_mg(l)-1) = temp(:,:,nxl_mg(l))
    774773       ENDIF
    775        IF ( inflow_r .OR. outflow_r .OR. nest_bound_r .OR. force_bound_r )  THEN
     774       IF ( bc_dirichlet_r  .OR.  bc_radiation_r )  THEN
    776775          temp(:,:,nxr_mg(l)+1) = temp(:,:,nxr_mg(l))
    777776       ENDIF
     
    779778
    780779    IF ( .NOT. bc_ns_cyc )  THEN
    781        IF ( inflow_n .OR. outflow_n .OR. nest_bound_n .OR. force_bound_n )  THEN
     780       IF ( bc_dirichlet_n  .OR.  bc_radiation_n )  THEN
    782781          temp(:,nyn_mg(l)+1,:) = temp(:,nyn_mg(l),:)
    783782       ENDIF
    784        IF ( inflow_s .OR. outflow_s .OR. nest_bound_s .OR. force_bound_s )  THEN
     783       IF ( bc_dirichlet_s  .OR.  bc_radiation_s )  THEN
    785784          temp(:,nys_mg(l)-1,:) = temp(:,nys_mg(l),:)
    786785       ENDIF
     
    12001199
    12011200             IF ( .NOT. bc_lr_cyc )  THEN
    1202                 IF ( inflow_l .OR. outflow_l .OR. nest_bound_l .OR. force_bound_l )  THEN
     1201                IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
    12031202                   p_mg(:,:,nxl_mg(l)-1) = p_mg(:,:,nxl_mg(l))
    12041203                ENDIF
    1205                 IF ( inflow_r .OR. outflow_r .OR. nest_bound_r .OR. force_bound_r )  THEN
     1204                IF ( bc_dirichlet_r  .OR.  bc_radiation_r )  THEN
    12061205                   p_mg(:,:,nxr_mg(l)+1) = p_mg(:,:,nxr_mg(l))
    12071206                ENDIF
     
    12091208
    12101209             IF ( .NOT. bc_ns_cyc )  THEN
    1211                 IF ( inflow_n .OR. outflow_n .OR. nest_bound_n .OR. force_bound_n )  THEN
     1210                IF ( bc_dirichlet_n  .OR.  bc_radiation_n )  THEN
    12121211                   p_mg(:,nyn_mg(l)+1,:) = p_mg(:,nyn_mg(l),:)
    12131212                ENDIF
    1214                 IF ( inflow_s .OR. outflow_s .OR. nest_bound_s .OR. force_bound_s )  THEN
     1213                IF ( bc_dirichlet_s  .OR.  bc_radiation_s )  THEN
    12151214                   p_mg(:,nys_mg(l)-1,:) = p_mg(:,nys_mg(l),:)
    12161215                ENDIF
     
    14221421                  gamma_mg, grid_level_count, ibc_p_b, ibc_p_t,                &
    14231422                  maximum_grid_level,                                          &
    1424                   mg_switch_to_pe0_level, mg_switch_to_pe0, nest_domain, ngsrb
     1423                  mg_switch_to_pe0_level, mg_switch_to_pe0, ngsrb
    14251424
    14261425
     
    15621561!--          because then they have the total domain.
    15631562             IF ( bc_lr_dirrad )  THEN
    1564                 inflow_l  = .TRUE.
    1565                 inflow_r  = .FALSE.
    1566                 outflow_l = .FALSE.
    1567                 outflow_r = .TRUE.
     1563                bc_dirichlet_l  = .TRUE.
     1564                bc_dirichlet_r  = .FALSE.
     1565                bc_radiation_l = .FALSE.
     1566                bc_radiation_r = .TRUE.
    15681567             ELSEIF ( bc_lr_raddir )  THEN
    1569                 inflow_l  = .FALSE.
    1570                 inflow_r  = .TRUE.
    1571                 outflow_l = .TRUE.
    1572                 outflow_r = .FALSE.
    1573              ELSEIF ( nest_domain )  THEN
    1574                 nest_bound_l = .TRUE.
    1575                 nest_bound_r = .TRUE.
    1576              ELSEIF ( forcing )  THEN
    1577                 force_bound_l = .TRUE.
    1578                 force_bound_r = .TRUE.
     1568                bc_dirichlet_l  = .FALSE.
     1569                bc_dirichlet_r  = .TRUE.
     1570                bc_radiation_l = .TRUE.
     1571                bc_radiation_r = .FALSE.
     1572             ELSEIF ( child_domain  .OR.  nesting_offline )  THEN
     1573                bc_dirichlet_l = .TRUE.
     1574                bc_dirichlet_r = .TRUE.
    15791575             ENDIF
    15801576
    15811577             IF ( bc_ns_dirrad )  THEN
    1582                 inflow_n  = .TRUE.
    1583                 inflow_s  = .FALSE.
    1584                 outflow_n = .FALSE.
    1585                 outflow_s = .TRUE.
     1578                bc_dirichlet_n  = .TRUE.
     1579                bc_dirichlet_s  = .FALSE.
     1580                bc_radiation_n = .FALSE.
     1581                bc_radiation_s = .TRUE.
    15861582             ELSEIF ( bc_ns_raddir )  THEN
    1587                 inflow_n  = .FALSE.
    1588                 inflow_s  = .TRUE.
    1589                 outflow_n = .TRUE.
    1590                 outflow_s = .FALSE.
    1591              ELSEIF ( nest_domain )  THEN
    1592                 nest_bound_s = .TRUE.
    1593                 nest_bound_n = .TRUE.
    1594              ELSEIF ( forcing )  THEN
    1595                 force_bound_s = .TRUE.
    1596                 force_bound_n = .TRUE.
     1583                bc_dirichlet_n  = .FALSE.
     1584                bc_dirichlet_s  = .TRUE.
     1585                bc_radiation_n = .TRUE.
     1586                bc_radiation_s = .FALSE.
     1587             ELSEIF ( child_domain  .OR.  nesting_offline )  THEN
     1588                bc_dirichlet_s = .TRUE.
     1589                bc_dirichlet_n = .TRUE.
    15971590             ENDIF
    15981591
     
    16551648!--          For non-cyclic lateral boundary conditions and in case of nesting,
    16561649!--          restore the in-/outflow conditions.
    1657              inflow_l  = .FALSE.;  inflow_r  = .FALSE.
    1658              inflow_n  = .FALSE.;  inflow_s  = .FALSE.
    1659              outflow_l = .FALSE.;  outflow_r = .FALSE.
    1660              outflow_n = .FALSE.;  outflow_s = .FALSE.
    1661 !
    1662 !--          In case of nesting, restore lateral boundary conditions
    1663              IF ( nest_domain )  THEN
    1664                 nest_bound_l = .FALSE.
    1665                 nest_bound_r = .FALSE.
    1666                 nest_bound_s = .FALSE.
    1667                 nest_bound_n = .FALSE.     
    1668              ENDIF
    1669              IF ( forcing )  THEN
    1670                 force_bound_l = .FALSE.
    1671                 force_bound_r = .FALSE.
    1672                 force_bound_s = .FALSE.
    1673                 force_bound_n = .FALSE.     
    1674              ENDIF
     1650             bc_dirichlet_l = .FALSE.;  bc_dirichlet_r = .FALSE.
     1651             bc_dirichlet_n = .FALSE.;  bc_dirichlet_s = .FALSE.
     1652             bc_radiation_l = .FALSE.;  bc_radiation_r = .FALSE.
     1653             bc_radiation_n = .FALSE.;  bc_radiation_s = .FALSE.
    16751654
    16761655             IF ( pleft == MPI_PROC_NULL )  THEN
    1677                 IF ( bc_lr_dirrad )  THEN
    1678                    inflow_l  = .TRUE.
     1656                IF ( bc_lr_dirrad  .OR.  child_domain  .OR.  nesting_offline )  &
     1657                THEN
     1658                   bc_dirichlet_l = .TRUE.
    16791659                ELSEIF ( bc_lr_raddir )  THEN
    1680                    outflow_l = .TRUE.
    1681                 ELSEIF ( nest_domain )  THEN
    1682                    nest_bound_l = .TRUE.
    1683                 ELSEIF ( forcing )  THEN
    1684                    force_bound_l = .TRUE.
     1660                   bc_radiation_l = .TRUE.
    16851661                ENDIF
    16861662             ENDIF
     
    16881664             IF ( pright == MPI_PROC_NULL )  THEN
    16891665                IF ( bc_lr_dirrad )  THEN
    1690                    outflow_r = .TRUE.
    1691                 ELSEIF ( bc_lr_raddir )  THEN
    1692                    inflow_r  = .TRUE.
    1693                 ELSEIF ( nest_domain )  THEN
    1694                    nest_bound_r = .TRUE.
    1695                 ELSEIF ( forcing )  THEN
    1696                    force_bound_r = .TRUE.
     1666                   bc_radiation_r = .TRUE.
     1667                ELSEIF ( bc_lr_raddir  .OR.  child_domain  .OR.                 &
     1668                         nesting_offline )  THEN
     1669                   bc_dirichlet_r = .TRUE.
    16971670                ENDIF
    16981671             ENDIF
     
    17001673             IF ( psouth == MPI_PROC_NULL )  THEN
    17011674                IF ( bc_ns_dirrad )  THEN
    1702                    outflow_s = .TRUE.
    1703                 ELSEIF ( bc_ns_raddir )  THEN
    1704                    inflow_s  = .TRUE.
    1705                 ELSEIF ( nest_domain )  THEN
    1706                    nest_bound_s = .TRUE.
    1707                 ELSEIF ( forcing )  THEN
    1708                    force_bound_s = .TRUE.
     1675                   bc_radiation_s = .TRUE.
     1676                ELSEIF ( bc_ns_raddir  .OR.  child_domain  .OR.                 &
     1677                         nesting_offline )  THEN
     1678                   bc_dirichlet_s = .TRUE.
    17091679                ENDIF
    17101680             ENDIF
    17111681
    17121682             IF ( pnorth == MPI_PROC_NULL )  THEN
    1713                 IF ( bc_ns_dirrad )  THEN
    1714                    inflow_n  = .TRUE.
     1683                IF ( bc_ns_dirrad  .OR.  child_domain  .OR.  nesting_offline )  &
     1684                THEN
     1685                   bc_dirichlet_n = .TRUE.
    17151686                ELSEIF ( bc_ns_raddir )  THEN
    1716                    outflow_n = .TRUE.
    1717                 ELSEIF ( nest_domain )  THEN
    1718                    nest_bound_n = .TRUE.
    1719                 ELSEIF ( forcing )  THEN
    1720                    force_bound_n = .TRUE.
     1687                   bc_radiation_n = .TRUE.
    17211688                ENDIF
    17221689             ENDIF
     
    18971864!--          Set non-cyclic boundary conditions on respective multigrid level
    18981865             IF ( .NOT. bc_ns_cyc )  THEN
    1899                 IF ( inflow_s  .OR.  outflow_s  .OR.  nest_bound_s  .OR.       &
    1900                      force_bound_s )  THEN
     1866                IF ( bc_dirichlet_s  .OR.  bc_radiation_s )  THEN
    19011867!                    topo_tmp(:,-2,:) = topo_tmp(:,0,:)
    19021868                   topo_tmp(:,-1,:) = topo_tmp(:,0,:)
    19031869                ENDIF
    1904                 IF ( inflow_n  .OR.  outflow_n  .OR.  nest_bound_n  .OR.       &
    1905                      force_bound_n )  THEN
     1870                IF ( bc_dirichlet_n  .OR.  bc_radiation_n )  THEN
    19061871!                    topo_tmp(:,nyn_l+2,:) = topo_tmp(:,nyn_l,:)
    19071872                   topo_tmp(:,nyn_l+1,:) = topo_tmp(:,nyn_l,:)
     
    19091874             ENDIF
    19101875             IF ( .NOT. bc_lr_cyc )  THEN
    1911                 IF ( inflow_l  .OR.  outflow_l  .OR.  nest_bound_l  .OR.       &
    1912                      force_bound_l )  THEN
     1876                IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
    19131877!                    topo_tmp(:,:,-2) = topo_tmp(:,:,0)
    19141878                   topo_tmp(:,:,-1) = topo_tmp(:,:,0)
    19151879                ENDIF
    1916                 IF ( inflow_r  .OR.  outflow_r  .OR.  nest_bound_r  .OR.       &
    1917                      force_bound_r )  THEN
     1880                IF ( bc_dirichlet_r  .OR.  bc_radiation_r )  THEN
    19181881!                    topo_tmp(:,:,nxr_l+2) = topo_tmp(:,:,nxr_l)     
    19191882                   topo_tmp(:,:,nxr_l+1) = topo_tmp(:,:,nxr_l)   
Note: See TracChangeset for help on using the changeset viewer.