triss; AFM; Lorentz restrains included -debug might be on
[unres4.git] / source / unres / io_base.f90
index 0a9dc14..0e1a986 100644 (file)
@@ -68,6 +68,7 @@
         write(iout,*) ' iss:',(iss(i),i=1,ns)
 ! Check whether the specified bridging residues are cystines.
       do i=1,ns
+         write(iout,*) i,iss(i)
        if (itype(iss(i)).ne.1) then
          if (me.eq.king.or..not.out1file) write (iout,'(2a,i3,a)') &
          'Do you REALLY think that the residue ',&
 #endif
         endif
       enddo
+      if (dyn_ss) then 
+        if(.not.allocated(ihpb)) allocate(ihpb(ns))
+        if(.not.allocated(jhpb)) allocate(jhpb(ns))
+      endif
 ! Read preformed bridges.
       if (ns.gt.0) then
         read (inp,*) nss
       card=card(:ilen(card)+1)//karta
       return
       end subroutine card_concat
+!----------------------------------------------------------------------------
+      subroutine read_afminp
+      use geometry_data
+      use energy_data
+      use control_data, only:out1file
+      use MPI_data
+      character*320 afmcard
+      integer i
+      print *, "wchodze"
+      call card_concat(afmcard,.true.)
+      call readi(afmcard,"BEG",afmbeg,0)
+      call readi(afmcard,"END",afmend,0)
+      call reada(afmcard,"FORCE",forceAFMconst,0.0d0)
+      call reada(afmcard,"VEL",velAFMconst,0.0d0)
+      print *,'FORCE=' ,forceAFMconst
+!------ NOW PROPERTIES FOR AFM
+       distafminit=0.0d0
+       do i=1,3
+        distafminit=(c(i,afmend)-c(i,afmbeg))**2+distafminit
+       enddo
+        distafminit=dsqrt(distafminit)
+        print *,'initdist',distafminit
+      return
+      end subroutine read_afminp
 !-----------------------------------------------------------------------------
       subroutine read_dist_constr
       use MPI_data
 !      write (iout,*) "Calling read_dist_constr"
 !      write (iout,*) "nres",nres," nstart_sup",nstart_sup," nsup",nsup
 !      call flush(iout)
+      if(.not.allocated(ihpb)) allocate(ihpb(maxdim))
+      if(.not.allocated(jhpb)) allocate(jhpb(maxdim))
+      if(.not.allocated(dhpb)) allocate(dhpb(maxdim))
+      if(.not.allocated(dhpb1)) allocate(dhpb1(maxdim))
+      if(.not.allocated(forcon)) allocate(forcon(maxdim))
+      if(.not.allocated(fordepth)) allocate(fordepth(maxdim))
+      if ((genconstr.gt.0).and.(constr_dist.eq.11)) then
+      call gen_dist_constr2
+      go to 1712
+      endif
       call card_concat(controlcard,.true.)
       call readi(controlcard,"NFRAG",nfrag_,0)
       call readi(controlcard,"NPAIR",npair_,0)
 !      do i=1,npair_
 !        write (iout,*) i,ipair_(1,i),ipair_(2,i),wpair_(i)
 !      enddo
-      if(.not.allocated(ihpb)) allocate(ihpb(maxdim))
-      if(.not.allocated(jhpb)) allocate(jhpb(maxdim))
-      if(.not.allocated(dhpb)) allocate(dhpb(maxdim))
-      if(.not.allocated(forcon)) allocate(forcon(maxdim))
-
+!      if(.not.allocated(ihpb)) allocate(ihpb(maxdim))
+!      if(.not.allocated(jhpb)) allocate(jhpb(maxdim))
+!      if(.not.allocated(dhpb)) allocate(dhpb(maxdim))
+!      if(.not.allocated(forcon)) allocate(forcon(maxdim))
+      
       call flush(iout)
       do i=1,nfrag_
         if (ifrag_(1,i).lt.nstart_sup) ifrag_(1,i)=nstart_sup
         endif
       enddo 
       do i=1,ndist_
