1 c-------------------------------------------------------------
3 subroutine local_move_init(debug)
7 implicit real*8 (a-h,o-z)
8 include 'DIMENSIONS' ! Needed by COMMON.LOCAL
9 include 'COMMON.GEO' ! For pi, deg2rad
10 include 'COMMON.LOCAL' ! For vbl
11 include 'COMMON.LOCMOVE'
17 c Determine wheter to do some debugging output
20 c Set the init_called flag to 1
23 c The following are never changed
24 min_theta=60.D0*deg2rad ! (0,PI)
25 max_theta=175.D0*deg2rad ! (0,PI)
26 dmin2=vbl*vbl*2.*(1.-cos(min_theta))
27 dmax2=vbl*vbl*2.*(1.-cos(max_theta))
30 small2=0.5*small*small
32 c Not really necessary...
40 c-------------------------------------------------------------
42 subroutine local_move(n_start, n_end, PHImin, PHImax)
43 c Perform a local move between residues m and n (inclusive)
44 c PHImin and PHImax [0,PI] determine the size of the move
45 c Works on whatever structure is in the variables theta and phi,
46 c sidechain variables are left untouched
47 c The final structure is NOT minimized, but both the cartesian
48 c variables c and the angles are up-to-date at the end (no further
49 c chainbuild is required)
53 implicit real*8 (a-h,o-z)
56 include 'COMMON.CHAIN'
58 include 'COMMON.MINIM'
59 include 'COMMON.SBRIDGE'
60 include 'COMMON.LOCMOVE'
65 double precision ran_number
69 integer n_start, n_end ! First and last residues to move
70 double precision PHImin, PHImax ! min/max angles [0,PI]
74 double precision min,max
78 c Check if local_move_init was called. This assumes that it
79 c would not be 1 if not explicitely initialized
80 if (init_called.ne.1) then
81 write(6,*)' *** local_move_init not called!!!'
85 c Quick check for crazy range
86 if (n_start.gt.n_end .or. n_start.lt.1 .or. n_end.gt.nres) then
87 write(6,'(a,i3,a,i3)')
88 + ' *** Cannot make local move between n_start = ',
89 + n_start,' and n_end = ',n_end
93 c Take care of end residues first...
94 if (n_start.eq.1) then
95 c Move residue 1 (completely random)
96 theta(3)=ran_number(min_theta,max_theta)
97 phi(4)=ran_number(-PI,PI)
102 if (n_end.eq.nres) then
103 c Move residue nres (completely random)
104 theta(nres)=ran_number(min_theta,max_theta)
105 phi(nres)=ran_number(-PI,PI)
111 c ...then go through all other residues one by one
112 c Start from the two extremes and converge
117 c$$$c Move the first two residues by less than the others
118 c$$$ if (i-n_start.lt.3) then
119 c$$$ if (i-n_start.eq.0) then
122 c$$$ else if (i-n_start.eq.1) then
125 c$$$ else if (i-n_start.eq.2) then
131 c The actual move, on residue i
132 iretcode=move_res(min,max,i) ! Discard iretcode
138 c$$$c Move the last two residues by less than the others
139 c$$$ if (n_end-j.lt.3) then
140 c$$$ if (n_end-j.eq.0) then
143 c$$$ else if (n_end-j.eq.1) then
146 c$$$ else if (n_end-j.eq.2) then
152 c The actual move, on residue j
153 iretcode=move_res(min,max,j) ! Discard iretcode
158 call int_from_cart(.false.,.false.)
163 c-------------------------------------------------------------
165 subroutine output_tabs
166 c Prints out the contents of a_..., b_..., res_...
171 include 'COMMON.LOCMOVE'
178 write(6,'(8f7.1)')(a_ang(i)*rad2deg,i=0,a_n-1)
179 write(6,'(8(2x,3l1,2x))')((a_tab(i,j),i=0,2),j=0,a_n-1)
182 write(6,'(4f7.1)')(b_ang(i)*rad2deg,i=0,b_n-1)
183 write(6,'(4(2x,3l1,2x))')((b_tab(i,j),i=0,2),j=0,b_n-1)
186 write(6,'(12f7.1)')(res_ang(i)*rad2deg,i=0,res_n-1)
187 write(6,'(12(2x,3l1,2x))')((res_tab(0,i,j),i=0,2),j=0,res_n-1)
188 write(6,'(12(2x,3l1,2x))')((res_tab(1,i,j),i=0,2),j=0,res_n-1)
189 write(6,'(12(2x,3l1,2x))')((res_tab(2,i,j),i=0,2),j=0,res_n-1)
194 c-------------------------------------------------------------
196 subroutine angles2tab(PHImin,PHImax,n,ang,tab)
197 c Only uses angles if [0,PI] (but PHImin cannot be 0.,
198 c and PHImax cannot be PI)
205 double precision PHImin,PHImax
209 double precision ang(0:3)
213 if (PHImin .eq. PHImax) then
214 c Special case with two 010's
224 else if (PHImin .eq. PI) then
225 c Special case with one 010
231 else if (PHImax .eq. 0.) then
232 c Special case with one 010
241 if (PHImin .gt. 0.) then
242 c Start of range (011)
254 if (PHImax .lt. PI) then
255 c Start of range (011)
272 c-------------------------------------------------------------
274 subroutine minmax_angles(x,y,z,r,n,ang,tab)
275 c When solutions do not exist, assume all angles
276 c are acceptable - i.e., initial geometry must be correct
281 include 'COMMON.LOCMOVE'
284 double precision x,y,z,r
288 double precision ang(0:3)
292 double precision num, denom, phi
293 double precision Kmin, Kmax
297 num = x*x + y*y + z*z
300 if (denom .gt. 0.) then
302 denom = 2.*r*sqrt(denom)
304 Kmin = (num - dmin2)/denom
305 Kmax = (num - dmax2)/denom
307 c Allowed values of K (else all angles are acceptable)
310 if (Kmin .gt. 1. .or. abs(Kmin-1.) .lt. small2) then
312 else if (Kmin .lt. -1. .or. abs(Kmin+1.) .lt. small2) then
318 if (Kmax .lt. -1. .or. abs(Kmax+1.) .lt. small2) then
320 else if (Kmax .gt. 1. .or. abs(Kmax-1.) .lt. small2) then
326 if (Kmax .lt. Kmin) Kmax = Kmin
328 call angles2tab(Kmin, Kmax, n, ang, tab)
330 c Add phi and check that angles are within range (-PI,PI]
333 if (ang(i) .le. -PI) then
334 ang(i) = ang(i)+2.*PI
335 else if (ang(i) .gt. PI) then
336 ang(i) = ang(i)-2.*PI
344 c-------------------------------------------------------------
346 subroutine construct_tab
347 c Take a_... and b_... values and produces the results res_...
348 c x_ang are assumed to be all different (diff > small)
349 c x_tab(1,i) must be 1 for all i (i.e., all x_ang are acceptable)
353 include 'COMMON.LOCMOVE'
356 integer n_max,i,j,index
362 if (n_max .eq. 0) then
369 res_tab(j,0,i) = .true.
370 res_tab(j,2,i) = .true.
371 res_tab(j,1,i) = .false.
379 res_ang(index) = flag
383 if ((a_ang(i)-phi).gt.small .and.
384 + a_ang(i) .lt. res_ang(index)) then
385 c Found a lower angle
386 res_ang(index) = a_ang(i)
387 c Copy the values from a_tab into res_tab(0,,)
388 res_tab(0,0,index) = a_tab(0,i)
389 res_tab(0,1,index) = a_tab(1,i)
390 res_tab(0,2,index) = a_tab(2,i)
391 c Set default values for res_tab(1,,)
392 res_tab(1,0,index) = .true.
393 res_tab(1,1,index) = .false.
394 res_tab(1,2,index) = .true.
395 else if (abs(a_ang(i)-res_ang(index)).lt.small) then
396 c Found an equal angle (can only be equal to a b_ang)
397 res_tab(0,0,index) = a_tab(0,i)
398 res_tab(0,1,index) = a_tab(1,i)
399 res_tab(0,2,index) = a_tab(2,i)
404 if ((b_ang(i)-phi).gt.small .and.
405 + b_ang(i) .lt. res_ang(index)) then
406 c Found a lower angle
407 res_ang(index) = b_ang(i)
408 c Copy the values from b_tab into res_tab(1,,)
409 res_tab(1,0,index) = b_tab(0,i)
410 res_tab(1,1,index) = b_tab(1,i)
411 res_tab(1,2,index) = b_tab(2,i)
412 c Set default values for res_tab(0,,)
413 res_tab(0,0,index) = .true.
414 res_tab(0,1,index) = .false.
415 res_tab(0,2,index) = .true.
416 else if (abs(b_ang(i)-res_ang(index)).lt.small) then
417 c Found an equal angle (can only be equal to an a_ang)
418 res_tab(1,0,index) = b_tab(0,i)
419 res_tab(1,1,index) = b_tab(1,i)
420 res_tab(1,2,index) = b_tab(2,i)
424 if (res_ang(index) .eq. flag) then
427 else if (index .eq. n_max-1) then
431 phi = res_ang(index) ! Store previous angle
440 do while (.not.res_tab(0,1,index))
443 done = res_tab(0,2,index)
445 if (res_tab(0,1,i)) then
446 done = res_tab(0,2,i)
448 res_tab(0,0,i) = done
449 res_tab(0,1,i) = done
450 res_tab(0,2,i) = done
453 done = res_tab(0,0,index)
455 if (res_tab(0,1,i)) then
456 done = res_tab(0,0,i)
458 res_tab(0,0,i) = done
459 res_tab(0,1,i) = done
460 res_tab(0,2,i) = done
465 res_tab(0,0,i) = .true.
466 res_tab(0,1,i) = .true.
467 res_tab(0,2,i) = .true.
473 do while (.not.res_tab(1,1,index))
476 done = res_tab(1,2,index)
478 if (res_tab(1,1,i)) then
479 done = res_tab(1,2,i)
481 res_tab(1,0,i) = done
482 res_tab(1,1,i) = done
483 res_tab(1,2,i) = done
486 done = res_tab(1,0,index)
488 if (res_tab(1,1,i)) then
489 done = res_tab(1,0,i)
491 res_tab(1,0,i) = done
492 res_tab(1,1,i) = done
493 res_tab(1,2,i) = done
498 res_tab(1,0,i) = .true.
499 res_tab(1,1,i) = .true.
500 res_tab(1,2,i) = .true.
504 c Finally fill the last row with AND operation
507 res_tab(2,j,i) = (res_tab(0,j,i) .and. res_tab(1,j,i))
514 c-------------------------------------------------------------
516 subroutine construct_ranges(phi_n,phi_start,phi_end)
517 c Given the data in res_..., construct a table of
518 c min/max allowed angles
523 include 'COMMON.LOCMOVE'
527 double precision phi_start(0:11),phi_end(0:11)
534 if (res_n .eq. 0) then
535 c Any move is allowed
544 c Find start of range (01x)
547 if (res_tab(2,0,index).or.(.not.res_tab(2,1,index))) then
551 phi_start(phi_n) = res_ang(index)
553 if (index .eq. res_n) done = .true.
555 c If a start was found (index < res_n), find the end of range (x10)
556 c It may not be found without wrapping around
557 if (index .lt. res_n) then
560 if ((.not.res_tab(2,1,index)).or.res_tab(2,2,index)) then
565 if (index .eq. res_n) done = .true.
567 if (index .lt. res_n) then
568 c Found the end of the range
569 phi_end(phi_n) = res_ang(index)
572 if (index .eq. res_n) then
578 c Need to wrap around
580 phi_end(phi_n) = flag
584 c Take care of the last one if need to wrap around
585 if (phi_end(phi_n) .eq. flag) then
587 do while ((.not.res_tab(2,1,index)).or.res_tab(2,2,index))
590 phi_end(phi_n) = res_ang(index) + 2.*PI
598 c-------------------------------------------------------------
600 subroutine fix_no_moves(phi)
605 include 'COMMON.LOCMOVE'
612 double precision diff,temp
615 c Look for first 01x in gammas (there MUST be at least one)
618 do while (res_tab(1,0,index) .or. (.not.res_tab(1,1,index)))
621 if (res_ang(index) .le. 0.D0) then ! Make sure it's from PHImax
622 c Try to increase PHImax
623 if (index .gt. 0) then
624 phi = res_ang(index-1)
625 diff = abs(res_ang(index) - res_ang(index-1))
627 c Look for last (corresponding) x10
629 do while ((.not.res_tab(1,1,index)) .or. res_tab(1,2,index))
632 if (index .lt. res_n-1) then
633 temp = abs(res_ang(index) - res_ang(index+1))
634 if (temp .lt. diff) then
635 phi = res_ang(index+1)
641 c If increasing PHImax didn't work, decreasing PHImin
642 c will (with one exception)
643 c Look for first x10 (there MUST be at least one)
645 do while ((.not.res_tab(1,1,index)) .or. res_tab(1,2,index))
648 if (res_ang(index) .lt. 0.D0) then ! Make sure it's from PHImin
649 c Try to decrease PHImin
650 if (index .lt. res_n-1) then
651 temp = abs(res_ang(index) - res_ang(index+1))
652 if (res_ang(index+1) .le. 0.D0 .and. temp .lt. diff) then
653 phi = res_ang(index+1)
657 c Look for last (corresponding) 01x
659 do while (res_tab(1,0,index) .or. (.not.res_tab(1,1,index)))
662 if (index .gt. 0) then
663 temp = abs(res_ang(index) - res_ang(index-1))
664 if (res_ang(index-1) .ge. 0.D0 .and. temp .lt. diff) then
665 phi = res_ang(index-1)
671 c If it still didn't work, it must be PHImax == 0. or PHImin == PI
672 if (diff .eq. flag) then
674 if (res_tab(index,1,0) .or. (.not.res_tab(index,1,1)) .or.
675 + res_tab(index,1,2)) index = res_n - 1
676 c This MUST work at this point
677 if (index .eq. 0) then
680 phi = res_ang(index - 1)
687 c-------------------------------------------------------------
689 integer function move_res(PHImin,PHImax,i_move)
690 c Moves residue i_move (in array c), leaving everything else fixed
691 c Starting geometry is not checked, it should be correct!
692 c R(,i_move) is the only residue that will move, but must have
693 c 1 < i_move < nres (i.e., cannot move ends)
694 c Whether any output is done is controlled by locmove_output
698 implicit real*8 (a-h,o-z)
700 include 'COMMON.CHAIN'
702 include 'COMMON.LOCMOVE'
705 double precision ran_number
709 double precision PHImin,PHImax
713 c 0: move successfull
714 c 1: Dmin or Dmax had to be modified
715 c 2: move failed - check your input geometry
719 double precision X(0:2),Y(0:2),Z(0:2),Orig(0:2)
720 double precision P(0:2)
721 logical no_moves,done
723 double precision phi,temp,radius
724 double precision phi_start(0:11), phi_end(0:11)
727 c Set up the coordinate system
729 Orig(i)=0.5*(c(i+1,i_move-1)+c(i+1,i_move+1)) ! Position of origin
733 Z(i)=c(i+1,i_move+1)-c(i+1,i_move-1)
735 temp=sqrt(Z(0)*Z(0)+Z(1)*Z(1)+Z(2)*Z(2))
741 X(i)=c(i+1,i_move)-Orig(i)
743 c radius is the radius of the circle on which c(,i_move) can move
744 radius=sqrt(X(0)*X(0)+X(1)*X(1)+X(2)*X(2))
749 Y(0)=Z(1)*X(2)-X(1)*Z(2)
750 Y(1)=X(0)*Z(2)-Z(0)*X(2)
751 Y(2)=Z(0)*X(1)-X(0)*Z(1)
753 c Calculate min, max angles coming from dmin, dmax to c(,i_move-2)
754 if (i_move.gt.2) then
756 P(i)=c(i+1,i_move-2)-Orig(i)
758 call minmax_angles(P(0)*X(0)+P(1)*X(1)+P(2)*X(2),
759 + P(0)*Y(0)+P(1)*Y(1)+P(2)*Y(2),
760 + P(0)*Z(0)+P(1)*Z(1)+P(2)*Z(2),
761 + radius,a_n,a_ang,a_tab)
766 c Calculate min, max angles coming from dmin, dmax to c(,i_move+2)
767 if (i_move.lt.nres-2) then
769 P(i)=c(i+1,i_move+2)-Orig(i)
771 call minmax_angles(P(0)*X(0)+P(1)*X(1)+P(2)*X(2),
772 + P(0)*Y(0)+P(1)*Y(1)+P(2)*Y(2),
773 + P(0)*Z(0)+P(1)*Z(1)+P(2)*Z(2),
774 + radius,b_n,b_ang,b_tab)
779 c Construct the resulting table for alpha and beta
782 if (locmove_output) then
783 print *,'ALPHAS & BETAS TABLE'
787 c Check that there is at least one possible move
789 if (res_n .eq. 0) then
793 do while ((index .lt. res_n) .and. no_moves)
794 if (res_tab(2,1,index)) no_moves = .false.
799 if (locmove_output) print *,' *** Cannot move anywhere'
804 c Transfer res_... into a_...
807 if ( (res_tab(2,0,i).neqv.res_tab(2,1,i)) .or.
808 + (res_tab(2,0,i).neqv.res_tab(2,2,i)) ) then
809 a_ang(a_n) = res_ang(i)
811 a_tab(j,a_n) = res_tab(2,j,i)
817 c Check that the PHI's are within [0,PI]
818 if (PHImin .lt. 0. .or. abs(PHImin) .lt. small) PHImin = -flag
819 if (PHImin .gt. PI .or. abs(PHImin-PI) .lt. small) PHImin = PI
820 if (PHImax .gt. PI .or. abs(PHImax-PI) .lt. small) PHImax = flag
821 if (PHImax .lt. 0. .or. abs(PHImax) .lt. small) PHImax = 0.
822 if (PHImax .lt. PHImin) PHImax = PHImin
823 c Calculate min and max angles coming from PHImin and PHImax,
824 c and put them in b_...
825 call angles2tab(PHImin, PHImax, b_n, b_ang, b_tab)
826 c Construct the final table
829 if (locmove_output) then
830 print *,'FINAL TABLE'
834 c Check that there is at least one possible move
836 if (res_n .eq. 0) then
840 do while ((index .lt. res_n) .and. no_moves)
841 if (res_tab(2,1,index)) no_moves = .false.
847 c Take care of the case where no solution exists...
848 call fix_no_moves(phi)
849 if (locmove_output) then
850 print *,' *** Had to modify PHImin or PHImax'
851 print *,'phi: ',phi*rad2deg
855 c ...or calculate the solution
856 c Construct phi_start/phi_end arrays
857 call construct_ranges(phi_n, phi_start, phi_end)
858 c Choose random angle phi in allowed range(s)
861 temp = temp + phi_end(i) - phi_start(i)
863 phi = ran_number(phi_start(0),phi_start(0)+temp)
867 if (phi .lt. phi_end(index)) then
872 if (index .eq. phi_n) then
874 else if (.not.done) then
875 phi = phi + phi_start(index) - phi_end(index-1)
878 if (index.eq.phi_n) phi=phi_end(phi_n-1) ! Fix numerical errors
879 if (phi .gt. PI) phi = phi-2.*PI
881 if (locmove_output) then
882 print *,'ALLOWED RANGE(S)'
884 print *,phi_start(i)*rad2deg,phi_end(i)*rad2deg
886 print *,'phi: ',phi*rad2deg
891 c Re-use radius as temp variable
893 radius=radius*sin(phi)
895 c(i+1,i_move)=Orig(i)+temp*X(i)+radius*Y(i)
901 c-------------------------------------------------------------
907 implicit real*8 (a-h,o-z)
910 include 'COMMON.LOCAL'
911 include 'COMMON.LOCMOVE'
920 double precision phi_start(0:11),phi_end(0:11)
922 double precision R(0:2,0:5)
924 locmove_output=.true.
926 c call angles2tab(30.*deg2rad,70.*deg2rad,a_n,a_ang,a_tab)
927 c call angles2tab(80.*deg2rad,130.*deg2rad,b_n,b_ang,b_tab)
928 c call minmax_angles(0.D0,3.8D0,0.D0,3.8D0,b_n,b_ang,b_tab)
932 c call construct_ranges(phi_n,phi_start,phi_end)
934 c print *,phi_start(i)*rad2deg,phi_end(i)*rad2deg
937 c call fix_no_moves(phi)
938 c print *,'NO MOVES FOUND, BEST PHI IS',phi*rad2deg
944 R(1,1)=-cos(28.D0*deg2rad)
945 R(2,1)=-0.5D0-sin(28.D0*deg2rad)
949 R(0,3)=cos(30.D0*deg2rad)
956 R(1,5)=cos(26.D0*deg2rad)
957 R(2,5)=0.5D0+sin(26.D0*deg2rad)
963 c i=move_res(R(0,1),0.D0*deg2rad,180.D0*deg2rad)
965 i=move_res(0.D0*deg2rad,180.D0*deg2rad,imov)
966 print *,'RETURNED ',i
967 print *,(R(i,3)/vbl,i=0,2)
972 c-------------------------------------------------------------