corrections of max... ranges of arrays
[unres4.git] / source / unres / unres.f90
index 8700369..4216238 100644 (file)
       else
 #endif
       if (modecalc.eq.0) then
-!write(iout,*)"!!!!!!!!!!!!!!!!! in unres"
-
         call exec_eeval_or_minim
-!write(iout,*)"!!!!!!!!!!!!!!!!! in unres"
-
       else if (modecalc.eq.1) then
         call exec_regularize
       else if (modecalc.eq.2) then
         call exec_mult_eeval_or_minim
       else if (modecalc.eq.5) then
         call exec_checkgrad
-!write(iout,*) "check grad dwa razy"
-!el        call exec_checkgrad
       else if (ModeCalc.eq.7) then
         call exec_map
       else if (ModeCalc.eq.8) then
         write (iout,'(a)') 'This calculation type is not supported',&
          ModeCalc
       endif
-!elwrite(iout,*)"!!!!!!!!!!!!!!!!!"
 
 #ifdef MPI
       endif
 
        print *,"Processor",myrank," after chainbuild"
        icall=1
-!elwrite(iout,*)"in exec_eeval or minimim"
 
        call etotal_long(energy_long)
        write (iout,*) "Printing long range energy"
        call enerprint(energy_long)
-!elwrite(iout,*)"in exec_eeval or minimim"
 
        call etotal_short(energy_short)
        write (iout,*) "Printing short range energy"
       endif
 
       call etotal(energy_)
-!elwrite(iout,*)"after etotal in exec_eev"
 #ifdef MPI
       time_ene=MPI_Wtime()-time00
 #endif
       etota = energy_(0)
       etot = etota
       call enerprint(energy_)
-!write(iout,*)"after enerprint"
       call hairpin(.true.,nharp,iharp)
-!write(iout,*) "after hairpin"!,hfrag(1,1)
       call secondary2(.true.)
-!write(iout,*) "after secondary2"
       if (minim) then
 !rc overlap test
-!elwrite(iout,*) "after secondary2 minim",minim
         if (overlapsc) then 
           print *, 'Calling OVERLAP_SC'
-!write(iout,*) 'Calling OVERLAP_SC'
           call overlap_sc(fail)
-!write(iout,*) 'after Calling OVERLAP_SC'
         endif 
 
         if (searchsc) then 
         endif 
 
         if (dccart) then
-!write(iout,*) 'CART  calling minim_dc', nvar
           print *, 'Calling MINIM_DC'
 #ifdef MPI
           time1=MPI_WTIME()
           call minim_dc(etot,iretcode,nfun)
 !    call check_ecartint !el
         else 
-!write(iout,*) "indpdb",indpdb
           if (indpdb.ne.0) then 
-!write(iout,*) 'if indpdb', indpdb
             call bond_regular
             call chainbuild
           endif
           call geom_to_var(nvar,varia)
-!write(iout,*) 'po geom to var; calling minimize', nvar
           print *,'Calling MINIMIZE.'
 #ifdef MPI
           time1=MPI_WTIME()
           write (iout,'(a,i20)') '# of energy evaluations:',nfun+1
           write (iout,'(a,f16.3)')'# of energy evaluations/sec:',evals
       else
-!elwrite(iout,*) "after secondary2 minim",minim
         print *,'refstr=',refstr
         if (refstr) call rms_nac_nnc(rms,frac,frac_nn,co,.true.)
-!elwrite(iout,*) "rms_nac"
-!elwrite(iout,*) "before briefout"
         call briefout(0,etot)
-!elwrite(iout,*) "after briefout"
       endif
       if (outpdb) call pdbout(etot,titel(:32),ipdb)
       if (outmol2) call mol2out(etot,titel(:32))