File: plot_io.f90

package info (click to toggle)
espresso 6.7-2
  • links: PTS, VCS
  • area: main
  • in suites: bookworm, bullseye
  • size: 311,040 kB
  • sloc: f90: 447,429; ansic: 52,566; sh: 40,631; xml: 37,561; tcl: 20,077; lisp: 5,923; makefile: 4,502; python: 4,379; perl: 1,219; cpp: 761; fortran: 618; java: 568; awk: 128
file content (130 lines) | stat: -rw-r--r-- 4,850 bytes parent folder | download | duplicates (7)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
!
! Copyright (C) 2001-2003 PWSCF group
! This file is distributed under the terms of the
! GNU General Public License. See the file `License'
! in the root directory of the present distribution,
! or http://www.gnu.org/copyleft/gpl.txt .
!
!
!-----------------------------------------------------------------------
subroutine plot_io (filplot, title, nr1x, nr2x, nr3x, nr1, nr2, &
     nr3, nat, ntyp, ibrav, celldm, at, gcutm, dual, ecut, plot_num, atm, &
     ityp, zv, tau, plot, iflag)
  !-----------------------------------------------------------------------
  !
  !     iflag >0 : write header and the quantity to be plotted ("plot")
  !                to file "filplot"
  !     iflag< 0 : read everything (requires that all variables that are
  !                read are allocated with the correct dimensions!)
  !
  USE io_global,  ONLY : stdout
  USE kinds, only : DP
  implicit none
  character (len=*) :: filplot
  character (len=75) :: title
!   integer :: nr1x, nr2x, nr3x, nr1, nr2, nr3, nat, ntyp, ibrav, &
!        plot_num, ityp (nat), iflag, i
  integer :: nr1x, nr2x, nr3x, nr1, nr2, nr3, nat, ntyp, ibrav, &
       plot_num, ityp (*), iflag, i
  character (len=3) :: atm(*)
!   real(DP) :: celldm (6), gcutm, dual, ecut, zv (ntyp), tau (3, nat) &
!        , plot (nr1x * nr2x * nr3x), at(3,3)
  real(DP) :: celldm (6), gcutm, dual, ecut, zv (*), tau (3, *) &
       , plot (*), at(3,3)
  !
  integer :: iunplot, ios, ipol, na, nt, ir, ndum
  !
  if (filplot == ' ') call errore ('plot_io', 'filename missing', 1)
  !
  iunplot = 4
  if (iflag == 0 ) call errore('plot_io',&
                        ' iflag==0 not allowed, use read_io_header ',1)
  if (iflag > 0) then
     WRITE( stdout, '(5x,"Writing data to file  ",a)') TRIM(filplot)
     open (unit = iunplot, file = filplot, form = 'formatted', &
          status = 'unknown', err = 100, iostat = ios)
  else
     WRITE( stdout, '(5x,"Reading data from file  ",a)') TRIM(filplot)
     open (unit = iunplot, file = filplot, form = 'formatted', &
          status = 'old', err = 100, iostat = ios)
  endif

100 call errore ('plot_io', 'opening file '//TRIM(filplot), abs (ios) )

  rewind (iunplot)
  if (iflag > 0) then
     write (iunplot, '(a)') title
     write (iunplot, '(8i8)') nr1x, nr2x, nr3x, nr1, nr2, nr3, nat, ntyp
     write (iunplot, '(i6,2x,6f16.8)') ibrav, celldm
     if (ibrav == 0) then
        do i = 1,3
           write ( iunplot, * ) ( at(ipol,i),ipol=1,3 )
        enddo
     endif
     write (iunplot, '(3f20.10,i6)') gcutm, dual, ecut, plot_num
     write (iunplot, '(i4,3x,a2,3x,f5.2)') &
          (nt, atm (nt), zv (nt), nt=1, ntyp)
     write (iunplot, '(i4,3x,3f15.9,3x,i2)') (na, &
          (tau (ipol, na), ipol = 1, 3), ityp (na), na = 1, nat)
     write (iunplot, '(5(1pe17.9))') (plot (ir) , ir = 1, nr1x * nr2x * nr3)
  else
     read (iunplot, '(a)') title
     read (iunplot, * ) nr1x, nr2x, nr3x, nr1, nr2, nr3, nat, ntyp
     read (iunplot, * ) ibrav, celldm
     if (ibrav == 0) then
        do i = 1,3
           read ( iunplot, * ) ( at(ipol,i),ipol=1,3 )
        enddo
     endif
     read (iunplot, * ) gcutm, dual, ecut, plot_num
     read (iunplot, '(i4,3x,a2,3x,f5.2)') &
             (ndum, atm(nt), zv(nt), nt=1, ntyp)
     read (iunplot, *) (ndum,  (tau (ipol, na), ipol = 1, 3), &
             ityp(na), na = 1, nat)
     read (iunplot, * ) (plot (ir), ir = 1, nr1x * nr2x * nr3)
  endif

  close (unit = iunplot)

  return
end subroutine plot_io
!-----------------------------------------------------------------------
subroutine read_io_header(filplot, title, nr1x, nr2x, nr3x, nr1, nr2, nr3, &
                  nat, ntyp, ibrav, celldm, at, gcutm, dual, ecut, plot_num)
     
  !-----------------------------------------------------------------------
  !
  !     read header of file "filplot" 
  !
  USE io_global,  ONLY : stdout
  USE kinds, only : DP
  implicit none
  character (len=*) :: filplot
  character (len=75) :: title
  integer :: nr1x, nr2x, nr3x, nr1, nr2, nr3, nat, ntyp, ibrav, plot_num, i
  real(DP) :: celldm (6), gcutm, dual, ecut, at(3,3)
  !
  integer :: iunplot, ios, ipol
  !
  if (filplot == ' ') call errore ('read_io_h', 'filename missing', 1)
  !
  iunplot = 4
  WRITE( stdout, '(5x,"Reading header from file  ",a)') TRIM(filplot)
  open (unit = iunplot, file = filplot, form = 'formatted', &
          status = 'old', err = 100, iostat = ios)
100 call errore ('plot_io', 'opening file '//TRIM(filplot), abs (ios) )

  rewind (iunplot)
  read (iunplot, '(a)') title
  read (iunplot, * ) nr1x, nr2x, nr3x, nr1, nr2, nr3, nat, ntyp
  read (iunplot, * ) ibrav, celldm
  if (ibrav == 0) then
     do i = 1,3
        read ( iunplot, * ) ( at(ipol,i),ipol=1,3 )
     enddo
  endif
  read (iunplot, * ) gcutm, dual, ecut, plot_num
  close (unit = iunplot)

  return
end subroutine read_io_header