working martini
[unres4.git] / source / unres / io_config.F90
index 48d2105..cdd6231 100644 (file)
              read(iion,*) msc(i,5),restok(i,5),ichargecat(i)
              print *,msc(i,5),restok(i,5)
             enddo
-            ip(5)=0.2
+!            ip(5)=0.2
 !            isc(5)=0.2
             read (iion,*) ncatprotparm
             allocate(catprm(ncatprotparm,4))
       !HERE THE MASS of MARTINI
       write(*,*) "before MARTINI PARAM"
       do i=1,ntyp_molec(4)
-       msc(i,4)=0.0d0
-       mp(4)=72.0d0
+       msc(i,4)=72.0d0
+       mp(4)=0.0d0
        isc(i,4)=0.d0
       enddo
       ip(4)=0.0
+      msc(ntyp_molec(4)+1,4)=0.1d0
       !relative dielectric constant = 15 for implicit screening
       k_coulomb_lip=332.0d0/15.0d0
       !kbond = 1250 kJ/(mol*nm*2)
 
 ! Ions by Aga
 
-       allocate(alphapolcat(ntyp,ntyp),epsheadcat(ntyp,ntyp),sig0headcat(ntyp,ntyp))
-       allocate(alphapolcat2(ntyp,ntyp))
-       allocate(sigiso1cat(ntyp,ntyp),rborn1cat(ntyp,ntyp),rborn2cat(ntyp,ntyp),sigmap1cat(ntyp,ntyp))
-       allocate(sigmap2cat(ntyp,ntyp),sigiso2cat(ntyp,ntyp))
-       allocate(chis1cat(ntyp,ntyp),chis2cat(ntyp,ntyp),wquadcat(ntyp,ntyp),chipp1cat(ntyp,ntyp),chipp2cat(ntyp,ntyp))
-       allocate(epsintabcat(ntyp,ntyp))
-       allocate(dtailcat(2,ntyp,ntyp))
-       allocate(alphasurcat(4,ntyp,ntyp),alphisocat(4,ntyp,ntyp))
-       allocate(wqdipcat(2,ntyp,ntyp))
-       allocate(wstatecat(4,ntyp,ntyp))
-       allocate(dheadcat(2,2,ntyp,ntyp))
-       allocate(nstatecat(ntyp,ntyp))
-       allocate(debaykapcat(ntyp,ntyp))
-
-      if (.not.allocated(epscat)) allocate (epscat(0:ntyp1,0:ntyp1))
-      if (.not.allocated(sigmacat)) allocate(sigmacat(0:ntyp1,0:ntyp1))
+       allocate(alphapolcat(ntyp,-1:ntyp_molec(5)),epsheadcat(ntyp,-1:ntyp_molec(5)),sig0headcat(ntyp,-1:ntyp_molec(5)))
+       allocate(alphapolcat2(ntyp,-1:ntyp_molec(5)))
+       allocate(sigiso1cat(ntyp,-1:ntyp_molec(5)),rborn1cat(ntyp,-1:ntyp_molec(5)),rborn2cat(ntyp,-1:ntyp_molec(5)),sigmap1cat(ntyp,-1:ntyp_molec(5)))
+       allocate(sigmap2cat(ntyp,-1:ntyp_molec(5)),sigiso2cat(ntyp,-1:ntyp_molec(5)))
+       allocate(chis1cat(ntyp,-1:ntyp_molec(5)),chis2cat(ntyp,-1:ntyp_molec(5)),wquadcat(ntyp,-1:ntyp_molec(5)),chipp1cat(ntyp,-1:ntyp_molec(5)),chipp2cat(ntyp,-1:ntyp_molec(5)))
+       allocate(epsintabcat(ntyp,-1:ntyp_molec(5)))
+       allocate(dtailcat(2,ntyp,-1:ntyp_molec(5)))
+       allocate(alphasurcat(4,ntyp,-1:ntyp_molec(5)),alphisocat(4,ntyp,-1:ntyp_molec(5)))
+       allocate(wqdipcat(2,ntyp,-1:ntyp_molec(5)))
+       allocate(wstatecat(4,ntyp,-1:ntyp_molec(5)))
+       allocate(dheadcat(2,2,ntyp,-1:ntyp_molec(5)))
+       allocate(nstatecat(ntyp,-1:ntyp_molec(5)))
+       allocate(debaykapcat(ntyp,-1:ntyp_molec(5)))
+
+      if (.not.allocated(epscat)) allocate (epscat(0:ntyp1,-1:ntyp1))
+      if (.not.allocated(sigmacat)) allocate(sigmacat(0:ntyp1,-1:ntyp1))
 !      if (.not.allocated(chicat)) allocate(chicat(ntyp1,ntyp1)) !(ntyp,ntyp)
