PBC working for EGB (only)
[unres4.git] / source / unres / io_config.f90
index 018dbee..da0414d 100644 (file)
         endif
       enddo
 #else
-      read (ibond,*) junk,vbldp0,akp,rjunk,mp,ip,pstok
+      read (ibond,*) junk,vbldpDUM,vbldp0,akp,rjunk,mp,ip,pstok
       do i=1,ntyp
         read (ibond,*) nbondterm(i),(vbldsc0(j,i),aksc(j,i),abond0(j,i),&
          j=1,nbondterm(i)),msc(i),isc(i),restok(i)
           goto 10
         else if (card(:3).eq.'TER') then
 ! End current chain
-          ires_old=ires+1
+          ires_old=ires+2
           ishift1=ishift1+1
           itype(ires_old)=ntyp1
+          itype(ires_old-1)=ntyp1
           ibeg=2
 !          write (iout,*) "Chain ended",ires,ishift,ires_old
           if (unres_pdb) then
       nres=ires
       do i=2,nres-1
 !        write (iout,*) i,itype(i)
-        if (itype(i).eq.ntyp1) then
+!        if (itype(i).eq.ntyp1) then
 !          write (iout,*) "dummy",i,itype(i)
-          do j=1,3
-            c(j,i)=((c(j,i-1)+c(j,i+1))/2+2*c(j,i-1)-c(j,i-2))/2
+!          do j=1,3
+!            c(j,i)=((c(j,i-1)+c(j,i+1))/2+2*c(j,i-1)-c(j,i-2))/2
 !            c(j,i)=(c(j,i-1)+c(j,i+1))/2
-            dc(j,i)=c(j,i)
-          enddo
-        endif
+!            dc(j,i)=c(j,i)
+!          enddo
+!        endif
+        if (itype(i).eq.ntyp1) then
+         if (itype(i+1).eq.ntyp1) then
+! 16/01/2014 by Adasko: Adding to dummy atoms in the chain
+! first is connected prevous chain (itype(i+1).eq.ntyp1)=true
+! second dummy atom is conected to next chain itype(i+1).eq.ntyp1=false
+           if (unres_pdb) then
+! 2/15/2013 by Adam: corrected insertion of the last dummy residue
+!            print *,i,'tu dochodze'
+            call refsys(i-3,i-2,i-1,e1,e2,e3,fail)
+            if (fail) then
+              e2(1)=0.0d0
+              e2(2)=1.0d0
+              e2(3)=0.0d0
+            endif !fail
+            print *,i,'a tu?'
+            do j=1,3
+             c(j,i)=c(j,i-1)-1.9d0*e2(j)
+            enddo
+           else   !unres_pdb
+           do j=1,3
+             dcj=(c(j,i-2)-c(j,i-3))/2.0
+            if (dcj.eq.0) dcj=1.23591524223
+             c(j,i)=c(j,i-1)+dcj
+             c(j,nres+i)=c(j,i)
+           enddo
+          endif   !unres_pdb
+         else     !itype(i+1).eq.ntyp1
+          if (unres_pdb) then
+! 2/15/2013 by Adam: corrected insertion of the first dummy residue
+            call refsys(i+1,i+2,i+3,e1,e2,e3,fail)
+            if (fail) then
+              e2(1)=0.0d0
+              e2(2)=1.0d0
+              e2(3)=0.0d0
+            endif
+            do j=1,3
+              c(j,i)=c(j,i+1)-1.9d0*e2(j)
+            enddo
+          else !unres_pdb
+           do j=1,3
+            dcj=(c(j,i+3)-c(j,i+2))/2.0
+            if (dcj.eq.0) dcj=1.23591524223
+            c(j,i)=c(j,i+1)-dcj
+            c(j,nres+i)=c(j,i)
+           enddo
+          endif !unres_pdb
+         endif !itype(i+1).eq.ntyp1
+        endif  !itype.eq.ntyp1
+
       enddo
 ! Calculate the CM of the last side chain.
       if (iii.gt.0)  then
       timem=timlim
       modecalc=0
       call reada(controlcard,"T_BATH",t_bath,300.0d0)
+!C  Varibles set size of box
+      call reada(controlcard,'BOXX',boxxsize,100.0d0)
+      call reada(controlcard,'BOXY',boxysize,100.0d0)
+      call reada(controlcard,'BOXZ',boxzsize,100.0d0)
+! CUTOFFF ON ELECTROSTATICS
+      call reada(controlcard,"R_CUT_ELE",r_cut_ele,15.0d0)
+      call reada(controlcard,"LAMBDA_ELE",rlamb_ele,0.3d0)
+
+!C-------------------------
       minim=(index(controlcard,'MINIMIZE').gt.0)
       dccart=(index(controlcard,'CART').gt.0)
       overlapsc=(index(controlcard,'OVERLAP').gt.0)