module geometry_data !----------------------------------------------------------------------------- ! commom.bounds ! common /bounds/ real(kind=8),dimension(:,:),allocatable :: phibound !(2,maxres) !----------------------------------------------------------------------------- ! commom.chain ! common /chain/ real(kind=8),dimension(:,:),allocatable :: c !(3,maxres2+2) real(kind=8),dimension(:,:),allocatable :: dc,dc_old,& dc_norm,dc_norm2 !(3,0:maxres2) real(kind=8),dimension(:,:),allocatable :: xloc,xrot !(3,maxres) real(kind=8),dimension(:),allocatable :: dc_work !(MAXRES6) integer :: nres,nres0 ! common /rotmat/ real(kind=8),dimension(:,:,:),allocatable :: prod,rt !(3,3,maxres) ! common /refstruct/ real(kind=8),dimension(:,:,:),allocatable :: cref !(3,maxres2+2,maxperm), real(kind=8),dimension(:,:),allocatable :: crefjlee !(3,maxres2+2), real(kind=8),dimension(:,:,:),allocatable :: chain_rep !(3,maxres2+2,maxsym) integer :: nsup,nstart_sup,nstart_seq,chain_length,iprzes,nperm integer :: nend_sup,ishift_pdb !wham real(kind=8) :: rmssing,anatemp !wham integer,dimension(:,:),allocatable :: tabperm !(maxperm,maxsym) ! common /from_zscore/ in module.compare !----------------------------------------------------------------------------- ! common.geo ! common /geo/ real(kind=8) :: pi,dwapi,pipol,pi3,dwapi3,deg2rad,rad2deg,angmin !----------------------------------------------------------------------------- ! common.local ! Inverses of the actual virtual bond lengths ! common /invlen/ real(kind=8),dimension(:),allocatable :: vbld_inv !(maxres2) !----------------------------------------------------------------------------- ! Max. number of lobes in SC distribution integer,parameter :: maxlob=5 !----------------------------------------------------------------------------- ! Max number of symetric chains integer,parameter :: maxsym=50 integer,parameter :: maxperm=120 !----------------------------------------------------------------------------- ! common.var ! Store the geometric variables in the following COMMON block. ! common /var/ real(kind=8),dimension(:),allocatable :: theta,phi,alph,omeg,& thetaref,phiref,costtab,sinttab,cost2tab,sint2tab !(maxres) real(kind=8),dimension(:),allocatable :: vbld !(2*maxres) real(kind=8),dimension(:,:),allocatable :: omicron !(2,maxres) real(kind=8),dimension(:,:),allocatable :: tauangle !(3,maxres) real(kind=8),dimension(:),allocatable :: xxtab,yytab,zztab,& xxref,yyref,zzref !(maxres) integer,dimension(:,:),allocatable :: ialph !(maxres,2) integer,dimension(:),allocatable :: ivar !(4*maxres2) integer :: ntheta,nphi,nside,nvar ! Store the angles and variables corresponding to old conformations (for use ! in MCM). ! common /oldgeo/ !el real(kind=8),dimension(:,:),allocatable :: varsave !(maxvar,maxsave) ! real(kind=8),dimension(:),allocatable :: esave !(maxsave) ! integer,dimension(:),allocatable :: Origin !(maxsave) ! integer :: nstore ! freeze some variables ! common /restr/ real(kind=8),dimension(:),allocatable :: varall !(maxvar) integer,dimension(:),allocatable :: mask_theta,& mask_phi,mask_side !(maxres) logical :: mask_r !----------------------------------------------------------------------------- ! common.MD ! common /qmeas/ real(kind=8),dimension(50) :: qfrag real(kind=8),dimension(100) :: qpair real(kind=8),dimension(:,:),allocatable :: qinfrag,wfrag !(50,maxprocs/20) real(kind=8),dimension(:,:),allocatable :: qinpair,wpair !(100,maxprocs/20) real(kind=8) :: Uconst integer,dimension(:,:,:),allocatable :: ifrag !(2,50,maxprocs/20) integer,dimension(:,:,:),allocatable :: ipair !(2,100,maxprocs/20) integer :: nfrag,npair !----------------------------------------------------------------------------- integer,dimension(:),allocatable :: itype_pdb !(maxres) initialize in molread !----------------------------------------------------------------------------- !----------------------------------------------------------------------------- ! common.box real(kind=8) :: boxxsize,boxysize,boxzsize end module geometry_data