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/advect_tracer.f90

    r252 r295  
    2626  SUBROUTINE init_advect_tracer 
    2727    USE advect_mod 
     28    USE omp_para 
    2829    REAL(rstd),POINTER :: tangent(:,:) 
    2930    REAL(rstd),POINTER :: normal(:,:) 
     
    4849       tangent=f_tangent(ind) 
    4950       sqrt_leng=f_sqrt_leng(ind) 
    50        CALL init_advect(normal,tangent,sqrt_leng) 
     51       IF (is_omp_level_master) CALL init_advect(normal,tangent,sqrt_leng) 
    5152    END DO 
    5253 
     
    238239 
    239240!--> flush dzqw, adzqw 
    240 !!$OMP BARRIER 
     241!$OMP BARRIER 
    241242 
    242243    ! minmod-limited slope of q 
     
    258259 
    259260    ! 0 slope in top and bottom layers 
    260     IF (omp_first) THEN 
     261    IF (is_omp_first_level) THEN 
    261262      DO ij=ijb,ije 
    262263           dzq(ij,1)=0. 
     
    264265    ENDIF 
    265266       
    266     IF (omp_last) THEN 
     267    IF (is_omp_last_level) THEN 
    267268      DO ij=ijb,ije 
    268269          dzq(ij,llm)=0. 
     
    271272 
    272273!---> flush dzq 
    273 !!$OMP BARRIER   
     274!$OMP BARRIER   
    274275 
    275276    ! sigw = fraction of mass that leaves level l/l+1 
     
    290291    END DO 
    291292    ! wq = 0 at top and bottom 
    292     IF (omp_first) THEN 
     293    IF (is_omp_first_level) THEN 
    293294       DO ij=ijb,ije 
    294295            wq(ij,1)=0. 
     
    296297    ENDIF 
    297298     
    298     IF (omp_last) THEN 
     299    IF (is_omp_last_level) THEN 
    299300      DO ij=ijb,ije 
    300301            wq(ij,llm+1)=0. 
     
    303304 
    304305! --> flush wq 
    305 !!$OMP BARRIER 
     306!$OMP BARRIER 
    306307 
    307308 
Note: See TracChangeset for help on using the changeset viewer.