-      if (.not.allocated(chi1cat)) allocate(chi1cat(ntyp1,ntyp1)) !(ntyp,ntyp)
-      if (.not.allocated(chi2cat)) allocate(chi2cat(ntyp1,ntyp1)) !(ntyp,ntyp)
+      if (.not.allocated(chi1cat)) allocate(chi1cat(ntyp1,-1:ntyp1)) !(ntyp,ntyp)
+      if (.not.allocated(chi2cat)) allocate(chi2cat(ntyp1,-1:ntyp1)) !(ntyp,ntyp)
 
 
             if (.not.allocated(ichargecat))&
            ! mp(5)=0.2
              pstok(5)=3.0
 !DIR$ NOUNROLL 
-      do j=1,ntyp_molec(5)-1 ! this is without Zn will be modified for ALL tranistion metals
+      do j=-1,ntyp_molec(5)-1 ! this is without Zn will be modified for ALL tranistion metals
+       if (j.eq.0) cycle
        do i=1,ntyp
 !       do j=1,ntyp_molec(5)
 !        write (*,*) "Im in ALAB", i, " ", j
         read(iion,*) &
        epscat(i,j),sigmacat(i,j), &
 !       chicat(i,j),chicat(j,i),chippcat(i,j),chippcat(j,i), &
-       chi1cat(i,j),chi2cat(i,j),chipp1cat(i,j),chipp2cat(i,j), &
+       chi1cat(i,j),chi2cat(i,j),chipp1cat(i,j),chipp2cat(i,j), & !6
 
-       (alphasurcat(k,i,j),k=1,4),sigmap1cat(i,j),sigmap2cat(i,j),&
+       (alphasurcat(k,i,j),k=1,4),sigmap1cat(i,j),sigmap2cat(i,j),&!12
 !       chiscat(i,j),chiscat(j,i), &
        chis1cat(i,j),chis2cat(i,j), &
 
-       nstatecat(i,j),(wstatecat(k,i,j),k=1,4), &                           !5 w tej lini - 1 integer pierwszy
-       dheadcat(1,1,i,j),dheadcat(1,2,i,j),dheadcat(2,1,i,j),dheadcat(2,2,i,j),&
+       nstatecat(i,j),(wstatecat(k,i,j),k=1,4), & !19                          !5 w tej lini - 1 integer pierwszy
+       dheadcat(1,1,i,j),dheadcat(1,2,i,j),dheadcat(2,1,i,j),dheadcat(2,2,i,j),&!23
        dtailcat(1,i,j),dtailcat(2,i,j), &
-       epsheadcat(i,j),sig0headcat(i,j), &
+       epsheadcat(i,j),sig0headcat(i,j), &!27
 !wdipcat = w1 , w2
 !       rborncat(i,j),rborncat(j,i),&
        rborn1cat(i,j),rborn2cat(i,j),&
-       (wqdipcat(k,i,j),k=1,2), &
-       alphapolcat(i,j),alphapolcat2(j,i), &
+       (wqdipcat(k,i,j),k=1,2), &!31
+       alphapolcat(i,j),alphapolcat2(j,i), &!33
        (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)
 
        END DO
       END DO
-      allocate(aa_aq_cat(-ntyp:ntyp,ntyp),bb_aq_cat(-ntyp:ntyp,ntyp))
+      allocate(aa_aq_cat(-ntyp:ntyp,-1:ntyp_molec(5)),&
+               bb_aq_cat(-ntyp:ntyp,-1:ntyp_molec(5)))
       do i=1,ntyp
-        do j=1,ntyp_molec(5)
+        do j=-1,ntyp_molec(5)
+          if (j.eq.0) cycle
           epsij=epscat(i,j)
           rrij=sigmacat(i,j)
           rrij=rrij**expon
       write (iout,'(3(a,f10.2))') 'v1ss:',v1ss,' v2ss:',v2ss,&
         ' v3ss:',v3ss
       endif
