correcation in ion param and dyn_ss
[unres4.git] / source / unres / io_config.F90
index 626d03f..052bde4 100644 (file)
           enddo
         enddo
       endif
+
+
+
+      if (.not.allocated(ichargecat)) allocate (ichargecat(ntyp_molec(5)))
        if (oldion.eq.1) then
             do i=1,ntyp_molec(5)
-             read(iion,*) msc(i,5),restok(i,5)
+             read(iion,*) msc(i,5),restok(i,5),ichargecat(i)
              print *,msc(i,5),restok(i,5)
             enddo
             ip(5)=0.2
             enddo
             print *, catprm
          endif
+      allocate(catnuclprm(14,ntyp_molec(2),ntyp_molec(5)))
+      do i=1,ntyp_molec(5)
+         do j=1,ntyp_molec(2)
+         write(iout,*) i,j
+            read(iionnucl,*) (catnuclprm(k,j,i),k=1,14)
+         enddo
+      enddo
+      write(*,'(3(5x,a6)11(7x,a6))') "w1    ","w2    ","epslj ","pis1  ", &
+      "sigma0","epsi0 ","chi1   ","chip1 ","sig   ","b1    ","b2    ", &
+      "b3    ","b4    ","chis1  "
+      do i=1,ntyp_molec(5)
+         do j=1,ntyp_molec(2)
+            write(*,'(3(f10.3,x),11(f12.6,x),a3,2a)') (catnuclprm(k,j,i),k=1,14), &
+                                      restyp(i,5),"-",restyp(j,2)
+         enddo
+      enddo
 !            read (iion,*) (vcatprm(k),k=1,ncatprotpram)
 !----------------------------------------------------
       allocate(a0thet(-ntyp:ntyp),theta0(-ntyp:ntyp))
        (alphasur(k,i,j),k=1,4),sigmap1(i,j),sigmap2(i,j), &           !6 w tej linii
        chis(i,j),chis(j,i)                                            !2 w tej linii
         endif
-!       print *,eps(i,j),sigma(i,j),"SIGMAP",i,j,sigmap1(i,j),sigmap2(j,i) 
+       print *,eps(i,j),sigma(i,j),"SIGMAP",i,j,sigmap1(i,j),sigmap2(j,i), wqdip(1,i,j)
        END DO
       END DO
       do i=1,ntyp
       if (.not.allocated(chi2cat)) allocate(chi2cat(ntyp1,ntyp1)) !(ntyp,ntyp)
 
 
-      allocate (ichargecat(ntyp_molec(5)))
+            if (.not.allocated(ichargecat)) allocate (ichargecat(ntyp_molec(5)))
 ! i to SC, j to jon, isideocat - nazwa pliku z ktorego czytam parametry
        if (oldion.eq.0) then
             if (.not.allocated(icharge)) then ! this mean you are oprating in old sc-sc mode
              print *,msc(i,5),restok(i,5)
             enddo
             ip(5)=0.2
-
-      do i=1,ntyp
-       do j=1,ntyp_molec(5)
+!DIR$ NOUNROLL 
+      do j=1,ntyp_molec(5)
+       do i=1,ntyp
+!       do j=1,ntyp_molec(5)
 !        write (*,*) "Im in ALAB", i, " ", j
         read(iion,*) &
        epscat(i,j),sigmacat(i,j), &
        (wqdipcat(k,i,j),k=1,2), &
        alphapolcat(i,j),alphapolcat(j,i), &
        (alphisocat(k,i,j),k=1,4),sigiso1cat(i,j),sigiso2cat(i,j),epsintabcat(i,j),debaykapcat(i,j)
+
+       if (chi1cat(i,j).gt.0.9) write (*,*) "WTF ANISO", i,j, chi1cat(i,j)
 !       print *,eps(i,j),sigma(i,j),"SIGMAP",i,j,sigmap1(i,j),sigmap2(j,i) 
 !     if (i.eq.1) then
 !     write (iout,*) 'i= ', i, ' j= ', j
         do j=1,ntyp_molec(5)
           epsij=epscat(i,j)
           rrij=sigmacat(i,j)
