randvectors.f90 3.7 KB

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