dcdfort
Modern Fortran library for analyzing DCD trajectories
Data Types | Functions/Subroutines
dcdfort_reader Module Reference

Module that contains dcdreader class. More...

Data Types

type  dcdfile
 dcdwriter class More...
 

Functions/Subroutines

subroutine dcdfile_open (this, filename)
 Opens file to read from. More...
 
subroutine dcdfile_read_header (this, nframes, istart, nevery, iend, timestep, natoms)
 Reads header of open DCD file. More...
 
subroutine dcdfile_close (this)
 Closes DCD file. More...
 
subroutine dcdfile_read_next (this, xyz, box)
 Reads next frame into memory. More...
 
subroutine dcdfile_skip_next (this, n)
 Skips reading this frame into memory. More...
 

Detailed Description

Module that contains dcdreader class.

Function/Subroutine Documentation

◆ dcdfile_close()

subroutine dcdfort_reader::dcdfile_close ( class(dcdfile), intent(inout)  this)
private

Closes DCD file.

Parameters
[in,out]thisdcdreader object
190 
191  implicit none
192  class(dcdfile), intent(inout) :: this
193 
194  close(this%u)
195 

◆ dcdfile_open()

subroutine dcdfort_reader::dcdfile_open ( class(dcdfile), intent(inout)  this,
character(len=*), intent(in)  filename 
)

Opens file to read from.

Also detects if the DCD file is compatible with this library and swaps endinness if necessary.

