21INTEGER (KIND=c_int) FUNCTION read_vas(vas_f, lvas, navas, nbsvas, is_npt) bind (C,NAME='read_vas_')
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
39 vas_file(
i:
i) = vas_f(
i)
44inquire (file=vas_file, exist=isok)
47 open (unit=20, file=vas_file,
action=
'read', status=
'old',
err=001)
56 call show_error (
"Impossible to allocate memory"//char(0), &
57 "Function: read_vas"//char(0),
"Table: FULLPOS"//char(0))
62 call show_error (
"Impossible to allocate memory"//char(0), &
63 "Function: read_vas"//char(0),
"Table: TAB_OF_TYPE"//char(0))
74 read (20, *,
err=002)
fullpos(
l,1,
i),
fullpos(
l,2,
i),
fullpos(
l,3,
i)
80 if (is_npt .eq. 1)
call send_steps (
ns)
101INTEGER,
INTENT(IN) :: unitfile, natl
109 read (unitfile, *, iostat=eof)
114 if (mod(lenf-7,natl+1) .eq. 0)
then
117else if (mod(lenf-6,natl+1) .eq. 0)
then
120else if (mod(lenf-5,natl+1) .eq. 0)
then
void show_error(char *error, int val, GtkWidget *win)
show error message
double precision, dimension(:,:,:), allocatable fullpos
character(len=2), dimension(:), allocatable tab_of_type
character(len=2), dimension(:), allocatable label
integer function test_vas(unitfile, natl)
integer(kind=c_int) function read_vas(vas_f, lvas, navas, nbsvas, is_npt)