Changeset 1815 for palm/trunk


Ignore:
Timestamp:
Apr 6, 2016 1:49:59 PM (8 years ago)
Author:
raasch
Message:

cpp-switches removed + cpp-bugfixes + zero-settings for velocities inside topography re-activated

Location:
palm/trunk/SOURCE
Files:
8 edited

Legend:

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

    r1692 r1815  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! comment change
    2222!
    2323! Former revisions:
     
    194194
    195195#if defined( __nec )
    196        REAL(sp) ::  m1n, m1z  !Wichtig: Division !<
     196       REAL(sp) ::  m1n, m1z  !< important for optimisation of division
    197197       REAL(sp), DIMENSION(:,:), ALLOCATABLE :: m1, sw !<
    198198#else
  • palm/trunk/SOURCE/fft_xy.f90

    r1750 r1815  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! cpp-directives for ibmy removed
    2222!
    2323! Former revisions:
     
    285285          sqr_dnx = SQRT( dnx )
    286286          sqr_dny = SQRT( dny )
    287 #if defined( __ibm )  &&  ! defined( __ibmy_special )
     287#if defined( __ibm )
    288288!
    289289!--       Initialize tables for fft along x
     
    626626       ELSEIF ( fft_method == 'system-specific' )  THEN
    627627
    628 #if defined( __ibm )  &&  ! defined( __ibmy_special )
     628#if defined( __ibm )
    629629          IF ( forward_fft )  THEN
    630630
     
    938938       ELSEIF ( fft_method == 'system-specific' )  THEN
    939939
    940 #if defined( __ibm )  &&  ! defined( __ibmy_special )
     940#if defined( __ibm )
    941941          IF ( forward_fft )  THEN
    942942
     
    12551255       ELSEIF ( fft_method == 'system-specific' )  THEN
    12561256
    1257 #if defined( __ibm )  &&  ! defined( __ibmy_special )
     1257#if defined( __ibm )
    12581258          IF ( forward_fft)  THEN
    12591259
     
    15661566       ELSEIF ( fft_method == 'system-specific' )  THEN
    15671567
    1568 #if defined( __ibm )  &&  ! defined( __ibmy_special )
     1568#if defined( __ibm )
    15691569          IF ( forward_fft )  THEN
    15701570
  • palm/trunk/SOURCE/flow_statistics.f90

    r1784 r1815  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! cpp-directives for intel openmp bug removed
    2222!
    2323! Former revisions:
     
    358358
    359359       !$OMP PARALLEL PRIVATE( i, j, k, tn )
    360 #if defined( __intel_openmp_bug )
    361        tn = omp_get_thread_num()
    362 #else
    363360!$     tn = omp_get_thread_num()
    364 #endif
    365361
    366362       !$OMP DO
     
    561557!--          are zero at the walls and inside buildings.
    562558       tn = 0
    563 #if defined( __intel_openmp_bug )
    564        !$OMP PARALLEL PRIVATE( i, j, k, pts, sums_ll, sums_l_eper, sums_l_etot, &
    565        !$OMP                    tn, ust, ust2, u2, vst, vst2, v2, w2 )
    566        tn = omp_get_thread_num()
    567 #else
    568        !$OMP PARALLEL PRIVATE( i, j, k, pts, sums_ll, sums_l_eper, sums_l_etot, tn, ust, ust2, u2, vst, vst2, v2, w2 )
     559       !$OMP PARALLEL PRIVATE( i, j, k, pts, sums_ll, sums_l_eper,             &
     560       !$OMP                   sums_l_etot, tn, ust, ust2, u2, vst, vst2, v2,  &
     561       !$OMP                   w2 )
    569562!$     tn = omp_get_thread_num()
    570 #endif
     563
    571564       !$OMP DO
    572565       DO  i = nxl, nxr
     
    18411834
    18421835       !$OMP PARALLEL PRIVATE( i, j, k, tn )
    1843 #if defined( __intel_openmp_bug )
    1844        tn = omp_get_thread_num()
    1845 #else
    18461836!$     tn = omp_get_thread_num()
    1847 #endif
    18481837
    18491838       !$acc update device( sums_l )
     
    21172106!--          are zero at the walls and inside buildings.
    21182107       tn = 0
    2119 #if defined( __intel_openmp_bug )
    2120        !$OMP PARALLEL PRIVATE( i, j, k, pts, sums_ll, sums_l_eper, sums_l_etot, &
    2121        !$OMP                    tn, ust, ust2, u2, vst, vst2, v2, w2 )
    2122        tn = omp_get_thread_num()
    2123 #else
    2124        !$OMP PARALLEL PRIVATE( i, j, k, pts, sums_ll, sums_l_eper, sums_l_etot, tn, ust, ust2, u2, vst, vst2, v2, w2 )
     2108       !$OMP PARALLEL PRIVATE( i, j, k, pts, sums_ll, sums_l_eper,             &
     2109       !$OMP                   sums_l_etot, tn, ust, ust2, u2, vst, vst2, v2,  &
     2110       !$OMP                   w2 )
    21252111!$     tn = omp_get_thread_num()
    2126 #endif
     2112
    21272113       !$OMP DO
    21282114       !$acc parallel loop gang present( e, hom, kh, km, p, pt, w, rflags_invers, rmask, sums_l ) create( s1, s2, s3, s4, s5, s6, s7 )
  • palm/trunk/SOURCE/init_3d_model.f90

    r1789 r1815  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! zero-settings for velocities inside topography re-activated (was deactivated
     22! in r1762)
    2223!
    2324! Former revisions:
     
    857858!--       levels to zero in order to avoid too small time steps caused by the
    858859!--       diffusion limit in the initial phase of a run (at k=1, dz/2 occurs
    859 !--       in the limiting formula!). The original values are stored to be later
    860 !--       used for volume flow control.
    861           ! TO_DO:  Antti will check if this is really required
    862           !AH IF ( ibc_uv_b /= 1 )  THEN
    863           !AH    DO  i = nxlg, nxrg
    864           !AH       DO  j = nysg, nyng
    865           !AH          u(nzb:nzb_u_inner(j,i)+1,j,i) = 0.0_wp
    866           !AH          v(nzb:nzb_v_inner(j,i)+1,j,i) = 0.0_wp
    867           !AH       ENDDO
    868           !AH    ENDDO
    869           !AH ENDIF
     860!--       in the limiting formula!).
     861          IF ( ibc_uv_b /= 1 )  THEN
     862             DO  i = nxlg, nxrg
     863                DO  j = nysg, nyng
     864                   u(nzb:nzb_u_inner(j,i)+1,j,i) = 0.0_wp
     865                   v(nzb:nzb_v_inner(j,i)+1,j,i) = 0.0_wp
     866                ENDDO
     867             ENDDO
     868          ENDIF
    870869
    871870          IF ( humidity  .OR.  passive_scalar )  THEN
  • palm/trunk/SOURCE/init_pegrid.f90

    r1805 r1815  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! cpp-directives for intel openmp bug removed
    2222!
    2323! Former revisions:
     
    208208!-- Get the number of OpenMP threads
    209209    !$OMP PARALLEL
    210 #if defined( __intel_openmp_bug )
    211     threads_per_task = omp_get_num_threads()
    212 #else
    213210!$  threads_per_task = omp_get_num_threads()
    214 #endif
    215211    !$OMP END PARALLEL
    216212
  • palm/trunk/SOURCE/modules.f90

    r1809 r1815  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! cpp-directive for decalpha removed
    2222!
    2323! Former revisions:
     
    926926                               topography_color = (/ 0.8_wp, 0.7_wp, 0.6_wp /)
    927927
    928 #if defined( __decalpha )
    929     REAL(wp), DIMENSION(2,10)  ::  slicer_range_limits_dvrp = RESHAPE( (/      &
    930                                    -1.0_wp, 1.0_wp, -1.0_wp, 1.0_wp, -1.0_wp, 1.0_wp, -1.0_wp, 1.0_wp, &
    931                                    -1.0_wp, 1.0_wp, -1.0_wp, 1.0_wp, -1.0_wp, 1.0_wp, -1.0_wp, 1.0_wp, &
    932                                    -1.0_wp, 1.0_wp, -1.0_wp, 1.0_wp /), (/ 2, 10 /) )
    933 
    934     REAL(wp), DIMENSION(3,10)  ::  isosurface_color = RESHAPE( (/                 &
    935                                    0.9_wp, 0.9_wp, 0.9_wp,  0.8_wp, 0.1_wp, 0.1_wp,  0.1_wp, 0.1_wp, 0.8_wp, &
    936                                    0.1_wp, 0.8_wp, 0.1_wp,  0.6_wp, 0.1_wp, 0.1_wp,  0.1_wp, 0.1_wp, 0.6_wp, &
    937                                    0.1_wp, 0.6_wp, 0.1_wp,  0.4_wp, 0.1_wp, 0.1_wp,  0.1_wp, 0.1_wp, 0.4_wp, &
    938                                    0.1_wp, 0.4_wp, 0.1_wp /), (/ 3, 10 /) )
    939 
    940     REAL(sp), DIMENSION(2,100) ::  interval_values_dvrp, interval_h_dvrp =      &
    941                                    RESHAPE( (/ 270.0_sp, 225.0_sp, 225.0_sp, 180.0_sp,      &
    942                                                 70.0_sp,  25.0_sp,  25.0_sp, -25.0_sp,      &
    943                                                ( 0.0_sp, i9 = 1, 192 ) /),         &
    944                                             (/ 2, 100 /) ),                     &
    945                                    interval_l_dvrp = 0.5_sp, interval_s_dvrp = 1.0_sp,&
    946                                    interval_a_dvrp = 0.0_sp,                       &
    947                                    interval_values_dvrp_prt,                    &
    948                                    interval_h_dvrp_prt = RESHAPE(               &
    949                                    (/ 270.0_sp, 225.0_sp, 225.0_sp, 180.0_sp, 70.0_sp, 25.0_sp,   &
    950                                       25.0_sp, -25.0_sp, ( 0.0_sp, i9 = 1, 192 ) /),     &
    951                                                    (/ 2, 100 /) ),              &
    952                                    interval_l_dvrp_prt = 0.5_sp,                   &
    953                                    interval_s_dvrp_prt = 1.0_sp,                   &
    954                                    interval_a_dvrp_prt = 0.0_sp
    955 #else
    956928    REAL(wp), DIMENSION(2,10)     ::  slicer_range_limits_dvrp
    957929
     
    980952    DATA  interval_h_dvrp_prt / 270.0_wp, 225.0_wp, 225.0_wp, 180.0_wp, 70.0_wp, 25.0_wp, &
    981953                                25.0_wp, -25.0_wp, 192 * 0.0_wp /
    982 #endif
    983954
    984955    REAL(sp), DIMENSION(:), ALLOCATABLE ::  xcoor_dvrp, ycoor_dvrp, zcoor_dvrp
  • palm/trunk/SOURCE/spectrum.f90

    r1809 r1815  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! bugfix: preprocessor directives included for the non-parallel case
    2222!
    2323! Former revisions:
     
    294294       USE kinds
    295295
     296#if defined( __parallel )
    296297#if defined( __mpifh )
    297298       INCLUDE "mpif.h"
    298299#else
    299300       USE MPI
     301#endif
    300302#endif
    301303       USE pegrid,                                                             &
     
    396398       USE kinds
    397399
     400#if defiend( __parallel )
    398401#if defined( __mpifh )
    399402       INCLUDE "mpif.h"
    400403#else
    401404       USE MPI
     405#endif
    402406#endif
    403407       USE pegrid,                                                             &
     
    537541       USE kinds
    538542
     543#if defined( __parallel )
    539544#if defined( __mpifh )
    540545       INCLUDE "mpif.h"
    541546#else
    542547       USE MPI
     548#endif
    543549#endif
    544550       USE pegrid,                                                             &
  • palm/trunk/SOURCE/tridia_solver.f90

    r1809 r1815  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! cpp-switch intel11 removed
    2222!
    2323! Former revisions:
     
    521521
    522522       IF ( j <= nnyh )  THEN
    523 #if defined( __intel11 )
    524           CALL maketri_1dd( j, tri_for_1d )
    525 #else
    526523          CALL maketri_1dd( j )
    527 #endif
    528524       ELSE
    529 #if defined( __intel11 )
    530           CALL maketri_1dd( ny+1-j, tri_for_1d )
    531 #else
    532525          CALL maketri_1dd( ny+1-j )
    533 #endif
    534526       ENDIF
    535 #if defined( __intel11 )
    536        CALL split_1dd( tri_for_1d )
    537 #else
     527
    538528       CALL split_1dd
    539 #endif
    540529       CALL substi_1dd( ar, tri_for_1d )
    541530
     
    548537!> computes the i- and j-dependent component of the matrix
    549538!------------------------------------------------------------------------------!
    550 #if defined( __intel11 )
    551        SUBROUTINE maketri_1dd( j, tri_for_1d )
    552 #else
    553539       SUBROUTINE maketri_1dd( j )
    554 #endif
    555540
    556541          USE constants,                                                       &
     
    570555
    571556          REAL(wp), DIMENSION(0:nx) ::  l !<
    572 
    573 #if defined( __intel11 )
    574           REAL(wp), DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d !<
    575 #endif
    576557
    577558
     
    623604!> Splitting of the tridiagonal matrix (Thomas algorithm)
    624605!------------------------------------------------------------------------------!
    625 #if defined( __intel11 )
    626        SUBROUTINE split_1dd( tri_for_1d )
    627 #else
    628606       SUBROUTINE split_1dd
    629 #endif
    630 
    631607
    632608          IMPLICIT NONE
     
    634610          INTEGER(iwp) ::  i !<
    635611          INTEGER(iwp) ::  k !<
    636 
    637 #if defined( __intel11 )
    638           REAL(wp), DIMENSION(5,0:nx,0:nz-1) ::  tri_for_1d !<
    639 #endif
    640612
    641613
Note: See TracChangeset for help on using the changeset viewer.