randvectors.f90 3.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185
  1. module randvectors
  2. ! This file contains some subroutines :
  3. ! rand0, vecrand
  4. ! helsing, rbf
  5. ! Author: S. Duminil
  6. implicit none
  7. contains
  8. subroutine rand0(n)
  9. integer n,i,init(4)
  10. real(kind=8),allocatable,dimension(:) ::x
  11. integer*4,dimension(3) ::timearray
  12. real ::rand
  13. call itime(timearray) ! Get the current time
  14. i = rand ( timearray(1)+timearray(2)+timearray(3) )
  15. close(20)
  16. allocate(x(n))
  17. do i=1,n
  18. x(i)=rand(0);
  19. enddo
  20. open(unit=10,file='rand0.dat',status='unknown')
  21. do i=1,n
  22. write(unit=10,FMT=*) x(i)
  23. enddo
  24. close(10)
  25. deallocate(x)
  26. end subroutine rand0
  27. subroutine vecrand(n)
  28. ! vecrand.f90
  29. ! This file creates two random vectors and stores them in the file vecrand.dat
  30. !
  31. ! 01 February 13
  32. ! Created by S.Duminil
  33. integer n,i,j,a,b,init(4)
  34. real(kind=8),allocatable,dimension(:) ::x,y
  35. integer*4,dimension(3) ::timearray
  36. real ::rand
  37. call itime(timearray) ! Get the current time
  38. i = rand ( timearray(1)+timearray(2)+timearray(3) )
  39. a=1
  40. b=0
  41. do while(a.ge.b)
  42. print*,'Enter the interval limits'
  43. read*,a,b
  44. if (a.ge.b) then
  45. print*,'Choose a<b'
  46. endif
  47. end do
  48. allocate(x(n),y(n))
  49. do i=1,n
  50. x(i)=rand(0)*dble(b-a)-dble(b);
  51. y(i)=rand(0)*dble(b-a)-dble(b);
  52. enddo
  53. open(unit=10,file='vecrand.dat',status='unknown')
  54. do i=1,n
  55. write(unit=10,FMT=*) x(i),y(i)
  56. enddo
  57. close(10)
  58. deallocate(x,y)
  59. end subroutine vecrand
  60. subroutine helsing(n)
  61. ! helsing.f90
  62. ! This file creates a matrix defined by :
  63. ! A(i,j)= -log|z(i)-z(j)| , if i .neq. j
  64. ! -log|r(i)|
  65. ! where z(i) are n somehow randomly distributed points in a unit square
  66. ! centered at the origin in the complex plane and where each r(i) is a
  67. ! number in (0,d(i)[, d(i) being the distance between the point z(i)
  68. ! and its nearest neighbour.
  69. ! For more details, see:
  70. ! S. Duminil, A parallel implementation of the CMRH method for dense
  71. ! linear systems, Numer. Algor., DOI : 10.1007/s11075-012-9616-4
  72. !
  73. ! We store this matrix in matrixfile.dat
  74. ! 01 February 2013
  75. ! S. Duminil
  76. integer :: m,n,coef,d,i,j,init(4)
  77. real(kind=8) :: l,r
  78. real(kind=8), allocatable, dimension(:) :: xx,yy,value,value2
  79. real(kind=8), allocatable, dimension(:,:) :: A
  80. m=n
  81. allocate(value(2*m),value2(m),xx(m),yy(m),A(n,n))
  82. open(unit=30,file='vecrand.dat',status='old')
  83. read(30,*)value
  84. do i=1,m
  85. xx(i)=value(2*i-1)
  86. yy(i)=value(2*i)
  87. end do
  88. close(30)
  89. open(unit=40,file='rand0.dat',status='old')
  90. read(40,*)value2
  91. close(40)
  92. coef=-1
  93. do i=1,n
  94. d=0
  95. do j=1,m
  96. r=dsqrt((xx(i)-xx(j))**2+(yy(j)-yy(i))**2)
  97. if (r>0) then
  98. A(i,j)=coef*log(r)
  99. if (d.eq.0)then
  100. d=j
  101. l=dble(0.5*value2(i)*dble(d))
  102. A(i,i)=-log(l)
  103. end if
  104. end if
  105. end do
  106. end do
  107. deallocate(xx,yy,value,value2)
  108. open(unit=10,file='matrixfile.dat',status='unknown')
  109. do i=1,n
  110. write(10,*) (A(i,j),j=1,n)
  111. end do
  112. close(10)
  113. deallocate(A)
  114. end subroutine helsing
  115. subroutine rbf(n)
  116. ! rbf.f90
  117. ! This file creates a matrix defined by :
  118. !
  119. !
  120. ! We store this matrix in matrixfile.dat
  121. ! 01 February 2013
  122. ! S. Duminil
  123. integer :: m,n,d,i,j,init(4)
  124. real(kind=8) :: l,r,coef
  125. real(kind=8), allocatable, dimension(:) :: xx,yy,value,value2
  126. real(kind=8), allocatable, dimension(:,:) :: A
  127. real :: rand
  128. m=n-3
  129. allocate(value(2*m),value2(m),xx(m),yy(m),A(n,n))
  130. open(unit=30,file='vecrand.dat',status='old')
  131. read(30,*)value
  132. do i=1,m
  133. xx(i)=value(2*i-1)
  134. yy(i)=value(2*i)
  135. end do
  136. close(30)
  137. do i=1,m
  138. d=0
  139. do j=1,m
  140. r=dsqrt((xx(i)-xx(j))**2+(yy(j)-yy(i))**2)
  141. if (r>0) then
  142. A(i,j)=r*r*log(r)
  143. if (d==0)then
  144. d=j
  145. coef=0.5*d*rand(0)
  146. A(i,i)=coef*coef*log(coef)
  147. end if
  148. end if
  149. end do
  150. end do
  151. do j=1,m
  152. A(m+1,j)=xx(j)
  153. A(m+2,j)=yy(j)
  154. A(m+3,j)=1.d0
  155. A(j,m+1)=xx(j)
  156. A(j,m+2)=yy(j)
  157. A(j,m+3)=1.d0
  158. end do
  159. do i=m+1,n
  160. do j=m+1,n
  161. A(i,j)=0.d0
  162. end do
  163. end do
  164. deallocate(xx,yy,value,value2)
  165. open(unit=10,file='matrixfile.dat',status='unknown')
  166. do i=1,n
  167. write(10,*) (A(i,j),j=1,n)
  168. end do
  169. close(10)
  170. deallocate(A)
  171. end subroutine rbf
  172. end module randvectors