Changeset 353


Ignore:
Timestamp:
08/06/15 10:48:45 (9 years ago)
Author:
dubos
Message:

OpenMP fixes for DCMIP

Location:
codes/icosagcm/trunk/src
Files:
7 edited

Legend:

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

    r209 r353  
    1   MODULE disvert_dcmip31_mod 
     1MODULE disvert_dcmip31_mod 
    22  USE icosa 
    3   
     3  IMPLICIT NONE 
     4  PRIVATE 
     5 
    46  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:) 
    57!$OMP THREADPRIVATE(ap) 
     
    911!$OMP THREADPRIVATE(presnivs) 
    1012 
     13  PUBLIC :: ap,bp,presnivs, init_disvert 
     14 
    1115CONTAINS 
    1216!========================================================================= 
    1317 
    1418  SUBROUTINE init_disvert 
    15   USE icosa 
    16   IMPLICIT NONE 
    17    
    1819    ALLOCATE(ap(llm+1)) 
    1920    ALLOCATE(bp(llm+1)) 
    2021    ALLOCATE(presnivs(llm)) 
    21      
    2222    CALL disvert(ap,bp,presnivs)     
    23  
    24   END SUBROUTINE init_disvert   
     23  END SUBROUTINE init_disvert 
    2524 
    2625  SUBROUTINE disvert(ap,bp,presnivs) 
    27   USE icosa 
    2826  USE mpipara 
    29   IMPLICIT NONE 
    3027  REAL(rstd),INTENT(OUT) :: ap(:) 
    3128  REAL(rstd),INTENT(OUT) :: bp(:) 
  • codes/icosagcm/trunk/src/etat0.f90

    r346 r353  
    188188 
    189189    INTEGER :: l,i,j,ij 
     190 
     191    !$OMP BARRIER 
    190192 
    191193    SELECT CASE (TRIM(etat0_type)) 
     
    219221    END SELECT 
    220222 
     223    !$OMP BARRIER 
     224 
    221225    CALL compute_wind_perp_from_lonlat_compound(ulon_e, ulat_e, u) 
    222226 
  • codes/icosagcm/trunk/src/etat0_dcmip1.f90

    r344 r353  
    105105 
    106106  SUBROUTINE compute_etat0_ncar(icase,ngrid,lon,lat, q) 
    107   USE icosa 
    108107  USE disvert_mod 
    109   IMPLICIT NONE   
     108  USE omp_para 
    110109  INTEGER, INTENT(IN) :: icase, ngrid 
    111110  REAL(rstd),INTENT(IN) :: lon(ngrid),lat(ngrid)   
     
    158157 
    159158    SUBROUTINE cosine_bell_1(hx) 
    160     IMPLICIT NONE  
    161159    REAL(rstd) :: hx(ngrid,llm) 
    162160    REAL(rstd) :: rr1,rr2    
    163161    INTEGER :: n,l 
    164     DO l=1,llm  
     162    DO l=ll_begin,ll_end  
    165163       DO n=1,ngrid 
    166164          CALL dist_lonlat(lon0,lat0,lon(n),lat(n),rr1)  ! GC distance from center  
     
    181179    REAL(rstd) :: rr1,rr2,dd1,dd2,dd1t1,dd1t2,dd2t1 
    182180    INTEGER :: n,l 
    183     DO l=1,llm 
     181    DO l=ll_begin,ll_end 
    184182       DO n=1,ngrid 
    185183          CALL dist_lonlat(lonc1,latc1,lon(n),lat(n),rr1)  ! GC distance from center  
     
    208206    REAL(rstd) :: rr1,rr2,dd1,dd2,dd1t1,dd1t2,dd2t1 
    209207    INTEGER :: n,l 
    210     DO l=1,llm 
     208    DO l=ll_begin,ll_end 
    211209       DO n=1,ngrid 
    212210          CALL dist_lonlat(lonc1,latc1,lon(n),lat(n),rr1)  ! GC distance from center  
     
    245243      INTEGER :: n,l 
    246244       
    247       DO l=1,llm 
     245      DO l=ll_begin,ll_end 
    248246         IF ( ( zz1 .LT. zrl(l) ) .and. ( zrl(l) .LT. zz2 ) )  THEN  
    249247            hx(:,l) = 0.5*(1. + cos(2*pi*(zrl(l)-zz0)/(zz2-zz1)))   
  • codes/icosagcm/trunk/src/etat0_dcmip2.f90

    r344 r353  
    11MODULE etat0_dcmip2_mod 
    2  
    32! test cases DCMIP 2012, category 2 : Orographic gravity waves 
    4  
    53  USE icosa 
     4  IMPLICIT NONE 
    65  PRIVATE 
    76 
     
    3332  SUBROUTINE compute_etat0(ngrid,lon,lat, phis, ps, Temp, ulon, ulat) 
    3433    USE disvert_mod 
    35     IMPLICIT NONE 
     34    USE omp_para 
    3635    INTEGER, INTENT(IN)    :: ngrid 
    3736    REAL(rstd),INTENT(IN)  :: lon(ngrid) 
     
    4645 
    4746    ! Hexagons : ps,phis,temp 
    48     DO l=1,llm 
     47    DO l=ll_begin,ll_end 
    4948       ! The surface pressure is not set yet so we provide the hybrid coefficients 
    5049       hyam = .5*(ap(l)+ap(l+1))/preff 
  • codes/icosagcm/trunk/src/etat0_dcmip3.f90

    r345 r353  
    1111    USE dcmip_initial_conditions_test_1_2_3 
    1212    USE disvert_mod 
     13    USE omp_para 
    1314    INTEGER, INTENT(IN) :: ngrid 
    1415    REAL(rstd), INTENT(IN) :: lon(ngrid) 
     
    2829            dummy,dummy,dummy,dummy,phis(ij),ps(ij),dummy,dummy) 
    2930    END DO 
    30     DO l=1,llm 
     31    DO l=ll_begin,ll_end 
    3132       DO ij=1,ngrid 
    3233          pp = .5*(ap(l)+ap(l+1)) + .5*(bp(l)+bp(l+1))*ps(ij) ! full-layer pressure 
     
    3435               ulon(ij,l),ulat(ij,l),dummy,Temp(ij,l),dummy,dummy,dummy,dummy) 
    3536       END DO 
    36     END DO     
    37     q=0. 
     37    END DO 
     38    q(:,:,:)=0. 
    3839  END SUBROUTINE compute_etat0 
    3940 
  • codes/icosagcm/trunk/src/etat0_dcmip4.f90

    r346 r353  
    3939    USE icosa 
    4040    USE disvert_mod 
     41    USE omp_para 
    4142    INTEGER, INTENT(IN) :: ngrid 
    4243    REAL(rstd),INTENT(IN) :: lon(ngrid) 
     
    6667    ENDDO 
    6768     
    68     DO l=1,llm 
     69    DO l=ll_begin,ll_end 
    6970       etal = 0.5 *( ap(l)/preff+bp(l) + ap(l+1)/preff+bp(l+1) ) 
    7071       etavl=(etal-eta0)*Pi/2 
  • codes/icosagcm/trunk/src/etat0_dcmip5.f90

    r340 r353  
    2222 
    2323  INTEGER, SAVE :: dcmip5_testcase 
     24!$OMP THREADPRIVATE(dcmip5_testcase) 
    2425 
    2526  PUBLIC getin_etat0, compute_etat0 
     
    4142  SUBROUTINE compute_etat0(ngrid,lon,lat, phis, ps, Temp, ulon, ulat, q) 
    4243    USE disvert_mod 
     44    USE omp_para 
    4345    INTEGER, INTENT(IN)    :: ngrid 
    4446    REAL(rstd),INTENT(IN)  :: lon(ngrid) 
     
    6163    END DO 
    6264 
    63     DO l=1,llm 
     65    DO l=ll_begin,ll_end 
    6466       aa=.5*(ap(l)+ap(l+1)) 
    6567       bb=.5*(bp(l)+bp(l+1)) 
Note: See TracChangeset for help on using the changeset viewer.