Ignore:
Timestamp:
10/31/14 14:52:01 (10 years ago)
Author:
ymipsl
Message:

Merging OpenMP parallisme mode : by subdomain and on vertical level.
This feature is actually experimental but may be retro-compatible with the last method based only on subdomain

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/pression.f90

    r186 r295  
    1313    INTEGER :: ind 
    1414 
     15!$OMP BARRIER 
    1516    DO ind=1,ndomain 
    1617      IF (.NOT. assigned_domain(ind)) CYCLE 
     
    2122      CALL compute_pression(ps, p,0) 
    2223    ENDDO 
     24!$OMP BARRIER 
    2325   
    2426  END SUBROUTINE pression 
     
    2729  USE icosa 
    2830  USE disvert_mod 
     31  USE omp_para 
    2932  IMPLICIT NONE 
    3033    REAL(rstd),INTENT(IN) :: ps(iim*jjm) 
     
    3437 
    3538    IF(ap_bp_present) THEN 
    36     DO    l    = 1, llm+1 
    37       DO j=jj_begin-offset,jj_end+offset 
    38         DO i=ii_begin-offset,ii_end+offset 
    39           ij=(j-1)*iim+i 
    40           p(ij,l) = ap(l) + bp(l) * ps(ij) 
     39      DO    l    = ll_begin, ll_endp1 
     40!      DO    l    = 1, llm + 1 
     41        DO j=jj_begin-offset,jj_end+offset 
     42          DO i=ii_begin-offset,ii_end+offset 
     43            ij=(j-1)*iim+i 
     44            p(ij,l) = ap(l) + bp(l) * ps(ij) 
     45          ENDDO 
    4146        ENDDO 
    4247      ENDDO 
    43     ENDDO 
    4448    END IF 
     49 
    4550  END SUBROUTINE compute_pression 
    4651 
Note: See TracChangeset for help on using the changeset viewer.