Ignore:
Timestamp:
Feb 19, 2020 8:16:04 PM (4 years ago)
Author:
suehring
Message:

Remove deprecated topography arrays; Move basic initialization of numerics into an extra module interface

File:
1 edited

Legend:

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

    r4360 r4414  
    2525! -----------------
    2626! $Id$
     27! Remove double-declared use only construct.
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Introduction of wall_flags_total_0, which currently sets bits based on static
    2831! topography information used in wall_flags_static_0
     
    8487
    8588    SUBROUTINE poismg_noopt( r )
    86    
    8789
    8890       USE arrays_3d,                                                          &
    8991           ONLY:  d, p_loc
    90 
    91        USE control_parameters,                                                 &
    92            ONLY:  bc_lr_cyc, bc_ns_cyc, gathered_size, grid_level_count,       &
    93                   ibc_p_t, maximum_grid_level, message_string, mgcycles,       &
    94                   mg_cycles, mg_switch_to_pe0_level, residual_limit,           &
    95                   subdomain_size
    9692
    9793       USE control_parameters,                                                 &
     
    16551651
    16561652       USE control_parameters,                                                 &
    1657            ONLY:  bc_lr_cyc, bc_ns_cyc, masking_method, maximum_grid_level
     1653           ONLY:  bc_lr_cyc, bc_ns_cyc, masking_method, maximum_grid_level,    &
     1654                  psolver
    16581655
    16591656       USE indices,                                                            &
     
    16781675
    16791676       INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  topo_tmp
     1677
     1678       IF ( psolver /= 'multigrid_noopt' )  RETURN
    16801679!
    16811680!--    Gridpoint increment of the current level.
Note: See TracChangeset for help on using the changeset viewer.