atomes 1.1.14
atomes: an atomic scale modeling tool box
Loading...
Searching...
No Matches
parameters.F90
Go to the documentation of this file.
1! This file is part of the 'atomes' software.
2!
3! 'atomes' is free software: you can redistribute it and/or modify it under the terms
4! of the GNU Affero General Public License as published by the Free Software Foundation,
5! either version 3 of the License, or (at your option) any later version.
6!
7! 'atomes' is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY;
8! without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
9! See the GNU General Public License for more details.
10!
11! You should have received a copy of the GNU Affero General Public License along with 'atomes'.
12! If not, see <https://www.gnu.org/licenses/>
13!
14! Copyright (C) 2022-2024 by CNRS and University of Strasbourg
15!
20
21!################################################################
22! This is the atomes code main include file which contains:
23! - Variables
24! - Structures
25! used all along the code and classified as follow:
26!
27! - LOGICAL type variables
28! - LOGICAL (:) type variables
29! - LOGICAL (:,:) type variables
30!
31! - INTEGER type variables
32! - INTEGER(:) type variables
33! - INTEGER(:,:) type variables
34! - INTEGER(:,:,:) type variables
35! - INTEGER(:,:,:,:) type variables
36! - INTEGER(:,:,:,:,:) type variables
37!
38! - CHARACTER type variables
39! - CHARACTER(:) type variables
40! - CHARACTER(:,:) type variables
41! - CHARACTER(:,:,:) type variables
42!
43! - DOUBLE PRECISION type variables
44!
45! - DOUBLE PRECISION type variables
46! - DOUBLE PRECISION(:) type variables
47! - DOUBLE PRECISION(:,:) type variables
48! - DOUBLE PRECISION(:,:,:) type variables
49! - DOUBLE PRECISION(:,:,:,:) type variables
50!
51! - STRUCTURES definitions
52!
53! - MPI // Only variables
54!
55! furthermore inside this first selection variables
56! have been sorted by routines when necessary/possible
57!################################################################
58
60
61use, INTRINSIC :: iso_c_binding
62
63IMPLICIT NONE
64
65!#################################### LOGICAL VARIABLES ####################################!
66
67LOGICAL :: pbc=.false. ! 1/0 Enable or disable periodic boundary conditions
68LOGICAL :: frac=.false. ! 1/0 Lattice relatives or DOUBLE PRECISIONs positions for atoms
69LOGICAL :: nohp=.false. ! 1/0 Enable/disable homopolar bonds in connectivty
70LOGICAL :: abab=.false. ! 1/0 Enable or disable only ABAB rings if more than 3 chemical species
71LOGICAL :: aaaa=.false. ! 1/0 Enable or disable only AAAA chains
72LOGICAL :: acac=.false. ! 1/0 Enable or disable only ABAB chains
73LOGICAL :: isolated=.false. ! 1/0 1-2-2-1 chains or N-2-2-N N=1,3 ... chains
74LOGICAL :: tomo=.false. ! 1/0 Homopolar or no homopolar bonds in the rings
75LOGICAL :: calc_rings=.false. ! 1/0 Compute ring statistics
76LOGICAL :: calc_r0=.false. ! 1/0 Find all existing rings in the box
77LOGICAL :: calc_r1=.false. ! 1/0 Shortest Path analysis
78LOGICAL :: calc_r2=.false. ! 1/0 King's analysis
79LOGICAL :: calc_r3=.false. ! 1/0 SP + Homo
80LOGICAL :: calc_r4=.false. ! 1/0 King's + Homo
81LOGICAL :: calc_prings=.false. ! 1/0 Compute primitive ring statistics
82LOGICAL :: calc_strings=.false. ! 1/0 Compute strongs ring statistics
83LOGICAL :: ring_p1=.false. ! 1/0 Compute first part of detailed ring properties
84LOGICAL :: ring_p2=.false. ! 1/0 Compute second part of detailed ring properties
85LOGICAL :: ring_p3=.false. ! 1/0 Compute third part of detailed ring properties
86LOGICAL :: ring_p4=.false. ! 1/0 Compute fourth part of detailed ring properties
87LOGICAL :: ring_p5=.false. ! 1/0 Compute fifth part of detailed ring properties
88LOGICAL :: overall_cubic=.false. ! 1/0 Cubic a=b=c, 90.0, 90.0, 90.0
89#ifdef OPENMP
90LOGICAL :: all_atoms=.false. ! 1/0 Force OpenMP on ATOMS
91#endif
92
93! *rings*.f90 !
94
95LOGICAL :: factatring=.false. ! 1/0 Calculate atomic ring factor using the RN variable (thesis S. LE ROUX)
96LOGICAL :: factatpna=.false. ! 1/0 Calculate atomic ring factor using the PN variable (thesis S. LE ROUX)
97LOGICAL :: factatrmax=.false. ! 1/0 Calculate atomic ring factor using the Pmax var (thesis S. LE ROUX)
98LOGICAL :: factatrmin=.false. ! 1/0 Calculate atomic ring factor using the Pmin var (thesis S. LE ROUX)
99LOGICAL :: runsearch ! 1/0 Run ring statistics in the case of 3 or more species
100LOGICAL :: addspec ! 1/0 Add to chain in the ring case of 3 or more species
101LOGICAL :: doampat=.false. ! 1/0 if CALC_R1,R2,R3 or R4 to known if there are paths > TAILLD
102LOGICAL :: saut, ssaut
103LOGICAL :: found
104LOGICAL :: pathout
105LOGICAL :: firr, pirr
106LOGICAL :: homo
107LOGICAL :: dosearch
108LOGICAL :: tbr=.false.
109LOGICAL :: alc=.false.
110LOGICAL :: no_homo=.false.
111LOGICAL :: allrings=.false.
112
113!##########################################################################################!
114
115
116!###################################### INTEGER VARIABLES #####################################!
117
118!***************************************** Misc *******************************************!
119
120INTEGER :: h=0, i=0, j=0, k=0, l=0, m=0, n=0, o=0, p=0, r=0, t=0, u=0, v=0
121INTEGER :: noa, nob, noc, nod, noe
123INTEGER :: nsub, ntsub, tsub, err
124INTEGER :: nl, nc, nsi, nsj
125INTEGER :: number_of_i
126INTEGER :: dtv
127INTEGER :: nbonds, anbonds
128INTEGER :: ndx, nbx, idr
129INTEGER :: gr_index
130INTEGER :: sum_index
131INTEGER :: ang_i
132INTEGER :: finish, indexmsf
133INTEGER :: id1, id2, id, gtbsize
134INTEGER :: spirr
135INTEGER :: l_tot, la_tot
136INTEGER :: numa, sc
137INTEGER :: path, nnp, nna
138INTEGER :: loa, lob, loc
139INTEGER :: maxat, minat
140INTEGER :: maxst, minst
142INTEGER :: ab, abc
143
144!*************************************** Defined ******************************************!
145
146INTEGER :: na, number_of_a ! Number of atom in the box
147INTEGER :: nsp, nsp_by_step ! Number of species
148INTEGER :: ns, nos, nstp ! Number of DM steps = Number of configurations
149INTEGER :: nsbg ! Number of step between each geomerty
150INTEGER :: taillr, tailld ! Depth for rings hunt
151INTEGER :: taille, taillh, taillt ! Depth for rings hunt
152INTEGER :: taillc ! Depth for chains hunt
153INTEGER :: tlt, ntlt
154INTEGER :: number_of_qmod ! Number of Qvect modulus
155INTEGER :: number_of_qvect ! Number of Qvectors
156INTEGER :: ltlt ! Ring's hunt species
157INTEGER :: ncells ! Number of lattice 1 or MD steps if NPT calculation
158
159INTEGER :: idgr=0
160INTEGER :: idsq=1
161INTEGER :: idsk=2
162INTEGER :: idgrfft=3
163INTEGER :: idbd=4
164INTEGER :: idan=5
165INTEGER :: idri=6
166INTEGER :: idch=7
167INTEGER :: idsp=8
168INTEGER :: idmsd=9
169
170INTEGER :: maxn=20 ! The maximun number of neighbors an atom can have
171
172! *rings*.f90 !
173
174INTEGER :: molats
175INTEGER :: molstep
176INTEGER :: molcounter
177INTEGER :: tmbs
178
179!##########################################################################################!
180
181
182!#################################### INTEGER(:) VARIABLES #####################################!
183
184!************************************* defined ********************************************!
185
186INTEGER, DIMENSION(:), ALLOCATABLE :: lot
187INTEGER, DIMENSION(:), ALLOCATABLE :: nbspbs ! Number of atom of species=index_1
188
189! prepdata.F90 !
190
191INTEGER, DIMENSION(:), ALLOCATABLE :: atomid
192
193! dmtx.f90 !
194
195INTEGER, DIMENSION(3) :: isize
196
197! sk.f90 !
198
199INTEGER, DIMENSION(:), ALLOCATABLE :: degeneracy
200
201! molecuels.f90 !
202
203INTEGER, DIMENSION(:), ALLOCATABLE :: mibs
204
205! bonds.F90 !
206
207INTEGER, DIMENSION(:), ALLOCATABLE :: tot_gsa
208INTEGER, DIMENSION(:), ALLOCATABLE :: ntetra
209INTEGER, DIMENSION(:), ALLOCATABLE :: lp_geom
210INTEGER, DIMENSION(:), ALLOCATABLE :: togl, tigl
211INTEGER, DIMENSION(:), ALLOCATABLE :: lgsa, ngsa
212
213! *rings*.f90 !
214
215INTEGER, DIMENSION(:), ALLOCATABLE :: rpat, cpat
216INTEGER, DIMENSION(:), ALLOCATABLE :: mol_atoms
217
218! alloc*rings.F90 - rings.F90 !
219
220INTEGER, DIMENSION(:), ALLOCATABLE :: res_list
221INTEGER, DIMENSION(:), ALLOCATABLE :: apna, spna
222INTEGER, DIMENSION(:), ALLOCATABLE :: valid
223
224! primrings.F90 !
225
226INTEGER, DIMENSION(:), ALLOCATABLE :: queue, ringstat
227INTEGER, DIMENSION(:), ALLOCATABLE :: npring, matdist
228
229!#################################### INTEGER (:,:) VARIABLES ###################################!
230
231! bonds.F90 !
232
233INTEGER, DIMENSION(:,:), ALLOCATABLE :: lt_geom
234INTEGER, DIMENSION(:,:), ALLOCATABLE :: geom_la
235INTEGER, DIMENSION(:,:), ALLOCATABLE :: tot_geomsa
236INTEGER, DIMENSION(:,:), ALLOCATABLE :: tetra
237
238! molecules.f90 !
239
240INTEGER, DIMENSION(:,:), ALLOCATABLE :: tiida
241INTEGER, DIMENSION(:,:), ALLOCATABLE :: tisp
242
243! dmtx.f90 !
244
245INTEGER, DIMENSION(:,:), ALLOCATABLE :: contj
246
247! escs.F90 !
248
249INTEGER, DIMENSION(:,:), ALLOCATABLE :: cort
250INTEGER, DIMENSION(:,:), ALLOCATABLE :: edget
251INTEGER, DIMENSION(:,:), ALLOCATABLE :: deft
252INTEGER, DIMENSION(:,:), ALLOCATABLE :: corta
253INTEGER, DIMENSION(:,:), ALLOCATABLE :: edgeta
254INTEGER, DIMENSION(:,:), ALLOCATABLE :: defta
255INTEGER, DIMENSION(:,:), ALLOCATABLE :: tda
256
257! alloc*rings.F90 - rings.F90 !
258
259INTEGER, DIMENSION(:,:), ALLOCATABLE, TARGET :: indr
260INTEGER, DIMENSION(:,:), ALLOCATABLE, TARGET :: nring
261INTEGER, DIMENSION(:,:), ALLOCATABLE :: vpat
262INTEGER, DIMENSION(:,:), ALLOCATABLE :: indrat, nirrat, nirr
263INTEGER, DIMENSION(:,:), ALLOCATABLE :: atrmsx, atrmsn
264INTEGER, DIMENSION(:,:), ALLOCATABLE :: ampat, atrmax, atrmin
265INTEGER, DIMENSION(:,:), ALLOCATABLE :: maxpna, minpna
266
267! primrings.F90 !
268
269INTEGER, DIMENSION(:,:), ALLOCATABLE :: pring
270INTEGER, DIMENSION(:,:), ALLOCATABLE :: querng, vref
271INTEGER, DIMENSION(:,:), ALLOCATABLE :: pringord
272
273!##########################################################################################!
274
275
276!#################################### INTEGER VARIABLES #################################!
277
278! bonds.F90 !
279
280INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: la_count
281
282! escs.F90 !
283
284INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: corner
285INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: edge
286INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: def
287INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: cornera
288INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: edgea
289INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: defa
290INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: tdsa
291
292! dmtx.f90 !
293
294INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: voisj
295
296! bonds.f90 !
297
298INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: statbd
299
300! allocrings.F90 - rings.F90 !
301
302INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: indring, indsring, lirr
303INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: atring, atpna, matpna
304INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: stpna
305INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: pna, sna
306INTEGER, DIMENSION(:,:,:), ALLOCATABLE, TARGET :: ringsaved
307
308! primrings.F90 !
309
310INTEGER, DIMENSION(:,:,:), ALLOCATABLE, TARGET :: sringsaved
311
312!##########################################################################################!
313
314
315!################################## INTEGER(:,:,:,:) VARIABLES #################################!
316
317! angles.f90 !
318
319! allocrings.F90 - rings.F90 !
320
321INTEGER, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: ringord
322
323! allocprims.f90 - primrings.F90 !
324
325INTEGER, DIMENSION(:,:,:,:), ALLOCATABLE, TARGET :: sringord
326
327!##########################################################################################!
328
329
330!###################################### CHARACTER VARIABLES ####################################!
331
332! Misc !
333
334CHARACTER (LEN=15) :: sdate, stime, szone ! Starting date and time
335CHARACTER (LEN=15) :: edate, etime, ezone ! Ending date and time
336CHARACTER (LEN=9) :: progname="ATOMES"
337
338! misc !
339
340CHARACTER (LEN=2) :: choose
341CHARACTER (LEN=2) :: a1, a2
342CHARACTER (LEN=2) :: atot
343CHARACTER (LEN=20) :: nom_tmp
344CHARACTER (LEN=15) :: ntmp, ntmp2, ntmp3, nstep, nomx, nomy
345CHARACTER (LEN=15) :: nom, nom1, nom2, nom3, nom4
346CHARACTER (LEN=40) :: nomsys, noms
347CHARACTER (LEN=16) :: spind
348CHARACTER (LEN=20) :: alc_tab
349
350!##########################################################################################!
351
352
353!##################################### CHARACTER (:) VARIABLES ###################################!
354
355! Misc !
356
357CHARACTER (LEN=2), DIMENSION(:), ALLOCATABLE :: tl, ftab ! Label of species=index_1
358CHARACTER (LEN=2), DIMENSION(:), ALLOCATABLE :: tab_of_type ! List of atom by name(species)=indx_1, by DM step=indx_2
359CHARACTER (LEN=2), DIMENSION(:), ALLOCATABLE :: label ! Label of species=index in input
360
361! prepdata.F90 !
362
363CHARACTER (LEN=15), DIMENSION(:), ALLOCATABLE :: elemid
364
365
366!##########################################################################################!
367
368!#################################### CHARACTER (:,:) VARIABLES ##################################!
369
370CHARACTER (LEN=12), DIMENSION(:,:), ALLOCATABLE :: liste_geoms
371
372!##########################################################################################!
373
374!################################### CHARACTER (:,:,:) VARIABLES #################################!
375
376! CHARACTER (LEN=12), DIMENSION(:,:,:), ALLOCATABLE :: LGEO
377CHARACTER (LEN=12), DIMENSION(:,:,:), ALLOCATABLE :: lgeo
378
379!##########################################################################################!
380
381
382
383!###################################### DOUBLE PRECISION VARIABLES ####################################!
384
385DOUBLE PRECISION :: ltemp
386
387!##########################################################################################!
388
389
390
391!###################################### DOUBLE PRECISION VARIABLES ##################################!
392
393! Misc !
394
395DOUBLE PRECISION :: w=0.0d0, x=0.0d0, y=0.0d0, z=0.0d0
396DOUBLE PRECISION, PARAMETER :: pi=acos(-1.0)
397DOUBLE PRECISION, PARAMETER :: avogadro=6.02214179d0
398DOUBLE PRECISION, PARAMETER :: angtobohr=0.52917721
399DOUBLE PRECISION :: p1, p2, p3
400DOUBLE PRECISION :: time_tot, tstat
401DOUBLE PRECISION :: mbox
402DOUBLE PRECISION :: boxs2
403DOUBLE PRECISION :: base
404DOUBLE PRECISION :: teta
405DOUBLE PRECISION :: dc
406DOUBLE PRECISION :: delta_ang
407DOUBLE PRECISION :: meanvol
408DOUBLE PRECISION :: total_density, real_density
409DOUBLE PRECISION :: freevol, ecfreev
410DOUBLE PRECISION :: dij, dil, vij
411DOUBLE PRECISION :: gr_cutoff
412DOUBLE PRECISION :: cutf
413!DOUBLE PRECISION :: A2A, B2B, C2C, AAA, BBB, CCC
414
415! sq.f90 !
416
417DOUBLE PRECISION :: phi, sinus_phi
418
419! sk.f90 !
420
421DOUBLE PRECISION :: norm_tot, delta_q
422DOUBLE PRECISION :: rmax, sinus_fact_rmax, fact_rmax
423DOUBLE PRECISION :: sigma_liss
424DOUBLE PRECISION :: qvmod, qvmax, qvmin
425
426!##########################################################################################!
427
428
429!#################################### DOUBLE PRECISION (:) VARIABLES ##################################!
430
431! Misc !
432
433DOUBLE PRECISION, DIMENSION(3) :: rij, ril, rim, dab, var ! Position vector
434DOUBLE PRECISION, DIMENSION(3) :: r2ij, r2cor, rcm, rcm2
435DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: s_length
436DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: mass, m_ss
437DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: rvdw, r_dw
438DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: dcte ! Diffusion Cte
439DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: dist_ij, dist_ji
440DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: cmoy, xi
441DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: mtabl
442
443! dmtx.f90 !
444
445DOUBLE PRECISION, DIMENSION(3) :: cutfv
446DOUBLE PRECISION, DIMENSION(3) :: pmin, pmax
447
448! bonds.F90 !
449
450DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: mac
451DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: sa_count
452
453! escs.f90 !
454
455DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: eabl, cabl, dabl
456DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: etabl, ctabl, dtabl
457DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: ectabl, tdtabl
458
459! gr.f90 !
460
461DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: r_point
462DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: grtab
463DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: grtot, ggrtot ! Total RDF
464DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: drn, trn ! Total RDF
465DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: xgrtot, xggrtot ! Total RDF
466DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: drx, trx ! Total RDF
467DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: shell_vol ! Shell volume as a function of d=(index-0.5)DELTA
468
469! sq.f90 !
470
471DOUBLE PRECISION, DIMENSION(2) :: gd, gn, go, c_box
472DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: nscattl ! Neutron Scattering Length of species=index
473DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: xscattl ! X-ray Scattering Length of species=index
474DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: s, xs ! Total structure factor \\ Go=f(G(r))
475DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: gr_t
476DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: q_point, k_point
477
478! sk.f90 - utils.f90 !
479
480DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: fnbspbs
481DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: modq
482DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: qvectx, qvecty, qvectz
483DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: cij, sik
484
485! grfft.f90 !
486
487DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: gfft, dfft, r_pfft, tdfft
488
489! resrings.f90 !
490
491DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: moypur, moyred
492DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: moypat, moyrat
493DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: ectype, ectyp, ectypat, ectat
494DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: irred, red
495DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: redat, irrat
496DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: totpstep
497DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: rnamax, rnamin
498DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: evmax, evmin
499
500!##########################################################################################!
501
502
503!################################## DOUBLE PRECISION (:,:) VARIABLES ##################################!
504
505! Misc !
506
507DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: epna
508DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: poa, pob ! Atm=indx_1, coord=indx_2(1=x, 2=y, 3=z)
509
510! bonds.F90 !
511
512DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: ma_count
513DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: num_gsa
514DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: gr_cut, gr_tmp
515
516! fzbt.f90 !
517
518DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: btij ! Bathia-Thornton Partial g(r)/s(q)
519
520! escs.F90 !
521
522DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: etype
523DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: ctype
524DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: detype
525DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: etypea
526DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: ctypea
527DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: detypea
528DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: etda
529
530! sk.f90 !
531
532DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: qvect
533
534! msd.f90 !
535
536DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: drift, cor
537DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE :: d2i, d2inac
538
539!##########################################################################################!
540
541
542!################################# DOUBLE PRECISION (:,:,:) VARIABLES #################################!
543
544! Misc !
545
546DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: fullpos
547DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: fullvel
548DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: nfullpos, nfpos
549DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: ecart_type
550
551! gr.f90 !
552
553DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: gr_ij ! Average of the RDF on all the MD run
554DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: ggr_ij ! Average of the RDF on all the MD run
555DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: dn_ij ! Average of the Dn on all the MD run
556
557! grfft.f90 !
558
559DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: gqbt
560
561! sq.f90 !
562
563DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: sij, spij ! Partial structure factor
564DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: ss_ij ! Partial structure factor
565
566! fzbt.f90 !
567
568DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: fzsij
569
570! msd.f90 !
571
572DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: d2ij, d2ijnac, d2dir, d2dirnac
573DOUBLE PRECISION, DIMENSION(:,:,:), ALLOCATABLE :: cornac
574
575!##########################################################################################!
576
577
578!################################ DOUBLE PRECISION (:,:,:,:) VARIABLES ################################!
579
580! gr.F90 !
581
582DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: gij ! RDF distance=index_1, atom_a=index_2, atom_b=index_3, step=index_4
583DOUBLE PRECISION, DIMENSION(:,:,:,:), ALLOCATABLE :: dn ! Dn distance=index_1, atom_a=index_2, atom_b=index_3, step=index_4
584
585!##########################################################################################!
586
587!################################ STRUCTURES VARIABLES Definition ###############################!
588
589!TYPE ATOM !
590! INTEGER :: INDICE !
591! INTEGER :: ELEMENT !
592! INTEGER :: NEIGHBOR ! Atom structure definition
593! DOUBLE PRECISION :: X, Y, Z !
594! TYPE (ATOM), POINTER :: PAST !
595! TYPE (ATOM), POINTER :: NEXT !
596!END TYPE ATOM !
597
598!TYPE MOLECULE !
599! INTEGER :: INDICE !
600! INTEGER :: ATOMS !
601! TYPE (ATOM), POINTER :: FIRST_ATOM !
602! TYPE (ATOM), POINTER :: LAST_ATOM ! Molecule structure definition
603! TYPE (MOLECULE), POINTER :: NEXT_MOL !
604! TYPE (MOLECULE), POINTER :: PAST_MOL !
605!END TYPE MOLECULE
606
607!TYPE MODEL !
608! INTEGER :: ATOMS !
609! INTEGER :: MOLECULES ! Model structure definition
610! TYPE (MOLECULE), POINTER :: FIRST_MOL !
611! TYPE (MOLECULE), POINTER :: LAST_MOL !
612!END TYPE MODEL
613 !
614!TYPE (ATOM), POINTER :: AT !
615!TYPE (MOLECULE), POINTER :: MOL !
616!TYPE (MODEL), POINTER :: MODL !
617
618TYPE at
619 INTEGER :: ind
620 TYPE (at), POINTER :: next
621 TYPE (at), POINTER :: prev
622END TYPE at
623
624TYPE mol
625 INTEGER :: mid
626 INTEGER :: step
627 INTEGER :: atomes
628 INTEGER, DIMENSION(:), ALLOCATABLE :: bsp
629 TYPE (at), POINTER :: first_at
630 TYPE (at), POINTER :: atom
631 TYPE (mol), POINTER :: next
632 TYPE (mol), POINTER :: prev
633END TYPE mol
634
635TYPE ring !
636 INTEGER :: atom !
637 INTEGER :: neighbor ! Ring structure definition
638 INTEGER :: spec !
639 TYPE (ring), POINTER :: past ! used in the ring search subroutines
640 TYPE (ring), POINTER :: next !
641END TYPE ring !
642
643TYPE pixel !
644 INTEGER :: neighbor ! Pixel structure definition
645 INTEGER :: atoms !
646 INTEGER, DIMENSION(:), ALLOCATABLE :: atom_id ! Note: MAXN*10 vs. ALL for Angles
647 LOGICAL :: tocheck !
648 LOGICAL :: checked !
649 INTEGER, DIMENSION(27) :: idneigh !
650END TYPE pixel
651
652TYPE (pixel), DIMENSION(:), ALLOCATABLE :: thepix, testpix
653
655 LOGICAL :: glass=.false. ! 1/0 if the structure is 'cubic like' (90/90/90)
656 LOGICAL :: cubic=.false. ! 1/0 if the structure is 'cubic' (90/90/90, a=b=c)
657 DOUBLE PRECISION :: volume
658 DOUBLE PRECISION, DIMENSION(3) :: modv ! Lattice parameters
659 DOUBLE PRECISION :: minv, maxv ! Min, max a,b, c
660 DOUBLE PRECISION, DIMENSION(3) :: modr ! Reciprocal lattice parameters
661 DOUBLE PRECISION :: minr, maxr ! Min, max, ra, rb, rc
662 DOUBLE PRECISION, DIMENSION(3,3) :: lvect ! Lattice vectors
663 DOUBLE PRECISION, DIMENSION(3,3) :: lrecp ! Reciprocal lattice vectors
664 DOUBLE PRECISION, DIMENSION(3,3) :: fractocart, carttofrac ! Conversion matrix
665END TYPE lattice
666
667TYPE (lattice), DIMENSION(:), ALLOCATABLE, TARGET :: the_box
668TYPE (lattice), POINTER :: nbox
669
670!##########################################################################################!
671
672!##########################################################################################!
673
674END MODULE parameters
675
676! ######################################## EOF ###########################################!
677
integer rate_count
integer nsi
integer tsub
integer, dimension(:,:), allocatable atrmax
double precision, dimension(:), allocatable cmoy
double precision, dimension(:,:,:), allocatable fullpos
integer, dimension(:,:,:), allocatable statbd
logical homo
double precision qvmin
double precision, parameter angtobohr
double precision, dimension(:), allocatable drx
integer ncells
integer loa
character(len=2) a2
double precision, dimension(:), allocatable fnbspbs
logical allrings
double precision total_density
integer, dimension(:), allocatable mibs
double precision rmax
integer nsj
integer, dimension(:), allocatable mol_atoms
integer ntlt
double precision, dimension(:,:,:), allocatable nfullpos
integer nos
logical abab
double precision, dimension(2) gd
double precision fact_rmax
double precision, parameter avogadro
double precision, dimension(:), allocatable tdtabl
logical found
double precision, dimension(:), allocatable mtabl
character(len=15) ntmp
double precision, dimension(3) var
double precision, dimension(3) rcm
double precision, dimension(:), allocatable moyred
double precision w
character(len=40) nomsys
double precision qvmod
character(len=15) nom4
double precision, dimension(:), allocatable trx
logical calc_r3
character(len=15) nom3
logical factatrmax
logical ring_p4
double precision, dimension(:), allocatable qvectx
integer, dimension(3) isize
character(len=2) choose
double precision sigma_liss
logical firr
integer ltlt
integer molcounter
logical factatring
integer idmsd
integer, dimension(:,:), allocatable atrmsx
double precision, dimension(:), allocatable nscattl
double precision, dimension(3) rim
double precision, dimension(:,:), allocatable d2inac
double precision, dimension(:), allocatable mass
double precision teta
double precision, dimension(:), allocatable dist_ji
double precision ltemp
double precision, dimension(:,:,:), allocatable fullvel
integer la_tot
double precision dc
double precision, dimension(:,:,:), allocatable fzsij
double precision, dimension(:), allocatable moypat
integer number_of_qmod
double precision boxs2
double precision x
double precision, dimension(:,:,:), allocatable dn_ij
logical isolated
integer taillc
integer, dimension(:,:,:), allocatable atpna
integer number_of_qvect
double precision, dimension(:), allocatable ectyp
character(len=20) nom_tmp
double precision, dimension(:), allocatable qvecty
double precision, dimension(:,:), allocatable pob
integer id2
double precision, dimension(:), allocatable r_pfft
integer, dimension(:,:), allocatable indrat
integer idan
integer tmbs
logical acac
integer, dimension(:), allocatable spna
integer sknum
double precision, dimension(:), allocatable ggrtot
integer shnum
logical calc_r2
double precision delta_q
integer tailld
character(len=2) atot
integer max_count
integer, dimension(:,:,:), allocatable def
double precision, dimension(:), allocatable cij
character(len=2), dimension(:), allocatable tab_of_type
character(len=15), dimension(:), allocatable elemid
double precision, dimension(:), allocatable q_point
integer, dimension(:), allocatable lgsa
double precision, dimension(:,:,:), allocatable ggr_ij
double precision, dimension(:), allocatable grtab
double precision, dimension(:,:), allocatable gr_tmp
integer, dimension(:,:,:), allocatable edge
double precision, dimension(:), allocatable xi
double precision, dimension(:), allocatable moypur
logical pathout
integer, dimension(:,:), allocatable contj
double precision, dimension(:,:), allocatable ctypea
integer finish
double precision, dimension(:,:,:), allocatable d2dirnac
double precision, dimension(:,:), allocatable poa
integer, dimension(:,:,:), allocatable atring
integer idsk
double precision, dimension(:,:,:), allocatable nfpos
logical calc_prings
double precision, dimension(:), allocatable dist_ij
integer nna
character(len=2), dimension(:), allocatable tl
double precision, dimension(:,:), allocatable ma_count
logical factatpna
double precision, dimension(:), allocatable ctabl
double precision, dimension(:), allocatable totpstep
double precision, dimension(:,:,:), allocatable spij
double precision cutf
logical tbr
double precision, dimension(:), allocatable dcte
integer lob
logical ring_p1
double precision, dimension(:), allocatable m_ss
double precision real_density
logical ring_p2
double precision, dimension(3) pmax
integer, dimension(:,:), allocatable ampat
integer gr_index
logical ssaut
character(len=20) alc_tab
type(pixel), dimension(:), allocatable thepix
integer nbx
double precision, dimension(:), allocatable k_point
integer nnp
integer gqnum
integer, dimension(:,:,:), allocatable lirr
character(len=12), dimension(:,:), allocatable liste_geoms
integer nob
integer, dimension(:,:,:), allocatable defa
double precision freevol
double precision base
integer chnum
character(len=15) sdate
integer, dimension(:), allocatable nbspbs
integer molstep
double precision, dimension(:), allocatable evmin
double precision, dimension(:,:), allocatable d2i
integer noc
double precision phi
double precision, dimension(:), allocatable s
integer idsp
integer, dimension(:,:), allocatable maxpna
double precision, dimension(:), allocatable r_point
double precision, dimension(3) r2ij
integer, dimension(:,:), allocatable minpna
double precision, dimension(:,:), allocatable btij
integer, dimension(:,:), allocatable querng
integer, dimension(:,:), allocatable nirr
integer, dimension(:,:), allocatable pringord
integer noa
integer ntsub
integer, dimension(:,:,:), allocatable edgea
double precision, dimension(:,:,:,:), allocatable gij
double precision, dimension(:), allocatable grtot
character(len=15) ntmp3
integer, dimension(:), allocatable degeneracy
double precision, dimension(:,:), allocatable ctype
double precision, dimension(:,:), allocatable etypea
double precision, dimension(:), allocatable ectypat
integer taillt
double precision, dimension(:), allocatable s_length
integer nsbg
double precision p1
integer, dimension(:), allocatable valid
character(len=15) ntmp2
character(len=15) nomy
double precision, dimension(:), allocatable eabl
type(lattice), pointer nbox
double precision, dimension(:), allocatable red
logical ring_p5
integer nbonds
integer id1
double precision gr_cutoff
integer, dimension(:,:), allocatable corta
double precision, dimension(3) ril
integer gtbsize
integer idbd
integer, dimension(:,:), allocatable edget
double precision, dimension(:), allocatable ectype
integer taillr
double precision, dimension(:), allocatable xs
integer, dimension(:), allocatable tot_gsa
integer maxat
integer molats
double precision p2
double precision z
double precision, dimension(2) c_box
integer numa
integer, dimension(:,:,:), allocatable la_count
integer err
integer dtv
integer, dimension(:), allocatable rpat
double precision, dimension(:,:), allocatable cor
double precision, dimension(:), allocatable modq
integer, dimension(:), allocatable res_list
double precision, dimension(:), allocatable evmax
double precision delta_ang
character(len=16) spind
logical calc_r4
double precision, dimension(3) rij
integer, dimension(:,:), allocatable tisp
type(lattice), dimension(:), allocatable, target the_box
integer, dimension(:,:,:), allocatable tdsa
integer idr
double precision, dimension(:), allocatable mac
double precision ecfreev
integer nsp_by_step
character(len=12), dimension(:,:,:), allocatable lgeo
integer anbonds
logical nohp
integer, dimension(:,:,:), allocatable indsring
double precision, dimension(:), allocatable tdfft
character(len=15) nom1
double precision, dimension(:,:), allocatable qvect
integer, dimension(:,:), allocatable pring
integer nstp
double precision, dimension(:,:,:), allocatable d2dir
integer, dimension(:,:), allocatable atrmsn
type(pixel), dimension(:), allocatable testpix
character(len=15) nomx
double precision, dimension(:), allocatable irred
logical saut
integer, dimension(:), allocatable ngsa
double precision, dimension(:), allocatable cabl
double precision, dimension(:,:,:), allocatable d2ijnac
integer, dimension(:,:), allocatable tot_geomsa
integer maxn
double precision, dimension(3) pmin
integer indexmsf
character(len=15) nstep
integer idsq
integer, dimension(:,:), allocatable edgeta
double precision, dimension(:,:,:), allocatable ss_ij
integer, dimension(:,:,:), allocatable voisj
double precision, dimension(:), allocatable irrat
integer maxst
double precision, dimension(:,:,:,:), allocatable dn
integer l_tot
double precision norm_tot
integer, dimension(:,:), allocatable tda
integer, dimension(:,:), allocatable deft
double precision, dimension(:,:,:), allocatable gr_ij
integer, dimension(:,:), allocatable tetra
integer, dimension(:,:,:,:), allocatable, target sringord
integer grnum
double precision, dimension(3) dab
integer, dimension(:,:,:,:), allocatable, target ringord
double precision, dimension(:,:,:), allocatable d2ij
character(len=9) progname
character(len=15) nom
double precision, dimension(:,:), allocatable etda
double precision dil
double precision, dimension(:), allocatable moyrat
logical addspec
integer nsub
double precision dij
integer, dimension(:,:,:), allocatable matpna
integer sum_index
double precision vij
double precision, dimension(:), allocatable xggrtot
logical alc
double precision, dimension(2) go
double precision, dimension(:,:), allocatable num_gsa
integer, dimension(:,:,:), allocatable pna
logical frac
double precision, dimension(:), allocatable xscattl
double precision, dimension(:,:), allocatable drift
integer minst
integer idgrfft
character(len=2), dimension(:), allocatable ftab
double precision p3
logical runsearch
logical calc_rings
double precision, dimension(:,:), allocatable epna
character(len=15) szone
integer idri
double precision, dimension(:), allocatable shell_vol
double precision meanvol
integer noe
integer bdnum
integer, dimension(:,:,:), allocatable cornera
integer, dimension(:,:), allocatable vref
double precision, dimension(:), allocatable qvectz
integer, dimension(:,:), allocatable atrmin
character(len=15) ezone
integer abc
integer, dimension(:,:), allocatable defta
integer counter
integer ndx
character(len=15) edate
double precision, dimension(:), allocatable ectat
double precision, dimension(:), allocatable ectabl
integer, dimension(:,:), allocatable, target indr
logical doampat
logical dosearch
integer, dimension(:,:,:), allocatable indring
double precision, dimension(:), allocatable rnamin
integer nod
integer msnum
logical ring_p3
logical aaaa
integer, dimension(:,:), allocatable vpat
logical calc_strings
integer, dimension(:,:,:), allocatable stpna
integer, dimension(:,:,:), allocatable sna
double precision, dimension(:,:), allocatable gr_cut
integer, dimension(:), allocatable npring
character(len=15) nom2
integer, dimension(:), allocatable lp_geom
double precision, dimension(:), allocatable dfft
integer loc
double precision, dimension(:), allocatable gfft
double precision, dimension(:), allocatable etabl
integer, dimension(:), allocatable atomid
double precision y
double precision, dimension(:,:), allocatable etype
integer spirr
character(len=2) a1
double precision, dimension(:), allocatable dabl
double precision, dimension(:), allocatable r_dw
double precision, dimension(:), allocatable gr_t
integer idch
double precision, dimension(:,:), allocatable detype
double precision mbox
integer, dimension(:,:), allocatable nirrat
double precision tstat
character(len=15) stime
double precision, dimension(:), allocatable rnamax
double precision sinus_fact_rmax
double precision, dimension(:,:,:), allocatable gqbt
integer annum
character(len=2), dimension(:), allocatable label
integer, dimension(:), allocatable cpat
double precision time_tot
integer, dimension(:), allocatable apna
integer ang_i
logical overall_cubic
logical tomo
logical factatrmin
logical calc_r1
double precision, dimension(:), allocatable redat
integer taillh
double precision, dimension(:), allocatable drn
integer, dimension(:,:,:), allocatable, target ringsaved
integer idgr
integer tlt
integer number_of_a
integer, dimension(:), allocatable ringstat
double precision, dimension(:), allocatable sa_count
double precision, dimension(:), allocatable trn
double precision, dimension(3) rcm2
double precision, dimension(:), allocatable dtabl
integer sqnum
integer, dimension(:), allocatable ntetra
integer, dimension(:,:,:), allocatable corner
integer, dimension(:), allocatable lot
double precision, dimension(:,:,:), allocatable ecart_type
logical pirr
integer minat
double precision, dimension(:), allocatable rvdw
double precision sinus_phi
logical pbc
integer, dimension(:), allocatable matdist
double precision, dimension(:,:), allocatable detypea
integer, dimension(:,:), allocatable, target nring
integer nsp
double precision, dimension(2) gn
double precision qvmax
integer, dimension(:,:), allocatable lt_geom
integer, dimension(:), allocatable tigl
double precision, dimension(:,:,:), allocatable sij
double precision, dimension(:), allocatable xgrtot
double precision, dimension(3) cutfv
integer, dimension(:,:,:), allocatable, target sringsaved
integer, dimension(:), allocatable togl
double precision, dimension(:,:,:), allocatable cornac
logical calc_r0
logical no_homo
integer, dimension(:), allocatable queue
integer, dimension(:,:), allocatable geom_la
double precision, parameter pi
double precision, dimension(:), allocatable sik
integer, dimension(:,:), allocatable cort
integer, dimension(:,:), allocatable tiida
character(len=40) noms
double precision, dimension(3) r2cor
integer taille
integer rinum
integer number_of_i
Definition global.h:839