Ignore:
Timestamp:
10/20/17 09:31:39 (7 years ago)
Author:
aquiquet
Message:

Grisli-iLoveclim branch: merged to trunk at revision 145

Location:
branches/iLoveclim
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/iLoveclim

  • branches/iLoveclim/SOURCES/resol_adv_diff_2D-sept2009.f90

    r77 r146  
    278278 
    279279relax_loop: do while(.not.stopp) 
    280 ntour=ntour+1 
    281 !$OMP PARALLEL 
    282 !$OMP DO PRIVATE(reste) 
    283 do j=2,ny-1 
    284    do i=2,nx-1 
    285  
    286       reste = (((arelax(i,j)*newH(i-1,j) +drelax(i,j)*newH(i,j-1)) & 
    287            + (brelax(i,j)*newH(i+1,j) + erelax(i,j)*newH(i,j+1))) & 
    288            + crelax(i,j)*newH(i,j))- frelax(i,j) 
    289  
    290 !if (ntour.eq.1)  debug_3D(i,j,49)=(((arelax(i,j)*newH(i-1,j) +drelax(i,j)*newH(i,j-1)) & 
    291 !           + (brelax(i,j)*newH(i+1,j) + erelax(i,j)*newH(i,j+1))) & 
    292 !           + crelax(i,j)*newH(i,j)) 
    293  
    294  
    295       deltaH(i,j) = reste/crelax(i,j) 
    296  
     280   ntour=ntour+1 
     281   !$OMP PARALLEL 
     282   !$OMP DO PRIVATE(reste) 
     283   do j=2,ny-1 
     284      do i=2,nx-1 
     285         reste = (((arelax(i,j)*newH(i-1,j) +drelax(i,j)*newH(i,j-1)) & 
     286               + (brelax(i,j)*newH(i+1,j) + erelax(i,j)*newH(i,j+1))) & 
     287               + crelax(i,j)*newH(i,j))- frelax(i,j) 
     288 
     289         deltaH(i,j) = reste/crelax(i,j) 
     290      end do 
    297291   end do 
    298 end do 
    299 !$OMP END DO 
    300  
    301 !debug_3D(:,:,50)=arelax(:,:) 
    302 !debug_3D(:,:,51)=brelax(:,:) 
    303 !debug_3D(:,:,52)=crelax(:,:) 
    304 !debug_3D(:,:,53)=drelax(:,:) 
    305 !debug_3D(:,:,54)=erelax(:,:) 
    306 !debug_3D(:,:,55)=frelax(:,:) 
    307  
    308  
    309 !$OMP WORKSHARE 
    310 newH(:,:)=newH(:,:)-deltaH(:,:) 
    311 !$OMP END WORKSHARE 
    312 !$OMP END PARALLEL 
     292   !$OMP END DO 
     293 
     294   !$OMP WORKSHARE 
     295   newH(:,:)=newH(:,:)-deltaH(:,:) 
     296   !$OMP END WORKSHARE 
     297   !$OMP END PARALLEL 
    313298 
    314299 
    315300! critere d'arret: 
    316301! ----------------          
    317  
    318 delh=0 
    319  
    320 !$OMP PARALLEL 
    321 !$OMP DO REDUCTION(+:delh) 
    322 do j=2,ny-1 
    323    do i=2,nx-1 
    324       delh=delh+deltaH(i,j)**2 
     302   delh=0 
     303 
     304   !$OMP PARALLEL 
     305   !$OMP DO REDUCTION(+:delh) 
     306   do j=2,ny-1 
     307      do i=2,nx-1 
     308         delh=delh+deltaH(i,j)**2 
     309      end do 
    325310   end do 
    326 end do 
    327 !$OMP END DO 
    328 !$OMP END PARALLEL 
    329  
    330 if (delh.gt.0.) then 
    331    testh=sqrt(delh)/((nx-2)*(ny-2)) 
    332 else 
    333    testh=0. 
    334 endif 
    335 stopp = (testh.lt.1.e-4).or.(ntour.gt.100) 
    336  
    337  
     311   !$OMP END DO 
     312   !$OMP END PARALLEL 
     313 
     314   if (delh.gt.0.) then 
     315      testh=sqrt(delh)/((nx-2)*(ny-2)) 
     316   else 
     317      testh=0. 
     318   endif 
     319   stopp = (testh.lt.1.e-4).or.(ntour.gt.100) 
    338320 
    339321end do relax_loop 
    340322 
    341  
    342 ! thickness at the upwind node 
    343 !do j = 1, ny 
    344 !   do i = 2, nx 
    345 !      debug_3D(i,j,92) = c_west(i,j) * newH(i-1,j) + c_east(i,j) * newH(i,j) 
    346 !   end do 
    347 !end do 
    348 !do j = 2, ny 
    349 !   do i = 1, nx 
    350 !      debug_3D(i,j,93) = c_south(i,j) * newH(i,j-1) + c_north(i,j) * newH(i,j) 
    351 !   end do 
    352 !end do 
    353  
    354323if (itracebug.eq.1)  call tracebug(' fin routine resolution_diffusion') 
    355  
    356324  
    357325return 
Note: See TracChangeset for help on using the changeset viewer.