Parameters
[in,out]thisdcdreader object
[in]filenamename of of DCD file to read from
58 
59  implicit none
60  character(len=*), parameter :: magic_string = "CORD"
61  integer(int32), parameter :: magic_number = 84
62  character(len=*), intent(in) :: filename
63  class(dcdfile), intent(inout) :: this
64  integer(kind=int32) :: line1, charmm_version, has_extra_block, four_dimensions
65  character(len=4) :: line2
66  logical :: ex
67 
68  ! Does file exist?
69  inquire(file=trim(filename), exist=ex, size=this%filesize)
70  if (ex .eqv. .false.) then
71  call error_stop_program("The specified DCD file '"//trim(filename)//"' does not exist.")
72  end if
73 
74  ! Open file in native endinness
75  open(newunit=this%u, file=trim(filename), form="unformatted", access="stream", status="old")
76 
77  ! Read in magic number of magic string
78  read(this%u,pos=1) line1
79  read(this%u) line2
80 
81  ! Ensure the magic number and string are correct, if not we'll swap the endinness
82  if (line1 .ne. magic_number .or. line2 .ne. magic_string) then
83 
84  ! Try converting to the reverse endianness
85  close(this%u)
86  open(newunit=this%u, file=trim(filename), form="unformatted", access="stream", status="old", convert="swap")
87 
88  read(this%u,pos=1) line2
89  read(this%u) line2
90 
91  ! We tried both native and reverse endiness and didn't have magic number or string
92  if (line1 .ne. magic_number .or. line2 .ne. magic_string) then
93  call error_stop_program("This DCD file format is not supported, or the file header is corrupt.")
94  end if
95 
96  end if
97 
98  ! Check if the file identifies as CHARMM (LAMMPS pretends to be CHARMM v. 24)
99  read(this%u, pos=85) charmm_version
100  if (charmm_version .eq. 0) then
101  call error_stop_program("DCD file indicates it is not CHARMM. Only CHARMM-style DCD files are supported.")
102  end if
103 
104  ! We only support files with the extra unitcell block
105  read(this%u, pos=49) has_extra_block
106  if (has_extra_block .ne. 1) then
107  call error_stop_program("DCD file indicates it does not have unit cell information. Only DCD files with&
108  & unit cell information are supported.")
109  end if
110 
111  ! We don't support files with four dimensions
112  read(this%u) four_dimensions
113  if (four_dimensions .eq. 1) then
114  call error_stop_program("DCD file indicates it has four dimensions. Only DCD files with three dimensions&
115  & are supported.")
116  end if
117 

◆ dcdfile_read_header()

subroutine dcdfort_reader::dcdfile_read_header ( class(dcdfile), intent(inout)  this,
integer(kind=int32), intent(out)  nframes,
integer(kind=int32), intent(out)  istart,
integer(kind=int32), intent(out)  nevery,
integer(kind=int32), intent(out)  iend,
real(kind=real32), intent(out)  timestep,
integer(kind=int32), intent(out)  natoms 
)
private

Reads header of open DCD file.

Should be called after open()

Parameters
[in,out]thisdcdreader object
[in]nframesrnumber of frames (snapshots) in file
[out]istartfirst timestep of trajectory file
[out]neveryhow often (in timesteps) file was written to
[out]iendlast timestep of trajectory file
[out]timesteptimestep of simulation
[out]natomsnumber of atoms in each snapshot
130 
131  implicit none
132 
133  integer(kind=int32), intent(out) :: nframes, istart, nevery, iend, natoms
134  integer(kind=int32) :: i, ntitle, n, dummy, pos
135  integer(kind=int64) :: nframes2
136  character(len=80) :: title_string
137  real(kind=real32), intent(out) :: timestep
138  class(dcdfile), intent(inout) :: this
139 
140  read(this%u, pos=9) nframes, istart, nevery, iend
141 
142  read(this%u, pos=45) timestep
143 
144  read(this%u, pos=97) ntitle
145  if (ntitle > 0) then
146  write(error_unit,'(a)') prompt//"The following titles were found:"
147  end if
148  do i = 1, ntitle
149  read(this%u) title_string
150 
151  n = 1
152  do while (n .le. 80 .and. title_string(n:n) .ne. c_null_char)
153  n = n + 1
154  end do
155 
156  write(error_unit,'(a)') prompt//" "//trim(title_string(1:n-1))
157  end do
158 
159  read(this%u) dummy, dummy
160  if (dummy .ne. 4) then
161  call error_stop_program("This DCD file format is not supported, or the file header is corrupt.")
162  end if
163 
164  ! Number of atoms in each snapshot
165  read(this%u) natoms, dummy
166  if (dummy .ne. 4) then
167  call error_stop_program("This DCD file format is not supported, or the file header is corrupt.")
168  end if
169 
170  inquire(unit=this%u, pos=pos)
171  pos = pos - 1
172 
173  ! Each frame has natoms*3 (4 bytes each) = natoms*12
174  ! plus 6 box dimensions (8 bytes each) = 48
175  ! Additionally there are 32 bytes of file information in each frame
176  this%framesize = natoms*12 + 80
177  ! Header is typically 276 bytes, but inquire gives us exact size
178  nframes2 = (this%filesize-pos)/this%framesize
179  if ( nframes2 .ne. nframes) then
180  write(error_unit,'(a,i0,a,i0,a)') prompt//"WARNING: Header indicates ", nframes, &
181  &" frames, but file size indicates ", nframes2, "."
182  nframes = int(nframes2)
183  end if
184 

◆ dcdfile_read_next()

subroutine dcdfort_reader::dcdfile_read_next ( class(dcdfile), intent(inout)  this,
real(kind=real32), dimension(:,:), intent(inout), allocatable  xyz,
real(kind=real64), dimension(6), intent(inout)  box 
)
private

Reads next frame into memory.

Parameters
[in,out]thisdcdreader object
[in,out]xyzcoordinates of all atoms in snapshot. First dimension is atom number, second dimension is x, y, or z !coordinate.
[in,out]boxdimensions of snapshot. Array containing 6 elements, ordered as A, B, C, alpha, beta, gamma. A = length of unit cell vector along x-axis; B = length of unit cell vector in xy-plane; C = length of unit cell vector in yz-plane; alpha = cosine of angle between B and C; beta = cosine of angle between A and C; gamma = cosine of angle between A and B;
211 
212  implicit none
213  real(kind=real32), allocatable, intent(inout) :: xyz(:,:)
214  real(kind=real64), intent(inout) :: box(6)
215  integer(kind=int32) :: dummy(6), nbytes, ndims, i
216  class(dcdfile), intent(inout) :: this
217 
218  nbytes = size(xyz,1)*4
219  ndims = size(xyz,2)
220 
221  if (ndims /= 3) then
222  call error_stop_program("Number of dimensions of xyz array is incorrect.")
223  end if
224 
225  read(this%u) dummy(1)
226  if (dummy(1) /= 48) then
227  call error_stop_program("Problem reading in DCD snapshot.")
228  end if
229 
230  ! A gamma B beta alpha C
231  read(this%u) box(1), box(6), box(2), box(5), box(4), box(3)
232  if (box(1) < 0 .or. box(2) < 0 .or. box(3) < 0) then
233  call error_stop_program("Problem reading in DCD snapshot box dimensions.")
234  end if
235 
236  ! 48, then no. of bytes for x coordinates, x coordinates (repeat for y and z coordinates)
237  read(this%u) dummy(1:2), xyz(:,1), dummy(3:4), xyz(:,2), dummy(5:6), xyz(:,3)
238 
239  if (dummy(1) /= 48) then
240  call error_stop_program("Problem reading in DCD snapshot coordinates.")
241  end if
242 
243  do i = 2, 6
244  if (dummy(i) /= nbytes) then
245  call error_stop_program("Number of bytes in DCD snapshot is incorrect for size of xyz array passed.")
246  end if
247  end do
248 
249  read(this%u) dummy(1)
250  if (dummy(1) .ne. nbytes) then
251  call error_stop_program("Problem reading in DCD snapshot.")
252  end if
253 

◆ dcdfile_skip_next()

subroutine dcdfort_reader::dcdfile_skip_next ( class(dcdfile), intent(inout)  this,
integer(kind=int32), intent(in), optional  n 
)
private

Skips reading this frame into memory.

Parameters
[in,out]thisdcdreader object
[in]nnumber of frames to skip
260 
261  implicit none
262  integer(kind=int32) :: dummy
263  integer(kind=int64) :: pos, newpos
264  integer(kind=int32), intent(in), optional :: n
265  class(dcdfile), intent(inout) :: this
266 
267  ! Where are we?
268  inquire(unit=this%u, pos=pos)
269 
270  ! We subtract 4 bytes so that the next read of the 4-byte integer will line things up properly for the next read
271  if (.not. present(n)) then
272  newpos = pos + this%framesize - 4
273  else
274  newpos = pos + this%framesize*n - 4
275  end if
276 
277  read(this%u, pos=newpos) dummy
278