atomes 1.1.14
atomes: an atomic scale modeling tool box
Loading...
Searching...
No Matches
allochem.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
21INTEGER FUNCTION allochem ()
22
23USE parameters
24
25IMPLICIT NONE
26
27grnum=16+5*nsp*nsp
28sqnum=8+4*nsp*nsp
29sknum=8+4*nsp*nsp
33if (nsp .eq. 2) then
34 grnum=grnum+6
35 sqnum=sqnum+8
36 sknum=sknum+8
37 gqnum=gqnum+6
38endif
39rinum=20*(nsp+1)
40chnum=nsp+1
41shnum=nsp+1
42msnum=0
43if (ns .gt. 1) msnum=14*nsp+6
44
45if (allocated(nbspbs)) deallocate(nbspbs)
46allocate(nbspbs(nsp+1), stat=err)
47if (err .ne. 0) then
48 call show_error ("Impossible to allocate memory"//char(0), &
49 "Function: ALLOCHEM"//char(0), "Table: NBSPBS"//char(0))
50 allochem = 0
51 goto 001
52endif
53if (allocated(tl)) deallocate(tl)
54allocate(tl(nsp), stat=err)
55if (err .ne. 0) then
56 call show_error ("Impossible to allocate memory"//char(0), &
57 "Function: ALLOCHEM"//char(0), "Table: TL"//char(0))
58 allochem = 0
59 goto 001
60endif
61if (allocated(mass)) deallocate(mass)
62allocate(mass(nsp), stat=err)
63if (err .ne. 0) then
64 call show_error ("Impossible to allocate memory"//char(0), &
65 "Function: ALLOCHEM"//char(0), "Table: MASS"//char(0))
66 allochem = 0
67 goto 001
68endif
69if (allocated(rvdw)) deallocate(rvdw)
70allocate(rvdw(nsp), stat=err)
71if (err .ne. 0) then
72 call show_error ("Impossible to allocate memory"//char(0), &
73 "Function: ALLOCHEM"//char(0), "Table: RVDW"//char(0))
74 allochem = 0
75 goto 001
76endif
77if (allocated(atomid)) deallocate(atomid)
78allocate(atomid(nsp), stat=err)
79if (err .ne. 0) then
80 call show_error ("Impossible to allocate memory"//char(0), &
81 "Function: ALLOCHEM"//char(0), "Table: ATOMID"//char(0))
82 allochem = 0
83 goto 001
84endif
85if (allocated(gr_cut)) deallocate(gr_cut)
86allocate(gr_cut(nsp,nsp), stat=err)
87if (err .ne. 0) then
88 call show_error ("Impossible to allocate memory"//char(0), &
89 "Function: ALLOCHEM"//char(0), "Table: Gr_CUT"//char(0))
90 allochem = 0
91 goto 001
92endif
93if (allocated(xi)) deallocate(xi)
94allocate(xi(nsp), stat=err)
95if (err .ne. 0) then
96 call show_error ("Impossible to allocate memory"//char(0), &
97 "Function: ALLOCHEM"//char(0), "Table: Xi"//char(0))
98 allochem = 0
99 goto 001
100endif
101if (allocated(nscattl)) deallocate(nscattl)
102allocate(nscattl(nsp), stat=err)
103if (err .ne. 0) then
104 call show_error ("Impossible to allocate memory"//char(0), &
105 "Function: ALLOCHEM"//char(0), "Table: NSCATTL"//char(0))
106 allochem = 0
107 goto 001
108endif
109if (allocated(xscattl)) deallocate(xscattl)
110allocate(xscattl(nsp), stat=err)
111if (err .ne. 0) then
112 call show_error ("Impossible to allocate memory"//char(0), &
113 "Function: ALLOCHEM"//char(0), "Table: XSCATTL"//char(0))
114 allochem = 0
115 goto 001
116endif
117
118allochem = 1
119
120001 continue
121
122END FUNCTION
integer function allochem()
Definition allochem.F90:22
void show_error(char *error, int val, GtkWidget *win)
show error message
Definition interface.c:293
double precision, dimension(:), allocatable nscattl
double precision, dimension(:), allocatable mass
integer sknum
integer shnum
double precision, dimension(:), allocatable xi
character(len=2), dimension(:), allocatable tl
integer gqnum
integer chnum
integer, dimension(:), allocatable nbspbs
integer err
integer grnum
double precision, dimension(:), allocatable xscattl
integer bdnum
integer msnum
double precision, dimension(:,:), allocatable gr_cut
integer, dimension(:), allocatable atomid
integer annum
integer sqnum
double precision, dimension(:), allocatable rvdw
integer nsp
integer rinum