added nanostructures energy to wham, no differs
[unres.git] / source / wham / src-M / readrtns.F
index 276e7a6..ff5b18e 100644 (file)
@@ -18,6 +18,8 @@
       include "COMMON.CONTROL"
       include "COMMON.ENERGIES"
       include "COMMON.SPLITELE"
+      include "COMMON.SBRIDGE"
+      include "COMMON.SHIELD"
       character*800 controlcard
       integer i,j,k,ii,n_ene_found
       integer ind,itype1,itype2,itypf,itypsc,itypp
@@ -26,7 +28,7 @@
       character*16 ucase
       character*16 key
       external ucase
-
+      double precision pi
       call card_concat(controlcard,.true.)
       call readi(controlcard,"N_ENE",n_ene,max_ene)
       if (n_ene.gt.max_ene) then
        call reada(controlcard,'BOXX',boxxsize,100.0d0)
        call reada(controlcard,'BOXY',boxysize,100.0d0)
        call reada(controlcard,'BOXZ',boxzsize,100.0d0)
+      call readi(controlcard,'TUBEMOD',tubelog,0)
+      write (iout,*) TUBElog,"TUBEMODE"
+      call readi(controlcard,'GENCONSTR',genconstr,0)
+
 c Cutoff range for interactions
       call reada(controlcard,"R_CUT",r_cut,15.0d0)
       call reada(controlcard,"LAMBDA",rlamb,0.3d0)
@@ -104,6 +110,17 @@ C      endif
       write (iout,*) "einicheck",einicheck
       write (iout,*) "rescale_mode",rescale_mode
       call flush(iout)
+      if (TUBElog.gt.0) then
+       call reada(controlcard,"XTUBE",tubecenter(1),0.0d0)
+       call reada(controlcard,"YTUBE",tubecenter(2),0.0d0)
+       call reada(controlcard,"ZTUBE",tubecenter(3),0.0d0)
+       call reada(controlcard,"RTUBE",tubeR0,0.0d0)
+       call reada(controlcard,"TUBETOP",bordtubetop,boxzsize)
+       call reada(controlcard,"TUBEBOT",bordtubebot,0.0d0)
+       call reada(controlcard,"TUBEBUF",tubebufthick,1.0d0)
+       buftubebot=bordtubebot+tubebufthick
+       buftubetop=bordtubetop-tubebufthick
+      endif
       bxfile=index(controlcard,"BXFILE").gt.0
       cxfile=index(controlcard,"CXFILE").gt.0
       if (nslice .eq. 1 .and. .not.bxfile .and. .not.cxfile)
@@ -114,7 +131,35 @@ C      endif
       zscfile=index(controlcard,"ZSCFILE").gt.0
       with_dihed_constr = index(controlcard,"WITH_DIHED_CONSTR").gt.0
       write (iout,*) "with_dihed_constr ",with_dihed_constr
+      with_theta_constr = index(controlcard,"WITH_THETA_CONSTR").gt.0
+      write (iout,*) "with_theta_constr ",with_theta_constr
+      call readi(controlcard,'SHIELD',shield_mode,0)
+C      if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) then
+        write(iout,*) "shield_mode",shield_mode
+C      endif
+      call readi(controlcard,'TORMODE',tor_mode,0)
+C      if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) then
+        write(iout,*) "torsional and valence angle mode",tor_mode
+      if (shield_mode.gt.0) then
+      pi=3.141592d0
+C VSolvSphere the volume of solving sphere
+C      print *,pi,"pi"
+C rpp(1,1) is the energy r0 for peptide group contact and will be used for it 
+C there will be no distinction between proline peptide group and normal peptide
+C group in case of shielding parameters
+      VSolvSphere=4.0/3.0*pi*rpp(1,1)**3
+      VSolvSphere_div=VSolvSphere-4.0/3.0*pi*(rpp(1,1)/2.0)**3
+      write (iout,*) VSolvSphere,VSolvSphere_div
+C long axis of side chain 
+C      do i=1,ntyp
+C      long_r_sidechain(i)=vbldsc0(1,i)
+C      short_r_sidechain(i)=sigma0(i)
+C      enddo
+      buff_shield=1.0d0
+      endif
+
       call readi(controlcard,'CONSTR_DIST',constr_dist,0)
+      dyn_ss=index(controlcard,"DYN_SS").gt.0
       return
       end
 c------------------------------------------------------------------------------
@@ -424,7 +469,7 @@ c-------------------------------------------------------------------------------
       external ilen,iroof
       double precision rmsdev,energia(0:max_ene),efree,eini,temp
       double precision prop(maxQ)
-      integer ntot_all(maxslice,0:maxprocs-1)
+      integer ntot_all(maxslice,0:maxprocs-1), maxslice_buff
       integer iparm,ib,iib,ir,nprop,nthr,npars
       double precision etot,time
       integer ixdrf,iret 
@@ -555,7 +600,13 @@ c DA scratchfile.
 
 #ifdef MPI
 c Check if everyone has the same number of conformations
-      call MPI_Allgather(stot(1),maxslice,MPI_INTEGER,
+
+c      call MPI_ALLgather(MPI_IN_PLACE,stot(1),MPI_DATATYPE_NULL,
+c     &  ntot_all(1,0),maxslice,MPI_INTEGER,MPI_Comm_World,IERROR)
+
+      maxslice_buff=maxslice
+
+      call MPI_Allgather(stot(1),maxslice_buff,MPI_INTEGER,
      &  ntot_all(1,0),maxslice,MPI_INTEGER,MPI_Comm_World,IERROR)
       lerr=.false.
       do i=0,nprocs-1