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)

Closes DCD file.

Parameters
[in,out]thisdcdreader object
185 
186  implicit none
187  class(dcdfile), intent(inout) :: this
188 
189  close(this%u)
190 

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

◆ dcdfile_read_header()

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

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
129 
130  implicit none
131 
132  integer, intent(out) :: nframes, istart, nevery, iend, natoms
133  integer :: i, ntitle, n, framesize, nframes2, dummy
134  character (len=80) :: title_string
135  real, intent(out) :: timestep
136  class(dcdfile), intent(inout) :: this
137 
138  read(this%u, pos=9) nframes, istart, nevery, iend
139 
140  read(this%u, pos=45) timestep
141 
142  read(this%u, pos=97) ntitle
143  if (ntitle > 0) then
144  write(error_unit,'(a)') prompt//"The following titles were found:"
145  end if
146  do i = 1, ntitle
147  read(this%u) title_string
148 
149  n = 1
150  do while (n .le. 80 .and. title_string(n:n) .ne. c_null_char)
151  n = n + 1
152  end do
153 
154  write(error_unit,'(a)') prompt//" "//trim(title_string(1:n))
155  end do
156 
157  read(this%u) dummy, dummy
158  if (dummy .ne. 4) then
159  call error_stop_program("This DCD file format is not supported, or the file header is corrupt.")
160  end if
161 
162  ! Number of atoms in each snapshot
163  read(this%u) natoms, dummy
164  if (dummy .ne. 4) then
165  call error_stop_program("This DCD file format is not supported, or the file header is corrupt.")
166  end if
167 
168  ! Each frame has natoms*3 (4 bytes each) = natoms*12
169  ! plus 6 box dimensions (8 bytes each) = 48
170  ! Additionally there are 32 bytes of file information in each frame
171  this%framesize = natoms*12 + 80
172  ! Header is 276 bytes
173  nframes2 = (this%filesize-276)/this%framesize
174  if ( nframes2 .ne. nframes) then
175  write(error_unit,'(a,i0,a,i0,a)') prompt//"WARNING: Header indicates ", nframes, &
176  &" frames, but file size indicates ", nframes2, "."
177  nframes = nframes2
178  end if
179 

◆ dcdfile_read_next()

subroutine dcdfort_reader::dcdfile_read_next ( class(dcdfile), intent(inout)  this,
real, dimension(:,:), intent(inout), allocatable  xyz,
real(8), dimension(6), intent(inout)  box 
)

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;
206 
207  implicit none
208  real, allocatable, intent(inout) :: xyz(:,:)
209  real(8), intent(inout) :: box(6)
210  integer :: dummy(2)
211  class(dcdfile), intent(inout) :: this
212 
213  ! Should be 48
214  read(this%u) dummy(1)
215 
216  ! A gamma B beta alpha C
217  read(this%u) box(1), box(6), box(2), box(5), box(4), box(3)
218 
219  ! 48, then no. of bytes for x coordinates, x coordinates (repeat for y and z coordinates)
220  read(this%u) dummy, xyz(:,1), dummy, xyz(:,2), dummy, xyz(:,3)
221 
222  read(this%u) dummy(1)
223 

◆ dcdfile_skip_next()

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

Skips reading this frame into memory.

Parameters
[in,out]thisdcdreader object
[in]nnumber of frames to skip
230 
231  implicit none
232  real :: real_dummy
233  integer :: dummy, i
234  integer(8) :: pos, newpos
235  integer, intent(in), optional :: n
236  real(8) :: box_dummy(6)
237  class(dcdfile), intent(inout) :: this
238 
239  ! Where are we?
240  inquire(unit=this%u, pos=pos)
241 
242  ! We subtract 4 bytes so that the next read of the 4-byte integer will line things up properly for the next read
243  if (.not. present(n)) then
244  newpos = pos + this%framesize - 4
245  else
246  newpos = pos + this%framesize*n - 4
247  end if
248 
249  read(this%u, pos=newpos) dummy
250