working energy for shield and lipid wrong gradient
[unres4.git] / source / unres / data / geometry_data.f90
1       module geometry_data
2 !-----------------------------------------------------------------------------
3 ! commom.bounds
4 !      common /bounds/
5       real(kind=8),dimension(:,:),allocatable :: phibound !(2,maxres)
6 !-----------------------------------------------------------------------------
7 ! commom.chain
8 !      common /chain/
9       real(kind=8),dimension(:,:),allocatable :: c !(3,maxres2+2)
10       real(kind=8),dimension(:,:),allocatable :: dc,dc_old,&
11        dc_norm,dc_norm2 !(3,0:maxres2)
12       real(kind=8),dimension(:,:),allocatable :: xloc,xrot !(3,maxres)
13       real(kind=8),dimension(:),allocatable :: dc_work !(MAXRES6)
14       integer :: nres,nres0
15 !      common /rotmat/
16       real(kind=8),dimension(:,:,:),allocatable :: prod,rt !(3,3,maxres)
17 !      common /refstruct/
18       real(kind=8),dimension(:,:,:),allocatable :: cref !(3,maxres2+2,maxperm),
19       real(kind=8),dimension(:,:),allocatable :: crefjlee !(3,maxres2+2),
20       real(kind=8),dimension(:,:,:),allocatable :: chain_rep !(3,maxres2+2,maxsym)
21       integer :: nsup,nstart_sup,nstart_seq,chain_length,iprzes,nperm
22       integer :: nend_sup,ishift_pdb  !wham
23       real(kind=8) :: rmssing,anatemp !wham
24       real(kind=8) :: buftubebot, buftubetop,bordtubebot,bordtubetop, &
25         tubebufthick
26       real(kind=8) :: buflipbot, bufliptop,bordlipbot,bordliptop,     &
27         lipbufthick,lipthick
28       integer,dimension(:,:),allocatable :: tabperm !(maxperm,maxsym)
29 !      common /from_zscore/ in module.compare
30 !-----------------------------------------------------------------------------
31 ! common.geo
32 !      common /geo/
33       real(kind=8) :: pi,dwapi,pipol,pi3,dwapi3,deg2rad,rad2deg,angmin
34 !-----------------------------------------------------------------------------
35 ! common.local
36 ! Inverses of the actual virtual bond lengths
37 !      common /invlen/
38       real(kind=8),dimension(:),allocatable :: vbld_inv !(maxres2)
39 !-----------------------------------------------------------------------------
40 ! Max. number of lobes in SC distribution
41       integer,parameter :: maxlob=5
42 !-----------------------------------------------------------------------------
43 ! Max number of symetric chains
44       integer,parameter :: maxsym=50
45       integer,parameter :: maxperm=120
46 !-----------------------------------------------------------------------------
47 ! common.var
48 ! Store the geometric variables in the following COMMON block.
49 !      common /var/
50       real(kind=8),dimension(:),allocatable :: theta,phi,alph,omeg,&
51        thetaref,phiref,costtab,sinttab,cost2tab,sint2tab !(maxres)
52       real(kind=8),dimension(:),allocatable :: vbld !(2*maxres)
53       real(kind=8),dimension(:,:),allocatable :: omicron !(2,maxres)
54       real(kind=8),dimension(:,:),allocatable :: tauangle !(3,maxres)
55       real(kind=8),dimension(:),allocatable :: xxtab,yytab,zztab,&
56        xxref,yyref,zzref !(maxres)
57       integer,dimension(:,:),allocatable :: ialph !(maxres,2)
58       integer,dimension(:),allocatable :: ivar !(4*maxres2)
59       integer :: ntheta,nphi,nside,nvar
60 ! Store the angles and variables corresponding to old conformations (for use
61 ! in MCM).
62 !      common /oldgeo/
63 !el      real(kind=8),dimension(:,:),allocatable :: varsave !(maxvar,maxsave)
64 !      real(kind=8),dimension(:),allocatable :: esave !(maxsave)
65 !      integer,dimension(:),allocatable :: Origin !(maxsave)
66 !      integer :: nstore
67 ! freeze some variables
68 !      common /restr/
69       real(kind=8),dimension(:),allocatable :: varall !(maxvar)
70       integer,dimension(:),allocatable :: mask_theta,&
71        mask_phi,mask_side !(maxres)
72       logical :: mask_r
73 !-----------------------------------------------------------------------------
74 ! common.MD
75 !      common /qmeas/
76       real(kind=8),dimension(50) :: qfrag
77       real(kind=8),dimension(100) :: qpair
78       real(kind=8),dimension(:,:),allocatable :: qinfrag,wfrag !(50,maxprocs/20)
79       real(kind=8),dimension(:,:),allocatable :: qinpair,wpair !(100,maxprocs/20)
80       real(kind=8) :: Uconst
81       integer,dimension(:,:,:),allocatable :: ifrag !(2,50,maxprocs/20)
82       integer,dimension(:,:,:),allocatable :: ipair !(2,100,maxprocs/20)
83       integer :: nfrag,npair
84 !-----------------------------------------------------------------------------
85       integer,dimension(:),allocatable :: itype_pdb !(maxres) initialize in molread
86 !-----------------------------------------------------------------------------
87 !-----------------------------------------------------------------------------
88 !  common.box
89       real(kind=8) :: boxxsize,boxysize,boxzsize
90
91       end module geometry_data