+          rrij=rrij**expon
           sigeps=dsign(1.0D0,epsij)
           epsij=dabs(epsij)
           aa_aq_cat(i,j)=epsij*rrij*rrij
 
        do i=1,ntyp
        do j=1,ntyp_molec(5)
-      if (i.eq.1) then
+      if (i.eq.10) then
       write (iout,*) 'i= ', i, ' j= ', j
       write (iout,*) 'epsi0= ', epscat(i,j)
       write (iout,*) 'sigma0= ', sigmacat(i,j)
       write (iout,*) 'epsin= ', epsintabcat(1,j), epsintabcat(j,1)
       write (iout,*) 'alphapol1= ',  alphapolcat(1,j)
       write (iout,*) 'alphapol2= ',  alphapolcat(j,1)
-      write (iout,*) 'w1= ', wqdipcat(1,1,j)
-      write (iout,*) 'w2= ', wqdipcat(2,1,j)
+      write (iout,*) 'w1= ', wqdipcat(1,i,j)
+      write (iout,*) 'w2= ', wqdipcat(2,i,j)
       write (iout,*) 'debaykapcat(i,j)= ',  debaykapcat(1,j)
       endif
 
          istype(i)=istype_temp(i)
         enddo
        enddo
+       if ((itype(1,1).eq.ntyp1).and.itype(2,5).ne.0) then
+! I have only ions now dummy atoms in the system        
+       molnum(1)=5
+       itype(1,5)=itype(2,5)
+       itype(1,1)=0
+       do i=2,nres
+         itype(i,5)=itype(i+1,5)
+       enddo
+       itype(nres,5)=0
+       nres=nres-1
+       nres_molec(1)=nres_molec(1)-1
+      endif
 !      if (itype(1,1).eq.ntyp1) then
 !        nsup=nsup-1
 !        nstart_sup=2
       endif
 
 ! CUTOFFF ON ELECTROSTATICS
-      call reada(controlcard,"R_CUT_ELE",r_cut_ele,15.0d0)
+      call reada(controlcard,"R_CUT_ELE",r_cut_ele,25.0d0)
       call reada(controlcard,"LAMBDA_ELE",rlamb_ele,0.3d0)
       write(iout,*) "R_CUT_ELE=",r_cut_ele
 ! Lipidic parameters
 !      enddo
       buff_shield=1.0d0
       endif
+      itime_mat=0
       return
       end subroutine read_control
 !-----------------------------------------------------------------------------
       print_compon = index(controlcard,"PRINT_COMPON").gt.0
       rattle = index(controlcard,"RATTLE").gt.0
       preminim=(index(controlcard,'PREMINIM').gt.0)
+      forceminim=(index(controlcard,'FORCEMINIM').gt.0)
       write (iout,*) "PREMINIM ",preminim
       dccart=(index(controlcard,'CART').gt.0)
       if (preminim) call read_minim
       open (itube,file=tubename,status='old')
       call getenv_loc('IONPAR',ionname)
       open (iion,file=ionname,status='old')
+      call getenv_loc('IONPAR_NUCL',ionnuclname)
+      open (iionnucl,file=ionnuclname,status='old')
 #else
       open(1,file=pref_orig(:ilen(pref_orig))//'.inp',status='old',&
         readonly)
       open (itube,file=tubename,status='old',action='read')
       call getenv_loc('IONPAR',ionname)
       open (iion,file=ionname,status='old',action='read')
+      call getenv_loc('IONPAR_NUCL',ionnuclname)
+      open (iionnucl,file=ionnuclname,status='old',action='read')
 
 #ifndef CRYST_SC
       call getenv_loc('ROTPARPDB',rotname_pdb)