CMRH.f90 10 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429
  1. program CMRH
  2. !***************************************************************
  3. ! CMRH program
  4. !***************************************************************
  5. external SSWAP,DCOPY,DSCAL,DGEMV,DSWAP
  6. intrinsic dabs,dsqrt
  7. !********************************************
  8. ! VARIABLES
  9. !********************************************
  10. integer ::n,code,i,j,k,choix,solchoice,iprint
  11. real(kind=8) ::init(5)
  12. real(kind=8),allocatable,dimension(:,:) ::A
  13. real(kind=8) ::btemp,bmax,btemp2,err,res
  14. real(kind=8),allocatable,dimension(:) ::b,sol,rs,temp,x,work,tempn,c,s,temp2,xx,yy,valeurs
  15. integer,allocatable,dimension(:) ::p
  16. real*8 ::dnorm2,D_inv,beta,dnorm,dnrm2,tol,alpha,H_k1,dgam,r
  17. integer ::indice,idamax,k1,n_k
  18. real dtime, delta, delta0, da(2), dt1, dt2, dt3
  19. real etime, eelta, eelta0, ea(2), et1, et2, et3
  20. real t1, t2, t3, tm1, tm2, tm3
  21. real dtime1, delta1, delta01, da1(2)
  22. real etime1, eelta1, eelta01, ea1(2),l,p1,p2
  23. integer nb_ligne
  24. real ::rand
  25. da(1)=0.d0
  26. da(2)=1.d0
  27. !call itime(timearray) ! Get the current time
  28. !i = rand ( timearray(1)+timearray(2)+timearray(3) )
  29. !************************************
  30. ! Matrix Initialisation
  31. !************************************
  32. open(unit=10,file='inputfile.dat',status='old')
  33. read(10,*)init
  34. close(10)
  35. iprint=int(init(1))
  36. n=int(init(2))
  37. choix=int(init(3))
  38. solchoice=int(init(4))
  39. tol=init(5)
  40. !call init(iprint,n,choix,solchoice)
  41. allocate(b(n),rs(n),x(n),A(n,n),work(n),sol(n))
  42. if (choix<3)then
  43. call matrice(A,n,n,2.d0,1.d0,choix)
  44. else
  45. allocate(valeurs(n))
  46. open(unit=30,file='matrixfile.dat',status='old')
  47. do i=1,n
  48. read(30,*)valeurs
  49. A(i,:)=valeurs(:)
  50. enddo
  51. close(30)
  52. endif
  53. !********************************************
  54. ! End Matrix initialisation
  55. !********************************************
  56. !********************************************
  57. ! Solution initialisation
  58. !********************************************
  59. call solution(A,b,sol,n,n,solchoice)
  60. !********************************************
  61. ! End solution initialisation
  62. !********************************************
  63. !********************************************
  64. ! Permutation Vector initialisation
  65. ! and computation of initial residual
  66. !********************************************
  67. allocate(p(n))
  68. do i=1,n
  69. p(i)=i
  70. end do
  71. dnorm2=dnrm2(n,b,1)
  72. if (iprint==2)then
  73. print*,''
  74. print*,'||r0|| =',dnorm2
  75. print*,''
  76. end if
  77. !********************************************
  78. ! Computation of max b(i)
  79. !********************************************
  80. indice = idamax(n,b,1)
  81. beta = b(indice)
  82. D_inv = 1.d0/beta
  83. !********************************************
  84. ! First permutation
  85. !********************************************
  86. if (indice .ne.1) then
  87. call dswap(1,b(indice),1,b(1),1)
  88. call dswap(n,A(1,indice),1,A(1,1),1)
  89. call dswap(n,A(indice,1),n,A(1,1),n)
  90. call sswap(1,p(indice),1,p(1),1)
  91. end if
  92. !********************************************
  93. ! End permutation
  94. !********************************************
  95. ! call dscal(n,0.d0,x,1)
  96. call dscal(n,D_inv,b,1)
  97. rs(1)=beta
  98. dnorm=dabs(beta)
  99. allocate(c(n),s(n))
  100. call dscal(n,0.d0,x,1)
  101. ! Fin initialisation de A
  102. !print*,'Fin initialisation des matrices'
  103. k=0
  104. if (iprint==2)then
  105. write(*,*)'iter., pseudo-residual norm'
  106. end if
  107. !tol=1.d-7
  108. delta0 = dtime(da)
  109. eelta0 = etime(ea)
  110. open(unit=30,file='residual.dat',status='unknown')
  111. write(30,*)'Iteration, Pseudo-Residual Norm'
  112. !********************************************
  113. ! Loop
  114. !********************************************
  115. do while((dnorm.gt.tol).and.(k.lt.n))
  116. k=k+1;
  117. n_k=n-k;
  118. k1=k+1;
  119. if (iprint==2)then
  120. write(*,10)k-1,dnorm
  121. end if
  122. write(30,10)k-1,dnorm
  123. 10 format(i5,2x,e12.4)
  124. !********************************************
  125. ! workl = A*b
  126. !********************************************
  127. call dcopy(n,A(1,k),1,work,1)
  128. call dgemv('N',n,n_k,1.d0,A(1,k1),n,b(k1),1,1.d0,work,1)
  129. ! ! call dscal(nl,0.d0,workl,1)
  130. ! ! do j=k1,n
  131. ! ! do i=1,nl
  132. ! ! workl(i)=workl(i)+AL(i,j)*b(j)
  133. ! ! end do
  134. ! ! end do
  135. !********************************************
  136. ! A(:,k)=b
  137. !********************************************
  138. call dcopy(n_k,b(k1),1,A(k1,k),1)
  139. !********************************************
  140. ! j Loop
  141. !********************************************
  142. do j=1,k
  143. !********************************************
  144. ! A(j,k)=workl(j)
  145. ! workl(j)=0
  146. !********************************************
  147. A(j,k)=work(j)
  148. work(j)=0.d0
  149. alpha=-A(j,k)
  150. !********************************************
  151. ! workl=workl - alpha A(:,j)
  152. !********************************************
  153. call daxpy(n-j,alpha,A(j+1,j),1,work(j+1),1)
  154. end do
  155. !********************************************
  156. ! End j Loop
  157. !********************************************
  158. if (k.lt.n)then
  159. !********************************************
  160. ! Search indice i_0
  161. !********************************************
  162. indice=k+idamax(n_k,work(k1),1)
  163. H_k1=work(indice)
  164. !********************************************
  165. ! Permutation
  166. !********************************************
  167. if (indice.ne.k1) then
  168. call sswap(1,p(indice),1,p(k1),1)
  169. call dswap(1,work(indice),1,work(k1),1)
  170. call dswap(n,A(1,indice),1,A(1,k1),1)
  171. call dswap(n,A(indice,1),n,A(k1,1),n)
  172. end if
  173. !********************************************
  174. ! End Permutation
  175. !********************************************
  176. if (H_k1.ne.0.d0)then
  177. !********************************************
  178. ! b=b/(b)_(i_0)
  179. !********************************************
  180. D_inv=1.d0/H_k1
  181. call dcopy(n,work,1,b,1)
  182. call dscal(n,D_inv,b,1)
  183. end if
  184. else
  185. H_k1=0.d0
  186. call dscal(n,0.d0,b,1)
  187. end if
  188. !********************************************
  189. ! Application of Givens rotations
  190. !********************************************
  191. if (k.gt.1)then
  192. do i=2,k
  193. btemp=A(i-1,k)
  194. A(i-1,k)=c(i-1)*btemp+s(i-1)*A(i,k)
  195. A(i,k)=-s(i-1)*btemp+c(i-1)*A(i,k)
  196. end do
  197. end if
  198. if (k.le.n)then
  199. btemp=A(k,k)
  200. dgam=dsqrt(btemp**2+H_k1**2)
  201. c(k)=dabs(btemp)/dgam
  202. s(k)=(H_k1*dabs(btemp))/(btemp*dgam)
  203. rs(k1)=-s(k)*rs(k)
  204. rs(k)=c(k)*rs(k)
  205. dnorm=dabs(rs(k1))
  206. A(k,k)=c(k)*btemp+s(k)*H_k1
  207. end if
  208. !********************************************
  209. ! End Givens rotations
  210. !********************************************
  211. end do
  212. !********************************************
  213. ! Solve H_k d_k = alpha e_1
  214. !********************************************
  215. call dtrsv('U','N','N',k,A,n,rs,1)
  216. call dcopy(k,rs,1,work,1)
  217. call dtrmv('L','N','U',k,A,n,rs,1)
  218. call dgemv('N',n-k,k,1.d0,A(k1,1),n,work,1,0.d0,c,1)
  219. call daxpy(k,1.d0,rs,1,x,1)
  220. call daxpy(n-k,1.d0,c,1,x(k1),1)
  221. do j=1,n
  222. b(p(j))=x(j)
  223. end do
  224. !!***********************************************
  225. !!allocate(b(n),rs(n),x(n),A(n,n),work(n),sol(n))
  226. !if (choix<3)then
  227. !call matrice(A,n,n,2.d0,1.d0,choix)
  228. !else
  229. !allocate(valeurs(n))
  230. !open(unit=30,file='matrixfile.dat',status='old')
  231. !do i=1,n
  232. !read(30,*)valeurs
  233. !A(i,:)=valeurs(:)
  234. !enddo
  235. !close(30)
  236. !endif
  237. !!********************************************
  238. !! End Matrix initialisation
  239. !!********************************************
  240. !!********************************************
  241. !! Solution initialisation
  242. !!********************************************
  243. !call solution(A,work,sol,n,n,solchoice)
  244. !!*********************************************
  245. !! Residual and Error Norm
  246. !!*********************************************
  247. !call dgemv('N',n,n,-1.d0,A(k1,1),n,b,1,1.d0,work,1)
  248. !dnorm=dnorm2(n,work,1)
  249. !call dcopy(n,sol,1,rs,1)
  250. !call daxpy(n,-1.d0,b,1,rs,1)
  251. !dnorm2=dnorm2(n,rs,1)
  252. !!***********************************************
  253. delta = dtime(da)
  254. eelta = etime(ea)
  255. dt2 = delta-delta0
  256. et2 = eelta-eelta0
  257. t2 = dt2+et2
  258. tm2 = 0.5*(t2)
  259. !tm2=0.d0
  260. if (iprint >= 2) then
  261. print*,'Results : iter, pseudo-residual norm, time'
  262. write(*,40)k,dnorm, tm2
  263. end if
  264. write(30,20)k,dnorm
  265. close(30)
  266. open(unit=100,file='tempsseq.dat',status='unknown',access='append')
  267. write(unit=100,FMT=*)'Iteration Number :',k,' temps :',tm2
  268. close(100)
  269. !20 format(i5,2x,e12.4,e12.4)
  270. if (iprint==2) then
  271. write(*,*)
  272. write(*,*)' Swap, CMRH Solution, Exact Solution : '
  273. write(*,*)' ______________________________________________ '
  274. if (n.lt.10)then
  275. do i=1,n
  276. write(*,20)p(i), b(i), sol(i)
  277. end do
  278. else
  279. do i=1,10
  280. write(*,20)p(i), b(i), sol(i)
  281. end do
  282. end if
  283. end if
  284. 30 format(A37,4(f14.7,1x))
  285. 20 format(1x,i5,2(1x,f14.8))
  286. 40 format(1x,i5,2(1x,e12.4))
  287. deallocate(A,b,sol,work,c,s,rs,x)
  288. deallocate(p)
  289. end program CMRH
  290. !********************************************
  291. ! End CMRH
  292. !********************************************
  293. !********************************************
  294. ! Matrix Choice
  295. !********************************************
  296. subroutine matrice(A,nl,n,alpha,beta,choix)
  297. integer ::n,i,j,choix,nl
  298. real(kind=8),dimension(nl,n)::A
  299. real*8 ::alpha,beta
  300. if (choix==1) then
  301. do i = 1, nl
  302. do j = 1, i
  303. A(i,j) = (2.d0*dble(j)-1.d0)/dble(n-i+j)
  304. end do
  305. do j = i+1, n
  306. A(i,j) = (2.d0*dble(i)-1.d0)/dble(n-i+j)
  307. end do
  308. end do
  309. end if
  310. if (choix==2)then
  311. do i=1,nl
  312. do j=1,i
  313. A(i,j)=dble(i)
  314. end do
  315. do j=i+1,n
  316. A(i,j)=dble(j)
  317. end do
  318. end do
  319. end if
  320. end subroutine matrice
  321. !********************************************
  322. ! Solution Choice
  323. !********************************************
  324. subroutine solution(A,b,sol,nl,n,solchoice)
  325. integer ::n,i,nl,solchoice
  326. real(kind=8),dimension(n,n) ::A
  327. real(kind=8),dimension(n) ::sol
  328. real(kind=8),dimension(nl) ::b
  329. do i=1,n
  330. if (solchoice==1) then
  331. sol(i)=1.d0
  332. end if
  333. if (solchoice==2) then
  334. sol(i)=dble(n-i+1)
  335. end if
  336. if (solchoice==3)then
  337. sol(i)=rand(0)
  338. end if
  339. end do
  340. call dgemv('N',nl,n,1.d0,A,nl,sol,1,0.d0,b,1)
  341. end subroutine solution
  342. !subroutine init(iprint,n,choix,choixsol)
  343. !integer :: iprint,n,choix,choixsol
  344. !print*,'Would you print results ? : 1-No / 2-All / 3-Time and final residual norm'
  345. !read*,iprint
  346. !print*,'Enter matrix size : '
  347. !read*,n
  348. !print*,'Enter matrix choice : (more details in README.txt) '
  349. !print*,'1- A(i,j)=2j-1 / n-i+j for j=1,k '
  350. !print*,' 2i-1 / n-i+j for j=i+1,n '
  351. !print*,'2- A(i,j)=i for j=1,i '
  352. !print*,' j for j=i+1,n '
  353. !print*,'3- Matrix File (copy in matrixfile.dat) '
  354. !read*,choix
  355. !print*,'Enter solution choice : 1- [1,...,1]^T / 2- [n,...,1]^T '
  356. !read*,choixsol
  357. !endsubroutine init