Merge branch 'UCGM' of mmka.chem.univ.gda.pl:unres4 into UCGM
[unres4.git] / source / unres / control.F90
index 7ecc757..a1e49d3 100644 (file)
 !      ielep_nucl= 131
       isidep_nucl=132
       iscpp_nucl=133
-
-
+      isidep_scbase=141
+      isidep_pepbase=142
+      isidep_scpho=143
+      isidep_peppho=144
 
       iliptranpar=60
       itube=61
+!     IONS
+      iion=401
 #if defined(WHAM_RUN) || defined(CLUSTER)
 !
 ! setting the mpi variables for WHAM
             ind_eleint_old_nucl,ind_eleint_nucl,nele_int_tot_vdw_nucl,&
             my_ele_inds_vdw_nucl,my_ele_inde_vdw_nucl,ind_eleint_vdw_nucl,&
             ind_eleint_vdw_old_nucl,nscp_int_tot_nucl,my_scp_inds_nucl,&
-            my_scp_inde_nucl,ind_scpint_nucl,ind_scpint_old_nucl
+            my_scp_inde_nucl,ind_scpint_nucl,ind_scpint_old_nucl,impishi
 !      integer,dimension(5) :: nct_molec,nnt_molec
 !el      allocate(itask_cont_from(0:nfgtasks-1)) !(0:max_fg_procs-1)
 !el      allocate(itask_cont_to(0:nfgtasks-1)) !(0:max_fg_procs-1)
         write (iout,'(i3,2(2x,2i3))') &
        i,(istart(i,iint),iend(i,iint),iint=1,nint_gr(i))
       enddo
-      endif
+!      endif
 !      lprint=.false.
       write (iout,'(a)') 'Interaction array2:' 
       do i=iatsc_s_nucl,iatsc_e_nucl
         write (iout,'(i3,2(2x,2i4))') &
        i,(istart_nucl(i,iint),iend_nucl(i,iint),iint=1,nint_gr_nucl(i))
       enddo
-
+      endif
       ispp=4 !?? wham ispp=2
 #ifdef MPI
 ! Now partition the electrostatic-interaction array
       ibond_nucl_start=ibond_nucl_start+nnt_molec(2)-1
       ibond_nucl_end=ibond_nucl_end+nnt_molec(2)-1
       print *,"NUCLibond",ibond_nucl_start,ibond_nucl_end
+      if (nres_molec(2).ne.0) then
       print *, "before devision",nnt_molec(2),nct_molec(2)-nnt_molec(2)
       call int_bounds(nct_molec(2)-nnt_molec(2),ibondp_nucl_start,ibondp_nucl_end)
       ibondp_nucl_start=ibondp_nucl_start+nnt_molec(2)
       ibondp_nucl_end=ibondp_nucl_end+nnt_molec(2)
+       else
+       ibondp_nucl_start=1
+       ibondp_nucl_end=0
+       endif
       print *,"NUCLibond2",ibondp_nucl_start,ibondp_nucl_end
 
 
         call MPI_Type_contiguous(18,MPI_DOUBLE_PRECISION,MPI_UYZGRAD,&
           IERROR)
         call MPI_Type_commit(MPI_UYZGRAD,IERROR)
+        call MPI_Type_contiguous(maxcontsshi,MPI_INTEGER,MPI_I50,IERROR)
+        call MPI_Type_commit(MPI_I50,IERROR)
+        call MPI_Type_contiguous(maxcontsshi,MPI_DOUBLE_PRECISION,MPI_D50,IERROR)
+        call MPI_Type_commit(MPI_D50,IERROR)
+
+         impishi=maxcontsshi*3
+!        call MPI_Type_contiguous(impishi,MPI_DOUBLE_PRECISION, &
+!        MPI_SHI,IERROR)
+!        call MPI_Type_commit(MPI_SHI,IERROR)
+!        print *,MPI_SHI,"MPI_SHI",MPI_D50
         call MPI_Type_contiguous(2,MPI_DOUBLE_PRECISION,MPI_MU,IERROR)
         call MPI_Type_commit(MPI_MU,IERROR)
         call MPI_Type_contiguous(4,MPI_DOUBLE_PRECISION,MPI_MAT1,IERROR)
       nside=0
       do i=2,nres-1
       mnum=molnum(i)
+      write(iout,*) "i",molnum(i)
 #ifdef WHAM_RUN
         if (itype(i,1).ne.10) then
 #else
-        if (itype(i,1).ne.10 .and. itype(i,mnum).ne.ntyp1_molec(mnum)) then
+        if (itype(i,1).ne.10 .and. itype(i,mnum).ne.ntyp1_molec(mnum) .and. mnum.ne.5) then
 #endif
          nside=nside+1
           ialph(i,1)=nvar+nside
       return
       end subroutine setup_var
 !-----------------------------------------------------------------------------
-! rescode.f
-!-----------------------------------------------------------------------------
-      integer function rescode(iseq,nam,itype,molecule)
-
-      use io_base, only: ucase
-!      implicit real*8 (a-h,o-z)
-!      include 'DIMENSIONS'
-!      include 'COMMON.NAMES'
-!      include 'COMMON.IOUNITS'
-      character(len=3) :: nam  !,ucase
-      integer :: iseq,itype,i
-      integer :: molecule
-      print *,molecule,nam
-      if (molecule.eq.1) then 
-      if (itype.eq.0) then
-
-      do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
-        if (ucase(nam).eq.restyp(i,molecule)) then
-          rescode=i
-          return
-        endif
-      enddo
-
-      else
-
-      do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
-        if (nam(1:1).eq.onelet(i)) then
-          rescode=i
-          return  
-        endif  
-      enddo
-
-      endif
-      else if (molecule.eq.2) then
-      do i=1,ntyp1_molec(molecule)
-         print *,nam(1:1),restyp(i,molecule)(1:1) 
-        if (nam(2:2).eq.restyp(i,molecule)(1:1)) then
-          rescode=i
-          return
-        endif
-      enddo
-      else if (molecule.eq.3) then
-       write(iout,*) "SUGAR not yet implemented"
-       stop
-      else if (molecule.eq.4) then
-       write(iout,*) "Explicit LIPID not yet implemented"
-       stop
-      else if (molecule.eq.5) then
-      do i=1,ntyp1_molec(molecule)
-        print *,i,restyp(i,molecule)(1:2)
-        if (ucase(nam(1:2)).eq.restyp(i,molecule)(1:2)) then
-          rescode=i
-          return
-        endif
-      enddo
-      else   
-       write(iout,*) "molecule not defined"
-      endif
-      write (iout,10) iseq,nam
-      stop
-   10 format ('**** Error - residue',i4,' has an unresolved name ',a3)
-      end function rescode
-      integer function sugarcode(sugar,ires)
-      character sugar
-      integer ires
-      if (sugar.eq.'D') then
-        sugarcode=1
-      else if (sugar.eq.' ') then
-        sugarcode=2
-      else
-        write (iout,*) 'UNKNOWN sugar type for residue',ires,' ',sugar
-        stop
-      endif
-      return
-      end function sugarcode
-
-!-----------------------------------------------------------------------------
 ! timing.F
 !-----------------------------------------------------------------------------
 ! $Date: 1994/10/05 16:41:52 $