-        read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),forcon(nhpb+1)
+!        read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),forcon(nhpb+1)
+!        if (forcon(nhpb+1).gt.0.0d0) then
+!          nhpb=nhpb+1
+!          dhpb(nhpb)=dist(ihpb(nhpb),jhpb(nhpb))
+        if (constr_dist.eq.11) then
+        read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),dhpb(i),dhpb1(i), &
+          ibecarb(i),forcon(nhpb+1),fordepth(nhpb+1)
+        fordepth(nhpb+1)=fordepth(nhpb+1)/forcon(nhpb+1)
+        else
+!C        print *,"in else"
+        read (inp,*) ihpb(nhpb+1),jhpb(nhpb+1),dhpb(i),dhpb1(i), &
+          ibecarb(i),forcon(nhpb+1)
+        endif
         if (forcon(nhpb+1).gt.0.0d0) then
           nhpb=nhpb+1
-          dhpb(nhpb)=dist(ihpb(nhpb),jhpb(nhpb))
+          if (ibecarb(i).gt.0) then
+            ihpb(i)=ihpb(i)+nres
+            jhpb(i)=jhpb(i)+nres
+          endif
+          if (dhpb(nhpb).eq.0.0d0) &
+            dhpb(nhpb)=dist(ihpb(nhpb),jhpb(nhpb))
+        endif
+
 #ifdef MPI
           if (.not.out1file .or. me.eq.king) &
           write (iout,'(a,3i5,f8.2,f10.1)') "+dist.constr ",&
           write (iout,'(a,3i5,f8.2,f10.1)') "+dist.constr ",&
            nhpb,ihpb(nhpb),jhpb(nhpb),dhpb(nhpb),forcon(nhpb)
 #endif
-        endif
       enddo
+ 1712 continue
       call flush(iout)
       return
       end subroutine read_dist_constr
 !-----------------------------------------------------------------------------
+      subroutine gen_dist_constr2
+      use MPI_data
+   !  use control
+      use geometry, only: dist
+      use geometry_data
+      use control_data
+      use energy_data
+      integer :: i,j
+      real(kind=8) :: distance
+      if (constr_dist.eq.11) then
+             do i=nstart_sup,nstart_sup+nsup-1
+              do j=i+2,nstart_sup+nsup-1
+                 distance=dist(i,j)
+                 if (distance.le.15.0) then
+                 nhpb=nhpb+1
+                 ihpb(nhpb)=i+nstart_seq-nstart_sup
+                 jhpb(nhpb)=j+nstart_seq-nstart_sup
+                 forcon(nhpb)=sqrt(0.04*distance)
+                 fordepth(nhpb)=sqrt(40.0/distance)
+                 dhpb(nhpb)=distance-0.1d0
+                 dhpb1(nhpb)=distance+0.1d0
+
+#ifdef MPI
+          if (.not.out1file .or. me.eq.king) &
+          write (iout,'(a,3i5,f8.2,f10.2)') "+dist.constr ", &
+          nhpb,ihpb(nhpb),jhpb(nhpb),dhpb(nhpb),forcon(nhpb)
+#else
+          write (iout,'(a,3i5,f8.2,f10.2)') "+dist.constr ", &
+          nhpb,ihpb(nhpb),jhpb(nhpb),dhpb(nhpb),forcon(nhpb)
+#endif
+            endif
+             enddo
+           enddo
+      else
+      do i=nstart_sup,nstart_sup+nsup-1
+        do j=i+2,nstart_sup+nsup-1
+          nhpb=nhpb+1
+          ihpb(nhpb)=i+nstart_seq-nstart_sup
+          jhpb(nhpb)=j+nstart_seq-nstart_sup
+          forcon(nhpb)=weidis
+          dhpb(nhpb)=dist(i,j)
+        enddo
+      enddo
+      endif
+      return
+      end subroutine gen_dist_constr2
+
+!-----------------------------------------------------------------------------
 #ifdef WINIFL
       subroutine flush(iu)
       return
 !      iii=igeom
       igeom=iout
 #endif
+      print *,nss
       IF (NSS.LE.9) THEN
 #ifdef CLUSTER
         WRITE (igeom,180) IT,ENER,free,NSS,(IHPB(I),JHPB(I),I=1,NSS)