atomes 1.1.14
atomes: an atomic scale modeling tool box
Loading...
Searching...
No Matches
vas.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_vas(vas_f, lvas, navas, nbsvas, is_npt) bind (C,NAME='read_vas_')
22
23!
24! Lecture of atom types and coordinates - VASP trajectory
25!
26
27USE parameters
28
29IMPLICIT NONE
30
31LOGICAL :: isok
32INTEGER :: nvas
33INTEGER (KIND=c_int), INTENT(IN) :: lvas, navas, is_npt
34INTEGER (KIND=c_int), DIMENSION(NSP), INTENT(IN) :: nbsvas
35CHARACTER (KIND=c_char), DIMENSION(*), INTENT(IN) :: vas_f
36CHARACTER (LEN=lvas) :: vas_file
37
38do i=1, lvas
39 vas_file(i:i) = vas_f(i)
40enddo
41
43
44inquire (file=vas_file, exist=isok)
45if (isok) then
46
47 open (unit=20, file=vas_file, action='read', status='old', err=001)
48 ns=0
49 na=navas
50 nvas=test_vas(20, na)
51 if (nvas.ge.1) then
52 rewind(20)
53 if (allocated(fullpos)) deallocate(fullpos)
54 allocate (fullpos(na,3,ns), stat=err)
55 if (err .ne. 0) then
56 call show_error ("Impossible to allocate memory"//char(0), &
57 "Function: read_vas"//char(0), "Table: FULLPOS"//char(0))
58 endif
59 if (allocated(tab_of_type)) deallocate(tab_of_type)
60 allocate (tab_of_type(na), stat=err)
61 if (err .ne. 0) then
62 call show_error ("Impossible to allocate memory"//char(0), &
63 "Function: read_vas"//char(0), "Table: TAB_OF_TYPE"//char(0))
64 endif
65 do i=1, nvas
66 read (20, *, err=002)
67 enddo
68 do i=1, ns
69 ! Read the 'Konfig' line
70 read (20, *, err=002)
71 l=1
72 do j=1, nsp
73 do k=1, nbsvas(j)
74 read (20, *, err=002) fullpos(l,1,i), fullpos(l,2,i), fullpos(l,3,i)
76 l=l+1
77 enddo
78 enddo
79 enddo
80 if (is_npt .eq. 1) call send_steps (ns)
81 read_vas=0
82 else
83 read_vas=2
84 endif
85
86 002 continue
87
88 close (20)
89
90 001 continue
91
92endif
93
94CONTAINS
95
96INTEGER FUNCTION test_vas(UNITFILE, NATL)
97
98USE parameters
99
100IMPLICIT NONE
101INTEGER, INTENT(IN) :: unitfile, natl
102INTEGER :: lenf
103INTEGER :: eof
104
105rewind(unitfile)
106eof=0
107lenf=0
108do while (eof .eq. 0)
109 read (unitfile, *, iostat=eof)
110 lenf=lenf+1
111enddo
112lenf=lenf-1
113
114 if (mod(lenf-7,natl+1) .eq. 0) then
115 ns=(lenf-7)/(natl+1)
116 test_vas=7
117else if (mod(lenf-6,natl+1) .eq. 0) then
118 ns=(lenf-6)/(natl+1)
119 test_vas=6
120else if (mod(lenf-5,natl+1) .eq. 0) then
121 ns=(lenf-5)/(natl+1)
122 test_vas=5
123else
124 test_vas=0
125endif
126
127END FUNCTION
128
129END FUNCTION
130
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
character(len=2), dimension(:), allocatable tab_of_type
integer err
character(len=2), dimension(:), allocatable label
integer nsp
integer function test_vas(unitfile, natl)
Definition vas.F90:97
integer(kind=c_int) function read_vas(vas_f, lvas, navas, nbsvas, is_npt)
Definition vas.F90:22