unres_package_Oct_2016 from emilial
[unres4.git] / source / unres / random.f90
index 61b3f14..fa14312 100644 (file)
@@ -4,6 +4,7 @@
       use prng ! prng.f90 or prng_32.f90
       use math
       implicit none
+!      public :: rndv
 !
 !-----------------------------------------------------------------------------
       contains
@@ -85,7 +86,7 @@
         data iset/0/
 !elwrite(iout,*) "anorm distr start",x,sigma,alowb,aupb
         if(iset.eq.0) then
-1               v1=2.0d0*ran_number(0.0d0,1.0d0)-1.0d0
+    1           v1=2.0d0*ran_number(0.0d0,1.0d0)-1.0d0
                 v2=2.0d0*ran_number(0.0d0,1.0d0)-1.0d0
                 rsq=v1**2+v2**2
                 if(rsq.ge.1.d0.or.rsq.eq.0.0d0) goto 1
 !     enddo
       if (eig(1).lt.eig_limit) then
         print *,'From Mult_Norm: Eigenvalues of A are too small.'
-        fail=.true.    
-       return
+        fail=.true.
+      return
       endif
 ! 
 ! Generate points following the normal distributions along the principal
 ! axes of the moment matrix. Store in WORK.
 !
       do i=1,n
-       sigma=1.0D0/dsqrt(eig(i))
-       alim=-3.0D0*sigma
-       work(i)=anorm_distr(0.0D0,sigma,-alim,alim)
+        sigma=1.0D0/dsqrt(eig(i))
+        alim=-3.0D0*sigma
+        work(i)=anorm_distr(0.0D0,sigma,-alim,alim)
       enddo
 !
 ! Transform the vector of normal variables back to the original basis.
 !
       do i=1,n
-       xi=0.0D0
-       do j=1,n
-         xi=xi+a(i,j)*work(j)
+        xi=0.0D0
+        do j=1,n
+          xi=xi+a(i,j)*work(j)
         enddo
-       x(i)=xi
+        x(i)=xi
       enddo
       return
       end subroutine mult_norm
       enddo
       ww=0.0D0
       do i=1,n
-       xi=pinorm(x(i)-z(i))
-       ww=ww+0.5D0*a(i,i)*xi*xi
-       do j=i+1,n
-         ww=ww+a(i,j)*xi*pinorm(x(j)-z(j))
+        xi=pinorm(x(i)-z(i))
+        ww=ww+0.5D0*a(i,i)*xi*xi
+        do j=i+1,n
+          ww=ww+a(i,j)*xi*pinorm(x(j)-z(j))
         enddo
       enddo
       dec=ran_number(0.0D0,1.0D0)