atomes 1.1.14
atomes: an atomic scale modeling tool box
Loading...
Searching...
No Matches
xyz.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 (KIND=c_int) FUNCTION read_xyz (xyz_f, lxyz, is_npt) bind (C,NAME='read_xyz_')
22
23!INTEGER FUNCTION read_xyz (xyz_file, lxyz)
24
25!
26! Lecture of atom types and coordinates - XYZ files
27!
28USE parameters
29
30IMPLICIT NONE
31
32LOGICAL :: isok
33INTEGER (KIND=c_int), INTENT(IN) :: lxyz, is_npt
34CHARACTER (KIND=c_char), DIMENSION(*), INTENT(IN) :: xyz_f
35CHARACTER (LEN=lxyz) :: xyz_file
36INTERFACE
37INTEGER FUNCTION test_length(UNITFILE, NATL)
38 INTEGER, INTENT(IN) :: unitfile, natl
39END FUNCTION
40END INTERFACE
41
42do i=1, lxyz
43 xyz_file(i:i) = xyz_f(i)
44enddo
45
47
48inquire (file=xyz_file, exist=isok)
49if (isok) then
50
51 open (unit=20, file=xyz_file, action='read', status='old', err=001)
52 ns=0
53 read (20, *, err=002) na
54 ns = test_length(20, na+2)
55 if (ns .gt. 0) then
56
57 rewind(20)
58 if (allocated(fullpos)) deallocate(fullpos)
59 allocate (fullpos(na,3,ns), stat=err)
60 if (err .ne. 0) then
61 call show_error ("Impossible to allocate memory"//char(0), &
62 "Function: read_xyz"//char(0), "Table: FULLPOS"//char(0))
63 endif
64 if (allocated(tab_of_type)) deallocate(tab_of_type)
65 allocate (tab_of_type(na), stat=err)
66 if (err .ne. 0) then
67 call show_error ("Impossible to allocate memory"//char(0), &
68 "Function: read_xyz"//char(0), "Table: TAB_OF_TYPE"//char(0))
69 endif
70
71 do i=1, ns
72 read (20, *, err=002)
73 read (20, *, err=002)
74 do j=1, na
75 read (20, *, err=002) tab_of_type(j), fullpos(j,1,i), fullpos(j,2,i), fullpos(j,3,i)
76 enddo
77 enddo
78 if (is_npt .eq. 1) call send_steps (ns)
79 read_xyz=0
80 else
81 read_xyz=2
82 endif
83
84 002 continue
85
86 close (20)
87
88 001 continue
89
90endif
91
92END FUNCTION
93
94INTEGER FUNCTION test_length (UNITFILE, NATL)
95
96IMPLICIT NONE
97INTEGER, INTENT(IN) :: unitfile, natl
98INTEGER :: lenf
99INTEGER :: eof
100
101rewind(unitfile)
102eof=0
103lenf=0
104do while (eof .eq. 0)
105 read (unitfile, *, iostat=eof)
106 lenf=lenf+1
107enddo
108lenf=lenf-1
109
110test_length=mod(lenf,natl)
111if (test_length .eq. 0) then
112 test_length=lenf/natl
113else
115endif
116
117END FUNCTION
118
119SUBROUTINE send_label (sp_id, sp_ln, spec_label) bind (C,NAME='send_label_')
120
121USE parameters
122
123IMPLICIT NONE
124
125INTEGER (KIND=c_int), INTENT(IN) :: sp_id, sp_ln
126CHARACTER (KIND=c_char), DIMENSION(sp_ln), INTENT(IN) :: spec_label
127
128tl(sp_id)=" "
129do i=1, sp_ln
130 tl(sp_id)(i:i) = spec_label(i)
131enddo
132
133END SUBROUTINE
134
135INTEGER (KIND=c_int) FUNCTION write_xyz (xyz_f, lxyz, fxyz, txyz) bind (C,NAME='write_xyz_')
136
137!
138! output of atom types and coordinates - Multiple XYZ files
139!
140
141USE parameters
142
143IMPLICIT NONE
144
145INTEGER (KIND=c_int), INTENT(IN) :: lxyz, fxyz, txyz
146CHARACTER (KIND=c_char), DIMENSION(*), INTENT(IN) :: xyz_f
147DOUBLE PRECISION, DIMENSION(3) :: savep
148CHARACTER (LEN=lxyz) :: xyz_file
149
150INTERFACE
151INTEGER FUNCTION test_length(UNITFILE, NATL)
152 INTEGER, INTENT(IN) :: unitfile, natl
153END FUNCTION
154END INTERFACE
155
156do i=1, lxyz
157 xyz_file(i:i) = xyz_f(i)
158enddo
159
160write_xyz=1
161open (unit=20, file=xyz_file, action='write', status='unknown', err=001)
162do i=1, ns
163 write (20, '(i10)') na
164 write (20, *)
165 do j=1, na
166 if (fxyz .eq. 1) then
167 if (ncells .gt. 1) then
168 nbox => the_box(i)
169 else
170 nbox => the_box(1)
171 endif
172 savep = matmul(fullpos(j,:,i),nbox%carttofrac)
173 else
174 savep = fullpos(j,:,i)
175 if (txyz .eq. 1) then
176 savep(:) = savep(:)/angtobohr
177 endif
178 endif
179 write (20, '(a2,3(3x,f15.10))', err=002) tl(lot(j)), savep
180 enddo
181enddo
182write_xyz=0
183
184002 continue
185
186close (20)
187
188001 continue
189
190END FUNCTION
action
Definition glview.h:189
void show_error(char *error, int val, GtkWidget *win)
show error message
Definition interface.c:293
double precision, dimension(:,:,:), allocatable fullpos
double precision, parameter angtobohr
integer ncells
character(len=2), dimension(:), allocatable tab_of_type
character(len=2), dimension(:), allocatable tl
type(lattice), pointer nbox
integer err
type(lattice), dimension(:), allocatable, target the_box
integer, dimension(:), allocatable lot
subroutine send_label(sp_id, sp_ln, spec_label)
Definition xyz.F90:120
integer(kind=c_int) function write_xyz(xyz_f, lxyz, fxyz, txyz)
Definition xyz.F90:136
integer function test_length(unitfile, natl)
Definition xyz.F90:95
integer(kind=c_int) function read_xyz(xyz_f, lxyz, is_npt)
Definition xyz.F90:22