Reflection files format: Difference between revisions

Jump to navigation Jump to search
(Created page with "CCP4 reflection files are binary files that are usually read by routines from CCP4 libraries. However, sometimes one wants to read them with a different programming language o...")
 
 
(8 intermediate revisions by the same user not shown)
Line 197: Line 197:


The CCP4 LCF (labelled column format) files were phased-out in the early 90's but some interesting data still lingers on half-inch tapes so, if they can be read, the LCF files can be converted to ASCII or other formats for safe-keeping, or further use.  
The CCP4 LCF (labelled column format) files were phased-out in the early 90's but some interesting data still lingers on half-inch tapes so, if they can be read, the LCF files can be converted to ASCII or other formats for safe-keeping, or further use.  
Jonathan Cooper has worked out how to read them, mainly using Python, and [https://readingccp4lcffiles.blogspot.com/ documents this].
Jonathan Cooper has worked out how to read them, mainly using Python, and [https://readingccp4lcffiles.blogspot.com/ documents this]. The directory ftp://ftp.ccp4.ac.uk/lcfstuff/ has some Fortran routines.
 
A Fortran program (lcf_dump) to accomplish this is:
<pre>
! reads cell, column labels, comment, and reflection data from LCF file - Kay Diederichs 7/2019 .
! Nota bene - symmetry i.e. space group seemingly not stored in LCF file
! reading VAX format is easy with the ifort compiler since it understands VAX REAL format:
! ifort lcf_dump.f90 -o lcf_dump
IMPLICIT NONE
 
! LCF items
INTEGER(2) :: header(8),ncol
INTEGER(2), ALLOCATABLE :: refdat(:)
REAL :: cell(6)
CHARACTER :: separator*12 ! length may depend on machine that wrote LCF file
 
! program variables
INTEGER :: i
CHARACTER :: string*120
 
i=COMMAND_ARGUMENT_COUNT()
IF (i/=1) STOP 'usage: lcf_dump <name.LCF>'
! read command line
CALL GET_COMMAND_ARGUMENT(1,string)  ! expects LCF filename on command line
! OPEN(CONVERT=...) options are documented at
! https://software.intel.com/en-us/fortran-compiler-developer-guide-and-reference-open-convert-specifier
OPEN(1,FILE=string,ACCESS='STREAM',ACTION='READ',CONVERT='VAXG')
WRITE(*,*) 'LCF file: ',TRIM(string)
 
! read header and cell
READ(1) header,separator  ! reads 8*2+12 bytes. ends after byte 28
WRITE(*,'(a,8(i0,1x))') ' header: ',header
 
! the following code determines ncol according to lcflib.f line 1534ff:
IF (header(1) /= -32768) STOP 'error - first header item is not -32768'
IF (header(5) == -12) THEN
  ncol=6
ELSE IF (header(6)==-14) THEN
  ncol=7
ELSE
  ncol=-header(7)/2
  IF (ncol<0 .OR. ncol>100) STOP 'error - could not determine ncol'
END IF
WRITE(*,'(a,i0)') ' ncol: ',ncol
ALLOCATE(refdat(ncol))
 
DO i=1,6
  READ(1) cell(i),separator  ! reads 6*(4+12) bytes. ends after byte 124
END DO
WRITE(*,'(a,6f10.4)') ' cell:',cell
 
! read column labels and comment
string=''
DO i=1,(header(8)+3)/4
  READ(1)string(1+(i-1)*4:i*4),separator
END DO
WRITE(*,'(a)') TRIM(string)
 
! read reflections
READ(1) refdat(1:2) ! needed for positioning - what is their meaning?
DO
  READ(1) refdat
  IF (refdat(1)==32767) EXIT
  WRITE(*,*) refdat
END DO
 
END
</pre>
1,330

edits

Cookies help us deliver our services. By using our services, you agree to our use of cookies.

Navigation menu