Ignore:
Timestamp:
06/29/16 16:21:13 (8 years ago)
Author:
dumas
Message:

OpenMP parallelization in conserv-mass-adv-diff_sept2009_mod.f90, diffusiv-polyn-0.6.f90, dragging_neff_slope_mod.f90, eaubasale-0.5_mod.f90 and relaxation_water_diffusion.f90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/relaxation_water_diffusion.f90

    r65 r76  
    1818 
    1919subroutine relaxation_waterdif(NXX,NYY,DT,DX,vieuxHWATER,limit_hw,klimit,BMELT,INFILTR,PGMX,PGMY,KOND,KONDMAX,HWATER) 
    20     implicit none 
     20 
     21  !$ USE OMP_LIB 
     22 
     23  implicit none 
    2124 
    2225 
     
    5760 
    5861! write(166,*)' entree  relaxation waterdif' 
     62!$OMP PARALLEL 
     63!$OMP WORKSHARE 
    5964    HWATER(:,:)= vieuxHWATER(:,:) 
    60  
     65!$OMP END WORKSHARE 
    6166    !   calcul de kmx et kmx a partir de KOND 
    6267    !   conductivite hyrdraulique sur les noeuds mineurs 
    6368    !   moyenne harmonique 
    6469    !   ---------------------------------------- 
    65  
     70!$OMP DO 
    6671    do j=2,nyy 
    6772       do i=2,nxx 
     
    7580       end do 
    7681    end do 
    77  
     82!$OMP END DO 
     83 
     84!$OMP DO 
    7885    do j=2,nyy 
    7986       do i=2,nxx 
     
    8693       enddo 
    8794    enddo 
    88  
     95!$OMP END DO 
    8996 
    9097    !   attribution des coefficients  arelax .... 
     
    100107    dtwdx2=dt/dx/dx 
    101108 
    102 arelax(:,:)=0. 
    103 brelax(:,:)=0. 
    104 crelax(:,:)=1. 
    105 drelax(:,:)=0. 
    106 erelax(:,:)=0. 
    107 frelax(:,:)=limit_hw(:,:) 
    108  
    109  
    110  
     109!$OMP WORKSHARE 
     110  arelax(:,:)=0. 
     111  brelax(:,:)=0. 
     112  crelax(:,:)=1. 
     113  drelax(:,:)=0. 
     114  erelax(:,:)=0. 
     115  frelax(:,:)=limit_hw(:,:) 
     116!$OMP END WORKSHARE 
     117 
     118!$OMP DO 
    111119    do J=2,NYY-1 
    112120       do I=2,NXX-1 
    113121 
    114122          if (klimit(i,j).eq.0) then 
    115  
    116123! calcul du vecteur 
    117  
    118124          FRELAX(I,J)= VIEUXHWATER(I,J)+(BMELT(I,J)-INFILTR)*DT 
    119125          frelax(i,j)=frelax(i,j)+(kmx(i,j)*pgmx(i,j)-kmx(i+1,j)*pgmx(i+1,j))*dtsrgdx 
    120126          frelax(i,j)=frelax(i,j)+(kmy(i,j)*pgmy(i,j)-kmy(i,j+1)*pgmy(i,j+1))*dtsrgdx 
    121  
    122127! calcul des diagonales       
    123128          arelax(i,j)=-kmx(i,j)*dtwdx2        ! arelax : diagonale i-1,j  
     
    131136          crelax(i,j)=1.+((kmx(i,j)+kmx(i+1,j))+(kmy(i,j)+kmy(i,j+1)))*dtwdx2  
    132137                                              !crelax : diagonale i,j  
    133  
    134138          else if (klimit(i,j).eq.1) then 
    135139             hwater(i,j)=limit_hw(i,j) 
    136140!             write(6,*) i,j,hwater(i,j),crelax(i,j),frelax(i,j),arelax(i,j) 
    137  
    138141          endif 
    139  
    140142       end do 
    141143    end do 
    142  
    143  
     144!$OMP END DO 
     145!$OMP END PARALLEL 
    144146 
    145147    ! Boucle de relaxation : 
     
    152154       ntour=ntour+1 
    153155!       write(6,*) 'boucle de relaxation numero',ntour 
    154  
     156       !$OMP PARALLEL 
     157       !$OMP DO PRIVATE(reste) 
    155158       do j=2,NYY-1 
    156159          do i=2,NXX-1 
     
    161164 
    162165             DELTAH(I,J) = RESTE/CRELAX(I,J)              
    163  
    164166          end do 
    165167       end do 
    166  
    167 deltah(:,:)=min(deltah(:,:),10.) 
    168 deltah(:,:)=max(deltah(:,:),-10.) 
    169       
    170  
    171  
     168       !$OMP END DO 
     169 
     170       !$OMP WORKSHARE 
     171       deltah(:,:)=min(deltah(:,:),10.) 
     172       deltah(:,:)=max(deltah(:,:),-10.) 
     173       !$OMP END WORKSHARE 
    172174       ! il faut faire le calcul suivant dans une autre boucle car RESTE est fonction 
    173175       ! de hwater sur les points voisins. 
     176       !$OMP DO 
    174177       do j=2,NYY-1 
    175178          do i=2,NXX-1 
    176179             HWATER(I,J) = HWATER(I,J) - DELTAH(I,J) 
    177  
    178180          end do 
    179181       end do 
    180  
     182       !$OMP END DO 
    181183 
    182184       ! critere d'arret: 
    183  
    184        
    185  
    186185       Delh=0 
    187186       Vh=0 
    188  
     187        
     188       !$OMP DO REDUCTION(+:Delh) 
    189189       DO j=2,NYY-1 
    190190          DO i=2,NXX-1 
    191191              
    192192             !   write(166,*) I,J,delh,deltah(i,j) 
    193                          Delh=Delh+deltah(i,j)**2 
     193             Delh=Delh+deltah(i,j)**2 
    194194             !            Vh=Vh+h(i,j)**2. 
    195195          END DO 
    196196       END DO 
    197  
     197       !$OMP END DO 
     198       !$OMP END PARALLEL 
    198199!       write(6,*) delh,maxval(deltah),minval(deltah) 
    199200       !      testh=SQRT(Delh/Vh) 
Note: See TracChangeset for help on using the changeset viewer.