+
+!------------MARTINI-PROTEIN-parameters-------------------------
+       allocate(alphapolmart(ntyp,ntyp),epsheadmart(ntyp,ntyp_molec(4)),sig0headmart(ntyp,ntyp_molec(4)))
+       allocate(alphapolmart2(ntyp,ntyp))
+       allocate(sigiso1mart(ntyp,ntyp_molec(4)),rborn1mart(ntyp,ntyp_molec(4)),rborn2mart(ntyp,ntyp_molec(4)),sigmap1mart(ntyp,ntyp_molec(4)))
+       allocate(sigmap2mart(ntyp,ntyp_molec(4)),sigiso2mart(ntyp,ntyp_molec(4)))
+       allocate(chis1mart(ntyp,ntyp_molec(4)),chis2mart(ntyp,ntyp_molec(4)),wquadmart(ntyp,ntyp_molec(4)),chipp1mart(ntyp,ntyp_molec(4)),chipp2mart(ntyp,ntyp_molec(4)))
+       allocate(epsintabmart(ntyp,ntyp_molec(4)))
+       allocate(dtailmart(2,ntyp,ntyp_molec(4)))
+       allocate(alphasurmart(4,ntyp,ntyp_molec(4)),alphisomart(4,ntyp,ntyp_molec(4)))
+       allocate(wqdipmart(2,ntyp,ntyp_molec(4)))
+       allocate(wstatemart(4,ntyp,ntyp_molec(4)))
+       allocate(dheadmart(2,2,ntyp,ntyp_molec(4))) 
+       allocate(nstatemart(ntyp,ntyp_molec(4)))
+       allocate(debaykapmart(ntyp,ntyp_molec(4)))
+
+      if (.not.allocated(epsmart)) allocate (epsmart(0:ntyp1,ntyp1))
+      if (.not.allocated(sigmamart)) allocate(sigmamart(0:ntyp1,ntyp1))
+!      if (.not.allocated(chimart)) allomarte(chimart(ntyp1,ntyp1)) !(ntyp,ntyp)
+      if (.not.allocated(chi1mart)) allocate(chi1mart(ntyp1,ntyp1)) !(ntyp,ntyp)
+      if (.not.allocated(chi2mart)) allocate(chi2mart(ntyp1,ntyp1)) !(ntyp,ntyp)
+
+!DIR$ NOUNROLL 
+      do i=1,ntyp-3 ! there are phosporylated missing
+      do j=1,ntyp_molec(4) ! this is without Zn will be modified for ALL tranistion metals
+!       do j=1,ntyp_molec(5) 
+        print *,"lipmart",i,j
+!        write (*,*) "Im in ALAB", i, " ", j
+        read(imartprot,*) &
+       epsmart(i,j),sigmamart(i,j), &
+!       chimart(i,j),chimart(j,i),chippmart(i,j),chippmart(j,i), &
+       chi1mart(i,j),chi2mart(i,j),chipp1mart(i,j),chipp2mart(i,j), & !6
+
+       (alphasurmart(k,i,j),k=1,4),sigmap1mart(i,j),sigmap2mart(i,j),&!12
+!       chismart(i,j),chismart(j,i), &
+       chis1mart(i,j),chis2mart(i,j), &
+
+       nstatemart(i,j),(wstatemart(k,i,j),k=1,4), & !19                          !5 w tej lini - 1 integer pierwszy
+       dheadmart(1,1,i,j),dheadmart(1,2,i,j),dheadmart(2,1,i,j),dheadmart(2,2,i,j),&!23
+       dtailmart(1,i,j),dtailmart(2,i,j), &
+       epsheadmart(i,j),sig0headmart(i,j), &!27 
+!wdipmart = w1 , w2
+!       rbornmart(i,j),rbornmart(j,i),&
+       rborn1mart(i,j),rborn2mart(i,j),&
+       (wqdipmart(k,i,j),k=1,2), &!31
+       alphapolmart(i,j),alphapolmart2(j,i), &!33
+       (alphisomart(k,i,j),k=1,4),sigiso1mart(i,j),sigiso2mart(i,j),epsintabmart(i,j),debaykapmart(i,j) 
+       enddo
+       enddo
+      allocate(aa_aq_mart(-ntyp:ntyp,ntyp_molec(4)),&
+               bb_aq_mart(-ntyp:ntyp,ntyp_molec(4)))
+      do i=1,ntyp-3 ! still no phophorylated residues
+        do j=1,ntyp_molec(4)
+          if (j.eq.0) cycle
+          epsij=epsmart(i,j)
+          rrij=sigmamart(i,j)
+          rrij=rrij**expon
+          sigeps=dsign(1.0D0,epsij)
+          epsij=dabs(epsij)
+          aa_aq_mart(i,j)=epsij*rrij*rrij
+          bb_aq_mart(i,j)=-sigeps*epsij*rrij
+         enddo
+       enddo
+
+
+
+
+
+
+
+
+
+
+
       if (shield_mode.gt.0) then
       pi=4.0D0*datan(1.0D0)
 !C VSolvSphere the volume of solving sphere
 ! CUTOFFF ON ELECTROSTATICS
       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
+      
+      write(iout,*) "R_CUT_ELE=",r_cut_ele,rlamb_ele
       call reada(controlcard,"R_CUT_MART",r_cut_mart,15.0d0)
       call reada(controlcard,"LAMBDA_MART",rlamb_mart,0.3d0)
       call reada(controlcard,"R_CUT_ANG",r_cut_ang,4.2d0)
 
+      call reada(controlcard,"DELTA",graddelta,1.0d-5)
 ! Lipidec parameters
       call reada(controlcard,"LIPTHICK",lipthick,0.0d0)
       call reada(controlcard,"LIPAQBUF",lipbufthick,0.0d0)
       open (ilipbond,file=lipbondname,status='old',action='read')
       call getenv_loc('LIPNONBOND',lipnonbondname)
       open (ilipnonbond,file=lipnonbondname,status='old',action='read')
+      call getenv_loc('LIPPROT',lipprotname)
+      open (imartprot,file=lipprotname,status='old',action='read')
+
       call getenv_loc('TUBEPAR',tubename)
       open (itube,file=tubename,status='old',action='read')
       call getenv_loc('IONPAR',ionname)