PCMRH.f90 16 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576
  1. program PCMRH
  2. !***************************************************************
  3. ! Parallel CMRH program with MPI
  4. !***************************************************************
  5. use mpi
  6. external SSWAP,DCOPY,DSCAL,DGEMV,DSWAP
  7. intrinsic dabs,dsqrt
  8. !********************************************
  9. ! VARIABLES
  10. !********************************************
  11. integer,parameter ::Nprocs_max=16
  12. integer ::rang,Nprocs,n,nl,code,i,j,k,choix,solchoice,iprint
  13. real(kind=8) ::init(5)
  14. integer,dimension(MPI_STATUS_SIZE) ::statut
  15. real(kind=8),allocatable,dimension(:,:) ::AL
  16. real(kind=8) ::btemp,bmax,btemp2
  17. real(kind=8),allocatable,dimension(:) ::b,sol,rs,temp,x,workl,work,tempn,c,s,xl,cl,temp2,xx,yy,valeurs
  18. integer,allocatable,dimension(:) ::p
  19. real*8 ::dnorm2,D_inv,beta,dnorm,dnrm2,tol,alpha,H_k1,dgam,r
  20. integer ::indice,idamax,k1,n_k,knl,knlp,inl,inlp
  21. real*8 dtime, delta, delta0, dt1, dt2, dt3
  22. real*8 etime, eelta, eelta0, et1, et2, et3
  23. real*8 t1, t2, t3, tm1, tm2, tm3
  24. real*8 dtime1, delta1, delta01
  25. real*8 etime1, eelta1, eelta01,l,p1,p2
  26. integer nb_ligne
  27. real(kind=8) ::temps,tempsd,tempsf,temps2
  28. integer*4,dimension(3) ::timearray
  29. real ::rand
  30. real*4 da(2),ea(2),da1(2),ea1(2)
  31. !********************************************
  32. ! MPI CONFIG
  33. !********************************************
  34. call MPI_INIT(code)
  35. call MPI_COMM_RANK(MPI_COMM_WORLD,rang,code)
  36. call MPI_COMM_SIZE(MPI_COMM_WORLD,Nprocs,code)
  37. call MPI_BARRIER(MPI_COMM_WORLD,code)
  38. call itime(timearray) ! Get the current time
  39. i = rand ( timearray(1)+timearray(2)+timearray(3) )
  40. !************************************
  41. ! Matrix Initialisation
  42. !************************************
  43. if (rang==0) then
  44. open(unit=10,file='inputfile.dat',status='old')
  45. read(10,*)init
  46. close(10)
  47. iprint=int(init(1))
  48. n=int(init(2))
  49. choix=int(init(3))
  50. solchoice=int(init(4))
  51. tol=init(5)
  52. end if
  53. tempsd=MPI_WTIME()
  54. call MPI_BCAST(n,1,MPI_INTEGER,0,MPI_COMM_WORLD,code)
  55. call MPI_BCAST(choix,1,MPI_INTEGER,0,MPI_COMM_WORLD,code)
  56. call MPI_BCAST(tol,1,MPI_DOUBLE_PRECISION,0,MPI_COMM_WORLD,code)
  57. if (mod(n,Nprocs)==0)then
  58. nl=n/Nprocs
  59. else
  60. nl=(n/Nprocs)+1
  61. end if
  62. allocate(b(n),rs(n),x(n),AL(nl,n),workl(nl),sol(n),temp(n),temp2(n))
  63. if (choix<3)then
  64. call matrice(AL,nl,n,2.d0,1.d0,choix,rang)
  65. else
  66. allocate(valeurs(n))
  67. open(unit=30,file='matrixfile.dat',status='old')
  68. do i=1,n
  69. call position(i,nl,inl,inlp)
  70. read(30,*)valeurs
  71. if (rang.eq.inl)then
  72. AL(inlp,:)=valeurs(:)
  73. endif
  74. enddo
  75. close(30)
  76. endif
  77. !********************************************
  78. ! End Matrix initialisation
  79. !********************************************
  80. !********************************************
  81. ! Solution initialisation
  82. !********************************************
  83. call MPI_BCAST(solchoice,1,MPI_INTEGER,0,MPI_COMM_WORLD,code)
  84. call solution(AL,workl,sol,nl,n,solchoice)
  85. call MPI_ALLGATHER(workl,nl,MPI_DOUBLE_PRECISION,b,nl,MPI_DOUBLE_PRECISION,MPI_COMM_WORLD,code)
  86. !********************************************
  87. ! End solution initialisation
  88. !********************************************
  89. !********************************************
  90. ! Permutation Vector initialisation
  91. ! and computation of initial residual
  92. !********************************************
  93. if (rang==0) then
  94. allocate(p(n))
  95. do i=1,n
  96. p(i)=i
  97. end do
  98. end if
  99. dnorm2=dnrm2(n,b,1)
  100. if (rang==0)then
  101. if (iprint==2)then
  102. print*,''
  103. print*,'la norme 2 de r0=',dnorm2
  104. print*,''
  105. end if
  106. end if
  107. !********************************************
  108. ! Computation of max b(i)
  109. !********************************************
  110. indice = idamax(n,b,1)
  111. beta = b(indice)
  112. D_inv = 1.d0/beta
  113. !********************************************
  114. ! First permutation
  115. !********************************************
  116. if (indice .ne.1) then
  117. call dswap(1,b(indice),1,b(1),1)
  118. call dswap(nl,AL(1,indice),1,AL(1,1),1)
  119. call position(indice,nl,inl,inlp)
  120. if (inl==0) then
  121. if (rang==inl)then
  122. call dswap(n,AL(inlp,1),nl,AL(1,1),nl)
  123. end if
  124. else
  125. if (rang==inl) then
  126. call dcopy(n,AL(inlp,1),nl,temp,1)
  127. end if
  128. call MPI_BCAST(temp,n,MPI_DOUBLE_PRECISION,inl,MPI_COMM_WORLD,code)
  129. if (rang==0)then
  130. call dcopy(n,AL(1,1),nl,temp2,1)
  131. end if
  132. call MPI_BCAST(temp2,n,MPI_DOUBLE_PRECISION,0,MPI_COMM_WORLD,code)
  133. if (rang==inl)then
  134. call dcopy(n,temp2,1,AL(inlp,1),nl)
  135. end if
  136. if (rang==0)then
  137. call dcopy(n,temp,1,AL(1,1),nl)
  138. end if
  139. end if
  140. if (rang==0)then
  141. call sswap(1,p(indice),1,p(1),1)
  142. end if
  143. end if
  144. !********************************************
  145. ! End permutation
  146. !********************************************
  147. ! call dscal(n,0.d0,x,1)
  148. call dscal(n,D_inv,b,1)
  149. rs(1)=beta
  150. dnorm=dabs(beta)
  151. allocate(tempn(nl),work(n),c(n),s(n),xl(nl),cl(nl))
  152. call dscal(nl,0.d0,xl,1)
  153. call MPI_BARRIER(MPI_COMM_WORLD,code)
  154. k=0
  155. if (rang==0) then
  156. if (iprint==2)then
  157. write(*,*)'iter., pseudo residu '
  158. end if
  159. open(unit=30,file='presidual.dat',status='unknown')
  160. write(30,*)'Iter., Pseudo Residual Norm'
  161. end if
  162. !tol=1.d-7
  163. delta0 = dtime(da)
  164. eelta0 = etime(ea)
  165. tempsf=MPI_WTIME()
  166. !********************************************
  167. ! Loop
  168. !********************************************
  169. do while((dnorm.gt.tol).and.(k.lt.n))
  170. k=k+1;
  171. n_k=n-k;
  172. k1=k+1;
  173. if (rang==0) then
  174. if (iprint==2)then
  175. write(*,10)k-1,dnorm
  176. end if
  177. write(30,10)k-1,dnorm
  178. end if
  179. 10 format(i5,2x,e12.4)
  180. !********************************************
  181. ! workl = A*b
  182. !********************************************
  183. call dgemv('N',nl,n_k+1,1.d0,AL(1,k),nl,b(k),1,0.d0,workl,1)
  184. ! ! call dscal(nl,0.d0,workl,1)
  185. ! ! do j=k1,n
  186. ! ! do i=1,nl
  187. ! ! workl(i)=workl(i)+AL(i,j)*b(j)
  188. ! ! end do
  189. ! ! end do
  190. !********************************************
  191. ! A(:,k)=b
  192. !********************************************
  193. call position(k1,nl,knl,knlp)
  194. if (rang>knl)then
  195. call dcopy(nl,b(rang*nl+1),1,AL(1,k),1)
  196. else
  197. if (rang==knl) then
  198. call dcopy(nl-knlp+1,b(k1),1,AL(knlp,k),1)
  199. end if
  200. end if
  201. !********************************************
  202. ! j Loop
  203. !********************************************
  204. do j=1,k
  205. !********************************************
  206. ! A(j,k)=workl(j)
  207. ! workl(j)=0
  208. !********************************************
  209. call position(j,nl,knl,knlp)
  210. if (rang==knl) then
  211. AL(knlp,k)=workl(knlp)
  212. workl(knlp)=0.d0
  213. alpha=-AL(knlp,k)
  214. end if
  215. call MPI_BCAST(alpha,1,MPI_DOUBLE_PRECISION,knl,MPI_COMM_WORLD,code)
  216. !********************************************
  217. ! workl=workl - alpha A(:,j)
  218. !********************************************
  219. call position(j+1,nl,knl,knlp)
  220. if (rang >knl)then
  221. call daxpy(nl,alpha,AL(1,j),1,workl,1)
  222. end if
  223. if (rang==knl) then
  224. call daxpy(nl-knlp+1,alpha,AL(knlp,j),1,workl(knlp),1)
  225. end if
  226. end do
  227. !********************************************
  228. ! End j Loop
  229. !********************************************
  230. if (k.lt.n)then
  231. call MPI_ALLGATHER(workl,nl,MPI_DOUBLE_PRECISION,b,nl,MPI_DOUBLE_PRECISION,MPI_COMM_WORLD,code)
  232. !********************************************
  233. ! Search indice i_0
  234. !********************************************
  235. indice=k+idamax(n_k,b(k1),1)
  236. H_k1=b(indice)
  237. !********************************************
  238. ! Permutation
  239. !********************************************
  240. if (indice.ne.k1) then
  241. if (rang==0) then
  242. call sswap(1,p(indice),1,p(k1),1)
  243. end if
  244. call dswap(1,b(indice),1,b(k1),1)
  245. call dswap(nl,AL(1,indice),1,AL(1,k1),1)
  246. call MPI_BARRIER(MPI_COMM_WORLD,code)
  247. call position(k1,nl,knl,knlp)
  248. call position(indice,nl,inl,inlp)
  249. if (inl==knl) then
  250. if (rang==inl)then
  251. call dswap(n,AL(inlp,1),nl,AL(knlp,1),nl)
  252. end if
  253. else
  254. if (rang==inl) then
  255. call dcopy(n,AL(inlp,1),nl,temp,1)
  256. end if
  257. call MPI_BCAST(temp,n,MPI_DOUBLE_PRECISION,inl,MPI_COMM_WORLD,code)
  258. if (rang==knl)then
  259. call dcopy(n,AL(knlp,1),nl,temp2,1)
  260. end if
  261. call MPI_BCAST(temp2,n,MPI_DOUBLE_PRECISION,knl,MPI_COMM_WORLD,code)
  262. if (rang==inl)then
  263. call dcopy(n,temp2,1,AL(inlp,1),nl)
  264. end if
  265. if (rang==knl)then
  266. call dcopy(n,temp,1,AL(knlp,1),nl)
  267. end if
  268. end if
  269. end if
  270. !********************************************
  271. ! End Permutation
  272. !********************************************
  273. if (H_k1.ne.0.d0)then
  274. !********************************************
  275. ! b=b/(b)_(i_0)
  276. !********************************************
  277. D_inv=1.d0/H_k1
  278. ! call dcopy(n,work,1,b,1)
  279. call dscal(n,D_inv,b,1)
  280. end if
  281. else
  282. H_k1=0.d0
  283. call dscal(n,0.d0,b,1)
  284. end if
  285. !********************************************
  286. ! Application of Givens rotations
  287. !********************************************
  288. if (k.gt.1)then
  289. do i=2,k
  290. call position(i-1,nl,knl,knlp)
  291. call position(i,nl,inl,inlp)
  292. if (inl==knl)then
  293. if (rang==inl)then
  294. btemp=AL(knlp,k)
  295. AL(knlp,k)=c(i-1)*btemp+s(i-1)*AL(inlp,k)
  296. AL(inlp,k)=-s(i-1)*btemp+c(i-1)*AL(inlp,k)
  297. end if
  298. else
  299. if (rang==inl)then
  300. btemp=AL(inlp,k)
  301. end if
  302. if (rang==knl)then
  303. btemp2=AL(knlp,k)
  304. end if
  305. call MPI_BCAST(btemp,1,MPI_DOUBLE_PRECISION,inl,MPI_COMM_WORLD,code)
  306. call MPI_BCAST(btemp2,1,MPI_DOUBLE_PRECISION,knl,MPI_COMM_WORLD,code)
  307. net=net+2
  308. if (rang==inl)then
  309. AL(inlp,k)=-s(i-1)*btemp2+c(i-1)*btemp
  310. end if
  311. if (rang==knl)then
  312. AL(knlp,k)=c(i-1)*btemp2+s(i-1)*btemp
  313. end if
  314. end if
  315. end do
  316. end if
  317. if (k.le.n)then
  318. call position(k,nl,knl,knlp)
  319. if (rang==knl)then
  320. btemp=AL(knlp,k)
  321. end if
  322. call MPI_BCAST(btemp,1,MPI_DOUBLE_PRECISION,knl,MPI_COMM_WORLD,code)
  323. dgam=dsqrt(btemp**2+H_k1**2)
  324. c(k)=dabs(btemp)/dgam
  325. s(k)=(H_k1*dabs(btemp))/(btemp*dgam)
  326. rs(k1)=-s(k)*rs(k)
  327. rs(k)=c(k)*rs(k)
  328. dnorm=dabs(rs(k1))
  329. if (rang==knl)then
  330. AL(knlp,k)=c(k)*btemp+s(k)*H_k1
  331. end if
  332. end if
  333. !********************************************
  334. ! End Givens rotations
  335. !********************************************
  336. end do
  337. !********************************************
  338. ! Solve H_k d_k = alpha e_1
  339. !********************************************
  340. call position(k,nl,knl,knlp)
  341. do j=k,1,-1
  342. call position(j,nl,inl,inlp)
  343. if (rang==inl) then
  344. rs(j)=rs(j)/AL(inlp,j)
  345. btemp=rs(j)
  346. end if
  347. call MPI_BCAST(btemp,1,MPI_DOUBLE_PRECISION,inl,MPI_COMM_WORLD,code)
  348. rs(j)=btemp
  349. work(j)=btemp
  350. call position(j-1,nl,inl,inlp)
  351. if (rang==inl)then
  352. call daxpy(inlp,-btemp,AL(1,j),1,rs(rang*nl+1),1)
  353. end if
  354. if (rang.lt.inl)then
  355. call daxpy(nl,-btemp,AL(1,j),1,rs(rang*nl+1),1)
  356. end if
  357. end do
  358. do j=k,1,-1
  359. btemp=rs(j)
  360. call position(k,nl,knl,knlp)
  361. call position(j+1,nl,inl,inlp)
  362. if (rang==inl)then
  363. if (rang==knl)then
  364. call daxpy((knlp-inlp+1),btemp,AL(inlp,j),1,rs(rang*nl+inlp),1)
  365. end if
  366. if (rang.lt.knl)then
  367. call daxpy(nl-inlp+1,btemp,AL(inlp,j),1,rs(rang*nl+inlp),1)
  368. end if
  369. end if
  370. if (rang.gt.inl)then
  371. if (rang==knl)then
  372. call daxpy(knlp,btemp,AL(1,j),1,rs(rang*nl+1),1)
  373. end if
  374. if (rang.lt.knl)then
  375. call daxpy(nl,btemp,AL(1,j),1,rs(rang*nl+1),1)
  376. end if
  377. end if
  378. end do
  379. !********************************************
  380. ! End Loop
  381. !********************************************
  382. !********************************************
  383. ! Update x_k=x_0 + L_k d_k
  384. !********************************************
  385. call position(k1,nl,knl,knlp)
  386. if (rang.gt.knl)then
  387. call dgemv('N',nl,k,1.d0,AL(1,1),nl,work,1,0.d0,c(rang*nl+1),1)
  388. end if
  389. if (rang==knl)then
  390. call dgemv('N',nl-knlp+1,k,1.d0,AL(knlp,1),nl,work,1,0.d0,c(rang*nl+knlp),1)
  391. end if
  392. call position(k,nl,knl,knlp)
  393. if (rang.lt.knl)then
  394. call daxpy(nl,1.d0,rs(rang*nl+1),1,xl,1)
  395. end if
  396. if (rang==knl)then
  397. call daxpy(knlp,1.d0,rs(rang*nl+1),1,xl,1)
  398. call daxpy(nl-knlp,1.d0,c(rang*nl+knlp+1),1,xl(knlp+1),1)
  399. end if
  400. if (rang.gt.knl)then
  401. call daxpy(nl,1.d0,c(rang*nl+1),1,xl,1)
  402. end if
  403. !********************************************
  404. ! Reorder the components of x_k
  405. !********************************************
  406. call MPI_GATHER(xl,nl,MPI_DOUBLE_PRECISION,x,nl,MPI_DOUBLE_PRECISION,0,MPI_COMM_WORLD,code)
  407. call MPI_BARRIER(MPI_COMM_WORLD,code)
  408. if (rang==0)then
  409. do j=1,n
  410. b(p(j))=x(j)
  411. end do
  412. end if
  413. tempsf=(MPI_WTIME()-tempsf)
  414. tempsd=(MPI_WTIME()-tempsd)
  415. !write(*,*)'rang et temps',rang,tempsf,tempsd
  416. call MPI_REDUCE(tempsf,temps,1,MPI_DOUBLE_PRECISION,MPI_MAX,0,MPI_COMM_WORLD,code)
  417. call MPI_REDUCE(tempsd,temps2,1,MPI_DOUBLE_PRECISION,MPI_MAX,0,MPI_COMM_WORLD,code)
  418. if (rang==0)then
  419. if (iprint >= 2) then
  420. print*,'Results : iter, norm residual, time'
  421. write(*,40)k,dnorm,temps,temps2
  422. end if
  423. write(30,10),k,dnorm
  424. close(30)
  425. open(unit=10,file='temps.txt',status='unknown',access='append')
  426. write(unit=10,FMT=*)'Proc. Number :',Nprocs,'Iter. Number:',k,'Time:',temps,temps2
  427. close(10)
  428. end if
  429. if (rang==0)then
  430. if (iprint==2) then
  431. write(*,*)
  432. write(*,*)' la perm. et les solutions CMRH et EXACTE sont : '
  433. write(*,*)' ______________________________________________ '
  434. if (n.lt.10)then
  435. do i=1,n
  436. write(*,20)p(i), b(i), sol(i)
  437. end do
  438. else
  439. do i=1,10
  440. write(*,20)p(i), b(i), sol(i)
  441. end do
  442. end if
  443. end if
  444. end if
  445. 30 format(A37,4(f14.7,1x))
  446. 20 format(1x,i5,2(1x,f14.8))
  447. 40 format(1x,i5,4(1x,e12.4))
  448. ! deallocate(AL,b,sol,workl,temp,tempn,work,c,s,rs,xl,x,cl)
  449. if (rang==0) then
  450. deallocate(p)
  451. end if
  452. call MPI_FINALIZE(code)
  453. end program PCMRH
  454. !********************************************
  455. ! End Parallel CMRH
  456. !********************************************
  457. !********************************************
  458. ! Matrix Choice
  459. !********************************************
  460. subroutine matrice(A,nl,n,alpha,beta,choix,rang)
  461. integer ::n,i,j,choix,rang,nl,k
  462. real(kind=8),dimension(nl,n)::A
  463. real*8 ::alpha,beta
  464. if (choix==1) then
  465. do i = 1, nl
  466. k=rang*nl+i
  467. do j = 1, k
  468. A(i,j) = (2.d0*dble(j)-1.d0)/dble(n-k+j)
  469. end do
  470. do j = k+1, n
  471. A(i,j) = (2.d0*dble(k)-1.d0)/dble(n-k+j)
  472. end do
  473. end do
  474. end if
  475. if (choix==2)then
  476. do i=1,nl
  477. k=rang*nl+i
  478. do j=1,k
  479. A(i,j)=dble(k)
  480. end do
  481. do j=k+1,n
  482. A(i,j)=dble(j)
  483. end do
  484. end do
  485. end if
  486. end subroutine matrice
  487. !********************************************
  488. ! Solution Choice
  489. !********************************************
  490. subroutine solution(A,b,sol,nl,n,solchoice)
  491. integer ::n,i,nl,solchoice
  492. real(kind=8),dimension(n,n) ::A
  493. real(kind=8),dimension(n) ::sol
  494. real(kind=8),dimension(nl) ::b
  495. real ::rand
  496. do i=1,n
  497. if (solchoice==1) then
  498. sol(i)=1.d0
  499. end if
  500. if (solchoice==2) then
  501. sol(i)=dble(n-i+1)
  502. end if
  503. if (solchoice==3)then
  504. sol(i)=rand(0)
  505. end if
  506. end do
  507. call dgemv('N',nl,n,1.d0,A,nl,sol,1,0.d0,b,1)
  508. end subroutine solution
  509. !********************************************
  510. ! Where are we ?
  511. !********************************************
  512. subroutine position(k,nl,knl,knlp)
  513. integer :: k,nl,knl,knlp
  514. knl=(k-1)/nl
  515. knlp=k-knl*nl
  516. end subroutine position