ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/ripple/ordpar.f
Revision: 1185
Committed: Fri May 21 20:07:10 2004 UTC (20 years, 1 month ago) by xsun
File size: 4237 byte(s)
Log Message:
this is the ripple codes

File Contents

# User Rev Content
1 xsun 1185 SUBROUTINE DIRECT ( RCUT, BOX, DENS, N, nstep, maxbin)
2    
3    
4     COMMON / BLOCK1 / RX, RY, RZ, VX, VY, VZ
5     COMMON / BLOCK2 / UX, UY, UZ, JX, JY, JZ
6     COMMON / BLOCK3/ DIRECTOR
7    
8    
9     C *******************************************************
10     C ** Director and order parameter determination **
11     C *******************************************************
12    
13     integer bin, maxbin, nbins, i, j, n, bind, which
14     integer hist(maxbin), histd(maxbin), startstep
15     integer nstep, stopstep, ndiag, nfilled, ifail, lwork
16     integer it, k
17     double precision delr, rijsq, rxij, ryij, rzij, rij
18     double precision delrd, rijsqd, rijd, orderpar(1000), nideal
19     double precision omat(3,3), evals(100), const, pi, rlower
20     double precision rcut, box, dens, director(3,1000), rupper
21     double precision rx(1000,1000), ry(1000,1000), rz(1000,1000)
22     double precision ux(1000,1000), uy(1000,1000), uz(1000,1000)
23     double precision vx(1000,1000), vy(1000,1000), vz(1000,1000)
24     double precision jx(1000,1000), jy(1000,1000), jz(1000,1000)
25     double precision grd(5000), gr(5000), max, binmin, binmax
26     parameter(lwork=9)
27     double precision onethird, work(lwork), ordvals(5000)
28     character*1 job, uplo
29    
30    
31    
32     open(30, file = 'ordhist.dat')
33     open(31, file = 'director.dat')
34    
35     onethird = 1.0d0/3.0d0
36     startstep = 1
37     stopstep = nstep
38     ndiag = 3
39     nfilled = 3
40     job = 'V'
41     uplo = 'U'
42     ifail = 0
43     pi = 3.1415927d0
44     c write(*,*) 'nstep', nstep
45     binmin = 0.0
46     binmax = 1.0
47     delr = (binmax-binmin)/dble(maxbin)
48    
49     do k = 1, maxbin
50     ordvals(k) = 0.0
51     hist(k) = 0.0
52     enddo
53    
54     do it = startstep, stopstep
55    
56     c Important part starts here:
57     c zero out the omat
58    
59     do i = 1,3
60     do j = 1,3
61     omat(i,j) = 0.0d0
62     enddo
63     enddo
64    
65     c fill the omat in each configuration
66    
67     do i = 1,n
68     omat(1,1) = omat(1,1) + ux(i,it)*ux(i,it)-onethird
69     omat(1,2) = omat(1,2) + ux(i,it)*uy(i,it)
70     omat(1,3) = omat(1,3) + ux(i,it)*uz(i,it)
71     omat(2,1) = omat(2,1) + uy(i,it)*ux(i,it)
72     omat(2,2) = omat(2,2) + uy(i,it)*uy(i,it)-onethird
73     omat(2,3) = omat(2,3) + uy(i,it)*uz(i,it)
74     omat(3,1) = omat(3,1) + uz(i,it)*ux(i,it)
75     omat(3,2) = omat(3,2) + uz(i,it)*uy(i,it)
76     omat(3,3) = omat(3,3) + uz(i,it)*uz(i,it)-onethird
77     enddo
78    
79     c divide by the number of particles
80    
81     do i = 1,3
82     do j = 1,3
83     omat(i,j) = omat(i,j)/dble(n)
84     enddo
85     enddo
86    
87    
88     c diagonalize omat to get eigenvalues (evals) and
89     c eigenvectors (placed in omat)
90    
91     call dsyev(job, uplo, nfilled, omat, ndiag, evals, work, lwork
92     : , ifail)
93     c write(*,*) evals(1), evals(2), evals(3)
94     c director axis will have largest eigenvalue:
95    
96     max = 0.0
97     do i = 1,3
98     if(dabs(evals(i)).gt.max) then
99     which = i
100     max = dabs(evals(i))
101     endif
102     enddo
103     c write(*,*) max
104    
105     c find director axis:
106     director(1,it) = omat(1,which)
107     director(2,it) = omat(2,which)
108     director(3,it) = omat(3,which)
109     c write(*,*) director(1,it), director(2,it), director(3,it), it
110    
111     c find orientational order parameter
112     orderpar (it) = 1.5d0 * max
113    
114     c this ends the important part
115    
116     c make a histogram of orderparameters observed in this simulation:
117    
118     bin = int(orderpar(it)/delr)+1
119    
120    
121     if(bin.le.maxbin) then
122     hist(bin) = hist(bin) + 1
123     endif
124    
125     write(31,*) orderpar(it), it
126    
127     enddo
128    
129     ! *** normalization ***
130    
131     c const = 4.0d0 * pi * dens / 3.0
132     const = 1.0
133    
134     do bin = 1,maxbin
135    
136     rlower = real ( bin-1 ) * delr
137     rupper = rlower + delr
138     ordvals(bin) = rlower + (delr/2.0d0)
139     nideal = const * ( rupper**3 - rlower**3 )
140     gr(bin) = real(hist(bin)) / real(nstep) / nideal
141    
142     write(30,*) ordvals(bin), gr(bin)
143    
144    
145     enddo
146    
147     return
148     end
149