Changeset 1804 for palm/trunk/SOURCE


Ignore:
Timestamp:
Apr 5, 2016 4:30:18 PM (9 years ago)
Author:
maronga
Message:

removed parameter file check. update of mrungui for compilation with qt5

Location:
palm/trunk/SOURCE
Files:
2 deleted
13 edited

Legend:

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

    r1784 r1804  
    1111! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    1212!
    13 ! You should have received a copy of the GNU General Public License along with
     13! You should have received a copy of the GNU fGeneral Public License along with
    1414! PALM. If not, see <http://www.gnu.org/licenses/>.
    1515!
     
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    208208    IF ( openfile(file_id)%opened )  RETURN
    209209
    210 #if ! defined ( __check )
    211210!
    212211!-- Only certain files are allowed to be re-opened
     
    231230       END SELECT
    232231    ENDIF
    233 #endif
    234232
    235233!
     
    283281       CASE ( 11 )
    284282
    285 #if defined ( __check )
    286 !
    287 !--       In case of a prior parameter file check, the p3d data is stored in
    288 !--       PARIN, while the p3df is stored in PARINF. This only applies to
    289 !--       check_namelist_files!
    290           IF ( check_restart == 2 ) THEN
    291              OPEN ( 11, FILE='PARINF'//TRIM( coupling_char ),                  &
    292                         FORM='FORMATTED', STATUS='OLD' )
    293           ELSE
    294              OPEN ( 11, FILE='PARIN'//TRIM( coupling_char ), FORM='FORMATTED', &
    295                         STATUS='OLD' )
    296           END IF
    297 #else
    298 
    299283          OPEN ( 11, FILE='PARIN'//TRIM( coupling_char ), FORM='FORMATTED',    &
    300284                     STATUS='OLD' )
    301 #endif
    302285
    303286       CASE ( 13 )
     
    328311                CALL local_system( 'mkdir  BINOUT' // TRIM( coupling_char ) )
    329312             ENDIF
    330 #if defined( __parallel ) && ! defined ( __check )
     313#if defined( __parallel )
    331314!
    332315!--          Set a barrier in order to allow that all other processors in the
     
    371354                        FORM='UNFORMATTED', POSITION='APPEND' )
    372355          ELSE
    373 #if defined( __parallel ) && ! defined ( __check )
     356#if defined( __parallel )
    374357!
    375358!--          Set a barrier in order to allow that all other processors in the
     
    563546                                   TRIM( coupling_char ) )
    564547             ENDIF
    565 #if defined( __parallel ) && ! defined ( __check )
     548#if defined( __parallel )
    566549!
    567550!--          Set a barrier in order to allow that thereafter all other
     
    615598                                   TRIM( coupling_char ) )
    616599             ENDIF
    617 #if defined( __parallel ) && ! defined ( __check )
     600#if defined( __parallel )
    618601!
    619602!--          Set a barrier in order to allow that thereafter all other
     
    673656                CALL netcdf_handle_error( 'check_open', 21 )
    674657                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
    675 #if defined( __parallel ) && ! defined ( __check )
     658#if defined( __parallel )
    676659!
    677660!--             Set a barrier in order to assure that PE0 deleted the old file
     
    735718                CALL netcdf_handle_error( 'check_open', 24 )
    736719                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
    737 #if defined( __parallel ) && ! defined ( __check )
     720#if defined( __parallel )
    738721!
    739722!--             Set a barrier in order to assure that PE0 deleted the old file
     
    797780                CALL netcdf_handle_error( 'check_open', 27 )
    798781                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
    799 #if defined( __parallel ) && ! defined ( __check )
     782#if defined( __parallel )
    800783!
    801784!--             Set a barrier in order to assure that PE0 deleted the old file
     
    940923                CALL netcdf_handle_error( 'check_open', 36 )
    941924                IF ( myid == 0 )  CALL local_system( 'rm ' // TRIM( filename ) )
    942 #if defined( __parallel ) && ! defined ( __check )
     925#if defined( __parallel )
    943926!
    944927!--             Set a barrier in order to assure that PE0 deleted the old file
     
    10571040                                       TRIM( coupling_char ) // '/' )
    10581041                ENDIF
    1059 #if defined( __parallel ) && ! defined ( __check )
     1042#if defined( __parallel )
    10601043!
    10611044!--             Set a barrier in order to allow that all other processors in the
  • palm/trunk/SOURCE/check_parameters.f90

    r1796 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    425425
    426426
    427 #if ! defined( __check )
    428427       IF ( myid == 0 ) THEN
    429428          CALL MPI_SEND( dt_coupling, 1, MPI_REAL, target_id, 11, comm_inter,  &
     
    433432       ENDIF
    434433       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    435 #endif     
     434
    436435       IF ( dt_coupling /= remote )  THEN
    437436          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
     
    441440       ENDIF
    442441       IF ( dt_coupling <= 0.0_wp )  THEN
    443 #if ! defined( __check )
     442
    444443          IF ( myid == 0  ) THEN
    445444             CALL MPI_SEND( dt_max, 1, MPI_REAL, target_id, 19, comm_inter, ierr )
     
    448447          ENDIF   
    449448          CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    450 #endif         
     449     
    451450          dt_coupling = MAX( dt_max, remote )
    452451          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
     
    455454          CALL message( 'check_parameters', 'PA0005', 0, 1, 0, 6, 0 )
    456455       ENDIF
    457 #if ! defined( __check )
     456
    458457       IF ( myid == 0 ) THEN
    459458          CALL MPI_SEND( restart_time, 1, MPI_REAL, target_id, 12, comm_inter, &
     
    463462       ENDIF
    464463       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    465 #endif     
     464 
    466465       IF ( restart_time /= remote )  THEN
    467466          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
     
    470469          CALL message( 'check_parameters', 'PA0006', 1, 2, 0, 6, 0 )
    471470       ENDIF
    472 #if ! defined( __check )
     471
    473472       IF ( myid == 0 ) THEN
    474473          CALL MPI_SEND( dt_restart, 1, MPI_REAL, target_id, 13, comm_inter,   &
     
    478477       ENDIF   
    479478       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    480 #endif     
     479   
    481480       IF ( dt_restart /= remote )  THEN
    482481          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
     
    487486
    488487       simulation_time_since_reference = end_time - coupling_start_time
    489 #if ! defined( __check )
     488
    490489       IF  ( myid == 0 ) THEN
    491490          CALL MPI_SEND( simulation_time_since_reference, 1, MPI_REAL, target_id, &
     
    495494       ENDIF
    496495       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    497 #endif     
     496   
    498497       IF ( simulation_time_since_reference /= remote )  THEN
    499498          WRITE( message_string, * ) 'coupling mode "', TRIM( coupling_mode ), &
     
    504503       ENDIF
    505504
    506 #if ! defined( __check )
    507505       IF ( myid == 0 ) THEN
    508506          CALL MPI_SEND( dx, 1, MPI_REAL, target_id, 15, comm_inter, ierr )
     
    512510       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    513511
    514 #endif
     512
    515513       IF ( coupling_mode == 'atmosphere_to_ocean') THEN
    516514
     
    531529       ENDIF
    532530
    533 #if ! defined( __check )
    534531       IF ( myid == 0) THEN
    535532          CALL MPI_SEND( dy, 1, MPI_REAL, target_id, 16, comm_inter, ierr )
     
    538535       ENDIF
    539536       CALL MPI_BCAST( remote, 1, MPI_REAL, 0, comm2d, ierr)
    540 #endif
     537
    541538       IF ( coupling_mode == 'atmosphere_to_ocean') THEN
    542539
     
    579576    ENDIF
    580577
    581 #if defined( __parallel ) && ! defined ( __check )
     578#if defined( __parallel )
    582579!
    583580!-- Exchange via intercommunicator
     
    38563853!
    38573854!-- Check the NetCDF data format
    3858 #if ! defined ( __check )
    38593855    IF ( netcdf_data_format > 2 )  THEN
    38603856#if defined( __netcdf4 )
     
    38793875#endif
    38803876    ENDIF
    3881 #endif
    38823877
    38833878!
  • palm/trunk/SOURCE/exchange_horiz.f90

    r1683 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    102102                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !<
    103103                       
    104 
    105 #if ! defined( __check )
    106104
    107105    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'start' )
     
    290288    CALL cpu_log( log_point_s(2), 'exchange_horiz', 'stop' )
    291289
    292 #endif
    293290 END SUBROUTINE exchange_horiz
    294291
     
    319316                        nxl-nbgp_local:nxr+nbgp_local) ::  ar  !< treated array
    320317
    321 #if ! defined( __check )
    322318
    323319#if defined( __parallel )
     
    386382
    387383#endif
    388 #endif
    389384
    390385
  • palm/trunk/SOURCE/exchange_horiz_2d.f90

    r1763 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    8686   
    8787
    88 #if ! defined( __check )
    8988    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
    9089
     
    181180    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
    182181
    183 #endif
    184182 END SUBROUTINE exchange_horiz_2d
    185183
     
    215213    INTEGER(iwp) ::  ar(nysg:nyng,nxlg:nxrg)  !<
    216214
    217 #if ! defined( __check )
    218215    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
    219216
     
    308305    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
    309306
    310 #endif
    311307 END SUBROUTINE exchange_horiz_2d_int
  • palm/trunk/SOURCE/init_grid.f90

    r1780 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    703703
    704704             ENDIF
    705 #if defined( __parallel ) && ! defined ( __check )
     705#if defined( __parallel )
    706706             CALL MPI_BARRIER( comm2d, ierr )
    707707#endif
     
    925925          ENDIF
    926926       ENDDO
    927 #if ! defined ( __check )
     927
    928928!
    929929!--    Exchange of lateral boundary values (parallel computers) and cyclic
     
    962962          ENDDO
    963963       ENDDO
    964 #endif
     964
    965965    ENDIF
    966966
    967 #if ! defined ( __check )
    968967!
    969968!-- Preliminary: to be removed after completion of the topography code!
     
    17361735                nzb_tmp, vertical_influence, wall_l, wall_n, wall_r, wall_s )
    17371736
    1738 #endif
    17391737
    17401738 END SUBROUTINE init_grid
  • palm/trunk/SOURCE/init_masks.f90

    r1784 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    444444!--    Set global masks along all three dimensions (required by
    445445!--    define_netcdf_header).
    446 #if defined( __parallel ) && ! defined ( __check )
     446#if defined( __parallel )
    447447!
    448448!--    PE0 receives partial arrays from all processors of the respective mask
     
    536536       ENDIF
    537537
    538 #elif ! defined ( __parallel )
     538#else
    539539!
    540540!--    Local arrays can be relocated directly.
  • palm/trunk/SOURCE/init_pegrid.f90

    r1780 r1804  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    267267
    268268
    269 #if ! defined( __check)
    270269!
    271270!-- Create the virtual processor grid
     
    293292    CALL MPI_COMM_RANK( comm1dy, myidy, ierr )
    294293
    295 #endif
    296294
    297295!
     
    489487
    490488
    491 #if ! defined( __check)
    492489!
    493490!-- Collect index bounds from other PEs (to be written to restart file later)
     
    520517    ENDIF
    521518
    522 #endif
    523519
    524520#if defined( __print )
     
    556552#endif
    557553
    558 #if defined( __parallel ) && ! defined( __check)
     554#if defined( __parallel )
    559555#if defined( __mpi2 )
    560556!
     
    897893
    898894          IF ( i == mg_switch_to_pe0_level )  THEN
    899 #if defined( __parallel ) && ! defined( __check )
     895#if defined( __parallel )
    900896!
    901897!--          Save the grid size of the subdomain at the switch level, because
     
    930926                              ( nzt_l - nzb + 2 )
    931927
    932 #elif ! defined ( __parallel )
     928#else
    933929             message_string = 'multigrid gather/scatter impossible ' // &
    934930                          'in non parallel mode'
     
    972968    grid_level = 0
    973969
    974 #if defined( __parallel ) && ! defined ( __check )
     970#if defined( __parallel )
    975971!
    976972!-- Gridpoint number for the exchange of ghost points (y-line for 2D-arrays)
     
    10681064#endif
    10691065
    1070 #if defined( __parallel ) && ! defined ( __check )
     1066#if defined( __parallel )
    10711067!
    10721068!-- Setting of flags for inflow/outflow/nesting conditions in case of non-cyclic
     
    11381134    CALL location_message( 'finished', .TRUE. )
    11391135
    1140 #elif ! defined ( __parallel )
     1136#else
    11411137    IF ( bc_lr == 'dirichlet/radiation' )  THEN
    11421138       inflow_l  = .TRUE.
  • palm/trunk/SOURCE/local_stop.f90

    r1765 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    6868        ONLY:  nested_run
    6969
    70 #if defined( __parallel ) && ! defined ( __check )
     70#if defined( __parallel )
    7171    IF ( coupling_mode == 'uncoupled' )  THEN
    7272       IF ( nested_run )  THEN
  • palm/trunk/SOURCE/modules.f90

    r1789 r1804  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    687687                     subs_vertical_gradient_level_i(10) = -9999
    688688
    689 #if defined ( __check )
    690     INTEGER(iwp) :: check_restart = 0
    691 #endif
    692689
    693690    INTEGER(iwp), DIMENSION(0:1) :: ntdim_2d_xy, ntdim_2d_xz, ntdim_2d_yz, ntdim_3d
     
    11761173    USE kinds
    11771174
    1178 #if defined( __parallel ) && ! defined ( __check )
     1175#if defined( __parallel )
    11791176#if defined( __lc )
    11801177    USE MPI
     
    12111208
    12121209    INTEGER(iwp) ::  ibuf(12), pcoord(2)
    1213 
    1214 #if ! defined ( __check )
    12151210    INTEGER(iwp) ::  status(MPI_STATUS_SIZE)
    12161211    INTEGER(iwp), DIMENSION(MPI_STATUS_SIZE,100) ::  wait_stat
    1217 #endif
    12181212
    12191213    INTEGER(iwp) :: ngp_yz_int, type_xz_int, type_yz_int
  • palm/trunk/SOURCE/parin.f90

    r1784 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    363363          READ ( 11, inipar, ERR=10, END=11 )
    364364
    365 #if defined ( __check )
    366 !
    367 !--       In case of a namelist file check, &inipar from the p3d file is
    368 !--       used. The p3d file here must be closed and the p3df file for reading
    369 !--       3dpar is opened.
    370           IF ( check_restart == 1 )  THEN
    371              CALL close_file( 11 )
    372              check_restart = 2
    373              CALL check_open( 11 )             
    374              initializing_actions = 'read_restart_data'
    375           ENDIF
    376 #endif
    377365          GOTO 12
    378366
     
    389377!--       check_open)
    390378 12       IF ( TRIM( initializing_actions ) == 'read_restart_data' )  THEN
    391 #if ! defined ( __check )
    392379             CALL read_var_list
    393380!
     
    398385!--          Increment the run count
    399386             runnr = runnr + 1
    400 #endif
    401387          ENDIF
    402388
     
    510496
    511497       ENDIF
    512 #if defined( __parallel ) && ! ( __check )
     498#if defined( __parallel )
    513499       CALL MPI_BARRIER( MPI_COMM_WORLD, ierr )
    514500#endif
  • palm/trunk/SOURCE/poisfft.f90

    r1683 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    150150    PRIVATE
    151151
    152 #if ! defined ( __check )
    153152    PUBLIC  poisfft, poisfft_init
    154153
     
    160159       MODULE PROCEDURE poisfft_init
    161160    END INTERFACE poisfft_init
    162 #else
    163     PUBLIC  poisfft_init
    164 
    165     INTERFACE poisfft_init
    166        MODULE PROCEDURE poisfft_init
    167     END INTERFACE poisfft_init
    168 #endif
     161
    169162
    170163 CONTAINS
     
    196189
    197190
    198 #if ! defined ( __check )
     191
    199192!------------------------------------------------------------------------------!
    200193! Description:
     
    14991492    END SUBROUTINE ffty_tri_ffty
    15001493
    1501 #endif
    1502 
    15031494 END MODULE poisfft_mod
  • palm/trunk/SOURCE/tridia_solver.f90

    r1683 r1804  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    130130!
    131131!--    Calculate constant coefficients of the tridiagonal matrix
    132 #if ! defined ( __check )
    133132       CALL maketri
    134133       CALL split
    135 #endif
    136134
    137135    END SUBROUTINE tridia_init
  • palm/trunk/SOURCE/user_statistics.f90

    r1784 r1804  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Removed code for parameter file check (__check)
    2222!
    2323! Former revisions:
     
    140140!--           value on all PEs, you can omit the MPI_ALLREDUCE call and
    141141!--           assign ts_value(dots_num_palm+1:,sr) = ts_value_l directly.
    142 !#if defined( __parallel ) && ! defined ( __check )
     142!#if defined( __parallel )
    143143!       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    144144!       CALL MPI_ALLREDUCE( ts_value_l(dots_num_palm+1),                         &
Note: See TracChangeset for help on using the changeset viewer.