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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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.