atomes 1.1.14
atomes: an atomic scale modeling tool box
Loading...
Searching...
No Matches
trj.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
22INTEGER (KIND=c_int) FUNCTION read_trj (trj_f, ltrj, natrj, nbstrj, is_npt) bind (C,NAME='read_trj_')
23
24!
25! Lecture of atom types and coordinates - CPMD trajectory
26!
27
28USE parameters
29
30IMPLICIT NONE
31
32LOGICAL :: isok
33INTEGER (KIND=c_int), INTENT(IN) :: ltrj, natrj, is_npt
34INTEGER (KIND=c_int), DIMENSION(NSP), INTENT(IN) :: nbstrj
35CHARACTER (KIND=c_char), DIMENSION(*), INTENT(IN) :: trj_f
36CHARACTER (LEN=ltrj) :: trj_file
37INTERFACE
38INTEGER FUNCTION test_length(UNITFILE, NATL)
39 INTEGER, INTENT(IN) :: unitfile, natl
40END FUNCTION
41END INTERFACE
42
43do i=1, ltrj
44 trj_file(i:i) = trj_f(i)
45enddo
46
47read_trj = 1
48inquire (file=trj_file, exist=isok)
49if (isok) then
50
51 open (unit=20, file=trj_file, action='read', status='old', err=001)
52 ns=0
53 na=natrj
54 ns=test_length(20, na)
55 if (ns .ge. 1) then
56 rewind(20)
57 if (allocated(fullpos)) deallocate(fullpos)
58 allocate (fullpos(na,3,ns), stat=err)
59 if (err .ne. 0) then
60 call show_error ("Impossible to allocate memory"//char(0), &
61 "Function: read_trj"//char(0), "Table: FULLPOS"//char(0))
62 read_trj=3
63 goto 001
64 endif
65 if (allocated(tab_of_type)) deallocate(tab_of_type)
66 allocate (tab_of_type(na), stat=err)
67 if (err .ne. 0) then
68 call show_error ("Impossible to allocate memory"//char(0), &
69 "Function: read_trj"//char(0), "Table: TAB_OF_TYPE"//char(0))
70 read_trj=3
71 goto 001
72 endif
73 do i=1, ns
74 l=1
75 do j=1, nsp
76 do k=1, nbstrj(j)
77 read (20, *, err=002) z, fullpos(l,1,i), fullpos(l,2,i), fullpos(l,3,i)
78 ! CPMD trajectory is in atomic units
79 do m=1, 3
81 enddo
83 l=l+1
84 enddo
85 enddo
86 enddo
87 if (is_npt .eq. 1) call send_steps (ns)
88 read_trj=0
89 else
90 read_trj=2
91 endif
92
93 002 continue
94
95 close (20)
96
97 001 continue
98
99endif
100
101END 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
character(len=2), dimension(:), allocatable tab_of_type
double precision z
integer err
character(len=2), dimension(:), allocatable label
integer nsp
integer(kind=c_int) function read_trj(trj_f, ltrj, natrj, nbstrj, is_npt)
Definition trj.F90:23
integer function test_length(unitfile, natl)
Definition xyz.F90:95