X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fsrc_MD-M%2Freadrtns_CSA.F;h=7b3f9a81c3d5bc9874f0dc179b96710b94d3c918;hb=3a2758de24121fb0f72bd604e2163b7a4b73a27e;hp=2eb63d130e29d3b4a1604c1c604c4dc0c02bcd02;hpb=036299742bb15ca3871e0907c6e6e3ea6fe96e0f;p=unres.git diff --git a/source/unres/src_MD-M/readrtns_CSA.F b/source/unres/src_MD-M/readrtns_CSA.F index 2eb63d1..7b3f9a8 100644 --- a/source/unres/src_MD-M/readrtns_CSA.F +++ b/source/unres/src_MD-M/readrtns_CSA.F @@ -98,6 +98,13 @@ c print *,"Processor",me," fg_rank",fg_rank," out1file",out1file C Set up the time limit (caution! The time must be input in minutes!) read_cart=index(controlcard,'READ_CART').gt.0 call readi(controlcard,'CONSTR_DIST',constr_dist,0) + write (iout,*) "constr_dist",constr_dist + call readi(controlcard,'NSAXS',nsaxs,0) + call readi(controlcard,'SAXS_MODE',saxs_mode,0) + call reada(controlcard,'SCAL_RAD',scal_rad,1.0d0) + call reada(controlcard,'SAXS_CUTOFF',saxs_cutoff,1.0d0) + write (iout,*) "Number of SAXS restraints",NSAXS," SAXS_MODE", + & SAXS_MODE," SCAL_RAD",scal_rad,"SAXS_CUTOFF",saxs_cutoff call readi(controlcard,'CONSTR_HOMOL',constr_homology,0) call readi(controlcard,'SYM',symetr,1) call reada(controlcard,'TIMLIM',timlim,960.0D0) ! default 16 hours @@ -241,10 +248,10 @@ C endif if ((lipbufthick*2.0d0).gt.lipthick) &write(iout,*) "WARNING WRONG SIZE OF LIP AQ BUF" endif - write(iout,*) "bordliptop=",bordliptop - write(iout,*) "bordlipbot=",bordlipbot - write(iout,*) "bufliptop=",bufliptop - write(iout,*) "buflipbot=",buflipbot +c write(iout,*) "bordliptop=",bordliptop +c write(iout,*) "bordlipbot=",bordlipbot +c write(iout,*) "bufliptop=",bufliptop +c write(iout,*) "buflipbot=",buflipbot if (me.eq.king .or. .not.out1file ) @@ -619,6 +626,7 @@ C Read weights of the subsequent energy terms. call reada(weightcard,'DELT_CORR',delt_corr,0.5d0) call reada(weightcard,'TEMP0',temp0,300.0d0) call reada(weightcard,'WLT',wliptran,0.0D0) + call reada(weightcard,'WSAXS',wsaxs,1.0D0) if (index(weightcard,'SOFT').gt.0) ipot=6 C 12/1/95 Added weight for the multi-body term WCORR call reada(weightcard,'WCORRH',wcorr,1.0D0) @@ -642,6 +650,7 @@ C 12/1/95 Added weight for the multi-body term WCORR weights(17)=wbond weights(18)=scal14 weights(21)=wsccor + weights(25)=wsaxs if(me.eq.king.or..not.out1file) & write (iout,10) wsc,wscp,welec,wvdwpp,wbond,wang,wscloc,wtor, & wtor_d,wstrain,wel_loc,wcorr,wcorr5,wcorr6,wsccor,wturn3, @@ -803,12 +812,16 @@ c print *,'Finished reading pdb data' call gen_side(iti,theta(i+1),alph(i),omeg(i),fail) nsi=nsi+1 enddo +c AL 7/10/16 +c Calculalte only the coordinates of the current sidechain; no need to rebuild +c whole chain + call locate_side_chain(i) if(fail) write(iout,*)'Adding sidechain failed for res ', & i,' after ',nsi,' trials' endif enddo C 10/03/12 Adam: Recalculate coordinates with new side chain positions - call chainbuild +c call chainbuild endif endif if (indpdb.eq.0) then @@ -869,6 +882,7 @@ C 8/13/98 Set limits to generating the dihedral angles phibound(2,i)=pi enddo read (inp,*) ndih_constr + write (iout,*) "ndish_constr",ndih_constr if (ndih_constr.gt.0) then read (inp,*) ftors read (inp,*) (idih_constr(i),phi0(i),drange(i),i=1,ndih_constr) @@ -963,7 +977,7 @@ c---------------------- call MPI_Finalize(MPI_COMM_WORLD,IERROR) stop 'Error reading reference structure' #endif - 39 call chainbuild + 39 call chainbuild_extconf call setup_var czscore call geom_to_var(nvar,coord_exp_zs(1,1)) nstart_sup=nnt @@ -980,7 +994,7 @@ czscore call geom_to_var(nvar,coord_exp_zs(1,1)) c write (iout,*) "constr_dist",constr_dist,nstart_sup,nsup call flush(iout) if (constr_dist.gt.0) call read_dist_constr - write (iout,*) "After read_dist_constr nhpb",nhpb +c write (iout,*) "After read_dist_constr nhpb",nhpb if ((AFMlog.gt.0).or.(selfguide.gt.0)) call read_afminp if(me.eq.king.or..not.out1file) & write (iout,*) 'Contact order:',co @@ -998,6 +1012,8 @@ c write (iout,*) "constr_dist",constr_dist,nstart_sup,nsup enddo endif endif + write (iout,*) "calling read_saxs_consrtr",nsaxs + if (nsaxs.gt.0) call read_saxs_constr if (constr_homology.gt.0) then @@ -1082,7 +1098,10 @@ C initial geometry. enddo return else + write (iout,*) "Calling read_ang" call read_angles(inp,*36) + write (iout,*) "Calling chainbuild" + call chainbuild_extconf endif goto 37 36 write (iout,'(a)') 'Error reading angle file.' @@ -1107,6 +1126,53 @@ C initial geometry. omeg(i)=-120d0*deg2rad if (itype(i).le.0) omeg(i)=-omeg(i) enddo +c from old chainbuild +C +C Define the origin and orientation of the coordinate system and locate the +C first three CA's and SC(2). +C + call orig_frame +* +* Build the alpha-carbon chain. +* + do i=4,nres + call locate_next_res(i) + enddo +C +C First and last SC must coincide with the corresponding CA. +C + do j=1,3 + dc(j,nres+1)=0.0D0 + dc_norm(j,nres+1)=0.0D0 + dc(j,nres+nres)=0.0D0 + dc_norm(j,nres+nres)=0.0D0 + c(j,nres+1)=c(j,1) + c(j,nres+nres)=c(j,nres) + enddo +C +C Define the origin and orientation of the coordinate system and locate the +C first three CA's and SC(2). +C + call orig_frame +* +* Build the alpha-carbon chain. +* + do i=4,nres + call locate_next_res(i) + enddo +C +C First and last SC must coincide with the corresponding CA. +C + do j=1,3 + dc(j,nres+1)=0.0D0 + dc_norm(j,nres+1)=0.0D0 + dc(j,nres+nres)=0.0D0 + dc_norm(j,nres+nres)=0.0D0 + c(j,nres+1)=c(j,1) + c(j,nres+nres)=c(j,nres) + enddo + +c else if(me.eq.king.or..not.out1file) & write (iout,'(a)') 'Random-generated initial geometry.' @@ -1782,6 +1848,8 @@ c---------------------------------------------------------------------------- include 'DIMENSIONS' include 'COMMON.MINIM' include 'COMMON.IOUNITS' + include 'COMMON.CONTROL' + include 'COMMON.SETUP' character*80 ucase character*320 minimcard call card_concat(minimcard) @@ -1794,12 +1862,18 @@ c---------------------------------------------------------------------------- print_min_stat=min0(index(minimcard,'PRINT_MIN_STAT'),1) print_min_res=min0(index(minimcard,'PRINT_MIN_RES'),1) print_min_ini=min0(index(minimcard,'PRINT_MIN_INI'),1) +#ifdef MPI + if (.not. out1file .or. me.eq.king) then +#endif write (iout,'(/80(1h*)/20x,a/80(1h*))') & 'Options in energy minimization:' write (iout,'(4(a,i5),a,1pe14.5,a,1pe14.5)') & 'MaxMin:',MaxMin,' MaxFun:',MaxFun, & 'MinMin:',MinMin,' MinFun:',MinFun, & ' TolF:',TolF,' RTolF:',RTolF +#ifdef MPI + endif +#endif return end c---------------------------------------------------------------------------- @@ -2062,6 +2136,8 @@ C Get parameter filenames and open the parameter files. open (ielep,file=elename,status='old') call getenv_loc('SIDEPAR',sidename) open (isidep,file=sidename,status='old') + call getenv_loc('LIPTRANPAR',liptranname) + open (iliptranpar,file=liptranname,status='old') #else open(1,file=pref_orig(:ilen(pref_orig))//'.inp',status='old', & readonly) @@ -2093,7 +2169,7 @@ c print *,ithep_pdb," opened" call getenv_loc('SIDEPAR',sidename) open (isidep,file=sidename,status='old',readonly) call getenv_loc('LIPTRANPAR',liptranname) - open (iliptranpar,file=liptranname,status='old',action='read') + open (iliptranpar,file=liptranname,status='old',readonly) #ifndef CRYST_SC call getenv_loc('ROTPARPDB',rotname_pdb) open (irotam_pdb,file=rotname_pdb,status='old',action='read') @@ -2389,6 +2465,72 @@ CCCC NOW PROPERTIES FOR AFM end c------------------------------------------------------------------------------- + subroutine read_saxs_constr + implicit real*8 (a-h,o-z) + include 'DIMENSIONS' +#ifdef MPI + include 'mpif.h' +#endif + include 'COMMON.SETUP' + include 'COMMON.CONTROL' + include 'COMMON.CHAIN' + include 'COMMON.IOUNITS' + include 'COMMON.SBRIDGE' + double precision cm(3) +c read(inp,*) nsaxs + write (iout,*) "Calling read_saxs nsaxs",nsaxs + call flush(iout) + if (saxs_mode.eq.0) then +c SAXS distance distribution + do i=1,nsaxs + read(inp,*) distsaxs(i),Psaxs(i) + enddo + Cnorm = 0.0d0 + do i=1,nsaxs + Cnorm = Cnorm + Psaxs(i) + enddo + write (iout,*) "Cnorm",Cnorm + do i=1,nsaxs + Psaxs(i)=Psaxs(i)/Cnorm + enddo + write (iout,*) "Normalized distance distribution from SAXS" + do i=1,nsaxs + write (iout,'(f8.2,e15.5)') distsaxs(i),Psaxs(i) + enddo + Wsaxs0=0.0d0 + do i=1,nsaxs + Wsaxs0=Wsaxs0-Psaxs(i)*dlog(Psaxs(i)) + enddo + write (iout,*) "Wsaxs0",Wsaxs0 + else +c SAXS "spheres". + do i=1,nsaxs + read (inp,'(30x,3f8.3)') (Csaxs(j,i),j=1,3) + enddo + do j=1,3 + cm(j)=0.0d0 + enddo + do i=1,nsaxs + do j=1,3 + cm(j)=cm(j)+Csaxs(j,i) + enddo + enddo + do j=1,3 + cm(j)=cm(j)/nsaxs + enddo + do i=1,nsaxs + do j=1,3 + Csaxs(j,i)=Csaxs(j,i)-cm(j) + enddo + enddo + write (iout,*) "SAXS sphere coordinates" + do i=1,nsaxs + write (iout,'(i5,3f10.5)') i,(Csaxs(j,i),j=1,3) + enddo + endif + return + end +c------------------------------------------------------------------------------- subroutine read_dist_constr implicit real*8 (a-h,o-z) include 'DIMENSIONS' @@ -2589,13 +2731,17 @@ c Alternative: reading from input read2sigma=(index(controlcard,'READ2SIGMA').gt.0) start_from_model=(index(controlcard,'START_FROM_MODELS').gt.0) if(.not.read2sigma.and.start_from_model) then - write(iout,*) 'START_FROM_MODELS works only with READ2SIGMA' + if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) + & write(iout,*) 'START_FROM_MODELS works only with READ2SIGMA' start_from_model=.false. endif - if(start_from_model) write(iout,*) 'START_FROM_MODELS is ON' + if(start_from_model .and. (me.eq.king .or. .not. out1file)) + & write(iout,*) 'START_FROM_MODELS is ON' if(start_from_model .and. rest) then - write(iout,*) 'START_FROM_MODELS is OFF' - write(iout,*) 'remove restart keyword from input' + if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) then + write(iout,*) 'START_FROM_MODELS is OFF' + write(iout,*) 'remove restart keyword from input' + endif endif if (homol_nset.gt.1)then call card_concat(controlcard) @@ -2619,7 +2765,7 @@ cd call flush(iout) lim_odl=0 lim_dih=0 c - write(iout,*) 'nnt=',nnt,'nct=',nct +c write(iout,*) 'nnt=',nnt,'nct=',nct c do i = nnt,nct do k=1,constr_homology @@ -2638,11 +2784,8 @@ c do k=1,constr_homology read(inp,'(a)') pdbfile -c Next stament causes error upon compilation (?) -c if(me.eq.king.or. .not. out1file) -c write (iout,'(2a)') 'PDB data will be read from file ', -c & pdbfile(:ilen(pdbfile)) - write (iout,'(a,5x,a)') 'HOMOL: Opening PDB file', + if(me.eq.king .or. .not. out1file) + & write (iout,'(a,5x,a)') 'HOMOL: Opening PDB file', & pdbfile(:ilen(pdbfile)) open(ipdbin,file=pdbfile,status='old',err=33) goto 34 @@ -2691,7 +2834,8 @@ c write(iout,*) "tpl_k_rescore - ",tpl_k_rescore rescore(k,i_tmp)=rescore_tmp rescore2(k,i_tmp)=rescore2_tmp rescore3(k,i_tmp)=rescore3_tmp - write(iout,'(a7,i5,3f10.5,i5)') "rescore", + if (.not. out1file .or. me.eq.king) + & write(iout,'(a7,i5,3f10.5,i5)') "rescore", & i_tmp,rescore2_tmp,rescore_tmp, & rescore3_tmp,idomain_tmp else